Skip to content

Commit ed22d34

Browse files
committed
More precise environment type
Casting to the exact type should be slightly faster since we avoid the test for i31.
1 parent db86964 commit ed22d34

File tree

8 files changed

+139
-77
lines changed

8 files changed

+139
-77
lines changed

compiler/lib-wasm/code_generation.ml

+25
Original file line numberDiff line numberDiff line change
@@ -510,6 +510,31 @@ let tee ?typ x e =
510510

511511
let should_make_global x st = Var.Set.mem x st.context.globalized_variables, st
512512

513+
let get_constant x st = Hashtbl.find_opt st.context.constants x, st
514+
515+
let placeholder_value typ f =
516+
let* c = get_constant typ in
517+
match c with
518+
| None ->
519+
let x = Var.fresh () in
520+
let* () = register_constant typ (W.GlobalGet x) in
521+
let* () =
522+
register_global
523+
~constant:true
524+
x
525+
{ mut = false; typ = Ref { nullable = false; typ = Type typ } }
526+
(f typ)
527+
in
528+
return (W.GlobalGet x)
529+
| Some c -> return c
530+
531+
let empty_struct =
532+
let* typ =
533+
register_type "empty_struct" (fun () ->
534+
return { supertype = None; final = true; typ = W.Struct [] })
535+
in
536+
placeholder_value typ (fun typ -> W.StructNew (typ, []))
537+
513538
let value_type st = st.context.value_type, st
514539

515540
let rec store ?(always = false) ?typ x e =

compiler/lib-wasm/code_generation.mli

+2
Original file line numberDiff line numberDiff line change
@@ -203,3 +203,5 @@ val function_body :
203203
-> param_names:Code.Var.t list
204204
-> body:unit t
205205
-> (Wasm_ast.var * Wasm_ast.value_type) list * Wasm_ast.instruction list
206+
207+
val empty_struct : expression

compiler/lib-wasm/curry.ml

+11-6
Original file line numberDiff line numberDiff line change
@@ -35,7 +35,12 @@ module Make (Target : Target_sig.S) = struct
3535

