Rename NO -> NONE.

git-svn-id: http://caml.inria.fr/svn/ocaml/branches/abstract_intel_emit@15354 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Alain Frisch 2014-09-26 16:11:54 +00:00
parent 2aca1bc091
commit d4affdb259
6 changed files with 20 additions and 20 deletions

View File

@ -123,7 +123,7 @@ let load_symbol_addr s arg =
if !Clflags.dlcode && not windows then
I.movq (from_rip QWORD (emit_symbol s ^ "@GOTPCREL"), arg)
else if !pic_code then
I.leaq (from_rip NO (emit_symbol s), arg)
I.leaq (from_rip NONE (emit_symbol s), arg)
else
I.movq (sym (emit_symbol s), arg)
@ -446,7 +446,7 @@ let emit_instr fallthrough i =
I.xorpd (res i 0, res i 0)
| _ ->
let lbl = add_float_constant f in
I.movsd (from_rip NO (emit_label lbl), res i 0)
I.movsd (from_rip NONE (emit_label lbl), res i 0)
end
| Lop(Iconst_symbol s) ->
add_used_symbol s;
@ -547,7 +547,7 @@ let emit_instr fallthrough i =
let lbl_call_gc = new_label() in
let lbl_frame = record_frame_label i.live Debuginfo.none in
I.jb (label lbl_call_gc);
I.leaq (mem_ptr NO 8 R15, res i 0);
I.leaq (mem_ptr NONE 8 R15, res i 0);
call_gc_sites :=
{ gc_lbl = lbl_call_gc;
gc_return_lbl = lbl_redo;
@ -562,7 +562,7 @@ let emit_instr fallthrough i =
emit_call "caml_allocN"
end;
record_frame i.live Debuginfo.none;
I.leaq (mem_ptr NO 8 R15, res i 0)
I.leaq (mem_ptr NONE 8 R15, res i 0)
end
| Lop(Iintop(Icomp cmp)) ->
I.cmpq (arg i 1, arg i 0);
@ -592,7 +592,7 @@ let emit_instr fallthrough i =
(* We have i.arg.(0) = i.res.(0) *)
instr_for_intop op (arg i 1, res i 0)
| Lop(Iintop_imm(Iadd, n)) when i.arg.(0).loc <> i.res.(0).loc ->
I.leaq (mem_ptr NO n (arg64 i 0), res i 0)
I.leaq (mem_ptr NONE n (arg64 i 0), res i 0)
| Lop(Iintop_imm(Iadd, 1) | Iintop_imm(Isub, -1)) ->
I.incq (res i 0)
| Lop(Iintop_imm(Iadd, -1) | Iintop_imm(Isub, 1)) ->
@ -611,7 +611,7 @@ let emit_instr fallthrough i =
| Lop(Iintoffloat) ->
I.cvttsd2si (arg i 0, res i 0)
| Lop(Ispecific(Ilea addr)) ->
I.leaq (addressing addr NO i 0, res i 0)
I.leaq (addressing addr NONE i 0, res i 0)
| Lop(Ispecific(Istore_int(n, addr, _))) ->
I.movq (emit_nat n, addressing addr QWORD i 0)
| Lop(Ispecific(Istore_symbol(s, addr, _))) ->
@ -700,7 +700,7 @@ let emit_instr fallthrough i =
then (phys_reg 4 (*rdx*), phys_reg 0 (*rax*))
else (phys_reg 0 (*rax*), phys_reg 4 (*rdx*)) in
I.leaq (from_rip NO lbl, reg tmp1);
I.leaq (from_rip NONE lbl, reg tmp1);
I.movslq (mem_ptr DWORD 0 (arg64 i 0) ~scale:4 ~base:(reg64 tmp1), reg tmp2);
I.addq (reg tmp2, reg tmp1);
I.jmp (reg tmp1);

View File

@ -615,7 +615,7 @@ let emit_instr fallthrough i =
let lbl_call_gc = new_label() in
let lbl_frame = record_frame_label i.live Debuginfo.none in
I.jb (label lbl_call_gc);
I.leal (mem_ptr NO 4 EAX, reg i.res.(0));
I.leal (mem_ptr NONE 4 EAX, reg i.res.(0));
call_gc_sites :=
{ gc_lbl = lbl_call_gc;
gc_return_lbl = lbl_redo;
@ -630,7 +630,7 @@ let emit_instr fallthrough i =
emit_call "caml_allocN"
end;
record_frame i.live Debuginfo.none;
I.leal (mem_ptr NO 4 EAX, reg i.res.(0))
I.leal (mem_ptr NONE 4 EAX, reg i.res.(0))
end
| Lop(Iintop(Icomp cmp)) ->
I.cmpl (reg i.arg.(1), reg i.arg.(0));
@ -660,7 +660,7 @@ let emit_instr fallthrough i =
(* We have i.arg.(0) = i.res.(0) *)
instr_for_intop op (reg i.arg.(1), reg i.res.(0))
| Lop(Iintop_imm(Iadd, n)) when i.arg.(0).loc <> i.res.(0).loc ->
I.leal (mem_ptr NO n (reg32 i.arg.(0)), reg i.res.(0))
I.leal (mem_ptr NONE n (reg32 i.arg.(0)), reg i.res.(0))
| Lop(Iintop_imm(Iadd, 1) | Iintop_imm(Isub, -1)) ->
I.incl (reg i.res.(0))
| Lop(Iintop_imm(Iadd, -1) | Iintop_imm(Isub, 1)) ->
@ -704,11 +704,11 @@ let emit_instr fallthrough i =
stack_offset := !stack_offset - 8;
I.subl (int 8, esp);
cfi_adjust_cfa_offset 8;
I.fnstcw (mem_ptr NO 4 ESP);
I.fnstcw (mem_ptr NONE 4 ESP);
I.movw (mem_ptr WORD 4 ESP, ax);
I.movb (int 12, ah);
I.movw (ax, mem_ptr WORD 0 ESP);
I.fldcw (mem_ptr NO 0 ESP);
I.fldcw (mem_ptr NONE 0 ESP);
begin match i.res.(0).loc with
| Stack _ ->
I.fistpl (reg i.res.(0))
@ -716,7 +716,7 @@ let emit_instr fallthrough i =
I.fistpl (mem_ptr DWORD 0 ESP);
I.movl (mem_ptr DWORD 0 ESP, reg i.res.(0))
end;
I.fldcw (mem_ptr NO 4 ESP);
I.fldcw (mem_ptr NONE 4 ESP);
I.addl (int 8, esp);
cfi_adjust_cfa_offset (-8);
stack_offset := !stack_offset + 8
@ -837,7 +837,7 @@ let emit_instr fallthrough i =
end
| Lswitch jumptbl ->
let lbl = new_label() in
I.jmp (mem_ptr NO 0 (reg32 i.arg.(0)) ~scale:4 ~sym:(emit_label lbl));
I.jmp (mem_ptr NONE 0 (reg32 i.arg.(0)) ~scale:4 ~sym:(emit_label lbl));
_data ();
_label (emit_label lbl);
for i = 0 to Array.length jumptbl - 1 do

View File

@ -43,7 +43,7 @@ type constant =
to infer the instruction suffix. *)
type data_type =
| NO
| NONE
| REAL4 | REAL8 (* floating point values *)
| BYTE | WORD | DWORD | QWORD | OWORD (* integer values *)
| NEAR | PROC

View File

@ -87,7 +87,7 @@ module DSL = struct
let _model name = directive (Model name)
let _global s = directive (Global s)
let _align n = directive (Align (false, n))
let _llabel s = directive (NewLabel (s, NO)) (* local label *)
let _llabel s = directive (NewLabel (s, NONE)) (* local label *)
let _comment s = directive (Comment s)
let _extrn s ptr = directive (External (s, ptr))
let _private_extern s = directive (Private_extern s)

View File

@ -74,7 +74,7 @@ let suf = function
| Mem32 {typ=REAL8; _} | Mem64 {typ=REAL8; _} -> "l"
| Mem32 {typ=QWORD; _} | Mem64 {typ=QWORD; _} | Reg64 _ -> "q"
| Mem32 {typ=REAL4; _} | Mem64 {typ=REAL4; _} -> "s"
| Mem32 {typ=NO; _} | Mem64 {typ=NO; _} -> assert false
| Mem32 {typ=NONE; _} | Mem64 {typ=NONE; _} -> assert false
| _ -> ""
let i0 b s = bprintf b "\t%s" s

View File

@ -18,7 +18,7 @@ let bprintf = Printf.bprintf
let string_of_datatype = function
| QWORD -> "QWORD"
| OWORD -> "OWORD"
| NO -> assert false
| NONE -> assert false
| REAL4 -> "REAL4"
| REAL8 -> "REAL8"
| BYTE -> "BYTE"
@ -31,7 +31,7 @@ let string_of_datatype = function
let string_of_datatype_ptr = function
| QWORD -> "QWORD PTR "
| OWORD -> "OWORD PTR "
| NO -> ""
| NONE -> ""
| REAL4 -> "REAL4 PTR "
| REAL8 -> "REAL8 PTR "
| BYTE -> "BYTE PTR "
@ -231,7 +231,7 @@ let print_line b = function
| End -> bprintf b "END"
| Global s -> bprintf b "\tPUBLIC\t%s" s
| Long n -> bprintf b "\tDWORD\t%a" cst n
| NewLabel (s, NO) -> bprintf b "%s:" s
| NewLabel (s, NONE) -> bprintf b "%s:" s
| NewLabel (s, ptr) -> bprintf b "%s LABEL %s" s (string_of_datatype ptr)
| Quad n -> bprintf b "\tQWORD\t%a" cst n
| Section ([".data"], None, []) -> bprintf b "\t.DATA"