genjs.ml 45 KB

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