Default case of switch node in AST to keep pos
[hiphop-php.git] / hphp / hack / src / typing / typing_get_locals.ml
blobf0f9e52879ee1a0b820ebf62eea04c5630bd7503
1 (*
2 * Copyright (c) 2015, Facebook, Inc.
3 * All rights reserved.
5 * This source code is licensed under the MIT license found in the
6 * LICENSE file in the "hack" directory of this source tree.
8 *)
10 open Core_kernel
11 open Ast_defs
12 open Utils
13 module FuncTerm = Typing_func_terminality
14 module NS = Namespaces
16 (* Module calculating the locals for a statement
17 * This is useful when someone uses $x on both sides
18 * of an If statement, for example:
19 * if(true) {
20 * $x = 0;
21 * } else {
22 * $x = 1;
23 * }
26 let smap_union
27 ((nsenv : Namespace_env.env), (m1 : Pos.t SMap.t)) (m2 : Pos.t SMap.t) =
28 let m_combined = SMap.fold SMap.add m1 m2 in
29 (nsenv, m_combined)
31 let rec lvalue ((nsenv, m) as acc) (p, e) =
32 match e with
33 | Aast.List lv -> List.fold_left ~init:acc ~f:lvalue lv
34 | Aast.Lvar (_, lid) -> (nsenv, SMap.add (Local_id.to_string lid) p m)
35 | Aast.Unop (Uref, (p, Aast.Lvar (_, lid))) ->
36 (nsenv, SMap.add (Local_id.to_string lid) p m)
37 | _ -> acc
39 (* TODO It really sucks that this and Nast_terminality.Terminal are very
40 * slightly different (notably, this version is somewhat buggier). Fixing that
41 * exposes a lot of errors in www unfortunately -- we should bite the bullet on
42 * fixing switch all the way when we do that, most likely though -- see tasks
43 * #3140431 and #2813555. *)
44 let rec terminal nsenv ~in_try stl = List.iter stl (terminal_ nsenv ~in_try)
46 and terminal_ nsenv ~in_try st =
47 match snd st with
48 | Aast.Throw _ when not in_try -> raise Exit
49 | Aast.Throw _ -> ()
50 | Aast.Continue
51 | Aast.TempContinue _
52 | Aast.Expr
53 ( _,
54 ( Aast.Call (_, (_, Aast.Id (_, "assert")), _, [(_, Aast.False)], [])
55 | Aast.Call
56 (_, (_, Aast.Id (_, "invariant")), _, (_, Aast.False) :: _ :: _, [])
57 ) )
58 | Aast.Return _ ->
59 raise Exit
60 | Aast.Expr (_, Aast.Call (_, (_, Aast.Id fun_id), _, _, _)) ->
61 let (_, fun_name) = NS.elaborate_id nsenv NS.ElaborateFun fun_id in
62 FuncTerm.(raise_exit_if_terminal (get_fun fun_name))
63 | Aast.Expr
64 ( _,
65 Aast.Call
66 ( _,
67 ( _,
68 Aast.Class_const
69 ((_, Aast.CIexpr (_, Aast.Id cls_id)), (_, meth_name)) ),
72 _ ) ) ->
73 let (_, cls_name) = NS.elaborate_id nsenv NS.ElaborateClass cls_id in
74 FuncTerm.(raise_exit_if_terminal (get_static_meth cls_name meth_name))
75 | Aast.If (_, b1, b2) ->
76 (try
77 terminal nsenv ~in_try b1;
79 with Exit -> terminal nsenv ~in_try b2)
80 | Aast.Switch (_, cl) -> terminal_cl nsenv ~in_try cl
81 | Aast.Block b -> terminal nsenv ~in_try b
82 | Aast.Using u -> terminal nsenv ~in_try u.Aast.us_block
83 | Aast.Try (b, catch_l, _fb) ->
84 (* return is not allowed in finally, so we can ignore fb *)
85 terminal nsenv ~in_try:true b;
86 List.iter catch_l (terminal_catch nsenv ~in_try)
87 | Aast.Break
88 (* TODO this is terminal sometimes too, except switch, see above. *)
90 | Aast.TempBreak _
91 | Aast.Expr _
92 | Aast.Markup _
93 | Aast.Let _
94 | Aast.Do _
95 | Aast.While _
96 | Aast.For _
97 | Aast.Foreach _
98 | Aast.Def_inline _
99 | Aast.Noop
100 | Aast.Fallthrough
101 | Aast.GotoLabel _
102 | Aast.Goto _
103 | Aast.Awaitall _ ->
106 and terminal_catch nsenv ~in_try (_, _, b) = terminal nsenv ~in_try b
108 and terminal_cl nsenv ~in_try = function
109 | [] -> raise Exit
110 | Aast.Case (_, b) :: rl ->
111 (try
112 terminal nsenv ~in_try b;
113 if blockHasBreak b then
115 else
116 raise Exit
117 with Exit -> terminal_cl nsenv ~in_try rl)
118 | Aast.Default (_, b) :: rl ->
119 begin
120 try terminal nsenv ~in_try b with Exit -> terminal_cl nsenv ~in_try rl
123 and blockHasBreak = function
124 | [] -> false
125 | (_, Aast.Break) :: _ -> true
126 | x :: xs ->
127 let x' =
128 match snd x with
129 | Aast.If (_, [], []) -> false
130 | Aast.If (_, b, [])
131 | Aast.If (_, [], b) ->
132 blockHasBreak b
133 | Aast.If (_, b1, b2) -> blockHasBreak b1 && blockHasBreak b2
134 | _ -> false
136 x' || blockHasBreak xs
138 let is_terminal nsenv stl =
140 terminal nsenv ~in_try:false stl;
141 false
142 with Exit -> true
144 let rec expr acc (_, e) =
145 let expr_expr acc e1 e2 =
146 let acc = expr acc e1 in
147 let acc = expr acc e2 in
150 let field acc f =
151 match f with
152 | Aast.AFvalue e -> expr acc e
153 | Aast.AFkvalue (k, v) -> expr_expr acc k v
155 let exprs acc es = List.fold_left es ~init:acc ~f:expr in
156 match e with
157 | Aast.Binop (Eq None, lv, rv) ->
158 let acc = expr acc rv in
159 lvalue acc lv
160 | Aast.Array fields
161 | Aast.Collection (_, _, fields) ->
162 List.fold_left fields ~init:acc ~f:field
163 | Aast.Varray (_, es)
164 | Aast.List es
165 | Aast.Expr_list es
166 | Aast.String2 es ->
167 exprs acc es
168 | Aast.PrefixedString (_, e) -> expr acc e
169 | Aast.Darray (_, exprexprs) ->
170 List.fold_left exprexprs ~init:acc ~f:(fun acc (e1, e2) ->
171 expr_expr acc e1 e2)
172 | Aast.Shape fields ->
173 List.fold_left fields ~init:acc ~f:(fun acc (_, e) -> expr acc e)
174 | Aast.Clone e
175 | Aast.Await e
176 | Aast.Is (e, _)
177 | Aast.As (e, _, _)
178 | Aast.BracedExpr e
179 | Aast.ParenthesizedExpr e
180 | Aast.Cast (_, e)
181 | Aast.Unop (_, e)
182 | Aast.Class_const ((_, Aast.CIexpr e), _)
183 | Aast.Callconv (_, e)
184 | Aast.Import (_, e)
185 | Aast.Yield_from e
186 | Aast.Suspend e ->
187 expr acc e
188 | Aast.Obj_get (e1, e2, _)
189 | Aast.Binop (_, e1, e2)
190 | Aast.Pipe (_, e1, e2)
191 | Aast.Class_get ((_, Aast.CIexpr e1), Aast.CGexpr e2) ->
192 expr_expr acc e1 e2
193 | Aast.Class_get ((_, Aast.CIexpr e1), _) -> expr acc e1
194 | Aast.Class_const _
195 | Aast.Class_get _ ->
196 failwith "Unexpected Expr: Typing_get_locals expected CIexpr"
197 | Aast.Array_get (e1, oe2) ->
198 let acc = expr acc e1 in
199 let acc = Option.value_map oe2 ~default:acc ~f:(expr acc) in
201 | Aast.New ((_, Aast.CIexpr e1), _, es2, es3, _)
202 | Aast.Call (_, e1, _, es2, es3) ->
203 let acc = expr acc e1 in
204 let acc = exprs acc es2 in
205 let acc = exprs acc es3 in
207 | Aast.New _ ->
208 failwith "Unexpected Expr: Typing_get_locals expected CIexpr in New"
209 | Aast.Record ((_, Aast.CIexpr e1), _, exprexprs) ->
210 let acc = expr acc e1 in
211 List.fold_left exprexprs ~init:acc ~f:(fun acc (e1, e2) ->
212 expr_expr acc e1 e2)
213 | Aast.Record _ ->
214 failwith "Unexpected Expr: Typing_get_locals expected CIexpr in Record"
215 | Aast.Yield f -> field acc f
216 | Aast.Eif (e1, oe2, e3) ->
217 let acc = expr acc e1 in
218 let (_, acc2) = Option.value_map oe2 ~default:acc ~f:(expr acc) in
219 let (_, acc3) = expr acc e3 in
220 smap_union acc (smap_inter acc2 acc3)
221 | Aast.Xml (_, attribs, es) ->
222 let attrib acc a =
223 match a with
224 | Aast.Xhp_simple (_, e)
225 | Aast.Xhp_spread e ->
226 expr acc e
228 let acc = List.fold_left attribs ~init:acc ~f:attrib in
229 let acc = exprs acc es in
231 | Aast.Null
232 | Aast.True
233 | Aast.False
234 | Aast.Omitted
235 | Aast.Id _
236 | Aast.Yield_break
237 | Aast.Int _
238 | Aast.Float _
239 | Aast.String _
240 | Aast.Efun _
241 | Aast.Lfun _
242 | Aast.Lvar _
243 | Aast.PU_atom _
244 | Aast.PU_identifier _ ->
246 (* These are not in the original AST *)
247 | Aast.This
248 | Aast.Any
249 | Aast.ValCollection _
250 | Aast.KeyValCollection _
251 | Aast.ImmutableVar _
252 | Aast.Dollardollar _
253 | Aast.Lplaceholder _
254 | Aast.Fun_id _
255 | Aast.Method_id _
256 | Aast.Method_caller _
257 | Aast.Smethod_id _
258 | Aast.Special_func _
259 | Aast.Pair _
260 | Aast.Assert _
261 | Aast.Typename _ ->
262 failwith "Unexpected Expr: Typing_get_locals expr not found on legacy AST"
264 let rec stmt (acc : Namespace_env.env * Pos.t SMap.t) st =
265 let nsenv = fst acc in
266 match snd st with
267 | Aast.Expr e -> expr acc e
268 | Aast.Fallthrough
269 | Aast.Markup _
270 | Aast.Break
271 | Aast.TempBreak _
272 | Aast.Continue
273 | Aast.TempContinue _
274 | Aast.Throw _ ->
276 | Aast.Do (b, e) ->
277 let acc = block acc b in
278 let acc = expr acc e in
280 | Aast.While (e, _b) -> expr acc e
281 | Aast.For (e1, e2, _e3, _b) ->
282 let acc = expr acc e1 in
283 let acc = expr acc e2 in
285 | Aast.Foreach (e, as_e, _b) ->
286 let acc = expr acc e in
287 begin
288 match as_e with
289 | Aast.As_v v
290 | Aast.Await_as_v (_, v) ->
291 expr acc v
292 | Aast.As_kv (k, v)
293 | Aast.Await_as_kv (_, k, v) ->
294 let acc = expr acc k in
295 let acc = expr acc v in
298 | Aast.Return _
299 | Aast.Goto _
300 | Aast.GotoLabel _
301 | Aast.Def_inline _
302 | Aast.Noop ->
304 | Aast.Awaitall (el, b) ->
305 let acc =
306 List.fold_left ~init:acc ~f:(fun acc (_, e2) -> expr acc e2) el
308 let acc = block acc b in
310 | Aast.Let (_x, _h, e) ->
311 (* We would like to exclude scoped locals here, but gather the locals in
312 * expression *)
313 expr acc e
314 | Aast.Using u -> block acc u.Aast.us_block
315 | Aast.Block b -> block acc b
316 | Aast.If (e, b1, b2) ->
317 let acc = expr acc e in
318 let term1 = is_terminal nsenv b1 in
319 let term2 = is_terminal nsenv b2 in
320 if term1 && term2 then
322 else if term1 then
323 let (_, m2) = block (nsenv, SMap.empty) b2 in
324 smap_union acc m2
325 else if term2 then
326 let (_, m1) = block (nsenv, SMap.empty) b1 in
327 smap_union acc m1
328 else
329 let (_, m1) = block (nsenv, SMap.empty) b1 in
330 let (_, m2) = block (nsenv, SMap.empty) b2 in
331 let (m : Pos.t SMap.t) = smap_inter m1 m2 in
332 smap_union acc m
333 | Aast.Switch (e, cl) ->
334 let acc = expr acc e in
335 let cl =
336 List.filter cl ~f:(function
337 | Aast.Case (_, b)
338 | Aast.Default (_, b)
339 -> not (is_terminal nsenv b))
341 let cl = casel nsenv cl in
342 let c = smap_inter_list cl in
343 smap_union acc c
344 | Aast.Try (b, cl, _fb) ->
345 let (_, c) = block (nsenv, SMap.empty) b in
346 let cl = List.filter cl ~f:(fun (_, _, b) -> not (is_terminal nsenv b)) in
347 let lcl = List.map cl (catch nsenv) in
348 let c = smap_inter_list (c :: lcl) in
349 smap_union acc c
351 and block acc l = List.fold_left ~init:acc ~f:(fun acc st -> stmt acc st) l
353 and casel nsenv cl =
354 match cl with
355 | [] -> []
356 | Aast.Case (_, []) :: rl -> casel nsenv rl
357 | Aast.Default (_, b) :: rl
358 | Aast.Case (_, b) :: rl ->
359 let (_, b) = block (nsenv, SMap.empty) b in
360 b :: casel nsenv rl
362 and catch nsenv (_, _, b) = snd (block (nsenv, SMap.empty) b)