genjs.ml 39 KB

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