Skip to content

Commit 1bd51a5

Browse files
committed
Wasm: specialization of number comparisons
1 parent da2ce43 commit 1bd51a5

File tree

2 files changed

+144
-10
lines changed

2 files changed

+144
-10
lines changed

compiler/lib-wasm/generate.ml

Lines changed: 110 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -115,13 +115,6 @@ module Generate (Target : Target_sig.S) = struct
115115
; "caml_erf_float", (`Pure, [ Float ], Float)
116116
; "caml_erfc_float", (`Pure, [ Float ], Float)
117117
; "caml_float_compare", (`Pure, [ Float; Float ], Int)
118-
; "caml_greaterthan", (`Mutator, [ Value; Value ], Int)
119-
; "caml_greaterequal", (`Mutator, [ Value; Value ], Int)
120-
; "caml_lessthan", (`Mutator, [ Value; Value ], Int)
121-
; "caml_lessequal", (`Mutator, [ Value; Value ], Int)
122-
; "caml_equal", (`Mutator, [ Value; Value ], Int)
123-
; "caml_notequal", (`Mutator, [ Value; Value ], Int)
124-
; "caml_compare", (`Mutator, [ Value; Value ], Int)
125118
];
126119
h
127120

@@ -290,6 +283,39 @@ module Generate (Target : Target_sig.S) = struct
290283
(transl_prim_arg ctx ?typ:tz z)
291284
| _ -> invalid_arity name l ~expected:3)
292285

