Dict literals
[hiphop-php.git] / hphp / hack / src / naming / nast_visitor.ml
blobeb8db718e7850c80c4b8b847a4baa375e93ca53e
1 (**
2 * Copyright (c) 2015, Facebook, Inc.
3 * All rights reserved.
5 * This source code is licensed under the BSD-style license found in the
6 * LICENSE file in the "hack" directory of this source tree. An additional grant
7 * of patent rights can be found in the PATENTS file in the same directory.
9 *)
11 (*****************************************************************************)
12 (* This module defines a visitor class on the Nast data structure.
13 * To use it you must inherit the generic object and redefine the appropriate
14 * methods.
16 (*****************************************************************************)
18 open Nast
20 (*****************************************************************************)
21 (* The signature of the visitor. *)
22 (*****************************************************************************)
24 class type ['a] nast_visitor_type = object
25 method on_block : 'a -> Nast.block -> 'a
26 method on_break : 'a -> Pos.t -> 'a
27 method on_case : 'a -> Nast.case -> 'a
28 method on_catch : 'a -> Nast.catch -> 'a
29 method on_continue : 'a -> Pos.t -> 'a
30 method on_do : 'a -> Nast.block -> Nast.expr -> 'a
31 method on_expr : 'a -> Nast.expr -> 'a
32 method on_expr_ : 'a -> Nast.expr_ -> 'a
33 method on_for :
34 'a -> Nast.expr -> Nast.expr -> Nast.expr -> Nast.block -> 'a
35 method on_foreach :
36 'a -> Nast.expr -> Nast.as_expr -> Nast.block -> 'a
37 method on_if : 'a -> Nast.expr -> Nast.block -> Nast.block -> 'a
38 method on_noop : 'a -> 'a
39 method on_fallthrough : 'a -> 'a
40 method on_return : 'a -> Pos.t -> Nast.expr option -> 'a
41 method on_static_var : 'a -> Nast.expr list -> 'a
42 method on_stmt : 'a -> Nast.stmt -> 'a
43 method on_switch : 'a -> Nast.expr -> Nast.case list -> 'a
44 method on_throw : 'a -> Nast.is_terminal -> Nast.expr -> 'a
45 method on_try : 'a -> Nast.block -> Nast.catch list -> Nast.block -> 'a
46 method on_while : 'a -> Nast.expr -> Nast.block -> 'a
47 method on_as_expr : 'a -> as_expr -> 'a
48 method on_array : 'a -> afield list -> 'a
49 method on_shape : 'a -> expr ShapeMap.t -> 'a
50 method on_valCollection : 'a -> string -> expr list -> 'a
51 method on_keyValCollection : 'a -> Nast.kvc_kind -> field list -> 'a
52 method on_this : 'a -> 'a
53 method on_id : 'a -> sid -> 'a
54 method on_lvar : 'a -> id -> 'a
55 method on_dollardollar : 'a -> id -> 'a
56 method on_fun_id : 'a -> sid -> 'a
57 method on_method_id : 'a -> expr -> pstring -> 'a
58 method on_smethod_id : 'a -> sid -> pstring -> 'a
59 method on_method_caller : 'a -> sid -> pstring -> 'a
60 method on_obj_get : 'a -> expr -> expr -> 'a
61 method on_array_get : 'a -> expr -> expr option -> 'a
62 method on_class_get : 'a -> class_id -> pstring -> 'a
63 method on_class_const : 'a -> class_id -> pstring -> 'a
64 method on_call : 'a -> call_type -> expr -> expr list -> expr list -> 'a
65 method on_true : 'a -> 'a
66 method on_false : 'a -> 'a
67 method on_int : 'a -> pstring -> 'a
68 method on_float : 'a -> pstring -> 'a
69 method on_null : 'a -> 'a
70 method on_string : 'a -> pstring -> 'a
71 method on_string2 : 'a -> expr list -> 'a
72 method on_special_func : 'a -> special_func -> 'a
73 method on_yield_break : 'a -> 'a
74 method on_yield : 'a -> afield -> 'a
75 method on_await : 'a -> expr -> 'a
76 method on_list : 'a -> expr list -> 'a
77 method on_pair : 'a -> expr -> expr -> 'a
78 method on_expr_list : 'a -> expr list -> 'a
79 method on_cast : 'a -> hint -> expr -> 'a
80 method on_unop : 'a -> Ast.uop -> expr -> 'a
81 method on_binop : 'a -> Ast.bop -> expr -> expr -> 'a
82 method on_pipe : 'a -> id -> expr -> expr -> 'a
83 method on_eif : 'a -> expr -> expr option -> expr -> 'a
84 method on_nullCoalesce : 'a -> expr -> expr -> 'a
85 method on_typename : 'a -> sid -> 'a
86 method on_instanceOf : 'a -> expr -> class_id -> 'a
87 method on_class_id : 'a -> class_id -> 'a
88 method on_new : 'a -> class_id -> expr list -> expr list -> 'a
89 method on_efun : 'a -> fun_ -> id list -> 'a
90 method on_xml : 'a -> sid -> (pstring * expr) list -> expr list -> 'a
91 method on_assert : 'a -> assert_expr -> 'a
92 method on_clone : 'a -> expr -> 'a
93 method on_field: 'a -> field -> 'a
94 method on_afield: 'a -> afield -> 'a
96 end
98 (*****************************************************************************)
99 (* The generic visitor ('a is the type of the accumulator). *)
100 (*****************************************************************************)
102 class virtual ['a] nast_visitor: ['a] nast_visitor_type = object(this)
104 method on_break acc _ = acc
105 method on_continue acc _ = acc
106 method on_noop acc = acc
107 method on_fallthrough acc = acc
109 method on_throw acc _ e =
110 let acc = this#on_expr acc e in
113 method on_return acc _ eopt =
114 match eopt with
115 | None -> acc
116 | Some e -> this#on_expr acc e
118 method on_static_var acc el = List.fold_left this#on_expr acc el
120 method on_if acc e b1 b2 =
121 let acc = this#on_expr acc e in
122 let acc = this#on_block acc b1 in
123 let acc = this#on_block acc b2 in
126 method on_do acc b e =
127 let acc = this#on_block acc b in
128 let acc = this#on_expr acc e in
131 method on_while acc e b =
132 let acc = this#on_expr acc e in
133 let acc = this#on_block acc b in
136 method on_for acc e1 e2 e3 b =
137 let acc = this#on_expr acc e1 in
138 let acc = this#on_expr acc e2 in
139 let acc = this#on_expr acc e3 in
140 let acc = this#on_block acc b in
143 method on_switch acc e cl =
144 let acc = this#on_expr acc e in
145 let acc = List.fold_left this#on_case acc cl in
148 method on_foreach acc e ae b =
149 let acc = this#on_expr acc e in
150 let acc = this#on_as_expr acc ae in
151 let acc = this#on_block acc b in
154 method on_try acc b cl fb =
155 let acc = this#on_block acc b in
156 let acc = List.fold_left this#on_catch acc cl in
157 let acc = this#on_block acc fb in
160 method on_block acc b =
161 List.fold_left this#on_stmt acc b
163 method on_case acc = function
164 | Default b ->
165 let acc = this#on_block acc b in
167 | Case (e, b) ->
168 let acc = this#on_expr acc e in
169 let acc = this#on_block acc b in
172 method on_as_expr acc = function
173 | As_v e
174 | Await_as_v (_, e) ->
175 let acc = this#on_expr acc e in
177 | As_kv (e1, e2)
178 | Await_as_kv (_, e1, e2) ->
179 let acc = this#on_expr acc e1 in
180 let acc = this#on_expr acc e2 in
183 method on_catch acc (_, _, b) = this#on_block acc b
185 method on_stmt acc = function
186 | Expr e -> this#on_expr acc e
187 | Break p -> this#on_break acc p
188 | Continue p -> this#on_continue acc p
189 | Throw (is_term, e) -> this#on_throw acc is_term e
190 | Return (p, eopt) -> this#on_return acc p eopt
191 | If (e, b1, b2) -> this#on_if acc e b1 b2
192 | Do (b, e) -> this#on_do acc b e
193 | While (e, b) -> this#on_while acc e b
194 | For (e1, e2, e3, b) -> this#on_for acc e1 e2 e3 b
195 | Switch (e, cl) -> this#on_switch acc e cl
196 | Foreach (e, ae, b) -> this#on_foreach acc e ae b
197 | Try (b, cl, fb) -> this#on_try acc b cl fb
198 | Noop -> this#on_noop acc
199 | Fallthrough -> this#on_fallthrough acc
200 | Static_var el -> this#on_static_var acc el
202 method on_expr acc (_, e) =
203 this#on_expr_ acc e
205 method on_expr_ acc e =
206 match e with
207 | Any -> acc
208 | Array afl -> this#on_array acc afl
209 | Shape sh -> this#on_shape acc sh
210 | True -> this#on_true acc
211 | False -> this#on_false acc
212 | Int n -> this#on_int acc n
213 | Float n -> this#on_float acc n
214 | Null -> this#on_null acc
215 | String s -> this#on_string acc s
216 | This -> this#on_this acc
217 | Id sid -> this#on_id acc sid
218 | Lplaceholder _pos -> acc
219 | Dollardollar id -> this#on_dollardollar acc id
220 | Lvar id -> this#on_lvar acc id
221 | Fun_id sid -> this#on_fun_id acc sid
222 | Method_id (expr, pstr) -> this#on_method_id acc expr pstr
223 | Method_caller (sid, pstr) -> this#on_method_caller acc sid pstr
224 | Smethod_id (sid, pstr) -> this#on_smethod_id acc sid pstr
225 | Yield_break -> this#on_yield_break acc
226 | Yield e -> this#on_yield acc e
227 | Await e -> this#on_await acc e
228 | List el -> this#on_list acc el
229 | Assert ae -> this#on_assert acc ae
230 | Clone e -> this#on_clone acc e
231 | Expr_list el -> this#on_expr_list acc el
232 | Special_func sf -> this#on_special_func acc sf
233 | Obj_get (e1, e2, _) -> this#on_obj_get acc e1 e2
234 | Array_get (e1, e2) -> this#on_array_get acc e1 e2
235 | Class_get (cid, id) -> this#on_class_get acc cid id
236 | Class_const (cid, id) -> this#on_class_const acc cid id
237 | Call (ct, e, el, uel) -> this#on_call acc ct e el uel
238 | String2 el -> this#on_string2 acc el
239 | Pair (e1, e2) -> this#on_pair acc e1 e2
240 | Cast (hint, e) -> this#on_cast acc hint e
241 | Unop (uop, e) -> this#on_unop acc uop e
242 | Binop (bop, e1, e2) -> this#on_binop acc bop e1 e2
243 | Pipe (id, e1, e2) -> this#on_pipe acc id e1 e2
244 | Eif (e1, e2, e3) -> this#on_eif acc e1 e2 e3
245 | NullCoalesce (e1, e2) -> this#on_nullCoalesce acc e1 e2
246 | InstanceOf (e1, e2) -> this#on_instanceOf acc e1 e2
247 | Typename n -> this#on_typename acc n
248 | New (cid, el, uel) -> this#on_new acc cid el uel
249 | Efun (f, idl) -> this#on_efun acc f idl
250 | Xml (sid, attrl, el) -> this#on_xml acc sid attrl el
251 | ValCollection (s, el) ->
252 this#on_valCollection acc s el
253 | KeyValCollection (s, fl) ->
254 this#on_keyValCollection acc s fl
256 method on_array acc afl =
257 List.fold_left this#on_afield acc afl
259 method on_shape acc sm =
260 ShapeMap.fold begin fun _ e acc ->
261 let acc = this#on_expr acc e in
263 end sm acc
265 method on_valCollection acc _ el =
266 List.fold_left this#on_expr acc el
268 method on_keyValCollection acc _ fieldl =
269 List.fold_left this#on_field acc fieldl
271 method on_this acc = acc
272 method on_id acc _ = acc
273 method on_lvar acc _ = acc
274 method on_dollardollar acc id =
275 this#on_lvar acc id
277 method on_fun_id acc _ = acc
278 method on_method_id acc _ _ = acc
279 method on_smethod_id acc _ _ = acc
280 method on_method_caller acc _ _ = acc
281 method on_typename acc _ = acc
283 method on_obj_get acc e1 e2 =
284 let acc = this#on_expr acc e1 in
285 let acc = this#on_expr acc e2 in
288 method on_array_get acc e e_opt =
289 let acc = this#on_expr acc e in
290 let acc =
291 match e_opt with
292 | None -> acc
293 | Some e -> this#on_expr acc e
297 method on_class_get acc cid _ = this#on_class_id acc cid
299 method on_class_const acc cid _ = this#on_class_id acc cid
301 method on_call acc _ e el uel =
302 let acc = this#on_expr acc e in
303 let acc = List.fold_left this#on_expr acc el in
304 let acc = List.fold_left this#on_expr acc uel in
307 method on_true acc = acc
308 method on_false acc = acc
309 method on_int acc _ = acc
310 method on_float acc _ = acc
311 method on_null acc = acc
312 method on_string acc _ = acc
314 method on_string2 acc el =
315 let acc = List.fold_left this#on_expr acc el in
318 method on_special_func acc = function
319 | Gena e
320 | Gen_array_rec e -> this#on_expr acc e
321 | Genva el -> List.fold_left this#on_expr acc el
323 method on_yield_break acc = acc
324 method on_yield acc e = this#on_afield acc e
325 method on_await acc e = this#on_expr acc e
326 method on_list acc el = List.fold_left this#on_expr acc el
328 method on_pair acc e1 e2 =
329 let acc = this#on_expr acc e1 in
330 let acc = this#on_expr acc e2 in
333 method on_expr_list acc el =
334 let acc = List.fold_left this#on_expr acc el in
337 method on_cast acc _ e = this#on_expr acc e
338 method on_unop acc _ e = this#on_expr acc e
340 method on_binop acc _ e1 e2 =
341 let acc = this#on_expr acc e1 in
342 let acc = this#on_expr acc e2 in
345 method on_pipe acc _id e1 e2 =
346 let acc = this#on_expr acc e1 in
347 let acc = this#on_expr acc e2 in
350 method on_eif acc e1 e2 e3 =
351 let acc = this#on_expr acc e1 in
352 let acc =
353 match e2 with
354 | None -> acc
355 | Some e -> this#on_expr acc e
357 let acc = this#on_expr acc e3 in
360 method on_nullCoalesce acc e1 e2 =
361 let acc = this#on_expr acc e1 in
362 let acc = this#on_expr acc e2 in
365 method on_instanceOf acc e1 e2 =
366 let acc = this#on_expr acc e1 in
367 let acc = this#on_class_id acc e2 in
370 method on_class_id acc = function
371 | CIexpr e -> this#on_expr acc e
372 | _ -> acc
374 method on_new acc cid el uel =
375 let acc = this#on_class_id acc cid in
376 let acc = List.fold_left this#on_expr acc el in
377 let acc = List.fold_left this#on_expr acc uel in
380 method on_efun acc f _ = match f.f_body with
381 | UnnamedBody _ ->
382 failwith "lambdas expected to be named in the context of the surrounding function"
383 | NamedBody { fnb_nast ; _ } -> this#on_block acc fnb_nast
385 method on_xml acc _ attrl el =
386 let acc = List.fold_left begin fun acc (_, e) ->
387 this#on_expr acc e
388 end acc attrl in
389 let acc = List.fold_left this#on_expr acc el in
392 method on_assert acc = function
393 | AE_assert e -> this#on_expr acc e
395 method on_clone acc e = this#on_expr acc e
397 method on_field acc (e1, e2) =
398 let acc = this#on_expr acc e1 in
399 let acc = this#on_expr acc e2 in
402 method on_afield acc = function
403 | AFvalue e -> this#on_expr acc e
404 | AFkvalue (e1, e2) ->
405 let acc = this#on_expr acc e1 in
406 let acc = this#on_expr acc e2 in
410 (*****************************************************************************)
411 (* Returns true if a block has a return statement. *)
412 (*****************************************************************************)
414 module HasReturn: sig
415 val block: block -> bool
416 end = struct
418 let visitor =
419 object
420 inherit [bool] nast_visitor
421 method! on_expr acc _ = acc
422 method! on_return _ _ _ = true
425 let block b = visitor#on_block false b
429 (* Used by HasBreak and HasContinue. Does not traverse nested loops, since the
430 * breaks / continues in those loops do not affect the control flow of the
431 * outermost loop. *)
433 class loop_visitor =
434 object
435 inherit [bool] nast_visitor
436 method! on_expr acc _ = acc
437 method! on_for acc _ _ _ _ = acc
438 method! on_foreach acc _ _ _ = acc
439 method! on_do acc _ _ = acc
440 method! on_while acc _ _ = acc
441 method! on_switch acc _ _ = acc
444 (*****************************************************************************)
445 (* Returns true if a block has a continue statement.
446 * It is necessary to properly handle the type of locals.
447 * When a block statement has a continue statement, the control flow graph
448 * could be interrupted. When that is the case, the types of locals has to
449 * be more conservative. Locals can have different types depending on their
450 * position in a block. In the presence of constructions that can interrupt
451 * the control flow (exceptions, continue), the type of the local becomes:
452 * "any type that the local had, regardless of its position".
454 (*****************************************************************************)
456 module HasContinue: sig
457 val block: block -> bool
458 end = struct
460 let visitor =
461 object
462 inherit loop_visitor
463 method! on_continue _ _ = true
466 let block b = visitor#on_block false b
470 (*****************************************************************************)
471 (* Returns true if a block has a continue statement.
472 * Useful for checking if a while(true) {...} loop is non-terminating.
474 (*****************************************************************************)
476 module HasBreak: sig
477 val block: block -> bool
478 end = struct
480 let visitor =
481 object
482 inherit loop_visitor
483 method! on_break _ _ = true
486 let block b = visitor#on_block false b