genas3.ml 36 KB

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