Skip to content

Commit 4b5ba14

Browse files
committed
WIP
1 parent 559b7e9 commit 4b5ba14

File tree

5 files changed

+109
-34
lines changed

5 files changed

+109
-34
lines changed

compiler/lib-wasm/closure_conversion.ml

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -22,6 +22,7 @@ open Code
2222
type closure =
2323
{ functions : (Var.t * int) list
2424
; free_variables : Var.t list
25+
; mutable id : int option
2526
}
2627

2728
module SCC = Strongly_connected_components.Make (Var)
@@ -144,7 +145,8 @@ let rec traverse var_depth closures program pc depth =
144145
in
145146
List.iter
146147
~f:(fun (f, _) ->
147-
closures := Var.Map.add f { functions; free_variables } !closures)
148+
closures :=
149+
Var.Map.add f { functions; free_variables; id = None } !closures)
148150
functions;
149151
fun_lst)
150152
components

compiler/lib-wasm/closure_conversion.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -19,6 +19,7 @@
1919
type closure =
2020
{ functions : (Code.Var.t * int) list
2121
; free_variables : Code.Var.t list
22+
; mutable id : int option
2223
}
2324

2425
val f : Code.program -> Code.program * closure Code.Var.Map.t

compiler/lib-wasm/code_generation.ml

Lines changed: 65 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -46,6 +46,7 @@ type context =
4646
; types : Wasm_ast.type_field Var.Hashtbl.t
4747
; mutable closure_envs : Var.t Var.Map.t
4848
(** GC: mapping of recursive functions to their shared environment *)
49+
; closure_types : (W.value_type option list, int) Hashtbl.t
4950
; mutable apply_funs : Var.t IntMap.t
5051
; mutable cps_apply_funs : Var.t IntMap.t
5152
; mutable curry_funs : Var.t IntMap.t
@@ -71,6 +72,7 @@ let make_context ~value_type =
7172
; type_names = String.Hashtbl.create 128
7273
; types = Var.Hashtbl.create 128
7374
; closure_envs = Var.Map.empty
75+
; closure_types = Poly.Hashtbl.create 128
7476
; apply_funs = IntMap.empty
7577
; cps_apply_funs = IntMap.empty
7678
; curry_funs = IntMap.empty
@@ -499,6 +501,59 @@ let load x =
499501
| Local (_, x, _) -> return (W.LocalGet x)
500502
| Expr e -> e
501503

