Skip to content

Commit 559b7e9

Browse files
committed
Make local initialization for arbitrary local values
We change the type of the local into a nullable type if we cannot use a placeholder value
1 parent 7e12ce9 commit 559b7e9

File tree

4 files changed

+136
-7
lines changed

4 files changed

+136
-7
lines changed

compiler/lib-wasm/generate.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1097,7 +1097,7 @@ module Generate (Target : Target_sig.S) = struct
10971097
| Some loc -> event loc
10981098
| None -> return ())
10991099
in
1100-
let body = post_process_function_body ~param_names ~locals body in
1100+
let locals, body = post_process_function_body ~param_names ~locals body in
11011101
W.Function
11021102
{ name =
11031103
(match name_opt with

compiler/lib-wasm/initialize_locals.ml

Lines changed: 133 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -109,6 +109,111 @@ and scan_instructions ctx l =
109109
let ctx = fork_context ctx in
110110
List.iter ~f:(fun i -> scan_instruction ctx i) l
111111

112+
let rec rewrite_expression uninitialized (e : Wasm_ast.expression) =
113+
match e with
114+
| Const _ | GlobalGet _ | Pop _ | RefFunc _ | RefNull _ -> e
115+
| UnOp (op, e') -> UnOp (op, rewrite_expression uninitialized e')
116+
| I32WrapI64 e' -> I32WrapI64 (rewrite_expression uninitialized e')
117+
| I64ExtendI32 (s, e') -> I64ExtendI32 (s, rewrite_expression uninitialized e')
118+
| F32DemoteF64 e' -> F32DemoteF64 (rewrite_expression uninitialized e')
119+
| F64PromoteF32 e' -> F64PromoteF32 (rewrite_expression uninitialized e')
120+
| RefI31 e' -> RefI31 (rewrite_expression uninitialized e')
121+
| I31Get (s, e') -> I31Get (s, rewrite_expression uninitialized e')
122+
| ArrayLen e' -> ArrayLen (rewrite_expression uninitialized e')
123+
| StructGet (s, ty, i, e') -> StructGet (s, ty, i, rewrite_expression uninitialized e')
124+
| RefCast (ty, e') -> RefCast (ty, rewrite_expression uninitialized e')
125+
| RefTest (ty, e') -> RefTest (ty, rewrite_expression uninitialized e')
126+
| Br_on_cast (i, ty, ty', e') ->
127+
Br_on_cast (i, ty, ty', rewrite_expression uninitialized e')
128+
| Br_on_cast_fail (i, ty, ty', e') ->
129+
Br_on_cast_fail (i, ty, ty', rewrite_expression uninitialized e')
130+
| Br_on_null (i, e') -> Br_on_null (i, rewrite_expression uninitialized e')
131+
| BinOp (op, e', e'') ->
132+
BinOp (op, rewrite_expression uninitialized e', rewrite_expression uninitialized e'')
133+
| ArrayNew (ty, e', e'') ->
134+
ArrayNew
135+
(ty, rewrite_expression uninitialized e', rewrite_expression uninitialized e'')
136+
| ArrayNewData (ty, i, e', e'') ->
137+
ArrayNewData
138+
(ty, i, rewrite_expression uninitialized e', rewrite_expression uninitialized e'')
139+
| ArrayGet (s, ty, e', e'') ->
140+
ArrayGet
141+
(s, ty, rewrite_expression uninitialized e', rewrite_expression uninitialized e'')
142+
| RefEq (e', e'') ->
143+
RefEq (rewrite_expression uninitialized e', rewrite_expression uninitialized e'')
144+
| LocalGet i ->
145+
if Code.Var.Hashtbl.mem uninitialized i
146+
then RefCast (Code.Var.Hashtbl.find uninitialized i, e)
147+
else e
148+
| LocalTee (i, e') ->
149+
let e = Wasm_ast.LocalTee (i, rewrite_expression uninitialized e') in
150+
if Code.Var.Hashtbl.mem uninitialized i
151+
then RefCast (Code.Var.Hashtbl.find uninitialized i, e)
152+
else e
153+
| Call_ref (f, e', l) ->
154+
Call_ref
155+
(f, rewrite_expression uninitialized e', rewrite_expressions uninitialized l)
156+
| Call (f, l) -> Call (f, rewrite_expressions uninitialized l)
157+
| ArrayNewFixed (ty, l) -> ArrayNewFixed (ty, rewrite_expressions uninitialized l)
158+
| StructNew (ty, l) -> StructNew (ty, rewrite_expressions uninitialized l)
159+
| BlockExpr (ty, l) -> BlockExpr (ty, rewrite_instructions uninitialized l)
160+
| Seq (l, e') ->
161+
Seq (rewrite_instructions uninitialized l, rewrite_expression uninitialized e')
162+
| IfExpr (ty, cond, e1, e2) ->
163+
IfExpr
164+
( ty
165+
, rewrite_expression uninitialized cond
166+
, rewrite_expression uninitialized e1
167+
, rewrite_expression uninitialized e2 )
168+
| Try (ty, body, catches) -> Try (ty, rewrite_instructions uninitialized body, catches)
169+
| ExternConvertAny e' -> ExternConvertAny (rewrite_expression uninitialized e')
170+
171+
and rewrite_expressions uninitialized l =
172+
List.map ~f:(fun e -> rewrite_expression uninitialized e) l
173+
174+
and rewrite_instruction uninitialized i =
175+
match i with
176+
| Wasm_ast.Drop e -> Wasm_ast.Drop (rewrite_expression uninitialized e)
177+
| GlobalSet (x, e) -> GlobalSet (x, rewrite_expression uninitialized e)
178+
| Br (i, Some e) -> Br (i, Some (rewrite_expression uninitialized e))
179+
| Br_if (i, e) -> Br_if (i, rewrite_expression uninitialized e)
180+
| Br_table (e, l, i) -> Br_table (rewrite_expression uninitialized e, l, i)
181+
| Throw (t, e) -> Throw (t, rewrite_expression uninitialized e)
182+
| Return (Some e) -> Return (Some (rewrite_expression uninitialized e))
183+
| Push e -> Push (rewrite_expression uninitialized e)
184+
| StructSet (ty, i, e, e') ->
185+
StructSet
186+
(ty, i, rewrite_expression uninitialized e, rewrite_expression uninitialized e')
187+
| LocalSet (i, e) -> LocalSet (i, rewrite_expression uninitialized e)
188+
| Loop (ty, l) -> Loop (ty, rewrite_instructions uninitialized l)
189+
| Block (ty, l) -> Block (ty, rewrite_instructions uninitialized l)
190+
| If (ty, e, l, l') ->
191+
If
192+
( ty
193+
, rewrite_expression uninitialized e
194+
, rewrite_instructions uninitialized l
195+
, rewrite_instructions uninitialized l' )
196+
| CallInstr (f, l) -> CallInstr (f, rewrite_expressions uninitialized l)
197+
| Return_call (f, l) -> Return_call (f, rewrite_expressions uninitialized l)
198+
| Br (_, None) | Return None | Rethrow _ | Nop | Unreachable | Event _ -> i
199+
| ArraySet (ty, e, e', e'') ->
200+
ArraySet
201+
( ty
202+
, rewrite_expression uninitialized e
203+
, rewrite_expression uninitialized e'
204+
, rewrite_expression uninitialized e'' )
205+
| Return_call_ref (f, e', l) ->
206+
Return_call_ref
207+
(f, rewrite_expression uninitialized e', rewrite_expressions uninitialized l)
208+
209+
and rewrite_instructions uninitialized l =
210+
List.map ~f:(fun i -> rewrite_instruction uninitialized i) l
211+
212+
let has_default (ty : Wasm_ast.heap_type) =
213+
match ty with
214+
| Any | Eq | I31 -> true
215+
| Func | Extern | Array | Struct | None_ | Type _ -> false
216+
112217
let f ~param_names ~locals instrs =
113218
let ctx =
114219
{ initialized = Code.Var.Set.empty; uninitialized = ref Code.Var.Set.empty }
@@ -121,7 +226,31 @@ let f ~param_names ~locals instrs =
121226
| Ref { nullable = false; _ } -> ())
122227
locals;
123228
scan_instructions ctx instrs;
124-
List.map
125-
~f:(fun i -> Wasm_ast.LocalSet (i, RefI31 (Const (I32 0l))))
126-
(Code.Var.Set.elements !(ctx.uninitialized))
127-
@ instrs
229+
let local_types = Code.Var.Hashtbl.create 16 in
230+
let locals =
231+
List.map
232+
~f:(fun ((var, typ) as local) ->
233+
match typ with
234+
| Ref ({ nullable = false; typ } as ref_typ) ->
235+
if Code.Var.Set.mem var !(ctx.uninitialized) && not (has_default typ)
236+
then (
237+
Code.Var.Hashtbl.add local_types var ref_typ;
238+
var, Wasm_ast.Ref { nullable = true; typ })
239+
else local
240+
| I32 | I64 | F32 | F64 | Ref { nullable = true; _ } -> local)
241+
locals
242+
in
243+
let initializations =
244+
List.filter_map
245+
~f:(fun i ->
246+
if Code.Var.Hashtbl.mem local_types i
247+
then None
248+
else Some (Wasm_ast.LocalSet (i, RefI31 (Const (I32 0l)))))
249+
(Code.Var.Set.elements !(ctx.uninitialized))
250+
in
251+
let instrs =
252+
if Code.Var.Hashtbl.length local_types = 0
253+
then instrs
254+
else rewrite_instructions local_types instrs
255+
in
256+
locals, initializations @ instrs

compiler/lib-wasm/initialize_locals.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -20,4 +20,4 @@ val f :
2020
param_names:Wasm_ast.var list
2121
-> locals:(Wasm_ast.var * Wasm_ast.value_type) list
2222
-> Wasm_ast.instruction list
23-
-> Wasm_ast.instruction list
23+
-> (Wasm_ast.var * Wasm_ast.value_type) list * Wasm_ast.instruction list

compiler/lib-wasm/target_sig.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -277,7 +277,7 @@ module type S = sig
277277
param_names:Wasm_ast.var list
278278
-> locals:(Wasm_ast.var * Wasm_ast.value_type) list
279279
-> Wasm_ast.instruction list
280-
-> Wasm_ast.instruction list
280+
-> (Wasm_ast.var * Wasm_ast.value_type) list * Wasm_ast.instruction list
281281

282282
val entry_point :
283283
toplevel_fun:Wasm_ast.var

0 commit comments

Comments
 (0)