Suite du portage HPUX
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@894 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
131c5a2818
commit
0819dc8a4f
|
@ -69,6 +69,10 @@ let label_prefix = if hpux then "L$" else "L"
|
|||
let emit_label lbl =
|
||||
emit_string label_prefix; emit_int lbl
|
||||
|
||||
let emit_deflabel lbl =
|
||||
emit_label lbl;
|
||||
if not hpux then `:`
|
||||
|
||||
(* Output a symbol *)
|
||||
|
||||
let symbol_prefix = if hpux then "" else "_"
|
||||
|
@ -76,6 +80,10 @@ let symbol_prefix = if hpux then "" else "_"
|
|||
let emit_symbol s =
|
||||
emit_string symbol_prefix; Emitaux.emit_symbol '$' s
|
||||
|
||||
let emit_defsymbol s =
|
||||
emit_symbol s;
|
||||
if not hpux then `:`
|
||||
|
||||
(* Output a pseudo-register *)
|
||||
|
||||
let emit_reg r =
|
||||
|
@ -279,7 +287,7 @@ let record_frame live =
|
|||
{ fd_lbl = lbl;
|
||||
fd_frame_size = frame_size();
|
||||
fd_live_offset = !live_offset } :: !frame_descriptors;
|
||||
`{emit_label lbl}:\n`
|
||||
`{emit_deflabel lbl}\n`
|
||||
|
||||
let emit_frame fd =
|
||||
` {emit_string dir_word} {emit_label fd.fd_lbl} + 3\n`;
|
||||
|
@ -300,7 +308,7 @@ let emit_float_constant (lbl, cst) =
|
|||
then ` .lit\n`
|
||||
else ` .literal8\n`;
|
||||
emit_align 8;
|
||||
`{emit_label lbl}: .double {emit_string cst}\n`
|
||||
`{emit_deflabel lbl} .double {emit_string cst}\n`
|
||||
|
||||
(* Record external calls and generate stub code for these *)
|
||||
|
||||
|
@ -315,7 +323,7 @@ let stub_label symb =
|
|||
lbl
|
||||
|
||||
let emit_stub symb lbl =
|
||||
`{emit_label lbl}: ldil L\`{emit_symbol symb}, %r1\n`;
|
||||
`{emit_deflabel lbl} ldil L\`{emit_symbol symb}, %r1\n`;
|
||||
` ble,n {emit_symbol_low symb}(4, %r1)\n`
|
||||
|
||||
let emit_stubs () =
|
||||
|
@ -327,7 +335,7 @@ let emit_stubs () =
|
|||
|
||||
let emit_call s retreg =
|
||||
if hpux then begin
|
||||
` .call\n`;
|
||||
(* ` .call\n`; *)
|
||||
` bl {emit_symbol s}, {emit_string retreg}\n`;
|
||||
call_symbol s
|
||||
end else
|
||||
|
@ -530,7 +538,7 @@ let rec emit_instr i dslot =
|
|||
` ldi {emit_int n}, %r1\n`; (* in delay slot *)
|
||||
record_frame i.live;
|
||||
` addi 4, %r3, {emit_reg i.res.(0)}\n`;
|
||||
`{emit_label lbl_cont}:\n`
|
||||
`{emit_deflabel lbl_cont}\n`
|
||||
end else begin
|
||||
emit_call "caml_alloc" "%r2";
|
||||
` ldi {emit_int n}, %r1\n`; (* in delay slot *)
|
||||
|
@ -650,7 +658,7 @@ let rec emit_instr i dslot =
|
|||
` bv 0(%r2)\n`;
|
||||
` ldo {emit_int(-n)}(%r30), %r30\n` (* in delay slot *)
|
||||
| Llabel lbl ->
|
||||
`{emit_label lbl}:\n`
|
||||
`{emit_deflabel lbl}\n`
|
||||
| Lbranch lbl ->
|
||||
begin match dslot with
|
||||
None ->
|
||||
|
@ -795,7 +803,7 @@ let fundecl fundecl =
|
|||
` .code\n`;
|
||||
` .align 4\n`;
|
||||
` .export {emit_symbol fundecl.fun_name}, ENTRY, PRIV_LEV=3\n`;
|
||||
`{emit_symbol fundecl.fun_name}:\n`;
|
||||
`{emit_defsymbol fundecl.fun_name}\n`;
|
||||
` .proc\n`;
|
||||
if !contains_calls then
|
||||
` .callinfo frame={emit_int n}, calls, save_rp\n`
|
||||
|
@ -806,16 +814,16 @@ let fundecl fundecl =
|
|||
` .text\n`;
|
||||
` .align 2\n`;
|
||||
` .globl {emit_symbol fundecl.fun_name}\n`;
|
||||
`{emit_symbol fundecl.fun_name}:\n`
|
||||
`{emit_defsymbol fundecl.fun_name}\n`
|
||||
end;
|
||||
if !contains_calls then
|
||||
` stwm %r2, {emit_int n}(%r30)\n`
|
||||
else if n > 0 then
|
||||
` ldo {emit_int n}(%r30), %r30\n`;
|
||||
`{emit_label !tailrec_entry_point}:\n`;
|
||||
`{emit_deflabel !tailrec_entry_point}\n`;
|
||||
emit_all fundecl.fun_body;
|
||||
if !range_check_trap > 0 then begin
|
||||
`{emit_label !range_check_trap}:\n`;
|
||||
`{emit_deflabel !range_check_trap}\n`;
|
||||
if hpux then begin
|
||||
emit_call "array_bound_error" "%r31";
|
||||
` nop\n`
|
||||
|
@ -841,9 +849,9 @@ let emit_global s =
|
|||
let emit_item = function
|
||||
Cdefine_symbol s ->
|
||||
emit_global s;
|
||||
`{emit_symbol s}:\n`
|
||||
`{emit_defsymbol s}\n`
|
||||
| Cdefine_label lbl ->
|
||||
`{emit_label (lbl + 10000)}:\n`
|
||||
`{emit_deflabel (lbl + 10000)}\n`
|
||||
| Cint8 n ->
|
||||
` .byte {emit_int n}\n`
|
||||
| Cint16 n ->
|
||||
|
@ -901,18 +909,18 @@ let begin_assembly() =
|
|||
let lbl_begin = Compilenv.current_unit_name() ^ "_begin" in
|
||||
` .data\n`;
|
||||
emit_global lbl_begin;
|
||||
`{emit_symbol lbl_begin}:\n`
|
||||
`{emit_defsymbol lbl_begin}\n`
|
||||
|
||||
let end_assembly() =
|
||||
emit_stubs();
|
||||
if not hpux then emit_stubs();
|
||||
` .data\n`;
|
||||
let lbl_end = Compilenv.current_unit_name() ^ "_end" in
|
||||
emit_global lbl_end;
|
||||
`{emit_symbol lbl_end}:\n`;
|
||||
`{emit_defsymbol lbl_end}\n`;
|
||||
` {emit_string dir_word} 0\n`;
|
||||
let lbl = Compilenv.current_unit_name() ^ "_frametable" in
|
||||
emit_global lbl;
|
||||
`{emit_symbol lbl}:\n`;
|
||||
`{emit_defsymbol lbl}\n`;
|
||||
` {emit_string dir_word} {emit_int (List.length !frame_descriptors)}\n`;
|
||||
List.iter emit_frame !frame_descriptors;
|
||||
frame_descriptors := [];
|
||||
|
|
|
@ -315,9 +315,12 @@ let contains_calls = ref false
|
|||
(* Calling the assembler and the archiver *)
|
||||
|
||||
let assemble_file infile outfile =
|
||||
Sys.command ("/bin/as -o " ^ outfile ^ " " ^ infile)
|
||||
Sys.command ("as -o " ^ outfile ^ " " ^ infile)
|
||||
|
||||
let create_archive archive file_list =
|
||||
Misc.remove_file archive;
|
||||
Sys.command ("ar rc " ^ archive ^ " " ^ String.concat " " file_list ^
|
||||
" && ranlib " ^ archive)
|
||||
if Config.system = "hpux" then
|
||||
Sys.command ("ar rc " ^ archive ^ " " ^ String.concat " " file_list)
|
||||
else
|
||||
Sys.command ("ar rc " ^ archive ^ " " ^ String.concat " " file_list ^
|
||||
" && ranlib " ^ archive)
|
||||
|
|
Loading…
Reference in New Issue