504+
let value_type st = st.context.value_type, st
505+
506+
let rec variable_type x st =
507+
match Var.Map.find_opt x st.vars with
508+
| Some (Local (_, _, typ)) -> typ, st
509+
| Some (Expr e) ->
510+
(let* e = e in
511+
expression_type e)
512+
st
513+
| None -> None, st
514+
515+
and expression_type (e : W.expression) st =
516+
match e with
517+
| Const _
518+
| UnOp _
519+
| BinOp _
520+
| I32WrapI64 _
521+
| I64ExtendI32 _
522+
| F32DemoteF64 _
523+
| F64PromoteF32 _
524+
| GlobalGet _
525+
| BlockExpr _
526+
| Call _
527+
| RefFunc _
528+
| Call_ref _
529+
| I31Get _
530+
| ArrayGet _
531+
| ArrayLen _
532+
| RefTest _
533+
| RefEq _
534+
| RefNull _
535+
| Try _
536+
| Br_on_null _ -> None, st
537+
| LocalGet x | LocalTee (x, _) -> variable_type x st
538+
| Seq (_, e') -> expression_type e' st
539+
| Pop typ -> Some typ, st
540+
| RefI31 _ -> Some (Ref { nullable = false; typ = I31 }), st
541+
| ArrayNew (ty, _, _)
542+
| ArrayNewFixed (ty, _)
543+
| ArrayNewData (ty, _, _, _)
544+
| StructNew (ty, _) -> Some (Ref { nullable = false; typ = Type ty }), st
545+
| StructGet (_, ty, i, _) -> (
546+
match (Var.Hashtbl.find st.context.types ty).typ with
547+
| Struct l -> (
548+
match (List.nth l i).typ with
549+
| Value typ ->
550+
(if Poly.equal typ st.context.value_type then None else Some typ), st
551+
| Packed _ -> assert false)
552+
| Array _ | Func _ -> assert false)
553+
| RefCast (typ, _) | Br_on_cast (_, _, typ, _) | Br_on_cast_fail (_, typ, _, _) ->
554+
Some (Ref typ), st
555+
| IfExpr (_, _, _, _) | ExternConvertAny _ -> None, st
556+
502557
let tee ?typ x e =
503558
let* e = e in
504559
let* b = is_small_constant e in
@@ -507,13 +562,16 @@ let tee ?typ x e =
507562
let* () = register_constant x e in
508563
return e
509564
else
565+
let* typ =
566+
match typ with
567+
| Some _ -> return typ
568+
| None -> expression_type e
569+
in
510570
let* i = add_var ?typ x in
511571
return (W.LocalTee (i, e))
512572

513573
let should_make_global x st = Var.Set.mem x st.context.globalized_variables, st
514574

515-
let value_type st = st.context.value_type, st
516-
517575
let get_constant x st = Var.Hashtbl.find_opt st.context.constants x, st
518576

519577
let placeholder_value typ f =
@@ -585,6 +643,11 @@ let rec store ?(always = false) ?typ x e =
585643
let* () = register_constant x (W.GlobalGet x) in
586644
instr (GlobalSet (x, e))
587645
else
646+
let* typ =
647+
match typ with
648+
| Some _ -> return typ
649+
| None -> if always then return None else expression_type e
650+
in
588651
let* i = add_var ?typ x in
589652
instr (LocalSet (i, e))
590653

compiler/lib-wasm/code_generation.mli

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -30,6 +30,7 @@ type context =
3030
; types : Wasm_ast.type_field Code.Var.Hashtbl.t
3131
; mutable closure_envs : Code.Var.t Code.Var.Map.t
3232
(** GC: mapping of recursive functions to their shared environment *)
33+
; closure_types : (Wasm_ast.value_type option list, int) Hashtbl.t
3334
; mutable apply_funs : Code.Var.t Stdlib.IntMap.t
3435
; mutable cps_apply_funs : Code.Var.t Stdlib.IntMap.t
3536
; mutable curry_funs : Code.Var.t Stdlib.IntMap.t
@@ -60,7 +61,7 @@ val instr : Wasm_ast.instruction -> unit t
6061

6162
val seq : unit t -> expression -> expression
6263

63-
val expression_list : ('a -> expression) -> 'a list -> Wasm_ast.expression list t
64+
val expression_list : ('a -> 'b t) -> 'a list -> 'b list t
6465

6566
module Arith : sig
6667
val const : int32 -> expression
@@ -204,6 +205,8 @@ val function_body :
204205
-> body:unit t
205206
-> (Wasm_ast.var * Wasm_ast.value_type) list * Wasm_ast.instruction list
206207

208+
val variable_type : Code.Var.t -> Wasm_ast.value_type option t
209+
207210
val array_placeholder : Code.Var.t -> expression
208211

209212
val default_value :

compiler/lib-wasm/gc_target.ml

Lines changed: 36 additions & 30 deletions
Original file line numberDiff line numberDiff line change
@@ -281,11 +281,19 @@ module Type = struct
281281
])
282282
})
283283

