overloadingConstructor.ml 16 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458
  1. (*
  2. The Haxe Compiler
  3. Copyright (C) 2005-2019 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 Option
  17. open Common
  18. open Type
  19. open Gencommon
  20. (* ******************************************* *)
  21. (* overloading reflection constructors *)
  22. (* ******************************************* *)
  23. (*
  24. this module works on languages that support function overloading and
  25. enable function hiding via static functions.
  26. it takes the constructor body out of the constructor and adds it to a special ctor
  27. static function. The static function will receive the same parameters as the constructor,
  28. plus the special "me" var, which will replace "this"
  29. Then it always adds two constructors to the class: one that receives a special marker class,
  30. indicating that the object should be constructed without executing constructor body,
  31. and one that executes its normal constructor.
  32. Both will only include a super() call to the superclasses' emtpy constructor.
  33. This enables two things:
  34. empty construction without the need of incompatibility with the platform's native construction method
  35. the ability to call super() constructor in any place in the constructor
  36. *)
  37. let rec prev_ctor c tl =
  38. match c.cl_super with
  39. | None ->
  40. raise Not_found
  41. | Some (sup,stl) ->
  42. let stl = List.map (apply_params c.cl_params tl) stl in
  43. match sup.cl_constructor with
  44. | None -> prev_ctor sup stl
  45. | Some ctor -> ctor, sup, stl
  46. let make_static_ctor_name cl =
  47. let name = mk_internal_name "hx" "ctor" in
  48. name ^ "_" ^ (String.concat "_" (fst cl.cl_path)) ^ "_" ^ (snd cl.cl_path)
  49. (* replaces super() call with last static constructor call *)
  50. let replace_super_call com c tl with_params me p follow_type =
  51. let rec loop_super c tl =
  52. match c.cl_super with
  53. | None ->
  54. raise Not_found
  55. | Some(sup,stl) ->
  56. let stl = List.map (apply_params c.cl_params tl) stl in
  57. try
  58. let static_ctor_name = make_static_ctor_name sup in
  59. sup, stl, PMap.find static_ctor_name sup.cl_statics
  60. with Not_found ->
  61. loop_super sup stl
  62. in
  63. let sup, stl, cf = loop_super c tl in
  64. let with_params = (mk (TLocal me) me.v_type p) :: with_params in
  65. let cf =
  66. try
  67. (* choose best super function *)
  68. List.iter (fun e -> replace_mono e.etype) with_params;
  69. List.find (fun cf ->
  70. replace_mono cf.cf_type;
  71. let args, _ = get_fun (apply_params cf.cf_params stl cf.cf_type) in
  72. try
  73. List.for_all2 (fun (_,_,t) e -> try
  74. let e_etype = follow_type e.etype in
  75. let t = follow_type t in
  76. unify e_etype t; true
  77. with Unify_error _ ->
  78. false
  79. ) args with_params
  80. with Invalid_argument _ ->
  81. false
  82. ) (cf :: cf.cf_overloads)
  83. with Not_found ->
  84. com.error "No suitable overload for the super call arguments was found" p; cf
  85. in
  86. {
  87. eexpr = TCall(
  88. {
  89. eexpr = TField(Texpr.Builder.make_static_this sup p, FStatic(sup,cf));
  90. etype = apply_params cf.cf_params stl cf.cf_type;
  91. epos = p
  92. },
  93. with_params
  94. );
  95. etype = com.basic.tvoid;
  96. epos = p;
  97. }
  98. (* will create a static counterpart of 'ctor', and replace its contents to a call to the static version*)
  99. let create_static_ctor com ~empty_ctor_expr cl ctor follow_type =
  100. match Meta.has Meta.SkipCtor ctor.cf_meta with
  101. | true -> ()
  102. | false when is_none ctor.cf_expr -> ()
  103. | false ->
  104. let static_ctor_name = make_static_ctor_name cl in
  105. (* create the static constructor *)
  106. let ctor_types = List.map clone_param cl.cl_params in
  107. let ctor_type_params = extract_param_types ctor_types in
  108. List.iter (fun ttp -> match get_constraints ttp with
  109. | [] ->
  110. ()
  111. | before ->
  112. let after = List.map (apply_params cl.cl_params ctor_type_params) before in
  113. ttp.ttp_constraints <- Some (lazy after)
  114. ) ctor_types;
  115. let me = alloc_var "__hx_this" (TInst(cl, extract_param_types ctor_types)) in
  116. add_var_flag me VCaptured;
  117. let fn_args, _ = get_fun ctor.cf_type in
  118. let ctor_params = extract_param_types ctor_types in
  119. let fn_type = TFun((me.v_name,false, me.v_type) :: List.map (fun (n,o,t) -> (n,o,apply_params cl.cl_params ctor_params t)) fn_args, com.basic.tvoid) in
  120. let cur_tf_args = match ctor.cf_expr with
  121. | Some { eexpr = TFunction(tf) } -> tf.tf_args
  122. | _ -> Globals.die "" __LOC__
  123. in
  124. let changed_tf_args = List.map (fun (v,_) -> (v,None)) cur_tf_args in
  125. let local_map = Hashtbl.create (List.length cur_tf_args) in
  126. let static_tf_args = (me, None) :: List.map (fun (v,b) ->
  127. let new_v = alloc_var v.v_name (apply_params cl.cl_params ctor_params v.v_type) in
  128. add_var_flag new_v VCaptured;
  129. Hashtbl.add local_map v.v_id new_v;
  130. (new_v, b)
  131. ) cur_tf_args in
  132. let static_ctor = mk_class_field ~static:true static_ctor_name fn_type false ctor.cf_pos (Method MethNormal) ctor_types in
  133. let static_ctor_meta = if has_class_flag cl CFinal then Meta.Private else Meta.Protected in
  134. static_ctor.cf_meta <- (static_ctor_meta,[],ctor.cf_pos) :: static_ctor.cf_meta;
  135. (* change ctor contents to reference the 'me' var instead of 'this' *)
  136. let actual_super_call = ref None in
  137. let rec map_expr ~is_first e = match e.eexpr with
  138. | TCall (({ eexpr = TConst TSuper } as tsuper), params) -> (try
  139. let params = List.map (fun e -> map_expr ~is_first:false e) params in
  140. actual_super_call := Some { e with eexpr = TCall(tsuper, [empty_ctor_expr]) };
  141. replace_super_call com cl ctor_params params me e.epos follow_type
  142. with | Not_found ->
  143. (* last static function was not found *)
  144. actual_super_call := Some e;
  145. if not is_first then
  146. com.error "Super call must be the first call when extending native types" e.epos;
  147. { e with eexpr = TBlock([]) })
  148. | TFunction tf when is_first ->
  149. do_map ~is_first:true e
  150. | TConst TThis ->
  151. mk_local me e.epos
  152. | TBlock (fst :: bl) ->
  153. let fst = map_expr ~is_first:is_first fst in
  154. { e with eexpr = TBlock(fst :: List.map (fun e -> map_expr ~is_first:false e) bl); etype = apply_params cl.cl_params ctor_params e.etype }
  155. | _ ->
  156. do_map e
  157. and do_map ?(is_first=false) e =
  158. let do_t = apply_params cl.cl_params ctor_params in
  159. let do_v v = try
  160. Hashtbl.find local_map v.v_id
  161. with | Not_found ->
  162. v.v_type <- do_t v.v_type; v
  163. in
  164. Type.map_expr_type (map_expr ~is_first:is_first) do_t do_v e
  165. in
  166. let expr = do_map ~is_first:true (get ctor.cf_expr) in
  167. let expr = match expr.eexpr with
  168. | TFunction(tf) ->
  169. { expr with etype = fn_type; eexpr = TFunction({ tf with tf_args = static_tf_args }) }
  170. | _ -> Globals.die "" __LOC__ in
  171. static_ctor.cf_expr <- Some expr;
  172. (* add to the statics *)
  173. (try
  174. let stat = PMap.find static_ctor_name cl.cl_statics in
  175. stat.cf_overloads <- static_ctor :: stat.cf_overloads
  176. with | Not_found ->
  177. cl.cl_ordered_statics <- static_ctor :: cl.cl_ordered_statics;
  178. cl.cl_statics <- PMap.add static_ctor_name static_ctor cl.cl_statics);
  179. (* change current super call *)
  180. match ctor.cf_expr with
  181. | Some({ eexpr = TFunction(tf) } as e) ->
  182. let block_contents, p = match !actual_super_call with
  183. | None -> [], ctor.cf_pos
  184. | Some super -> [super], super.epos
  185. in
  186. let el_args =
  187. let rec loop fn_args cur_args =
  188. match cur_args with
  189. | [] -> []
  190. | (v,_) :: cur_args ->
  191. let local = mk_local v p in
  192. match fn_args, cur_args with
  193. | [_,_,t], [] when ExtType.is_rest (follow t) ->
  194. [mk (TUnop(Spread,Prefix,local)) v.v_type p]
  195. | [], _ ->
  196. local :: loop fn_args cur_args
  197. | _ :: fn_args, _ ->
  198. local :: loop fn_args cur_args
  199. in
  200. loop fn_args cur_tf_args
  201. in
  202. let block_contents = block_contents @ [{
  203. eexpr = TCall(
  204. {
  205. eexpr = TField(
  206. Texpr.Builder.make_static_this cl p,
  207. FStatic(cl, static_ctor));
  208. etype = apply_params static_ctor.cf_params (extract_param_types cl.cl_params) static_ctor.cf_type;
  209. epos = p
  210. },
  211. [{ eexpr = TConst TThis; etype = TInst(cl, extract_param_types cl.cl_params); epos = p }]
  212. @ el_args
  213. );
  214. etype = com.basic.tvoid;
  215. epos = p
  216. }] in
  217. ctor.cf_expr <- Some { e with eexpr = TFunction({ tf with tf_expr = { tf.tf_expr with eexpr = TBlock block_contents }; tf_args = changed_tf_args }) }
  218. | _ -> Globals.die "" __LOC__
  219. (* makes constructors that only call super() for the 'ctor' argument *)
  220. let clone_ctors com ctor sup stl cl =
  221. let clone cf =
  222. let ncf = mk_class_field "new" (apply_params sup.cl_params stl cf.cf_type) (has_class_field_flag cf CfPublic) cf.cf_pos cf.cf_kind cf.cf_params in
  223. if Meta.has Meta.Protected cf.cf_meta then
  224. ncf.cf_meta <- (Meta.Protected,[],ncf.cf_pos) :: ncf.cf_meta;
  225. let args, ret = get_fun ncf.cf_type in
  226. (* single expression: call to super() *)
  227. let tf_args = List.map (fun (name,_,t) ->
  228. (* the constructor will have no optional arguments, as presumably this will be handled by the underlying expr *)
  229. alloc_var name t, None
  230. ) args in
  231. let super_call =
  232. {
  233. eexpr = TCall(
  234. { eexpr = TConst TSuper; etype = TInst(cl, extract_param_types cl.cl_params); epos = ctor.cf_pos },
  235. List.map (fun (v,_) -> mk_local v ctor.cf_pos) tf_args);
  236. etype = com.basic.tvoid;
  237. epos = ctor.cf_pos;
  238. } in
  239. ncf.cf_expr <- Some
  240. {
  241. eexpr = TFunction {
  242. tf_args = tf_args;
  243. tf_type = com.basic.tvoid;
  244. tf_expr = mk_block super_call;
  245. };
  246. etype = ncf.cf_type;
  247. epos = ctor.cf_pos;
  248. };
  249. ncf
  250. in
  251. (* take off createEmpty *)
  252. let all = List.filter (fun cf -> replace_mono cf.cf_type; not (Meta.has Meta.SkipCtor cf.cf_meta)) (ctor :: ctor.cf_overloads) in
  253. let clones = List.map clone all in
  254. match clones with
  255. | [] ->
  256. (* raise Not_found *)
  257. Globals.die "" __LOC__ (* should never happen *)
  258. | cf :: [] -> cf
  259. | cf :: overl ->
  260. add_class_field_flag cf CfOverload;
  261. cf.cf_overloads <- overl; cf
  262. let rec descends_from_native_or_skipctor cl =
  263. not (is_hxgen (TClassDecl cl)) || Meta.has Meta.SkipCtor cl.cl_meta || match cl.cl_super with
  264. | None -> false
  265. | Some(c,_) -> descends_from_native_or_skipctor c
  266. let ensure_super_is_first com cf =
  267. let rec loop e =
  268. match e.eexpr with
  269. | TBlock (b :: block) ->
  270. loop b
  271. | TBlock []
  272. | TCall({ eexpr = TConst TSuper },_) -> ()
  273. | _ ->
  274. com.error "Types that derive from a native class must have its super() call as the first statement in the constructor" cf.cf_pos
  275. in
  276. match cf.cf_expr with
  277. | None -> ()
  278. | Some e -> Type.iter loop e
  279. let init com (empty_ctor_type : t) (empty_ctor_expr : texpr) (follow_type : t -> t) =
  280. let basic = com.basic in
  281. let should_change cl = not (has_class_flag cl CInterface) && (not (has_class_flag cl CExtern) || is_hxgen (TClassDecl cl)) && (match cl.cl_kind with KAbstractImpl _ | KModuleFields _ -> false | _ -> true) in
  282. let msize = List.length com.types in
  283. let processed, empty_ctors = Hashtbl.create msize, Hashtbl.create msize in
  284. let rec get_last_empty cl =
  285. try
  286. Hashtbl.find empty_ctors cl.cl_path
  287. with | Not_found ->
  288. match cl.cl_super with
  289. | None -> raise Not_found
  290. | Some (sup,_) -> get_last_empty sup
  291. in
  292. let rec change cl =
  293. if not (Hashtbl.mem processed cl.cl_path) then begin
  294. Hashtbl.add processed cl.cl_path true;
  295. (* make sure we've processed the super types *)
  296. Option.may (fun (super,_) -> if should_change super then change super) cl.cl_super;
  297. (* implement static hx_ctor and reimplement constructors *)
  298. (try
  299. let ctor =
  300. match cl.cl_constructor with
  301. | Some ctor ->
  302. ctor
  303. | None ->
  304. try
  305. let sctor, sup, stl = prev_ctor cl (extract_param_types cl.cl_params) in
  306. (* we'll make constructors that will only call super() *)
  307. let ctor = clone_ctors com sctor sup stl cl in
  308. cl.cl_constructor <- Some ctor;
  309. ctor
  310. with Not_found -> (* create default constructor *)
  311. let ctor = mk_class_field "new" (TFun ([], basic.tvoid)) false cl.cl_pos (Method MethNormal) [] in
  312. ctor.cf_expr <- Some {
  313. eexpr = TFunction {
  314. tf_args = [];
  315. tf_type = basic.tvoid;
  316. tf_expr = mk (TBlock []) basic.tvoid cl.cl_pos;
  317. };
  318. etype = ctor.cf_type;
  319. epos = ctor.cf_pos;
  320. };
  321. cl.cl_constructor <- Some ctor;
  322. ctor
  323. in
  324. let has_super_constructor =
  325. match cl.cl_super with
  326. | None -> false
  327. | Some (csup,_) -> has_constructor csup
  328. in
  329. (* now that we made sure we have a constructor, exit if native gen *)
  330. if not (is_hxgen (TClassDecl cl)) || Meta.has Meta.SkipCtor cl.cl_meta then begin
  331. if descends_from_native_or_skipctor cl && has_super_constructor then
  332. List.iter (fun cf -> ensure_super_is_first com cf) (ctor :: ctor.cf_overloads);
  333. raise Exit
  334. end;
  335. (* if cl descends from a native class, we cannot use the static constructor strategy *)
  336. if descends_from_native_or_skipctor cl && has_super_constructor then
  337. List.iter (fun cf -> ensure_super_is_first com cf) (ctor :: ctor.cf_overloads)
  338. else
  339. (* now that we have a current ctor, create the static counterparts *)
  340. List.iter (fun cf -> create_static_ctor com ~empty_ctor_expr:empty_ctor_expr cl cf follow_type) (ctor :: ctor.cf_overloads)
  341. with Exit -> ());
  342. (* implement empty ctor *)
  343. (try
  344. (* now that we made sure we have a constructor, exit if native gen *)
  345. if not (is_hxgen (TClassDecl cl)) then raise Exit;
  346. (* get first *)
  347. let empty_type = TFun (["empty",false,empty_ctor_type],basic.tvoid) in
  348. let super =
  349. match cl.cl_super with
  350. | None -> (* implement empty *)
  351. []
  352. | Some (sup,_) ->
  353. try
  354. ignore (get_last_empty sup);
  355. let esuper = mk (TConst TSuper) (TInst (cl, extract_param_types cl.cl_params)) cl.cl_pos in
  356. [mk (TCall (esuper, [empty_ctor_expr])) basic.tvoid cl.cl_pos]
  357. with Not_found ->
  358. try
  359. (* super type is native: find super constructor with least arguments *)
  360. let sctor, sup, stl = prev_ctor cl (extract_param_types cl.cl_params) in
  361. let rec loop remaining (best,n) =
  362. match remaining with
  363. | [] -> best
  364. | cf :: r ->
  365. let args,_ = get_fun cf.cf_type in
  366. if (List.length args) < n then
  367. loop r (cf,List.length args)
  368. else
  369. loop r (best,n)
  370. in
  371. let args,_ = get_fun sctor.cf_type in
  372. let best = loop sctor.cf_overloads (sctor, List.length args) in
  373. let args,_ = get_fun (apply_params sup.cl_params stl best.cf_type) in
  374. let esuper = mk (TConst TSuper) (TInst (sup, stl)) cl.cl_pos in
  375. [mk (TCall (esuper, List.map (fun (n,o,t) -> null t cl.cl_pos) args)) basic.tvoid cl.cl_pos]
  376. with Not_found ->
  377. (* extends native type, but no ctor found *)
  378. []
  379. in
  380. let ctor = mk_class_field "new" empty_type false cl.cl_pos (Method MethNormal) [] in
  381. ctor.cf_expr <- Some {
  382. eexpr = TFunction {
  383. tf_type = basic.tvoid;
  384. tf_args = [alloc_var "empty" empty_ctor_type, None];
  385. tf_expr = mk (TBlock super) basic.tvoid cl.cl_pos
  386. };
  387. etype = empty_type;
  388. epos = cl.cl_pos;
  389. };
  390. ctor.cf_meta <- [Meta.SkipCtor, [], ctor.cf_pos];
  391. Hashtbl.add empty_ctors cl.cl_path ctor;
  392. match cl.cl_constructor with
  393. | None ->
  394. cl.cl_constructor <- Some ctor
  395. | Some c ->
  396. c.cf_overloads <- ctor :: c.cf_overloads
  397. with Exit -> ());
  398. end
  399. in
  400. let module_filter md =
  401. (match md with
  402. | TClassDecl cl when should_change cl ->
  403. change cl;
  404. | _ ->
  405. ());
  406. md
  407. in
  408. module_filter
  409. let init_expr_filter create_empty =
  410. let rec run e =
  411. match e.etype, e.eexpr with
  412. | TInst (cl, params), TCall ({ eexpr = TField (_, FStatic ({cl_path = [],"Type"}, {cf_name = "createEmptyInstance"})) }, [{eexpr = TTypeExpr ((TClassDecl cl_arg) as mt_arg) }]) when cl == cl_arg && is_hxgen mt_arg ->
  413. create_empty cl params e.epos
  414. | _ ->
  415. Type.map_expr run e
  416. in
  417. run
  418. let priority = 0.0
  419. let name = "overloading_constructor"
  420. let configure gen ~empty_ctor_type ~empty_ctor_expr =
  421. gen.gtools.r_create_empty <- (fun cl params pos -> mk (TNew(cl,params,[empty_ctor_expr])) (TInst(cl,params)) pos);
  422. let module_filter = init gen.gcon empty_ctor_type empty_ctor_expr (run_follow gen) in
  423. gen.gmodule_filters#add name (PCustom priority) module_filter;
  424. let expr_filter = init_expr_filter gen.gtools.r_create_empty in
  425. gen.gexpr_filters#add name (PCustom priority) expr_filter