genjs.ml 43 KB

1234567891011121314151617181920212223242526272829303132333435363738394041424344454647484950515253545556575859606162636465666768697071727374757677787980818283848586878889909192939495969798991001011021031041051061071081091101111121131141151161171181191201211221231241251261271281291301311321331341351361371381391401411421431441451461471481491501511521531541551561571581591601611621631641651661671681691701711721731741751761771781791801811821831841851861871881891901911921931941951961971981992002012022032042052062072082092102112122132142152162172182192202212222232242252262272282292302312322332342352362372382392402412422432442452462472482492502512522532542552562572582592602612622632642652662672682692702712722732742752762772782792802812822832842852862872882892902912922932942952962972982993003013023033043053063073083093103113123133143153163173183193203213223233243253263273283293303313323333343353363373383393403413423433443453463473483493503513523533543553563573583593603613623633643653663673683693703713723733743753763773783793803813823833843853863873883893903913923933943953963973983994004014024034044054064074084094104114124134144154164174184194204214224234244254264274284294304314324334344354364374384394404414424434444454464474484494504514524534544554564574584594604614624634644654664674684694704714724734744754764774784794804814824834844854864874884894904914924934944954964974984995005015025035045055065075085095105115125135145155165175185195205215225235245255265275285295305315325335345355365375385395405415425435445455465475485495505515525535545555565575585595605615625635645655665675685695705715725735745755765775785795805815825835845855865875885895905915925935945955965975985996006016026036046056066076086096106116126136146156166176186196206216226236246256266276286296306316326336346356366376386396406416426436446456466476486496506516526536546556566576586596606616626636646656666676686696706716726736746756766776786796806816826836846856866876886896906916926936946956966976986997007017027037047057067077087097107117127137147157167177187197207217227237247257267277287297307317327337347357367377387397407417427437447457467477487497507517527537547557567577587597607617627637647657667677687697707717727737747757767777787797807817827837847857867877887897907917927937947957967977987998008018028038048058068078088098108118128138148158168178188198208218228238248258268278288298308318328338348358368378388398408418428438448458468478488498508518528538548558568578588598608618628638648658668678688698708718728738748758768778788798808818828838848858868878888898908918928938948958968978988999009019029039049059069079089099109119129139149159169179189199209219229239249259269279289299309319329339349359369379389399409419429439449459469479489499509519529539549559569579589599609619629639649659669679689699709719729739749759769779789799809819829839849859869879889899909919929939949959969979989991000100110021003100410051006100710081009101010111012101310141015101610171018101910201021102210231024102510261027102810291030103110321033103410351036103710381039104010411042104310441045104610471048104910501051105210531054105510561057105810591060106110621063106410651066106710681069107010711072107310741075107610771078107910801081108210831084108510861087108810891090109110921093109410951096109710981099110011011102110311041105110611071108110911101111111211131114111511161117111811191120112111221123112411251126112711281129113011311132113311341135113611371138113911401141114211431144114511461147114811491150115111521153115411551156115711581159116011611162116311641165116611671168116911701171117211731174117511761177117811791180118111821183118411851186118711881189119011911192119311941195119611971198119912001201120212031204120512061207120812091210121112121213121412151216121712181219122012211222122312241225122612271228122912301231123212331234123512361237123812391240124112421243124412451246124712481249125012511252125312541255125612571258125912601261126212631264126512661267126812691270127112721273127412751276127712781279128012811282128312841285128612871288128912901291129212931294129512961297129812991300130113021303130413051306130713081309131013111312131313141315131613171318131913201321132213231324132513261327132813291330133113321333133413351336133713381339134013411342134313441345134613471348134913501351135213531354135513561357135813591360136113621363136413651366136713681369137013711372137313741375137613771378137913801381138213831384138513861387138813891390139113921393139413951396139713981399140014011402140314041405140614071408140914101411141214131414141514161417141814191420142114221423142414251426142714281429143014311432143314341435
  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 : Rbuffer.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 : Rbuffer.t;
  40. chan : out_channel;
  41. packages : (string list,unit) Hashtbl.t;
  42. smap : sourcemap;
  43. js_modern : bool;
  44. js_flatten : bool;
  45. mutable current : tclass;
  46. mutable statics : (tclass * string * texpr) list;
  47. mutable inits : texpr list;
  48. mutable tabs : string;
  49. mutable in_value : tvar option;
  50. mutable in_loop : bool;
  51. mutable handle_break : bool;
  52. mutable id_counter : int;
  53. mutable type_accessor : module_type -> string;
  54. mutable separator : bool;
  55. mutable found_expose : bool;
  56. }
  57. type object_store = {
  58. os_name : string;
  59. mutable os_fields : object_store list;
  60. }
  61. let get_exposed ctx path meta =
  62. if not ctx.js_modern then []
  63. else try
  64. let (_, args, pos) = Meta.get Meta.Expose meta in
  65. (match args with
  66. | [ EConst (String s), _ ] -> [s]
  67. | [] -> [path]
  68. | _ -> error "Invalid @:expose parameters" pos)
  69. with Not_found -> []
  70. let dot_path = Ast.s_type_path
  71. let flat_path (p,s) =
  72. (* Replace _ with _$ in paths to prevent name collisions. *)
  73. let escape str = String.concat "_$" (ExtString.String.nsplit str "_") in
  74. match p with
  75. | [] -> escape s
  76. | _ -> String.concat "_" (List.map escape p) ^ "_" ^ (escape s)
  77. let s_path ctx = if ctx.js_flatten then flat_path else dot_path
  78. let kwds =
  79. let h = Hashtbl.create 0 in
  80. List.iter (fun s -> Hashtbl.add h s ()) [
  81. "abstract"; "as"; "boolean"; "break"; "byte"; "case"; "catch"; "char"; "class"; "continue"; "const";
  82. "debugger"; "default"; "delete"; "do"; "double"; "else"; "enum"; "export"; "extends"; "false"; "final";
  83. "finally"; "float"; "for"; "function"; "goto"; "if"; "implements"; "import"; "in"; "instanceof"; "int";
  84. "interface"; "is"; "let"; "long"; "namespace"; "native"; "new"; "null"; "package"; "private"; "protected";
  85. "public"; "return"; "short"; "static"; "super"; "switch"; "synchronized"; "this"; "throw"; "throws";
  86. "transient"; "true"; "try"; "typeof"; "use"; "var"; "void"; "volatile"; "while"; "with"; "yield"
  87. ];
  88. h
  89. (* Identifiers Haxe reserves to make the JS output cleaner. These can still be used in untyped code (TLocal),
  90. but are escaped upon declaration. *)
  91. let kwds2 =
  92. let h = Hashtbl.create 0 in
  93. List.iter (fun s -> Hashtbl.add h s ()) [
  94. (* https://developer.mozilla.org/en-US/docs/Web/JavaScript/Reference/Global_Objects *)
  95. "Infinity"; "NaN"; "decodeURI"; "decodeURIComponent"; "encodeURI"; "encodeURIComponent";
  96. "escape"; "eval"; "isFinite"; "isNaN"; "parseFloat"; "parseInt"; "undefined"; "unescape";
  97. "JSON"; "Number"; "Object"; "console"; "window"; "require";
  98. ];
  99. h
  100. let valid_js_ident s =
  101. String.length s > 0 && try
  102. for i = 0 to String.length s - 1 do
  103. match String.unsafe_get s i with
  104. | 'a'..'z' | 'A'..'Z' | '$' | '_' -> ()
  105. | '0'..'9' when i > 0 -> ()
  106. | _ -> raise Exit
  107. done;
  108. true
  109. with Exit ->
  110. false
  111. let field s = if Hashtbl.mem kwds s || not (valid_js_ident s) then "[\"" ^ s ^ "\"]" else "." ^ s
  112. let ident s = if Hashtbl.mem kwds s then "$" ^ s else s
  113. let check_var_declaration v = if Hashtbl.mem kwds2 v.v_name then v.v_name <- "$" ^ v.v_name
  114. let anon_field s = if Hashtbl.mem kwds s || not (valid_js_ident s) then "'" ^ s ^ "'" else s
  115. let static_field c s =
  116. match s with
  117. | "length" | "name" when not c.cl_extern || Meta.has Meta.HxGen c.cl_meta-> ".$" ^ s
  118. | s -> field s
  119. let has_feature ctx = Common.has_feature ctx.com
  120. let add_feature ctx = Common.add_feature ctx.com
  121. let handle_newlines ctx str =
  122. if ctx.com.debug then
  123. let rec loop from =
  124. try begin
  125. let next = String.index_from str from '\n' + 1 in
  126. Rbuffer.add_char ctx.smap.mappings ';';
  127. ctx.smap.output_last_col <- 0;
  128. ctx.smap.print_comma <- false;
  129. loop next
  130. end with Not_found ->
  131. ctx.smap.output_current_col <- String.length str - from
  132. in
  133. loop 0
  134. else ()
  135. let flush ctx =
  136. Rbuffer.output_buffer ctx.chan ctx.buf;
  137. Rbuffer.clear ctx.buf
  138. let spr ctx s =
  139. ctx.separator <- false;
  140. handle_newlines ctx s;
  141. Rbuffer.add_string ctx.buf s
  142. let print ctx =
  143. ctx.separator <- false;
  144. Printf.kprintf (fun s -> begin
  145. handle_newlines ctx s;
  146. Rbuffer.add_string ctx.buf s
  147. end)
  148. let unsupported p = error "This expression cannot be compiled to Javascript" p
  149. let add_mapping ctx e =
  150. if not ctx.com.debug || e.epos.pmin < 0 then () else
  151. let pos = e.epos in
  152. let smap = ctx.smap in
  153. let file = try
  154. Hashtbl.find smap.sources_hash pos.pfile
  155. with Not_found ->
  156. let length = DynArray.length smap.sources in
  157. Hashtbl.replace smap.sources_hash pos.pfile length;
  158. DynArray.add smap.sources pos.pfile;
  159. length
  160. in
  161. let line, col = Lexer.find_pos pos in
  162. let line = line - 1 in
  163. let col = col - 1 in
  164. if smap.source_last_file != file || smap.source_last_line != line || smap.source_last_col != col then begin
  165. if smap.print_comma then
  166. Rbuffer.add_char smap.mappings ','
  167. else
  168. smap.print_comma <- true;
  169. let base64_vlq number =
  170. let encode_digit digit =
  171. let chars = [|
  172. 'A';'B';'C';'D';'E';'F';'G';'H';'I';'J';'K';'L';'M';'N';'O';'P';
  173. 'Q';'R';'S';'T';'U';'V';'W';'X';'Y';'Z';'a';'b';'c';'d';'e';'f';
  174. 'g';'h';'i';'j';'k';'l';'m';'n';'o';'p';'q';'r';'s';'t';'u';'v';
  175. 'w';'x';'y';'z';'0';'1';'2';'3';'4';'5';'6';'7';'8';'9';'+';'/'
  176. |] in
  177. Array.unsafe_get chars digit
  178. in
  179. let to_vlq number =
  180. if number < 0 then
  181. ((-number) lsl 1) + 1
  182. else
  183. number lsl 1
  184. in
  185. let rec loop vlq =
  186. let shift = 5 in
  187. let base = 1 lsl shift in
  188. let mask = base - 1 in
  189. let continuation_bit = base in
  190. let digit = vlq land mask in
  191. let next = vlq asr shift in
  192. Rbuffer.add_char smap.mappings (encode_digit (
  193. if next > 0 then digit lor continuation_bit else digit));
  194. if next > 0 then loop next else ()
  195. in
  196. loop (to_vlq number)
  197. in
  198. base64_vlq (smap.output_current_col - smap.output_last_col);
  199. base64_vlq (file - smap.source_last_file);
  200. base64_vlq (line - smap.source_last_line);
  201. base64_vlq (col - smap.source_last_col);
  202. smap.source_last_file <- file;
  203. smap.source_last_line <- line;
  204. smap.source_last_col <- col;
  205. smap.output_last_col <- smap.output_current_col
  206. end
  207. let write_mappings ctx =
  208. let basefile = Filename.basename ctx.com.file in
  209. print ctx "\n//# sourceMappingURL=%s.map" basefile;
  210. let channel = open_out_bin (ctx.com.file ^ ".map") in
  211. let sources = DynArray.to_list ctx.smap.sources in
  212. let to_url file =
  213. ExtString.String.map (fun c -> if c == '\\' then '/' else c) (Common.get_full_path file)
  214. in
  215. output_string channel "{\n";
  216. output_string channel "\"version\":3,\n";
  217. output_string channel ("\"file\":\"" ^ (String.concat "\\\\" (ExtString.String.nsplit basefile "\\")) ^ "\",\n");
  218. output_string channel ("\"sourceRoot\":\"file:///\",\n");
  219. output_string channel ("\"sources\":[" ^
  220. (String.concat "," (List.map (fun s -> "\"" ^ to_url s ^ "\"") sources)) ^
  221. "],\n");
  222. if Common.defined ctx.com Define.SourceMapContent then begin
  223. output_string channel ("\"sourcesContent\":[" ^
  224. (String.concat "," (List.map (fun s -> try "\"" ^ Ast.s_escape (Std.input_file ~bin:true s) ^ "\"" with _ -> "null") sources)) ^
  225. "],\n");
  226. end;
  227. output_string channel "\"names\":[],\n";
  228. output_string channel "\"mappings\":\"";
  229. Rbuffer.output_buffer channel ctx.smap.mappings;
  230. output_string channel "\"\n";
  231. output_string channel "}";
  232. close_out channel
  233. let newline ctx =
  234. match Rbuffer.nth ctx.buf (Rbuffer.length ctx.buf - 1) with
  235. | '}' | '{' | ':' | ';' when not ctx.separator -> print ctx "\n%s" ctx.tabs
  236. | _ -> print ctx ";\n%s" ctx.tabs
  237. let newprop ctx =
  238. match Rbuffer.nth ctx.buf (Rbuffer.length ctx.buf - 1) with
  239. | '{' -> print ctx "\n%s" ctx.tabs
  240. | _ -> print ctx "\n%s," ctx.tabs
  241. let semicolon ctx =
  242. match Rbuffer.nth ctx.buf (Rbuffer.length ctx.buf - 1) with
  243. | '}' when not ctx.separator -> ()
  244. | _ -> spr ctx ";"
  245. let rec concat ctx s f = function
  246. | [] -> ()
  247. | [x] -> f x
  248. | x :: l ->
  249. f x;
  250. spr ctx s;
  251. concat ctx s f l
  252. let fun_block ctx f p =
  253. let e = List.fold_left (fun e (a,c) ->
  254. match c with
  255. | None | Some TNull -> e
  256. | Some c -> Type.concat (Codegen.set_default ctx.com a c p) e
  257. ) f.tf_expr f.tf_args in
  258. e
  259. let open_block ctx =
  260. let oldt = ctx.tabs in
  261. ctx.tabs <- "\t" ^ ctx.tabs;
  262. (fun() -> ctx.tabs <- oldt)
  263. let rec has_return e =
  264. match e.eexpr with
  265. | TBlock [] -> false
  266. | TBlock el -> has_return (List.hd (List.rev el))
  267. | TReturn _ -> true
  268. | _ -> false
  269. let rec iter_switch_break in_switch e =
  270. match e.eexpr with
  271. | TFunction _ | TWhile _ | TFor _ -> ()
  272. | TSwitch _ when not in_switch -> iter_switch_break true e
  273. | TBreak when in_switch -> raise Exit
  274. | _ -> iter (iter_switch_break in_switch) e
  275. let handle_break ctx e =
  276. let old = ctx.in_loop, ctx.handle_break in
  277. ctx.in_loop <- true;
  278. try
  279. iter_switch_break false e;
  280. ctx.handle_break <- false;
  281. (fun() ->
  282. ctx.in_loop <- fst old;
  283. ctx.handle_break <- snd old;
  284. )
  285. with
  286. Exit ->
  287. spr ctx "try {";
  288. let b = open_block ctx in
  289. newline ctx;
  290. ctx.handle_break <- true;
  291. (fun() ->
  292. b();
  293. ctx.in_loop <- fst old;
  294. ctx.handle_break <- snd old;
  295. newline ctx;
  296. spr ctx "} catch( e ) { if( e != \"__break__\" ) throw e; }";
  297. )
  298. let this ctx = match ctx.in_value with None -> "this" | Some _ -> "$this"
  299. let is_dynamic_iterator ctx e =
  300. let check x =
  301. has_feature ctx "HxOverrides.iter" && (match follow x.etype with
  302. | TInst ({ cl_path = [],"Array" },_)
  303. | TInst ({ cl_kind = KTypeParameter _}, _)
  304. | TAnon _
  305. | TDynamic _
  306. | TMono _ ->
  307. true
  308. | _ -> false
  309. )
  310. in
  311. match e.eexpr with
  312. | TField (x,f) when field_name f = "iterator" -> check x
  313. | _ ->
  314. false
  315. let gen_constant ctx p = function
  316. | TInt i -> print ctx "%ld" i
  317. | TFloat s -> spr ctx s
  318. | TString s -> print ctx "\"%s\"" (Ast.s_escape s)
  319. | TBool b -> spr ctx (if b then "true" else "false")
  320. | TNull -> spr ctx "null"
  321. | TThis -> spr ctx (this ctx)
  322. | TSuper -> assert false
  323. let rec gen_call ctx e el in_value =
  324. match e.eexpr , el with
  325. | TConst TSuper , params ->
  326. (match ctx.current.cl_super with
  327. | None -> error "Missing api.setCurrentClass" e.epos
  328. | Some (c,_) ->
  329. print ctx "%s.call(%s" (ctx.type_accessor (TClassDecl c)) (this ctx);
  330. List.iter (fun p -> print ctx ","; gen_value ctx p) params;
  331. spr ctx ")";
  332. );
  333. | TField ({ eexpr = TConst TSuper },f) , params ->
  334. (match ctx.current.cl_super with
  335. | None -> error "Missing api.setCurrentClass" e.epos
  336. | Some (c,_) ->
  337. let name = field_name f in
  338. print ctx "%s.prototype%s.call(%s" (ctx.type_accessor (TClassDecl c)) (field name) (this ctx);
  339. List.iter (fun p -> print ctx ","; gen_value ctx p) params;
  340. spr ctx ")";
  341. );
  342. | TCall (x,_) , el when (match x.eexpr with TLocal { v_name = "__js__" } -> false | _ -> true) ->
  343. spr ctx "(";
  344. gen_value ctx e;
  345. spr ctx ")";
  346. spr ctx "(";
  347. concat ctx "," (gen_value ctx) el;
  348. spr ctx ")";
  349. | TLocal { v_name = "__new__" }, { eexpr = TConst (TString cl) } :: params ->
  350. print ctx "new %s(" cl;
  351. concat ctx "," (gen_value ctx) params;
  352. spr ctx ")";
  353. | TLocal { v_name = "__new__" }, e :: params ->
  354. spr ctx "new ";
  355. gen_value ctx e;
  356. spr ctx "(";
  357. concat ctx "," (gen_value ctx) params;
  358. spr ctx ")";
  359. | TLocal { v_name = "__js__" }, [{ eexpr = TConst (TString "this") }] ->
  360. spr ctx (this ctx)
  361. | TLocal { v_name = "__js__" }, [{ eexpr = TConst (TString code) }] ->
  362. spr ctx (String.concat "\n" (ExtString.String.nsplit code "\r\n"))
  363. | TLocal { v_name = "__js__" }, { eexpr = TConst (TString code); epos = p } :: tl ->
  364. Codegen.interpolate_code ctx.com code tl (spr ctx) (gen_expr ctx) p
  365. | TLocal { v_name = "__instanceof__" }, [o;t] ->
  366. spr ctx "(";
  367. gen_value ctx o;
  368. print ctx " instanceof ";
  369. gen_value ctx t;
  370. spr ctx ")";
  371. | TLocal { v_name = "__typeof__" }, [o] ->
  372. spr ctx "typeof(";
  373. gen_value ctx o;
  374. spr ctx ")";
  375. | TLocal { v_name = "__strict_eq__" } , [x;y] ->
  376. (* add extra parenthesis here because of operator precedence *)
  377. spr ctx "((";
  378. gen_value ctx x;
  379. spr ctx ") === ";
  380. gen_value ctx y;
  381. spr ctx ")";
  382. | TLocal { v_name = "__strict_neq__" } , [x;y] ->
  383. (* add extra parenthesis here because of operator precedence *)
  384. spr ctx "((";
  385. gen_value ctx x;
  386. spr ctx ") !== ";
  387. gen_value ctx y;
  388. spr ctx ")";
  389. | TLocal ({v_name = "__define_feature__"}), [_;e] ->
  390. gen_expr ctx e
  391. | TLocal { v_name = "__feature__" }, { eexpr = TConst (TString f) } :: eif :: eelse ->
  392. (if has_feature ctx f then
  393. gen_value ctx eif
  394. else match eelse with
  395. | [] -> ()
  396. | e :: _ -> gen_value ctx e)
  397. | TLocal { v_name = "__resources__" }, [] ->
  398. spr ctx "[";
  399. concat ctx "," (fun (name,data) ->
  400. spr ctx "{ ";
  401. spr ctx "name : ";
  402. gen_constant ctx e.epos (TString name);
  403. spr ctx ", data : ";
  404. gen_constant ctx e.epos (TString (Codegen.bytes_serialize data));
  405. spr ctx "}"
  406. ) (Hashtbl.fold (fun name data acc -> (name,data) :: acc) ctx.com.resources []);
  407. spr ctx "]";
  408. | TLocal { v_name = "`trace" }, [e;infos] ->
  409. if has_feature ctx "haxe.Log.trace" then begin
  410. let t = (try List.find (fun t -> t_path t = (["haxe"],"Log")) ctx.com.types with _ -> assert false) in
  411. spr ctx (ctx.type_accessor t);
  412. spr ctx ".trace(";
  413. gen_value ctx e;
  414. spr ctx ",";
  415. gen_value ctx infos;
  416. spr ctx ")";
  417. end else begin
  418. spr ctx "console.log(";
  419. gen_value ctx e;
  420. spr ctx ")";
  421. end
  422. | _ ->
  423. gen_value ctx e;
  424. spr ctx "(";
  425. concat ctx "," (gen_value ctx) el;
  426. spr ctx ")"
  427. and gen_expr ctx e =
  428. add_mapping ctx e;
  429. match e.eexpr with
  430. | TConst c -> gen_constant ctx e.epos c
  431. | TLocal v -> spr ctx (ident v.v_name)
  432. | TArray (e1,{ eexpr = TConst (TString s) }) when valid_js_ident s && (match e1.eexpr with TConst (TInt _|TFloat _) -> false | _ -> true) ->
  433. gen_value ctx e1;
  434. spr ctx (field s)
  435. | TArray (e1,e2) ->
  436. gen_value ctx e1;
  437. spr ctx "[";
  438. gen_value ctx e2;
  439. spr ctx "]";
  440. | TBinop (op,{ eexpr = TField (x,f) },e2) when field_name f = "iterator" ->
  441. gen_value ctx x;
  442. spr ctx (field "iterator");
  443. print ctx " %s " (Ast.s_binop op);
  444. gen_value ctx e2;
  445. | TBinop (op,e1,e2) ->
  446. gen_value ctx e1;
  447. print ctx " %s " (Ast.s_binop op);
  448. gen_value ctx e2;
  449. | TField (x,f) when field_name f = "iterator" && is_dynamic_iterator ctx e ->
  450. add_feature ctx "use.$iterator";
  451. print ctx "$iterator(";
  452. gen_value ctx x;
  453. print ctx ")";
  454. | TField (x,FClosure (Some ({cl_path=[],"Array"},_), {cf_name="push"})) ->
  455. (* see https://github.com/HaxeFoundation/haxe/issues/1997 *)
  456. add_feature ctx "use.$arrayPushClosure";
  457. print ctx "$arrayPushClosure(";
  458. gen_value ctx x;
  459. print ctx ")"
  460. | TField (x,FClosure (_,f)) ->
  461. add_feature ctx "use.$bind";
  462. (match x.eexpr with
  463. | TConst _ | TLocal _ ->
  464. print ctx "$bind(";
  465. gen_value ctx x;
  466. print ctx ",";
  467. gen_value ctx x;
  468. print ctx "%s)" (field f.cf_name)
  469. | _ ->
  470. print ctx "($_=";
  471. gen_value ctx x;
  472. print ctx ",$bind($_,$_%s))" (field f.cf_name))
  473. | TEnumParameter (x,_,i) ->
  474. gen_value ctx x;
  475. print ctx "[%i]" (i + 2)
  476. | TField ({ eexpr = TConst (TInt _ | TFloat _) } as x,f) ->
  477. gen_expr ctx { e with eexpr = TField(mk (TParenthesis x) x.etype x.epos,f) }
  478. | TField (x, (FInstance(_,_,f) | FStatic(_,f) | FAnon(f))) when Meta.has Meta.SelfCall f.cf_meta ->
  479. gen_value ctx x;
  480. | TField (x,f) ->
  481. gen_value ctx x;
  482. let name = field_name f in
  483. spr ctx (match f with FStatic(c,_) -> static_field c name | FEnum _ | FInstance _ | FAnon _ | FDynamic _ | FClosure _ -> field name)
  484. | TTypeExpr t ->
  485. spr ctx (ctx.type_accessor t)
  486. | TParenthesis e ->
  487. spr ctx "(";
  488. gen_value ctx e;
  489. spr ctx ")";
  490. | TMeta (_,e) ->
  491. gen_expr ctx e
  492. | TReturn eo ->
  493. if ctx.in_value <> None then unsupported e.epos;
  494. (match eo with
  495. | None ->
  496. spr ctx "return"
  497. | Some e ->
  498. spr ctx "return ";
  499. gen_value ctx e);
  500. | TBreak ->
  501. if not ctx.in_loop then unsupported e.epos;
  502. if ctx.handle_break then spr ctx "throw \"__break__\"" else spr ctx "break"
  503. | TContinue ->
  504. if not ctx.in_loop then unsupported e.epos;
  505. spr ctx "continue"
  506. | TBlock el ->
  507. print ctx "{";
  508. let bend = open_block ctx in
  509. List.iter (gen_block_element ctx) el;
  510. bend();
  511. newline ctx;
  512. print ctx "}";
  513. | TFunction f ->
  514. let old = ctx.in_value, ctx.in_loop in
  515. ctx.in_value <- None;
  516. ctx.in_loop <- false;
  517. print ctx "function(%s) " (String.concat "," (List.map ident (List.map arg_name f.tf_args)));
  518. gen_expr ctx (fun_block ctx f e.epos);
  519. ctx.in_value <- fst old;
  520. ctx.in_loop <- snd old;
  521. ctx.separator <- true
  522. | TCall (e,el) ->
  523. gen_call ctx e el false
  524. | TArrayDecl el ->
  525. spr ctx "[";
  526. concat ctx "," (gen_value ctx) el;
  527. spr ctx "]"
  528. | TThrow e ->
  529. spr ctx "throw ";
  530. gen_value ctx e;
  531. | TVar (v,eo) ->
  532. spr ctx "var ";
  533. check_var_declaration v;
  534. spr ctx (ident v.v_name);
  535. begin match eo with
  536. | None -> ()
  537. | Some e ->
  538. spr ctx " = ";
  539. gen_value ctx e
  540. end
  541. | TNew ({ cl_path = [],"Array" },_,[]) ->
  542. print ctx "[]"
  543. | TNew (c,_,el) ->
  544. (match c.cl_constructor with
  545. | Some cf when Meta.has Meta.SelfCall cf.cf_meta -> ()
  546. | _ -> print ctx "new ");
  547. print ctx "%s(" (ctx.type_accessor (TClassDecl c));
  548. concat ctx "," (gen_value ctx) el;
  549. spr ctx ")"
  550. | TIf (cond,e,eelse) ->
  551. spr ctx "if";
  552. gen_value ctx cond;
  553. spr ctx " ";
  554. gen_expr ctx e;
  555. (match eelse with
  556. | None -> ()
  557. | Some e2 ->
  558. (match e.eexpr with
  559. | TObjectDecl _ -> ctx.separator <- false
  560. | _ -> ());
  561. semicolon ctx;
  562. spr ctx " else ";
  563. gen_expr ctx e2);
  564. | TUnop (op,Ast.Prefix,e) ->
  565. spr ctx (Ast.s_unop op);
  566. gen_value ctx e
  567. | TUnop (op,Ast.Postfix,e) ->
  568. gen_value ctx e;
  569. spr ctx (Ast.s_unop op)
  570. | TWhile (cond,e,Ast.NormalWhile) ->
  571. let handle_break = handle_break ctx e in
  572. spr ctx "while";
  573. gen_value ctx cond;
  574. spr ctx " ";
  575. gen_expr ctx e;
  576. handle_break();
  577. | TWhile (cond,e,Ast.DoWhile) ->
  578. let handle_break = handle_break ctx e in
  579. spr ctx "do ";
  580. gen_expr ctx e;
  581. semicolon ctx;
  582. spr ctx " while";
  583. gen_value ctx cond;
  584. handle_break();
  585. | TObjectDecl fields ->
  586. spr ctx "{ ";
  587. concat ctx ", " (fun (f,e) -> (match e.eexpr with
  588. | TMeta((Meta.QuotedField,_,_),e) -> print ctx "'%s' : " f;
  589. | _ -> print ctx "%s : " (anon_field f));
  590. gen_value ctx e
  591. ) fields;
  592. spr ctx "}";
  593. ctx.separator <- true
  594. | TFor (v,it,e) ->
  595. check_var_declaration v;
  596. let handle_break = handle_break ctx e in
  597. let it = ident (match it.eexpr with
  598. | TLocal v -> v.v_name
  599. | _ ->
  600. let id = ctx.id_counter in
  601. ctx.id_counter <- ctx.id_counter + 1;
  602. let name = "$it" ^ string_of_int id in
  603. print ctx "var %s = " name;
  604. gen_value ctx it;
  605. newline ctx;
  606. name
  607. ) in
  608. print ctx "while( %s.hasNext() ) {" it;
  609. let bend = open_block ctx in
  610. newline ctx;
  611. print ctx "var %s = %s.next()" (ident v.v_name) it;
  612. gen_block_element ctx e;
  613. bend();
  614. newline ctx;
  615. spr ctx "}";
  616. handle_break();
  617. | TTry (e,catchs) ->
  618. spr ctx "try ";
  619. gen_expr ctx e;
  620. let vname = (match catchs with [(v,_)] -> check_var_declaration v; v.v_name | _ ->
  621. let id = ctx.id_counter in
  622. ctx.id_counter <- ctx.id_counter + 1;
  623. "$e" ^ string_of_int id
  624. ) in
  625. print ctx " catch( %s ) {" vname;
  626. let bend = open_block ctx in
  627. let last = ref false in
  628. let else_block = ref false in
  629. if (has_feature ctx "haxe.CallStack.exceptionStack") then begin
  630. newline ctx;
  631. print ctx "%s.lastException = %s" (ctx.type_accessor (TClassDecl { null_class with cl_path = ["haxe"],"CallStack" })) vname
  632. end;
  633. if (has_feature ctx "js.Boot.HaxeError") then begin
  634. newline ctx;
  635. print ctx "if (%s instanceof %s) %s = %s.val" vname (ctx.type_accessor (TClassDecl { null_class with cl_path = ["js";"_Boot"],"HaxeError" })) vname vname;
  636. end;
  637. List.iter (fun (v,e) ->
  638. if !last then () else
  639. let t = (match follow v.v_type with
  640. | TEnum (e,_) -> Some (TEnumDecl e)
  641. | TInst (c,_) -> Some (TClassDecl c)
  642. | TAbstract (a,_) -> Some (TAbstractDecl a)
  643. | TFun _
  644. | TLazy _
  645. | TType _
  646. | TAnon _ ->
  647. assert false
  648. | TMono _
  649. | TDynamic _ ->
  650. None
  651. ) in
  652. match t with
  653. | None ->
  654. last := true;
  655. if !else_block then print ctx "{";
  656. if vname <> v.v_name then begin
  657. newline ctx;
  658. print ctx "var %s = %s" v.v_name vname;
  659. end;
  660. gen_block_element ctx e;
  661. if !else_block then begin
  662. newline ctx;
  663. print ctx "}";
  664. end
  665. | Some t ->
  666. if not !else_block then newline ctx;
  667. print ctx "if( %s.__instanceof(%s," (ctx.type_accessor (TClassDecl { null_class with cl_path = ["js"],"Boot" })) vname;
  668. gen_value ctx (mk (TTypeExpr t) (mk_mono()) e.epos);
  669. spr ctx ") ) {";
  670. let bend = open_block ctx in
  671. if vname <> v.v_name then begin
  672. newline ctx;
  673. print ctx "var %s = %s" v.v_name vname;
  674. end;
  675. gen_block_element ctx e;
  676. bend();
  677. newline ctx;
  678. spr ctx "} else ";
  679. else_block := true
  680. ) catchs;
  681. if not !last then print ctx "throw(%s)" vname;
  682. bend();
  683. newline ctx;
  684. spr ctx "}";
  685. | TSwitch (e,cases,def) ->
  686. spr ctx "switch";
  687. gen_value ctx e;
  688. spr ctx " {";
  689. newline ctx;
  690. List.iter (fun (el,e2) ->
  691. List.iter (fun e ->
  692. match e.eexpr with
  693. | TConst(c) when c = TNull ->
  694. spr ctx "case null: case undefined:";
  695. | _ ->
  696. spr ctx "case ";
  697. gen_value ctx e;
  698. spr ctx ":"
  699. ) el;
  700. let bend = open_block ctx in
  701. gen_block_element ctx e2;
  702. if not (has_return e2) then begin
  703. newline ctx;
  704. print ctx "break";
  705. end;
  706. bend();
  707. newline ctx;
  708. ) cases;
  709. (match def with
  710. | None -> ()
  711. | Some e ->
  712. spr ctx "default:";
  713. let bend = open_block ctx in
  714. gen_block_element ctx e;
  715. bend();
  716. newline ctx;
  717. );
  718. spr ctx "}"
  719. | TCast (e,None) ->
  720. gen_expr ctx e
  721. | TCast (e1,Some t) ->
  722. print ctx "%s.__cast(" (ctx.type_accessor (TClassDecl { null_class with cl_path = ["js"],"Boot" }));
  723. gen_expr ctx e1;
  724. spr ctx " , ";
  725. spr ctx (ctx.type_accessor t);
  726. spr ctx ")"
  727. and gen_block_element ?(after=false) ctx e =
  728. match e.eexpr with
  729. | TBlock el ->
  730. List.iter (gen_block_element ~after ctx) el
  731. | TCall ({ eexpr = TLocal { v_name = "__feature__" } }, { eexpr = TConst (TString f) } :: eif :: eelse) ->
  732. if has_feature ctx f then
  733. gen_block_element ~after ctx eif
  734. else (match eelse with
  735. | [] -> ()
  736. | [e] -> gen_block_element ~after ctx e
  737. | _ -> assert false)
  738. | TFunction _ ->
  739. gen_block_element ~after ctx (mk (TParenthesis e) e.etype e.epos)
  740. | TObjectDecl fl ->
  741. List.iter (fun (_,e) -> gen_block_element ~after ctx e) fl
  742. | _ ->
  743. if not after then newline ctx;
  744. gen_expr ctx e;
  745. if after then newline ctx
  746. and gen_value ctx e =
  747. add_mapping ctx e;
  748. let assign e =
  749. mk (TBinop (Ast.OpAssign,
  750. mk (TLocal (match ctx.in_value with None -> assert false | Some v -> v)) t_dynamic e.epos,
  751. e
  752. )) e.etype e.epos
  753. in
  754. let value() =
  755. let old = ctx.in_value, ctx.in_loop in
  756. let r = alloc_var "$r" t_dynamic in
  757. ctx.in_value <- Some r;
  758. ctx.in_loop <- false;
  759. spr ctx "(function($this) ";
  760. spr ctx "{";
  761. let b = open_block ctx in
  762. newline ctx;
  763. spr ctx "var $r";
  764. newline ctx;
  765. (fun() ->
  766. newline ctx;
  767. spr ctx "return $r";
  768. b();
  769. newline ctx;
  770. spr ctx "}";
  771. ctx.in_value <- fst old;
  772. ctx.in_loop <- snd old;
  773. print ctx "(%s))" (this ctx)
  774. )
  775. in
  776. match e.eexpr with
  777. | TConst _
  778. | TLocal _
  779. | TArray _
  780. | TBinop _
  781. | TField _
  782. | TEnumParameter _
  783. | TTypeExpr _
  784. | TParenthesis _
  785. | TObjectDecl _
  786. | TArrayDecl _
  787. | TNew _
  788. | TUnop _
  789. | TFunction _ ->
  790. gen_expr ctx e
  791. | TMeta (_,e1) ->
  792. gen_value ctx e1
  793. | TCall (e,el) ->
  794. gen_call ctx e el true
  795. | TReturn _
  796. | TBreak
  797. | TContinue ->
  798. unsupported e.epos
  799. | TCast (e1, None) ->
  800. gen_value ctx e1
  801. | TCast (e1, Some t) ->
  802. print ctx "%s.__cast(" (ctx.type_accessor (TClassDecl { null_class with cl_path = ["js"],"Boot" }));
  803. gen_value ctx e1;
  804. spr ctx " , ";
  805. spr ctx (ctx.type_accessor t);
  806. spr ctx ")"
  807. | TVar _
  808. | TFor _
  809. | TWhile _
  810. | TThrow _ ->
  811. (* value is discarded anyway *)
  812. let v = value() in
  813. gen_expr ctx e;
  814. v()
  815. | TBlock [e] ->
  816. gen_value ctx e
  817. | TBlock el ->
  818. let v = value() in
  819. let rec loop = function
  820. | [] ->
  821. spr ctx "return null";
  822. | [e] ->
  823. gen_expr ctx (assign e);
  824. | e :: l ->
  825. gen_expr ctx e;
  826. newline ctx;
  827. loop l
  828. in
  829. loop el;
  830. v();
  831. | TIf (cond,e,eo) ->
  832. (* remove parenthesis unless it's an operation with higher precedence than ?: *)
  833. let cond = (match cond.eexpr with
  834. | TParenthesis { eexpr = TBinop ((Ast.OpAssign | Ast.OpAssignOp _),_,_) | TIf _ } -> cond
  835. | TParenthesis e -> e
  836. | _ -> cond
  837. ) in
  838. gen_value ctx cond;
  839. spr ctx "?";
  840. gen_value ctx e;
  841. spr ctx ":";
  842. (match eo with
  843. | None -> spr ctx "null"
  844. | Some e -> gen_value ctx e);
  845. | TSwitch (cond,cases,def) ->
  846. let v = value() in
  847. gen_expr ctx (mk (TSwitch (cond,
  848. List.map (fun (e1,e2) -> (e1,assign e2)) cases,
  849. match def with None -> None | Some e -> Some (assign e)
  850. )) e.etype e.epos);
  851. v()
  852. | TTry (b,catchs) ->
  853. let v = value() in
  854. let block e = mk (TBlock [e]) e.etype e.epos in
  855. gen_expr ctx (mk (TTry (block (assign b),
  856. List.map (fun (v,e) -> v, block (assign e)) catchs
  857. )) e.etype e.epos);
  858. v()
  859. let generate_package_create ctx (p,_) =
  860. let rec loop acc = function
  861. | [] -> ()
  862. | p :: l when Hashtbl.mem ctx.packages (p :: acc) -> loop (p :: acc) l
  863. | p :: l ->
  864. Hashtbl.add ctx.packages (p :: acc) ();
  865. (match acc with
  866. | [] ->
  867. if ctx.js_modern then
  868. print ctx "var %s = {}" p
  869. else
  870. print ctx "var %s = %s || {}" p p
  871. | _ ->
  872. let p = String.concat "." (List.rev acc) ^ (field p) in
  873. if ctx.js_modern then
  874. print ctx "%s = {}" p
  875. else
  876. print ctx "if(!%s) %s = {}" p p
  877. );
  878. ctx.separator <- true;
  879. newline ctx;
  880. loop (p :: acc) l
  881. in
  882. match p with
  883. | [] -> print ctx "var "
  884. | _ -> loop [] p
  885. let check_field_name c f =
  886. match f.cf_name with
  887. | "prototype" | "__proto__" | "constructor" ->
  888. 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);
  889. | _ -> ()
  890. (* convert a.b.c to ["a"]["b"]["c"] *)
  891. let path_to_brackets path =
  892. let parts = ExtString.String.nsplit path "." in
  893. "[\"" ^ (String.concat "\"][\"" parts) ^ "\"]"
  894. let gen_class_static_field ctx c f =
  895. match f.cf_expr with
  896. | None | Some { eexpr = TConst TNull } when not (has_feature ctx "Type.getClassFields") ->
  897. ()
  898. | None when is_extern_field f ->
  899. ()
  900. | None ->
  901. print ctx "%s%s = null" (s_path ctx c.cl_path) (static_field c f.cf_name);
  902. newline ctx
  903. | Some e ->
  904. match e.eexpr with
  905. | TFunction _ ->
  906. let path = (s_path ctx c.cl_path) ^ (static_field c f.cf_name) in
  907. let dot_path = (dot_path c.cl_path) ^ (static_field c f.cf_name) in
  908. ctx.id_counter <- 0;
  909. print ctx "%s = " path;
  910. (match (get_exposed ctx dot_path f.cf_meta) with [s] -> print ctx "$hx_exports%s = " (path_to_brackets s) | _ -> ());
  911. gen_value ctx e;
  912. newline ctx;
  913. | _ ->
  914. ctx.statics <- (c,f.cf_name,e) :: ctx.statics
  915. let can_gen_class_field ctx = function
  916. | { cf_expr = (None | Some { eexpr = TConst TNull }) } when not (has_feature ctx "Type.getInstanceFields") ->
  917. false
  918. | f ->
  919. not (is_extern_field f)
  920. let gen_class_field ctx c f =
  921. check_field_name c f;
  922. match f.cf_expr with
  923. | None ->
  924. newprop ctx;
  925. print ctx "%s: " (anon_field f.cf_name);
  926. print ctx "null";
  927. | Some e ->
  928. newprop ctx;
  929. print ctx "%s: " (anon_field f.cf_name);
  930. ctx.id_counter <- 0;
  931. gen_value ctx e;
  932. ctx.separator <- false
  933. let generate_class___name__ ctx c =
  934. if has_feature ctx "js.Boot.isClass" then begin
  935. let p = s_path ctx c.cl_path in
  936. print ctx "%s.__name__ = " p;
  937. if has_feature ctx "Type.getClassName" then
  938. print ctx "[%s]" (String.concat "," (List.map (fun s -> Printf.sprintf "\"%s\"" (Ast.s_escape s)) (fst c.cl_path @ [snd c.cl_path])))
  939. else
  940. print ctx "true";
  941. newline ctx;
  942. end
  943. let generate_class ctx c =
  944. ctx.current <- c;
  945. ctx.id_counter <- 0;
  946. (match c.cl_path with
  947. | [],"Function" -> error "This class redefine a native one" c.cl_pos
  948. | _ -> ());
  949. let p = s_path ctx c.cl_path in
  950. let hxClasses = has_feature ctx "Type.resolveClass" in
  951. if ctx.js_flatten then
  952. print ctx "var "
  953. else
  954. generate_package_create ctx c.cl_path;
  955. if ctx.js_modern || not hxClasses then
  956. print ctx "%s = " p
  957. else
  958. print ctx "%s = $hxClasses[\"%s\"] = " p (dot_path c.cl_path);
  959. (match (get_exposed ctx (dot_path c.cl_path) c.cl_meta) with [s] -> print ctx "$hx_exports%s = " (path_to_brackets s) | _ -> ());
  960. (match c.cl_kind with
  961. | KAbstractImpl _ ->
  962. (* abstract implementations only contain static members and don't need to have constructor functions *)
  963. print ctx "{}"; ctx.separator <- true
  964. | _ ->
  965. (match c.cl_constructor with
  966. | Some { cf_expr = Some e } -> gen_expr ctx e
  967. | _ -> (print ctx "function() { }"); ctx.separator <- true)
  968. );
  969. newline ctx;
  970. if ctx.js_modern && hxClasses then begin
  971. print ctx "$hxClasses[\"%s\"] = %s" (dot_path c.cl_path) p;
  972. newline ctx;
  973. end;
  974. generate_class___name__ ctx c;
  975. (match c.cl_implements with
  976. | [] -> ()
  977. | l ->
  978. print ctx "%s.__interfaces__ = [%s]" p (String.concat "," (List.map (fun (i,_) -> ctx.type_accessor (TClassDecl i)) l));
  979. newline ctx;
  980. );
  981. let gen_props props =
  982. String.concat "," (List.map (fun (p,v) -> p ^":\""^v^"\"") props) in
  983. let has_property_reflection =
  984. (has_feature ctx "Reflect.getProperty") || (has_feature ctx "Reflect.setProperty") in
  985. if has_property_reflection then begin
  986. (match Codegen.get_properties c.cl_ordered_statics with
  987. | [] -> ()
  988. | props ->
  989. print ctx "%s.__properties__ = {%s}" p (gen_props props);
  990. newline ctx);
  991. end;
  992. List.iter (gen_class_static_field ctx c) c.cl_ordered_statics;
  993. let has_class = has_feature ctx "js.Boot.getClass" && (c.cl_super <> None || c.cl_ordered_fields <> [] || c.cl_constructor <> None) in
  994. let has_prototype = c.cl_super <> None || has_class || List.exists (can_gen_class_field ctx) c.cl_ordered_fields in
  995. if has_prototype then begin
  996. (match c.cl_super with
  997. | None -> print ctx "%s.prototype = {" p;
  998. | Some (csup,_) ->
  999. let psup = ctx.type_accessor (TClassDecl csup) in
  1000. print ctx "%s.__super__ = %s" p psup;
  1001. newline ctx;
  1002. print ctx "%s.prototype = $extend(%s.prototype,{" p psup;
  1003. );
  1004. let bend = open_block ctx in
  1005. List.iter (fun f -> if can_gen_class_field ctx f then gen_class_field ctx c f) c.cl_ordered_fields;
  1006. if has_class then begin
  1007. newprop ctx;
  1008. print ctx "__class__: %s" p;
  1009. end;
  1010. if has_property_reflection then begin
  1011. let props = Codegen.get_properties c.cl_ordered_fields in
  1012. (match c.cl_super with
  1013. | _ when props = [] -> ()
  1014. | Some (csup,_) when Codegen.has_properties csup ->
  1015. newprop ctx;
  1016. let psup = s_path ctx csup.cl_path in
  1017. print ctx "__properties__: $extend(%s.prototype.__properties__,{%s})" psup (gen_props props)
  1018. | _ ->
  1019. newprop ctx;
  1020. print ctx "__properties__: {%s}" (gen_props props));
  1021. end;
  1022. bend();
  1023. print ctx "\n}";
  1024. (match c.cl_super with None -> ctx.separator <- true | _ -> print ctx ")");
  1025. newline ctx
  1026. end;
  1027. flush ctx
  1028. let generate_enum ctx e =
  1029. let p = s_path ctx e.e_path in
  1030. let ename = List.map (fun s -> Printf.sprintf "\"%s\"" (Ast.s_escape s)) (fst e.e_path @ [snd e.e_path]) in
  1031. if ctx.js_flatten then
  1032. print ctx "var "
  1033. else
  1034. generate_package_create ctx e.e_path;
  1035. print ctx "%s = " p;
  1036. if has_feature ctx "Type.resolveEnum" then print ctx "$hxClasses[\"%s\"] = " (dot_path e.e_path);
  1037. print ctx "{";
  1038. if has_feature ctx "js.Boot.isEnum" then print ctx " __ename__ : %s," (if has_feature ctx "Type.getEnumName" then "[" ^ String.concat "," ename ^ "]" else "true");
  1039. print ctx " __constructs__ : [%s] }" (String.concat "," (List.map (fun s -> Printf.sprintf "\"%s\"" s) e.e_names));
  1040. ctx.separator <- true;
  1041. newline ctx;
  1042. List.iter (fun n ->
  1043. let f = PMap.find n e.e_constrs in
  1044. print ctx "%s%s = " p (field f.ef_name);
  1045. (match f.ef_type with
  1046. | TFun (args,_) ->
  1047. let sargs = String.concat "," (List.map (fun (n,_,_) -> ident n) args) in
  1048. print ctx "function(%s) { var $x = [\"%s\",%d,%s]; $x.__enum__ = %s;" sargs f.ef_name f.ef_index sargs p;
  1049. if has_feature ctx "has_enum" then
  1050. spr ctx " $x.toString = $estr;";
  1051. spr ctx " return $x; }";
  1052. ctx.separator <- true;
  1053. | _ ->
  1054. print ctx "[\"%s\",%d]" f.ef_name f.ef_index;
  1055. newline ctx;
  1056. if has_feature ctx "has_enum" then begin
  1057. print ctx "%s%s.toString = $estr" p (field f.ef_name);
  1058. newline ctx;
  1059. end;
  1060. print ctx "%s%s.__enum__ = %s" p (field f.ef_name) p;
  1061. );
  1062. newline ctx
  1063. ) e.e_names;
  1064. if has_feature ctx "Type.allEnums" then begin
  1065. let ctors_without_args = List.filter (fun s ->
  1066. let ef = PMap.find s e.e_constrs in
  1067. match follow ef.ef_type with
  1068. | TFun _ -> false
  1069. | _ -> true
  1070. ) e.e_names in
  1071. print ctx "%s.__empty_constructs__ = [%s]" p (String.concat "," (List.map (fun s -> Printf.sprintf "%s.%s" p s) ctors_without_args));
  1072. newline ctx
  1073. end;
  1074. begin match Codegen.build_metadata ctx.com (TEnumDecl e) with
  1075. | None -> ()
  1076. | Some e ->
  1077. print ctx "%s.__meta__ = " p;
  1078. gen_expr ctx e;
  1079. newline ctx
  1080. end;
  1081. flush ctx
  1082. let generate_static ctx (c,f,e) =
  1083. print ctx "%s%s = " (s_path ctx c.cl_path) (static_field c f);
  1084. gen_value ctx e;
  1085. newline ctx
  1086. let generate_require ctx path meta =
  1087. let _, args, mp = Meta.get Meta.JsRequire meta in
  1088. let p = (s_path ctx path) in
  1089. if ctx.js_flatten then
  1090. spr ctx "var "
  1091. else
  1092. generate_package_create ctx path;
  1093. (match args with
  1094. | [(EConst(String(module_name)),_)] ->
  1095. print ctx "%s = require(\"%s\")" p module_name
  1096. | [(EConst(String(module_name)),_) ; (EConst(String(object_path)),_)] ->
  1097. print ctx "%s = require(\"%s\").%s" p module_name object_path
  1098. | _ ->
  1099. error "Unsupported @:jsRequire format" mp);
  1100. newline ctx
  1101. let generate_type ctx = function
  1102. | TClassDecl c ->
  1103. (match c.cl_init with
  1104. | None -> ()
  1105. | Some e ->
  1106. ctx.inits <- e :: ctx.inits);
  1107. (* Special case, want to add Math.__name__ only when required, handle here since Math is extern *)
  1108. let p = s_path ctx c.cl_path in
  1109. if p = "Math" then generate_class___name__ ctx c;
  1110. (* Another special case for Std because we do not want to generate it if it's empty. *)
  1111. if p = "Std" && c.cl_ordered_statics = [] then
  1112. ()
  1113. else if not c.cl_extern then
  1114. generate_class ctx c
  1115. else if Meta.has Meta.JsRequire c.cl_meta && is_directly_used ctx.com c.cl_meta then
  1116. generate_require ctx c.cl_path c.cl_meta
  1117. else if not ctx.js_flatten && Meta.has Meta.InitPackage c.cl_meta then
  1118. (match c.cl_path with
  1119. | ([],_) -> ()
  1120. | _ -> generate_package_create ctx c.cl_path)
  1121. | TEnumDecl e when e.e_extern ->
  1122. if Meta.has Meta.JsRequire e.e_meta && is_directly_used ctx.com e.e_meta then
  1123. generate_require ctx e.e_path e.e_meta
  1124. | TEnumDecl e -> generate_enum ctx e
  1125. | TTypeDecl _ | TAbstractDecl _ -> ()
  1126. let set_current_class ctx c =
  1127. ctx.current <- c
  1128. let alloc_ctx com =
  1129. let ctx = {
  1130. com = com;
  1131. buf = Rbuffer.create 16000;
  1132. chan = open_out_bin com.file;
  1133. packages = Hashtbl.create 0;
  1134. smap = {
  1135. source_last_line = 0;
  1136. source_last_col = 0;
  1137. source_last_file = 0;
  1138. print_comma = false;
  1139. output_last_col = 0;
  1140. output_current_col = 0;
  1141. sources = DynArray.create();
  1142. sources_hash = Hashtbl.create 0;
  1143. mappings = Rbuffer.create 16;
  1144. };
  1145. js_modern = not (Common.defined com Define.JsClassic);
  1146. js_flatten = not (Common.defined com Define.JsUnflatten);
  1147. statics = [];
  1148. inits = [];
  1149. current = null_class;
  1150. tabs = "";
  1151. in_value = None;
  1152. in_loop = false;
  1153. handle_break = false;
  1154. id_counter = 0;
  1155. type_accessor = (fun _ -> assert false);
  1156. separator = false;
  1157. found_expose = false;
  1158. } in
  1159. ctx.type_accessor <- (fun t ->
  1160. let p = t_path t in
  1161. match t with
  1162. | TClassDecl ({ cl_extern = true } as c) when not (Meta.has Meta.JsRequire c.cl_meta)
  1163. -> dot_path p
  1164. | TEnumDecl ({ e_extern = true } as e) when not (Meta.has Meta.JsRequire e.e_meta)
  1165. -> dot_path p
  1166. | _ -> s_path ctx p);
  1167. ctx
  1168. let gen_single_expr ctx e expr =
  1169. if expr then gen_expr ctx e else gen_value ctx e;
  1170. let str = Rbuffer.unsafe_contents ctx.buf in
  1171. Rbuffer.reset ctx.buf;
  1172. ctx.id_counter <- 0;
  1173. str
  1174. let generate com =
  1175. (match com.js_gen with
  1176. | Some g -> g()
  1177. | None ->
  1178. let ctx = alloc_ctx com in
  1179. Codegen.map_source_header com (fun s -> print ctx "// %s\n" s);
  1180. if has_feature ctx "Class" || has_feature ctx "Type.getClassName" then add_feature ctx "js.Boot.isClass";
  1181. if has_feature ctx "Enum" || has_feature ctx "Type.getEnumName" then add_feature ctx "js.Boot.isEnum";
  1182. let exposed = List.concat (List.map (fun t ->
  1183. match t with
  1184. | TClassDecl c ->
  1185. let path = dot_path c.cl_path in
  1186. let class_exposed = get_exposed ctx path c.cl_meta in
  1187. let static_exposed = List.map (fun f ->
  1188. get_exposed ctx (path ^ static_field c f.cf_name) f.cf_meta
  1189. ) c.cl_ordered_statics in
  1190. List.concat (class_exposed :: static_exposed)
  1191. | _ -> []
  1192. ) com.types) in
  1193. let anyExposed = exposed <> [] in
  1194. let exportMap = ref (PMap.create String.compare) in
  1195. let exposedObject = { os_name = ""; os_fields = [] } in
  1196. let toplevelExposed = ref [] in
  1197. List.iter (fun path -> (
  1198. let parts = ExtString.String.nsplit path "." in
  1199. let rec loop p pre = match p with
  1200. | f :: g :: ls ->
  1201. let path = match pre with "" -> f | pre -> (pre ^ "." ^ f) in
  1202. if not (PMap.exists path !exportMap) then (
  1203. let elts = { os_name = f; os_fields = [] } in
  1204. exportMap := PMap.add path elts !exportMap;
  1205. let cobject = match pre with "" -> exposedObject | pre -> PMap.find pre !exportMap in
  1206. cobject.os_fields <- elts :: cobject.os_fields
  1207. );
  1208. loop (g :: ls) path;
  1209. | f :: [] when pre = "" ->
  1210. toplevelExposed := f :: !toplevelExposed;
  1211. | _ -> ()
  1212. in loop parts "";
  1213. )) exposed;
  1214. let include_files = List.rev com.include_files in
  1215. List.iter (fun file ->
  1216. match file with
  1217. | path, "top" ->
  1218. let file_content = Std.input_file ~bin:true (fst file) in
  1219. print ctx "%s\n" file_content;
  1220. ()
  1221. | _ -> ()
  1222. ) include_files;
  1223. let closureArgs = [] in
  1224. let closureArgs = if (anyExposed && not (Common.defined com Define.ShallowExpose)) then
  1225. (
  1226. "$hx_exports",
  1227. (* TODO(bruno): Remove runtime branching when standard node haxelib is available *)
  1228. "typeof window != \"undefined\" ? window : exports"
  1229. ) :: closureArgs
  1230. else
  1231. closureArgs
  1232. in
  1233. (* Provide console for environments that may not have it. *)
  1234. let closureArgs = if (not (Common.defined com Define.JsEs5)) then
  1235. (
  1236. "console",
  1237. "typeof console != \"undefined\" ? console : {log:function(){}}"
  1238. ) :: closureArgs
  1239. else
  1240. closureArgs
  1241. in
  1242. if Common.raw_defined com "nodejs" then
  1243. (* Add node globals to pseudo-keywords, so they are not shadowed by local vars *)
  1244. List.iter (fun s -> Hashtbl.replace kwds2 s ()) [ "global"; "process"; "__filename"; "__dirname"; "module" ];
  1245. if ctx.js_modern then begin
  1246. (* Additional ES5 strict mode keywords. *)
  1247. List.iter (fun s -> Hashtbl.replace kwds s ()) [ "arguments"; "eval" ];
  1248. (* Wrap output in a closure *)
  1249. if (anyExposed && (Common.defined com Define.ShallowExpose)) then (
  1250. print ctx "var $hx_exports = $hx_exports || {}";
  1251. ctx.separator <- true;
  1252. newline ctx
  1253. );
  1254. print ctx "(function (%s) { \"use strict\"" (String.concat ", " (List.map fst closureArgs));
  1255. newline ctx;
  1256. let rec print_obj f root = (
  1257. let path = root ^ (path_to_brackets f.os_name) in
  1258. print ctx "%s = %s || {}" path path;
  1259. ctx.separator <- true;
  1260. newline ctx;
  1261. concat ctx ";" (fun g -> print_obj g path) f.os_fields
  1262. )
  1263. in
  1264. List.iter (fun f -> print_obj f "$hx_exports") exposedObject.os_fields;
  1265. end;
  1266. List.iter (fun file ->
  1267. match file with
  1268. | path, "closure" ->
  1269. let file_content = Std.input_file ~bin:true (fst file) in
  1270. print ctx "%s\n" file_content;
  1271. ()
  1272. | _ -> ()
  1273. ) include_files;
  1274. (* If ctx.js_modern, console is defined in closureArgs. *)
  1275. if (not ctx.js_modern) && (not (Common.defined com Define.JsEs5)) then
  1276. spr ctx "var console = Function(\"return typeof console != 'undefined' ? console : {log:function(){}}\")();\n";
  1277. (* TODO: fix $estr *)
  1278. let vars = [] in
  1279. 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
  1280. let vars = if has_feature ctx "has_enum"
  1281. then ("$estr = function() { return " ^ (ctx.type_accessor (TClassDecl { null_class with cl_path = ["js"],"Boot" })) ^ ".__string_rec(this,''); }") :: vars
  1282. else vars in
  1283. (match List.rev vars with
  1284. | [] -> ()
  1285. | vl ->
  1286. print ctx "var %s" (String.concat "," vl);
  1287. ctx.separator <- true;
  1288. newline ctx
  1289. );
  1290. if List.exists (function TClassDecl { cl_extern = false; cl_super = Some _ } -> true | _ -> false) com.types then begin
  1291. print ctx "function $extend(from, fields) {
  1292. function Inherit() {} Inherit.prototype = from; var proto = new Inherit();
  1293. for (var name in fields) proto[name] = fields[name];
  1294. if( fields.toString !== Object.prototype.toString ) proto.toString = fields.toString;
  1295. return proto;
  1296. }
  1297. ";
  1298. end;
  1299. List.iter (generate_type ctx) com.types;
  1300. let rec chk_features e =
  1301. if is_dynamic_iterator ctx e then add_feature ctx "use.$iterator";
  1302. match e.eexpr with
  1303. | TField (_,FClosure _) ->
  1304. add_feature ctx "use.$bind"
  1305. | _ ->
  1306. Type.iter chk_features e
  1307. in
  1308. List.iter chk_features ctx.inits;
  1309. List.iter (fun (_,_,e) -> chk_features e) ctx.statics;
  1310. if has_feature ctx "use.$iterator" then begin
  1311. add_feature ctx "use.$bind";
  1312. 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; }";
  1313. newline ctx;
  1314. end;
  1315. if has_feature ctx "use.$bind" then begin
  1316. print ctx "var $_, $fid = 0";
  1317. newline ctx;
  1318. 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; }";
  1319. newline ctx;
  1320. end;
  1321. if has_feature ctx "use.$arrayPushClosure" then begin
  1322. print ctx "function $arrayPushClosure(a) {";
  1323. print ctx " return function(x) { a.push(x); }; ";
  1324. print ctx "}";
  1325. newline ctx
  1326. end;
  1327. List.iter (gen_block_element ~after:true ctx) (List.rev ctx.inits);
  1328. List.iter (generate_static ctx) (List.rev ctx.statics);
  1329. (match com.main with
  1330. | None -> ()
  1331. | Some e -> gen_expr ctx e; newline ctx);
  1332. if ctx.js_modern then begin
  1333. print ctx "})(%s)" (String.concat ", " (List.map snd closureArgs));
  1334. newline ctx;
  1335. if (anyExposed && (Common.defined com Define.ShallowExpose)) then (
  1336. List.iter (fun f ->
  1337. print ctx "var %s = $hx_exports%s" f.os_name (path_to_brackets f.os_name);
  1338. ctx.separator <- true;
  1339. newline ctx
  1340. ) exposedObject.os_fields;
  1341. List.iter (fun f ->
  1342. print ctx "var %s = $hx_exports%s" f (path_to_brackets f);
  1343. ctx.separator <- true;
  1344. newline ctx
  1345. ) !toplevelExposed
  1346. );
  1347. end;
  1348. if com.debug then write_mappings ctx else (try Sys.remove (com.file ^ ".map") with _ -> ());
  1349. flush ctx;
  1350. close_out ctx.chan)