genswf.ml 40 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215
  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 Swf
  23. open As3
  24. open As3hl
  25. open Genswf9
  26. open Type
  27. open Common
  28. open Ast
  29. let rec make_tpath = function
  30. | HMPath (pack,name) ->
  31. let pdyn = ref false in
  32. let pack, name = match pack, name with
  33. | [], "void" -> [], "Void"
  34. | [], "int" -> [], "Int"
  35. | [], "uint" -> [], "UInt"
  36. | [], "Number" -> [], "Float"
  37. | [], "Boolean" -> [], "Bool"
  38. | [], "Object" -> ["flash";"utils"], "Object"
  39. | [], "Function" -> ["flash";"utils"], "Function"
  40. | [], "Class" | [],"Array" -> pdyn := true; pack, name
  41. | [], "Error" -> ["flash";"errors"], "Error"
  42. | [] , "XML" -> ["flash";"xml"], "XML"
  43. | [] , "XMLList" -> ["flash";"xml"], "XMLList"
  44. | [] , "QName" -> ["flash";"utils"], "QName"
  45. | [] , "Namespace" -> ["flash";"utils"], "Namespace"
  46. | [] , "RegExp" -> ["flash";"utils"], "RegExp"
  47. | ["__AS3__";"vec"] , "Vector" -> ["flash"], "Vector"
  48. | _ -> pack, name
  49. in
  50. {
  51. tpackage = pack;
  52. tname = name;
  53. tparams = if !pdyn then [TPType (CTPath { tpackage = []; tname = "Dynamic"; tparams = []; tsub = None; })] else[];
  54. tsub = None;
  55. }
  56. | HMName (id,ns) ->
  57. {
  58. tpackage = (match ns with
  59. | HNInternal (Some ns) -> ExtString.String.nsplit ns "."
  60. | HNPrivate (Some ns) ->
  61. (try
  62. let file, line = ExtString.String.split ns ".as$" in
  63. [file ^ "_" ^ line]
  64. with _ ->
  65. [])
  66. | _ -> []);
  67. tname = id;
  68. tparams = [];
  69. tsub = None;
  70. }
  71. | HMNSAny (id) ->
  72. {
  73. tpackage = [];
  74. tname = id;
  75. tparams = [];
  76. tsub = None;
  77. }
  78. | HMMultiName _ ->
  79. assert false
  80. | HMRuntimeName _ ->
  81. assert false
  82. | HMRuntimeNameLate ->
  83. assert false
  84. | HMMultiNameLate _ ->
  85. assert false
  86. | HMAttrib _ ->
  87. assert false
  88. | HMAny ->
  89. assert false
  90. | HMParams (t,params) ->
  91. let params = List.map (fun t -> TPType (CTPath (make_tpath t))) params in
  92. { (make_tpath t) with tparams = params }
  93. let make_param cl p =
  94. { tpackage = fst cl; tname = snd cl; tparams = [TPType (CTPath { tpackage = fst p; tname = snd p; tparams = []; tsub = None })]; tsub = None }
  95. let make_topt = function
  96. | None -> { tpackage = []; tname = "Dynamic"; tparams = []; tsub = None }
  97. | Some t -> make_tpath t
  98. let make_type t = CTPath (make_topt t)
  99. let make_dyn_type t =
  100. match make_topt t with
  101. | { tpackage = ["flash";"utils"]; tname = ("Object"|"Function") } -> make_type None
  102. | o -> CTPath o
  103. let is_valid_path com pack name =
  104. let rec loop = function
  105. | [] ->
  106. false
  107. | load :: l ->
  108. match load (pack,name) Ast.null_pos with
  109. | None -> loop l
  110. | Some (file,(_,a)) -> true
  111. in
  112. let file = Printf.sprintf "%s/%s.hx" (String.concat "/" pack) name in
  113. loop com.load_extern_type || (try ignore(Common.find_file com file); true with Not_found -> false)
  114. let build_class com c file =
  115. let path = make_tpath c.hlc_name in
  116. let pos = { pfile = file ^ "@" ^ s_type_path (path.tpackage,path.tname); pmin = 0; pmax = 0 } in
  117. match path with
  118. | { tpackage = ["flash";"utils"]; tname = ("Object"|"Function") } ->
  119. let inf = {
  120. d_name = path.tname;
  121. d_doc = None;
  122. d_params = [];
  123. d_meta = [];
  124. d_flags = [];
  125. d_data = CTPath { tpackage = []; tname = "Dynamic"; tparams = []; tsub = None; };
  126. } in
  127. (path.tpackage, [(ETypedef inf,pos)])
  128. | _ ->
  129. (* make flags *)
  130. let flags = [HExtern] in
  131. let flags = if c.hlc_interface then HInterface :: flags else flags in
  132. let flags = (match c.hlc_super with
  133. | None | Some (HMPath ([],"Object")) -> flags
  134. | Some (HMPath ([],"Function")) -> flags (* found in AIR SDK *)
  135. | Some s -> HExtends (make_tpath s) :: flags
  136. ) in
  137. let flags = List.map (fun i ->
  138. let i = (match i with
  139. | HMMultiName (Some id,ns) ->
  140. let rec loop = function
  141. | [] -> HMPath ([],id)
  142. | HNPublic (Some ns) :: _ when is_valid_path com (ExtString.String.nsplit ns ".") id -> HMPath (ExtString.String.nsplit ns ".",id)
  143. | _ :: l -> loop l
  144. in
  145. loop ns
  146. | HMPath _ -> i
  147. | _ -> assert false
  148. ) in
  149. if c.hlc_interface then HExtends (make_tpath i) else HImplements (make_tpath i)
  150. ) (Array.to_list c.hlc_implements) @ flags in
  151. let flags = if c.hlc_sealed || Common.defined com Define.FlashStrict then flags else HImplements (make_tpath (HMPath ([],"Dynamic"))) :: flags in
  152. (* make fields *)
  153. let getters = Hashtbl.create 0 in
  154. let setters = Hashtbl.create 0 in
  155. let override = Hashtbl.create 0 in
  156. let is_xml = (match path.tpackage, path.tname with
  157. | ["flash";"xml"], ("XML" | "XMLList") -> true
  158. | _ -> false
  159. ) in
  160. let make_field stat acc f =
  161. let meta = ref [] in
  162. let flags = (match f.hlf_name with
  163. | HMPath _ -> [APublic]
  164. | HMName (_,ns) ->
  165. (match ns with
  166. | HNPrivate _ | HNNamespace "http://www.adobe.com/2006/flex/mx/internal" -> []
  167. | HNNamespace ns ->
  168. if not (c.hlc_interface || is_xml) then meta := (Meta.Ns,[String ns]) :: !meta;
  169. [APublic]
  170. | HNExplicit _ | HNInternal _ | HNPublic _ ->
  171. [APublic]
  172. | HNStaticProtected _ | HNProtected _ ->
  173. meta := (Meta.Protected,[]) :: !meta;
  174. [APrivate])
  175. | _ -> []
  176. ) in
  177. if flags = [] then acc else
  178. let flags = if stat then AStatic :: flags else flags in
  179. let name = (make_tpath f.hlf_name).tname in
  180. let mk_meta() =
  181. List.map (fun (s,cl) -> s, List.map (fun c -> EConst c,pos) cl, pos) (!meta)
  182. in
  183. let cf = {
  184. cff_name = name;
  185. cff_doc = None;
  186. cff_pos = pos;
  187. cff_meta = mk_meta();
  188. cff_access = flags;
  189. cff_kind = FVar (None,None);
  190. } in
  191. match f.hlf_kind with
  192. | HFVar v ->
  193. if v.hlv_const then
  194. cf.cff_kind <- FProp ("default","never",Some (make_type v.hlv_type),None)
  195. else
  196. cf.cff_kind <- FVar (Some (make_dyn_type v.hlv_type),None);
  197. cf :: acc
  198. | HFMethod m when m.hlm_override ->
  199. Hashtbl.add override (name,stat) ();
  200. acc
  201. | HFMethod m ->
  202. (match m.hlm_kind with
  203. | MK3Normal ->
  204. let t = m.hlm_type in
  205. let p = ref 0 and pn = ref 0 in
  206. let make_type = if stat || name = "new" then make_dyn_type else make_type in
  207. let args = List.map (fun at ->
  208. let aname = (match t.hlmt_pnames with
  209. | None -> incr pn; "p" ^ string_of_int !pn
  210. | Some l ->
  211. match List.nth l !p with
  212. | None -> incr pn; "p" ^ string_of_int !pn
  213. | Some i -> i
  214. ) in
  215. let opt_val = (match t.hlmt_dparams with
  216. | None -> None
  217. | Some l ->
  218. try
  219. Some (List.nth l (!p - List.length t.hlmt_args + List.length l))
  220. with
  221. _ -> None
  222. ) in
  223. incr p;
  224. let t = make_type at in
  225. let is_opt = ref false in
  226. let def_val = match opt_val with
  227. | None -> None
  228. | Some v ->
  229. let v = (match v with
  230. | HVNone | HVNull | HVNamespace _ | HVString _ ->
  231. is_opt := true;
  232. None
  233. | HVBool b ->
  234. Some (Ident (if b then "true" else "false"))
  235. | HVInt i | HVUInt i ->
  236. Some (Int (Int32.to_string i))
  237. | HVFloat f ->
  238. Some (Float (string_of_float f))
  239. ) in
  240. match v with
  241. | None -> None
  242. | Some v ->
  243. (* add for --gen-hx-classes generation *)
  244. meta := (Meta.DefParam,[String aname;v]) :: !meta;
  245. Some (EConst v,pos)
  246. in
  247. (aname,!is_opt,Some t,def_val)
  248. ) t.hlmt_args in
  249. let args = if t.hlmt_var_args then
  250. args @ List.map (fun _ -> incr pn; ("p" ^ string_of_int !pn,true,Some (make_type None),None)) [1;2;3;4;5]
  251. else args in
  252. let f = {
  253. f_params = [];
  254. f_args = args;
  255. f_type = Some (make_type t.hlmt_ret);
  256. f_expr = None;
  257. } in
  258. cf.cff_meta <- mk_meta();
  259. cf.cff_kind <- FFun f;
  260. cf :: acc
  261. | MK3Getter ->
  262. Hashtbl.add getters (name,stat) m.hlm_type.hlmt_ret;
  263. acc
  264. | MK3Setter ->
  265. Hashtbl.add setters (name,stat) (match m.hlm_type.hlmt_args with [t] -> t | _ -> assert false);
  266. acc
  267. )
  268. | _ -> acc
  269. in
  270. let fields = if c.hlc_interface then [] else make_field false [] {
  271. hlf_name = HMPath ([],"new");
  272. hlf_slot = 0;
  273. hlf_metas = None;
  274. hlf_kind = HFMethod {
  275. hlm_type = { c.hlc_construct with hlmt_ret = Some (HMPath ([],"void")) };
  276. hlm_final = false;
  277. hlm_override = false;
  278. hlm_kind = MK3Normal
  279. }
  280. } in
  281. let fields = Array.fold_left (make_field false) fields c.hlc_fields in
  282. let fields = Array.fold_left (make_field true) fields c.hlc_static_fields in
  283. let make_get_set name stat tget tset =
  284. let get, set, t = (match tget, tset with
  285. | None, None -> assert false
  286. | Some t, None -> true, false, t
  287. | None, Some t -> false, true, t
  288. | Some t1, Some t2 -> true, true, (if t1 <> t2 then None else t1)
  289. ) in
  290. let t = if name = "endian" then Some (HMPath (["flash";"utils"],"Endian")) else t in
  291. let flags = [APublic] in
  292. let flags = if stat then AStatic :: flags else flags in
  293. {
  294. cff_name = name;
  295. cff_pos = pos;
  296. cff_doc = None;
  297. cff_access = flags;
  298. cff_meta = [];
  299. cff_kind = if get && set then FVar (Some (make_dyn_type t), None) else FProp ((if get then "default" else "never"),(if set then "default" else "never"),Some (make_dyn_type t),None);
  300. }
  301. in
  302. let fields = Hashtbl.fold (fun (name,stat) t acc ->
  303. if Hashtbl.mem override (name,stat) then acc else
  304. make_get_set name stat (Some t) (try Some (Hashtbl.find setters (name,stat)) with Not_found -> None) :: acc
  305. ) getters fields in
  306. let fields = Hashtbl.fold (fun (name,stat) t acc ->
  307. if Hashtbl.mem getters (name,stat) || Hashtbl.mem override (name,stat) then
  308. acc
  309. else
  310. make_get_set name stat None (Some t) :: acc
  311. ) setters fields in
  312. try
  313. (*
  314. If the class only contains static String constants, make it an enum
  315. *)
  316. let real_type = ref "" in
  317. let rec loop = function
  318. | [] -> []
  319. | f :: l ->
  320. match f.cff_kind with
  321. | FVar (Some (CTPath { tpackage = []; tname = ("String" | "Int" | "UInt") as tname }),None) when List.mem AStatic f.cff_access ->
  322. if !real_type = "" then real_type := tname else if !real_type <> tname then raise Exit;
  323. {
  324. ec_name = f.cff_name;
  325. ec_pos = pos;
  326. ec_args = [];
  327. ec_params = [];
  328. ec_meta = [];
  329. ec_doc = None;
  330. ec_type = None;
  331. } :: loop l
  332. | FFun { f_args = [] } when f.cff_name = "new" -> loop l
  333. | _ -> raise Exit
  334. in
  335. List.iter (function HExtends _ | HImplements _ -> raise Exit | _ -> ()) flags;
  336. let constr = loop fields in
  337. let name = "fakeEnum:" ^ String.concat "." (path.tpackage @ [path.tname]) in
  338. if not (Common.raw_defined com name) then raise Exit;
  339. let enum_data = {
  340. d_name = path.tname;
  341. d_doc = None;
  342. d_params = [];
  343. d_meta = [(Meta.FakeEnum,[EConst (Ident !real_type),pos],pos)];
  344. d_flags = [EExtern];
  345. d_data = constr;
  346. } in
  347. (path.tpackage, [(EEnum enum_data,pos)])
  348. with Exit ->
  349. let class_data = {
  350. d_name = path.tname;
  351. d_doc = None;
  352. d_params = [];
  353. d_meta = if c.hlc_final && List.exists (fun f -> f.cff_name <> "new" && not (List.mem AStatic f.cff_access)) fields then [Meta.Final,[],pos] else [];
  354. d_flags = flags;
  355. d_data = fields;
  356. } in
  357. (path.tpackage, [(EClass class_data,pos)])
  358. let extract_data (_,tags) =
  359. let t = Common.timer "read swf" in
  360. let h = Hashtbl.create 0 in
  361. let rec loop_field f =
  362. match f.hlf_kind with
  363. | HFClass c ->
  364. let path = make_tpath f.hlf_name in
  365. (match path with
  366. | { tpackage = []; tname = "Float" | "Bool" | "Int" | "UInt" | "Dynamic" } -> ()
  367. | { tpackage = _; tname = "MethodClosure" } -> ()
  368. | _ -> Hashtbl.add h (path.tpackage,path.tname) c)
  369. | _ -> ()
  370. in
  371. List.iter (fun t ->
  372. match t.tdata with
  373. | TActionScript3 (_,as3) ->
  374. List.iter (fun i -> Array.iter loop_field i.hls_fields) (As3hlparse.parse as3)
  375. | _ -> ()
  376. ) tags;
  377. t();
  378. h
  379. let remove_debug_infos as3 =
  380. let hl = As3hlparse.parse as3 in
  381. let methods = Hashtbl.create 0 in
  382. let rec loop_field f =
  383. { f with hlf_kind = (match f.hlf_kind with
  384. | HFMethod m -> HFMethod { m with hlm_type = loop_method m.hlm_type }
  385. | HFFunction f -> HFFunction (loop_method f)
  386. | HFVar v -> HFVar v
  387. | HFClass c -> HFClass (loop_class c))
  388. }
  389. and loop_class c =
  390. (* mutate in order to preserve sharing *)
  391. c.hlc_construct <- loop_method c.hlc_construct;
  392. c.hlc_fields <- Array.map loop_field c.hlc_fields;
  393. c.hlc_static_construct <- loop_method c.hlc_static_construct;
  394. c.hlc_static_fields <- Array.map loop_field c.hlc_static_fields;
  395. c
  396. and loop_static s =
  397. {
  398. hls_method = loop_method s.hls_method;
  399. hls_fields = Array.map loop_field s.hls_fields;
  400. }
  401. and loop_method m =
  402. try
  403. Hashtbl.find methods m.hlmt_index
  404. with Not_found ->
  405. let m2 = { m with hlmt_debug_name = None; hlmt_pnames = None } in
  406. Hashtbl.add methods m.hlmt_index m2;
  407. m2.hlmt_function <- (match m.hlmt_function with None -> None | Some f -> Some (loop_function f));
  408. m2
  409. and loop_function f =
  410. let cur = ref 0 in
  411. let positions = MultiArray.map (fun op ->
  412. let p = !cur in
  413. (match op with
  414. | HDebugReg _ | HDebugLine _ | HDebugFile _ | HBreakPointLine _ | HTimestamp -> ()
  415. | _ -> incr cur);
  416. p
  417. ) f.hlf_code in
  418. MultiArray.add positions (!cur);
  419. let code = MultiArray.create() in
  420. MultiArray.iteri (fun pos op ->
  421. match op with
  422. | HDebugReg _ | HDebugLine _ | HDebugFile _ | HBreakPointLine _ | HTimestamp -> ()
  423. | _ ->
  424. let p delta =
  425. MultiArray.get positions (pos + delta) - MultiArray.length code
  426. in
  427. let op = (match op with
  428. | HJump (j,delta) -> HJump (j, p delta)
  429. | HSwitch (d,deltas) -> HSwitch (p d,List.map p deltas)
  430. | HFunction m -> HFunction (loop_method m)
  431. | HCallStatic (m,args) -> HCallStatic (loop_method m,args)
  432. | HClassDef c -> HClassDef c (* mutated *)
  433. | _ -> op) in
  434. MultiArray.add code op
  435. ) f.hlf_code;
  436. f.hlf_code <- code;
  437. f.hlf_trys <- Array.map (fun t ->
  438. {
  439. t with
  440. hltc_start = MultiArray.get positions t.hltc_start;
  441. hltc_end = MultiArray.get positions t.hltc_end;
  442. hltc_handle = MultiArray.get positions t.hltc_handle;
  443. }
  444. ) f.hlf_trys;
  445. f
  446. in
  447. As3hlparse.flatten (List.map loop_static hl)
  448. let parse_swf com file =
  449. let t = Common.timer "read swf" in
  450. let is_swc = file_extension file = "swc" in
  451. let file = (try Common.find_file com file with Not_found -> failwith ((if is_swc then "SWC" else "SWF") ^ " Library not found : " ^ file)) in
  452. let ch = if is_swc then begin
  453. let zip = Zip.open_in file in
  454. try
  455. let entry = Zip.find_entry zip "library.swf" in
  456. let ch = IO.input_string (Zip.read_entry zip entry) in
  457. Zip.close_in zip;
  458. ch
  459. with _ ->
  460. Zip.close_in zip;
  461. failwith ("The input swc " ^ file ^ " is corrupted")
  462. end else
  463. IO.input_channel (open_in_bin file)
  464. in
  465. let h, tags = try
  466. Swf.parse ch
  467. with Out_of_memory ->
  468. failwith ("Out of memory while parsing " ^ file)
  469. | _ ->
  470. failwith ("The input swf " ^ file ^ " is corrupted")
  471. in
  472. IO.close_in ch;
  473. List.iter (fun t ->
  474. match t.tdata with
  475. | TActionScript3 (id,as3) when not com.debug && not com.display ->
  476. t.tdata <- TActionScript3 (id,remove_debug_infos as3)
  477. | _ -> ()
  478. ) tags;
  479. t();
  480. (h,tags)
  481. let add_swf_lib com file extern =
  482. let swf_data = ref None in
  483. let swf_classes = ref None in
  484. let getSWF = (fun() ->
  485. match !swf_data with
  486. | None ->
  487. let d = parse_swf com file in
  488. swf_data := Some d;
  489. d
  490. | Some d -> d
  491. ) in
  492. let extract = (fun() ->
  493. match !swf_classes with
  494. | None ->
  495. let d = extract_data (getSWF()) in
  496. swf_classes := Some d;
  497. d
  498. | Some d -> d
  499. ) in
  500. let build cl p =
  501. match (try Some (Hashtbl.find (extract()) cl) with Not_found -> None) with
  502. | None -> None
  503. | Some c -> Some (file, build_class com c file)
  504. in
  505. com.load_extern_type <- com.load_extern_type @ [build];
  506. if not extern then com.swf_libs <- (file,getSWF,extract) :: com.swf_libs
  507. (* ------------------------------- *)
  508. let tag ?(ext=false) d = {
  509. tid = 0;
  510. textended = ext;
  511. tdata = d;
  512. }
  513. let swf_ver = function
  514. | 6. -> 6
  515. | 7. -> 7
  516. | 8. -> 8
  517. | 9. -> 9
  518. | 10. | 10.1 -> 10
  519. | 10.2 -> 11
  520. | 10.3 -> 12
  521. | 11. -> 13
  522. | 11.1 -> 14
  523. | 11.2 -> 15
  524. | 11.3 -> 16
  525. | 11.4 -> 17
  526. | 11.5 -> 18
  527. | 11.6 -> 19
  528. | 11.7 -> 20
  529. | 11.8 -> 21
  530. | v -> failwith ("Invalid SWF version " ^ string_of_float v)
  531. let convert_header com (w,h,fps,bg) =
  532. let high = (max w h) * 20 in
  533. let rec loop b =
  534. if 1 lsl b > high then b else loop (b + 1)
  535. in
  536. let bits = loop 0 in
  537. {
  538. h_version = swf_ver com.flash_version;
  539. h_size = {
  540. rect_nbits = bits + 1;
  541. left = 0;
  542. top = 0;
  543. right = w * 20;
  544. bottom = h * 20;
  545. };
  546. h_frame_count = 1;
  547. h_fps = to_float16 (if fps > 127.0 then 127.0 else fps);
  548. h_compressed = not (Common.defined com Define.NoSwfCompress);
  549. } , bg
  550. let default_header com =
  551. convert_header com (400,300,30.,0xFFFFFF)
  552. type dependency_kind =
  553. | DKInherit
  554. | DKExpr
  555. | DKType
  556. let build_dependencies t =
  557. let h = ref PMap.empty in
  558. let add_path p k =
  559. h := PMap.add (p,k) () !h;
  560. in
  561. let rec add_type_rec l t =
  562. if List.memq t l then () else
  563. match t with
  564. | TEnum (e,pl) ->
  565. add_path e.e_path DKType;
  566. List.iter (add_type_rec (t::l)) pl;
  567. | TInst (c,pl) ->
  568. (match c.cl_kind with KTypeParameter _ -> () | _ -> add_path c.cl_path DKType);
  569. List.iter (add_type_rec (t::l)) pl;
  570. | TAbstract (a,pl) ->
  571. add_path a.a_path DKType;
  572. List.iter (add_type_rec (t::l)) pl;
  573. | TFun (pl,t2) ->
  574. List.iter (fun (_,_,t2) -> add_type_rec (t::l) t2) pl;
  575. add_type_rec (t::l) t2;
  576. | TAnon a ->
  577. PMap.iter (fun _ f -> add_type_rec (t::l) f.cf_type) a.a_fields
  578. | TDynamic t2 ->
  579. add_type_rec (t::l) t2;
  580. | TLazy f ->
  581. add_type_rec l ((!f)())
  582. | TMono r ->
  583. (match !r with
  584. | None -> ()
  585. | Some t -> add_type_rec l t)
  586. | TType (tt,pl) ->
  587. add_type_rec (t::l) tt.t_type;
  588. List.iter (add_type_rec (t::l)) pl
  589. and add_type t =
  590. add_type_rec [] t
  591. and add_expr e =
  592. match e.eexpr with
  593. | TTypeExpr t -> add_path (Type.t_path t) DKExpr
  594. | TNew (c,pl,el) ->
  595. add_path c.cl_path DKExpr;
  596. List.iter add_type pl;
  597. List.iter add_expr el;
  598. | TFunction f ->
  599. List.iter (fun (v,_) -> add_type v.v_type) f.tf_args;
  600. add_type f.tf_type;
  601. add_expr f.tf_expr;
  602. | TFor (v,e1,e2) ->
  603. add_type v.v_type;
  604. add_expr e1;
  605. add_expr e2;
  606. | TVars vl ->
  607. List.iter (fun (v,e) ->
  608. add_type v.v_type;
  609. match e with
  610. | None -> ()
  611. | Some e -> add_expr e
  612. ) vl
  613. | _ ->
  614. Type.iter add_expr e
  615. and add_field f =
  616. add_type f.cf_type;
  617. match f.cf_expr with
  618. | None -> ()
  619. | Some e -> add_expr e
  620. in
  621. let add_inherit (c,pl) =
  622. add_path c.cl_path DKInherit;
  623. List.iter add_type pl;
  624. in
  625. (match t with
  626. | TClassDecl c when not c.cl_extern ->
  627. List.iter add_field c.cl_ordered_fields;
  628. List.iter add_field c.cl_ordered_statics;
  629. (match c.cl_constructor with
  630. | None -> ()
  631. | Some f ->
  632. add_field f;
  633. if c.cl_path <> (["flash"],"Boot") then add_path (["flash"],"Boot") DKExpr;
  634. );
  635. (match c.cl_init with
  636. | None -> ()
  637. | Some e -> add_expr e);
  638. (match c.cl_super with
  639. | None -> add_path ([],"Object") DKInherit;
  640. | Some x -> add_inherit x);
  641. List.iter (fun (_,t) ->
  642. (* add type-parameters constraints dependencies *)
  643. match follow t with
  644. | TInst (c,_) -> List.iter add_inherit c.cl_implements
  645. | _ -> ()
  646. ) c.cl_types;
  647. List.iter add_inherit c.cl_implements;
  648. | TEnumDecl e when not e.e_extern ->
  649. PMap.iter (fun _ f -> add_type f.ef_type) e.e_constrs;
  650. | _ -> ());
  651. h := PMap.remove (([],"Int"),DKType) (!h);
  652. h := PMap.remove (([],"Int"),DKExpr) (!h);
  653. h := PMap.remove (([],"Void"),DKType) (!h);
  654. PMap.foldi (fun (c,k) () acc -> (c,k) :: acc) (!h) []
  655. let build_swc_catalog com types =
  656. let node x att l =
  657. Xml.Element (x,att,l)
  658. in
  659. let make_path t sep =
  660. let path, name = t_path t in
  661. String.concat sep (path @ [name])
  662. in
  663. let make_id path =
  664. match Genswf9.real_path path with
  665. | [],n -> n
  666. | l,n -> (String.concat "." l) ^ ":" ^ n
  667. in
  668. let build_script t =
  669. let deps = build_dependencies t in
  670. node "script" [("name",make_path t "/");("mod","0")] ([
  671. node "def" ["id",make_id (t_path t)] [];
  672. node "dep" [("id","AS3");("type","n")] [];
  673. ] @ List.map (fun (p,k) ->
  674. let t = (match k with
  675. | DKInherit -> "i"
  676. | DKExpr -> (match p with "flash" :: _ :: _ , _ -> "i" | _ -> "e")
  677. | DKType -> "s"
  678. ) in
  679. node "dep" [("id",make_id p);("type",t)] []
  680. ) deps)
  681. in
  682. let x = node "swc" ["xmlns","http://www.adobe.com/flash/swccatalog/9"] [
  683. node "versions" [] [
  684. node "swc" ["version","1.2"] [];
  685. node "haxe" ["version",Printf.sprintf "%d.%.2d" (com.version/100) (com.version mod 100)] [];
  686. ];
  687. node "features" [] [
  688. node "feature-script-deps" [] [];
  689. node "feature-files" [] [];
  690. ];
  691. node "libraries" [] [
  692. node "library" ["path","library.swf"] (List.map build_script types)
  693. ];
  694. node "files" [] [];
  695. ] in
  696. "<?xml version=\"1.0\" encoding =\"utf-8\"?>\n" ^ Xml.to_string_fmt x
  697. let remove_classes toremove lib hcl =
  698. let lib = lib() in
  699. match !toremove with
  700. | [] -> lib
  701. | _ ->
  702. let hcl = hcl() in
  703. match List.filter (fun c -> Hashtbl.mem hcl c) (!toremove) with
  704. | [] -> lib
  705. | classes ->
  706. let rec tags = function
  707. | [] -> []
  708. | t :: l ->
  709. match t.tdata with
  710. | TActionScript3 (h,data) ->
  711. let data = As3hlparse.parse data in
  712. let rec loop f =
  713. match f.hlf_kind with
  714. | HFClass _ ->
  715. let path = make_tpath f.hlf_name in
  716. not (List.mem (path.tpackage,path.tname) classes)
  717. | _ -> true
  718. in
  719. let data = List.map (fun s -> { s with hls_fields = Array.of_list (List.filter loop (Array.to_list s.hls_fields)) }) data in
  720. let data = List.filter (fun s -> Array.length s.hls_fields > 0) data in
  721. (if data = [] then
  722. tags l
  723. else
  724. { t with tdata = TActionScript3 (h,As3hlparse.flatten data) } :: tags l)
  725. | _ ->
  726. t :: tags l
  727. in
  728. toremove := List.filter (fun p -> not (List.mem p classes)) !toremove;
  729. fst lib, tags (snd lib)
  730. let build_swf8 com codeclip exports =
  731. let code, clips = Genswf8.generate com in
  732. let cid = ref 0 in
  733. let clips = List.fold_left (fun acc m ->
  734. let ename = Ast.s_type_path m in
  735. if Hashtbl.mem exports ename then
  736. acc
  737. else begin
  738. incr cid;
  739. tag ~ext:true (TClip { c_id = !cid; c_frame_count = 1; c_tags = [] }) ::
  740. tag ~ext:true (TExport [{ exp_id = !cid; exp_name = ename }]) ::
  741. acc
  742. end;
  743. ) [] clips in
  744. let code = (match codeclip with
  745. | None -> List.map tag code
  746. | Some link ->
  747. incr cid;
  748. [
  749. tag (TClip {
  750. c_id = !cid;
  751. c_frame_count = 1;
  752. c_tags = List.map tag code @ [tag TShowFrame];
  753. });
  754. tag (TExport [{ exp_id = !cid; exp_name = link }]);
  755. ]
  756. ) in
  757. clips @ code
  758. type file_format =
  759. | BJPG
  760. | BPNG
  761. | BGIF
  762. | SWAV
  763. | SMP3
  764. let detect_format data p =
  765. match (try data.[0],data.[1],data.[2] with _ -> '\x00','\x00','\x00') with
  766. | '\xFF', '\xD8', _ -> BJPG
  767. | '\x89', 'P', 'N' -> BPNG
  768. | 'R', 'I', 'F' -> SWAV
  769. | 'I', 'D', '3' -> SMP3
  770. | '\xFF', i, _ when (int_of_char i) land 0xE2 = 0xE2 -> SMP3
  771. | 'G', 'I', 'F' -> BGIF
  772. | _ ->
  773. error "Unknown file format" p
  774. let build_swf9 com file swc =
  775. let boot_name = if swc <> None || Common.defined com Define.HaxeBoot then "haxe" else "boot_" ^ (String.sub (Digest.to_hex (Digest.string (Filename.basename file))) 0 4) in
  776. let code = Genswf9.generate com boot_name in
  777. let code = (match swc with
  778. | Some cat ->
  779. cat := build_swc_catalog com (List.map (fun (t,_,_) -> t) code);
  780. List.map (fun (t,m,f) ->
  781. let path = (match t_path t with
  782. | [], name -> name
  783. | path, name -> String.concat "/" path ^ "/" ^ name
  784. ) in
  785. let init = {
  786. hls_method = m;
  787. hls_fields = [|f|];
  788. } in
  789. tag (TActionScript3 (Some (1,path),As3hlparse.flatten [init]))
  790. ) code
  791. | None ->
  792. let inits = List.map (fun (_,m,f) ->
  793. {
  794. hls_method = m;
  795. hls_fields = [|f|];
  796. }
  797. ) code in
  798. [tag (TActionScript3 (None,As3hlparse.flatten inits))]
  799. ) in
  800. let cid = ref 0 in
  801. let classes = ref [{ f9_cid = None; f9_classname = boot_name }] in
  802. let res = Hashtbl.fold (fun name data acc ->
  803. incr cid;
  804. classes := { f9_cid = Some !cid; f9_classname = s_type_path (Genswf9.resource_path name) } :: !classes;
  805. tag (TBinaryData (!cid,data)) :: acc
  806. ) com.resources [] in
  807. let load_file_data file p =
  808. let file = try Common.find_file com file with Not_found -> file in
  809. if String.length file > 5 && String.sub file 0 5 = "data:" then
  810. String.sub file 5 (String.length file - 5)
  811. else
  812. (try Std.input_file ~bin:true file with Invalid_argument("String.create") -> error "File is too big (max 16MB allowed)" p | _ -> error "File not found" p)
  813. in
  814. let bmp = List.fold_left (fun acc t ->
  815. match t with
  816. | TClassDecl c ->
  817. let rec loop = function
  818. | [] -> acc
  819. | (Meta.Font,(EConst (String file),p) :: args,_) :: l ->
  820. let file = try Common.find_file com file with Not_found -> file in
  821. let ch = try open_in_bin file with _ -> error "File not found" p in
  822. let ttf = TTFParser.parse ch in
  823. close_in ch;
  824. let range_str = match args with
  825. | [EConst (String str),_] -> str
  826. | _ -> ""
  827. in
  828. let ttf_swf = TTFSwfWriter.to_swf ttf range_str in
  829. let ch = IO.output_string () in
  830. let b = IO.output_bits ch in
  831. TTFSwfWriter.write_font2 ch b ttf_swf;
  832. let data = IO.close_out ch in
  833. incr cid;
  834. classes := { f9_cid = Some !cid; f9_classname = s_type_path c.cl_path } :: !classes;
  835. tag (TFont3 {
  836. cd_id = !cid;
  837. cd_data = data;
  838. }) :: loop l
  839. | (Meta.Bitmap,[EConst (String file),p],_) :: l ->
  840. let data = load_file_data file p in
  841. incr cid;
  842. classes := { f9_cid = Some !cid; f9_classname = s_type_path c.cl_path } :: !classes;
  843. let raw() =
  844. tag (TBitsJPEG2 { bd_id = !cid; bd_data = data; bd_table = None; bd_alpha = None; bd_deblock = Some 0 })
  845. in
  846. let t = (match detect_format data p with
  847. | BPNG ->
  848. (*
  849. There is a bug in Flash PNG decoder for 24-bits PNGs : Color such has 0xFF00FF is decoded as 0xFE00FE.
  850. In that particular case, we will then embed the decoded PNG bytes instead.
  851. *)
  852. (try
  853. let png = Png.parse (IO.input_string data) in
  854. let h = Png.header png in
  855. (match h.Png.png_color with
  856. | Png.ClTrueColor (Png.TBits8,Png.NoAlpha) ->
  857. if h.Png.png_width * h.Png.png_height * 4 > Sys.max_string_length then begin
  858. com.warning "Flash will loose some color information for this file, add alpha channel to preserve it" p;
  859. raise Exit;
  860. end;
  861. let data = Extc.unzip (Png.data png) in
  862. let raw_data = Png.filter png data in
  863. let cmp_data = Extc.zip raw_data in
  864. tag ~ext:true (TBitsLossless2 { bll_id = !cid; bll_format = 5; bll_width = h.Png.png_width; bll_height = h.Png.png_height; bll_data = cmp_data })
  865. | _ -> raw())
  866. with Exit ->
  867. raw()
  868. | _ ->
  869. com.error ("Failed to decode this PNG " ^ file) p;
  870. raw();
  871. )
  872. | _ -> raw()
  873. ) in
  874. t :: loop l
  875. | (Meta.Bitmap,[EConst (String dfile),p1;EConst (String afile),p2],_) :: l ->
  876. let ddata = load_file_data dfile p1 in
  877. let adata = load_file_data afile p2 in
  878. (match detect_format ddata p1 with
  879. | BJPG -> ()
  880. | _ -> error "RGB channel must be a JPG file" p1);
  881. (match detect_format adata p2 with
  882. | BPNG -> ()
  883. | _ -> error "Alpha channel must be a PNG file" p2);
  884. let png = Png.parse (IO.input_string adata) in
  885. let h = Png.header png in
  886. let amask = (match h.Png.png_color with
  887. | Png.ClTrueColor (Png.TBits8,Png.HaveAlpha) ->
  888. let data = Extc.unzip (Png.data png) in
  889. let raw_data = Png.filter png data in
  890. let alpha = String.make (h.Png.png_width * h.Png.png_height) '\000' in
  891. for i = 0 to String.length alpha do
  892. String.unsafe_set alpha i (String.unsafe_get raw_data (i lsl 2));
  893. done;
  894. Extc.zip alpha
  895. | _ -> error "PNG file must contain 8 bit alpha channel" p2
  896. ) in
  897. incr cid;
  898. classes := { f9_cid = Some !cid; f9_classname = s_type_path c.cl_path } :: !classes;
  899. tag (TBitsJPEG3 { bd_id = !cid; bd_data = ddata; bd_table = None; bd_alpha = Some amask; bd_deblock = Some 0 }) :: loop l
  900. | (Meta.File,[EConst (String file),p],_) :: l ->
  901. let data = load_file_data file p in
  902. incr cid;
  903. classes := { f9_cid = Some !cid; f9_classname = s_type_path c.cl_path } :: !classes;
  904. tag (TBinaryData (!cid,data)) :: loop l
  905. | (Meta.Sound,[EConst (String file),p],_) :: l ->
  906. let data = load_file_data file p in
  907. let make_flags fmt mono freq bits =
  908. let fbits = (match freq with 5512 when fmt <> 2 -> 0 | 11025 -> 1 | 22050 -> 2 | 44100 -> 3 | _ -> failwith ("Unsupported frequency " ^ string_of_int freq)) in
  909. let bbits = (match bits with 8 -> 0 | 16 -> 1 | _ -> failwith ("Unsupported bits " ^ string_of_int bits)) in
  910. (fmt lsl 4) lor (fbits lsl 2) lor (bbits lsl 1) lor (if mono then 0 else 1)
  911. in
  912. let flags, samples, data = (match detect_format data p with
  913. | SWAV ->
  914. (try
  915. let i = IO.input_string data in
  916. if IO.nread i 4 <> "RIFF" then raise Exit;
  917. ignore(IO.nread i 4); (* size *)
  918. if IO.nread i 4 <> "WAVE" || IO.nread i 4 <> "fmt " then raise Exit;
  919. let chunk_size = IO.read_i32 i in
  920. if not (chunk_size = 0x10 || chunk_size = 0x12 || chunk_size = 0x40) then failwith ("Unsupported chunk size " ^ string_of_int chunk_size);
  921. if IO.read_ui16 i <> 1 then failwith "Not a PCM file";
  922. let chan = IO.read_ui16 i in
  923. if chan > 2 then failwith "Too many channels";
  924. let freq = IO.read_i32 i in
  925. ignore(IO.read_i32 i);
  926. ignore(IO.read_i16 i);
  927. let bits = IO.read_ui16 i in
  928. if chunk_size <> 0x10 then ignore(IO.nread i (chunk_size - 0x10));
  929. if IO.nread i 4 <> "data" then raise Exit;
  930. let data_size = IO.read_i32 i in
  931. let data = IO.nread i data_size in
  932. make_flags 0 (chan = 1) freq bits, (data_size * 8 / (chan * bits)), data
  933. with Exit | IO.No_more_input | IO.Overflow _ ->
  934. error "Invalid WAV file" p
  935. | Failure msg ->
  936. error ("Invalid WAV file (" ^ msg ^ ")") p
  937. )
  938. | SMP3 ->
  939. (try
  940. let sampling = ref 0 in
  941. let mono = ref false in
  942. let samples = ref 0 in
  943. let i = IO.input_string data in
  944. let rec read_frame() =
  945. match (try IO.read_byte i with IO.No_more_input -> -1) with
  946. | -1 ->
  947. ()
  948. | 0x49 ->
  949. (* ID3 *)
  950. if IO.nread i 2 <> "D3" then raise Exit;
  951. ignore(IO.read_ui16 i); (* version *)
  952. ignore(IO.read_byte i); (* flags *)
  953. let size = IO.read_byte i land 0x7F in
  954. let size = size lsl 7 lor (IO.read_byte i land 0x7F) in
  955. let size = size lsl 7 lor (IO.read_byte i land 0x7F) in
  956. let size = size lsl 7 lor (IO.read_byte i land 0x7F) in
  957. ignore(IO.nread i size); (* id3 data *)
  958. read_frame()
  959. | 0x54 ->
  960. (* TAG and TAG+ *)
  961. if IO.nread i 3 = "AG+" then ignore(IO.nread i 223) else ignore(IO.nread i 124);
  962. read_frame()
  963. | 0xFF ->
  964. let infos = IO.read_byte i in
  965. let ver = (infos lsr 3) land 3 in
  966. sampling := [|11025;0;22050;44100|].(ver);
  967. let layer = (infos lsr 1) land 3 in
  968. let bits = IO.read_byte i in
  969. let bitrate = (if ver = 3 then [|0;32;40;48;56;64;80;96;112;128;160;192;224;256;320;-1|] else [|0;8;16;24;32;40;48;56;64;80;96;112;128;144;160;-1|]).(bits lsr 4) in
  970. let srate = [|
  971. [|11025;12000;8000;-1|];
  972. [|-1;-1;-1;-1|];
  973. [|22050;24000;16000;-1|];
  974. [|44100;48000;32000;-1|];
  975. |].(ver).((bits lsr 2) land 3) in
  976. let pad = (bits lsr 1) land 1 in
  977. mono := (IO.read_byte i) lsr 6 = 3;
  978. let bpp = (if ver = 3 then 144 else 72) in
  979. let size = ((bpp * bitrate * 1000) / srate) + pad - 4 in
  980. ignore(IO.nread i size);
  981. samples := !samples + (if layer = 3 then 384 else 1152);
  982. read_frame()
  983. | _ ->
  984. raise Exit
  985. in
  986. read_frame();
  987. make_flags 2 !mono !sampling 16, (!samples), ("\x00\x00" ^ data)
  988. with Exit | IO.No_more_input | IO.Overflow _ ->
  989. error "Invalid MP3 file" p
  990. | Failure msg ->
  991. error ("Invalid MP3 file (" ^ msg ^ ")") p
  992. )
  993. | _ ->
  994. error "Sound extension not supported (only WAV or MP3)" p
  995. ) in
  996. incr cid;
  997. classes := { f9_cid = Some !cid; f9_classname = s_type_path c.cl_path } :: !classes;
  998. tag (TSound { so_id = !cid; so_flags = flags; so_samples = samples; so_data = data }) :: loop l
  999. | _ :: l -> loop l
  1000. in
  1001. loop c.cl_meta
  1002. | _ -> acc
  1003. ) [] com.types in
  1004. let clips = [tag (TF9Classes (List.rev !classes))] in
  1005. res @ bmp @ code @ clips
  1006. let merge com file priority (h1,tags1) (h2,tags2) =
  1007. (* prioritize header+bgcolor for first swf *)
  1008. let header = if priority then { h2 with h_version = max h2.h_version (swf_ver com.flash_version) } else h1 in
  1009. let tags1 = if priority then List.filter (function { tdata = TSetBgColor _ } -> false | _ -> true) tags1 else tags1 in
  1010. (* remove unused tags *)
  1011. let use_stage = priority && Common.defined com Define.FlashUseStage in
  1012. let classes = ref [] in
  1013. let nframe = ref 0 in
  1014. let tags2 = List.filter (fun t ->
  1015. match t.tdata with
  1016. | TPlaceObject2 _
  1017. | TPlaceObject3 _
  1018. | TRemoveObject2 _
  1019. | TRemoveObject _ -> use_stage
  1020. | TShowFrame -> incr nframe; use_stage
  1021. | TFilesAttributes _ | TEnableDebugger2 _ | TScenes _ -> false
  1022. | TMetaData _ -> not (Common.defined com Define.SwfMetadata)
  1023. | TSetBgColor _ -> priority
  1024. | TExport el when !nframe = 0 && com.flash_version >= 9. ->
  1025. let el = List.filter (fun e ->
  1026. let path = parse_path e.exp_name in
  1027. let b = List.exists (fun t -> t_path t = path) com.types in
  1028. if not b && fst path = [] then List.iter (fun t ->
  1029. if snd (t_path t) = snd path then error ("Linkage name '" ^ snd path ^ "' in '" ^ file ^ "' should be '" ^ s_type_path (t_path t) ^"'") (t_infos t).mt_pos;
  1030. ) com.types;
  1031. b
  1032. ) el in
  1033. classes := !classes @ List.map (fun e -> { f9_cid = Some e.exp_id; f9_classname = e.exp_name }) el;
  1034. false
  1035. | TF9Classes el when !nframe = 0 ->
  1036. if com.flash_version < 9. then failwith "You can't use AS3 SWF with Flash8 target";
  1037. classes := !classes @ List.filter (fun e -> e.f9_cid <> None) el;
  1038. false
  1039. | _ -> true
  1040. ) tags2 in
  1041. (* rebuild character ids *)
  1042. let max_id = ref (-1) in
  1043. List.iter (SwfParser.scan (fun id -> if id > !max_id then max_id := id; id) (fun id -> id)) tags1;
  1044. incr max_id;
  1045. let rec loop t =
  1046. SwfParser.scan (fun id -> id + !max_id) (fun id -> id + !max_id) t;
  1047. match t.tdata with
  1048. | TClip c -> List.iter loop c.c_tags
  1049. | _ -> ()
  1050. in
  1051. List.iter loop tags2;
  1052. let classes = List.map (fun e -> match e.f9_cid with None -> e | Some id -> { e with f9_cid = Some (id + !max_id) }) !classes in
  1053. (* merge timelines *)
  1054. let rec loop l1 l2 =
  1055. match l1, l2 with
  1056. | ({ tdata = TSetBgColor _ } as t) :: l1, _
  1057. | ({ tdata = TEnableDebugger2 _ } as t) :: l1, _
  1058. | ({ tdata = TFilesAttributes _ } as t) :: l1, _ ->
  1059. t :: loop l1 l2
  1060. | _, ({ tdata = TSetBgColor _ } as t) :: l2 ->
  1061. t :: loop l1 l2
  1062. | { tdata = TShowFrame } :: l1, { tdata = TShowFrame } :: l2 ->
  1063. tag TShowFrame :: loop l1 l2
  1064. | { tdata = TF9Classes el } :: l1, _ ->
  1065. (* merge all classes together *)
  1066. tag (TF9Classes (classes @ el)) :: loop l1 l2
  1067. | x :: l1, { tdata = TShowFrame } :: _ ->
  1068. (* wait until we finish frame on other swf *)
  1069. x :: loop l1 l2
  1070. | _ , x :: l2 ->
  1071. x :: loop l1 l2
  1072. | x :: l1, [] ->
  1073. x :: loop l1 l2
  1074. | [], [] ->
  1075. []
  1076. in
  1077. let tags = loop tags1 tags2 in
  1078. header, tags
  1079. let generate com swf_header =
  1080. let t = Common.timer "generate swf" in
  1081. let isf9 = com.flash_version >= 9. in
  1082. let swc = if Common.defined com Define.Swc then Some (ref "") else None in
  1083. if swc <> None && not isf9 then failwith "SWC support is only available for Flash9+";
  1084. let file , codeclip = (try let f , c = ExtString.String.split com.file "@" in f, Some c with _ -> com.file , None) in
  1085. (* list exports *)
  1086. let exports = Hashtbl.create 0 in
  1087. let toremove = ref [] in
  1088. List.iter (fun (file,lib,_) ->
  1089. let _, tags = lib() in
  1090. List.iter (fun t ->
  1091. match t.tdata with
  1092. | TExport l -> List.iter (fun e -> Hashtbl.add exports e.exp_name ()) l
  1093. | TF9Classes el ->
  1094. List.iter (fun e ->
  1095. if e.f9_cid <> None then List.iter (fun t ->
  1096. let extern = (match t with
  1097. | TClassDecl c -> c.cl_extern
  1098. | TEnumDecl e -> e.e_extern
  1099. | TAbstractDecl a -> false
  1100. | TTypeDecl t -> false
  1101. ) in
  1102. if not extern && s_type_path (t_path t) = e.f9_classname then
  1103. match t with
  1104. | TClassDecl c ->
  1105. if Meta.has Meta.Bind c.cl_meta then
  1106. toremove := (t_path t) :: !toremove
  1107. else
  1108. error ("Class already exists in '" ^ file ^ "', use @:bind to redefine it") (t_infos t).mt_pos
  1109. | _ ->
  1110. error ("Invalid redefinition of class defined in '" ^ file ^ "'") (t_infos t).mt_pos
  1111. ) com.types;
  1112. ) el
  1113. | _ -> ()
  1114. ) tags;
  1115. ) com.swf_libs;
  1116. (* build haxe swf *)
  1117. let tags = if isf9 then build_swf9 com file swc else build_swf8 com codeclip exports in
  1118. let header, bg = (match swf_header with None -> default_header com | Some h -> convert_header com h) in
  1119. let bg = tag (TSetBgColor { cr = bg lsr 16; cg = (bg lsr 8) land 0xFF; cb = bg land 0xFF }) in
  1120. let swf_debug_password = try
  1121. Digest.to_hex(Digest.string (Common.defined_value com Define.SwfDebugPassword))
  1122. with Not_found ->
  1123. ""
  1124. in
  1125. let debug = (if isf9 && Common.defined com Define.Fdb then [tag (TEnableDebugger2 (0, swf_debug_password))] else []) in
  1126. let meta_data =
  1127. try
  1128. let file = Common.defined_value com Define.SwfMetadata in
  1129. let file = try Common.find_file com file with Not_found -> file in
  1130. let data = try Std.input_file ~bin:true file with Sys_error _ -> failwith ("Metadata resource file not found : " ^ file) in
  1131. [tag(TMetaData (data))]
  1132. with Not_found ->
  1133. []
  1134. in
  1135. let fattr = (if com.flash_version < 8. then [] else
  1136. [tag (TFilesAttributes {
  1137. fa_network = Common.defined com Define.NetworkSandbox;
  1138. fa_as3 = isf9;
  1139. fa_metadata = meta_data <> [];
  1140. fa_gpu = com.flash_version > 9. && Common.defined com Define.SwfGpu;
  1141. fa_direct_blt = com.flash_version > 9. && Common.defined com Define.SwfDirectBlit;
  1142. })]
  1143. ) in
  1144. let fattr = if Common.defined com Define.AdvancedTelemetry then fattr @ [tag (TUnknown (0x5D,"\x00\x00"))] else fattr in
  1145. let preframe, header =
  1146. if Common.defined com Define.SwfPreloaderFrame then
  1147. [tag TShowFrame], {h_version=header.h_version; h_size=header.h_size; h_frame_count=header.h_frame_count+1; h_fps=header.h_fps; h_compressed=header.h_compressed; }
  1148. else
  1149. [], header in
  1150. let swf_script_limits = try
  1151. let s = Common.defined_value com Define.SwfScriptTimeout in
  1152. let i = try int_of_string s with _ -> error "Argument to swf_script_timeout must be an integer" Ast.null_pos in
  1153. [tag(TScriptLimits (256, if i < 0 then 0 else if i > 65535 then 65535 else i))]
  1154. with Not_found ->
  1155. []
  1156. in
  1157. let swf = header, fattr @ meta_data @ bg :: debug @ swf_script_limits @ preframe @ tags @ [tag TShowFrame] in
  1158. (* merge swf libraries *)
  1159. let priority = ref (swf_header = None) in
  1160. let swf = List.fold_left (fun swf (file,lib,cl) ->
  1161. let swf = merge com file !priority swf (remove_classes toremove lib cl) in
  1162. priority := false;
  1163. swf
  1164. ) swf com.swf_libs in
  1165. t();
  1166. (* write swf/swc *)
  1167. let t = Common.timer "write swf" in
  1168. let level = (try int_of_string (Common.defined_value com Define.SwfCompressLevel) with Not_found -> 9) in
  1169. SwfParser.init Extc.input_zip (Extc.output_zip ~level);
  1170. (match swc with
  1171. | Some cat ->
  1172. let ch = IO.output_strings() in
  1173. Swf.write ch swf;
  1174. let swf = IO.close_out ch in
  1175. let z = Zip.open_out file in
  1176. Zip.add_entry (!cat) z "catalog.xml";
  1177. Zip.add_entry (match swf with [s] -> s | _ -> failwith "SWF too big for SWC") z ~level:0 "library.swf";
  1178. Zip.close_out z
  1179. | None ->
  1180. let ch = IO.output_channel (open_out_bin file) in
  1181. Swf.write ch swf;
  1182. IO.close_out ch;
  1183. );
  1184. t()
  1185. ;;
  1186. SwfParser.init Extc.input_zip Extc.output_zip;
  1187. Swf.warnings := false;