genphp.ml 61 KB

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