filters.ml 34 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131
  1. (*
  2. The Haxe Compiler
  3. Copyright (C) 2005-2016 Haxe Foundation
  4. This program is free software; you can redistribute it and/or
  5. modify it under the terms of the GNU General Public License
  6. as published by the Free Software Foundation; either version 2
  7. of the License, or (at your option) any later version.
  8. This program is distributed in the hope that it will be useful,
  9. but WITHOUT ANY WARRANTY; without even the implied warranty of
  10. MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
  11. GNU General Public License for more details.
  12. You should have received a copy of the GNU General Public License
  13. along with this program; if not, write to the Free Software
  14. Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.
  15. *)
  16. open Ast
  17. open Common
  18. open Type
  19. open Typecore
  20. (* PASS 1 begin *)
  21. (* Adds final returns to functions as required by some platforms *)
  22. let rec add_final_return e =
  23. let rec loop e t =
  24. let def_return p =
  25. let c = (match follow t with
  26. | TAbstract ({ a_path = [],"Int" },_) -> TInt 0l
  27. | TAbstract ({ a_path = [],"Float" },_) -> TFloat "0."
  28. | TAbstract ({ a_path = [],"Bool" },_) -> TBool false
  29. | _ -> TNull
  30. ) in
  31. { eexpr = TReturn (Some { eexpr = TConst c; epos = p; etype = t }); etype = t_dynamic; epos = p }
  32. in
  33. match e.eexpr with
  34. | TBlock el ->
  35. (match List.rev el with
  36. | [] -> e
  37. | elast :: el ->
  38. match loop elast t with
  39. | { eexpr = TBlock el2 } -> { e with eexpr = TBlock ((List.rev el) @ el2) }
  40. | elast -> { e with eexpr = TBlock (List.rev (elast :: el)) })
  41. | TReturn _ ->
  42. e
  43. | _ ->
  44. { e with eexpr = TBlock [e;def_return e.epos] }
  45. in
  46. let e = Type.map_expr add_final_return e in
  47. match e.eexpr with
  48. | TFunction f ->
  49. let f = (match follow f.tf_type with
  50. | TAbstract ({ a_path = [],"Void" },[]) -> f
  51. | _ -> { f with tf_expr = loop f.tf_expr f.tf_type }
  52. ) in
  53. { e with eexpr = TFunction f }
  54. | _ -> e
  55. let rec wrap_js_exceptions com e =
  56. let rec is_error t =
  57. match follow t with
  58. | TInst ({cl_path = (["js"],"Error")},_) -> true
  59. | TInst ({cl_super = Some (csup,tl)}, _) -> is_error (TInst (csup,tl))
  60. | _ -> false
  61. in
  62. let rec loop e =
  63. match e.eexpr with
  64. | TThrow eerr when not (is_error eerr.etype) ->
  65. let terr = List.find (fun mt -> match mt with TClassDecl {cl_path = ["js";"_Boot"],"HaxeError"} -> true | _ -> false) com.types in
  66. let cerr = match terr with TClassDecl c -> c | _ -> assert false in
  67. (match eerr.etype with
  68. | TDynamic _ ->
  69. let eterr = Codegen.ExprBuilder.make_static_this cerr e.epos in
  70. let ewrap = Codegen.fcall eterr "wrap" [eerr] t_dynamic e.epos in
  71. { e with eexpr = TThrow ewrap }
  72. | _ ->
  73. let ewrap = { eerr with eexpr = TNew (cerr,[],[eerr]) } in
  74. { e with eexpr = TThrow ewrap }
  75. )
  76. | _ ->
  77. Type.map_expr loop e
  78. in
  79. loop e
  80. (* -------------------------------------------------------------------------- *)
  81. (* CHECK LOCAL VARS INIT *)
  82. let check_local_vars_init e =
  83. let intersect vl1 vl2 =
  84. PMap.mapi (fun v t -> t && PMap.find v vl2) vl1
  85. in
  86. let join vars cvars =
  87. List.iter (fun v -> vars := intersect !vars v) cvars
  88. in
  89. let restore vars old_vars declared =
  90. (* restore variables declared in this block to their previous state *)
  91. vars := List.fold_left (fun acc v ->
  92. try PMap.add v (PMap.find v old_vars) acc with Not_found -> PMap.remove v acc
  93. ) !vars declared;
  94. in
  95. let declared = ref [] in
  96. let outside_vars = ref IntMap.empty in
  97. let rec loop vars e =
  98. match e.eexpr with
  99. | TLocal v ->
  100. let init = (try PMap.find v.v_id !vars with Not_found -> true) in
  101. if not init && not (IntMap.mem v.v_id !outside_vars) then begin
  102. if v.v_name = "this" then error "Missing this = value" e.epos
  103. else error ("Local variable " ^ v.v_name ^ " used without being initialized") e.epos
  104. end
  105. | TVar (v,eo) ->
  106. begin
  107. match eo with
  108. | None ->
  109. declared := v.v_id :: !declared;
  110. vars := PMap.add v.v_id false !vars
  111. | Some e ->
  112. loop vars e
  113. end
  114. | TBlock el ->
  115. let old = !declared in
  116. let old_vars = !vars in
  117. declared := [];
  118. List.iter (loop vars) el;
  119. restore vars old_vars (List.rev !declared);
  120. declared := old;
  121. | TBinop (OpAssign,{ eexpr = TLocal v },e) when PMap.mem v.v_id !vars ->
  122. loop vars e;
  123. vars := PMap.add v.v_id true !vars
  124. | TIf (e1,e2,eo) ->
  125. loop vars e1;
  126. let vbase = !vars in
  127. loop vars e2;
  128. (match eo with
  129. | None -> vars := vbase
  130. (* ignore else false cases (they are added by the side-effect handler) *)
  131. | Some {eexpr = TConst (TBool(false))} -> ()
  132. | Some e ->
  133. let v1 = !vars in
  134. vars := vbase;
  135. loop vars e;
  136. vars := intersect !vars v1)
  137. | TWhile (cond,e,flag) ->
  138. (match flag with
  139. | NormalWhile when (match cond.eexpr with TParenthesis {eexpr = TConst (TBool true)} -> false | _ -> true) ->
  140. loop vars cond;
  141. let old = !vars in
  142. loop vars e;
  143. vars := old;
  144. | _ ->
  145. loop vars e;
  146. loop vars cond)
  147. | TTry (e,catches) ->
  148. let cvars = List.map (fun (v,e) ->
  149. let old = !vars in
  150. loop vars e;
  151. let v = !vars in
  152. vars := old;
  153. v
  154. ) catches in
  155. loop vars e;
  156. join vars cvars;
  157. | TSwitch (e,cases,def) ->
  158. loop vars e;
  159. let cvars = List.map (fun (ec,e) ->
  160. let old = !vars in
  161. List.iter (loop vars) ec;
  162. vars := old;
  163. loop vars e;
  164. let v = !vars in
  165. vars := old;
  166. v
  167. ) cases in
  168. (match def with
  169. | None when (match e.eexpr with TMeta((Meta.Exhaustive,_,_),_) | TParenthesis({eexpr = TMeta((Meta.Exhaustive,_,_),_)}) -> true | _ -> false) ->
  170. (match cvars with
  171. | cv :: cvars ->
  172. PMap.iter (fun i b -> if b then vars := PMap.add i b !vars) cv;
  173. join vars cvars
  174. | [] -> ())
  175. | None -> ()
  176. | Some e ->
  177. loop vars e;
  178. join vars cvars)
  179. (* mark all reachable vars as initialized, since we don't exit the block *)
  180. | TBreak | TContinue | TReturn None ->
  181. vars := PMap.map (fun _ -> true) !vars
  182. | TThrow e | TReturn (Some e) ->
  183. loop vars e;
  184. vars := PMap.map (fun _ -> true) !vars
  185. | TFunction tf ->
  186. let old = !outside_vars in
  187. (* Mark all known variables as "outside" so we can ignore their initialization state within the function.
  188. We cannot use `vars` directly because we still care about initializations the function might make.
  189. *)
  190. PMap.iter (fun i _ -> outside_vars := IntMap.add i true !outside_vars) !vars;
  191. loop vars tf.tf_expr;
  192. outside_vars := old;
  193. | _ ->
  194. Type.iter (loop vars) e
  195. in
  196. loop (ref PMap.empty) e;
  197. e
  198. (* -------------------------------------------------------------------------- *)
  199. (* BLOCK VARIABLES CAPTURE *)
  200. (*
  201. For some platforms, it will simply mark the variables which are used in closures
  202. using the v_capture flag so it can be processed in a more optimized
  203. For Flash/JS platforms, it will ensure that variables used in loop sub-functions
  204. have an unique scope. It transforms the following expression :
  205. for( x in array )
  206. funs.push(function() return x++);
  207. Into the following :
  208. for( _x in array ) {
  209. var x = [_x];
  210. funs.push(function(x) { function() return x[0]++; }(x));
  211. }
  212. *)
  213. type usage =
  214. | Block of ((usage -> unit) -> unit)
  215. | Loop of ((usage -> unit) -> unit)
  216. | Function of ((usage -> unit) -> unit)
  217. | Declare of tvar
  218. | Use of tvar
  219. | Assign of tvar
  220. let rec local_usage f e =
  221. match e.eexpr with
  222. | TBinop ((OpAssign | OpAssignOp _), { eexpr = TLocal v }, e2) ->
  223. local_usage f e2;
  224. f (Assign v)
  225. | TUnop ((Increment | Decrement), _, { eexpr = TLocal v }) ->
  226. f (Assign v)
  227. | TLocal v ->
  228. f (Use v)
  229. | TVar (v,eo) ->
  230. (match eo with None -> () | Some e -> local_usage f e);
  231. f (Declare v);
  232. | TFunction tf ->
  233. let cc f =
  234. List.iter (fun (v,_) -> f (Declare v)) tf.tf_args;
  235. local_usage f tf.tf_expr;
  236. in
  237. f (Function cc)
  238. | TBlock l ->
  239. f (Block (fun f -> List.iter (local_usage f) l))
  240. | TFor (v,it,e) ->
  241. local_usage f it;
  242. f (Loop (fun f ->
  243. f (Declare v);
  244. local_usage f e;
  245. ))
  246. | TWhile _ ->
  247. f (Loop (fun f ->
  248. iter (local_usage f) e
  249. ))
  250. | TTry (e,catchs) ->
  251. local_usage f e;
  252. List.iter (fun (v,e) ->
  253. f (Block (fun f ->
  254. f (Declare v);
  255. local_usage f e;
  256. ))
  257. ) catchs;
  258. | _ ->
  259. iter (local_usage f) e
  260. let captured_vars com e =
  261. let t = com.basic in
  262. let impl = match com.platform with
  263. (* optimized version for C#/Java - use native arrays *)
  264. | Cs | Java ->
  265. let cnativearray =
  266. match (List.find (fun md -> match md with
  267. | TClassDecl ({ cl_path = ["cs"|"java"],"NativeArray" }) -> true
  268. | _ -> false
  269. ) com.types)
  270. with TClassDecl cl -> cl | _ -> assert false
  271. in
  272. object
  273. method captured_type t = TInst (cnativearray,[t])
  274. method mk_ref v ve p =
  275. match ve with
  276. | None ->
  277. let eone = mk (TConst (TInt (Int32.of_int 1))) t.tint p in
  278. let t = match v.v_type with TInst (_, [t]) -> t | _ -> assert false in
  279. mk (TNew (cnativearray,[t],[eone])) v.v_type p
  280. | Some e ->
  281. { (Optimizer.mk_untyped_call "__array__" p [e]) with etype = v.v_type }
  282. method mk_ref_access e v =
  283. mk (TArray ({ e with etype = v.v_type }, mk (TConst (TInt 0l)) t.tint e.epos)) e.etype e.epos
  284. method mk_init av v pos =
  285. let elocal = mk (TLocal v) v.v_type pos in
  286. let earray = { (Optimizer.mk_untyped_call "__array__" pos [elocal]) with etype = av.v_type } in
  287. mk (TVar (av,Some earray)) t.tvoid pos
  288. end
  289. (* default implementation - use haxe array *)
  290. | _ ->
  291. object
  292. method captured_type = t.tarray
  293. method mk_ref v ve p =
  294. mk (TArrayDecl (match ve with None -> [] | Some e -> [e])) v.v_type p
  295. method mk_ref_access e v =
  296. mk (TArray ({ e with etype = v.v_type }, mk (TConst (TInt 0l)) t.tint e.epos)) e.etype e.epos
  297. method mk_init av v pos =
  298. mk (TVar (av,Some (mk (TArrayDecl [mk (TLocal v) v.v_type pos]) av.v_type pos))) t.tvoid pos
  299. end
  300. in
  301. let mk_var v used =
  302. let v2 = alloc_var v.v_name (PMap.find v.v_id used) in
  303. v2.v_meta <- v.v_meta;
  304. v2
  305. in
  306. let rec wrap used e =
  307. match e.eexpr with
  308. | TVar (v,ve) ->
  309. let v,ve =
  310. if PMap.mem v.v_id used then
  311. v, Some (impl#mk_ref v (Option.map (wrap used) ve) e.epos)
  312. else
  313. v, (match ve with None -> None | Some e -> Some (wrap used e))
  314. in
  315. { e with eexpr = TVar (v,ve) }
  316. | TLocal v when PMap.mem v.v_id used ->
  317. impl#mk_ref_access e v
  318. | TFor (v,it,expr) when PMap.mem v.v_id used ->
  319. let vtmp = mk_var v used in
  320. let it = wrap used it in
  321. let expr = wrap used expr in
  322. mk (TFor (vtmp,it,Type.concat (impl#mk_init v vtmp e.epos) expr)) e.etype e.epos
  323. | TTry (expr,catchs) ->
  324. let catchs = List.map (fun (v,e) ->
  325. let e = wrap used e in
  326. try
  327. let vtmp = mk_var v used in
  328. vtmp, Type.concat (impl#mk_init v vtmp e.epos) e
  329. with Not_found ->
  330. v, e
  331. ) catchs in
  332. mk (TTry (wrap used expr,catchs)) e.etype e.epos
  333. | TFunction f ->
  334. (*
  335. list variables that are marked as used, but also used in that
  336. function and which are not declared inside it !
  337. *)
  338. let fused = ref PMap.empty in
  339. let tmp_used = ref used in
  340. let rec browse = function
  341. | Block f | Loop f | Function f -> f browse
  342. | Use v | Assign v ->
  343. if PMap.mem v.v_id !tmp_used then fused := PMap.add v.v_id v !fused;
  344. | Declare v ->
  345. tmp_used := PMap.remove v.v_id !tmp_used
  346. in
  347. local_usage browse e;
  348. let vars = PMap.fold (fun v acc -> v :: acc) !fused [] in
  349. (* in case the variable has been marked as used in a parallel scope... *)
  350. let fexpr = ref (wrap used f.tf_expr) in
  351. let fargs = List.map (fun (v,o) ->
  352. if PMap.mem v.v_id used then
  353. let vtmp = mk_var v used in
  354. fexpr := Type.concat (impl#mk_init v vtmp e.epos) !fexpr;
  355. vtmp, o
  356. else
  357. v, o
  358. ) f.tf_args in
  359. let e = { e with eexpr = TFunction { f with tf_args = fargs; tf_expr = !fexpr } } in
  360. (*
  361. Create a new function scope to make sure that the captured loop variable
  362. will not be overwritten in next loop iteration
  363. *)
  364. if com.config.pf_capture_policy = CPLoopVars then
  365. (* We don't want to duplicate any variable declarations, so let's make copies (issue #3902). *)
  366. let new_vars = List.map (fun v -> v.v_id,alloc_var v.v_name v.v_type) vars in
  367. let rec loop e = match e.eexpr with
  368. | TLocal v ->
  369. begin try
  370. let v' = List.assoc v.v_id new_vars in
  371. v'.v_capture <- true;
  372. {e with eexpr = TLocal v'}
  373. with Not_found ->
  374. e
  375. end
  376. | _ ->
  377. Type.map_expr loop e
  378. in
  379. let e = loop e in
  380. mk (TCall (
  381. Codegen.mk_parent (mk (TFunction {
  382. tf_args = List.map (fun (_,v) -> v, None) new_vars;
  383. tf_type = e.etype;
  384. tf_expr = mk_block (mk (TReturn (Some e)) e.etype e.epos);
  385. }) (TFun (List.map (fun (_,v) -> v.v_name,false,v.v_type) new_vars,e.etype)) e.epos),
  386. List.map (fun v -> mk (TLocal v) v.v_type e.epos) vars)
  387. ) e.etype e.epos
  388. else
  389. e
  390. | _ ->
  391. map_expr (wrap used) e
  392. and do_wrap used e =
  393. if PMap.is_empty used then
  394. e
  395. else
  396. let used = PMap.map (fun v ->
  397. let vt = v.v_type in
  398. v.v_type <- impl#captured_type vt;
  399. v.v_capture <- true;
  400. vt
  401. ) used in
  402. wrap used e
  403. and out_loop e =
  404. match e.eexpr with
  405. | TFor _ | TWhile _ ->
  406. (*
  407. collect variables that are declared in loop but used in subfunctions
  408. *)
  409. let vars = ref PMap.empty in
  410. let used = ref PMap.empty in
  411. let depth = ref 0 in
  412. let rec collect_vars in_loop = function
  413. | Block f ->
  414. let old = !vars in
  415. f (collect_vars in_loop);
  416. vars := old;
  417. | Loop f ->
  418. let old = !vars in
  419. f (collect_vars true);
  420. vars := old;
  421. | Function f ->
  422. incr depth;
  423. f (collect_vars false);
  424. decr depth;
  425. | Declare v ->
  426. if in_loop then vars := PMap.add v.v_id !depth !vars;
  427. | Use v | Assign v ->
  428. try
  429. let d = PMap.find v.v_id !vars in
  430. if d <> !depth then used := PMap.add v.v_id v !used;
  431. with Not_found ->
  432. ()
  433. in
  434. local_usage (collect_vars false) e;
  435. do_wrap !used e
  436. | _ ->
  437. map_expr out_loop e
  438. and all_vars e =
  439. let vars = ref PMap.empty in
  440. let used = ref PMap.empty in
  441. let assigned = ref PMap.empty in
  442. let depth = ref 0 in
  443. let rec collect_vars = function
  444. | Block f ->
  445. let old = !vars in
  446. f collect_vars;
  447. vars := old;
  448. | Loop f ->
  449. let old = !vars in
  450. f collect_vars;
  451. vars := old;
  452. | Function f ->
  453. incr depth;
  454. f collect_vars;
  455. decr depth;
  456. | Declare v ->
  457. vars := PMap.add v.v_id !depth !vars;
  458. | Use v ->
  459. (try
  460. let d = PMap.find v.v_id !vars in
  461. if d <> !depth then used := PMap.add v.v_id v !used;
  462. with Not_found -> ())
  463. | Assign v ->
  464. (try
  465. let d = PMap.find v.v_id !vars in
  466. (* different depth - needs wrap *)
  467. if d <> !depth then begin
  468. used := PMap.add v.v_id v !used;
  469. assigned := PMap.add v.v_id v !assigned;
  470. end
  471. (* same depth but assigned after being used on a different depth - needs wrap *)
  472. else if PMap.mem v.v_id !used then
  473. assigned := PMap.add v.v_id v !assigned;
  474. with Not_found -> ())
  475. in
  476. local_usage collect_vars e;
  477. (* mark all capture variables - also used in rename_local_vars at later stage *)
  478. PMap.iter (fun _ v -> v.v_capture <- true) !used;
  479. !assigned
  480. in
  481. let captured = all_vars e in
  482. match com.config.pf_capture_policy with
  483. | CPNone -> e
  484. | CPWrapRef -> do_wrap captured e
  485. | CPLoopVars -> out_loop e
  486. (* -------------------------------------------------------------------------- *)
  487. (* RENAME LOCAL VARS *)
  488. let rename_local_vars ctx e =
  489. let cfg = ctx.com.config in
  490. let all_scope = (not cfg.pf_captured_scope) || (not cfg.pf_locals_scope) in
  491. let vars = ref PMap.empty in
  492. let all_vars = ref PMap.empty in
  493. let vtemp = alloc_var "~" t_dynamic in
  494. let rebuild_vars = ref false in
  495. let rebuild m =
  496. PMap.fold (fun v acc -> PMap.add v.v_name v acc) m PMap.empty
  497. in
  498. let save() =
  499. let old = !vars in
  500. if cfg.pf_unique_locals || not cfg.pf_locals_scope then (fun() -> ()) else (fun() -> vars := if !rebuild_vars then rebuild old else old)
  501. in
  502. let count = ref 1 in
  503. let rename vars v =
  504. while PMap.mem (v.v_name ^ string_of_int !count) vars do
  505. incr count;
  506. done;
  507. v.v_name <- v.v_name ^ string_of_int !count;
  508. in
  509. let declare v p =
  510. (match follow v.v_type with
  511. | TAbstract ({a_path = [],"Void"},_) -> error "Arguments and variables of type Void are not allowed" p
  512. | _ -> ());
  513. (* chop escape char for all local variables generated *)
  514. if is_gen_local v then v.v_name <- "_g" ^ String.sub v.v_name 1 (String.length v.v_name - 1);
  515. let look_vars = (if not cfg.pf_captured_scope && v.v_capture then !all_vars else !vars) in
  516. (try
  517. let v2 = PMap.find v.v_name look_vars in
  518. (*
  519. block_vars will create some wrapper-functions that are declaring
  520. the same variable twice. In that case do not perform a rename since
  521. we are sure it's actually the same variable
  522. *)
  523. if v == v2 then raise Not_found;
  524. rename look_vars v;
  525. with Not_found ->
  526. ());
  527. vars := PMap.add v.v_name v !vars;
  528. if all_scope then all_vars := PMap.add v.v_name v !all_vars;
  529. in
  530. (*
  531. This is quite a rare case, when a local variable would otherwise prevent
  532. accessing a type because it masks the type value or the package name.
  533. *)
  534. let check t =
  535. match (t_infos t).mt_path with
  536. | [], name | name :: _, _ ->
  537. let vars = if cfg.pf_locals_scope then vars else all_vars in
  538. (try
  539. let v = PMap.find name !vars in
  540. if v == vtemp then raise Not_found; (* ignore *)
  541. rename (!vars) v;
  542. rebuild_vars := true;
  543. vars := PMap.add v.v_name v !vars
  544. with Not_found ->
  545. ());
  546. vars := PMap.add name vtemp !vars
  547. in
  548. let check_type t =
  549. match follow t with
  550. | TInst (c,_) -> check (TClassDecl c)
  551. | TEnum (e,_) -> check (TEnumDecl e)
  552. | TType (t,_) -> check (TTypeDecl t)
  553. | TAbstract (a,_) -> check (TAbstractDecl a)
  554. | TMono _ | TLazy _ | TAnon _ | TDynamic _ | TFun _ -> ()
  555. in
  556. let rec loop e =
  557. match e.eexpr with
  558. | TVar (v,eo) ->
  559. if not cfg.pf_locals_scope then declare v e.epos;
  560. (match eo with None -> () | Some e -> loop e);
  561. if cfg.pf_locals_scope then declare v e.epos;
  562. | TFunction tf ->
  563. let old = save() in
  564. List.iter (fun (v,_) -> declare v e.epos) tf.tf_args;
  565. loop tf.tf_expr;
  566. old()
  567. | TBlock el ->
  568. let old = save() in
  569. (* we have to look ahead for vars on these targets (issue #3344) *)
  570. begin match ctx.com.platform with
  571. | Js ->
  572. let rec check_var e = match e.eexpr with
  573. | TVar (v,eo) ->
  574. (match eo with None -> () | Some e -> loop e);
  575. declare v e.epos
  576. | TBlock _ ->
  577. ()
  578. | _ ->
  579. Type.iter check_var e
  580. in
  581. List.iter check_var el
  582. | _ ->
  583. ()
  584. end;
  585. List.iter loop el;
  586. old()
  587. | TFor (v,it,e1) ->
  588. loop it;
  589. let old = save() in
  590. declare v e.epos;
  591. loop e1;
  592. old()
  593. | TTry (e,catchs) ->
  594. loop e;
  595. List.iter (fun (v,e) ->
  596. let old = save() in
  597. declare v e.epos;
  598. check_type v.v_type;
  599. loop e;
  600. old()
  601. ) catchs;
  602. | TTypeExpr t ->
  603. check t
  604. | TNew (c,_,_) ->
  605. Type.iter loop e;
  606. check (TClassDecl c);
  607. | TCast (e,Some t) ->
  608. loop e;
  609. check t;
  610. | TConst TSuper ->
  611. check_type e.etype
  612. | _ ->
  613. Type.iter loop e
  614. in
  615. declare (alloc_var "this" t_dynamic) Ast.null_pos; (* force renaming of 'this' vars in abstract *)
  616. begin match ctx.curclass.cl_path with
  617. | s :: _,_ | [],s -> declare (alloc_var s t_dynamic) Ast.null_pos
  618. end;
  619. loop e;
  620. e
  621. let check_unification ctx e t =
  622. begin match e.eexpr,t with
  623. | TLocal v,TType({t_path = ["cs"],("Ref" | "Out")},_) ->
  624. (* TODO: this smells of hack, but we have to deal with it somehow *)
  625. v.v_capture <- true
  626. | _ ->
  627. ()
  628. end;
  629. e
  630. (* PASS 1 end *)
  631. (* Saves a class state so it can be restored later, e.g. after DCE or native path rewrite *)
  632. let save_class_state ctx t = match t with
  633. | TClassDecl c ->
  634. let mk_field_restore f =
  635. let rec mk_overload_restore f =
  636. f.cf_name,f.cf_kind,f.cf_expr,f.cf_type,f.cf_meta,f.cf_params
  637. in
  638. ( f,mk_overload_restore f, List.map (fun f -> f,mk_overload_restore f) f.cf_overloads )
  639. in
  640. let restore_field (f,res,overloads) =
  641. let restore_field (f,(name,kind,expr,t,meta,params)) =
  642. f.cf_name <- name; f.cf_kind <- kind; f.cf_expr <- expr; f.cf_type <- t; f.cf_meta <- meta; f.cf_params <- params;
  643. f
  644. in
  645. let f = restore_field (f,res) in
  646. f.cf_overloads <- List.map restore_field overloads;
  647. f
  648. in
  649. let mk_pmap lst =
  650. List.fold_left (fun pmap f -> PMap.add f.cf_name f pmap) PMap.empty lst
  651. in
  652. let meta = c.cl_meta and path = c.cl_path and ext = c.cl_extern and over = c.cl_overrides in
  653. let sup = c.cl_super and impl = c.cl_implements in
  654. let csr = Option.map (mk_field_restore) c.cl_constructor in
  655. let ofr = List.map (mk_field_restore) c.cl_ordered_fields in
  656. let osr = List.map (mk_field_restore) c.cl_ordered_statics in
  657. let init = c.cl_init in
  658. c.cl_restore <- (fun() ->
  659. c.cl_super <- sup;
  660. c.cl_implements <- impl;
  661. c.cl_meta <- meta;
  662. c.cl_extern <- ext;
  663. c.cl_path <- path;
  664. c.cl_init <- init;
  665. c.cl_ordered_fields <- List.map restore_field ofr;
  666. c.cl_ordered_statics <- List.map restore_field osr;
  667. c.cl_fields <- mk_pmap c.cl_ordered_fields;
  668. c.cl_statics <- mk_pmap c.cl_ordered_statics;
  669. c.cl_constructor <- Option.map restore_field csr;
  670. c.cl_overrides <- over;
  671. )
  672. | _ ->
  673. ()
  674. (* PASS 2 begin *)
  675. let rec is_removable_class c =
  676. match c.cl_kind with
  677. | KGeneric ->
  678. (Meta.has Meta.Remove c.cl_meta ||
  679. (match c.cl_super with
  680. | Some (c,_) -> is_removable_class c
  681. | _ -> false) ||
  682. List.exists (fun (_,t) -> match follow t with
  683. | TInst(c,_) ->
  684. Codegen.has_ctor_constraint c || Meta.has Meta.Const c.cl_meta
  685. | _ ->
  686. false
  687. ) c.cl_params)
  688. | KTypeParameter _ ->
  689. (* this shouldn't happen, have to investigate (see #4092) *)
  690. true
  691. | _ ->
  692. false
  693. let remove_generic_base ctx t = match t with
  694. | TClassDecl c when is_removable_class c ->
  695. c.cl_extern <- true
  696. | _ ->
  697. ()
  698. (* Removes extern and macro fields, also checks for Void fields *)
  699. let remove_extern_fields ctx t = match t with
  700. | TClassDecl c ->
  701. if not (Common.defined ctx.com Define.DocGen) then begin
  702. c.cl_ordered_fields <- List.filter (fun f ->
  703. let b = Codegen.is_removable_field ctx f in
  704. if b then c.cl_fields <- PMap.remove f.cf_name c.cl_fields;
  705. not b
  706. ) c.cl_ordered_fields;
  707. c.cl_ordered_statics <- List.filter (fun f ->
  708. let b = Codegen.is_removable_field ctx f in
  709. if b then c.cl_statics <- PMap.remove f.cf_name c.cl_statics;
  710. not b
  711. ) c.cl_ordered_statics;
  712. end
  713. | _ ->
  714. ()
  715. (* PASS 2 end *)
  716. (* PASS 3 begin *)
  717. (* Checks if a private class' path clashes with another path *)
  718. let check_private_path ctx t = match t with
  719. | TClassDecl c when c.cl_private ->
  720. let rpath = (fst c.cl_module.m_path,"_" ^ snd c.cl_module.m_path) in
  721. if Hashtbl.mem ctx.g.types_module rpath then error ("This private class name will clash with " ^ s_type_path rpath) c.cl_pos;
  722. | _ ->
  723. ()
  724. (* Rewrites class or enum paths if @:native metadata is set *)
  725. let apply_native_paths ctx t =
  726. let get_native_name meta =
  727. let rec get_native meta = match meta with
  728. | [] -> raise Not_found
  729. | (Meta.Native,[v],p as meta) :: _ ->
  730. meta
  731. | _ :: meta ->
  732. get_native meta
  733. in
  734. let (_,e,mp) = get_native meta in
  735. match e with
  736. | [Ast.EConst (Ast.String name),p] ->
  737. name,p
  738. | [] ->
  739. raise Not_found
  740. | _ ->
  741. error "String expected" mp
  742. in
  743. let get_real_name meta name =
  744. let name',p = get_native_name meta in
  745. (Meta.RealPath,[Ast.EConst (Ast.String (name)), p], p), name'
  746. in
  747. let get_real_path meta path =
  748. let name,p = get_native_name meta in
  749. (Meta.RealPath,[Ast.EConst (Ast.String (s_type_path path)), p], p), parse_path name
  750. in
  751. try
  752. (match t with
  753. | TClassDecl c ->
  754. let did_change = ref false in
  755. let field cf = try
  756. let meta,name = get_real_name cf.cf_meta cf.cf_name in
  757. cf.cf_name <- name;
  758. cf.cf_meta <- meta :: cf.cf_meta;
  759. List.iter (fun cf -> cf.cf_name <- name) cf.cf_overloads;
  760. did_change := true
  761. with Not_found ->
  762. ()
  763. in
  764. let fields cfs old_map =
  765. did_change := false;
  766. List.iter field cfs;
  767. if !did_change then
  768. List.fold_left (fun map f -> PMap.add f.cf_name f map) PMap.empty cfs
  769. else
  770. old_map
  771. in
  772. c.cl_fields <- fields c.cl_ordered_fields c.cl_fields;
  773. c.cl_statics <- fields c.cl_ordered_statics c.cl_statics;
  774. let meta,path = get_real_path c.cl_meta c.cl_path in
  775. c.cl_meta <- meta :: c.cl_meta;
  776. c.cl_path <- path;
  777. | TEnumDecl e ->
  778. let meta,path = get_real_path e.e_meta e.e_path in
  779. e.e_meta <- meta :: e.e_meta;
  780. e.e_path <- path;
  781. | TAbstractDecl a ->
  782. let meta,path = get_real_path a.a_meta a.a_path in
  783. a.a_meta <- meta :: a.a_meta;
  784. a.a_path <- path;
  785. | _ ->
  786. ())
  787. with Not_found ->
  788. ()
  789. (* Adds the __rtti field if required *)
  790. let add_rtti ctx t =
  791. let rec has_rtti c =
  792. Meta.has Meta.Rtti c.cl_meta || match c.cl_super with None -> false | Some (csup,_) -> has_rtti csup
  793. in
  794. match t with
  795. | TClassDecl c when has_rtti c && not (PMap.mem "__rtti" c.cl_statics) ->
  796. let f = mk_field "__rtti" ctx.t.tstring c.cl_pos in
  797. let str = Genxml.gen_type_string ctx.com t in
  798. f.cf_expr <- Some (mk (TConst (TString str)) f.cf_type c.cl_pos);
  799. c.cl_ordered_statics <- f :: c.cl_ordered_statics;
  800. c.cl_statics <- PMap.add f.cf_name f c.cl_statics;
  801. | _ ->
  802. ()
  803. (* Adds member field initializations as assignments to the constructor *)
  804. let add_field_inits ctx t =
  805. let is_as3 = Common.defined ctx.com Define.As3 && not ctx.in_macro in
  806. let apply c =
  807. let ethis = mk (TConst TThis) (TInst (c,List.map snd c.cl_params)) c.cl_pos in
  808. (* TODO: we have to find a variable name which is not used in any of the functions *)
  809. let v = alloc_var "_g" ethis.etype in
  810. let need_this = ref false in
  811. let inits,fields = List.fold_left (fun (inits,fields) cf ->
  812. match cf.cf_kind,cf.cf_expr with
  813. | Var _, Some _ ->
  814. if is_as3 then (inits, cf :: fields) else (cf :: inits, cf :: fields)
  815. | Method MethDynamic, Some e when is_as3 ->
  816. (* TODO : this would have a better place in genSWF9 I think - NC *)
  817. (* we move the initialization of dynamic functions to the constructor and also solve the
  818. 'this' problem along the way *)
  819. let rec use_this v e = match e.eexpr with
  820. | TConst TThis ->
  821. need_this := true;
  822. mk (TLocal v) v.v_type e.epos
  823. | _ -> Type.map_expr (use_this v) e
  824. in
  825. let e = Type.map_expr (use_this v) e in
  826. let cf2 = {cf with cf_expr = Some e} in
  827. (* if the method is an override, we have to remove the class field to not get invalid overrides *)
  828. let fields = if List.memq cf c.cl_overrides then begin
  829. c.cl_fields <- PMap.remove cf.cf_name c.cl_fields;
  830. fields
  831. end else
  832. cf2 :: fields
  833. in
  834. (cf2 :: inits, fields)
  835. | _ -> (inits, cf :: fields)
  836. ) ([],[]) c.cl_ordered_fields in
  837. c.cl_ordered_fields <- (List.rev fields);
  838. match inits with
  839. | [] -> ()
  840. | _ ->
  841. let el = List.map (fun cf ->
  842. match cf.cf_expr with
  843. | None -> assert false
  844. | Some e ->
  845. let lhs = mk (TField(ethis,FInstance (c,List.map snd c.cl_params,cf))) cf.cf_type e.epos in
  846. cf.cf_expr <- None;
  847. let eassign = mk (TBinop(OpAssign,lhs,e)) e.etype e.epos in
  848. if is_as3 then begin
  849. let echeck = mk (TBinop(OpEq,lhs,(mk (TConst TNull) lhs.etype e.epos))) ctx.com.basic.tbool e.epos in
  850. mk (TIf(echeck,eassign,None)) eassign.etype e.epos
  851. end else
  852. eassign;
  853. ) inits in
  854. let el = if !need_this then (mk (TVar((v, Some ethis))) ethis.etype ethis.epos) :: el else el in
  855. match c.cl_constructor with
  856. | None ->
  857. let ct = TFun([],ctx.com.basic.tvoid) in
  858. let ce = mk (TFunction {
  859. tf_args = [];
  860. tf_type = ctx.com.basic.tvoid;
  861. tf_expr = mk (TBlock el) ctx.com.basic.tvoid c.cl_pos;
  862. }) ct c.cl_pos in
  863. let ctor = mk_field "new" ct c.cl_pos in
  864. ctor.cf_kind <- Method MethNormal;
  865. c.cl_constructor <- Some { ctor with cf_expr = Some ce };
  866. | Some cf ->
  867. match cf.cf_expr with
  868. | Some { eexpr = TFunction f } ->
  869. let bl = match f.tf_expr with {eexpr = TBlock b } -> b | x -> [x] in
  870. let ce = mk (TFunction {f with tf_expr = mk (TBlock (el @ bl)) ctx.com.basic.tvoid c.cl_pos }) cf.cf_type cf.cf_pos in
  871. c.cl_constructor <- Some {cf with cf_expr = Some ce }
  872. | _ ->
  873. assert false
  874. in
  875. match t with
  876. | TClassDecl c ->
  877. apply c
  878. | _ ->
  879. ()
  880. (* Adds the __meta__ field if required *)
  881. let add_meta_field ctx t = match t with
  882. | TClassDecl c ->
  883. (match Codegen.build_metadata ctx.com t with
  884. | None -> ()
  885. | Some e ->
  886. add_feature ctx.com "has_metadata";
  887. let f = mk_field "__meta__" t_dynamic c.cl_pos in
  888. f.cf_expr <- Some e;
  889. let can_deal_with_interface_metadata () = match ctx.com.platform with
  890. | Flash when Common.defined ctx.com Define.As3 -> false
  891. | Php -> false
  892. | _ -> true
  893. in
  894. if c.cl_interface && not (can_deal_with_interface_metadata()) then begin
  895. (* borrowed from gencommon, but I did wash my hands afterwards *)
  896. let path = fst c.cl_path,snd c.cl_path ^ "_HxMeta" in
  897. let ncls = mk_class c.cl_module path c.cl_pos in
  898. let cf = mk_field "__meta__" e.etype e.epos in
  899. cf.cf_expr <- Some e;
  900. ncls.cl_statics <- PMap.add "__meta__" cf ncls.cl_statics;
  901. ncls.cl_ordered_statics <- cf :: ncls.cl_ordered_statics;
  902. ctx.com.types <- (TClassDecl ncls) :: ctx.com.types;
  903. c.cl_meta <- (Meta.Custom ":hasMetadata",[],e.epos) :: c.cl_meta
  904. end else begin
  905. c.cl_ordered_statics <- f :: c.cl_ordered_statics;
  906. c.cl_statics <- PMap.add f.cf_name f c.cl_statics
  907. end)
  908. | _ ->
  909. ()
  910. (* Removes interfaces tagged with @:remove metadata *)
  911. let check_remove_metadata ctx t = match t with
  912. | TClassDecl c ->
  913. c.cl_implements <- List.filter (fun (c,_) -> not (Meta.has Meta.Remove c.cl_meta)) c.cl_implements;
  914. | _ ->
  915. ()
  916. (* Checks for Void class fields *)
  917. let check_void_field ctx t = match t with
  918. | TClassDecl c ->
  919. let check f =
  920. match follow f.cf_type with TAbstract({a_path=[],"Void"},_) -> error "Fields of type Void are not allowed" f.cf_pos | _ -> ();
  921. in
  922. List.iter check c.cl_ordered_fields;
  923. List.iter check c.cl_ordered_statics;
  924. | _ ->
  925. ()
  926. (* Interfaces have no 'super', but can extend many other interfaces.
  927. This makes the first extended (implemented) interface the super for efficiency reasons (you can get one for 'free')
  928. and leaves the remaining ones as 'implemented' *)
  929. let promote_first_interface_to_super ctx t = match t with
  930. | TClassDecl c when c.cl_interface ->
  931. begin match c.cl_implements with
  932. | ({ cl_path = ["cpp";"rtti"],_ },_ ) :: _ -> ()
  933. | first_interface :: remaining ->
  934. c.cl_super <- Some first_interface;
  935. c.cl_implements <- remaining
  936. | _ -> ()
  937. end
  938. | _ ->
  939. ()
  940. let commit_features ctx t =
  941. let m = (t_infos t).mt_module in
  942. Hashtbl.iter (fun k v ->
  943. Common.add_feature ctx.com k;
  944. ) m.m_extra.m_features
  945. let check_reserved_type_paths ctx t =
  946. let check path pos =
  947. if List.mem path ctx.com.config.pf_reserved_type_paths then
  948. ctx.com.warning ("Type path " ^ (s_type_path path) ^ " is reserved on this target") pos
  949. in
  950. match t with
  951. | TClassDecl c when not c.cl_extern -> check c.cl_path c.cl_pos
  952. | TEnumDecl e when not e.e_extern -> check e.e_path e.e_pos
  953. | _ -> ()
  954. (* PASS 3 end *)
  955. let run_expression_filters ctx filters t =
  956. let run e =
  957. List.fold_left (fun e f -> f e) e filters
  958. in
  959. match t with
  960. | TClassDecl c when is_removable_class c -> ()
  961. | TClassDecl c ->
  962. ctx.curclass <- c;
  963. let rec process_field f =
  964. (match f.cf_expr with
  965. | Some e when not (Codegen.is_removable_field ctx f) ->
  966. Codegen.AbstractCast.cast_stack := f :: !Codegen.AbstractCast.cast_stack;
  967. f.cf_expr <- Some (run e);
  968. Codegen.AbstractCast.cast_stack := List.tl !Codegen.AbstractCast.cast_stack;
  969. | _ -> ());
  970. List.iter process_field f.cf_overloads
  971. in
  972. List.iter process_field c.cl_ordered_fields;
  973. List.iter process_field c.cl_ordered_statics;
  974. (match c.cl_constructor with
  975. | None -> ()
  976. | Some f -> process_field f);
  977. (match c.cl_init with
  978. | None -> ()
  979. | Some e ->
  980. c.cl_init <- Some (run e));
  981. | TEnumDecl _ -> ()
  982. | TTypeDecl _ -> ()
  983. | TAbstractDecl _ -> ()
  984. let pp_counter = ref 1
  985. let is_cached t =
  986. let m = (t_infos t).mt_module.m_extra in
  987. if m.m_processed = 0 then m.m_processed <- !pp_counter;
  988. m.m_processed <> !pp_counter
  989. let apply_filters_once ctx filters t =
  990. if not (is_cached t) then run_expression_filters ctx filters t
  991. let next_compilation() =
  992. incr pp_counter
  993. let iter_expressions fl mt =
  994. match mt with
  995. | TClassDecl c ->
  996. let field cf = match cf.cf_expr with
  997. | None -> ()
  998. | Some e -> List.iter (fun f -> f e) fl
  999. in
  1000. List.iter field c.cl_ordered_statics;
  1001. List.iter field c.cl_ordered_fields;
  1002. (match c.cl_constructor with None -> () | Some cf -> field cf)
  1003. | _ ->
  1004. ()
  1005. let run com tctx main =
  1006. begin match com.display with
  1007. | DMUsage | DMPosition -> Codegen.detect_usage com;
  1008. | _ -> ()
  1009. end;
  1010. if not (Common.defined com Define.NoDeprecationWarnings) then
  1011. Codegen.DeprecationCheck.run com;
  1012. let use_static_analyzer = Common.defined com Define.Analyzer in
  1013. let new_types = List.filter (fun t -> not (is_cached t)) com.types in
  1014. (* PASS 1: general expression filters *)
  1015. let filters = [
  1016. Codegen.AbstractCast.handle_abstract_casts tctx;
  1017. check_local_vars_init;
  1018. Optimizer.inline_constructors tctx;
  1019. Optimizer.reduce_expression tctx;
  1020. captured_vars com;
  1021. ] in
  1022. List.iter (run_expression_filters tctx filters) new_types;
  1023. if com.platform <> Cross then Analyzer.Run.run_on_types tctx use_static_analyzer new_types;
  1024. let filters = [
  1025. Optimizer.sanitize com;
  1026. if com.config.pf_add_final_return then add_final_return else (fun e -> e);
  1027. if com.platform = Js then wrap_js_exceptions com else (fun e -> e);
  1028. rename_local_vars tctx;
  1029. ] in
  1030. List.iter (run_expression_filters tctx filters) new_types;
  1031. next_compilation();
  1032. List.iter (fun f -> f()) (List.rev com.filters); (* macros onGenerate etc. *)
  1033. List.iter (save_class_state tctx) new_types;
  1034. (* PASS 2: type filters pre-DCE *)
  1035. List.iter (fun t ->
  1036. remove_generic_base tctx t;
  1037. remove_extern_fields tctx t;
  1038. Codegen.update_cache_dependencies t;
  1039. (* check @:remove metadata before DCE so it is ignored there (issue #2923) *)
  1040. check_remove_metadata tctx t;
  1041. ) com.types;
  1042. (* DCE *)
  1043. let dce_mode = if Common.defined com Define.As3 then
  1044. "no"
  1045. else
  1046. (try Common.defined_value com Define.Dce with _ -> "no")
  1047. in
  1048. begin match dce_mode with
  1049. | "full" -> Dce.run com main (not (Common.defined com Define.Interp))
  1050. | "std" -> Dce.run com main false
  1051. | "no" -> Dce.fix_accessors com
  1052. | _ -> failwith ("Unknown DCE mode " ^ dce_mode)
  1053. end;
  1054. (* PASS 3: type filters post-DCE *)
  1055. let type_filters = [
  1056. check_private_path;
  1057. apply_native_paths;
  1058. add_rtti;
  1059. (match com.platform with | Java | Cs -> (fun _ _ -> ()) | _ -> add_field_inits);
  1060. add_meta_field;
  1061. check_void_field;
  1062. (match com.platform with | Cpp -> promote_first_interface_to_super | _ -> (fun _ _ -> ()) );
  1063. commit_features;
  1064. (if com.config.pf_reserved_type_paths <> [] then check_reserved_type_paths else (fun _ _ -> ()));
  1065. ] in
  1066. List.iter (fun t -> List.iter (fun f -> f tctx t) type_filters) com.types