2
0

genjs.ml 34 KB

1234567891011121314151617181920212223242526272829303132333435363738394041424344454647484950515253545556575859606162636465666768697071727374757677787980818283848586878889909192939495969798991001011021031041051061071081091101111121131141151161171181191201211221231241251261271281291301311321331341351361371381391401411421431441451461471481491501511521531541551561571581591601611621631641651661671681691701711721731741751761771781791801811821831841851861871881891901911921931941951961971981992002012022032042052062072082092102112122132142152162172182192202212222232242252262272282292302312322332342352362372382392402412422432442452462472482492502512522532542552562572582592602612622632642652662672682692702712722732742752762772782792802812822832842852862872882892902912922932942952962972982993003013023033043053063073083093103113123133143153163173183193203213223233243253263273283293303313323333343353363373383393403413423433443453463473483493503513523533543553563573583593603613623633643653663673683693703713723733743753763773783793803813823833843853863873883893903913923933943953963973983994004014024034044054064074084094104114124134144154164174184194204214224234244254264274284294304314324334344354364374384394404414424434444454464474484494504514524534544554564574584594604614624634644654664674684694704714724734744754764774784794804814824834844854864874884894904914924934944954964974984995005015025035045055065075085095105115125135145155165175185195205215225235245255265275285295305315325335345355365375385395405415425435445455465475485495505515525535545555565575585595605615625635645655665675685695705715725735745755765775785795805815825835845855865875885895905915925935945955965975985996006016026036046056066076086096106116126136146156166176186196206216226236246256266276286296306316326336346356366376386396406416426436446456466476486496506516526536546556566576586596606616626636646656666676686696706716726736746756766776786796806816826836846856866876886896906916926936946956966976986997007017027037047057067077087097107117127137147157167177187197207217227237247257267277287297307317327337347357367377387397407417427437447457467477487497507517527537547557567577587597607617627637647657667677687697707717727737747757767777787797807817827837847857867877887897907917927937947957967977987998008018028038048058068078088098108118128138148158168178188198208218228238248258268278288298308318328338348358368378388398408418428438448458468478488498508518528538548558568578588598608618628638648658668678688698708718728738748758768778788798808818828838848858868878888898908918928938948958968978988999009019029039049059069079089099109119129139149159169179189199209219229239249259269279289299309319329339349359369379389399409419429439449459469479489499509519529539549559569579589599609619629639649659669679689699709719729739749759769779789799809819829839849859869879889899909919929939949959969979989991000100110021003100410051006100710081009101010111012101310141015101610171018101910201021102210231024102510261027102810291030103110321033103410351036103710381039104010411042104310441045104610471048104910501051105210531054105510561057105810591060106110621063106410651066106710681069107010711072107310741075107610771078107910801081108210831084108510861087108810891090109110921093109410951096109710981099110011011102110311041105110611071108110911101111111211131114111511161117111811191120112111221123112411251126112711281129113011311132113311341135113611371138113911401141114211431144114511461147114811491150115111521153115411551156115711581159116011611162116311641165116611671168116911701171117211731174117511761177117811791180118111821183118411851186118711881189119011911192119311941195119611971198119912001201120212031204120512061207120812091210121112121213121412151216
  1. (*
  2. * Copyright (C)2005-2013 Haxe Foundation
  3. *
  4. * Permission is hereby granted, free of charge, to any person obtaining a
  5. * copy of this software and associated documentation files (the "Software"),
  6. * to deal in the Software without restriction, including without limitation
  7. * the rights to use, copy, modify, merge, publish, distribute, sublicense,
  8. * and/or sell copies of the Software, and to permit persons to whom the
  9. * Software is furnished to do so, subject to the following conditions:
  10. *
  11. * The above copyright notice and this permission notice shall be included in
  12. * all copies or substantial portions of the Software.
  13. *
  14. * THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
  15. * IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
  16. * FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
  17. * AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
  18. * LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
  19. * FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER
  20. * DEALINGS IN THE SOFTWARE.
  21. *)
  22. open Ast
  23. open Type
  24. open Common
  25. type pos = Ast.pos
  26. type sourcemap = {
  27. sources : (string) DynArray.t;
  28. sources_hash : (string, int) Hashtbl.t;
  29. mappings : Buffer.t;
  30. mutable source_last_line : int;
  31. mutable source_last_col : int;
  32. mutable source_last_file : int;
  33. mutable print_comma : bool;
  34. mutable output_last_col : int;
  35. mutable output_current_col : int;
  36. }
  37. type ctx = {
  38. com : Common.context;
  39. buf : Buffer.t;
  40. packages : (string list,unit) Hashtbl.t;
  41. smap : sourcemap;
  42. js_modern : bool;
  43. mutable current : tclass;
  44. mutable statics : (tclass * string * texpr) list;
  45. mutable inits : texpr list;
  46. mutable tabs : string;
  47. mutable in_value : tvar option;
  48. mutable in_loop : bool;
  49. mutable handle_break : bool;
  50. mutable id_counter : int;
  51. mutable type_accessor : module_type -> string;
  52. mutable separator : bool;
  53. mutable found_expose : bool;
  54. }
  55. let s_path ctx = Ast.s_type_path
  56. let kwds =
  57. let h = Hashtbl.create 0 in
  58. List.iter (fun s -> Hashtbl.add h s ()) [
  59. "abstract"; "as"; "boolean"; "break"; "byte"; "case"; "catch"; "char"; "class"; "continue"; "const";
  60. "debugger"; "default"; "delete"; "do"; "double"; "else"; "enum"; "export"; "extends"; "false"; "final";
  61. "finally"; "float"; "for"; "function"; "goto"; "if"; "implements"; "import"; "in"; "instanceof"; "int";
  62. "interface"; "is"; "long"; "namespace"; "native"; "new"; "null"; "package"; "private"; "protected";
  63. "public"; "return"; "short"; "static"; "super"; "switch"; "synchronized"; "this"; "throw"; "throws";
  64. "transient"; "true"; "try"; "typeof"; "use"; "var"; "void"; "volatile"; "while"; "with"
  65. ];
  66. h
  67. let valid_js_ident s =
  68. try
  69. for i = 0 to String.length s - 1 do
  70. match String.unsafe_get s i with
  71. | 'a'..'z' | 'A'..'Z' | '$' | '_' -> ()
  72. | '0'..'9' when i > 0 -> ()
  73. | _ -> raise Exit
  74. done;
  75. true
  76. with Exit ->
  77. false
  78. let field s = if Hashtbl.mem kwds s then "[\"" ^ s ^ "\"]" else "." ^ s
  79. let ident s = if Hashtbl.mem kwds s then "$" ^ s else s
  80. let anon_field s = if Hashtbl.mem kwds s || not (valid_js_ident s) then "'" ^ s ^ "'" else s
  81. let static_field s =
  82. match s with
  83. | "length" | "name" -> ".$" ^ s
  84. | s -> field s
  85. let has_feature ctx = Common.has_feature ctx.com
  86. let add_feature ctx = Common.add_feature ctx.com
  87. let handle_newlines ctx str =
  88. if ctx.com.debug then
  89. let rec loop from =
  90. try begin
  91. let next = String.index_from str from '\n' + 1 in
  92. Buffer.add_char ctx.smap.mappings ';';
  93. ctx.smap.output_last_col <- 0;
  94. ctx.smap.print_comma <- false;
  95. loop next
  96. end with Not_found ->
  97. ctx.smap.output_current_col <- String.length str - from
  98. in
  99. loop 0
  100. else ()
  101. let spr ctx s =
  102. ctx.separator <- false;
  103. handle_newlines ctx s;
  104. Buffer.add_string ctx.buf s
  105. let print ctx =
  106. ctx.separator <- false;
  107. Printf.kprintf (fun s -> begin
  108. handle_newlines ctx s;
  109. Buffer.add_string ctx.buf s
  110. end)
  111. let unsupported p = error "This expression cannot be compiled to Javascript" p
  112. let add_mapping ctx e =
  113. if not ctx.com.debug || e.epos.pmin < 0 then () else
  114. let pos = e.epos in
  115. let smap = ctx.smap in
  116. let file = try
  117. Hashtbl.find smap.sources_hash pos.pfile
  118. with Not_found ->
  119. let length = DynArray.length smap.sources in
  120. Hashtbl.replace smap.sources_hash pos.pfile length;
  121. DynArray.add smap.sources pos.pfile;
  122. length
  123. in
  124. let line, col = Lexer.find_pos pos in
  125. let line = line - 1 in
  126. let col = col - 1 in
  127. if smap.source_last_file != file || smap.source_last_line != line || smap.source_last_col != col then begin
  128. if smap.print_comma then
  129. Buffer.add_char smap.mappings ','
  130. else
  131. smap.print_comma <- true;
  132. let base64_vlq number =
  133. let encode_digit digit =
  134. let chars = [|
  135. 'A';'B';'C';'D';'E';'F';'G';'H';'I';'J';'K';'L';'M';'N';'O';'P';
  136. 'Q';'R';'S';'T';'U';'V';'W';'X';'Y';'Z';'a';'b';'c';'d';'e';'f';
  137. 'g';'h';'i';'j';'k';'l';'m';'n';'o';'p';'q';'r';'s';'t';'u';'v';
  138. 'w';'x';'y';'z';'0';'1';'2';'3';'4';'5';'6';'7';'8';'9';'+';'/'
  139. |] in
  140. Array.unsafe_get chars digit
  141. in
  142. let to_vlq number =
  143. if number < 0 then
  144. ((-number) lsl 1) + 1
  145. else
  146. number lsl 1
  147. in
  148. let rec loop vlq =
  149. let shift = 5 in
  150. let base = 1 lsl shift in
  151. let mask = base - 1 in
  152. let continuation_bit = base in
  153. let digit = vlq land mask in
  154. let next = vlq asr shift in
  155. Buffer.add_char smap.mappings (encode_digit (
  156. if next > 0 then digit lor continuation_bit else digit));
  157. if next > 0 then loop next else ()
  158. in
  159. loop (to_vlq number)
  160. in
  161. base64_vlq (smap.output_current_col - smap.output_last_col);
  162. base64_vlq (file - smap.source_last_file);
  163. base64_vlq (line - smap.source_last_line);
  164. base64_vlq (col - smap.source_last_col);
  165. smap.source_last_file <- file;
  166. smap.source_last_line <- line;
  167. smap.source_last_col <- col;
  168. smap.output_last_col <- smap.output_current_col
  169. end
  170. let basename path =
  171. try
  172. let idx = String.rindex path '/' in
  173. String.sub path (idx + 1) (String.length path - idx - 1)
  174. with Not_found -> path
  175. let write_mappings ctx =
  176. let basefile = basename ctx.com.file in
  177. print ctx "\n//@ sourceMappingURL=%s.map" basefile;
  178. let channel = open_out_bin (ctx.com.file ^ ".map") in
  179. let sources = DynArray.to_list ctx.smap.sources in
  180. let to_url file =
  181. ExtString.String.map (fun c -> if c == '\\' then '/' else c) (Common.get_full_path file)
  182. in
  183. output_string channel "{\n";
  184. output_string channel "\"version\":3,\n";
  185. output_string channel ("\"file\":\"" ^ basefile ^ "\",\n");
  186. output_string channel ("\"sourceRoot\":\"file://\",\n");
  187. output_string channel ("\"sources\":[" ^
  188. (String.concat "," (List.map (fun s -> "\"" ^ to_url s ^ "\"") sources)) ^
  189. "],\n");
  190. output_string channel "\"names\":[],\n";
  191. output_string channel "\"mappings\":\"";
  192. Buffer.output_buffer channel ctx.smap.mappings;
  193. output_string channel "\"\n";
  194. output_string channel "}";
  195. close_out channel
  196. let newline ctx =
  197. match Buffer.nth ctx.buf (Buffer.length ctx.buf - 1) with
  198. | '}' | '{' | ':' when not ctx.separator -> print ctx "\n%s" ctx.tabs
  199. | _ -> print ctx ";\n%s" ctx.tabs
  200. let newprop ctx =
  201. match Buffer.nth ctx.buf (Buffer.length ctx.buf - 1) with
  202. | '{' -> print ctx "\n%s" ctx.tabs
  203. | _ -> print ctx "\n%s," ctx.tabs
  204. let semicolon ctx =
  205. match Buffer.nth ctx.buf (Buffer.length ctx.buf - 1) with
  206. | '}' when not ctx.separator -> ()
  207. | _ -> spr ctx ";"
  208. let rec concat ctx s f = function
  209. | [] -> ()
  210. | [x] -> f x
  211. | x :: l ->
  212. f x;
  213. spr ctx s;
  214. concat ctx s f l
  215. let fun_block ctx f p =
  216. let e = List.fold_left (fun e (a,c) ->
  217. match c with
  218. | None | Some TNull -> e
  219. | Some c -> Codegen.concat (Codegen.set_default ctx.com a c p) e
  220. ) f.tf_expr f.tf_args in
  221. e
  222. let open_block ctx =
  223. let oldt = ctx.tabs in
  224. ctx.tabs <- "\t" ^ ctx.tabs;
  225. (fun() -> ctx.tabs <- oldt)
  226. let rec has_return e =
  227. match e.eexpr with
  228. | TBlock [] -> false
  229. | TBlock el -> has_return (List.hd (List.rev el))
  230. | TReturn _ -> true
  231. | _ -> false
  232. let rec iter_switch_break in_switch e =
  233. match e.eexpr with
  234. | TFunction _ | TWhile _ | TFor _ -> ()
  235. | TSwitch _ | TMatch _ when not in_switch -> iter_switch_break true e
  236. | TBreak when in_switch -> raise Exit
  237. | _ -> iter (iter_switch_break in_switch) e
  238. let handle_break ctx e =
  239. let old = ctx.in_loop, ctx.handle_break in
  240. ctx.in_loop <- true;
  241. try
  242. iter_switch_break false e;
  243. ctx.handle_break <- false;
  244. (fun() ->
  245. ctx.in_loop <- fst old;
  246. ctx.handle_break <- snd old;
  247. )
  248. with
  249. Exit ->
  250. spr ctx "try {";
  251. let b = open_block ctx in
  252. newline ctx;
  253. ctx.handle_break <- true;
  254. (fun() ->
  255. b();
  256. ctx.in_loop <- fst old;
  257. ctx.handle_break <- snd old;
  258. newline ctx;
  259. spr ctx "} catch( e ) { if( e != \"__break__\" ) throw e; }";
  260. )
  261. let handle_expose ctx path meta =
  262. let rec loop = function
  263. | (Meta.Expose, args, pos) :: l when ctx.js_modern ->
  264. ctx.found_expose <- true;
  265. let exposed_path = (match args with
  266. | [EConst (String s), _] -> s
  267. | [] -> path
  268. | _ -> error "Invalid @:expose parameters" pos
  269. ) in
  270. print ctx "$hxExpose(%s, \"%s\")" path exposed_path;
  271. newline ctx
  272. | _ :: l -> loop l
  273. | [] -> ()
  274. in
  275. loop meta
  276. let this ctx = match ctx.in_value with None -> "this" | Some _ -> "$this"
  277. let is_dynamic_iterator ctx e =
  278. let check x =
  279. has_feature ctx "HxOverrides.iter" && (match follow x.etype with TInst ({ cl_path = [],"Array" },_) | TAnon _ | TDynamic _ | TMono _ -> true | _ -> false)
  280. in
  281. match e.eexpr with
  282. | TField (x,f) when field_name f = "iterator" -> check x
  283. | _ ->
  284. false
  285. let gen_constant ctx p = function
  286. | TInt i -> print ctx "%ld" i
  287. | TFloat s -> spr ctx s
  288. | TString s ->
  289. if String.contains s '\000' then error "A String cannot contain \\0 characters" p;
  290. print ctx "\"%s\"" (Ast.s_escape s)
  291. | TBool b -> spr ctx (if b then "true" else "false")
  292. | TNull -> spr ctx "null"
  293. | TThis -> spr ctx (this ctx)
  294. | TSuper -> assert false
  295. let rec gen_call ctx e el in_value =
  296. match e.eexpr , el with
  297. | TConst TSuper , params ->
  298. (match ctx.current.cl_super with
  299. | None -> error "Missing api.setCurrentClass" e.epos
  300. | Some (c,_) ->
  301. print ctx "%s.call(%s" (ctx.type_accessor (TClassDecl c)) (this ctx);
  302. List.iter (fun p -> print ctx ","; gen_value ctx p) params;
  303. spr ctx ")";
  304. );
  305. | TField ({ eexpr = TConst TSuper },f) , params ->
  306. (match ctx.current.cl_super with
  307. | None -> error "Missing api.setCurrentClass" e.epos
  308. | Some (c,_) ->
  309. let name = field_name f in
  310. print ctx "%s.prototype%s.call(%s" (ctx.type_accessor (TClassDecl c)) (field name) (this ctx);
  311. List.iter (fun p -> print ctx ","; gen_value ctx p) params;
  312. spr ctx ")";
  313. );
  314. | TCall (x,_) , el when (match x.eexpr with TLocal { v_name = "__js__" } -> false | _ -> true) ->
  315. spr ctx "(";
  316. gen_value ctx e;
  317. spr ctx ")";
  318. spr ctx "(";
  319. concat ctx "," (gen_value ctx) el;
  320. spr ctx ")";
  321. | TLocal { v_name = "__new__" }, { eexpr = TConst (TString cl) } :: params ->
  322. print ctx "new %s(" cl;
  323. concat ctx "," (gen_value ctx) params;
  324. spr ctx ")";
  325. | TLocal { v_name = "__new__" }, e :: params ->
  326. spr ctx "new ";
  327. gen_value ctx e;
  328. spr ctx "(";
  329. concat ctx "," (gen_value ctx) params;
  330. spr ctx ")";
  331. | TLocal { v_name = "__js__" }, [{ eexpr = TConst (TString code) }] ->
  332. spr ctx (String.concat "\n" (ExtString.String.nsplit code "\r\n"))
  333. | TLocal { v_name = "__instanceof__" }, [o;t] ->
  334. spr ctx "(";
  335. gen_value ctx o;
  336. print ctx " instanceof ";
  337. gen_value ctx t;
  338. spr ctx ")";
  339. | TLocal ({v_name = "__define_feature__"}), [_;e] ->
  340. gen_expr ctx e
  341. | TLocal { v_name = "__feature__" }, { eexpr = TConst (TString f) } :: eif :: eelse ->
  342. (if has_feature ctx f then
  343. gen_value ctx eif
  344. else match eelse with
  345. | [] -> ()
  346. | e :: _ -> gen_value ctx e)
  347. | TLocal { v_name = "__resources__" }, [] ->
  348. spr ctx "[";
  349. concat ctx "," (fun (name,data) ->
  350. spr ctx "{ ";
  351. spr ctx "name : ";
  352. gen_constant ctx e.epos (TString name);
  353. spr ctx ", data : ";
  354. gen_constant ctx e.epos (TString (Codegen.bytes_serialize data));
  355. spr ctx "}"
  356. ) (Hashtbl.fold (fun name data acc -> (name,data) :: acc) ctx.com.resources []);
  357. spr ctx "]";
  358. | TLocal { v_name = "`trace" }, [e;infos] ->
  359. if has_feature ctx "haxe.Log.trace" then begin
  360. let t = (try List.find (fun t -> t_path t = (["haxe"],"Log")) ctx.com.types with _ -> assert false) in
  361. spr ctx (ctx.type_accessor t);
  362. spr ctx ".trace(";
  363. gen_value ctx e;
  364. spr ctx ",";
  365. gen_value ctx infos;
  366. spr ctx ")";
  367. end else begin
  368. spr ctx "console.log(";
  369. gen_value ctx e;
  370. spr ctx ")";
  371. end
  372. | _ ->
  373. gen_value ctx e;
  374. spr ctx "(";
  375. concat ctx "," (gen_value ctx) el;
  376. spr ctx ")"
  377. and gen_expr ctx e =
  378. add_mapping ctx e;
  379. match e.eexpr with
  380. | TConst c -> gen_constant ctx e.epos c
  381. | TLocal v -> spr ctx (ident v.v_name)
  382. | TArray (e1,{ eexpr = TConst (TString s) }) when valid_js_ident s ->
  383. gen_value ctx e1;
  384. spr ctx (field s)
  385. | TArray (e1,e2) ->
  386. gen_value ctx e1;
  387. spr ctx "[";
  388. gen_value ctx e2;
  389. spr ctx "]";
  390. | TBinop (op,{ eexpr = TField (x,f) },e2) when field_name f = "iterator" ->
  391. gen_value ctx x;
  392. spr ctx (field "iterator");
  393. print ctx " %s " (Ast.s_binop op);
  394. gen_value ctx e2;
  395. | TBinop (op,e1,e2) ->
  396. gen_value ctx e1;
  397. print ctx " %s " (Ast.s_binop op);
  398. gen_value ctx e2;
  399. | TField (x,f) when field_name f = "iterator" && is_dynamic_iterator ctx e ->
  400. add_feature ctx "use.$iterator";
  401. print ctx "$iterator(";
  402. gen_value ctx x;
  403. print ctx ")";
  404. | TField (x,FClosure (_,f)) ->
  405. add_feature ctx "use.$bind";
  406. (match x.eexpr with
  407. | TConst _ | TLocal _ ->
  408. print ctx "$bind(";
  409. gen_value ctx x;
  410. print ctx ",";
  411. gen_value ctx x;
  412. print ctx "%s)" (field f.cf_name)
  413. | _ ->
  414. print ctx "($_=";
  415. gen_value ctx x;
  416. print ctx ",$bind($_,$_%s))" (field f.cf_name))
  417. | TField (x,f) ->
  418. gen_value ctx x;
  419. let name = field_name f in
  420. spr ctx (match f with FStatic _ | FEnum _ -> static_field name | FInstance _ | FAnon _ | FDynamic _ | FClosure _ -> field name)
  421. | TTypeExpr t ->
  422. spr ctx (ctx.type_accessor t)
  423. | TParenthesis e ->
  424. spr ctx "(";
  425. gen_value ctx e;
  426. spr ctx ")";
  427. | TReturn eo ->
  428. if ctx.in_value <> None then unsupported e.epos;
  429. (match eo with
  430. | None ->
  431. spr ctx "return"
  432. | Some e ->
  433. spr ctx "return ";
  434. gen_value ctx e);
  435. | TBreak ->
  436. if not ctx.in_loop then unsupported e.epos;
  437. if ctx.handle_break then spr ctx "throw \"__break__\"" else spr ctx "break"
  438. | TContinue ->
  439. if not ctx.in_loop then unsupported e.epos;
  440. spr ctx "continue"
  441. | TBlock el ->
  442. print ctx "{";
  443. let bend = open_block ctx in
  444. List.iter (gen_block ctx) el;
  445. bend();
  446. newline ctx;
  447. print ctx "}";
  448. | TFunction f ->
  449. let old = ctx.in_value, ctx.in_loop in
  450. ctx.in_value <- None;
  451. ctx.in_loop <- false;
  452. print ctx "function(%s) " (String.concat "," (List.map ident (List.map arg_name f.tf_args)));
  453. gen_expr ctx (fun_block ctx f e.epos);
  454. ctx.in_value <- fst old;
  455. ctx.in_loop <- snd old;
  456. ctx.separator <- true
  457. | TCall (e,el) ->
  458. gen_call ctx e el false
  459. | TArrayDecl el ->
  460. spr ctx "[";
  461. concat ctx "," (gen_value ctx) el;
  462. spr ctx "]"
  463. | TThrow e ->
  464. spr ctx "throw ";
  465. gen_value ctx e;
  466. | TVars [] ->
  467. ()
  468. | TVars vl ->
  469. spr ctx "var ";
  470. concat ctx ", " (fun (v,e) ->
  471. spr ctx (ident v.v_name);
  472. match e with
  473. | None -> ()
  474. | Some e ->
  475. spr ctx " = ";
  476. gen_value ctx e
  477. ) vl;
  478. | TNew (c,_,el) ->
  479. print ctx "new %s(" (ctx.type_accessor (TClassDecl c));
  480. concat ctx "," (gen_value ctx) el;
  481. spr ctx ")"
  482. | TIf (cond,e,eelse) ->
  483. spr ctx "if";
  484. gen_value ctx cond;
  485. spr ctx " ";
  486. gen_expr ctx e;
  487. (match eelse with
  488. | None -> ()
  489. | Some e2 ->
  490. (match e.eexpr with
  491. | TObjectDecl _ -> ctx.separator <- false
  492. | _ -> ());
  493. semicolon ctx;
  494. spr ctx " else ";
  495. gen_expr ctx e2);
  496. | TUnop (op,Ast.Prefix,e) ->
  497. spr ctx (Ast.s_unop op);
  498. gen_value ctx e
  499. | TUnop (op,Ast.Postfix,e) ->
  500. gen_value ctx e;
  501. spr ctx (Ast.s_unop op)
  502. | TWhile (cond,e,Ast.NormalWhile) ->
  503. let handle_break = handle_break ctx e in
  504. spr ctx "while";
  505. gen_value ctx cond;
  506. spr ctx " ";
  507. gen_expr ctx e;
  508. handle_break();
  509. | TWhile (cond,e,Ast.DoWhile) ->
  510. let handle_break = handle_break ctx e in
  511. spr ctx "do ";
  512. gen_expr ctx e;
  513. semicolon ctx;
  514. spr ctx " while";
  515. gen_value ctx cond;
  516. handle_break();
  517. | TObjectDecl fields ->
  518. spr ctx "{ ";
  519. concat ctx ", " (fun (f,e) -> print ctx "%s : " (anon_field f); gen_value ctx e) fields;
  520. spr ctx "}";
  521. ctx.separator <- true
  522. | TFor (v,it,e) ->
  523. let handle_break = handle_break ctx e in
  524. let it = ident (match it.eexpr with
  525. | TLocal v -> v.v_name
  526. | _ ->
  527. let id = ctx.id_counter in
  528. ctx.id_counter <- ctx.id_counter + 1;
  529. let name = "$it" ^ string_of_int id in
  530. print ctx "var %s = " name;
  531. gen_value ctx it;
  532. newline ctx;
  533. name
  534. ) in
  535. print ctx "while( %s.hasNext() ) {" it;
  536. let bend = open_block ctx in
  537. newline ctx;
  538. print ctx "var %s = %s.next()" (ident v.v_name) it;
  539. gen_block ctx e;
  540. bend();
  541. newline ctx;
  542. spr ctx "}";
  543. handle_break();
  544. | TTry (e,catchs) ->
  545. spr ctx "try ";
  546. gen_expr ctx e;
  547. let vname = (match catchs with [(v,_)] -> v.v_name | _ ->
  548. let id = ctx.id_counter in
  549. ctx.id_counter <- ctx.id_counter + 1;
  550. "$e" ^ string_of_int id
  551. ) in
  552. print ctx " catch( %s ) {" vname;
  553. let bend = open_block ctx in
  554. let last = ref false in
  555. let else_block = ref false in
  556. List.iter (fun (v,e) ->
  557. if !last then () else
  558. let t = (match follow v.v_type with
  559. | TEnum (e,_) -> Some (TEnumDecl e)
  560. | TInst (c,_) -> Some (TClassDecl c)
  561. | TAbstract (a,_) -> Some (TAbstractDecl a)
  562. | TFun _
  563. | TLazy _
  564. | TType _
  565. | TAnon _ ->
  566. assert false
  567. | TMono _
  568. | TDynamic _ ->
  569. None
  570. ) in
  571. match t with
  572. | None ->
  573. last := true;
  574. if !else_block then print ctx "{";
  575. if vname <> v.v_name then begin
  576. newline ctx;
  577. print ctx "var %s = %s" v.v_name vname;
  578. end;
  579. gen_block ctx e;
  580. if !else_block then begin
  581. newline ctx;
  582. print ctx "}";
  583. end
  584. | Some t ->
  585. if not !else_block then newline ctx;
  586. print ctx "if( %s.__instanceof(%s," (ctx.type_accessor (TClassDecl { null_class with cl_path = ["js"],"Boot" })) vname;
  587. gen_value ctx (mk (TTypeExpr t) (mk_mono()) e.epos);
  588. spr ctx ") ) {";
  589. let bend = open_block ctx in
  590. if vname <> v.v_name then begin
  591. newline ctx;
  592. print ctx "var %s = %s" v.v_name vname;
  593. end;
  594. gen_block ctx e;
  595. bend();
  596. newline ctx;
  597. spr ctx "} else ";
  598. else_block := true
  599. ) catchs;
  600. if not !last then print ctx "throw(%s)" vname;
  601. bend();
  602. newline ctx;
  603. spr ctx "}";
  604. | TMatch (e,(estruct,_),cases,def) ->
  605. let evar = (if List.for_all (fun (_,pl,_) -> pl = None) cases then begin
  606. spr ctx "switch( ";
  607. gen_value ctx (if Optimizer.need_parent e then Codegen.mk_parent e else e);
  608. spr ctx "[1] ) {";
  609. "???"
  610. end else begin
  611. let v = (match e.eexpr with
  612. | TLocal v -> v.v_name
  613. | _ ->
  614. spr ctx "var $e = ";
  615. gen_value ctx e;
  616. newline ctx;
  617. "$e"
  618. ) in
  619. print ctx "switch( %s[1] ) {" v;
  620. v
  621. end) in
  622. List.iter (fun (cl,params,e) ->
  623. List.iter (fun c ->
  624. newline ctx;
  625. print ctx "case %d:" c;
  626. ) cl;
  627. let bend = open_block ctx in
  628. (match params with
  629. | None -> ()
  630. | Some l ->
  631. let n = ref 1 in
  632. let l = List.fold_left (fun acc v -> incr n; match v with None -> acc | Some v -> (v.v_name,!n) :: acc) [] l in
  633. newline ctx;
  634. spr ctx "var ";
  635. concat ctx ", " (fun (v,n) ->
  636. print ctx "%s = %s[%d]" (ident v) evar n;
  637. ) l);
  638. gen_block ctx e;
  639. if not (has_return e) then begin
  640. newline ctx;
  641. print ctx "break";
  642. end;
  643. bend();
  644. ) cases;
  645. (match def with
  646. | None -> ()
  647. | Some e ->
  648. newline ctx;
  649. spr ctx "default:";
  650. let bend = open_block ctx in
  651. gen_block ctx e;
  652. bend();
  653. );
  654. newline ctx;
  655. spr ctx "}"
  656. | TSwitch (e,cases,def) ->
  657. spr ctx "switch";
  658. gen_value ctx e;
  659. spr ctx " {";
  660. newline ctx;
  661. List.iter (fun (el,e2) ->
  662. List.iter (fun e ->
  663. match e.eexpr with
  664. | TConst(c) when c = TNull ->
  665. spr ctx "case null: case undefined:";
  666. | _ ->
  667. spr ctx "case ";
  668. gen_value ctx e;
  669. spr ctx ":"
  670. ) el;
  671. let bend = open_block ctx in
  672. gen_block ctx e2;
  673. if not (has_return e2) then begin
  674. newline ctx;
  675. print ctx "break";
  676. end;
  677. bend();
  678. newline ctx;
  679. ) cases;
  680. (match def with
  681. | None -> ()
  682. | Some e ->
  683. spr ctx "default:";
  684. let bend = open_block ctx in
  685. gen_block ctx e;
  686. bend();
  687. newline ctx;
  688. );
  689. spr ctx "}"
  690. | TCast (e,None) ->
  691. gen_expr ctx e
  692. | TCast (e1,Some t) ->
  693. spr ctx "js.Boot.__cast(";
  694. gen_expr ctx e1;
  695. spr ctx " , ";
  696. spr ctx (ctx.type_accessor t);
  697. spr ctx ")"
  698. and gen_block ?(after=false) ctx e =
  699. match e.eexpr with
  700. | TBlock el ->
  701. List.iter (gen_block ~after ctx) el
  702. | TCall ({ eexpr = TLocal { v_name = "__feature__" } }, { eexpr = TConst (TString f) } :: eif :: eelse) ->
  703. if has_feature ctx f then
  704. gen_block ~after ctx eif
  705. else (match eelse with
  706. | [] -> ()
  707. | [e] -> gen_block ~after ctx e
  708. | _ -> assert false)
  709. | _ ->
  710. if not after then newline ctx;
  711. gen_expr ctx e;
  712. if after then newline ctx
  713. and gen_value ctx e =
  714. add_mapping ctx e;
  715. let assign e =
  716. mk (TBinop (Ast.OpAssign,
  717. mk (TLocal (match ctx.in_value with None -> assert false | Some v -> v)) t_dynamic e.epos,
  718. e
  719. )) e.etype e.epos
  720. in
  721. let value() =
  722. let old = ctx.in_value, ctx.in_loop in
  723. let r = alloc_var "$r" t_dynamic in
  724. ctx.in_value <- Some r;
  725. ctx.in_loop <- false;
  726. spr ctx "(function($this) ";
  727. spr ctx "{";
  728. let b = open_block ctx in
  729. newline ctx;
  730. spr ctx "var $r";
  731. newline ctx;
  732. (fun() ->
  733. newline ctx;
  734. spr ctx "return $r";
  735. b();
  736. newline ctx;
  737. spr ctx "}";
  738. ctx.in_value <- fst old;
  739. ctx.in_loop <- snd old;
  740. print ctx "(%s))" (this ctx)
  741. )
  742. in
  743. match e.eexpr with
  744. | TConst _
  745. | TLocal _
  746. | TArray _
  747. | TBinop _
  748. | TField _
  749. | TTypeExpr _
  750. | TParenthesis _
  751. | TObjectDecl _
  752. | TArrayDecl _
  753. | TNew _
  754. | TUnop _
  755. | TFunction _ ->
  756. gen_expr ctx e
  757. | TCall (e,el) ->
  758. gen_call ctx e el true
  759. | TReturn _
  760. | TBreak
  761. | TContinue ->
  762. unsupported e.epos
  763. | TCast (e1, None) ->
  764. gen_value ctx e1
  765. | TCast (e1, Some t) ->
  766. spr ctx "js.Boot.__cast(";
  767. gen_value ctx e1;
  768. spr ctx " , ";
  769. spr ctx (ctx.type_accessor t);
  770. spr ctx ")"
  771. | TVars _
  772. | TFor _
  773. | TWhile _
  774. | TThrow _ ->
  775. (* value is discarded anyway *)
  776. let v = value() in
  777. gen_expr ctx e;
  778. v()
  779. | TBlock [e] ->
  780. gen_value ctx e
  781. | TBlock el ->
  782. let v = value() in
  783. let rec loop = function
  784. | [] ->
  785. spr ctx "return null";
  786. | [e] ->
  787. gen_expr ctx (assign e);
  788. | e :: l ->
  789. gen_expr ctx e;
  790. newline ctx;
  791. loop l
  792. in
  793. loop el;
  794. v();
  795. | TIf (cond,e,eo) ->
  796. (* remove parenthesis unless it's an operation with higher precedence than ?: *)
  797. let cond = (match cond.eexpr with
  798. | TParenthesis { eexpr = TBinop ((Ast.OpAssign | Ast.OpAssignOp _),_,_) } -> cond
  799. | TParenthesis e -> e
  800. | _ -> cond
  801. ) in
  802. gen_value ctx cond;
  803. spr ctx "?";
  804. gen_value ctx e;
  805. spr ctx ":";
  806. (match eo with
  807. | None -> spr ctx "null"
  808. | Some e -> gen_value ctx e);
  809. | TSwitch (cond,cases,def) ->
  810. let v = value() in
  811. gen_expr ctx (mk (TSwitch (cond,
  812. List.map (fun (e1,e2) -> (e1,assign e2)) cases,
  813. match def with None -> None | Some e -> Some (assign e)
  814. )) e.etype e.epos);
  815. v()
  816. | TMatch (cond,enum,cases,def) ->
  817. let v = value() in
  818. gen_expr ctx (mk (TMatch (cond,enum,
  819. List.map (fun (constr,params,e) -> (constr,params,assign e)) cases,
  820. match def with None -> None | Some e -> Some (assign e)
  821. )) e.etype e.epos);
  822. v()
  823. | TTry (b,catchs) ->
  824. let v = value() in
  825. let block e = mk (TBlock [e]) e.etype e.epos in
  826. gen_expr ctx (mk (TTry (block (assign b),
  827. List.map (fun (v,e) -> v, block (assign e)) catchs
  828. )) e.etype e.epos);
  829. v()
  830. let generate_package_create ctx (p,_) =
  831. let rec loop acc = function
  832. | [] -> ()
  833. | p :: l when Hashtbl.mem ctx.packages (p :: acc) -> loop (p :: acc) l
  834. | p :: l ->
  835. Hashtbl.add ctx.packages (p :: acc) ();
  836. (match acc with
  837. | [] ->
  838. if ctx.js_modern then
  839. print ctx "var %s = {}" p
  840. else
  841. print ctx "var %s = %s || {}" p p
  842. | _ ->
  843. let p = String.concat "." (List.rev acc) ^ (field p) in
  844. if ctx.js_modern then
  845. print ctx "%s = {}" p
  846. else
  847. print ctx "if(!%s) %s = {}" p p
  848. );
  849. newline ctx;
  850. loop (p :: acc) l
  851. in
  852. match p with
  853. | [] -> print ctx "var "
  854. | _ -> loop [] p
  855. let check_field_name c f =
  856. match f.cf_name with
  857. | "prototype" | "__proto__" | "constructor" ->
  858. error ("The field name '" ^ f.cf_name ^ "' is not allowed in JS") (match f.cf_expr with None -> c.cl_pos | Some e -> e.epos);
  859. | _ -> ()
  860. let gen_class_static_field ctx c f =
  861. match f.cf_expr with
  862. | None | Some { eexpr = TConst TNull } when not (has_feature ctx "Type.getClassFields") ->
  863. ()
  864. | None when is_extern_field f ->
  865. ()
  866. | None ->
  867. print ctx "%s%s = null" (s_path ctx c.cl_path) (static_field f.cf_name);
  868. newline ctx
  869. | Some e ->
  870. match e.eexpr with
  871. | TFunction _ ->
  872. let path = (s_path ctx c.cl_path) ^ (static_field f.cf_name) in
  873. ctx.id_counter <- 0;
  874. print ctx "%s = " path;
  875. gen_value ctx e;
  876. ctx.separator <- false;
  877. newline ctx;
  878. handle_expose ctx path f.cf_meta
  879. | _ ->
  880. ctx.statics <- (c,f.cf_name,e) :: ctx.statics
  881. let can_gen_class_field ctx = function
  882. | { cf_expr = (None | Some { eexpr = TConst TNull }) } when not (has_feature ctx "Type.getInstanceFields") ->
  883. false
  884. | f ->
  885. not (is_extern_field f)
  886. let gen_class_field ctx c f =
  887. check_field_name c f;
  888. match f.cf_expr with
  889. | None ->
  890. newprop ctx;
  891. print ctx "%s: " (anon_field f.cf_name);
  892. print ctx "null";
  893. | Some e ->
  894. newprop ctx;
  895. print ctx "%s: " (anon_field f.cf_name);
  896. ctx.id_counter <- 0;
  897. gen_value ctx e;
  898. ctx.separator <- false
  899. let generate_class ctx c =
  900. ctx.current <- c;
  901. ctx.id_counter <- 0;
  902. (match c.cl_path with
  903. | [],"Function" -> error "This class redefine a native one" c.cl_pos
  904. | _ -> ());
  905. let p = s_path ctx c.cl_path in
  906. generate_package_create ctx c.cl_path;
  907. let hxClasses = has_feature ctx "Type.resolveClass" in
  908. if ctx.js_modern || not hxClasses then
  909. print ctx "%s = " p
  910. else
  911. print ctx "%s = $hxClasses[\"%s\"] = " p p;
  912. (match c.cl_constructor with
  913. | Some { cf_expr = Some e } -> gen_expr ctx e
  914. | _ -> print ctx "function() { }");
  915. newline ctx;
  916. if ctx.js_modern && hxClasses then begin
  917. print ctx "$hxClasses[\"%s\"] = %s" p p;
  918. newline ctx;
  919. end;
  920. handle_expose ctx p c.cl_meta;
  921. if has_feature ctx "js.Boot.isClass" then begin
  922. print ctx "%s.__name__ = " p;
  923. if has_feature ctx "Type.getClassName" then
  924. print ctx "[%s]" (String.concat "," (List.map (fun s -> Printf.sprintf "\"%s\"" (Ast.s_escape s)) (fst c.cl_path @ [snd c.cl_path])))
  925. else
  926. print ctx "true";
  927. newline ctx;
  928. end;
  929. (match c.cl_implements with
  930. | [] -> ()
  931. | l ->
  932. print ctx "%s.__interfaces__ = [%s]" p (String.concat "," (List.map (fun (i,_) -> s_path ctx i.cl_path) l));
  933. newline ctx;
  934. );
  935. let gen_props props =
  936. String.concat "," (List.map (fun (p,v) -> p ^":\""^v^"\"") props) in
  937. let has_property_reflection =
  938. (has_feature ctx "Reflect.getProperty") || (has_feature ctx "Reflect.setProperty") in
  939. if has_property_reflection then begin
  940. (match Codegen.get_properties c.cl_ordered_statics with
  941. | [] -> ()
  942. | props ->
  943. print ctx "%s.__properties__ = {%s}" p (gen_props props);
  944. newline ctx);
  945. end;
  946. List.iter (gen_class_static_field ctx c) c.cl_ordered_statics;
  947. let has_class = has_feature ctx "js.Boot.getClass" && (c.cl_super <> None || c.cl_ordered_fields <> [] || c.cl_constructor <> None) in
  948. let has_prototype = c.cl_super <> None || has_class || List.exists (can_gen_class_field ctx) c.cl_ordered_fields in
  949. if has_prototype then begin
  950. (match c.cl_super with
  951. | None -> print ctx "%s.prototype = {" p;
  952. | Some (csup,_) ->
  953. let psup = s_path ctx csup.cl_path in
  954. print ctx "%s.__super__ = %s" p psup;
  955. newline ctx;
  956. print ctx "%s.prototype = $extend(%s.prototype,{" p psup;
  957. );
  958. let bend = open_block ctx in
  959. List.iter (fun f -> if can_gen_class_field ctx f then gen_class_field ctx c f) c.cl_ordered_fields;
  960. if has_class then begin
  961. newprop ctx;
  962. print ctx "__class__: %s" p;
  963. end;
  964. if has_property_reflection then begin
  965. let props = Codegen.get_properties c.cl_ordered_fields in
  966. (match c.cl_super with
  967. | _ when props = [] -> ()
  968. | Some (csup,_) when Codegen.has_properties csup ->
  969. newprop ctx;
  970. let psup = s_path ctx csup.cl_path in
  971. print ctx "__properties__: $extend(%s.prototype.__properties__,{%s})" psup (gen_props props)
  972. | _ ->
  973. newprop ctx;
  974. print ctx "__properties__: {%s}" (gen_props props));
  975. end;
  976. bend();
  977. print ctx "\n}";
  978. (match c.cl_super with None -> () | _ -> print ctx ")");
  979. newline ctx
  980. end
  981. let generate_enum ctx e =
  982. let p = s_path ctx e.e_path in
  983. generate_package_create ctx e.e_path;
  984. let ename = List.map (fun s -> Printf.sprintf "\"%s\"" (Ast.s_escape s)) (fst e.e_path @ [snd e.e_path]) in
  985. print ctx "%s = " p;
  986. if has_feature ctx "Type.resolveEnum" then print ctx "$hxClasses[\"%s\"] = " p;
  987. print ctx "{";
  988. if has_feature ctx "js.Boot.isEnum" then print ctx " __ename__ : %s," (if has_feature ctx "Type.getEnumName" then "[" ^ String.concat "," ename ^ "]" else "true");
  989. print ctx " __constructs__ : [%s] }" (String.concat "," (List.map (fun s -> Printf.sprintf "\"%s\"" s) e.e_names));
  990. newline ctx;
  991. List.iter (fun n ->
  992. let f = PMap.find n e.e_constrs in
  993. print ctx "%s%s = " p (field f.ef_name);
  994. (match f.ef_type with
  995. | TFun (args,_) ->
  996. let sargs = String.concat "," (List.map (fun (n,_,_) -> ident n) args) in
  997. print ctx "function(%s) { var $x = [\"%s\",%d,%s]; $x.__enum__ = %s; $x.toString = $estr; return $x; }" sargs f.ef_name f.ef_index sargs p;
  998. | _ ->
  999. print ctx "[\"%s\",%d]" f.ef_name f.ef_index;
  1000. newline ctx;
  1001. print ctx "%s%s.toString = $estr" p (field f.ef_name);
  1002. newline ctx;
  1003. print ctx "%s%s.__enum__ = %s" p (field f.ef_name) p;
  1004. );
  1005. newline ctx
  1006. ) e.e_names;
  1007. match Codegen.build_metadata ctx.com (TEnumDecl e) with
  1008. | None -> ()
  1009. | Some e ->
  1010. print ctx "%s.__meta__ = " p;
  1011. gen_expr ctx e;
  1012. newline ctx
  1013. let generate_static ctx (c,f,e) =
  1014. print ctx "%s%s = " (s_path ctx c.cl_path) (static_field f);
  1015. gen_value ctx e;
  1016. newline ctx
  1017. let generate_type ctx = function
  1018. | TClassDecl c ->
  1019. (match c.cl_init with
  1020. | None -> ()
  1021. | Some e ->
  1022. ctx.inits <- e :: ctx.inits);
  1023. if not c.cl_extern then generate_class ctx c else if Meta.has Meta.InitPackage c.cl_meta then generate_package_create ctx c.cl_path
  1024. | TEnumDecl e when e.e_extern ->
  1025. ()
  1026. | TEnumDecl e -> generate_enum ctx e
  1027. | TTypeDecl _ | TAbstractDecl _ -> ()
  1028. let set_current_class ctx c =
  1029. ctx.current <- c
  1030. let alloc_ctx com =
  1031. let ctx = {
  1032. com = com;
  1033. buf = Buffer.create 16000;
  1034. packages = Hashtbl.create 0;
  1035. smap = {
  1036. source_last_line = 0;
  1037. source_last_col = 0;
  1038. source_last_file = 0;
  1039. print_comma = false;
  1040. output_last_col = 0;
  1041. output_current_col = 0;
  1042. sources = DynArray.create();
  1043. sources_hash = Hashtbl.create 0;
  1044. mappings = Buffer.create 16;
  1045. };
  1046. js_modern = not (Common.defined com Define.JsClassic);
  1047. statics = [];
  1048. inits = [];
  1049. current = null_class;
  1050. tabs = "";
  1051. in_value = None;
  1052. in_loop = false;
  1053. handle_break = false;
  1054. id_counter = 0;
  1055. type_accessor = (fun _ -> assert false);
  1056. separator = false;
  1057. found_expose = false;
  1058. } in
  1059. ctx.type_accessor <- (fun t -> s_path ctx (t_path t));
  1060. ctx
  1061. let gen_single_expr ctx e expr =
  1062. if expr then gen_expr ctx e else gen_value ctx e;
  1063. let str = Buffer.contents ctx.buf in
  1064. Buffer.reset ctx.buf;
  1065. ctx.id_counter <- 0;
  1066. str
  1067. let generate com =
  1068. let t = Common.timer "generate js" in
  1069. (match com.js_gen with
  1070. | Some g -> g()
  1071. | None ->
  1072. let ctx = alloc_ctx com in
  1073. if has_feature ctx "Class" || has_feature ctx "Type.getClassName" then add_feature ctx "js.Boot.isClass";
  1074. if has_feature ctx "Enum" || has_feature ctx "Type.getEnumName" then add_feature ctx "js.Boot.isEnum";
  1075. if ctx.js_modern then begin
  1076. (* Additional ES5 strict mode keywords. *)
  1077. List.iter (fun s -> Hashtbl.replace kwds s ()) [ "arguments"; "eval" ];
  1078. (* Wrap output in a closure. *)
  1079. print ctx "(function () { \"use strict\"";
  1080. newline ctx;
  1081. end;
  1082. let vars = [] in
  1083. let vars = (if has_feature ctx "Type.resolveClass" || has_feature ctx "Type.resolveEnum" then ("$hxClasses = " ^ (if ctx.js_modern then "{}" else "$hxClasses || {}")) :: vars else vars) in
  1084. let vars = (if List.exists (function TEnumDecl { e_extern = false } -> true | _ -> false) com.types then "$estr = function() { return js.Boot.__string_rec(this,''); }" :: vars else vars) in
  1085. (match List.rev vars with
  1086. | [] -> ()
  1087. | vl ->
  1088. print ctx "var %s" (String.concat "," vl);
  1089. ctx.separator <- true;
  1090. newline ctx
  1091. );
  1092. if List.exists (function TClassDecl { cl_extern = false; cl_super = Some _ } -> true | _ -> false) com.types then begin
  1093. print ctx "function $extend(from, fields) {
  1094. function inherit() {}; inherit.prototype = from; var proto = new inherit();
  1095. for (var name in fields) proto[name] = fields[name];
  1096. if( fields.toString !== Object.prototype.toString ) proto.toString = fields.toString;
  1097. return proto;
  1098. }
  1099. ";
  1100. end;
  1101. List.iter (generate_type ctx) com.types;
  1102. let rec chk_features e =
  1103. if is_dynamic_iterator ctx e then add_feature ctx "use.$iterator";
  1104. match e.eexpr with
  1105. | TField (_,FClosure _) ->
  1106. add_feature ctx "use.$bind"
  1107. | _ ->
  1108. Type.iter chk_features e
  1109. in
  1110. List.iter chk_features ctx.inits;
  1111. List.iter (fun (_,_,e) -> chk_features e) ctx.statics;
  1112. if has_feature ctx "use.$iterator" then begin
  1113. add_feature ctx "use.$bind";
  1114. print ctx "function $iterator(o) { if( o instanceof Array ) return function() { return HxOverrides.iter(o); }; return typeof(o.iterator) == 'function' ? $bind(o,o.iterator) : o.iterator; }";
  1115. ctx.separator <- true;
  1116. newline ctx;
  1117. end;
  1118. if has_feature ctx "use.$bind" then begin
  1119. print ctx "var $_, $fid = 0";
  1120. newline ctx;
  1121. print ctx "function $bind(o,m) { if( m == null ) return null; if( m.__id__ == null ) m.__id__ = $fid++; var f; if( o.hx__closures__ == null ) o.hx__closures__ = {}; else f = o.hx__closures__[m.__id__]; if( f == null ) { f = function(){ return f.method.apply(f.scope, arguments); }; f.scope = o; f.method = m; o.hx__closures__[m.__id__] = f; } return f; }";
  1122. ctx.separator <- true;
  1123. newline ctx;
  1124. end;
  1125. List.iter (gen_block ~after:true ctx) (List.rev ctx.inits);
  1126. List.iter (generate_static ctx) (List.rev ctx.statics);
  1127. (match com.main with
  1128. | None -> ()
  1129. | Some e -> gen_expr ctx e; newline ctx);
  1130. if ctx.found_expose then begin
  1131. (* TODO(bruno): Remove runtime branching when standard node haxelib is available *)
  1132. print ctx
  1133. "function $hxExpose(src, path) {
  1134. var o = typeof window != \"undefined\" ? window : exports;
  1135. var parts = path.split(\".\");
  1136. for(var ii = 0; ii < parts.length-1; ++ii) {
  1137. var p = parts[ii];
  1138. if(typeof o[p] == \"undefined\") o[p] = {};
  1139. o = o[p];
  1140. }
  1141. o[parts[parts.length-1]] = src;
  1142. }";
  1143. newline ctx;
  1144. end;
  1145. if ctx.js_modern then begin
  1146. print ctx "})()";
  1147. newline ctx;
  1148. end;
  1149. if com.debug then write_mappings ctx else (try Sys.remove (com.file ^ ".map") with _ -> ());
  1150. let ch = open_out_bin com.file in
  1151. output_string ch (Buffer.contents ctx.buf);
  1152. close_out ch);
  1153. t()