2
0

genas3.ml 34 KB

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