summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorAlain Frisch <alain@frisch.fr>2014-09-11 12:21:07 +0000
committerAlain Frisch <alain@frisch.fr>2014-09-11 12:21:07 +0000
commit90d828792df8264110e79d56f481dcf3fe807d78 (patch)
tree9a1369a599a9a19e0a8f10a2dc661efe1426d36e
parentca45ce13caf540dc28a2fd7008074e4797e2110b (diff)
Cleanup unary float operators.
git-svn-id: http://caml.inria.fr/svn/ocaml/branches/abstract_intel_emit@15214 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--asmcomp/i386/emit.mlp27
-rw-r--r--asmcomp/intel_dsl.ml4
2 files changed, 17 insertions, 14 deletions
diff --git a/asmcomp/i386/emit.mlp b/asmcomp/i386/emit.mlp
index 2b1543b26..2e55c2be9 100644
--- a/asmcomp/i386/emit.mlp
+++ b/asmcomp/i386/emit.mlp
@@ -296,9 +296,12 @@ let instr_for_intop = function
| Iasr -> I.sarl
| _ -> fatal_error "Emit_i386: instr_for_intop"
+let unary_instr_for_floatop = function
+ | Inegf -> I.fchs ()
+ | Iabsf -> I.fabs ()
+ | _ -> fatal_error "Emit_i386: unary_instr_for_floatop"
+
let instr_for_floatop = function
- Inegf -> I.fchs
- | Iabsf -> I.fabs
| Iaddf -> I.faddl
| Isubf -> I.fsubl
| Imulf -> I.fmull
@@ -308,7 +311,7 @@ let instr_for_floatop = function
| _ -> fatal_error "Emit_i386: instr_for_floatop"
let instr_for_floatop_reversed = function
- Iaddf -> I.faddl
+ | Iaddf -> I.faddl
| Isubf -> I.fsubrl
| Imulf -> I.fmull
| Idivf -> I.fdivrl
@@ -317,7 +320,7 @@ let instr_for_floatop_reversed = function
| _ -> fatal_error "Emit_i386: instr_for_floatop_reversed"
let instr_for_floatop_pop = function
- Iaddf -> I.faddp
+ | Iaddf -> I.faddp
| Isubf -> I.fsubp
| Imulf -> I.fmulp
| Idivf -> I.fdivp
@@ -326,7 +329,7 @@ let instr_for_floatop_pop = function
| _ -> fatal_error "Emit_i386: instr_for_floatop_pop"
let instr_for_floatarithmem double = function
- Ifloatadd -> if double then I.faddl else I.fadds
+ | Ifloatadd -> if double then I.faddl else I.fadds
| Ifloatsub -> if double then I.fsubl else I.fsubs
| Ifloatsubrev -> if double then I.fsubrl else I.fsubrs
| Ifloatmul -> if double then I.fmull else I.fmuls
@@ -334,12 +337,12 @@ let instr_for_floatarithmem double = function
| Ifloatdivrev -> if double then I.fdivrl else I.fdivrs
let name_for_cond_branch = function
- Isigned Ceq -> E | Isigned Cne -> NE
- | Isigned Cle -> LE | Isigned Cgt -> G
- | Isigned Clt -> L | Isigned Cge -> GE
+ | Isigned Ceq -> E | Isigned Cne -> NE
+ | Isigned Cle -> LE | Isigned Cgt -> G
+ | Isigned Clt -> L | Isigned Cge -> GE
| Iunsigned Ceq -> E | Iunsigned Cne -> NE
| Iunsigned Cle -> BE | Iunsigned Cgt -> A
- | Iunsigned Clt -> B | Iunsigned Cge -> AE
+ | Iunsigned Clt -> B | Iunsigned Cge -> AE
(* Output an = 0 or <> 0 test. *)
@@ -518,11 +521,11 @@ let emit_instr fallthrough i =
| 0x0000_0000_0000_0000L -> (* +0.0 *)
I.fldz ()
| 0x8000_0000_0000_0000L -> (* -0.0 *)
- I.fldz (); I.fchs None
+ I.fldz (); I.fchs ()
| 0x3FF0_0000_0000_0000L -> (* 1.0 *)
I.fld1 ()
| 0xBFF0_0000_0000_0000L -> (* -1.0 *)
- I.fld1 (); I.fchs None
+ I.fld1 (); I.fchs ()
| _ ->
let lbl = add_float_constant f in
I.fldl (_mem_sym (emit_label lbl))
@@ -688,7 +691,7 @@ let emit_instr fallthrough i =
| Lop(Inegf | Iabsf as floatop) ->
if not (is_tos i.arg.(0)) then
I.fldl (emit_reg i.arg.(0));
- instr_for_floatop floatop None
+ unary_instr_for_floatop floatop
| Lop(Iaddf | Isubf | Imulf | Idivf | Ispecific(Isubfrev | Idivfrev)
as floatop) ->
begin match (is_tos i.arg.(0), is_tos i.arg.(1)) with
diff --git a/asmcomp/intel_dsl.ml b/asmcomp/intel_dsl.ml
index ec43fb5ed..5b47bbd8e 100644
--- a/asmcomp/intel_dsl.ml
+++ b/asmcomp/intel_dsl.ml
@@ -251,8 +251,8 @@ module INS32 = struct
let fistpl arg = emit (FISTP (force_dword "fistpl" arg))
let fildl arg = emit (FILD (force_dword "fildl" arg))
- let fchs = function None -> emit FCHS | Some _ -> assert false
- let fabs = function None -> emit FABS | Some _ -> assert false
+ let fchs () = emit FCHS
+ let fabs () = emit FABS
let fadds, faddl = force_fxxx "fadd" (fun arg -> FADD arg)
let fsubs, fsubl = force_fxxx "fsub" (fun arg -> FSUB arg)