genphp.ml 65 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593159415951596159715981599160016011602160316041605160616071608160916101611161216131614161516161617161816191620162116221623162416251626162716281629163016311632163316341635163616371638163916401641164216431644164516461647164816491650165116521653165416551656165716581659166016611662166316641665166616671668166916701671167216731674167516761677167816791680168116821683168416851686168716881689169016911692169316941695169616971698169917001701170217031704170517061707170817091710171117121713171417151716171717181719172017211722172317241725172617271728172917301731173217331734173517361737173817391740174117421743174417451746174717481749175017511752175317541755175617571758175917601761176217631764176517661767176817691770177117721773177417751776177717781779178017811782178317841785178617871788178917901791179217931794179517961797179817991800180118021803180418051806180718081809181018111812181318141815181618171818181918201821182218231824182518261827182818291830183118321833183418351836183718381839184018411842184318441845184618471848184918501851185218531854185518561857185818591860186118621863186418651866186718681869187018711872187318741875187618771878187918801881188218831884188518861887188818891890189118921893189418951896189718981899190019011902190319041905190619071908190919101911191219131914191519161917191819191920192119221923192419251926192719281929193019311932193319341935193619371938193919401941194219431944194519461947194819491950195119521953195419551956195719581959196019611962196319641965196619671968196919701971197219731974197519761977197819791980198119821983198419851986198719881989199019911992199319941995199619971998199920002001200220032004200520062007200820092010201120122013201420152016201720182019202020212022202320242025202620272028202920302031203220332034203520362037203820392040204120422043204420452046204720482049205020512052205320542055205620572058205920602061206220632064206520662067206820692070207120722073207420752076207720782079208020812082208320842085208620872088208920902091209220932094209520962097209820992100210121022103210421052106210721082109211021112112211321142115211621172118211921202121212221232124212521262127212821292130213121322133213421352136213721382139214021412142214321442145214621472148214921502151215221532154215521562157215821592160216121622163216421652166216721682169217021712172217321742175217621772178217921802181218221832184218521862187218821892190219121922193219421952196219721982199220022012202220322042205220622072208220922102211221222132214221522162217221822192220222122222223222422252226222722282229223022312232223322342235223622372238223922402241224222432244224522462247224822492250225122522253225422552256225722582259226022612262226322642265226622672268226922702271227222732274227522762277227822792280228122822283228422852286228722882289229022912292229322942295229622972298229923002301230223032304230523062307230823092310231123122313231423152316231723182319232023212322232323242325232623272328232923302331233223332334233523362337233823392340234123422343234423452346234723482349235023512352235323542355235623572358235923602361
  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 Ast
  23. open Type
  24. open Common
  25. type method_name = {
  26. mutable mpath : path;
  27. mutable mname : string;
  28. }
  29. type inline_method = {
  30. iname : string;
  31. iindex : int;
  32. iexpr : texpr;
  33. ihasthis : bool;
  34. iin_block : bool;
  35. iarguments : string list;
  36. ilocals : (string,string) PMap.t;
  37. iinv_locals : (string,string) PMap.t;
  38. }
  39. type context = {
  40. com : Common.context;
  41. ch : out_channel;
  42. buf : Buffer.t;
  43. path : path;
  44. stack : Codegen.stack_context;
  45. mutable nested_loops : int;
  46. mutable inline_index : int;
  47. mutable curclass : tclass;
  48. mutable curmethod : string;
  49. mutable tabs : string;
  50. mutable in_value : string option;
  51. mutable in_loop : bool;
  52. mutable in_block : bool;
  53. mutable in_instance_method : bool;
  54. mutable imports : (string,string list list) Hashtbl.t;
  55. mutable extern_required_paths : (string list * string) list;
  56. mutable extern_classes_with_init : path list;
  57. mutable locals : (string,string) PMap.t;
  58. mutable inv_locals : (string,string) PMap.t;
  59. mutable local_types : t list;
  60. mutable inits : texpr list;
  61. mutable constructor_block : bool;
  62. mutable all_dynamic_methods: method_name list;
  63. mutable dynamic_methods: tclass_field list;
  64. mutable is_call : bool;
  65. mutable cwd : string;
  66. mutable inline_methods : inline_method list;
  67. mutable lib_path : string;
  68. }
  69. let join_class_path path separator =
  70. let result = match fst path, snd path with
  71. | [], s -> s
  72. | el, s -> String.concat separator el ^ separator ^ s in
  73. if (String.contains result '+') then begin
  74. let idx = String.index result '+' in
  75. (String.sub result 0 idx) ^ (String.sub result (idx+1) ((String.length result) - idx -1 ) )
  76. end else
  77. result;;
  78. (* Get a string to represent a type.
  79. The "suffix" will be nothing or "_obj", depending if we want the name of the
  80. pointer class or the pointee (_obj class *)
  81. let rec class_string klass suffix params =
  82. (match klass.cl_path with
  83. (* Array class *)
  84. | ([],"Array") -> (snd klass.cl_path) ^ suffix ^ "<" ^ (String.concat ","
  85. (List.map type_string params) ) ^ " >"
  86. | _ when (match klass.cl_kind with KTypeParameter _ -> true | _ -> false) -> "Dynamic"
  87. | ([],"#Int") -> "/* # */int"
  88. | (["haxe";"io"],"Unsigned_char__") -> "unsigned char"
  89. | ([],"Class") -> "Class"
  90. | ([],"Null") -> (match params with
  91. | [t] ->
  92. (match follow t with
  93. | TInst ({ cl_path = [],"Int" },_)
  94. | TInst ({ cl_path = [],"Float" },_)
  95. | TEnum ({ e_path = [],"Bool" },_) -> "Dynamic"
  96. | _ -> "/*NULL*/" ^ (type_string t) )
  97. | _ -> assert false);
  98. (* Normal class *)
  99. | _ -> (join_class_path klass.cl_path "::") ^ suffix
  100. )
  101. and type_string_suff suffix haxe_type =
  102. (match haxe_type with
  103. | TMono r -> (match !r with None -> "Dynamic" | Some t -> type_string_suff suffix t)
  104. | TAbstract ({ a_path = [],"Int" },[]) -> "int"
  105. | TAbstract ({ a_path = [],"Float" },[]) -> "double"
  106. | TAbstract ({ a_path = [],"Bool" },[]) -> "bool"
  107. | TAbstract ({ a_path = [],"Void" },[]) -> "Void"
  108. | TEnum ({ e_path = ([],"Void") },[]) -> "Void"
  109. | TEnum ({ e_path = ([],"Bool") },[]) -> "bool"
  110. | TInst ({ cl_path = ([],"Float") },[]) -> "double"
  111. | TInst ({ cl_path = ([],"Int") },[]) -> "int"
  112. | TEnum (enum,params) -> (join_class_path enum.e_path "::") ^ suffix
  113. | TInst (klass,params) -> (class_string klass suffix params)
  114. | TAbstract (abs,params) -> (join_class_path abs.a_path "::") ^ suffix
  115. | TType (type_def,params) ->
  116. (match type_def.t_path with
  117. | [] , "Null" ->
  118. (match params with
  119. | [t] ->
  120. (match follow t with
  121. | TInst ({ cl_path = [],"Int" },_)
  122. | TInst ({ cl_path = [],"Float" },_)
  123. | TEnum ({ e_path = [],"Bool" },_) -> "Dynamic"
  124. | _ -> type_string_suff suffix t)
  125. | _ -> assert false);
  126. | [] , "Array" ->
  127. (match params with
  128. | [t] -> "Array<" ^ (type_string (follow t) ) ^ " >"
  129. | _ -> assert false)
  130. | _ -> type_string_suff suffix (apply_params type_def.t_types params type_def.t_type)
  131. )
  132. | TFun (args,haxe_type) -> "Dynamic"
  133. | TAnon anon -> "Dynamic"
  134. | TDynamic haxe_type -> "Dynamic"
  135. | TLazy func -> type_string_suff suffix ((!func)())
  136. )
  137. and type_string haxe_type =
  138. type_string_suff "" haxe_type;;
  139. let debug_expression expression type_too =
  140. "/* " ^ Type.s_expr_kind expression ^ (if (type_too) then " = " ^ (type_string (follow expression.etype)) else "") ^ " */";;
  141. let rec register_extern_required_path ctx path =
  142. if (List.exists(fun p -> p = path) ctx.extern_classes_with_init) && not (List.exists(fun p -> p = path) ctx.extern_required_paths) then
  143. ctx.extern_required_paths <- path :: ctx.extern_required_paths
  144. let s_expr_expr = Type.s_expr_kind
  145. let s_expr_name e =
  146. s_type (print_context()) (follow e.etype)
  147. let s_type_name t =
  148. s_type (print_context()) t
  149. and start_with s test =
  150. let len = String.length test in
  151. (String.length s > len && String.sub s 0 len = test)
  152. let rec is_uncertain_type t =
  153. match follow t with
  154. | TInst (c, _) -> c.cl_interface
  155. | TMono _ -> true
  156. | TAnon a ->
  157. (match !(a.a_status) with
  158. | Statics _
  159. | EnumStatics _ -> false
  160. | _ -> true)
  161. | TDynamic _ -> true
  162. | _ -> false
  163. let is_uncertain_expr e =
  164. is_uncertain_type e.etype
  165. let rec is_anonym_type t =
  166. match follow t with
  167. | TAnon a ->
  168. (match !(a.a_status) with
  169. | Statics _
  170. | EnumStatics _ -> false
  171. | _ -> true)
  172. | TDynamic _ -> true
  173. | _ -> false
  174. let is_anonym_expr e = is_anonym_type e.etype
  175. let rec is_unknown_type t =
  176. match follow t with
  177. | TMono r ->
  178. (match !r with
  179. | None -> true
  180. | Some t -> is_unknown_type t)
  181. | _ -> false
  182. let is_unknown_expr e = is_unknown_type e.etype
  183. let rec is_string_type t =
  184. match follow t with
  185. | TInst ({cl_path = ([], "String")}, _) -> true
  186. | TAnon a ->
  187. (match !(a.a_status) with
  188. | Statics ({cl_path = ([], "String")}) -> true
  189. | _ -> false)
  190. | _ -> false
  191. let is_string_expr e = is_string_type e.etype
  192. let to_string ctx e =
  193. let v = alloc_var "__call__" t_dynamic in
  194. let f = mk (TLocal v) t_dynamic e.epos in
  195. mk (TCall (f, [ Codegen.string ctx.com "_hx_string_rec" e.epos; e; Codegen.string ctx.com "" e.epos])) ctx.com.basic.tstring e.epos
  196. let as_string_expr ctx e =
  197. match e.eexpr with
  198. | TConst (TNull) ->
  199. to_string ctx e
  200. | _ when not (is_string_expr e) ->
  201. to_string ctx e
  202. | _ -> e
  203. (* for known String type that could have null value *)
  204. let to_string_null ctx e =
  205. let v = alloc_var "__call__" t_dynamic in
  206. let f = mk (TLocal v) t_dynamic e.epos in
  207. mk (TCall (f, [ Codegen.string ctx.com "_hx_string_or_null" e.epos; e])) ctx.com.basic.tstring e.epos
  208. let as_string_expr ctx e = match e.eexpr with
  209. | TConst (TNull) -> to_string ctx e
  210. | TConst (TString s) -> e
  211. | TBinop (op,_,_) when (is_string_expr e)-> e
  212. | TCall ({eexpr = TField({eexpr = TTypeExpr(TClassDecl {cl_path = ([],"Std")})},FStatic(c,f) )}, [_]) when (f.cf_name="string") -> e
  213. | TCall ({eexpr = TLocal _}, [{eexpr = TConst (TString ("_hx_string_rec" | "_hx_str_or_null"))}]) -> e
  214. | _ when not (is_string_expr e) -> to_string ctx e
  215. | _ -> to_string_null ctx e
  216. let spr ctx s = Buffer.add_string ctx.buf s
  217. let print ctx = Printf.kprintf (fun s -> Buffer.add_string ctx.buf s)
  218. (*--php-prefix - added by skial bainn*)
  219. let prefix_class com name =
  220. match com.php_prefix with
  221. | Some prefix_class (* when not (String.length name <= 2 || String.sub name 0 2 = "__") *) ->
  222. prefix_class ^ name
  223. | _ ->
  224. name
  225. let prefix_init_replace com code =
  226. let r = Str.regexp "php_Boot" in
  227. Str.global_replace r ("php_" ^ (prefix_class com "Boot")) code
  228. let s_path ctx path isextern p =
  229. if isextern then begin
  230. register_extern_required_path ctx path;
  231. snd path
  232. end else begin
  233. (match path with
  234. (*--php-prefix*)
  235. | ([],"List") -> (prefix_class ctx.com "HList")
  236. (*--php-prefix*)
  237. | ([],name) -> (prefix_class ctx.com name)
  238. | (pack,name) ->
  239. (try
  240. (match Hashtbl.find ctx.imports name with
  241. | [p] when p = pack ->
  242. ()
  243. | packs ->
  244. if not (List.mem pack packs) then Hashtbl.replace ctx.imports name (pack :: packs))
  245. with Not_found ->
  246. Hashtbl.add ctx.imports name [pack]);
  247. (*--php-prefix*)
  248. String.concat "_" pack ^ "_" ^ (prefix_class ctx.com name))
  249. end
  250. let s_path_haxe path =
  251. match fst path, snd path with
  252. | [], s -> s
  253. | el, s -> String.concat "." el ^ "." ^ s
  254. let escape_bin s =
  255. let b = Buffer.create 0 in
  256. for i = 0 to String.length s - 1 do
  257. match Char.code (String.unsafe_get s i) with
  258. | c when c = Char.code('\\') or c = Char.code('"') or c = Char.code('$') ->
  259. Buffer.add_string b "\\";
  260. Buffer.add_char b (Char.chr c)
  261. | c when c < 32 ->
  262. Buffer.add_string b (Printf.sprintf "\\x%.2X" c)
  263. | c ->
  264. Buffer.add_char b (Char.chr c)
  265. done;
  266. Buffer.contents b
  267. (*
  268. haxe reserved words that match php ones: break, case, class, continue, default, do, else, extends, for, function, if, new, return, static, switch, var, while, interface, implements, public, private, try, catch, throw
  269. *)
  270. (* PHP only (for future use): cfunction, old_function *)
  271. let is_keyword n =
  272. match String.lowercase n with
  273. | "and" | "or" | "xor" | "__file__" | "exception" | "__line__" | "array"
  274. | "as" | "const" | "declare" | "die" | "echo"| "elseif" | "empty"
  275. | "enddeclare" | "endfor" | "endforeach" | "endif" | "endswitch"
  276. | "endwhile" | "eval" | "exit" | "foreach"| "global" | "include"
  277. | "include_once" | "isset" | "list" | "namespace" | "print" | "require" | "require_once"
  278. | "unset" | "use" | "__function__" | "__class__" | "__method__" | "final"
  279. | "php_user_filter" | "protected" | "abstract" | "__set" | "__get" | "__call"
  280. | "clone" | "instanceof" -> true
  281. | _ -> false
  282. let s_ident n =
  283. let suf = "h" in
  284. if (is_keyword n) then (suf ^ n) else n
  285. let s_ident_field n =
  286. if (is_keyword n) then ("{\"" ^ (escape_bin n) ^ "\"}") else n
  287. let s_ident_local n =
  288. let suf = "h" in
  289. match String.lowercase n with
  290. | "globals" | "_server" | "_get" | "_post" | "_cookie" | "_files"
  291. | "_env" | "_request" | "_session" -> suf ^ n
  292. | _ -> n
  293. let create_directory com ldir =
  294. let atm_path = ref (String.create 0) in
  295. atm_path := com.file;
  296. if not (Sys.file_exists com.file) then (Unix.mkdir com.file 0o755);
  297. (List.iter (fun p -> atm_path := !atm_path ^ "/" ^ p; if not (Sys.file_exists !atm_path) then (Unix.mkdir !atm_path 0o755);) ldir)
  298. let write_resource dir name data =
  299. let i = ref 0 in
  300. String.iter (fun c ->
  301. if c = '\\' || c = '/' || c = ':' || c = '*' || c = '?' || c = '"' || c = '<' || c = '>' || c = '|' then String.blit "_" 0 name !i 1;
  302. incr i
  303. ) name;
  304. let rdir = dir ^ "/res" in
  305. if not (Sys.file_exists dir) then Unix.mkdir dir 0o755;
  306. if not (Sys.file_exists rdir) then Unix.mkdir rdir 0o755;
  307. let ch = open_out_bin (rdir ^ "/" ^ name) in
  308. output_string ch data;
  309. close_out ch
  310. let stack_init com use_add =
  311. Codegen.stack_context_init com "GLOBALS['%s']" "GLOBALS['%e']" "__hx__spos" "tmp" use_add null_pos
  312. let init com cwd path def_type =
  313. let rec create acc = function
  314. | [] -> ()
  315. | d :: l ->
  316. let pdir = String.concat "/" (List.rev (d :: acc)) in
  317. if not (Sys.file_exists pdir) then Unix.mkdir pdir 0o755;
  318. create (d :: acc) l
  319. in
  320. let dir = if cwd <> "" then com.file :: (cwd :: fst path) else com.file :: fst path; in
  321. create [] dir;
  322. let filename path =
  323. prefix_class com (match path with
  324. | [], "List" -> "HList";
  325. | _, s -> s) in
  326. (*--php-prefix*)
  327. let ch = open_out (String.concat "/" dir ^ "/" ^ (filename path) ^ (if def_type = 0 then ".class" else if def_type = 1 then ".enum" else if def_type = 2 then ".interface" else ".extern") ^ ".php") in
  328. let imports = Hashtbl.create 0 in
  329. Hashtbl.add imports (snd path) [fst path];
  330. {
  331. com = com;
  332. stack = stack_init com false;
  333. tabs = "";
  334. ch = ch;
  335. path = path;
  336. buf = Buffer.create (1 lsl 14);
  337. in_value = None;
  338. in_loop = false;
  339. in_instance_method = false;
  340. imports = imports;
  341. extern_required_paths = [];
  342. extern_classes_with_init = [];
  343. curclass = null_class;
  344. curmethod = "";
  345. locals = PMap.empty;
  346. inv_locals = PMap.empty;
  347. local_types = [];
  348. inits = [];
  349. constructor_block = false;
  350. dynamic_methods = [];
  351. all_dynamic_methods = [];
  352. is_call = false;
  353. cwd = cwd;
  354. inline_methods = [];
  355. nested_loops = 0;
  356. inline_index = 0;
  357. in_block = false;
  358. lib_path = match com.php_lib with None -> "lib" | Some s -> s;
  359. }
  360. let unsupported msg p = error ("This expression cannot be generated to PHP: " ^ msg) p
  361. let newline ctx =
  362. match Buffer.nth ctx.buf (Buffer.length ctx.buf - 1) with
  363. | '{' | ':' | ' '
  364. | '}' when Buffer.nth ctx.buf (Buffer.length ctx.buf - 2) != '"' ->
  365. print ctx "\n%s" ctx.tabs
  366. | _ ->
  367. print ctx ";\n%s" ctx.tabs
  368. let rec concat ctx s f = function
  369. | [] -> ()
  370. | [x] -> f x
  371. | x :: l ->
  372. f x;
  373. spr ctx s;
  374. concat ctx s f l
  375. let open_block ctx =
  376. let oldt = ctx.tabs in
  377. ctx.tabs <- "\t" ^ ctx.tabs;
  378. (fun() -> ctx.tabs <- oldt)
  379. let parent e =
  380. match e.eexpr with
  381. | TParenthesis _ -> e
  382. | _ -> mk (TParenthesis e) e.etype e.epos
  383. let inc_extern_path ctx path =
  384. let rec slashes n =
  385. if n = 0 then "" else ("../" ^ slashes (n-1))
  386. in
  387. let pre = if ctx.cwd = "" then ctx.lib_path ^ "/" else "" in
  388. match path with
  389. | ([],name) ->
  390. pre ^ (slashes (List.length (fst ctx.path))) ^ (prefix_class ctx.com name) ^ ".extern.php"
  391. | (pack,name) ->
  392. pre ^ (slashes (List.length (fst ctx.path))) ^ String.concat "/" pack ^ "/" ^ (prefix_class ctx.com name) ^ ".extern.php"
  393. let close ctx =
  394. output_string ctx.ch "<?php\n";
  395. List.iter (fun path ->
  396. if path <> ctx.path then output_string ctx.ch ("require_once dirname(__FILE__).'/" ^ (inc_extern_path ctx path) ^ "';\n");
  397. ) (List.rev ctx.extern_required_paths);
  398. output_string ctx.ch "\n";
  399. output_string ctx.ch (Buffer.contents ctx.buf);
  400. close_out ctx.ch
  401. let save_locals ctx =
  402. let old = ctx.locals in
  403. let old_inv = ctx.inv_locals in
  404. (fun() -> ctx.locals <- old; ctx.inv_locals <- old_inv)
  405. let define_local ctx l =
  406. let rec loop n =
  407. let name = (if n = 1 then s_ident_local l else s_ident_local (l ^ string_of_int n)) in
  408. if PMap.mem name ctx.inv_locals then
  409. loop (n+1)
  410. else begin
  411. ctx.locals <- PMap.add l name ctx.locals;
  412. ctx.inv_locals <- PMap.add name l ctx.inv_locals;
  413. name
  414. end
  415. in
  416. loop 1
  417. let this ctx =
  418. if ctx.in_value <> None then "$__hx__this" else "$this"
  419. let gen_constant ctx p = function
  420. | TInt i -> print ctx "%ld" i
  421. | TFloat s -> spr ctx s
  422. | TString s ->
  423. print ctx "\"%s\"" (escape_bin s)
  424. | TBool b -> spr ctx (if b then "true" else "false")
  425. | TNull -> spr ctx "null"
  426. | TThis -> spr ctx (this ctx)
  427. | TSuper -> spr ctx "ERROR /* unexpected call to super in gen_constant */"
  428. let arg_is_opt c =
  429. match c with
  430. | Some _ -> true
  431. | None -> false
  432. let s_funarg ctx arg t p o =
  433. let byref = if (String.length arg > 7 && String.sub arg 0 7 = "byref__") then "&" else "" in
  434. print ctx "%s$%s" byref (s_ident_local arg);
  435. if o then spr ctx " = null"
  436. (*
  437. match c with
  438. | _, Some _ -> spr ctx " = null"
  439. | _, None -> ()
  440. *)
  441. let is_in_dynamic_methods ctx e s =
  442. List.exists (fun dm ->
  443. (* TODO: I agree, this is a mess ... but after hours of trials and errors I gave up; maybe in a calmer day *)
  444. ((String.concat "." ((fst dm.mpath) @ ["#" ^ (snd dm.mpath)])) ^ "." ^ dm.mname) = (s_type_name e.etype ^ "." ^ s)
  445. ) ctx.all_dynamic_methods
  446. let is_dynamic_method f =
  447. (match f.cf_kind with
  448. | Var _ -> true
  449. | Method MethDynamic -> true
  450. | _ -> false)
  451. let fun_block ctx f p =
  452. let e = (match f.tf_expr with { eexpr = TBlock [{ eexpr = TBlock _ } as e] } -> e | e -> e) in
  453. let e = List.fold_left (fun e (v,c) ->
  454. match c with
  455. | None | Some TNull -> e
  456. | Some c -> Codegen.concat (Codegen.set_default ctx.com v c p) e
  457. ) e f.tf_args in
  458. if ctx.com.debug then begin
  459. Codegen.stack_block ctx.stack ctx.curclass ctx.curmethod e
  460. end else
  461. mk_block e
  462. let rec gen_array_args ctx lst =
  463. match lst with
  464. | [] -> ()
  465. | h :: t ->
  466. spr ctx "[";
  467. gen_value ctx h;
  468. spr ctx "]";
  469. gen_array_args ctx t
  470. and gen_call ctx e el =
  471. let rec genargs lst =
  472. (match lst with
  473. | [] -> ()
  474. | h :: [] ->
  475. spr ctx " = ";
  476. gen_value ctx h;
  477. | h :: t ->
  478. spr ctx "[";
  479. gen_value ctx h;
  480. spr ctx "]";
  481. genargs t)
  482. in
  483. match e.eexpr , el with
  484. | TConst TSuper , params ->
  485. (match ctx.curclass.cl_super with
  486. | None -> assert false
  487. | Some (c,_) ->
  488. spr ctx "parent::__construct(";
  489. concat ctx "," (gen_value ctx) params;
  490. spr ctx ")";
  491. );
  492. | TField ({ eexpr = TConst TSuper },f) , params ->
  493. (match ctx.curclass.cl_super with
  494. | None -> assert false
  495. | Some (c,_) ->
  496. print ctx "parent::%s(" (s_ident (field_name f));
  497. concat ctx "," (gen_value ctx) params;
  498. spr ctx ")";
  499. );
  500. | TLocal { v_name = "__set__" }, { eexpr = TConst (TString code) } :: el ->
  501. print ctx "$%s" code;
  502. genargs el;
  503. | TLocal { v_name = "__set__" }, e :: el ->
  504. gen_value ctx e;
  505. genargs el;
  506. | TLocal { v_name = "__setfield__" }, e :: (f :: el) ->
  507. gen_value ctx e;
  508. spr ctx "->{";
  509. gen_value ctx f;
  510. spr ctx "}";
  511. genargs el;
  512. | TLocal { v_name = "__field__" }, e :: ({ eexpr = TConst (TString code) } :: el) ->
  513. gen_value ctx e;
  514. spr ctx "->";
  515. spr ctx code;
  516. gen_array_args ctx el;
  517. | TLocal { v_name = "__field__" }, e :: (f :: el) ->
  518. gen_value ctx e;
  519. spr ctx "->";
  520. gen_value ctx f;
  521. gen_array_args ctx el;
  522. | TLocal { v_name = "__prefix__" }, [] ->
  523. (match ctx.com.php_prefix with
  524. | Some prefix ->
  525. print ctx "\"%s\"" prefix
  526. | None ->
  527. spr ctx "null")
  528. | TLocal { v_name = "__var__" }, { eexpr = TConst (TString code) } :: el ->
  529. print ctx "$%s" code;
  530. gen_array_args ctx el;
  531. | TLocal { v_name = "__var__" }, e :: el ->
  532. gen_value ctx e;
  533. gen_array_args ctx el;
  534. | TLocal { v_name = "__call__" }, { eexpr = TConst (TString code) } :: el ->
  535. spr ctx code;
  536. spr ctx "(";
  537. concat ctx ", " (gen_value ctx) el;
  538. spr ctx ")";
  539. | TLocal { v_name = "__php__" }, [{ eexpr = TConst (TString code) }] ->
  540. (*--php-prefix*)
  541. spr ctx (prefix_init_replace ctx.com code)
  542. | TLocal { v_name = "__instanceof__" }, [e1;{ eexpr = TConst (TString t) }] ->
  543. gen_value ctx e1;
  544. print ctx " instanceof %s" t;
  545. | TLocal { v_name = "__physeq__" }, [e1;e2] ->
  546. spr ctx "(";
  547. gen_value ctx e1;
  548. spr ctx " === ";
  549. gen_value ctx e2;
  550. spr ctx ")"
  551. | TLocal _, []
  552. | TFunction _, []
  553. | TCall _, []
  554. | TParenthesis _, []
  555. | TBlock _, [] ->
  556. ctx.is_call <- true;
  557. spr ctx "call_user_func(";
  558. gen_value ctx e;
  559. ctx.is_call <- false;
  560. spr ctx ")";
  561. | TLocal _, el
  562. | TFunction _, el
  563. | TCall _, el
  564. | TParenthesis _, el
  565. | TBlock _, el ->
  566. ctx.is_call <- true;
  567. spr ctx "call_user_func_array(";
  568. gen_value ctx e;
  569. ctx.is_call <- false;
  570. spr ctx ", array(";
  571. concat ctx ", " (gen_value ctx) el;
  572. spr ctx "))"
  573. (*
  574. | TCall (x,_), el when (match x.eexpr with | TLocal _ -> false | _ -> true) ->
  575. ctx.is_call <- true;
  576. spr ctx "call_user_func_array(";
  577. gen_value ctx e;
  578. ctx.is_call <- false;
  579. spr ctx ", array(";
  580. concat ctx ", " (gen_value ctx) el;
  581. spr ctx "))"
  582. *)
  583. | _ ->
  584. ctx.is_call <- true;
  585. gen_value ctx e;
  586. ctx.is_call <- false;
  587. spr ctx "(";
  588. concat ctx ", " (gen_value ctx) el;
  589. spr ctx ")";
  590. and could_be_string_var s =
  591. s = "length"
  592. and gen_uncertain_string_var ctx s e =
  593. match s with
  594. | "length" ->
  595. spr ctx "_hx_len(";
  596. gen_value ctx e;
  597. spr ctx ")"
  598. | _ ->
  599. gen_field_access ctx true e s;
  600. and gen_string_var ctx s e =
  601. match s with
  602. | "length" ->
  603. spr ctx "strlen(";
  604. gen_value ctx e;
  605. spr ctx ")"
  606. | _ ->
  607. unsupported "gen_string_var " e.epos;
  608. and gen_string_static_call ctx s e el =
  609. match s with
  610. | "fromCharCode" ->
  611. spr ctx "chr(";
  612. concat ctx ", " (gen_value ctx) el;
  613. spr ctx ")";
  614. | _ -> unsupported "gen_string_static_call " e.epos;
  615. and could_be_string_call s =
  616. s = "substr" || s = "substring" || s = "charAt" || s = "charCodeAt" || s = "indexOf" ||
  617. s = "lastIndexOf" || s = "split" || s = "toLowerCase" || s = "toString" || s = "toUpperCase"
  618. and gen_string_call ctx s e el =
  619. match s with
  620. | "substr" ->
  621. spr ctx "_hx_substr(";
  622. gen_value ctx e;
  623. spr ctx ", ";
  624. concat ctx ", " (gen_value ctx) el;
  625. spr ctx ")"
  626. | "substring" ->
  627. spr ctx "_hx_substring(";
  628. gen_value ctx e;
  629. spr ctx ", ";
  630. concat ctx ", " (gen_value ctx) el;
  631. spr ctx ")"
  632. | "charAt" ->
  633. spr ctx "_hx_char_at(";
  634. gen_value ctx e;
  635. spr ctx ", ";
  636. concat ctx ", " (gen_value ctx) el;
  637. spr ctx ")"
  638. | "cca" ->
  639. spr ctx "ord(substr(";
  640. gen_value ctx e;
  641. spr ctx ",";
  642. concat ctx ", " (gen_value ctx) el;
  643. spr ctx ",1))"
  644. | "charCodeAt" ->
  645. spr ctx "_hx_char_code_at(";
  646. gen_value ctx e;
  647. spr ctx ", ";
  648. concat ctx ", " (gen_value ctx) el;
  649. spr ctx ")"
  650. | "indexOf" ->
  651. spr ctx "_hx_index_of(";
  652. gen_value ctx e;
  653. spr ctx ", ";
  654. concat ctx ", " (gen_value ctx) el;
  655. spr ctx ")"
  656. | "lastIndexOf" ->
  657. spr ctx "_hx_last_index_of(";
  658. gen_value ctx e;
  659. spr ctx ", ";
  660. concat ctx ", " (gen_value ctx) el;
  661. spr ctx ")"
  662. | "split" ->
  663. spr ctx "_hx_explode(";
  664. concat ctx ", " (gen_value ctx) el;
  665. spr ctx ", ";
  666. gen_value ctx e;
  667. spr ctx ")"
  668. | "toLowerCase" ->
  669. spr ctx "strtolower(";
  670. gen_value ctx e;
  671. spr ctx ")"
  672. | "toUpperCase" ->
  673. spr ctx "strtoupper(";
  674. gen_value ctx e;
  675. spr ctx ")"
  676. | "toString" ->
  677. gen_value ctx e;
  678. | _ ->
  679. unsupported "gen_string_call" e.epos;
  680. and gen_uncertain_string_call ctx s e el =
  681. spr ctx "_hx_string_call(";
  682. gen_value ctx e;
  683. print ctx ", \"%s\", array(" s;
  684. concat ctx ", " (gen_value ctx) el;
  685. spr ctx "))"
  686. and gen_field_op ctx e =
  687. match e.eexpr with
  688. | TField (f,s) ->
  689. (match follow e.etype with
  690. | TFun _ ->
  691. gen_field_access ctx true f (field_name s)
  692. | _ ->
  693. gen_value_op ctx e)
  694. | _ ->
  695. gen_value_op ctx e
  696. and gen_value_op ctx e =
  697. match e.eexpr with
  698. | TBinop (op,_,_) when op = Ast.OpAnd || op = Ast.OpOr || op = Ast.OpXor ->
  699. gen_value ctx e;
  700. | _ ->
  701. gen_value ctx e
  702. and is_static t =
  703. match follow t with
  704. | TAnon a -> (match !(a.a_status) with
  705. | Statics c -> true
  706. | _ -> false)
  707. | _ -> false
  708. and gen_member_access ctx isvar e s =
  709. match follow e.etype with
  710. | TAnon a ->
  711. (match !(a.a_status) with
  712. | EnumStatics _ ->
  713. print ctx "::%s%s" (if isvar then "$" else "") s
  714. | Statics _ ->
  715. print ctx "::%s%s" (if isvar then "$" else "") (s_ident s)
  716. | _ -> print ctx "->%s" (if isvar then s_ident_field s else s_ident s))
  717. | _ -> print ctx "->%s" (if isvar then s_ident_field s else s_ident s)
  718. and gen_field_access ctx isvar e s =
  719. match e.eexpr with
  720. | TTypeExpr t ->
  721. spr ctx (s_path ctx (t_path t) false e.epos);
  722. gen_member_access ctx isvar e s
  723. | TLocal _ ->
  724. gen_expr ctx e;
  725. print ctx "->%s" (if isvar then s_ident_field s else s_ident s)
  726. | TArray (e1,e2) ->
  727. spr ctx "_hx_array_get(";
  728. gen_value ctx e1;
  729. spr ctx ", ";
  730. gen_value ctx e2;
  731. spr ctx ")";
  732. gen_member_access ctx isvar e s
  733. | TBlock _
  734. | TParenthesis _
  735. | TObjectDecl _
  736. | TArrayDecl _
  737. | TNew _ ->
  738. spr ctx "_hx_deref(";
  739. ctx.is_call <- false;
  740. gen_value ctx e;
  741. spr ctx ")";
  742. gen_member_access ctx isvar e s
  743. | TCast (ec, _) when (match ec.eexpr with | TNew _ | TArrayDecl _ -> true | _ -> false) ->
  744. spr ctx "_hx_deref(";
  745. ctx.is_call <- false;
  746. gen_value ctx e;
  747. spr ctx ")";
  748. gen_member_access ctx isvar e s
  749. | _ ->
  750. gen_expr ctx e;
  751. gen_member_access ctx isvar e s
  752. and gen_dynamic_function ctx isstatic name f params p =
  753. let old = ctx.in_value in
  754. let old_l = ctx.locals in
  755. let old_li = ctx.inv_locals in
  756. let old_t = ctx.local_types in
  757. ctx.in_value <- None;
  758. ctx.local_types <- List.map snd params @ ctx.local_types;
  759. let byref = if (String.length name > 9 && String.sub name 0 9 = "__byref__") then "&" else "" in
  760. print ctx "function %s%s(" byref name;
  761. concat ctx ", " (fun (v,c) ->
  762. let arg = define_local ctx v.v_name in
  763. s_funarg ctx arg v.v_type p (arg_is_opt c);
  764. ) f.tf_args;
  765. spr ctx ") {";
  766. if (List.length f.tf_args) > 0 then begin
  767. if isstatic then
  768. print ctx " return call_user_func_array(self::$%s, array(" name
  769. else
  770. print ctx " return call_user_func_array($this->%s, array(" name;
  771. concat ctx ", " (fun (v,_) ->
  772. spr ctx ("$" ^ v.v_name)
  773. ) f.tf_args;
  774. print ctx ")); }";
  775. end else if isstatic then
  776. print ctx " return call_user_func(self::$%s); }" name
  777. else
  778. print ctx " return call_user_func($this->%s); }" name;
  779. newline ctx;
  780. if isstatic then
  781. print ctx "public static $%s = null" name
  782. else
  783. print ctx "public $%s = null" name;
  784. ctx.in_value <- old;
  785. ctx.locals <- old_l;
  786. ctx.inv_locals <- old_li;
  787. ctx.local_types <- old_t
  788. and gen_function ctx name f params p =
  789. let old = ctx.in_value in
  790. let old_l = ctx.locals in
  791. let old_li = ctx.inv_locals in
  792. let old_t = ctx.local_types in
  793. ctx.in_value <- None;
  794. ctx.local_types <- List.map snd params @ ctx.local_types;
  795. let byref = if (String.length name > 9 && String.sub name 0 9 = "__byref__") then "&" else "" in
  796. print ctx "function %s%s(" byref name;
  797. concat ctx ", " (fun (v,o) ->
  798. let arg = define_local ctx v.v_name in
  799. s_funarg ctx arg v.v_type p (arg_is_opt o);
  800. ) f.tf_args;
  801. print ctx ") ";
  802. gen_expr ctx (fun_block ctx f p);
  803. ctx.in_value <- old;
  804. ctx.locals <- old_l;
  805. ctx.inv_locals <- old_li;
  806. ctx.local_types <- old_t
  807. and gen_inline_function ctx f hasthis p =
  808. ctx.nested_loops <- ctx.nested_loops - 1;
  809. let old = ctx.in_value in
  810. let old_l = ctx.locals in
  811. let old_li = ctx.inv_locals in
  812. let old_t = ctx.local_types in
  813. ctx.in_value <- Some "closure";
  814. let args a = List.map (fun (v,_) -> v.v_name) a in
  815. let arguments = ref [] in
  816. if hasthis then begin arguments := "this" :: !arguments end;
  817. PMap.iter (fun n _ -> arguments := !arguments @ [n]) old_li;
  818. spr ctx "array(new _hx_lambda(array(";
  819. let c = ref 0 in
  820. List.iter (fun a ->
  821. if !c > 0 then spr ctx ", ";
  822. incr c;
  823. print ctx "&$%s" a;
  824. ) (remove_internals !arguments);
  825. spr ctx "), \"";
  826. spr ctx (inline_function ctx (args f.tf_args) hasthis (fun_block ctx f p));
  827. print ctx "\"), 'execute')";
  828. ctx.in_value <- old;
  829. ctx.locals <- old_l;
  830. ctx.inv_locals <- old_li;
  831. ctx.local_types <- old_t;
  832. ctx.nested_loops <- ctx.nested_loops + 1;
  833. and unset_locals ctx old_l =
  834. let lst = ref [] in
  835. PMap.iter (fun n _ ->
  836. if not (PMap.exists n old_l) then
  837. lst := ["$" ^ n] @ !lst;
  838. ) ctx.inv_locals;
  839. if (List.length !lst) > 0 then begin
  840. newline ctx;
  841. spr ctx "unset(";
  842. concat ctx "," (fun (s) -> spr ctx s; ) !lst;
  843. spr ctx ")"
  844. end
  845. and gen_while_expr ctx e =
  846. let old_loop = ctx.in_loop in
  847. ctx.in_loop <- true;
  848. let old_nested_loops = ctx.nested_loops in
  849. ctx.nested_loops <- 1;
  850. let old_l = ctx.inv_locals in
  851. let b = save_locals ctx in
  852. (match e.eexpr with
  853. | TBlock (el) ->
  854. List.iter (fun e -> newline ctx; gen_expr ctx e) el;
  855. | _ ->
  856. newline ctx;
  857. gen_expr ctx e);
  858. unset_locals ctx old_l;
  859. b();
  860. ctx.nested_loops <- old_nested_loops;
  861. ctx.in_loop <- old_loop
  862. and gen_tfield ctx e e1 s =
  863. match follow e.etype with
  864. | TFun (args, _) ->
  865. (if ctx.is_call then begin
  866. gen_field_access ctx false e1 s
  867. end else if is_in_dynamic_methods ctx e1 s then begin
  868. gen_field_access ctx true e1 s;
  869. end else begin
  870. let ob ex =
  871. (match ex with
  872. | TTypeExpr t ->
  873. print ctx "\"";
  874. spr ctx (s_path ctx (t_path t) false e1.epos);
  875. print ctx "\""
  876. | _ ->
  877. gen_expr ctx e1) in
  878. spr ctx "(isset(";
  879. gen_field_access ctx true e1 s;
  880. spr ctx ") ? ";
  881. gen_field_access ctx true e1 s;
  882. spr ctx ": array(";
  883. ob e1.eexpr;
  884. print ctx ", \"%s\"))" (s_ident s);
  885. end)
  886. | TMono _ ->
  887. if ctx.is_call then
  888. gen_field_access ctx false e1 s
  889. else
  890. gen_uncertain_string_var ctx s e1
  891. | _ ->
  892. if is_string_expr e1 then
  893. gen_string_var ctx s e1
  894. else if is_uncertain_expr e1 then
  895. gen_uncertain_string_var ctx s e1
  896. else
  897. gen_field_access ctx true e1 s
  898. and gen_expr ctx e =
  899. let in_block = ctx.in_block in
  900. ctx.in_block <- false;
  901. let restore_in_block ctx inb =
  902. if inb then ctx.in_block <- true
  903. in
  904. match e.eexpr with
  905. | TConst c ->
  906. gen_constant ctx e.epos c
  907. | TLocal v ->
  908. spr ctx ("$" ^ (try PMap.find v.v_name ctx.locals with Not_found -> (s_ident_local v.v_name)))
  909. | TArray (e1,e2) ->
  910. (match e1.eexpr with
  911. | TCall _
  912. | TBlock _
  913. | TParenthesis _
  914. | TArrayDecl _ ->
  915. spr ctx "_hx_array_get(";
  916. gen_value ctx e1;
  917. spr ctx ", ";
  918. gen_value ctx e2;
  919. spr ctx ")";
  920. | TCast (ec, _) when (match ec.eexpr with | TArrayDecl _ | TBlock _ -> true | _ -> false) ->
  921. spr ctx "_hx_array_get(";
  922. gen_value ctx e1;
  923. spr ctx ", ";
  924. gen_value ctx e2;
  925. spr ctx ")";
  926. | _ ->
  927. gen_value ctx e1;
  928. spr ctx "[";
  929. gen_value ctx e2;
  930. spr ctx "]");
  931. | TBinop (op,e1,e2) ->
  932. (* these operators are non-assoc in php, let let's make sure to separate them with parenthesises *)
  933. let non_assoc = function
  934. | (Ast.OpEq | Ast.OpNotEq | Ast.OpGt | Ast.OpGte | Ast.OpLt | Ast.OpLte) -> true
  935. | _ -> false
  936. in
  937. (match e1.eexpr with
  938. | TBinop (op2,_,_) when non_assoc op && non_assoc op2 ->
  939. gen_expr ctx { e with eexpr = TBinop (op,mk (TParenthesis e1) e1.etype e1.epos,e2) }
  940. | _ ->
  941. let leftside e =
  942. (match e.eexpr with
  943. | TArray(te1, te2) ->
  944. gen_value ctx te1;
  945. spr ctx "->a[";
  946. gen_value ctx te2;
  947. spr ctx "]";
  948. | _ ->
  949. gen_field_op ctx e1;) in
  950. let leftsidec e =
  951. (match e.eexpr with
  952. | TArray(te1, te2) ->
  953. gen_value ctx te1;
  954. spr ctx "->a[";
  955. gen_value ctx te2;
  956. spr ctx "]";
  957. | TField (e1,s) ->
  958. gen_field_access ctx true e1 (field_name s)
  959. | _ ->
  960. gen_field_op ctx e1;) in
  961. let leftsidef e =
  962. (match e.eexpr with
  963. | TField (e1,s) ->
  964. gen_field_access ctx true e1 (field_name s)
  965. | _ ->
  966. gen_field_op ctx e1;
  967. ) in
  968. (match op with
  969. | Ast.OpMod ->
  970. spr ctx "_hx_mod(";
  971. gen_value_op ctx e1;
  972. spr ctx ", ";
  973. gen_value_op ctx e2;
  974. spr ctx ")";
  975. | Ast.OpAssign ->
  976. (match e1.eexpr with
  977. | TArray(te1, te2) when (match te1.eexpr with | TCall _ | TParenthesis _ -> true | _ -> false) ->
  978. spr ctx "_hx_array_assign(";
  979. gen_value ctx te1;
  980. spr ctx ", ";
  981. gen_value ctx te2;
  982. spr ctx ", ";
  983. gen_value_op ctx e2;
  984. spr ctx ")";
  985. | _ ->
  986. leftsidef e1;
  987. spr ctx " = ";
  988. gen_value_op ctx e2;
  989. )
  990. | Ast.OpAssignOp(Ast.OpAdd) when (is_uncertain_expr e1 && is_uncertain_expr e2) ->
  991. (match e1.eexpr with
  992. | TArray(te1, te2) ->
  993. let t1 = define_local ctx "__hx__t1" in
  994. let t2 = define_local ctx "__hx__t2" in
  995. print ctx "_hx_array_assign($%s = " t1;
  996. gen_value ctx te1;
  997. print ctx ", $%s = " t2;
  998. gen_value ctx te2;
  999. print ctx ", $%s->a[$%s] + " t1 t2;
  1000. gen_value_op ctx e2;
  1001. spr ctx ")";
  1002. | _ ->
  1003. leftside e1;
  1004. spr ctx " = ";
  1005. spr ctx "_hx_add(";
  1006. gen_value_op ctx e1;
  1007. spr ctx ", ";
  1008. gen_value_op ctx e2;
  1009. spr ctx ")";
  1010. )
  1011. | Ast.OpAssignOp(Ast.OpAdd) when (is_string_expr e1 || is_string_expr e2) ->
  1012. leftside e1;
  1013. spr ctx " .= ";
  1014. gen_value_op ctx (as_string_expr ctx e2);
  1015. | Ast.OpAssignOp(Ast.OpShl) ->
  1016. leftside e1;
  1017. spr ctx " <<= ";
  1018. gen_value_op ctx e2;
  1019. | Ast.OpAssignOp(Ast.OpUShr) ->
  1020. leftside e1;
  1021. spr ctx " = ";
  1022. spr ctx "_hx_shift_right(";
  1023. gen_value_op ctx e1;
  1024. spr ctx ", ";
  1025. gen_value_op ctx e2;
  1026. spr ctx ")";
  1027. | Ast.OpAssignOp(Ast.OpMod) ->
  1028. leftside e1;
  1029. spr ctx " = ";
  1030. spr ctx "_hx_mod(";
  1031. gen_value_op ctx e1;
  1032. spr ctx ", ";
  1033. gen_value_op ctx e2;
  1034. spr ctx ")";
  1035. | Ast.OpAssignOp(_) ->
  1036. leftsidec e1;
  1037. print ctx " %s " (Ast.s_binop op);
  1038. gen_value_op ctx e2;
  1039. | Ast.OpAdd when (is_uncertain_expr e1 && is_uncertain_expr e2) ->
  1040. spr ctx "_hx_add(";
  1041. gen_value_op ctx e1;
  1042. spr ctx ", ";
  1043. gen_value_op ctx e2;
  1044. spr ctx ")";
  1045. | Ast.OpAdd when (is_string_expr e1 || is_string_expr e2) ->
  1046. gen_value_op ctx (as_string_expr ctx e1);
  1047. spr ctx " . ";
  1048. gen_value_op ctx (as_string_expr ctx e2);
  1049. | Ast.OpShl ->
  1050. gen_value_op ctx e1;
  1051. spr ctx " << ";
  1052. gen_value_op ctx e2;
  1053. | Ast.OpUShr ->
  1054. spr ctx "_hx_shift_right(";
  1055. gen_value_op ctx e1;
  1056. spr ctx ", ";
  1057. gen_value_op ctx e2;
  1058. spr ctx ")";
  1059. | Ast.OpNotEq
  1060. | Ast.OpEq ->
  1061. let s_op = if op = Ast.OpNotEq then " != " else " == " in
  1062. let s_phop = if op = Ast.OpNotEq then " !== " else " === " in
  1063. let se1 = s_expr_name e1 in
  1064. let se2 = s_expr_name e2 in
  1065. if
  1066. e1.eexpr = TConst (TNull)
  1067. || e2.eexpr = TConst (TNull)
  1068. then begin
  1069. (match e1.eexpr with
  1070. | TField (f, s) when is_anonym_expr e1 || is_unknown_expr e1 ->
  1071. spr ctx "_hx_field(";
  1072. gen_value ctx f;
  1073. print ctx ", \"%s\")" (field_name s);
  1074. | _ ->
  1075. gen_field_op ctx e1;
  1076. );
  1077. spr ctx s_phop;
  1078. (match e2.eexpr with
  1079. | TField (f, s) when is_anonym_expr e2 || is_unknown_expr e2 ->
  1080. spr ctx "_hx_field(";
  1081. gen_value ctx f;
  1082. print ctx ", \"%s\")" (field_name s);
  1083. | _ ->
  1084. gen_field_op ctx e2);
  1085. end else if
  1086. ((se1 = "Int" || se1 = "Null<Int>") && (se2 = "Int" || se2 = "Null<Int>"))
  1087. || ((se1 = "Float" || se1 = "Null<Float>") && (se2 = "Float" || se2 = "Null<Float>"))
  1088. then begin
  1089. gen_field_op ctx e1;
  1090. spr ctx s_phop;
  1091. gen_field_op ctx e2;
  1092. end else if
  1093. ((se1 = "Int" || se1 = "Float" || se1 = "Null<Int>" || se1 = "Null<Float>")
  1094. && (se1 = "Int" || se1 = "Float" || se1 = "Null<Int>" || se1 = "Null<Float>"))
  1095. || (is_unknown_expr e1 && is_unknown_expr e2)
  1096. || is_anonym_expr e1
  1097. || is_anonym_expr e2
  1098. then begin
  1099. if op = Ast.OpNotEq then spr ctx "!";
  1100. spr ctx "_hx_equal(";
  1101. gen_field_op ctx e1;
  1102. spr ctx ", ";
  1103. gen_field_op ctx e2;
  1104. spr ctx ")";
  1105. end else if
  1106. (
  1107. se1 == se2
  1108. || (match e1.eexpr with | TConst _ | TLocal _ | TArray _ | TNew _ -> true | _ -> false)
  1109. || (match e2.eexpr with | TConst _ | TLocal _ | TArray _ | TNew _ -> true | _ -> false)
  1110. || is_string_expr e1
  1111. || is_string_expr e2
  1112. || is_anonym_expr e1
  1113. || is_anonym_expr e2
  1114. || is_unknown_expr e1
  1115. || is_unknown_expr e2
  1116. )
  1117. && (type_string (follow e1.etype)) <> "Dynamic"
  1118. && (type_string (follow e2.etype)) <> "Dynamic"
  1119. then begin
  1120. gen_field_op ctx e1;
  1121. spr ctx s_phop;
  1122. gen_field_op ctx e2;
  1123. end else begin
  1124. gen_field_op ctx e1;
  1125. spr ctx s_op;
  1126. gen_field_op ctx e2;
  1127. end
  1128. | _ ->
  1129. leftside e1;
  1130. print ctx " %s " (Ast.s_binop op);
  1131. gen_value_op ctx e2;
  1132. ));
  1133. | TField (e1,s) ->
  1134. gen_tfield ctx e e1 (field_name s)
  1135. | TTypeExpr t ->
  1136. print ctx "_hx_qtype(\"%s\")" (s_path_haxe (t_path t))
  1137. | TParenthesis e ->
  1138. (match e.eexpr with
  1139. | TParenthesis _
  1140. | TReturn _ ->
  1141. gen_value ctx e;
  1142. | _ ->
  1143. spr ctx "(";
  1144. gen_value ctx e;
  1145. spr ctx ")"
  1146. );
  1147. | TReturn eo ->
  1148. (match eo with
  1149. | None ->
  1150. spr ctx "return"
  1151. | Some e when (match follow e.etype with TEnum({ e_path = [],"Void" },[]) | TAbstract ({ a_path = [],"Void" },[]) -> true | _ -> false) ->
  1152. gen_value ctx e;
  1153. newline ctx;
  1154. spr ctx "return"
  1155. | Some e ->
  1156. (match e.eexpr with
  1157. | TThrow _ -> ()
  1158. | _ -> spr ctx "return ");
  1159. gen_value ctx e;
  1160. );
  1161. | TBreak ->
  1162. if ctx.in_loop then spr ctx "break" else print ctx "break %d" ctx.nested_loops
  1163. | TContinue ->
  1164. if ctx.in_loop then spr ctx "continue" else print ctx "continue %d" ctx.nested_loops
  1165. | TBlock [] ->
  1166. spr ctx ""
  1167. | TBlock el ->
  1168. let old_l = ctx.inv_locals in
  1169. let b = save_locals ctx in
  1170. print ctx "{";
  1171. let bend = open_block ctx in
  1172. let cb = (
  1173. if not ctx.constructor_block then
  1174. (fun () -> ())
  1175. else begin
  1176. ctx.constructor_block <- false;
  1177. if List.length ctx.dynamic_methods > 0 then newline ctx else spr ctx " ";
  1178. List.iter (fun (f) ->
  1179. let name = f.cf_name in
  1180. match f.cf_expr with
  1181. | Some { eexpr = TFunction fd } ->
  1182. print ctx "if(!isset($this->%s)) $this->%s = " name name;
  1183. gen_inline_function ctx fd true e.epos;
  1184. newline ctx;
  1185. | _ -> ()
  1186. ) ctx.dynamic_methods;
  1187. if Codegen.constructor_side_effects e then begin
  1188. print ctx "if(!%s::$skip_constructor) {" (s_path ctx (["php"],"Boot") false e.epos);
  1189. (fun() -> print ctx "}")
  1190. end else
  1191. (fun() -> ());
  1192. end) in
  1193. let remaining = ref (List.length el) in
  1194. let build e =
  1195. (match e.eexpr with
  1196. | TBlock [] -> ()
  1197. | _ -> newline ctx);
  1198. if (in_block && !remaining = 1) then begin
  1199. (match e.eexpr with
  1200. | TIf _
  1201. | TSwitch _
  1202. | TThrow _
  1203. | TWhile _
  1204. | TFor _
  1205. | TMatch _
  1206. | TTry _
  1207. | TBreak
  1208. | TBlock _ ->
  1209. restore_in_block ctx in_block;
  1210. gen_expr ctx e;
  1211. unset_locals ctx old_l;
  1212. | TReturn (Some e1) ->
  1213. (match e1.eexpr with
  1214. | TIf _
  1215. | TSwitch _
  1216. | TThrow _
  1217. | TWhile _
  1218. | TFor _
  1219. | TMatch _
  1220. | TTry _
  1221. | TBlock _ -> ()
  1222. | _ ->
  1223. spr ctx "return "
  1224. );
  1225. gen_expr ctx e1;
  1226. | _ ->
  1227. spr ctx "return ";
  1228. gen_value ctx e;
  1229. )
  1230. end else begin
  1231. gen_expr ctx e;
  1232. end;
  1233. decr remaining;
  1234. in
  1235. List.iter build el;
  1236. if ctx.in_loop then begin
  1237. unset_locals ctx old_l;
  1238. end;
  1239. bend();
  1240. newline ctx;
  1241. cb();
  1242. print ctx "}";
  1243. b();
  1244. | TFunction f ->
  1245. let old = ctx.in_value, ctx.in_loop in
  1246. let old_meth = ctx.curmethod in
  1247. ctx.in_value <- None;
  1248. ctx.in_loop <- false;
  1249. ctx.curmethod <- ctx.curmethod ^ "@" ^ string_of_int (Lexer.get_error_line e.epos);
  1250. gen_inline_function ctx f false e.epos;
  1251. ctx.curmethod <- old_meth;
  1252. ctx.in_value <- fst old;
  1253. ctx.in_loop <- snd old;
  1254. | TCall (ec,el) ->
  1255. (match ec.eexpr with
  1256. | TArray _ ->
  1257. spr ctx "call_user_func_array(";
  1258. gen_value ctx ec;
  1259. spr ctx ", array(";
  1260. concat ctx ", " (gen_value ctx) el;
  1261. spr ctx "))";
  1262. | TField (ef,s) when is_static ef.etype && is_string_expr ef ->
  1263. gen_string_static_call ctx (field_name s) ef el
  1264. | TField (ef,s) when is_string_expr ef ->
  1265. gen_string_call ctx (field_name s) ef el
  1266. | TField (ef,s) when is_anonym_expr ef && could_be_string_call (field_name s) ->
  1267. gen_uncertain_string_call ctx (field_name s) ef el
  1268. | _ ->
  1269. gen_call ctx ec el);
  1270. | TArrayDecl el ->
  1271. spr ctx "new _hx_array(array(";
  1272. concat ctx ", " (gen_value ctx) el;
  1273. spr ctx "))";
  1274. | TThrow e ->
  1275. spr ctx "throw new HException(";
  1276. gen_value ctx e;
  1277. spr ctx ")";
  1278. | TVars [] ->
  1279. ()
  1280. | TVars vl ->
  1281. spr ctx "$";
  1282. concat ctx ("; $") (fun (v,e) ->
  1283. let restore = save_locals ctx in
  1284. let n = define_local ctx v.v_name in
  1285. let restore2 = save_locals ctx in
  1286. restore();
  1287. (match e with
  1288. | None ->
  1289. print ctx "%s = null" (s_ident_local n)
  1290. | Some e ->
  1291. print ctx "%s = " (s_ident_local n);
  1292. gen_value ctx e);
  1293. restore2()
  1294. ) vl;
  1295. | TNew (c,_,el) ->
  1296. (match c.cl_path, el with
  1297. | ([], "String"), _ ->
  1298. concat ctx "" (gen_value ctx) el
  1299. | ([], "Array"), el ->
  1300. spr ctx "new _hx_array(array(";
  1301. concat ctx ", " (gen_value ctx) el;
  1302. spr ctx "))"
  1303. | (_, _), _ ->
  1304. print ctx "new %s(" (s_path ctx c.cl_path c.cl_extern e.epos);
  1305. let count = ref (-1) in
  1306. concat ctx ", " (fun e ->
  1307. incr count;
  1308. match c.cl_constructor with
  1309. | Some f ->
  1310. gen_value ctx e;
  1311. | _ -> ();
  1312. ) el;
  1313. spr ctx ")")
  1314. | TIf (cond,e,eelse) ->
  1315. spr ctx "if";
  1316. gen_value ctx (parent cond);
  1317. spr ctx " ";
  1318. restore_in_block ctx in_block;
  1319. gen_expr ctx (mk_block e);
  1320. (match eelse with
  1321. | None -> ()
  1322. | Some e when e.eexpr = TConst(TNull) -> ()
  1323. | Some e ->
  1324. spr ctx " else ";
  1325. restore_in_block ctx in_block;
  1326. gen_expr ctx (mk_block e));
  1327. | TUnop (op,Ast.Prefix,e) ->
  1328. (match e.eexpr with
  1329. | TArray(te1, te2) ->
  1330. (match op with
  1331. | Increment ->
  1332. spr ctx "_hx_array_increment(";
  1333. gen_value ctx te1;
  1334. spr ctx ",";
  1335. gen_value ctx te2;
  1336. spr ctx ")";
  1337. | Decrement ->
  1338. spr ctx "_hx_array_decrement(";
  1339. gen_value ctx te1;
  1340. spr ctx ",";
  1341. gen_value ctx te2;
  1342. spr ctx ")";
  1343. | _ ->
  1344. spr ctx (Ast.s_unop op);
  1345. gen_value ctx te1;
  1346. spr ctx "[";
  1347. gen_value ctx te2;
  1348. spr ctx "]";
  1349. );
  1350. | TField (e1,s) ->
  1351. spr ctx (Ast.s_unop op);
  1352. gen_field_access ctx true e1 (field_name s)
  1353. | _ ->
  1354. spr ctx (Ast.s_unop op);
  1355. gen_value ctx e)
  1356. | TUnop (op,Ast.Postfix,e) ->
  1357. (match e.eexpr with
  1358. | TArray(te1, te2) ->
  1359. gen_value ctx te1;
  1360. spr ctx "->a[";
  1361. gen_value ctx te2;
  1362. spr ctx "]";
  1363. | TField (e1,s) ->
  1364. gen_field_access ctx true e1 (field_name s)
  1365. | _ ->
  1366. gen_value ctx e);
  1367. spr ctx (Ast.s_unop op)
  1368. | TWhile (cond,e,Ast.NormalWhile) ->
  1369. let old = save_locals ctx in
  1370. spr ctx "while";
  1371. gen_value ctx (parent cond);
  1372. spr ctx " {";
  1373. let bend = open_block ctx in
  1374. gen_while_expr ctx e;
  1375. bend();
  1376. newline ctx;
  1377. spr ctx "}";
  1378. old()
  1379. | TWhile (cond,e,Ast.DoWhile) ->
  1380. let old = save_locals ctx in
  1381. spr ctx "do {";
  1382. let bend = open_block ctx in
  1383. gen_while_expr ctx e;
  1384. bend();
  1385. newline ctx;
  1386. spr ctx "} while";
  1387. gen_value ctx (parent cond);
  1388. old()
  1389. | TObjectDecl fields ->
  1390. spr ctx "_hx_anonymous(array(";
  1391. concat ctx ", " (fun (f,e) -> print ctx "\"%s\" => " (escape_bin f); gen_value ctx e) fields;
  1392. spr ctx "))"
  1393. | TFor (v,it,e) ->
  1394. let b = save_locals ctx in
  1395. let tmp = define_local ctx "__hx__it" in
  1396. let v = define_local ctx v.v_name in
  1397. (match it.eexpr with
  1398. | TCall (e,_) ->
  1399. (match e.eexpr with
  1400. | TField (e,f) ->
  1401. spr ctx "if(null == ";
  1402. gen_value ctx e;
  1403. spr ctx ") throw new HException('null iterable')";
  1404. newline ctx;
  1405. | _ ->
  1406. ());
  1407. | _ -> ()
  1408. );
  1409. print ctx "$%s = " tmp;
  1410. gen_value ctx it;
  1411. newline ctx;
  1412. print ctx "while($%s->hasNext()) {" tmp;
  1413. let bend = open_block ctx in
  1414. newline ctx;
  1415. print ctx "$%s = $%s->next()" v tmp;
  1416. gen_while_expr ctx e;
  1417. bend();
  1418. newline ctx;
  1419. spr ctx "}";
  1420. b();
  1421. | TTry (e,catchs) ->
  1422. spr ctx "try ";
  1423. restore_in_block ctx in_block;
  1424. gen_expr ctx (mk_block e);
  1425. let old = save_locals ctx in
  1426. let ex = define_local ctx "__hx__e" in
  1427. print ctx "catch(Exception $%s) {" ex;
  1428. let bend = open_block ctx in
  1429. let first = ref true in
  1430. let catchall = ref false in
  1431. let evar = define_local ctx "_ex_" in
  1432. newline ctx;
  1433. print ctx "$%s = ($%s instanceof HException) ? $%s->e : $%s" evar ex ex ex;
  1434. old();
  1435. List.iter (fun (v,e) ->
  1436. let ev = define_local ctx v.v_name in
  1437. newline ctx;
  1438. let b = save_locals ctx in
  1439. if not !first then spr ctx "else ";
  1440. (match follow v.v_type with
  1441. | TEnum (te,_) -> (match te.e_path with
  1442. | [], "Bool" -> print ctx "if(is_bool($%s = $%s))" ev evar
  1443. | _ -> print ctx "if(($%s = $%s) instanceof %s)" ev evar (s_path ctx te.e_path te.e_extern e.epos));
  1444. restore_in_block ctx in_block;
  1445. gen_expr ctx (mk_block e);
  1446. | TInst (tc,_) -> (match tc.cl_path with
  1447. | [], "Int" -> print ctx "if(is_int($%s = $%s))" ev evar
  1448. | [], "Float" -> print ctx "if(is_numeric($%s = $%s))" ev evar
  1449. | [], "String" -> print ctx "if(is_string($%s = $%s))" ev evar
  1450. | [], "Array" -> print ctx "if(($%s = $%s) instanceof _hx_array)" ev evar
  1451. | _ -> print ctx "if(($%s = $%s) instanceof %s)" ev evar (s_path ctx tc.cl_path tc.cl_extern e.epos));
  1452. restore_in_block ctx in_block;
  1453. gen_expr ctx (mk_block e);
  1454. | TAbstract (ta,_) -> (match ta.a_path with
  1455. | [], "Int" -> print ctx "if(is_int($%s = $%s))" ev evar
  1456. | [], "Float" -> print ctx "if(is_numeric($%s = $%s))" ev evar
  1457. | [], "Bool" -> print ctx "if(is_bool($%s = $%s))" ev evar
  1458. | _ -> print ctx "if(($%s = $%s) instanceof %s)" ev evar (s_path ctx ta.a_path false e.epos));
  1459. restore_in_block ctx in_block;
  1460. gen_expr ctx (mk_block e);
  1461. | TFun _
  1462. | TLazy _
  1463. | TType _
  1464. | TAnon _ ->
  1465. assert false
  1466. | TMono _
  1467. | TDynamic _ ->
  1468. catchall := true;
  1469. if not !first then spr ctx "{ ";
  1470. print ctx "$%s = $%s" ev evar;
  1471. newline ctx;
  1472. restore_in_block ctx in_block;
  1473. gen_expr ctx (mk_block e);
  1474. if not !first then spr ctx "}"
  1475. );
  1476. b();
  1477. first := false;
  1478. ) catchs;
  1479. if not !catchall then
  1480. print ctx " else throw $%s;" ex;
  1481. bend();
  1482. newline ctx;
  1483. spr ctx "}"
  1484. | TMatch (e,_,cases,def) ->
  1485. let b = save_locals ctx in
  1486. let tmp = define_local ctx "__hx__t" in
  1487. print ctx "$%s = " tmp;
  1488. gen_value ctx e;
  1489. newline ctx;
  1490. print ctx "switch($%s->index) {" tmp;
  1491. let old_loop = ctx.in_loop in
  1492. ctx.in_loop <- false;
  1493. ctx.nested_loops <- ctx.nested_loops + 1;
  1494. newline ctx;
  1495. List.iter (fun (cl,params,e) ->
  1496. List.iter (fun c ->
  1497. print ctx "case %d:" c;
  1498. newline ctx;
  1499. ) cl;
  1500. let b = save_locals ctx in
  1501. (match params with
  1502. | None | Some [] -> ()
  1503. | Some l ->
  1504. let n = ref (-1) in
  1505. let l = List.fold_left (fun acc v -> incr n; match v with None -> acc | Some v -> (v.v_name,v.v_type,!n) :: acc) [] l in
  1506. match l with
  1507. | [] -> ()
  1508. | l ->
  1509. concat ctx "; " (fun (v,t,n) ->
  1510. let v = define_local ctx v in
  1511. print ctx "$%s = $%s->params[%d]" v tmp n;
  1512. ) l;
  1513. newline ctx);
  1514. restore_in_block ctx in_block;
  1515. gen_expr ctx (mk_block e);
  1516. print ctx "break";
  1517. newline ctx;
  1518. b()
  1519. ) cases;
  1520. (match def with
  1521. | None -> ()
  1522. | Some e ->
  1523. spr ctx "default:";
  1524. restore_in_block ctx in_block;
  1525. gen_expr ctx (mk_block e);
  1526. print ctx "break";
  1527. newline ctx;
  1528. );
  1529. ctx.nested_loops <- ctx.nested_loops - 1;
  1530. ctx.in_loop <- old_loop;
  1531. spr ctx "}";
  1532. b()
  1533. | TSwitch (e,cases,def) ->
  1534. let old_loop = ctx.in_loop in
  1535. ctx.in_loop <- false;
  1536. ctx.nested_loops <- ctx.nested_loops + 1;
  1537. let old = save_locals ctx in
  1538. spr ctx "switch";
  1539. gen_value ctx (parent e);
  1540. spr ctx " {";
  1541. newline ctx;
  1542. List.iter (fun (el,e2) ->
  1543. List.iter (fun e ->
  1544. spr ctx "case ";
  1545. gen_value ctx e;
  1546. spr ctx ":";
  1547. ) el;
  1548. restore_in_block ctx in_block;
  1549. gen_expr ctx (mk_block e2);
  1550. print ctx "break";
  1551. newline ctx;
  1552. ) cases;
  1553. (match def with
  1554. | None -> ()
  1555. | Some e ->
  1556. spr ctx "default:";
  1557. restore_in_block ctx in_block;
  1558. gen_expr ctx (mk_block e);
  1559. print ctx "break";
  1560. newline ctx;
  1561. );
  1562. spr ctx "}";
  1563. ctx.nested_loops <- ctx.nested_loops - 1;
  1564. ctx.in_loop <- old_loop;
  1565. old()
  1566. | TCast (e,None) ->
  1567. gen_expr ctx e
  1568. | TCast (e1,Some t) ->
  1569. let mk_texpr = function
  1570. | TClassDecl c -> TAnon { a_fields = PMap.empty; a_status = ref (Statics c) }
  1571. | TEnumDecl e -> TAnon { a_fields = PMap.empty; a_status = ref (EnumStatics e) }
  1572. | TAbstractDecl a -> TAnon { a_fields = PMap.empty; a_status = ref (AbstractStatics a) }
  1573. | TTypeDecl _ -> assert false
  1574. in
  1575. spr ctx "_hx_cast(";
  1576. gen_expr ctx e1;
  1577. spr ctx ", ";
  1578. gen_expr ctx (mk (TTypeExpr t) (mk_texpr t) e1.epos);
  1579. spr ctx ")"
  1580. and argument_list_from_locals include_this in_var l =
  1581. let lst = ref [] in
  1582. if (include_this && in_var) then lst := "__hx__this" :: !lst
  1583. else if include_this then lst := "this" :: !lst;
  1584. PMap.iter (fun n _ ->
  1585. lst := !lst @ [n];
  1586. ) l;
  1587. !lst
  1588. and remove_internals args =
  1589. List.filter (fun a -> a = "__hx__this" || not (start_with a "__hx__")) args;
  1590. and inline_block ctx e =
  1591. let index = ctx.inline_index in
  1592. ctx.inline_index <- ctx.inline_index + 1;
  1593. let block = {
  1594. iname = (s_path ctx ctx.curclass.cl_path ctx.curclass.cl_extern ctx.curclass.cl_pos) ^ "_" ^ string_of_int index;
  1595. iindex = index;
  1596. ihasthis = ctx.in_instance_method; (* param this *)
  1597. iarguments = [];
  1598. iexpr = e;
  1599. ilocals = ctx.locals;
  1600. iin_block = true;
  1601. iinv_locals = ctx.inv_locals;
  1602. } in
  1603. print ctx "%s(" block.iname;
  1604. let in_value = (match ctx.in_value with Some _ -> true | _ -> false) in
  1605. (match remove_internals (argument_list_from_locals ctx.in_instance_method in_value ctx.locals) with
  1606. | [] -> ()
  1607. | l -> print ctx "$%s" (String.concat ", $" l)
  1608. );
  1609. spr ctx ")";
  1610. ctx.inline_methods <- ctx.inline_methods @ [block]
  1611. and inline_function ctx args hasthis e =
  1612. let index = ctx.inline_index in
  1613. ctx.inline_index <- ctx.inline_index + 1;
  1614. let block = {
  1615. iname = (s_path ctx ctx.curclass.cl_path ctx.curclass.cl_extern ctx.curclass.cl_pos) ^ "_" ^ string_of_int index;
  1616. iindex = index;
  1617. ihasthis = hasthis; (* param this *)
  1618. iarguments = args;
  1619. iexpr = e;
  1620. ilocals = ctx.locals;
  1621. iin_block = false;
  1622. iinv_locals = ctx.inv_locals;
  1623. } in
  1624. ctx.inline_methods <- ctx.inline_methods @ [block];
  1625. block.iname
  1626. and canbe_ternary_param e =
  1627. match e.eexpr with
  1628. | TTypeExpr _
  1629. | TConst _
  1630. | TLocal _
  1631. | TField (_,FEnum _)
  1632. | TParenthesis _
  1633. | TObjectDecl _
  1634. | TArrayDecl _
  1635. | TCall _
  1636. | TUnop _
  1637. | TNew _
  1638. | TCast (_, _)
  1639. | TBlock [_] ->
  1640. true
  1641. | TIf (_,e,eelse) ->
  1642. cangen_ternary e eelse
  1643. | _ ->
  1644. false
  1645. and cangen_ternary e eelse =
  1646. match eelse with
  1647. | Some other ->
  1648. (canbe_ternary_param e) && (canbe_ternary_param other)
  1649. | _ ->
  1650. false
  1651. and gen_value ctx e =
  1652. match e.eexpr with
  1653. | TTypeExpr _
  1654. | TConst _
  1655. | TLocal _
  1656. | TArray _
  1657. | TBinop _
  1658. | TField _
  1659. | TParenthesis _
  1660. | TObjectDecl _
  1661. | TArrayDecl _
  1662. | TCall _
  1663. | TUnop _
  1664. | TNew _
  1665. | TFunction _ ->
  1666. gen_expr ctx e
  1667. | TBlock [] ->
  1668. ()
  1669. | TCast (e, _)
  1670. | TBlock [e] ->
  1671. gen_value ctx e
  1672. | TIf (cond,e,eelse) when (cangen_ternary e eelse) ->
  1673. spr ctx "(";
  1674. gen_value ctx cond;
  1675. spr ctx " ? ";
  1676. gen_value ctx e;
  1677. (match eelse with
  1678. | Some e ->
  1679. spr ctx " : ";
  1680. gen_value ctx e
  1681. | _ ->());
  1682. spr ctx ")";
  1683. (*
  1684. | TIf (cond,e,eelse) ->
  1685. spr ctx "if";
  1686. gen_value ctx (parent cond);
  1687. spr ctx " ";
  1688. restore_in_block ctx in_block;
  1689. gen_expr ctx (mk_block e);
  1690. (match eelse with
  1691. | None -> ()
  1692. | Some e when e.eexpr = TConst(TNull) -> ()
  1693. | Some e ->
  1694. spr ctx " else ";
  1695. restore_in_block ctx in_block;
  1696. gen_expr ctx (mk_block e));
  1697. *)
  1698. | TBlock _
  1699. | TBreak
  1700. | TContinue
  1701. | TVars _
  1702. | TReturn _
  1703. | TWhile _
  1704. | TThrow _
  1705. | TSwitch _
  1706. | TFor _
  1707. | TMatch _
  1708. | TIf _
  1709. | TTry _ ->
  1710. inline_block ctx e
  1711. let rec is_instance_method_defined cls m =
  1712. if PMap.exists m cls.cl_fields then
  1713. true
  1714. else
  1715. match cls.cl_super with
  1716. | Some (scls, _) ->
  1717. is_instance_method_defined scls m
  1718. | None ->
  1719. false
  1720. let is_method_defined ctx m static =
  1721. if static then
  1722. PMap.exists m ctx.curclass.cl_statics
  1723. else
  1724. is_instance_method_defined ctx.curclass m
  1725. let generate_self_method ctx rights m static setter =
  1726. if setter then (
  1727. if static then
  1728. print ctx "%s function %s($v) { return call_user_func(self::$%s, $v); }" rights (s_ident m) (s_ident m)
  1729. else
  1730. print ctx "%s function %s($v) { return call_user_func($this->%s, $v); }" rights (s_ident m) (s_ident m)
  1731. ) else (
  1732. if static then
  1733. print ctx "%s function %s() { return call_user_func(self::$%s); }" rights (s_ident m) (s_ident m)
  1734. else
  1735. print ctx "%s function %s() { return call_user_func($this->%s); }" rights (s_ident m) (s_ident m)
  1736. );
  1737. newline ctx
  1738. let gen_assigned_value ctx eo = match eo with
  1739. | Some ({eexpr = TConst _} as e) ->
  1740. print ctx " = ";
  1741. gen_value ctx e
  1742. | _ ->
  1743. ()
  1744. let generate_field ctx static f =
  1745. if not (is_extern_field f) then
  1746. newline ctx;
  1747. ctx.locals <- PMap.empty;
  1748. ctx.inv_locals <- PMap.empty;
  1749. ctx.in_instance_method <- not static;
  1750. let rights = if static then "static" else "public" in
  1751. let p = ctx.curclass.cl_pos in
  1752. match f.cf_expr with
  1753. | Some { eexpr = TFunction fd } ->
  1754. if f.cf_name = "__construct" then
  1755. ctx.curmethod <- "new"
  1756. else
  1757. ctx.curmethod <- f.cf_name;
  1758. spr ctx (rights ^ " ");
  1759. if is_dynamic_method f then
  1760. gen_dynamic_function ctx static (s_ident f.cf_name) fd f.cf_params p
  1761. else
  1762. gen_function ctx (s_ident f.cf_name) fd f.cf_params p
  1763. | _ ->
  1764. if (is_extern_field f) then
  1765. ()
  1766. else if ctx.curclass.cl_interface then
  1767. match follow f.cf_type, f.cf_kind with
  1768. | TFun (args,r), Method _ ->
  1769. print ctx "function %s(" (s_ident f.cf_name);
  1770. concat ctx ", " (fun (arg,o,t) ->
  1771. s_funarg ctx arg t p o;
  1772. ) args;
  1773. print ctx ")";
  1774. | _ -> spr ctx "//"; ()
  1775. else if
  1776. (match f.cf_kind with
  1777. | Var v ->
  1778. (match v.v_read, v.v_write with
  1779. | AccCall m1, AccCall m2 ->
  1780. if not (is_method_defined ctx m1 static) then (
  1781. generate_self_method ctx rights m1 static false;
  1782. print ctx "%s $%s" rights (s_ident m1);
  1783. if not (is_method_defined ctx m2 static) then
  1784. newline ctx);
  1785. if not (is_method_defined ctx m2 static) then (
  1786. generate_self_method ctx rights m2 static true;
  1787. print ctx "%s $%s" rights (s_ident m2);
  1788. newline ctx);
  1789. false
  1790. | AccCall m, _ ->
  1791. if not (is_method_defined ctx m static) then generate_self_method ctx rights m static false;
  1792. print ctx "%s $%s" rights (s_ident_field f.cf_name);
  1793. gen_assigned_value ctx f.cf_expr;
  1794. true
  1795. | _, AccCall m ->
  1796. if not (is_method_defined ctx m static) then generate_self_method ctx rights m static true;
  1797. print ctx "%s $%s" rights (s_ident_field f.cf_name);
  1798. gen_assigned_value ctx f.cf_expr;
  1799. true
  1800. | _ ->
  1801. false)
  1802. | _ -> false) then
  1803. ()
  1804. else begin
  1805. let name = if static then s_ident f.cf_name else f.cf_name in
  1806. if static then
  1807. (match f.cf_kind with
  1808. | Var _ ->
  1809. (match follow f.cf_type with
  1810. | TFun _
  1811. | TDynamic _ ->
  1812. print ctx "static function %s() { $args = func_get_args(); return call_user_func_array(self::$%s, $args); }" name name;
  1813. newline ctx;
  1814. | _ ->
  1815. ()
  1816. )
  1817. | _ ->
  1818. ()
  1819. );
  1820. print ctx "%s $%s" rights name;
  1821. gen_assigned_value ctx f.cf_expr
  1822. end
  1823. let generate_static_field_assign ctx path f =
  1824. let p = ctx.curclass.cl_pos in
  1825. if not ctx.curclass.cl_interface then
  1826. (match f.cf_expr with
  1827. | None -> ()
  1828. | Some e ->
  1829. match e.eexpr with
  1830. | TConst _ -> ()
  1831. | TFunction fd ->
  1832. (match f.cf_kind with
  1833. | Var _ when
  1834. (match follow f.cf_type with
  1835. | TFun _
  1836. | TDynamic _ ->
  1837. true;
  1838. | _ ->
  1839. false) ->
  1840. newline ctx;
  1841. print ctx "%s::$%s = " (s_path ctx path false p) (s_ident f.cf_name);
  1842. gen_value ctx e
  1843. | Method MethDynamic ->
  1844. newline ctx;
  1845. print ctx "%s::$%s = " (s_path ctx path false p) (s_ident f.cf_name);
  1846. gen_value ctx e
  1847. | _ -> ())
  1848. | _ ->
  1849. newline ctx;
  1850. print ctx "%s::$%s = " (s_path ctx path false p) (s_ident f.cf_name);
  1851. gen_value ctx e)
  1852. let rec super_has_dynamic c =
  1853. match c.cl_super with
  1854. | None -> false
  1855. | Some (csup, _) -> (match csup.cl_dynamic with
  1856. | Some _ -> true
  1857. | _ -> super_has_dynamic csup)
  1858. let generate_inline_method ctx c m =
  1859. (match ctx.inline_methods with
  1860. | [] -> ()
  1861. | h :: t -> ctx.inline_methods <- t
  1862. );
  1863. ctx.curclass <- c;
  1864. let old = save_locals ctx in
  1865. ctx.in_value <- Some m.iname;
  1866. ctx.in_block <- m.iin_block;
  1867. ctx.in_loop <- false;
  1868. ctx.locals <- m.ilocals;
  1869. ctx.inv_locals <- m.iinv_locals;
  1870. newline ctx;
  1871. print ctx "function %s(" m.iname;
  1872. (* arguments *)
  1873. let in_value = (match ctx.in_value with Some _ -> true | _ -> false) in
  1874. let arguments = remove_internals (argument_list_from_locals m.ihasthis in_value ctx.locals) in
  1875. let arguments = match arguments with
  1876. | [h] when h = "this" -> ["__hx__this"]
  1877. | h :: t when h = "this" -> "__hx__this" :: t
  1878. | _ -> arguments
  1879. in
  1880. let marguments = List.map (define_local ctx) m.iarguments in
  1881. let arguments = (List.map (fun a -> "&$" ^ a) arguments) @ (List.map (fun a -> "$" ^ a) marguments) in
  1882. (match arguments with
  1883. | [] -> ()
  1884. | l -> spr ctx (String.concat ", " arguments)
  1885. );
  1886. spr ctx ") {";
  1887. ctx.nested_loops <- ctx.nested_loops - 1;
  1888. let block = open_block ctx in
  1889. newline ctx;
  1890. gen_expr ctx m.iexpr;
  1891. block();
  1892. old();
  1893. ctx.nested_loops <- ctx.nested_loops + 1;
  1894. newline ctx;
  1895. spr ctx "}"
  1896. let generate_class ctx c =
  1897. let requires_constructor = ref true in
  1898. ctx.curclass <- c;
  1899. ctx.local_types <- List.map snd c.cl_types;
  1900. print ctx "%s %s " (if c.cl_interface then "interface" else "class") (s_path ctx c.cl_path c.cl_extern c.cl_pos);
  1901. (match c.cl_super with
  1902. | None -> ()
  1903. | Some (csup,_) ->
  1904. requires_constructor := false;
  1905. print ctx "extends %s " (s_path ctx csup.cl_path csup.cl_extern c.cl_pos));
  1906. let implements = ExtList.List.unique ~cmp:(fun a b -> (fst a).cl_path = (fst b).cl_path) c.cl_implements in
  1907. (match implements with
  1908. | [] -> ()
  1909. | l ->
  1910. spr ctx (if c.cl_interface then "extends " else "implements ");
  1911. concat ctx ", " (fun (i,_) ->
  1912. print ctx "%s" (s_path ctx i.cl_path i.cl_extern c.cl_pos)) l);
  1913. spr ctx "{";
  1914. let get_dynamic_methods = List.filter is_dynamic_method c.cl_ordered_fields in
  1915. if not ctx.curclass.cl_interface then ctx.dynamic_methods <- get_dynamic_methods;
  1916. let cl = open_block ctx in
  1917. (match c.cl_constructor with
  1918. | None ->
  1919. if !requires_constructor && not c.cl_interface then begin
  1920. newline ctx;
  1921. spr ctx "public function __construct(){}"
  1922. end;
  1923. | Some f ->
  1924. let f = { f with
  1925. cf_name = "__construct";
  1926. cf_public = true;
  1927. } in
  1928. ctx.constructor_block <- true;
  1929. generate_field ctx false f;
  1930. );
  1931. List.iter (generate_field ctx false) c.cl_ordered_fields;
  1932. (match c.cl_dynamic with
  1933. | Some _ when not c.cl_interface && not (super_has_dynamic c) ->
  1934. newline ctx;
  1935. spr ctx "public $__dynamics = array();\n\tpublic function __get($n) {\n\t\tif(isset($this->__dynamics[$n]))\n\t\t\treturn $this->__dynamics[$n];\n\t}\n\tpublic function __set($n, $v) {\n\t\t$this->__dynamics[$n] = $v;\n\t}\n\tpublic function __call($n, $a) {\n\t\tif(isset($this->__dynamics[$n]) && is_callable($this->__dynamics[$n]))\n\t\t\treturn call_user_func_array($this->__dynamics[$n], $a);\n\t\tif('toString' == $n)\n\t\t\treturn $this->__toString();\n\t\tthrow new HException(\"Unable to call <\".$n.\">\");\n\t}"
  1936. | Some _
  1937. | _ ->
  1938. if List.length ctx.dynamic_methods > 0 then begin
  1939. newline ctx;
  1940. spr ctx "public function __call($m, $a) {\n\t\tif(isset($this->$m) && is_callable($this->$m))\n\t\t\treturn call_user_func_array($this->$m, $a);\n\t\telse if(isset($this->__dynamics[$m]) && is_callable($this->__dynamics[$m]))\n\t\t\treturn call_user_func_array($this->__dynamics[$m], $a);\n\t\telse if('toString' == $m)\n\t\t\treturn $this->__toString();\n\t\telse\n\t\t\tthrow new HException('Unable to call <'.$m.'>');\n\t}";
  1941. end;
  1942. );
  1943. List.iter (generate_field ctx true) c.cl_ordered_statics;
  1944. let gen_props props =
  1945. String.concat "," (List.map (fun (p,v) -> "\"" ^ p ^ "\" => \"" ^ v ^ "\"") props)
  1946. in
  1947. let rec fields c =
  1948. let list = Codegen.get_properties (c.cl_ordered_statics @ c.cl_ordered_fields) in
  1949. match c.cl_super with
  1950. | Some (csup, _) ->
  1951. list @ fields csup
  1952. | None ->
  1953. list
  1954. in
  1955. if not c.cl_interface then (match fields c with
  1956. | [] ->
  1957. ()
  1958. | props ->
  1959. newline ctx;
  1960. print ctx "static $__properties__ = array(%s)" (gen_props props);
  1961. );
  1962. cl();
  1963. newline ctx;
  1964. if PMap.exists "__toString" c.cl_fields then
  1965. ()
  1966. else if PMap.exists "toString" c.cl_fields && (not c.cl_interface) && (not c.cl_extern) then begin
  1967. print ctx "\tfunction __toString() { return $this->toString(); }";
  1968. newline ctx
  1969. end else if (not c.cl_interface) && (not c.cl_extern) then begin
  1970. print ctx "\tfunction __toString() { return '%s'; }" (s_path_haxe c.cl_path) ;
  1971. newline ctx
  1972. end;
  1973. print ctx "}"
  1974. let createmain com e =
  1975. let filename = match com.php_front with None -> "index.php" | Some n -> n in
  1976. let ctx = {
  1977. com = com;
  1978. stack = stack_init com false;
  1979. tabs = "";
  1980. ch = open_out (com.file ^ "/" ^ filename);
  1981. path = ([], "");
  1982. buf = Buffer.create (1 lsl 14);
  1983. in_value = None;
  1984. in_loop = false;
  1985. in_instance_method = false;
  1986. imports = Hashtbl.create 0;
  1987. extern_required_paths = [];
  1988. extern_classes_with_init = [];
  1989. curclass = null_class;
  1990. curmethod = "";
  1991. locals = PMap.empty;
  1992. inv_locals = PMap.empty;
  1993. local_types = [];
  1994. inits = [];
  1995. constructor_block = false;
  1996. dynamic_methods = [];
  1997. all_dynamic_methods = [];
  1998. is_call = false;
  1999. cwd = "";
  2000. inline_methods = [];
  2001. nested_loops = 0;
  2002. inline_index = 0;
  2003. in_block = false;
  2004. lib_path = match com.php_lib with None -> "lib" | Some s -> s;
  2005. } in
  2006. spr ctx "if(version_compare(PHP_VERSION, '5.1.0', '<')) {
  2007. exit('Your current PHP version is: ' . PHP_VERSION . '. Haxe/PHP generates code for version 5.1.0 or later');
  2008. }";
  2009. newline ctx;
  2010. newline ctx;
  2011. spr ctx ("require_once dirname(__FILE__).'/" ^ ctx.lib_path ^ "/php/" ^ (prefix_class com "Boot.class.php';\n\n"));
  2012. gen_value ctx e;
  2013. newline ctx;
  2014. spr ctx "\n?>";
  2015. close ctx
  2016. let generate_main ctx c =
  2017. (match c.cl_ordered_statics with
  2018. | [{ cf_expr = Some e }] ->
  2019. gen_value ctx e;
  2020. | _ -> assert false);
  2021. newline ctx
  2022. let generate_enum ctx e =
  2023. ctx.local_types <- List.map snd e.e_types;
  2024. let pack = open_block ctx in
  2025. let ename = s_path ctx e.e_path e.e_extern e.e_pos in
  2026. print ctx "class %s extends Enum {" ename;
  2027. PMap.iter (fun _ c ->
  2028. newline ctx;
  2029. match c.ef_type with
  2030. | TFun (args,_) ->
  2031. print ctx "public static function %s($" c.ef_name;
  2032. concat ctx ", $" (fun (a,o,t) ->
  2033. spr ctx a;
  2034. if o then spr ctx " = null";
  2035. ) args;
  2036. spr ctx ") {";
  2037. print ctx " return new %s(\"%s\", %d, array($" ename c.ef_name c.ef_index;
  2038. concat ctx ", $" (fun (a,_,_) -> spr ctx a) args;
  2039. print ctx ")); }";
  2040. | _ ->
  2041. print ctx "public static $%s" c.ef_name;
  2042. ) e.e_constrs;
  2043. newline ctx;
  2044. spr ctx "public static $__constructors = array(";
  2045. let first = ref true in
  2046. PMap.iter (fun _ c ->
  2047. if not !first then spr ctx ", ";
  2048. print ctx "%d => '%s'" c.ef_index c.ef_name;
  2049. first := false;
  2050. ) e.e_constrs;
  2051. spr ctx ")";
  2052. newline ctx;
  2053. (match Codegen.build_metadata ctx.com (TEnumDecl e) with
  2054. | None -> ()
  2055. | Some _ ->
  2056. spr ctx "public static $__meta__";
  2057. newline ctx);
  2058. pack();
  2059. print ctx "}";
  2060. PMap.iter (fun _ c ->
  2061. match c.ef_type with
  2062. | TFun (args,_) ->
  2063. ();
  2064. | _ ->
  2065. newline ctx;
  2066. print ctx "%s::$%s = new %s(\"%s\", %d)" ename c.ef_name ename c.ef_name c.ef_index;
  2067. ) e.e_constrs;
  2068. newline ctx;
  2069. match Codegen.build_metadata ctx.com (TEnumDecl e) with
  2070. | None -> ()
  2071. | Some e ->
  2072. print ctx "%s::$__meta__ = " ename;
  2073. gen_expr ctx e;
  2074. newline ctx
  2075. let generate com =
  2076. let all_dynamic_methods = ref [] in
  2077. let extern_classes_with_init = ref [] in
  2078. let php_lib_path = (match com.php_lib with None -> "lib" | Some n -> n) in
  2079. create_directory com (Str.split (Str.regexp "/") php_lib_path);
  2080. (* check for methods with the same name but different case *)
  2081. let check_class_fields c =
  2082. let lc_names = ref [] in
  2083. let special_cases = ["toString"] in
  2084. let loop c lst static =
  2085. let in_special_cases name =
  2086. (List.exists (fun n -> String.lowercase n = name) (special_cases @ List.map (fun f -> f.cf_name) c.cl_overrides))
  2087. in
  2088. List.iter(fun cf ->
  2089. let name = String.lowercase cf.cf_name in
  2090. let prefixed_name s = (if s then "s_" else "i_") ^ name in
  2091. match cf.cf_kind, cf.cf_expr with
  2092. | (Method _, Some e) when not (in_special_cases name) ->
  2093. (try
  2094. let lc = List.find (fun n ->
  2095. let n = snd n in
  2096. if static then
  2097. (n = (prefixed_name false))
  2098. else
  2099. ((n = (prefixed_name false)) or (n = (prefixed_name true)))
  2100. ) !lc_names in
  2101. unsupported ("method '" ^ (s_type_path c.cl_path) ^ "." ^ cf.cf_name ^ "' already exists here '" ^ (fst lc) ^ "' (different case?)") c.cl_pos
  2102. with Not_found ->
  2103. lc_names := ((s_type_path c.cl_path) ^ "." ^ cf.cf_name, prefixed_name static) :: !lc_names)
  2104. | _ ->
  2105. ()
  2106. ) lst
  2107. in
  2108. let rec _check_class_fields cl =
  2109. (match cl.cl_super with
  2110. | Some (s,_) -> _check_class_fields s
  2111. | _ -> ());
  2112. loop cl cl.cl_ordered_statics true;
  2113. loop cl cl.cl_ordered_fields false
  2114. in
  2115. _check_class_fields c
  2116. in
  2117. List.iter (fun t ->
  2118. (match t with
  2119. | TClassDecl c ->
  2120. check_class_fields c
  2121. | TEnumDecl e ->
  2122. let e_names = ref [] in
  2123. List.iter(fun en -> (
  2124. if List.exists (fun n -> n = String.lowercase en) !e_names then
  2125. unsupported ("'" ^ en ^ "' constructor exists with different case") e.e_pos
  2126. else
  2127. e_names := (String.lowercase en) :: !e_names
  2128. )) (e.e_names)
  2129. | _ -> ())
  2130. ) com.types;
  2131. List.iter (fun t ->
  2132. (match t with
  2133. | TClassDecl c ->
  2134. let dynamic_methods_names lst =
  2135. List.map (fun fd -> {
  2136. mpath = c.cl_path;
  2137. mname = fd.cf_name;
  2138. }) (List.filter is_dynamic_method lst)
  2139. in
  2140. all_dynamic_methods := dynamic_methods_names c.cl_ordered_fields @ !all_dynamic_methods;
  2141. if c.cl_extern then
  2142. (match c.cl_init with
  2143. | Some _ ->
  2144. extern_classes_with_init := c.cl_path :: !extern_classes_with_init;
  2145. | _ ->
  2146. ())
  2147. else
  2148. all_dynamic_methods := dynamic_methods_names c.cl_ordered_statics @ !all_dynamic_methods;
  2149. | _ -> ())
  2150. ) com.types;
  2151. List.iter (Codegen.fix_abstract_inheritance com) com.types;
  2152. List.iter (fun t ->
  2153. (match t with
  2154. | TClassDecl c ->
  2155. if c.cl_extern then begin
  2156. (match c.cl_init with
  2157. | None -> ()
  2158. | Some e ->
  2159. let ctx = init com php_lib_path c.cl_path 3 in
  2160. gen_expr ctx e;
  2161. newline ctx;
  2162. close ctx;
  2163. );
  2164. end else
  2165. let ctx = init com php_lib_path c.cl_path (if c.cl_interface then 2 else 0) in
  2166. ctx.extern_classes_with_init <- !extern_classes_with_init;
  2167. ctx.all_dynamic_methods <- !all_dynamic_methods;
  2168. generate_class ctx c;
  2169. (match c.cl_init with
  2170. | None -> ()
  2171. | Some e ->
  2172. newline ctx;
  2173. gen_expr ctx e);
  2174. List.iter (generate_static_field_assign ctx c.cl_path) c.cl_ordered_statics;
  2175. if c.cl_path = (["php"], "Boot") & com.debug then begin
  2176. newline ctx;
  2177. print ctx "$%s = new _hx_array(array())" ctx.stack.Codegen.stack_var;
  2178. newline ctx;
  2179. print ctx "$%s = new _hx_array(array())" ctx.stack.Codegen.stack_exc_var;
  2180. end;
  2181. let rec loop l =
  2182. match l with
  2183. | [] -> ()
  2184. | h :: _ ->
  2185. generate_inline_method ctx c h;
  2186. loop ctx.inline_methods
  2187. in
  2188. loop ctx.inline_methods;
  2189. newline ctx;
  2190. close ctx
  2191. | TEnumDecl e ->
  2192. if e.e_extern then
  2193. ()
  2194. else
  2195. let ctx = init com php_lib_path e.e_path 1 in
  2196. generate_enum ctx e;
  2197. close ctx
  2198. | TTypeDecl _ | TAbstractDecl _ ->
  2199. ());
  2200. ) com.types;
  2201. (match com.main with
  2202. | None -> ()
  2203. | Some e -> createmain com e);
  2204. Hashtbl.iter (fun name data ->
  2205. write_resource com.file name data
  2206. ) com.resources;