284-
let env_type ~cps ~arity n =
284+
let make_env_type env_type =
285+
List.map
286+
~f:(fun typ ->
287+
{ W.mut = false
288+
; typ = W.Value (Option.value ~default:(W.Ref { nullable = false; typ = Eq }) typ)
289+
})
290+
env_type
291+
292+
let env_type ~cps ~arity ~env_type_id ~env_type =
285293
register_type
286294
(if cps
287-
then Printf.sprintf "cps_env_%d_%d" arity n
288-
else Printf.sprintf "env_%d_%d" arity n)
295+
then Printf.sprintf "cps_env_%d_%d" arity env_type_id
296+
else Printf.sprintf "env_%d_%d" arity env_type_id)
289297
(fun () ->
290298
let* cl_typ = closure_type ~usage:`Alloc ~cps arity in
291299
let* common = closure_common_fields ~cps in
@@ -309,18 +317,11 @@ module Type = struct
309317
; typ = Value (Ref { nullable = false; typ = Type fun_ty' })
310318
}
311319
])
312-
@ List.init
313-
~f:(fun _ ->
314-
{ W.mut = false
315-
; typ = W.Value (Ref { nullable = false; typ = Eq })
316-
})
317-
~len:n)
320+
@ make_env_type env_type)
318321
})
319322

320-
let rec_env_type ~function_count ~free_variable_count =
321-
register_type
322-
(Printf.sprintf "rec_env_%d_%d" function_count free_variable_count)
323-
(fun () ->
323+
let rec_env_type ~function_count ~env_type_id ~env_type =
324+
register_type (Printf.sprintf "rec_env_%d_%d" function_count env_type_id) (fun () ->
324325
return
325326
{ supertype = None
326327
; final = true
@@ -331,24 +332,20 @@ module Type = struct
331332
{ W.mut = i < function_count
332333
; typ = W.Value (Ref { nullable = false; typ = Eq })
333334
})
334-
~len:(function_count + free_variable_count))
335+
~len:function_count
336+
@ make_env_type env_type)
335337
})
336338

337-
let rec_closure_type ~cps ~arity ~function_count ~free_variable_count =
339+
let rec_closure_type ~cps ~arity ~function_count ~env_type_id ~env_type =
338340
register_type
339341
(if cps
340-
then
341-
Printf.sprintf
342-
"cps_closure_rec_%d_%d_%d"
343-
arity
344-
function_count
345-
free_variable_count
346-
else Printf.sprintf "closure_rec_%d_%d_%d" arity function_count free_variable_count)
342+
then Printf.sprintf "cps_closure_rec_%d_%d_%d" arity function_count env_type_id
343+
else Printf.sprintf "closure_rec_%d_%d_%d" arity function_count env_type_id)
347344
(fun () ->
348345
let* cl_typ = closure_type ~usage:`Alloc ~cps arity in
349346
let* common = closure_common_fields ~cps in
350347
let* fun_ty' = function_type ~cps arity in
351-
let* env_ty = rec_env_type ~function_count ~free_variable_count in
348+
let* env_ty = rec_env_type ~function_count ~env_type_id ~env_type in
352349
return
353350
{ supertype = Some cl_typ
354351
; final = true
@@ -1110,11 +1107,19 @@ module Closure = struct
11101107
in
11111108
return (W.GlobalGet name)
11121109
else
1113-
let free_variable_count = List.length free_variables in
1110+
let* env_type = expression_list variable_type free_variables in
1111+
let env_type_id =
1112+
try Hashtbl.find context.closure_types env_type
1113+
with Not_found ->
1114+
let id = Hashtbl.length context.closure_types in
1115+
Hashtbl.add context.closure_types env_type id;
1116+
id
1117+
in
1118+
info.id <- Some env_type_id;
11141119
match info.Closure_conversion.functions with
11151120
| [] -> assert false
11161121
| [ _ ] ->
1117-
let* typ = Type.env_type ~cps ~arity free_variable_count in
1122+
let* typ = Type.env_type ~cps ~arity ~env_type_id ~env_type in
11181123
let* l = expression_list load free_variables in
11191124
return
11201125
(W.StructNew
@@ -1133,7 +1138,7 @@ module Closure = struct
11331138
@ l ))
11341139
| (g, _) :: _ as functions ->
11351140
let function_count = List.length functions in
1136-
let* env_typ = Type.rec_env_type ~function_count ~free_variable_count in
1141+
let* env_typ = Type.rec_env_type ~function_count ~env_type_id ~env_type in
11371142
let env =
11381143
if Code.Var.equal f g
11391144
then
@@ -1155,7 +1160,7 @@ module Closure = struct
11551160
load env
11561161
in
11571162
let* typ =
1158-
Type.rec_closure_type ~cps ~arity ~function_count ~free_variable_count
1163+
Type.rec_closure_type ~cps ~arity ~function_count ~env_type_id ~env_type
11591164
in
11601165
let res =
11611166
let* env = env in
@@ -1200,12 +1205,13 @@ module Closure = struct
12001205
let* _ = add_var (Code.Var.fresh ()) in
12011206
return ()
12021207
else
1208+
let env_type_id = Option.value ~default:(-1) info.id in
12031209
let _, arity = List.find ~f:(fun (f', _) -> Code.Var.equal f f') info.functions in
12041210
let arity = if cps then arity - 1 else arity in
12051211
let offset = Memory.env_start arity in
12061212
match info.Closure_conversion.functions with
12071213
| [ _ ] ->
1208-
let* typ = Type.env_type ~cps ~arity free_variable_count in
1214+
let* typ = Type.env_type ~cps ~arity ~env_type_id ~env_type:[] in
12091215
let* _ = add_var f in
12101216
let env = Code.Var.fresh_n "env" in
12111217
let* () =
@@ -1225,11 +1231,11 @@ module Closure = struct
12251231
| functions ->
12261232
let function_count = List.length functions in
12271233
let* typ =
1228-
Type.rec_closure_type ~cps ~arity ~function_count ~free_variable_count
1234+
Type.rec_closure_type ~cps ~arity ~function_count ~env_type_id ~env_type:[]
12291235
in
12301236
let* _ = add_var f in
12311237
let env = Code.Var.fresh_n "env" in
1232-
let* env_typ = Type.rec_env_type ~function_count ~free_variable_count in
1238+
let* env_typ = Type.rec_env_type ~function_count ~env_type_id ~env_type:[] in
12331239
let* () =
12341240
store
12351241
~typ:(W.Ref { nullable = false; typ = Type env_typ })

0 commit comments

Comments
 (0)