genas3.ml 36 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284
  1. (*
  2. The Haxe Compiler
  3. Copyright (C) 2005-2015 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 Type
  17. open Common
  18. type context_infos = {
  19. com : Common.context;
  20. }
  21. type context = {
  22. inf : context_infos;
  23. ch : out_channel;
  24. buf : Buffer.t;
  25. path : path;
  26. mutable get_sets : (string * bool,string) Hashtbl.t;
  27. mutable curclass : tclass;
  28. mutable tabs : string;
  29. mutable in_value : tvar option;
  30. mutable in_static : bool;
  31. mutable handle_break : bool;
  32. mutable imports : (string,string list list) Hashtbl.t;
  33. mutable gen_uid : int;
  34. mutable local_types : t list;
  35. mutable constructor_block : bool;
  36. mutable block_inits : (unit -> unit) option;
  37. }
  38. let follow = Abstract.follow_with_abstracts
  39. let is_var_field f =
  40. match f with
  41. | FStatic (_,f) | FInstance (_,_,f) ->
  42. (match f.cf_kind with Var _ | Method MethDynamic -> true | _ -> false)
  43. | _ ->
  44. false
  45. let is_special_compare e1 e2 =
  46. match e1.eexpr, e2.eexpr with
  47. | TConst TNull, _ | _ , TConst TNull -> None
  48. | _ ->
  49. match follow e1.etype, follow e2.etype with
  50. | TInst ({ cl_path = ["flash"],"NativeXml" } as c,_) , _ | _ , TInst ({ cl_path = ["flash"],"NativeXml" } as c,_) -> Some c
  51. | _ -> None
  52. let is_fixed_override cf t =
  53. let is_type_parameter c = match c.cl_kind with
  54. | KTypeParameter _ -> true
  55. | _ -> false
  56. in
  57. match follow cf.cf_type,follow t with
  58. | TFun(_,r1),TFun(_,r2) ->
  59. begin match follow r1,follow r2 with
  60. | TInst(c1,_),TInst(c2,_) when c1 != c2 && not (is_type_parameter c1) && not (is_type_parameter c2) -> true
  61. | _ -> false
  62. end
  63. | _ ->
  64. false
  65. let protect name =
  66. match name with
  67. | "Error" | "Namespace" -> "_" ^ name
  68. | _ -> name
  69. let s_path ctx stat path p =
  70. match path with
  71. | ([],name) ->
  72. (match name with
  73. | "Int" -> "int"
  74. | "Float" -> "Number"
  75. | "Dynamic" -> "Object"
  76. | "Bool" -> "Boolean"
  77. | "Enum" -> "Class"
  78. | "EnumValue" -> "enum"
  79. | _ -> name)
  80. | (["flash"],"FlashXml__") ->
  81. "Xml"
  82. | (["flash";"errors"],"Error") ->
  83. "Error"
  84. | (["flash"],"Vector") ->
  85. "Vector"
  86. | (["flash";"xml"],"XML") ->
  87. "XML"
  88. | (["flash";"xml"],"XMLList") ->
  89. "XMLList"
  90. | ["flash";"utils"],"QName" ->
  91. "QName"
  92. | ["flash";"utils"],"Namespace" ->
  93. "Namespace"
  94. | (["haxe"],"Int32") when not stat ->
  95. "int"
  96. | (pack,name) ->
  97. let name = protect name in
  98. let packs = (try Hashtbl.find ctx.imports name with Not_found -> []) in
  99. if not (List.mem pack packs) then Hashtbl.replace ctx.imports name (pack :: packs);
  100. Ast.s_type_path (pack,name)
  101. let reserved =
  102. let h = Hashtbl.create 0 in
  103. List.iter (fun l -> Hashtbl.add h l ())
  104. (* these ones are defined in order to prevent recursion in some Std functions *)
  105. ["is";"as";"int";"uint";"const";"getTimer";"typeof";"parseInt";"parseFloat";
  106. (* AS3 keywords which are not Haxe ones *)
  107. "finally";"with";"final";"internal";"native";"namespace";"include";"delete";
  108. (* some globals give some errors with Flex SDK as well *)
  109. "print";"trace";
  110. (* we don't include get+set since they are not 'real' keywords, but they can't be used as method names *)
  111. "function";"class";"var";"if";"else";"while";"do";"for";"break";"continue";"return";"extends";"implements";
  112. "import";"switch";"case";"default";"static";"public";"private";"try";"catch";"new";"this";"throw";"interface";
  113. "override";"package";"null";"true";"false";"void"
  114. ];
  115. h
  116. (* "each", "label" : removed (actually allowed in locals and fields accesses) *)
  117. let s_ident n =
  118. if Hashtbl.mem reserved n then "_" ^ n else n
  119. let valid_as3_ident s =
  120. try
  121. for i = 0 to String.length s - 1 do
  122. match String.unsafe_get s i with
  123. | 'a'..'z' | 'A'..'Z' | '$' | '_' -> ()
  124. | '0'..'9' when i > 0 -> ()
  125. | _ -> raise Exit
  126. done;
  127. true
  128. with Exit ->
  129. false
  130. let anon_field s =
  131. let s = s_ident s in
  132. if not (valid_as3_ident s) then "\"" ^ s ^ "\"" else s
  133. let rec create_dir acc = function
  134. | [] -> ()
  135. | d :: l ->
  136. let dir = String.concat "/" (List.rev (d :: acc)) in
  137. if not (Sys.file_exists dir) then Unix.mkdir dir 0o755;
  138. create_dir (d :: acc) l
  139. let init infos path =
  140. let dir = infos.com.file :: fst path in
  141. create_dir [] dir;
  142. let ch = open_out (String.concat "/" dir ^ "/" ^ snd path ^ ".as") in
  143. let imports = Hashtbl.create 0 in
  144. Hashtbl.add imports (snd path) [fst path];
  145. {
  146. inf = infos;
  147. tabs = "";
  148. ch = ch;
  149. path = path;
  150. buf = Buffer.create (1 lsl 14);
  151. in_value = None;
  152. in_static = false;
  153. handle_break = false;
  154. imports = imports;
  155. curclass = null_class;
  156. gen_uid = 0;
  157. local_types = [];
  158. get_sets = Hashtbl.create 0;
  159. constructor_block = false;
  160. block_inits = None;
  161. }
  162. let close ctx =
  163. begin match ctx.inf.com.main_class with
  164. | Some tp when tp = ctx.curclass.cl_path ->
  165. output_string ctx.ch "// Compile __main__.as instead\n";
  166. | _ ->
  167. ()
  168. end;
  169. output_string ctx.ch (Printf.sprintf "package %s {\n" (String.concat "." (fst ctx.path)));
  170. Hashtbl.iter (fun name paths ->
  171. List.iter (fun pack ->
  172. let path = pack, name in
  173. if path <> ctx.path then output_string ctx.ch ("\timport " ^ Ast.s_type_path path ^ ";\n");
  174. ) paths
  175. ) ctx.imports;
  176. output_string ctx.ch (Buffer.contents ctx.buf);
  177. close_out ctx.ch
  178. let gen_local ctx l =
  179. ctx.gen_uid <- ctx.gen_uid + 1;
  180. if ctx.gen_uid = 1 then l else l ^ string_of_int ctx.gen_uid
  181. let spr ctx s = Buffer.add_string ctx.buf s
  182. let print ctx = Printf.kprintf (fun s -> Buffer.add_string ctx.buf s)
  183. let unsupported p = error "This expression cannot be generated to AS3" p
  184. let newline ctx =
  185. let rec loop p =
  186. match Buffer.nth ctx.buf p with
  187. | '}' | '{' | ':' | ';' -> print ctx "\n%s" ctx.tabs
  188. | '\n' | '\t' -> loop (p - 1)
  189. | _ -> print ctx ";\n%s" ctx.tabs
  190. in
  191. loop (Buffer.length ctx.buf - 1)
  192. let block_newline ctx = match Buffer.nth ctx.buf (Buffer.length ctx.buf - 1) with
  193. | '}' -> print ctx ";\n%s" ctx.tabs
  194. | _ -> newline ctx
  195. let rec concat ctx s f = function
  196. | [] -> ()
  197. | [x] -> f x
  198. | x :: l ->
  199. f x;
  200. spr ctx s;
  201. concat ctx s f l
  202. let open_block ctx =
  203. let oldt = ctx.tabs in
  204. ctx.tabs <- "\t" ^ ctx.tabs;
  205. (fun() -> ctx.tabs <- oldt)
  206. let parent e =
  207. match e.eexpr with
  208. | TParenthesis _ -> e
  209. | _ -> mk (TParenthesis e) e.etype e.epos
  210. let default_value tstr =
  211. match tstr with
  212. | "int" | "uint" -> "0"
  213. | "Number" -> "NaN"
  214. | "Boolean" -> "false"
  215. | _ -> "null"
  216. let rec type_str ctx t p =
  217. match t with
  218. | TEnum _ | TInst _ when List.memq t ctx.local_types ->
  219. "*"
  220. | TAbstract (a,pl) when not (Ast.Meta.has Ast.Meta.CoreType a.a_meta) ->
  221. type_str ctx (Abstract.get_underlying_type a pl) p
  222. | TAbstract (a,_) ->
  223. (match a.a_path with
  224. | [], "Void" -> "void"
  225. | [], "UInt" -> "uint"
  226. | [], "Int" -> "int"
  227. | [], "Float" -> "Number"
  228. | [], "Bool" -> "Boolean"
  229. | _ -> s_path ctx true a.a_path p)
  230. | TEnum (e,_) ->
  231. if e.e_extern then (match e.e_path with
  232. | [], "Void" -> "void"
  233. | [], "Bool" -> "Boolean"
  234. | _ ->
  235. let rec loop = function
  236. | [] -> "Object"
  237. | (Ast.Meta.FakeEnum,[Ast.EConst (Ast.Ident n),_],_) :: _ ->
  238. (match n with
  239. | "Int" -> "int"
  240. | "UInt" -> "uint"
  241. | _ -> n)
  242. | _ :: l -> loop l
  243. in
  244. loop e.e_meta
  245. ) else
  246. s_path ctx true e.e_path p
  247. | TInst ({ cl_path = ["flash"],"Vector" },[pt]) ->
  248. (match pt with
  249. | TInst({cl_kind = KTypeParameter _},_) -> "*"
  250. | _ -> "Vector.<" ^ type_str ctx pt p ^ ">")
  251. | TInst (c,_) ->
  252. (match c.cl_kind with
  253. | KNormal | KGeneric | KGenericInstance _ | KAbstractImpl _ -> s_path ctx false c.cl_path p
  254. | KTypeParameter _ | KExtension _ | KExpr _ | KMacroType | KGenericBuild _ -> "*")
  255. | TFun _ ->
  256. "Function"
  257. | TMono r ->
  258. (match !r with None -> "*" | Some t -> type_str ctx t p)
  259. | TAnon _ | TDynamic _ ->
  260. "*"
  261. | TType (t,args) ->
  262. (match t.t_path with
  263. | [], "UInt" -> "uint"
  264. | [] , "Null" ->
  265. (match args with
  266. | [t] ->
  267. (match follow t with
  268. | TAbstract ({ a_path = [],"UInt" },_)
  269. | TAbstract ({ a_path = [],"Int" },_)
  270. | TAbstract ({ a_path = [],"Float" },_)
  271. | TAbstract ({ a_path = [],"Bool" },_)
  272. | TInst ({ cl_path = [],"Int" },_)
  273. | TInst ({ cl_path = [],"Float" },_)
  274. | TEnum ({ e_path = [],"Bool" },_) -> "*"
  275. | _ -> type_str ctx t p)
  276. | _ -> assert false);
  277. | _ -> type_str ctx (apply_params t.t_params args t.t_type) p)
  278. | TLazy f ->
  279. type_str ctx ((!f)()) p
  280. let rec iter_switch_break in_switch e =
  281. match e.eexpr with
  282. | TFunction _ | TWhile _ | TFor _ -> ()
  283. | TSwitch _ when not in_switch -> iter_switch_break true e
  284. | TBreak when in_switch -> raise Exit
  285. | _ -> iter (iter_switch_break in_switch) e
  286. let handle_break ctx e =
  287. let old_handle = ctx.handle_break in
  288. try
  289. iter_switch_break false e;
  290. ctx.handle_break <- false;
  291. (fun() -> ctx.handle_break <- old_handle)
  292. with
  293. Exit ->
  294. spr ctx "try {";
  295. let b = open_block ctx in
  296. newline ctx;
  297. ctx.handle_break <- true;
  298. (fun() ->
  299. b();
  300. ctx.handle_break <- old_handle;
  301. newline ctx;
  302. spr ctx "} catch( e : * ) { if( e != \"__break__\" ) throw e; }";
  303. )
  304. let this ctx = if ctx.in_value <> None then "$this" else "this"
  305. let generate_resources infos =
  306. if Hashtbl.length infos.com.resources <> 0 then begin
  307. let dir = (infos.com.file :: ["__res"]) in
  308. create_dir [] dir;
  309. let add_resource name data =
  310. let name = Base64.str_encode name in
  311. let ch = open_out_bin (String.concat "/" (dir @ [name])) in
  312. output_string ch data;
  313. close_out ch
  314. in
  315. Hashtbl.iter (fun name data -> add_resource name data) infos.com.resources;
  316. let ctx = init infos ([],"__resources__") in
  317. spr ctx "\timport flash.utils.Dictionary;\n";
  318. spr ctx "\tpublic class __resources__ {\n";
  319. spr ctx "\t\tpublic static var list:Dictionary;\n";
  320. let inits = ref [] in
  321. let k = ref 0 in
  322. Hashtbl.iter (fun name _ ->
  323. let varname = ("v" ^ (string_of_int !k)) in
  324. k := !k + 1;
  325. print ctx "\t\t[Embed(source = \"__res/%s\", mimeType = \"application/octet-stream\")]\n" (Base64.str_encode name);
  326. print ctx "\t\tpublic static var %s:Class;\n" varname;
  327. inits := ("list[\"" ^ Ast.s_escape name ^ "\"] = " ^ varname ^ ";") :: !inits;
  328. ) infos.com.resources;
  329. spr ctx "\t\tstatic public function __init__():void {\n";
  330. spr ctx "\t\t\tlist = new Dictionary();\n";
  331. List.iter (fun init ->
  332. print ctx "\t\t\t%s\n" init
  333. ) !inits;
  334. spr ctx "\t\t}\n";
  335. spr ctx "\t}\n";
  336. spr ctx "}";
  337. close ctx;
  338. end
  339. let gen_constant ctx p = function
  340. | TInt i -> print ctx "%ld" i
  341. | TFloat s -> spr ctx s
  342. | TString s -> print ctx "\"%s\"" (Ast.s_escape s)
  343. | TBool b -> spr ctx (if b then "true" else "false")
  344. | TNull -> spr ctx "null"
  345. | TThis -> spr ctx (this ctx)
  346. | TSuper -> spr ctx "super"
  347. let gen_function_header ctx name f params p =
  348. let old = ctx.in_value in
  349. let old_t = ctx.local_types in
  350. let old_bi = ctx.block_inits in
  351. ctx.in_value <- None;
  352. ctx.local_types <- List.map snd params @ ctx.local_types;
  353. let init () =
  354. List.iter (fun (v,o) -> match o with
  355. | Some c when is_nullable v.v_type && c <> TNull ->
  356. newline ctx;
  357. print ctx "if(%s==null) %s=" v.v_name v.v_name;
  358. gen_constant ctx p c;
  359. | _ -> ()
  360. ) f.tf_args;
  361. ctx.block_inits <- None;
  362. in
  363. ctx.block_inits <- Some init;
  364. print ctx "function%s(" (match name with None -> "" | Some (n,meta) ->
  365. let rec loop = function
  366. | [] -> n
  367. | (Ast.Meta.Getter,[Ast.EConst (Ast.Ident i),_],_) :: _ -> "get " ^ i
  368. | (Ast.Meta.Setter,[Ast.EConst (Ast.Ident i),_],_) :: _ -> "set " ^ i
  369. | _ :: l -> loop l
  370. in
  371. " " ^ loop meta
  372. );
  373. concat ctx "," (fun (v,c) ->
  374. match v.v_name with
  375. | "__arguments__" ->
  376. print ctx "...__arguments__"
  377. | _ ->
  378. let tstr = type_str ctx v.v_type p in
  379. print ctx "%s : %s" (s_ident v.v_name) tstr;
  380. match c with
  381. | None ->
  382. if ctx.constructor_block then print ctx " = %s" (default_value tstr);
  383. | Some c ->
  384. spr ctx " = ";
  385. gen_constant ctx p c
  386. ) f.tf_args;
  387. print ctx ") : %s " (type_str ctx f.tf_type p);
  388. (fun () ->
  389. ctx.in_value <- old;
  390. ctx.local_types <- old_t;
  391. ctx.block_inits <- old_bi;
  392. )
  393. let rec gen_call ctx e el r =
  394. match e.eexpr , el with
  395. | TCall (x,_) , el ->
  396. spr ctx "(";
  397. gen_value ctx e;
  398. spr ctx ")";
  399. spr ctx "(";
  400. concat ctx "," (gen_value ctx) el;
  401. spr ctx ")";
  402. | TLocal { v_name = "__is__" } , [e1;e2] ->
  403. gen_value ctx e1;
  404. spr ctx " is ";
  405. gen_value ctx e2;
  406. | TLocal { v_name = "__in__" } , [e1;e2] ->
  407. spr ctx "(";
  408. gen_value ctx e1;
  409. spr ctx " in ";
  410. gen_value ctx e2;
  411. spr ctx ")"
  412. | TLocal { v_name = "__as__" }, [e1;e2] ->
  413. gen_value ctx e1;
  414. spr ctx " as ";
  415. gen_value ctx e2;
  416. | TLocal { v_name = "__int__" }, [e] ->
  417. spr ctx "int(";
  418. gen_value ctx e;
  419. spr ctx ")";
  420. | TLocal { v_name = "__float__" }, [e] ->
  421. spr ctx "Number(";
  422. gen_value ctx e;
  423. spr ctx ")";
  424. | TLocal { v_name = "__typeof__" }, [e] ->
  425. spr ctx "typeof ";
  426. gen_value ctx e;
  427. | TLocal { v_name = "__keys__" }, [e] ->
  428. let ret = (match ctx.in_value with None -> assert false | Some r -> r) in
  429. print ctx "%s = new Array()" ret.v_name;
  430. newline ctx;
  431. let tmp = gen_local ctx "$k" in
  432. print ctx "for(var %s : String in " tmp;
  433. gen_value ctx e;
  434. print ctx ") %s.push(%s)" ret.v_name tmp;
  435. | TLocal { v_name = "__hkeys__" }, [e] ->
  436. let ret = (match ctx.in_value with None -> assert false | Some r -> r) in
  437. print ctx "%s = new Array()" ret.v_name;
  438. newline ctx;
  439. let tmp = gen_local ctx "$k" in
  440. print ctx "for(var %s : String in " tmp;
  441. gen_value ctx e;
  442. print ctx ") %s.push(%s.substr(1))" ret.v_name tmp;
  443. | TLocal { v_name = "__foreach__" }, [e] ->
  444. let ret = (match ctx.in_value with None -> assert false | Some r -> r) in
  445. print ctx "%s = new Array()" ret.v_name;
  446. newline ctx;
  447. let tmp = gen_local ctx "$k" in
  448. print ctx "for each(var %s : * in " tmp;
  449. gen_value ctx e;
  450. print ctx ") %s.push(%s)" ret.v_name tmp;
  451. | TLocal { v_name = "__new__" }, e :: args ->
  452. spr ctx "new ";
  453. gen_value ctx e;
  454. spr ctx "(";
  455. concat ctx "," (gen_value ctx) args;
  456. spr ctx ")";
  457. | TLocal { v_name = "__delete__" }, [e;f] ->
  458. spr ctx "delete(";
  459. gen_value ctx e;
  460. spr ctx "[";
  461. gen_value ctx f;
  462. spr ctx "]";
  463. spr ctx ")";
  464. | TLocal { v_name = "__unprotect__" }, [e] ->
  465. gen_value ctx e
  466. | TLocal { v_name = "__vector__" }, [e] ->
  467. spr ctx (type_str ctx r e.epos);
  468. spr ctx "(";
  469. gen_value ctx e;
  470. spr ctx ")"
  471. | TField (_, FStatic( { cl_path = (["flash"],"Lib") }, { cf_name = "as" })), [e1;e2] ->
  472. gen_value ctx e1;
  473. spr ctx " as ";
  474. gen_value ctx e2
  475. | TField (_, FStatic ({ cl_path = (["flash"],"Vector") }, cf)), args ->
  476. (match cf.cf_name, args with
  477. | "ofArray", [e] | "convert", [e] ->
  478. (match follow r with
  479. | TInst ({ cl_path = (["flash"],"Vector") },[t]) ->
  480. print ctx "Vector.<%s>(" (type_str ctx t e.epos);
  481. gen_value ctx e;
  482. print ctx ")";
  483. | _ -> assert false)
  484. | _ -> assert false)
  485. | TField(e1, (FAnon {cf_name = s} | FDynamic s)),[ef] when s = "map" || s = "filter" ->
  486. spr ctx (s_path ctx true (["flash";],"Boot") e.epos);
  487. gen_field_access ctx t_dynamic (s ^ "Dynamic");
  488. spr ctx "(";
  489. concat ctx "," (gen_value ctx) [e1;ef];
  490. spr ctx ")"
  491. | TField (ee,f), args when is_var_field f ->
  492. spr ctx "(";
  493. gen_value ctx e;
  494. spr ctx ")";
  495. spr ctx "(";
  496. concat ctx "," (gen_value ctx) el;
  497. spr ctx ")"
  498. | TField (e1,FInstance(_,_,cf)),el when is_fixed_override cf e.etype ->
  499. let s = type_str ctx r e.epos in
  500. spr ctx "((";
  501. gen_value ctx e;
  502. spr ctx "(";
  503. concat ctx "," (gen_value ctx) el;
  504. spr ctx ")";
  505. print ctx ") as %s)" s
  506. | _ ->
  507. gen_value ctx e;
  508. spr ctx "(";
  509. concat ctx "," (gen_value ctx) el;
  510. spr ctx ")"
  511. and gen_value_op ctx e =
  512. match e.eexpr with
  513. | TBinop (op,_,_) when op = Ast.OpAnd || op = Ast.OpOr || op = Ast.OpXor ->
  514. spr ctx "(";
  515. gen_value ctx e;
  516. spr ctx ")";
  517. | _ ->
  518. gen_value ctx e
  519. and gen_field_access ctx t s =
  520. let field c =
  521. match fst c.cl_path, snd c.cl_path, s with
  522. | [], "Math", "NaN"
  523. | [], "Math", "NEGATIVE_INFINITY"
  524. | [], "Math", "POSITIVE_INFINITY"
  525. | [], "Math", "isFinite"
  526. | [], "Math", "isNaN"
  527. | [], "Date", "now"
  528. | [], "Date", "fromTime"
  529. | [], "Date", "fromString"
  530. ->
  531. print ctx "[\"%s\"]" s
  532. | [], "String", "charCodeAt" ->
  533. spr ctx "[\"charCodeAtHX\"]"
  534. | [], "Array", "map" ->
  535. spr ctx "[\"mapHX\"]"
  536. | [], "Array", "filter" ->
  537. spr ctx "[\"filterHX\"]"
  538. | [], "Date", "toString" ->
  539. print ctx "[\"toStringHX\"]"
  540. | [], "String", "cca" ->
  541. print ctx ".charCodeAt"
  542. | ["flash";"xml"], "XML", "namespace" ->
  543. print ctx ".namespace"
  544. | _ ->
  545. print ctx ".%s" (s_ident s)
  546. in
  547. match follow t with
  548. | TInst (c,_) -> field c
  549. | TAnon a ->
  550. (match !(a.a_status) with
  551. | Statics c -> field c
  552. | _ -> print ctx ".%s" (s_ident s))
  553. | _ ->
  554. print ctx ".%s" (s_ident s)
  555. and gen_expr ctx e =
  556. match e.eexpr with
  557. | TConst c ->
  558. gen_constant ctx e.epos c
  559. | TLocal v ->
  560. spr ctx (s_ident v.v_name)
  561. | TArray ({ eexpr = TLocal { v_name = "__global__" } },{ eexpr = TConst (TString s) }) ->
  562. let path = Ast.parse_path s in
  563. spr ctx (s_path ctx false path e.epos)
  564. | TArray (e1,e2) ->
  565. gen_value ctx e1;
  566. spr ctx "[";
  567. gen_value ctx e2;
  568. spr ctx "]";
  569. | TBinop (Ast.OpEq,e1,e2) when (match is_special_compare e1 e2 with Some c -> true | None -> false) ->
  570. let c = match is_special_compare e1 e2 with Some c -> c | None -> assert false in
  571. gen_expr ctx (mk (TCall (mk (TField (mk (TTypeExpr (TClassDecl c)) t_dynamic e.epos,FDynamic "compare")) t_dynamic e.epos,[e1;e2])) ctx.inf.com.basic.tbool e.epos);
  572. (* what is this used for? *)
  573. (* | TBinop (op,{ eexpr = TField (e1,s) },e2) ->
  574. gen_value_op ctx e1;
  575. gen_field_access ctx e1.etype s;
  576. print ctx " %s " (Ast.s_binop op);
  577. gen_value_op ctx e2; *)
  578. (* assignments to variable or dynamic methods fields on interfaces are generated as class["field"] = value *)
  579. | TBinop (op,{eexpr = TField (ei, FInstance({cl_interface = true},_,{cf_kind = (Method MethDynamic | Var _); cf_name = s}))},e2) ->
  580. gen_value ctx ei;
  581. print ctx "[\"%s\"]" s;
  582. print ctx " %s " (Ast.s_binop op);
  583. gen_value_op ctx e2;
  584. | TBinop (op,e1,e2) ->
  585. gen_value_op ctx e1;
  586. print ctx " %s " (Ast.s_binop op);
  587. gen_value_op ctx e2;
  588. (* variable fields and dynamic methods on interfaces are generated as (class["field"] as class) *)
  589. | TField (ei, FInstance({cl_interface = true},_,{cf_kind = (Method MethDynamic | Var _); cf_name = s})) ->
  590. spr ctx "(";
  591. gen_value ctx ei;
  592. print ctx "[\"%s\"]" s;
  593. print ctx " as %s)" (type_str ctx e.etype e.epos);
  594. | TField({eexpr = TArrayDecl _} as e1,s) ->
  595. spr ctx "(";
  596. gen_expr ctx e1;
  597. spr ctx ")";
  598. gen_field_access ctx e1.etype (field_name s)
  599. | TEnumParameter (e,_,i) ->
  600. gen_value ctx e;
  601. print ctx ".params[%i]" i;
  602. | TField (e,s) ->
  603. gen_value ctx e;
  604. gen_field_access ctx e.etype (field_name s)
  605. | TTypeExpr t ->
  606. spr ctx (s_path ctx true (t_path t) e.epos)
  607. | TParenthesis e ->
  608. spr ctx "(";
  609. gen_value ctx e;
  610. spr ctx ")";
  611. | TMeta (_,e) ->
  612. gen_expr ctx e
  613. | TReturn eo ->
  614. if ctx.in_value <> None then unsupported e.epos;
  615. (match eo with
  616. | None ->
  617. spr ctx "return"
  618. | Some e when (match follow e.etype with TEnum({ e_path = [],"Void" },[]) | TAbstract ({ a_path = [],"Void" },[]) -> true | _ -> false) ->
  619. print ctx "{";
  620. let bend = open_block ctx in
  621. newline ctx;
  622. gen_value ctx e;
  623. newline ctx;
  624. spr ctx "return";
  625. bend();
  626. newline ctx;
  627. print ctx "}";
  628. | Some e ->
  629. spr ctx "return ";
  630. gen_value ctx e);
  631. | TBreak ->
  632. if ctx.in_value <> None then unsupported e.epos;
  633. if ctx.handle_break then spr ctx "throw \"__break__\"" else spr ctx "break"
  634. | TContinue ->
  635. if ctx.in_value <> None then unsupported e.epos;
  636. spr ctx "continue"
  637. | TBlock el ->
  638. print ctx "{";
  639. let bend = open_block ctx in
  640. let cb = (if not ctx.constructor_block then
  641. (fun () -> ())
  642. else if not (Codegen.constructor_side_effects e) then begin
  643. ctx.constructor_block <- false;
  644. (fun () -> ())
  645. end else begin
  646. ctx.constructor_block <- false;
  647. print ctx " if( !%s.skip_constructor ) {" (s_path ctx true (["flash"],"Boot") e.epos);
  648. (fun() -> print ctx "}")
  649. end) in
  650. (match ctx.block_inits with None -> () | Some i -> i());
  651. List.iter (fun e -> gen_block_element ctx e) el;
  652. bend();
  653. newline ctx;
  654. cb();
  655. print ctx "}";
  656. | TFunction f ->
  657. let h = gen_function_header ctx None f [] e.epos in
  658. let old = ctx.in_static in
  659. ctx.in_static <- true;
  660. gen_expr ctx f.tf_expr;
  661. ctx.in_static <- old;
  662. h();
  663. | TCall (v,el) ->
  664. gen_call ctx v el e.etype
  665. | TArrayDecl el ->
  666. spr ctx "[";
  667. concat ctx "," (gen_value ctx) el;
  668. spr ctx "]"
  669. | TThrow e ->
  670. spr ctx "throw ";
  671. gen_value ctx e;
  672. | TVar (v,eo) ->
  673. spr ctx "var ";
  674. print ctx "%s : %s" (s_ident v.v_name) (type_str ctx v.v_type e.epos);
  675. begin match eo with
  676. | None -> ()
  677. | Some e ->
  678. spr ctx " = ";
  679. gen_value ctx e
  680. end
  681. | TNew (c,params,el) ->
  682. (match c.cl_path, params with
  683. | (["flash"],"Vector"), [pt] -> print ctx "new Vector.<%s>(" (type_str ctx pt e.epos)
  684. | _ -> print ctx "new %s(" (s_path ctx true c.cl_path e.epos));
  685. concat ctx "," (gen_value ctx) el;
  686. spr ctx ")"
  687. | TIf (cond,e,eelse) ->
  688. spr ctx "if";
  689. gen_value ctx (parent cond);
  690. spr ctx " ";
  691. gen_expr ctx e;
  692. (match eelse with
  693. | None -> ()
  694. | Some e ->
  695. newline ctx;
  696. spr ctx "else ";
  697. gen_expr ctx e);
  698. | TUnop (op,Ast.Prefix,e) ->
  699. spr ctx (Ast.s_unop op);
  700. gen_value ctx e
  701. | TUnop (op,Ast.Postfix,e) ->
  702. gen_value ctx e;
  703. spr ctx (Ast.s_unop op)
  704. | TWhile (cond,e,Ast.NormalWhile) ->
  705. let handle_break = handle_break ctx e in
  706. spr ctx "while";
  707. gen_value ctx (parent cond);
  708. spr ctx " ";
  709. gen_expr ctx e;
  710. handle_break();
  711. | TWhile (cond,e,Ast.DoWhile) ->
  712. let handle_break = handle_break ctx e in
  713. spr ctx "do ";
  714. gen_expr ctx e;
  715. spr ctx " while";
  716. gen_value ctx (parent cond);
  717. handle_break();
  718. | TObjectDecl fields ->
  719. spr ctx "{ ";
  720. concat ctx ", " (fun (f,e) -> print ctx "%s : " (anon_field f); gen_value ctx e) fields;
  721. spr ctx "}"
  722. | TFor (v,it,e) ->
  723. let handle_break = handle_break ctx e in
  724. let tmp = gen_local ctx "$it" in
  725. print ctx "{ var %s : * = " tmp;
  726. gen_value ctx it;
  727. newline ctx;
  728. print ctx "while( %s.hasNext() ) { var %s : %s = %s.next()" tmp (s_ident v.v_name) (type_str ctx v.v_type e.epos) tmp;
  729. newline ctx;
  730. gen_expr ctx e;
  731. newline ctx;
  732. spr ctx "}}";
  733. handle_break();
  734. | TTry (e,catchs) ->
  735. spr ctx "try ";
  736. gen_expr ctx e;
  737. List.iter (fun (v,e) ->
  738. newline ctx;
  739. print ctx "catch( %s : %s )" (s_ident v.v_name) (type_str ctx v.v_type e.epos);
  740. gen_expr ctx e;
  741. ) catchs;
  742. | TSwitch (e,cases,def) ->
  743. spr ctx "switch";
  744. gen_value ctx (parent e);
  745. spr ctx " {";
  746. newline ctx;
  747. List.iter (fun (el,e2) ->
  748. List.iter (fun e ->
  749. spr ctx "case ";
  750. gen_value ctx e;
  751. spr ctx ":";
  752. ) el;
  753. gen_block ctx e2;
  754. print ctx "break";
  755. newline ctx;
  756. ) cases;
  757. (match def with
  758. | None -> ()
  759. | Some e ->
  760. spr ctx "default:";
  761. gen_block ctx e;
  762. print ctx "break";
  763. newline ctx;
  764. );
  765. spr ctx "}"
  766. | TCast (e1,None) ->
  767. let s = type_str ctx e.etype e.epos in
  768. if s = "*" then
  769. gen_expr ctx e1
  770. else begin
  771. spr ctx "((";
  772. gen_value ctx e1;
  773. print ctx ") as %s)" s
  774. end
  775. | TCast (e1,Some t) ->
  776. gen_expr ctx (Codegen.default_cast ctx.inf.com e1 t e.etype e.epos)
  777. and gen_block_element ctx e = match e.eexpr with
  778. | TObjectDecl fl ->
  779. List.iter (fun (_,e) -> gen_block_element ctx e) fl
  780. | _ ->
  781. block_newline ctx;
  782. gen_expr ctx e
  783. and gen_block ctx e =
  784. newline ctx;
  785. match e.eexpr with
  786. | TBlock [] -> ()
  787. | _ ->
  788. gen_expr ctx e;
  789. newline ctx
  790. and gen_value ctx e =
  791. let assign e =
  792. mk (TBinop (Ast.OpAssign,
  793. mk (TLocal (match ctx.in_value with None -> assert false | Some r -> r)) t_dynamic e.epos,
  794. e
  795. )) e.etype e.epos
  796. in
  797. let block e =
  798. mk (TBlock [e]) e.etype e.epos
  799. in
  800. let value block =
  801. let old = ctx.in_value in
  802. let t = type_str ctx e.etype e.epos in
  803. let r = alloc_var (gen_local ctx "$r") e.etype in
  804. ctx.in_value <- Some r;
  805. if ctx.in_static then
  806. print ctx "function() : %s " t
  807. else
  808. print ctx "(function($this:%s) : %s " (snd ctx.path) t;
  809. let b = if block then begin
  810. spr ctx "{";
  811. let b = open_block ctx in
  812. newline ctx;
  813. print ctx "var %s : %s" r.v_name t;
  814. newline ctx;
  815. b
  816. end else
  817. (fun() -> ())
  818. in
  819. (fun() ->
  820. if block then begin
  821. newline ctx;
  822. print ctx "return %s" r.v_name;
  823. b();
  824. newline ctx;
  825. spr ctx "}";
  826. end;
  827. ctx.in_value <- old;
  828. if ctx.in_static then
  829. print ctx "()"
  830. else
  831. print ctx "(%s))" (this ctx)
  832. )
  833. in
  834. match e.eexpr with
  835. | TCall ({ eexpr = TLocal { v_name = "__keys__" } },_) | TCall ({ eexpr = TLocal { v_name = "__hkeys__" } },_) ->
  836. let v = value true in
  837. gen_expr ctx e;
  838. v()
  839. | TConst _
  840. | TLocal _
  841. | TArray _
  842. | TBinop _
  843. | TField _
  844. | TEnumParameter _
  845. | TTypeExpr _
  846. | TParenthesis _
  847. | TObjectDecl _
  848. | TArrayDecl _
  849. | TCall _
  850. | TNew _
  851. | TUnop _
  852. | TFunction _ ->
  853. gen_expr ctx e
  854. | TMeta (_,e1) ->
  855. gen_value ctx e1
  856. | TCast (e1,None) ->
  857. let s = type_str ctx e.etype e1.epos in
  858. begin match s with
  859. | "*" ->
  860. gen_value ctx e1
  861. | "Function" | "Array" | "String" ->
  862. spr ctx "((";
  863. gen_value ctx e1;
  864. print ctx ") as %s)" s;
  865. | _ ->
  866. print ctx "%s(" s;
  867. gen_value ctx e1;
  868. spr ctx ")";
  869. end
  870. | TCast (e1,Some t) ->
  871. gen_value ctx (Codegen.default_cast ctx.inf.com e1 t e.etype e.epos)
  872. | TReturn _
  873. | TBreak
  874. | TContinue ->
  875. unsupported e.epos
  876. | TVar _
  877. | TFor _
  878. | TWhile _
  879. | TThrow _ ->
  880. (* value is discarded anyway *)
  881. let v = value true in
  882. gen_expr ctx e;
  883. v()
  884. | TBlock [] ->
  885. spr ctx "null"
  886. | TBlock [e] ->
  887. gen_value ctx e
  888. | TBlock el ->
  889. let v = value true in
  890. let rec loop = function
  891. | [] ->
  892. spr ctx "return null";
  893. | [e] ->
  894. gen_expr ctx (assign e);
  895. | e :: l ->
  896. gen_expr ctx e;
  897. newline ctx;
  898. loop l
  899. in
  900. loop el;
  901. v();
  902. | TIf (cond,e,eo) ->
  903. spr ctx "(";
  904. gen_value ctx cond;
  905. spr ctx "?";
  906. gen_value ctx e;
  907. spr ctx ":";
  908. (match eo with
  909. | None -> spr ctx "null"
  910. | Some e -> gen_value ctx e);
  911. spr ctx ")"
  912. | TSwitch (cond,cases,def) ->
  913. let v = value true in
  914. gen_expr ctx (mk (TSwitch (cond,
  915. List.map (fun (e1,e2) -> (e1,assign e2)) cases,
  916. match def with None -> None | Some e -> Some (assign e)
  917. )) e.etype e.epos);
  918. v()
  919. | TTry (b,catchs) ->
  920. let v = value true in
  921. gen_expr ctx (mk (TTry (block (assign b),
  922. List.map (fun (v,e) -> v, block (assign e)) catchs
  923. )) e.etype e.epos);
  924. v()
  925. let final m =
  926. if Ast.Meta.has Ast.Meta.Final m then " final " else ""
  927. let generate_field ctx static f =
  928. newline ctx;
  929. ctx.in_static <- static;
  930. ctx.gen_uid <- 0;
  931. List.iter (fun(m,pl,_) ->
  932. match m,pl with
  933. | Ast.Meta.Meta, [Ast.ECall ((Ast.EConst (Ast.Ident n),_),args),_] ->
  934. let mk_arg (a,p) =
  935. match a with
  936. | Ast.EConst (Ast.String s) -> (None, s)
  937. | Ast.EBinop (Ast.OpAssign,(Ast.EConst (Ast.Ident n),_),(Ast.EConst (Ast.String s),_)) -> (Some n, s)
  938. | _ -> error "Invalid meta definition" p
  939. in
  940. print ctx "[%s" n;
  941. (match args with
  942. | [] -> ()
  943. | _ ->
  944. print ctx "(";
  945. concat ctx "," (fun a ->
  946. match mk_arg a with
  947. | None, s -> gen_constant ctx (snd a) (TString s)
  948. | Some s, e -> print ctx "%s=" s; gen_constant ctx (snd a) (TString e)
  949. ) args;
  950. print ctx ")");
  951. print ctx "]";
  952. | _ -> ()
  953. ) f.cf_meta;
  954. let public = f.cf_public || Hashtbl.mem ctx.get_sets (f.cf_name,static) || (f.cf_name = "main" && static)
  955. || f.cf_name = "resolve" || Ast.Meta.has Ast.Meta.Public f.cf_meta
  956. (* consider all abstract methods public to avoid issues with inlined private access *)
  957. || (match ctx.curclass.cl_kind with KAbstractImpl _ -> true | _ -> false)
  958. in
  959. let rights = (if static then "static " else "") ^ (if public then "public" else "protected") in
  960. let p = ctx.curclass.cl_pos in
  961. match f.cf_expr, f.cf_kind with
  962. | Some { eexpr = TFunction fd }, Method (MethNormal | MethInline) ->
  963. print ctx "%s%s " rights (if static then "" else final f.cf_meta);
  964. let rec loop c =
  965. match c.cl_super with
  966. | None -> ()
  967. | Some (c,_) ->
  968. if PMap.mem f.cf_name c.cl_fields then
  969. spr ctx "override "
  970. else
  971. loop c
  972. in
  973. if not static then loop ctx.curclass;
  974. let h = gen_function_header ctx (Some (s_ident f.cf_name, f.cf_meta)) fd f.cf_params p in
  975. gen_expr ctx fd.tf_expr;
  976. h();
  977. newline ctx
  978. | _ ->
  979. let is_getset = (match f.cf_kind with Var { v_read = AccCall } | Var { v_write = AccCall } -> true | _ -> false) in
  980. if ctx.curclass.cl_interface then
  981. match follow f.cf_type with
  982. | TFun (args,r) when (match f.cf_kind with Method MethDynamic | Var _ -> false | _ -> true) ->
  983. let rec loop = function
  984. | [] -> f.cf_name
  985. | (Ast.Meta.Getter,[Ast.EConst (Ast.String name),_],_) :: _ -> "get " ^ name
  986. | (Ast.Meta.Setter,[Ast.EConst (Ast.String name),_],_) :: _ -> "set " ^ name
  987. | _ :: l -> loop l
  988. in
  989. print ctx "function %s(" (loop f.cf_meta);
  990. concat ctx "," (fun (arg,o,t) ->
  991. let tstr = type_str ctx t p in
  992. print ctx "%s : %s" arg tstr;
  993. if o then print ctx " = %s" (default_value tstr);
  994. ) args;
  995. print ctx ") : %s " (type_str ctx r p);
  996. | _ -> ()
  997. else
  998. let gen_init () = match f.cf_expr with
  999. | None -> ()
  1000. | Some e ->
  1001. if not static || (match e.eexpr with | TConst _ | TFunction _ | TTypeExpr _ -> true | _ -> false) then begin
  1002. print ctx " = ";
  1003. gen_value ctx e
  1004. end else
  1005. Codegen.ExtClass.add_static_init ctx.curclass f e e.epos
  1006. in
  1007. if is_getset then begin
  1008. let t = type_str ctx f.cf_type p in
  1009. let id = s_ident f.cf_name in
  1010. let v = (match f.cf_kind with Var v -> v | _ -> assert false) in
  1011. (match v.v_read with
  1012. | AccNormal | AccNo | AccNever ->
  1013. print ctx "%s function get %s() : %s { return $%s; }" rights id t id;
  1014. newline ctx
  1015. | AccCall ->
  1016. print ctx "%s function get %s() : %s { return %s(); }" rights id t ("get_" ^ f.cf_name);
  1017. newline ctx
  1018. | _ -> ());
  1019. (match v.v_write with
  1020. | AccNormal | AccNo | AccNever ->
  1021. print ctx "%s function set %s( __v : %s ) : void { $%s = __v; }" rights id t id;
  1022. newline ctx
  1023. | AccCall ->
  1024. print ctx "%s function set %s( __v : %s ) : void { %s(__v); }" rights id t ("set_" ^ f.cf_name);
  1025. newline ctx
  1026. | _ -> ());
  1027. print ctx "%sprotected var $%s : %s" (if static then "static " else "") (s_ident f.cf_name) (type_str ctx f.cf_type p);
  1028. gen_init()
  1029. end else begin
  1030. print ctx "%s var %s : %s" rights (s_ident f.cf_name) (type_str ctx f.cf_type p);
  1031. gen_init()
  1032. end
  1033. let rec define_getset ctx stat c =
  1034. let def f name =
  1035. Hashtbl.add ctx.get_sets (name,stat) f.cf_name
  1036. in
  1037. let field f =
  1038. match f.cf_kind with
  1039. | Method _ -> ()
  1040. | Var v ->
  1041. (match v.v_read with AccCall -> def f ("get_" ^ f.cf_name) | _ -> ());
  1042. (match v.v_write with AccCall -> def f ("set_" ^ f.cf_name) | _ -> ())
  1043. in
  1044. List.iter field (if stat then c.cl_ordered_statics else c.cl_ordered_fields);
  1045. match c.cl_super with
  1046. | Some (c,_) when not stat -> define_getset ctx stat c
  1047. | _ -> ()
  1048. let generate_class ctx c =
  1049. ctx.curclass <- c;
  1050. define_getset ctx true c;
  1051. define_getset ctx false c;
  1052. ctx.local_types <- List.map snd c.cl_params;
  1053. let pack = open_block ctx in
  1054. print ctx "\tpublic %s%s%s %s " (final c.cl_meta) (match c.cl_dynamic with None -> "" | Some _ -> if c.cl_interface then "" else "dynamic ") (if c.cl_interface then "interface" else "class") (snd c.cl_path);
  1055. (match c.cl_super with
  1056. | None -> ()
  1057. | Some (csup,_) -> print ctx "extends %s " (s_path ctx true csup.cl_path c.cl_pos));
  1058. (match c.cl_implements with
  1059. | [] -> ()
  1060. | l ->
  1061. spr ctx (if c.cl_interface then "extends " else "implements ");
  1062. concat ctx ", " (fun (i,_) -> print ctx "%s" (s_path ctx true i.cl_path c.cl_pos)) l);
  1063. spr ctx "{";
  1064. let cl = open_block ctx in
  1065. (match c.cl_constructor with
  1066. | None -> ()
  1067. | Some f ->
  1068. let f = { f with
  1069. cf_name = snd c.cl_path;
  1070. cf_public = true;
  1071. cf_kind = Method MethNormal;
  1072. } in
  1073. ctx.constructor_block <- true;
  1074. generate_field ctx false f;
  1075. );
  1076. List.iter (generate_field ctx false) c.cl_ordered_fields;
  1077. List.iter (generate_field ctx true) c.cl_ordered_statics;
  1078. let has_init = match c.cl_init with
  1079. | None -> false
  1080. | Some e ->
  1081. newline ctx;
  1082. spr ctx "static static_init function init() : void";
  1083. gen_expr ctx (mk_block e);
  1084. true;
  1085. in
  1086. cl();
  1087. newline ctx;
  1088. print ctx "}";
  1089. pack();
  1090. newline ctx;
  1091. print ctx "}";
  1092. if has_init then begin
  1093. newline ctx;
  1094. spr ctx "namespace static_init";
  1095. newline ctx;
  1096. print ctx "%s.static_init::init()" (s_path ctx true ctx.curclass.cl_path Ast.null_pos);
  1097. end;
  1098. newline ctx;
  1099. if c.cl_interface && Ast.Meta.has (Ast.Meta.Custom ":hasMetadata") c.cl_meta then begin
  1100. (* we have to reference the metadata class in order for it to be compiled *)
  1101. let path = fst c.cl_path,snd c.cl_path ^ "_HxMeta" in
  1102. spr ctx (Ast.s_type_path path);
  1103. newline ctx
  1104. end
  1105. let generate_main ctx inits =
  1106. ctx.curclass <- { null_class with cl_path = [],"__main__" };
  1107. let pack = open_block ctx in
  1108. print ctx "\timport flash.Lib";
  1109. newline ctx;
  1110. print ctx "public class __main__ extends %s {" (s_path ctx true (["flash"],"Boot") Ast.null_pos);
  1111. let cl = open_block ctx in
  1112. newline ctx;
  1113. spr ctx "public function __main__() {";
  1114. let fl = open_block ctx in
  1115. newline ctx;
  1116. spr ctx "super()";
  1117. newline ctx;
  1118. spr ctx "flash.Lib.current = this";
  1119. List.iter (fun e -> newline ctx; gen_expr ctx e) inits;
  1120. fl();
  1121. newline ctx;
  1122. print ctx "}";
  1123. cl();
  1124. newline ctx;
  1125. print ctx "}";
  1126. pack();
  1127. newline ctx;
  1128. print ctx "}";
  1129. newline ctx
  1130. let generate_enum ctx e =
  1131. ctx.local_types <- List.map snd e.e_params;
  1132. let pack = open_block ctx in
  1133. let ename = snd e.e_path in
  1134. print ctx "\tpublic final class %s extends enum {" ename;
  1135. let cl = open_block ctx in
  1136. newline ctx;
  1137. print ctx "public static const __isenum : Boolean = true";
  1138. newline ctx;
  1139. print ctx "public function %s( t : String, index : int, p : Array = null ) : void { this.tag = t; this.index = index; this.params = p; }" ename;
  1140. PMap.iter (fun _ c ->
  1141. newline ctx;
  1142. match c.ef_type with
  1143. | TFun (args,_) ->
  1144. print ctx "public static function %s(" c.ef_name;
  1145. concat ctx ", " (fun (a,o,t) ->
  1146. print ctx "%s : %s" (s_ident a) (type_str ctx t c.ef_pos);
  1147. if o then spr ctx " = null";
  1148. ) args;
  1149. print ctx ") : %s {" ename;
  1150. print ctx " return new %s(\"%s\",%d,[" ename c.ef_name c.ef_index;
  1151. concat ctx "," (fun (a,_,_) -> spr ctx (s_ident a)) args;
  1152. print ctx "]); }";
  1153. | _ ->
  1154. print ctx "public static var %s : %s = new %s(\"%s\",%d)" c.ef_name ename ename c.ef_name c.ef_index;
  1155. ) e.e_constrs;
  1156. newline ctx;
  1157. (match Codegen.build_metadata ctx.inf.com (TEnumDecl e) with
  1158. | None -> ()
  1159. | Some e ->
  1160. print ctx "public static var __meta__ : * = ";
  1161. gen_expr ctx e;
  1162. newline ctx);
  1163. print ctx "public static var __constructs__ : Array = [%s];" (String.concat "," (List.map (fun s -> "\"" ^ Ast.s_escape s ^ "\"") e.e_names));
  1164. cl();
  1165. newline ctx;
  1166. print ctx "}";
  1167. pack();
  1168. newline ctx;
  1169. print ctx "}";
  1170. newline ctx
  1171. let generate_base_enum ctx =
  1172. let pack = open_block ctx in
  1173. spr ctx "\timport flash.Boot";
  1174. newline ctx;
  1175. spr ctx "public class enum {";
  1176. let cl = open_block ctx in
  1177. newline ctx;
  1178. spr ctx "public var tag : String";
  1179. newline ctx;
  1180. spr ctx "public var index : int";
  1181. newline ctx;
  1182. spr ctx "public var params : Array";
  1183. newline ctx;
  1184. spr ctx "public function toString() : String { return flash.Boot.enum_to_string(this); }";
  1185. cl();
  1186. newline ctx;
  1187. print ctx "}";
  1188. pack();
  1189. newline ctx;
  1190. print ctx "}";
  1191. newline ctx
  1192. let generate com =
  1193. let infos = {
  1194. com = com;
  1195. } in
  1196. generate_resources infos;
  1197. let ctx = init infos ([],"enum") in
  1198. generate_base_enum ctx;
  1199. close ctx;
  1200. let inits = ref [] in
  1201. List.iter (fun t ->
  1202. match t with
  1203. | TClassDecl c ->
  1204. let c = (match c.cl_path with
  1205. | ["flash"],"FlashXml__" -> { c with cl_path = [],"Xml" }
  1206. | (pack,name) -> { c with cl_path = (pack,protect name) }
  1207. ) in
  1208. if c.cl_extern then
  1209. (match c.cl_init with
  1210. | None -> ()
  1211. | Some e -> inits := e :: !inits)
  1212. else
  1213. let ctx = init infos c.cl_path in
  1214. generate_class ctx c;
  1215. close ctx
  1216. | TEnumDecl e ->
  1217. let pack,name = e.e_path in
  1218. let e = { e with e_path = (pack,protect name) } in
  1219. if e.e_extern then
  1220. ()
  1221. else
  1222. let ctx = init infos e.e_path in
  1223. generate_enum ctx e;
  1224. close ctx
  1225. | TTypeDecl _ | TAbstractDecl _ ->
  1226. ()
  1227. ) com.types;
  1228. (match com.main with
  1229. | None -> ()
  1230. | Some e -> inits := e :: !inits);
  1231. let ctx = init infos ([],"__main__") in
  1232. generate_main ctx (List.rev !inits);
  1233. close ctx