~ubuntu-branches/debian/sid/ocaml/sid

« back to all changes in this revision

Viewing changes to asmcomp/i386/emit.mlp

  • Committer: Bazaar Package Importer
  • Author(s): Stefano Zacchiroli
  • Date: 2009-02-22 08:49:13 UTC
  • mfrom: (12.1.1 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090222084913-3i0uw2bhd0lgw0ok
* Uploading to unstable
* debian/control: bump dh-ocaml to (>= 0.4) to avoid buggy ocamlinit.mk

Show diffs side-by-side

added added

removed removed

Lines of Context:
10
10
(*                                                                     *)
11
11
(***********************************************************************)
12
12
 
13
 
(* $Id: emit.mlp,v 1.38.4.2 2007/10/09 13:54:27 xleroy Exp $ *)
 
13
(* $Id: emit.mlp,v 1.41.2.2 2008/11/08 16:08:09 xleroy Exp $ *)
14
14
 
15
15
(* Emission of Intel 386 assembly code *)
16
16
 
35
35
(* Layout of the stack frame *)
36
36
 
37
37
let frame_size () =                     (* includes return address *)
38
 
  let sz = 
 
38
  let sz =
39
39
    !stack_offset + 4 * num_stack_slots.(0) + 8 * num_stack_slots.(1) + 4
40
40
  in Misc.align sz stack_alignment
41
41
 
116
116
      (fun n -> `       .align  {emit_int n}\n`)
117
117
  | _ ->
118
118
      (fun n -> `       .align  {emit_int(Misc.log2 n)}\n`)
119
 
  
 
119
 
120
120
let emit_Llabel fallthrough lbl =
121
121
  if not fallthrough && !fastcode_flag then
122
122
    emit_align 16 ;
123
123
  emit_label lbl
124
 
  
 
124
 
125
125
(* Output a pseudo-register *)
126
126
 
127
127
let emit_reg = function
299
299
  | Iunsigned Ceq -> "e"   | Iunsigned Cne -> "ne"
300
300
  | Iunsigned Cle -> "be"  | Iunsigned Cgt -> "a"
301
301
  | Iunsigned Clt -> "b"  | Iunsigned Cge -> "ae"
302
 
    
 
302
 
303
303
(* Output an = 0 or <> 0 test. *)
304
304
 
305
305
let output_test_zero arg =
737
737
            `   cmpl    {emit_reg i.arg.(1)}, {emit_reg i.arg.(0)}\n`;
738
738
            let b = name_for_cond_branch cmp in
739
739
            `   j{emit_string b}        {emit_label lbl}\n`
740
 
        | Iinttest_imm((Isigned Ceq | Isigned Cne | 
 
740
        | Iinttest_imm((Isigned Ceq | Isigned Cne |
741
741
                        Iunsigned Ceq | Iunsigned Cne) as cmp, 0) ->
742
742
            output_test_zero i.arg.(0);
743
743
            let b = name_for_cond_branch cmp in
875
875
      ` popl    %eax\n`
876
876
  | _ -> () (*unsupported yet*)
877
877
 
878
 
(* Declare a global function symbol *)
879
 
 
880
 
let declare_function_symbol name =
881
 
  `     .globl  {emit_symbol name}\n`;
882
 
  match Config.system with
883
 
    "linux_elf" | "bsd_elf" | "gnu" ->
884
 
      ` .type   {emit_symbol name},@function\n`
885
 
  | _ -> ()
886
 
 
887
878
(* Emission of a function declaration *)
888
879
 
889
880
let fundecl fundecl =
897
888
  bound_error_call := 0;
898
889
  `     .text\n`;
899
890
  emit_align 16;
900
 
  declare_function_symbol fundecl.fun_name;
 
891
  `     .globl  {emit_symbol fundecl.fun_name}\n`;
901
892
  `{emit_symbol fundecl.fun_name}:\n`;
902
893
  if !Clflags.gprofile then emit_profile();
903
894
  let n = frame_size() - 4 in
907
898
  emit_all true fundecl.fun_body;
908
899
  List.iter emit_call_gc !call_gc_sites;
909
900
  emit_call_bound_errors ();
910
 
  List.iter emit_float_constant !float_constants
 
901
  List.iter emit_float_constant !float_constants;
 
902
  match Config.system with
 
903
    "linux_elf" | "bsd_elf" | "gnu" ->
 
904
      ` .type   {emit_symbol fundecl.fun_name},@function\n`;
 
905
      ` .size   {emit_symbol fundecl.fun_name},.-{emit_symbol fundecl.fun_name}\n`
 
906
  | _ -> ()
 
907
 
911
908
 
912
909
(* Emission of data *)
913
910
 
962
959
let end_assembly() =
963
960
  let lbl_end = Compilenv.make_symbol (Some "code_end") in
964
961
  `     .text\n`;
 
962
  if macosx then `      NOP\n`; (* suppress "ld warning: atom sorting error" *)
965
963
  `     .globl  {emit_symbol lbl_end}\n`;
966
964
  `{emit_symbol lbl_end}:\n`;
967
965
  `     .data\n`;
986
984
        if use_ascii_dir
987
985
        then emit_string_directive "    .ascii  " s
988
986
        else emit_bytes_directive  "    .byte   " s) };
989
 
  if macosx then emit_external_symbols ()
 
987
  if macosx then emit_external_symbols ();
 
988
  if Config.system = "linux_elf" then
 
989
    (* Mark stack as non-executable, PR#4564 *)
 
990
    `\n .section .note.GNU-stack,\"\",%progbits\n`