286+
let register_comparison name cmp_int cmp_boxed_int cmp_float =
287+
register_prim name `Mutator (fun ctx _ l ->
288+
match l with
289+
| [ x; y ] -> (
290+
match get_type ctx x, get_type ctx y with
291+
| Int _, Int _ -> cmp_int ctx x y
292+
| Number (Int32, _), Number (Int32, _) ->
293+
let x = transl_prim_arg ctx ~typ:(Number (Int32, Unboxed)) x in
294+
let y = transl_prim_arg ctx ~typ:(Number (Int32, Unboxed)) y in
295+
int32_bin_op cmp_boxed_int x y
296+
| Number (Nativeint, _), Number (Nativeint, _) ->
297+
let x = transl_prim_arg ctx ~typ:(Number (Nativeint, Unboxed)) x in
298+
let y = transl_prim_arg ctx ~typ:(Number (Nativeint, Unboxed)) y in
299+
nativeint_bin_op cmp_boxed_int x y
300+
| Number (Int64, _), Number (Int64, _) ->
301+
let x = transl_prim_arg ctx ~typ:(Number (Int64, Unboxed)) x in
302+
let y = transl_prim_arg ctx ~typ:(Number (Int64, Unboxed)) y in
303+
int64_bin_op cmp_boxed_int x y
304+
| Number (Float, _), Number (Float, _) ->
305+
let x = transl_prim_arg ctx ~typ:(Number (Float, Unboxed)) x in
306+
let y = transl_prim_arg ctx ~typ:(Number (Float, Unboxed)) y in
307+
float_bin_op cmp_float x y
308+
| _ ->
309+
let* f =
310+
register_import
311+
~name
312+
(Fun { W.params = [ Type.value; Type.value ]; result = [ I32 ] })
313+
in
314+
let* x = transl_prim_arg ctx x in
315+
let* y = transl_prim_arg ctx y in
316+
return (W.Call (f, [ x; y ])))
317+
| _ -> invalid_arity name l ~expected:2)
318+
293319
let () =
294320
register_bin_prim
295321
"caml_floatarray_unsafe_get"
@@ -1092,7 +1118,83 @@ module Generate (Target : Target_sig.S) = struct
10921118
~ty:(Int Normalized)
10931119
(fun i j -> Arith.((j < i) - (i < j)));
10941120
register_prim "%js_array" `Pure (fun ctx _ l ->
1095-
Memory.allocate ~tag:0 (expression_list (fun x -> transl_prim_arg ctx x) l))
1121+
Memory.allocate ~tag:0 (expression_list (fun x -> transl_prim_arg ctx x) l));
1122+
register_comparison
1123+
"caml_greaterthan"
1124+
(fun ctx x y -> translate_int_comparison ctx (fun y x -> Arith.(x < y)) x y)
1125+
(Gt S)
1126+
Gt;
1127+
register_comparison
1128+
"caml_greaterequal"
1129+
(fun ctx x y -> translate_int_comparison ctx (fun y x -> Arith.(x <= y)) x y)
1130+
(Ge S)
1131+
Ge;
1132+
register_comparison
1133+
"caml_lessthan"
1134+
(fun ctx x y -> translate_int_comparison ctx Arith.( < ) x y)
1135+
(Lt S)
1136+
Lt;
1137+
register_comparison
1138+
"caml_lessequal"
1139+
(fun ctx x y -> translate_int_comparison ctx Arith.( <= ) x y)
1140+
(Le S)
1141+
Le;
1142+
register_comparison
1143+
"caml_equal"
1144+
(fun ctx x y -> translate_int_equality ctx ~negate:false x y)
1145+
Eq
1146+
Eq;
1147+
register_comparison
1148+
"caml_notequal"
1149+
(fun ctx x y -> translate_int_equality ctx ~negate:true x y)
1150+
Ne
1151+
Ne;
1152+
register_prim "caml_compare" `Mutator (fun ctx _ l ->
1153+
match l with
1154+
| [ x; y ] -> (
1155+
match get_type ctx x, get_type ctx y with
1156+
| Int _, Int _ ->
1157+
let x' = transl_prim_arg ctx ~typ:(Int Normalized) x in
1158+
let y' = transl_prim_arg ctx ~typ:(Int Normalized) y in
1159+
Arith.((y' < x') - (x' < y'))
1160+
| Number (Int32, _), Number (Int32, _)
1161+
| Number (Nativeint, _), Number (Nativeint, _) ->
1162+
let* f =
1163+
register_import
1164+
~name:"caml_int32_compare"
1165+
(Fun { W.params = [ I32; I32 ]; result = [ I32 ] })
1166+
in
1167+
let* x' = transl_prim_arg ctx ~typ:(Number (Int32, Unboxed)) x in
1168+
let* y' = transl_prim_arg ctx ~typ:(Number (Int32, Unboxed)) y in
1169+
return (W.Call (f, [ x'; y' ]))
1170+
| Number (Int64, _), Number (Int64, _) ->
1171+
let* f =
1172+
register_import
1173+
~name:"caml_int64_compare"
1174+
(Fun { W.params = [ I64; I64 ]; result = [ I32 ] })
1175+
in
1176+
let* x' = transl_prim_arg ctx ~typ:(Number (Int64, Unboxed)) x in
1177+
let* y' = transl_prim_arg ctx ~typ:(Number (Int64, Unboxed)) y in
1178+
return (W.Call (f, [ x'; y' ]))
1179+
| Number (Float, _), Number (Float, _) ->
1180+
let* f =
1181+
register_import
1182+
~name:"caml_float_compare"
1183+
(Fun { W.params = [ F64; F64 ]; result = [ I32 ] })
1184+
in
1185+
let* x' = transl_prim_arg ctx ~typ:(Number (Float, Unboxed)) x in
1186+
let* y' = transl_prim_arg ctx ~typ:(Number (Float, Unboxed)) y in
1187+
return (W.Call (f, [ x'; y' ]))
1188+
| _ ->
1189+
let* f =
1190+
register_import
1191+
~name:"caml_compare"
1192+
(Fun { W.params = [ Type.value; Type.value ]; result = [ I32 ] })
1193+
in
1194+
let* x' = transl_prim_arg ctx x in
1195+
let* y' = transl_prim_arg ctx y in
1196+
return (W.Call (f, [ x'; y' ])))
1197+
| _ -> invalid_arity "caml_compare" l ~expected:2)
10961198

10971199
let unboxed_type ty : W.value_type option =
10981200
match ty with

compiler/lib-wasm/typing.ml

Lines changed: 34 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -590,6 +590,24 @@ let primitives_with_unboxed_parameters =
590590
];
591591
h
592592

593+
let type_specialized_primitive types name args =
594+
match name with
595+
| "caml_greaterthan"
596+
| "caml_greaterequal"
597+
| "caml_lessthan"
598+
| "caml_lessequal"
599+
| "caml_equal"
600+
| "caml_notequal"
601+
| "caml_compare" -> (
602+
match List.map ~f:(arg_type ~approx:types) args with
603+
| [ Int _; Int _ ]
604+
| [ Number (Int32, _); Number (Int32, _) ]
605+
| [ Number (Int64, _); Number (Int64, _) ]
606+
| [ Number (Nativeint, _); Number (Nativeint, _) ]
607+
| [ Number (Float, _); Number (Float, _) ] -> true
608+
| _ -> false)
609+
| _ -> false
610+
593611
let box_numbers p st types =
594612
(* We box numbers eagerly if the boxed value is ever used. *)
595613
let should_box = Var.ISet.empty () in
@@ -636,7 +654,9 @@ let box_numbers p st types =
636654
then List.iter ~f:box args
637655
| Block (tag, lst, _, _) -> if tag <> 254 then Array.iter ~f:box lst
638656
| Prim (Extern s, args) ->
639-
if not (String.Hashtbl.mem primitives_with_unboxed_parameters s)
657+
if
658+
(not (String.Hashtbl.mem primitives_with_unboxed_parameters s))
659+
|| type_specialized_primitive types s args
640660
then
641661
List.iter
642662
~f:(fun a ->
@@ -667,6 +687,12 @@ let box_numbers p st types =
667687
())
668688
()
669689

690+
let print_opt typ f e =
691+
match e with
692+
| Prim (Extern name, args) when type_specialized_primitive typ name args ->
693+
Format.fprintf f " OPT"
694+
| _ -> ()
695+
670696
type t =
671697
{ types : typ Var.Tbl.t
672698
; return_types : typ Var.Hashtbl.t
@@ -696,7 +722,13 @@ let f ~global_flow_state ~global_flow_info ~fun_info ~deadcode_sentinal p =
696722
Format.err_formatter
697723
(fun _ i ->
698724
match i with
699-
| Instr (Let (x, _)) -> Format.asprintf "{%a}" Domain.print (Var.Tbl.get types x)
725+
| Instr (Let (x, e)) ->
726+
Format.asprintf
727+
"{%a}%a"
728+
Domain.print
729+
(Var.Tbl.get types x)
730+
(print_opt types)
731+
e
700732
| _ -> "")
701733
p);
702734
let return_types = Var.Hashtbl.create 128 in

0 commit comments

Comments
 (0)