3636
let call ?typ ~cps ~arity closure args =
3737
let funct = Var.fresh () in
38-
let* closure = tee ?typ funct closure in
38+
let closure = tee ?typ funct closure in
39+
let* closure =
40+
match typ with
41+
| None -> Memory.cast_closure ~cps ~arity closure
42+
| Some _ -> closure
43+
in
3944
let args = args @ [ closure ] in
4045
let* ty, funct =
4146
Memory.load_function_pointer
@@ -68,7 +73,7 @@ module Make (Target : Target_sig.S) = struct
6873
let body =
6974
let* () = no_event in
7075
let* () = bind_parameters args in
71-
let* _ = add_var f in
76+
let* _ = add_var ~typ:Type.closure f in
7277
let* args' = expression_list load args in
7378
let* _f = load f in
7479
let rec loop m args closure closure_typ =
@@ -119,7 +124,7 @@ module Make (Target : Target_sig.S) = struct
119124
let body =
120125
let* () = no_event in
121126
let* _ = add_var x in
122-
let* _ = add_var f in
127+
let* _ = add_var ~typ:Type.closure f in
123128
push (Closure.curry_allocate ~cps:false ~arity m ~f:name' ~closure:f ~arg:x)
124129
in
125130
let param_names = [ x; f ] in
@@ -140,7 +145,7 @@ module Make (Target : Target_sig.S) = struct
140145
let body =
141146
let* () = no_event in
142147
let* () = bind_parameters args in
143-
let* _ = add_var f in
148+
let* _ = add_var ~typ:Type.closure f in
144149
let* args' = expression_list load args in
145150
let* _f = load f in
146151
let rec loop m args closure closure_typ =
@@ -193,7 +198,7 @@ module Make (Target : Target_sig.S) = struct
193198
let* () = no_event in
194199
let* _ = add_var x in
195200
let* _ = add_var cont in
196-
let* _ = add_var f in
201+
let* _ = add_var ~typ:Type.closure f in
197202
let* e = Closure.curry_allocate ~cps:true ~arity m ~f:name' ~closure:f ~arg:x in
198203
let* c = call ~cps:false ~arity:1 (load cont) [ e ] in
199204
instr (W.Return (Some c))
@@ -302,7 +307,7 @@ module Make (Target : Target_sig.S) = struct
302307
let body =
303308
let* () = no_event in
304309
let* () = bind_parameters l in
305-
let* _ = add_var f in
310+
let* _ = add_var ~typ:Type.closure f in
306311
let* typ, closure = Memory.load_real_closure ~cps ~arity (load f) in
307312
let* l = expression_list load l in
308313
let* e =

compiler/lib-wasm/gc_target.ml

+14-4
Original file line numberDiff line numberDiff line change
@@ -27,6 +27,8 @@ let include_closure_arity = false
2727
module Type = struct
2828
let value = W.Ref { nullable = false; typ = Eq }
2929

30+
let closure = W.Ref { nullable = false; typ = Struct }
31+
3032
let block_type =
3133
register_type "block" (fun () ->
3234
return
@@ -205,7 +207,8 @@ module Type = struct
205207
let primitive_type n =
206208
{ W.params = List.init ~len:n ~f:(fun _ -> value); result = [ value ] }
207209

208-
let func_type n = primitive_type (n + 1)
210+
let func_type n =
211+
{ W.params = List.init ~len:n ~f:(fun _ -> value) @ [ closure ]; result = [ value ] }
209212

210213
let function_type ~cps n =
211214
let n = if cps then n + 1 else n in
@@ -433,6 +436,8 @@ module Value = struct
433436
let* t = Type.block_type in
434437
return (W.ArrayNewFixed (t, []))
435438

439+
let dummy_closure = empty_struct
440+
436441
let as_block e =
437442
let* t = Type.block_type in
438443
let* e = e in
@@ -816,6 +821,11 @@ module Memory = struct
816821
then 1
817822
else (if include_closure_arity then 1 else 0) + if arity = 1 then 1 else 2
818823

824+
let cast_closure ~cps ~arity closure =
825+
let arity = if cps then arity - 1 else arity in
826+
let* ty = Type.closure_type ~usage:`Access ~cps arity in
827+
wasm_cast ty closure
828+
819829
let load_function_pointer ~cps ~arity ?(skip_cast = false) closure =
820830
let arity = if cps then arity - 1 else arity in
821831
let* ty = Type.closure_type ~usage:`Access ~cps arity in
@@ -1192,7 +1202,7 @@ module Closure = struct
11921202
if free_variable_count = 0
11931203
then
11941204
(* The closures are all constants and the environment is empty. *)
1195-
let* _ = add_var (Code.Var.fresh ()) in
1205+
let* _ = add_var ~typ:Type.closure (Code.Var.fresh ()) in
11961206
return ()
11971207
else
11981208
let arity = List.assoc f info.functions in
@@ -1201,7 +1211,7 @@ module Closure = struct
12011211
match info.Closure_conversion.functions with
12021212
| [ _ ] ->
12031213
let* typ = Type.env_type ~cps ~arity free_variable_count in
1204-
let* _ = add_var f in
1214+
let* _ = add_var ~typ:Type.closure f in
12051215
let env = Code.Var.fresh_n "env" in
12061216
let* () =
12071217
store
@@ -1222,7 +1232,7 @@ module Closure = struct
12221232
let* typ =
12231233
Type.rec_closure_type ~cps ~arity ~function_count ~free_variable_count
12241234
in
1225-
let* _ = add_var f in
1235+
let* _ = add_var ~typ:Type.closure f in
12261236
let env = Code.Var.fresh_n "env" in
12271237
let* env_typ = Type.rec_env_type ~function_count ~free_variable_count in
12281238
let* () =

compiler/lib-wasm/generate.ml

+7-2
Original file line numberDiff line numberDiff line change
@@ -192,7 +192,12 @@ module Generate (Target : Target_sig.S) = struct
192192
| [] -> (
193193
let arity = List.length args in
194194
let funct = Var.fresh () in
195-
let* closure = tee funct (load f) in
195+
let* closure =
196+
Memory.cast_closure
197+
~cps:(Var.Set.mem x ctx.in_cps)
198+
~arity
199+
(tee funct (load f))
200+
in
196201
let* ty, funct =
197202
Memory.load_function_pointer
198203
~cps:(Var.Set.mem x ctx.in_cps)
@@ -208,7 +213,7 @@ module Generate (Target : Target_sig.S) = struct
208213
(* Functions with constant closures ignore their
209214
environment. In case of partial application, we
210215
still need the closure. *)
211-
let* cl = if exact then Value.unit else return closure in
216+
let* cl = if exact then Value.dummy_closure else return closure in
212217
return (W.Call (g, List.rev (cl :: acc)))
213218
| _ -> return (W.Call_ref (ty, funct, List.rev (closure :: acc))))
214219
| x :: r ->

compiler/lib-wasm/target_sig.ml

+6
Original file line numberDiff line numberDiff line change
@@ -26,6 +26,8 @@ module type S = sig
2626
-> [ `Expr of Wasm_ast.expression | `Var of Wasm_ast.var ] list
2727
-> expression
2828

29+
val cast_closure : cps:bool -> arity:int -> expression -> expression
30+
2931
val load_function_pointer :
3032
cps:bool
3133
-> arity:int
@@ -99,6 +101,8 @@ module type S = sig
99101
module Type : sig
100102
val value : Wasm_ast.value_type
101103

104+
val closure : Wasm_ast.value_type
105+
102106
val func_type : int -> Wasm_ast.func_type
103107

104108
val primitive_type : int -> Wasm_ast.func_type
@@ -159,6 +163,8 @@ module type S = sig
159163

160164
val dummy_block : expression
161165

166+
val dummy_closure : expression
167+
162168
val as_block : expression -> expression
163169
end
164170

0 commit comments

Comments
 (0)