main.ml 51 KB

1234567891011121314151617181920212223242526272829303132333435363738394041424344454647484950515253545556575859606162636465666768697071727374757677787980818283848586878889909192939495969798991001011021031041051061071081091101111121131141151161171181191201211221231241251261271281291301311321331341351361371381391401411421431441451461471481491501511521531541551561571581591601611621631641651661671681691701711721731741751761771781791801811821831841851861871881891901911921931941951961971981992002012022032042052062072082092102112122132142152162172182192202212222232242252262272282292302312322332342352362372382392402412422432442452462472482492502512522532542552562572582592602612622632642652662672682692702712722732742752762772782792802812822832842852862872882892902912922932942952962972982993003013023033043053063073083093103113123133143153163173183193203213223233243253263273283293303313323333343353363373383393403413423433443453463473483493503513523533543553563573583593603613623633643653663673683693703713723733743753763773783793803813823833843853863873883893903913923933943953963973983994004014024034044054064074084094104114124134144154164174184194204214224234244254264274284294304314324334344354364374384394404414424434444454464474484494504514524534544554564574584594604614624634644654664674684694704714724734744754764774784794804814824834844854864874884894904914924934944954964974984995005015025035045055065075085095105115125135145155165175185195205215225235245255265275285295305315325335345355365375385395405415425435445455465475485495505515525535545555565575585595605615625635645655665675685695705715725735745755765775785795805815825835845855865875885895905915925935945955965975985996006016026036046056066076086096106116126136146156166176186196206216226236246256266276286296306316326336346356366376386396406416426436446456466476486496506516526536546556566576586596606616626636646656666676686696706716726736746756766776786796806816826836846856866876886896906916926936946956966976986997007017027037047057067077087097107117127137147157167177187197207217227237247257267277287297307317327337347357367377387397407417427437447457467477487497507517527537547557567577587597607617627637647657667677687697707717727737747757767777787797807817827837847857867877887897907917927937947957967977987998008018028038048058068078088098108118128138148158168178188198208218228238248258268278288298308318328338348358368378388398408418428438448458468478488498508518528538548558568578588598608618628638648658668678688698708718728738748758768778788798808818828838848858868878888898908918928938948958968978988999009019029039049059069079089099109119129139149159169179189199209219229239249259269279289299309319329339349359369379389399409419429439449459469479489499509519529539549559569579589599609619629639649659669679689699709719729739749759769779789799809819829839849859869879889899909919929939949959969979989991000100110021003100410051006100710081009101010111012101310141015101610171018101910201021102210231024102510261027102810291030103110321033103410351036103710381039104010411042104310441045104610471048104910501051105210531054105510561057105810591060106110621063106410651066106710681069107010711072107310741075107610771078107910801081108210831084108510861087108810891090109110921093109410951096109710981099110011011102110311041105110611071108110911101111111211131114111511161117111811191120112111221123112411251126112711281129113011311132113311341135113611371138113911401141114211431144114511461147114811491150115111521153115411551156115711581159116011611162116311641165116611671168116911701171117211731174117511761177117811791180118111821183118411851186118711881189119011911192119311941195119611971198119912001201120212031204120512061207120812091210121112121213121412151216121712181219122012211222122312241225122612271228122912301231123212331234123512361237123812391240124112421243124412451246124712481249125012511252125312541255125612571258125912601261126212631264126512661267126812691270127112721273127412751276127712781279128012811282128312841285128612871288128912901291129212931294129512961297129812991300130113021303130413051306130713081309131013111312131313141315131613171318131913201321132213231324132513261327132813291330133113321333133413351336133713381339134013411342134313441345134613471348134913501351135213531354135513561357135813591360136113621363136413651366136713681369137013711372137313741375137613771378137913801381138213831384138513861387138813891390139113921393139413951396139713981399140014011402
  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 Printf
  23. open Ast
  24. open Genswf
  25. open Common
  26. open Type
  27. type context = {
  28. com : Common.context;
  29. mutable flush : unit -> unit;
  30. mutable setup : unit -> unit;
  31. mutable messages : string list;
  32. mutable has_next : bool;
  33. mutable has_error : bool;
  34. }
  35. type cache = {
  36. mutable c_haxelib : (string list, string list) Hashtbl.t;
  37. mutable c_files : (string, float * Ast.package) Hashtbl.t;
  38. mutable c_modules : (path * string, module_def) Hashtbl.t;
  39. }
  40. exception Abort
  41. exception Completion of string
  42. let version = 301
  43. let measure_times = ref false
  44. let prompt = ref false
  45. let start_time = ref (get_time())
  46. let global_cache = ref None
  47. let executable_path() =
  48. Extc.executable_path()
  49. let is_debug_run() =
  50. try Sys.getenv "HAXEDEBUG" = "1" with _ -> false
  51. let format msg p =
  52. if p = Ast.null_pos then
  53. msg
  54. else begin
  55. let error_printer file line = sprintf "%s:%d:" file line in
  56. let epos = Lexer.get_error_pos error_printer p in
  57. let msg = String.concat ("\n" ^ epos ^ " : ") (ExtString.String.nsplit msg "\n") in
  58. sprintf "%s : %s" epos msg
  59. end
  60. let ssend sock str =
  61. let rec loop pos len =
  62. if len = 0 then
  63. ()
  64. else
  65. let s = Unix.send sock str pos len [] in
  66. loop (pos + s) (len - s)
  67. in
  68. loop 0 (String.length str)
  69. let message ctx msg p =
  70. ctx.messages <- format msg p :: ctx.messages
  71. let deprecated = [
  72. "Class not found : IntIter","IntIter was renamed to IntIterator";
  73. "EReg has no field customReplace","EReg.customReplace was renamed to EReg.map";
  74. "#StringTools has no field isEOF","StringTools.isEOF was renamed to StringTools.isEof";
  75. "Class not found : haxe.BaseCode","haxe.BaseCode was moved to haxe.crypto.BaseCode";
  76. "Class not found : haxe.Md5","haxe.Md5 was moved to haxe.crypto.Md5";
  77. "Class not found : haxe.SHA1","haxe.SHA1 was moved to haxe.crypto.SHA1";
  78. "Class not found : Hash","Hash has been removed, use Map instead";
  79. "Class not found : IntHash","IntHash has been removed, use Map instead";
  80. "Class not found : haxe.FastList","haxe.FastList was moved to haxe.ds.GenericStack";
  81. "#Std has no field format","Std.format has been removed, use single quote 'string ${escape}' syntax instead";
  82. "Class not found : Int32","Int32 has been removed, use Int instead";
  83. "Identifier 'EType' is not part of enum haxe.macro.ExprDef","EType has been removed, use EField instead";
  84. "Identifier 'CType' is not part of enum haxe.macro.Constant","CType has been removed, use CIdent instead";
  85. "Class not found : haxe.rtti.Infos","Use @:rtti instead of implementing haxe.rtti.Infos";
  86. "Class not found : haxe.rtti.Generic","Use @:generic instead of implementing haxe.Generic";
  87. "Class not found : haxe.Int32","haxe.Int32 has been removed, use normal Int instead";
  88. "Class not found : flash.utils.TypedDictionary","flash.utils.TypedDictionary has been removed, use Map instead";
  89. "Class not found : haxe.Stack", "haxe.Stack has been renamed to haxe.CallStack";
  90. "Class not found : neko.zip.Reader", "neko.zip.Reader has been removed, use haxe.zip.Reader instead";
  91. "Class not found : neko.zip.Reader", "neko.zip.Writer has been removed, use haxe.zip.Writer instead";
  92. "Class not found : haxe.Public", "Use @:publicFields instead of implementing or extending haxe.Public";
  93. "#Xml has no field createProlog", "Xml.createProlog was renamed to Xml.createProcessingInstruction";
  94. ]
  95. let error ctx msg p =
  96. let msg = try List.assoc msg deprecated with Not_found -> msg in
  97. message ctx msg p;
  98. ctx.has_error <- true
  99. let htmlescape s =
  100. let s = String.concat "&amp;" (ExtString.String.nsplit s "&") in
  101. let s = String.concat "&lt;" (ExtString.String.nsplit s "<") in
  102. let s = String.concat "&gt;" (ExtString.String.nsplit s ">") in
  103. s
  104. let reserved_flags = [
  105. "cross";"flash8";"js";"neko";"flash";"php";"cpp";"cs";"java";
  106. "as3";"swc";"macro";"sys"
  107. ]
  108. let complete_fields fields =
  109. let b = Buffer.create 0 in
  110. Buffer.add_string b "<list>\n";
  111. List.iter (fun (n,t,d) ->
  112. Buffer.add_string b (Printf.sprintf "<i n=\"%s\"><t>%s</t><d>%s</d></i>\n" n (htmlescape t) (htmlescape d))
  113. ) (List.sort (fun (a,_,_) (b,_,_) -> compare a b) fields);
  114. Buffer.add_string b "</list>\n";
  115. raise (Completion (Buffer.contents b))
  116. let report_times print =
  117. let tot = ref 0. in
  118. Hashtbl.iter (fun _ t -> tot := !tot +. t.total) Common.htimers;
  119. print (Printf.sprintf "Total time : %.3fs" !tot);
  120. if !tot > 0. then begin
  121. print "------------------------------------";
  122. let timers = List.sort (fun t1 t2 -> compare t1.name t2.name) (Hashtbl.fold (fun _ t acc -> t :: acc) Common.htimers []) in
  123. List.iter (fun t -> print (Printf.sprintf " %s : %.3fs, %.0f%%" t.name t.total (t.total *. 100. /. !tot))) timers
  124. end
  125. let make_path f =
  126. let f = String.concat "/" (ExtString.String.nsplit f "\\") in
  127. let cl = ExtString.String.nsplit f "." in
  128. let cl = (match List.rev cl with
  129. | ["hx";path] -> ExtString.String.nsplit path "/"
  130. | _ -> cl
  131. ) in
  132. let error() =
  133. let msg =
  134. if String.length f == 0 then
  135. "Class name must not be empty"
  136. else match (List.hd (List.rev cl)).[0] with
  137. | 'A'..'Z' -> "Invalid class name"
  138. | _ -> "Class name must start with uppercase character"
  139. in
  140. failwith msg
  141. in
  142. let invalid_char x =
  143. for i = 1 to String.length x - 1 do
  144. match x.[i] with
  145. | 'A'..'Z' | 'a'..'z' | '0'..'9' | '_' -> ()
  146. | _ -> error()
  147. done;
  148. false
  149. in
  150. let rec loop = function
  151. | [] -> error()
  152. | [x] -> if String.length x = 0 || not (x.[0] = '_' || (x.[0] >= 'A' && x.[0] <= 'Z')) || invalid_char x then error() else [] , x
  153. | x :: l ->
  154. if String.length x = 0 || x.[0] < 'a' || x.[0] > 'z' || invalid_char x then error() else
  155. let path , name = loop l in
  156. x :: path , name
  157. in
  158. loop cl
  159. let unique l =
  160. let rec _unique = function
  161. | [] -> []
  162. | x1 :: x2 :: l when x1 = x2 -> _unique (x2 :: l)
  163. | x :: l -> x :: _unique l
  164. in
  165. _unique (List.sort compare l)
  166. let rec read_type_path com p =
  167. let classes = ref [] in
  168. let packages = ref [] in
  169. let p = (match p with
  170. | x :: l ->
  171. (try
  172. match PMap.find x com.package_rules with
  173. | Directory d -> d :: l
  174. | Remap s -> s :: l
  175. | _ -> p
  176. with
  177. Not_found -> p)
  178. | _ -> p
  179. ) in
  180. List.iter (fun path ->
  181. let dir = path ^ String.concat "/" p in
  182. let r = (try Sys.readdir dir with _ -> [||]) in
  183. Array.iter (fun f ->
  184. if (try (Unix.stat (dir ^ "/" ^ f)).Unix.st_kind = Unix.S_DIR with _ -> false) then begin
  185. if f.[0] >= 'a' && f.[0] <= 'z' then begin
  186. if p = ["."] then
  187. match read_type_path com [f] with
  188. | [] , [] -> ()
  189. | _ ->
  190. try
  191. match PMap.find f com.package_rules with
  192. | Forbidden -> ()
  193. | Remap f -> packages := f :: !packages
  194. | Directory _ -> raise Not_found
  195. with Not_found ->
  196. packages := f :: !packages
  197. else
  198. packages := f :: !packages
  199. end;
  200. end else if file_extension f = "hx" then begin
  201. let c = Filename.chop_extension f in
  202. if String.length c < 2 || String.sub c (String.length c - 2) 2 <> "__" then classes := c :: !classes;
  203. end;
  204. ) r;
  205. ) com.class_path;
  206. List.iter (fun (_,_,extract) ->
  207. Hashtbl.iter (fun (path,name) _ ->
  208. if path = p then classes := name :: !classes else
  209. let rec loop p1 p2 =
  210. match p1, p2 with
  211. | [], _ -> ()
  212. | x :: _, [] -> packages := x :: !packages
  213. | a :: p1, b :: p2 -> if a = b then loop p1 p2
  214. in
  215. loop path p
  216. ) (extract());
  217. ) com.swf_libs;
  218. List.iter (fun (path,std,close,all_files,lookup) ->
  219. List.iter (fun (path, name) ->
  220. if path = p then classes := name :: !classes else
  221. let rec loop p1 p2 =
  222. match p1, p2 with
  223. | [], _ -> ()
  224. | x :: _, [] -> packages := x :: !packages
  225. | a :: p1, b :: p2 -> if a = b then loop p1 p2
  226. in
  227. loop path p
  228. ) (all_files())
  229. ) com.java_libs;
  230. unique !packages, unique !classes
  231. let delete_file f = try Sys.remove f with _ -> ()
  232. let expand_env ?(h=None) path =
  233. let r = Str.regexp "%\\([A-Za-z0-9_]+\\)%" in
  234. Str.global_substitute r (fun s ->
  235. let key = Str.matched_group 1 s in
  236. try
  237. Sys.getenv key
  238. with Not_found -> try
  239. match h with
  240. | None -> raise Not_found
  241. | Some h -> Hashtbl.find h key
  242. with Not_found ->
  243. "%" ^ key ^ "%"
  244. ) path
  245. let unquote v =
  246. let len = String.length v in
  247. if len > 0 && v.[0] = '"' && v.[len - 1] = '"' then String.sub v 1 (len - 2) else v
  248. let parse_hxml_data data =
  249. let lines = Str.split (Str.regexp "[\r\n]+") data in
  250. List.concat (List.map (fun l ->
  251. let l = unquote (ExtString.String.strip l) in
  252. if l = "" || l.[0] = '#' then
  253. []
  254. else if l.[0] = '-' then
  255. try
  256. let a, b = ExtString.String.split l " " in
  257. [unquote a; unquote (ExtString.String.strip b)]
  258. with
  259. _ -> [l]
  260. else
  261. [l]
  262. ) lines)
  263. let parse_hxml file =
  264. let ch = IO.input_channel (try open_in_bin file with _ -> failwith ("File not found " ^ file)) in
  265. let data = IO.read_all ch in
  266. IO.close_in ch;
  267. parse_hxml_data data
  268. let lookup_classes com spath =
  269. let rec loop = function
  270. | [] -> []
  271. | cp :: l ->
  272. let cp = (if cp = "" then "./" else cp) in
  273. let c = normalize_path (Extc.get_real_path (Common.unique_full_path cp)) in
  274. let clen = String.length c in
  275. if clen < String.length spath && String.sub spath 0 clen = c then begin
  276. let path = String.sub spath clen (String.length spath - clen) in
  277. (try
  278. let path = make_path path in
  279. (match loop l with
  280. | [x] when String.length (Ast.s_type_path x) < String.length (Ast.s_type_path path) -> [x]
  281. | _ -> [path])
  282. with _ -> loop l)
  283. end else
  284. loop l
  285. in
  286. loop com.class_path
  287. let add_libs com libs =
  288. let call_haxelib() =
  289. let t = Common.timer "haxelib" in
  290. let cmd = "haxelib path " ^ String.concat " " libs in
  291. let pin, pout, perr = Unix.open_process_full cmd (Unix.environment()) in
  292. let lines = Std.input_list pin in
  293. let err = Std.input_list perr in
  294. let ret = Unix.close_process_full (pin,pout,perr) in
  295. if ret <> Unix.WEXITED 0 then failwith (match lines, err with
  296. | [], [] -> "Failed to call haxelib (command not found ?)"
  297. | [], [s] when ExtString.String.ends_with (ExtString.String.strip s) "Module not found : path" -> "The haxelib command has been strip'ed, please install it again"
  298. | _ -> String.concat "\n" (lines@err));
  299. t();
  300. lines
  301. in
  302. match libs with
  303. | [] -> []
  304. | _ ->
  305. let lines = match !global_cache with
  306. | Some cache ->
  307. (try
  308. (* if we are compiling, really call haxelib since library path might have changed *)
  309. if not com.display then raise Not_found;
  310. Hashtbl.find cache.c_haxelib libs
  311. with Not_found ->
  312. let lines = call_haxelib() in
  313. Hashtbl.replace cache.c_haxelib libs lines;
  314. lines)
  315. | _ -> call_haxelib()
  316. in
  317. let extra_args = ref [] in
  318. let lines = List.fold_left (fun acc l ->
  319. let l = ExtString.String.strip l in
  320. if l = "" then acc else
  321. if l.[0] <> '-' then l :: acc else
  322. match (try ExtString.String.split l " " with _ -> l, "") with
  323. | ("-L",dir) ->
  324. com.neko_libs <- String.sub l 3 (String.length l - 3) :: com.neko_libs;
  325. acc
  326. | param, value ->
  327. extra_args := param :: !extra_args;
  328. if value <> "" then extra_args := value :: !extra_args;
  329. acc
  330. ) [] lines in
  331. com.class_path <- lines @ com.class_path;
  332. List.rev !extra_args
  333. let run_command ctx cmd =
  334. let h = Hashtbl.create 0 in
  335. Hashtbl.add h "__file__" ctx.com.file;
  336. Hashtbl.add h "__platform__" (platform_name ctx.com.platform);
  337. let t = Common.timer "command" in
  338. let cmd = expand_env ~h:(Some h) cmd in
  339. let len = String.length cmd in
  340. if len > 3 && String.sub cmd 0 3 = "cd " then begin
  341. Sys.chdir (String.sub cmd 3 (len - 3));
  342. 0
  343. end else
  344. let binary_string s =
  345. if Sys.os_type <> "Win32" && Sys.os_type <> "Cygwin" then s else String.concat "\n" (Str.split (Str.regexp "\r\n") s)
  346. in
  347. let pout, pin, perr = Unix.open_process_full cmd (Unix.environment()) in
  348. let iout = Unix.descr_of_in_channel pout in
  349. let ierr = Unix.descr_of_in_channel perr in
  350. let berr = Buffer.create 0 in
  351. let bout = Buffer.create 0 in
  352. let tmp = String.create 1024 in
  353. let result = ref None in
  354. (*
  355. we need to read available content on process out/err if we want to prevent
  356. the process from blocking when the pipe is full
  357. *)
  358. let is_process_running() =
  359. let pid, r = Unix.waitpid [Unix.WNOHANG] (-1) in
  360. if pid = 0 then
  361. true
  362. else begin
  363. result := Some r;
  364. false;
  365. end
  366. in
  367. let rec loop ins =
  368. let (ch,_,_), timeout = (try Unix.select ins [] [] 0.02, true with _ -> ([],[],[]),false) in
  369. match ch with
  370. | [] ->
  371. (* make sure we read all *)
  372. if timeout && is_process_running() then
  373. loop ins
  374. else begin
  375. Buffer.add_string berr (IO.read_all (IO.input_channel perr));
  376. Buffer.add_string bout (IO.read_all (IO.input_channel pout));
  377. end
  378. | s :: _ ->
  379. let n = Unix.read s tmp 0 (String.length tmp) in
  380. if s == iout && n > 0 then
  381. ctx.com.print (String.sub tmp 0 n)
  382. else
  383. Buffer.add_substring (if s == iout then bout else berr) tmp 0 n;
  384. loop (if n = 0 then List.filter ((!=) s) ins else ins)
  385. in
  386. (try loop [iout;ierr] with Unix.Unix_error _ -> ());
  387. let serr = binary_string (Buffer.contents berr) in
  388. let sout = binary_string (Buffer.contents bout) in
  389. if serr <> "" then ctx.messages <- (if serr.[String.length serr - 1] = '\n' then String.sub serr 0 (String.length serr - 1) else serr) :: ctx.messages;
  390. if sout <> "" then ctx.com.print sout;
  391. let r = (match (try Unix.close_process_full (pout,pin,perr) with Unix.Unix_error (Unix.ECHILD,_,_) -> (match !result with None -> assert false | Some r -> r)) with
  392. | Unix.WEXITED e -> e
  393. | Unix.WSIGNALED s | Unix.WSTOPPED s -> if s = 0 then -1 else s
  394. ) in
  395. t();
  396. r
  397. let default_flush ctx =
  398. List.iter prerr_endline (List.rev ctx.messages);
  399. if ctx.has_error && !prompt then begin
  400. print_endline "Press enter to exit...";
  401. ignore(read_line());
  402. end;
  403. if ctx.has_error then exit 1
  404. let create_context params =
  405. let ctx = {
  406. com = Common.create version params;
  407. flush = (fun()->());
  408. setup = (fun()->());
  409. messages = [];
  410. has_next = false;
  411. has_error = false;
  412. } in
  413. ctx.flush <- (fun() -> default_flush ctx);
  414. ctx
  415. let rec process_params create pl =
  416. let each_params = ref [] in
  417. let rec loop acc = function
  418. | [] ->
  419. let ctx = create (!each_params @ (List.rev acc)) in
  420. init ctx;
  421. ctx.flush()
  422. | "--next" :: l when acc = [] -> (* skip empty --next *)
  423. loop [] l
  424. | "--next" :: l ->
  425. let ctx = create (!each_params @ (List.rev acc)) in
  426. ctx.has_next <- true;
  427. init ctx;
  428. ctx.flush();
  429. loop [] l
  430. | "--each" :: l ->
  431. each_params := List.rev acc;
  432. loop [] l
  433. | "--cwd" :: dir :: l ->
  434. (* we need to change it immediately since it will affect hxml loading *)
  435. (try Unix.chdir dir with _ -> ());
  436. loop (dir :: "--cwd" :: acc) l
  437. | "--connect" :: hp :: l ->
  438. (match !global_cache with
  439. | None ->
  440. let host, port = (try ExtString.String.split hp ":" with _ -> "127.0.0.1", hp) in
  441. do_connect host (try int_of_string port with _ -> raise (Arg.Bad "Invalid port")) ((List.rev acc) @ l)
  442. | Some _ ->
  443. (* already connected : skip *)
  444. loop acc l)
  445. | "--run" :: cl :: args ->
  446. let acc = (cl ^ ".main()") :: "--macro" :: acc in
  447. let ctx = create (!each_params @ (List.rev acc)) in
  448. ctx.com.sys_args <- args;
  449. init ctx;
  450. ctx.flush()
  451. | arg :: l ->
  452. match List.rev (ExtString.String.nsplit arg ".") with
  453. | "hxml" :: _ when (match acc with "-cmd" :: _ -> false | _ -> true) -> loop acc (parse_hxml arg @ l)
  454. | _ -> loop (arg :: acc) l
  455. in
  456. (* put --display in front if it was last parameter *)
  457. let pl = (match List.rev pl with
  458. | file :: "--display" :: pl -> "--display" :: file :: List.rev pl
  459. | "use_rtti_doc" :: "-D" :: file :: "--display" :: pl -> "--display" :: file :: List.rev pl
  460. | _ -> pl
  461. ) in
  462. loop [] pl
  463. and wait_loop boot_com host port =
  464. let sock = Unix.socket Unix.PF_INET Unix.SOCK_STREAM 0 in
  465. (try Unix.bind sock (Unix.ADDR_INET (Unix.inet_addr_of_string host,port)) with _ -> failwith ("Couldn't wait on " ^ host ^ ":" ^ string_of_int port));
  466. Unix.listen sock 10;
  467. Sys.catch_break false;
  468. let verbose = boot_com.verbose in
  469. let has_parse_error = ref false in
  470. if verbose then print_endline ("Waiting on " ^ host ^ ":" ^ string_of_int port);
  471. let bufsize = 1024 in
  472. let tmp = String.create bufsize in
  473. let cache = {
  474. c_haxelib = Hashtbl.create 0;
  475. c_files = Hashtbl.create 0;
  476. c_modules = Hashtbl.create 0;
  477. } in
  478. global_cache := Some cache;
  479. Typer.macro_enable_cache := true;
  480. Typeload.parse_hook := (fun com2 file p ->
  481. let sign = get_signature com2 in
  482. let ffile = Common.unique_full_path file in
  483. let ftime = file_time ffile in
  484. let fkey = ffile ^ "!" ^ sign in
  485. try
  486. let time, data = Hashtbl.find cache.c_files fkey in
  487. if time <> ftime then raise Not_found;
  488. data
  489. with Not_found ->
  490. has_parse_error := false;
  491. let data = Typeload.parse_file com2 file p in
  492. if verbose then print_endline ("Parsed " ^ ffile);
  493. if not !has_parse_error && ffile <> (!Parser.resume_display).Ast.pfile then Hashtbl.replace cache.c_files fkey (ftime,data);
  494. data
  495. );
  496. let cache_module m =
  497. Hashtbl.replace cache.c_modules (m.m_path,m.m_extra.m_sign) m;
  498. in
  499. let check_module_path com m p =
  500. m.m_extra.m_file = Common.unique_full_path (Typeload.resolve_module_file com m.m_path (ref[]) p)
  501. in
  502. let compilation_step = ref 0 in
  503. let compilation_mark = ref 0 in
  504. let mark_loop = ref 0 in
  505. Typeload.type_module_hook := (fun (ctx:Typecore.typer) mpath p ->
  506. let t = Common.timer "module cache check" in
  507. let com2 = ctx.Typecore.com in
  508. let sign = get_signature com2 in
  509. let dep = ref None in
  510. incr mark_loop;
  511. let mark = !mark_loop in
  512. let start_mark = !compilation_mark in
  513. let rec check m =
  514. if m.m_extra.m_dirty then begin
  515. dep := Some m;
  516. false
  517. end else if m.m_extra.m_mark = mark then
  518. true
  519. else try
  520. if m.m_extra.m_mark <= start_mark then begin
  521. (match m.m_extra.m_kind with
  522. | MFake -> () (* don't get classpath *)
  523. | MCode -> if not (check_module_path com2 m p) then raise Not_found;
  524. | MMacro when ctx.Typecore.in_macro -> if not (check_module_path com2 m p) then raise Not_found;
  525. | MMacro ->
  526. let _, mctx = Typer.get_macro_context ctx p in
  527. if not (check_module_path mctx.Typecore.com m p) then raise Not_found;
  528. );
  529. if file_time m.m_extra.m_file <> m.m_extra.m_time then begin
  530. if m.m_extra.m_kind = MFake then Hashtbl.remove Typecore.fake_modules m.m_extra.m_file;
  531. raise Not_found;
  532. end;
  533. end;
  534. m.m_extra.m_mark <- mark;
  535. PMap.iter (fun _ m2 -> if not (check m2) then begin dep := Some m2; raise Not_found end) m.m_extra.m_deps;
  536. true
  537. with Not_found ->
  538. m.m_extra.m_dirty <- true;
  539. false
  540. in
  541. let rec add_modules m0 m =
  542. if m.m_extra.m_added < !compilation_step then begin
  543. (match m0.m_extra.m_kind, m.m_extra.m_kind with
  544. | MCode, MMacro | MMacro, MCode ->
  545. (* this was just a dependency to check : do not add to the context *)
  546. ()
  547. | _ ->
  548. if verbose then print_endline ("Reusing cached module " ^ Ast.s_type_path m.m_path);
  549. m.m_extra.m_added <- !compilation_step;
  550. List.iter (fun t ->
  551. match t with
  552. | TClassDecl c -> c.cl_restore()
  553. | TEnumDecl e ->
  554. let rec loop acc = function
  555. | [] -> ()
  556. | (Ast.Meta.RealPath,[Ast.EConst (Ast.String path),_],_) :: l ->
  557. e.e_path <- Ast.parse_path path;
  558. e.e_meta <- (List.rev acc) @ l;
  559. | x :: l -> loop (x::acc) l
  560. in
  561. loop [] e.e_meta
  562. | TAbstractDecl a ->
  563. a.a_meta <- List.filter (fun (m,_,_) -> m <> Ast.Meta.ValueUsed) a.a_meta
  564. | _ -> ()
  565. ) m.m_types;
  566. Typeload.add_module ctx m p;
  567. PMap.iter (Hashtbl.add com2.resources) m.m_extra.m_binded_res;
  568. PMap.iter (fun _ m2 -> add_modules m0 m2) m.m_extra.m_deps);
  569. List.iter (Typer.call_init_macro ctx) m.m_extra.m_macro_calls
  570. end
  571. in
  572. try
  573. let m = Hashtbl.find cache.c_modules (mpath,sign) in
  574. if not (check m) then begin
  575. if verbose then print_endline ("Skipping cached module " ^ Ast.s_type_path mpath ^ (match !dep with None -> "" | Some m -> "(" ^ Ast.s_type_path m.m_path ^ ")"));
  576. raise Not_found;
  577. end;
  578. add_modules m m;
  579. t();
  580. Some m
  581. with Not_found ->
  582. t();
  583. None
  584. );
  585. let run_count = ref 0 in
  586. while true do
  587. let sin, _ = Unix.accept sock in
  588. let t0 = get_time() in
  589. Unix.set_nonblock sin;
  590. if verbose then print_endline "Client connected";
  591. let b = Buffer.create 0 in
  592. let rec read_loop count =
  593. let r = try
  594. Unix.recv sin tmp 0 bufsize []
  595. with Unix.Unix_error((Unix.EWOULDBLOCK|Unix.EAGAIN),_,_) ->
  596. 0
  597. in
  598. if verbose then begin
  599. if r > 0 then Printf.printf "Reading %d bytes\n" r else print_endline "Waiting for data...";
  600. end;
  601. Buffer.add_substring b tmp 0 r;
  602. if r > 0 && tmp.[r-1] = '\000' then
  603. Buffer.sub b 0 (Buffer.length b - 1)
  604. else begin
  605. if r = 0 then ignore(Unix.select [] [] [] 0.05); (* wait a bit *)
  606. if count = 100 then
  607. failwith "Aborting unactive connection"
  608. else
  609. read_loop (count + 1);
  610. end;
  611. in
  612. let rec cache_context com =
  613. if not com.display then begin
  614. List.iter cache_module com.modules;
  615. if verbose then print_endline ("Cached " ^ string_of_int (List.length com.modules) ^ " modules");
  616. end;
  617. match com.get_macros() with
  618. | None -> ()
  619. | Some com -> cache_context com
  620. in
  621. let create params =
  622. let ctx = create_context params in
  623. ctx.flush <- (fun() ->
  624. incr compilation_step;
  625. compilation_mark := !mark_loop;
  626. List.iter (fun s -> ssend sin (s ^ "\n"); if verbose then print_endline ("> " ^ s)) (List.rev ctx.messages);
  627. if ctx.has_error then ssend sin "\x02\n" else cache_context ctx.com;
  628. );
  629. ctx.setup <- (fun() ->
  630. Parser.display_error := (fun e p -> has_parse_error := true; ctx.com.error (Parser.error_msg e) p);
  631. if ctx.com.display then begin
  632. let file = (!Parser.resume_display).Ast.pfile in
  633. let fkey = file ^ "!" ^ get_signature ctx.com in
  634. (* force parsing again : if the completion point have been changed *)
  635. Hashtbl.remove cache.c_files fkey;
  636. (* force module reloading (if cached) *)
  637. Hashtbl.iter (fun _ m -> if m.m_extra.m_file = file then m.m_extra.m_dirty <- true) cache.c_modules
  638. end
  639. );
  640. ctx.com.print <- (fun str -> ssend sin ("\x01" ^ String.concat "\x01" (ExtString.String.nsplit str "\n") ^ "\n"));
  641. ctx
  642. in
  643. (try
  644. let data = parse_hxml_data (read_loop 0) in
  645. Unix.clear_nonblock sin;
  646. if verbose then print_endline ("Processing Arguments [" ^ String.concat "," data ^ "]");
  647. (try
  648. Common.display_default := false;
  649. Parser.resume_display := Ast.null_pos;
  650. Typeload.return_partial_type := false;
  651. measure_times := false;
  652. close_times();
  653. stats.s_files_parsed := 0;
  654. stats.s_classes_built := 0;
  655. stats.s_methods_typed := 0;
  656. stats.s_macros_called := 0;
  657. Hashtbl.clear Common.htimers;
  658. let _ = Common.timer "other" in
  659. incr compilation_step;
  660. compilation_mark := !mark_loop;
  661. start_time := get_time();
  662. process_params create data;
  663. close_times();
  664. if !measure_times then report_times (fun s -> ssend sin (s ^ "\n"))
  665. with Completion str ->
  666. if verbose then print_endline ("Completion Response =\n" ^ str);
  667. ssend sin str
  668. );
  669. if verbose then begin
  670. print_endline (Printf.sprintf "Stats = %d files, %d classes, %d methods, %d macros" !(stats.s_files_parsed) !(stats.s_classes_built) !(stats.s_methods_typed) !(stats.s_macros_called));
  671. print_endline (Printf.sprintf "Time spent : %.3fs" (get_time() -. t0));
  672. end
  673. with Unix.Unix_error _ ->
  674. if verbose then print_endline "Connection Aborted"
  675. | e ->
  676. let estr = Printexc.to_string e in
  677. if verbose then print_endline ("Uncaught Error : " ^ estr);
  678. (try ssend sin estr with _ -> ());
  679. );
  680. Unix.close sin;
  681. (* prevent too much fragmentation by doing some compactions every X run *)
  682. incr run_count;
  683. if !run_count mod 1 = 50 then begin
  684. let t0 = get_time() in
  685. Gc.compact();
  686. if verbose then begin
  687. let stat = Gc.quick_stat() in
  688. let size = (float_of_int stat.Gc.heap_words) *. 4. in
  689. print_endline (Printf.sprintf "Compacted memory %.3fs %.1fMB" (get_time() -. t0) (size /. (1024. *. 1024.)));
  690. end
  691. end else Gc.minor();
  692. done
  693. and do_connect host port args =
  694. let sock = Unix.socket Unix.PF_INET Unix.SOCK_STREAM 0 in
  695. (try Unix.connect sock (Unix.ADDR_INET (Unix.inet_addr_of_string host,port)) with _ -> failwith ("Couldn't connect on " ^ host ^ ":" ^ string_of_int port));
  696. let args = ("--cwd " ^ Unix.getcwd()) :: args in
  697. ssend sock (String.concat "" (List.map (fun a -> a ^ "\n") args) ^ "\000");
  698. let has_error = ref false in
  699. let rec print line =
  700. match (if line = "" then '\x00' else line.[0]) with
  701. | '\x01' ->
  702. print_string (String.concat "\n" (List.tl (ExtString.String.nsplit line "\x01")));
  703. flush stdout
  704. | '\x02' ->
  705. has_error := true;
  706. | _ ->
  707. prerr_endline line;
  708. in
  709. let buf = Buffer.create 0 in
  710. let process() =
  711. let lines = ExtString.String.nsplit (Buffer.contents buf) "\n" in
  712. (* the last line ends with \n *)
  713. let lines = (match List.rev lines with "" :: l -> List.rev l | _ -> lines) in
  714. List.iter print lines;
  715. in
  716. let tmp = String.create 1024 in
  717. let rec loop() =
  718. let b = Unix.recv sock tmp 0 1024 [] in
  719. Buffer.add_substring buf tmp 0 b;
  720. if b > 0 then begin
  721. if String.get tmp (b - 1) = '\n' then begin
  722. process();
  723. Buffer.reset buf;
  724. end;
  725. loop();
  726. end
  727. in
  728. loop();
  729. process();
  730. if !has_error then exit 1
  731. and init ctx =
  732. let usage = Printf.sprintf
  733. "Haxe Compiler %d.%d.%d - (C)2005-2013 Haxe Foundation\n Usage : haxe%s -main <class> [-swf|-js|-neko|-php|-cpp|-as3] <output> [options]\n Options :"
  734. (version / 100) ((version mod 100)/10) (version mod 10) (if Sys.os_type = "Win32" then ".exe" else "")
  735. in
  736. let com = ctx.com in
  737. let classes = ref [([],"Std")] in
  738. try
  739. let xml_out = ref None in
  740. let swf_header = ref None in
  741. let cmds = ref [] in
  742. let config_macros = ref [] in
  743. let cp_libs = ref [] in
  744. let added_libs = Hashtbl.create 0 in
  745. let gen_as3 = ref false in
  746. let no_output = ref false in
  747. let did_something = ref false in
  748. let force_typing = ref false in
  749. let pre_compilation = ref [] in
  750. let interp = ref false in
  751. Common.define_value com Define.HaxeVer (string_of_float (float_of_int version /. 100.));
  752. Common.raw_define com (if ((version / 10) land 1 == 0) then "haxe_release" else "haxe_svn");
  753. Common.raw_define com "haxe3";
  754. Common.define_value com Define.Dce "std";
  755. com.warning <- (fun msg p -> message ctx ("Warning : " ^ msg) p);
  756. com.error <- error ctx;
  757. if !global_cache <> None then com.run_command <- run_command ctx;
  758. Parser.display_error := (fun e p -> com.error (Parser.error_msg e) p);
  759. Parser.use_doc := !Common.display_default || (!global_cache <> None);
  760. (try
  761. let p = Sys.getenv "HAXE_STD_PATH" in
  762. let rec loop = function
  763. | drive :: path :: l ->
  764. if String.length drive = 1 && ((drive.[0] >= 'a' && drive.[0] <= 'z') || (drive.[0] >= 'A' && drive.[0] <= 'Z')) then
  765. (drive ^ ":" ^ path) :: loop l
  766. else
  767. drive :: loop (path :: l)
  768. | l ->
  769. l
  770. in
  771. let parts = "" :: Str.split_delim (Str.regexp "[;:]") p in
  772. com.class_path <- List.map normalize_path (loop parts)
  773. with
  774. Not_found ->
  775. if Sys.os_type = "Unix" then
  776. com.class_path <- ["/usr/lib/haxe/std/";"/usr/local/lib/haxe/std/";"/usr/lib/haxe/extraLibs/";"/usr/local/lib/haxe/extraLibs/";"";"/"]
  777. else
  778. let base_path = normalize_path (Extc.get_real_path (try executable_path() with _ -> "./")) in
  779. com.class_path <- [base_path ^ "std/";base_path ^ "extraLibs/";""]);
  780. com.std_path <- List.filter (fun p -> ExtString.String.ends_with p "std/" || ExtString.String.ends_with p "std\\") com.class_path;
  781. let set_platform pf file =
  782. if com.platform <> Cross then failwith "Multiple targets";
  783. Common.init_platform com pf;
  784. com.file <- file;
  785. if (pf = Flash8 || pf = Flash) && file_extension file = "swc" then Common.define com Define.Swc;
  786. in
  787. let define f = Arg.Unit (fun () -> Common.define com f) in
  788. let process_ref = ref (fun args -> ()) in
  789. let process_libs() =
  790. let libs = List.filter (fun l -> not (Hashtbl.mem added_libs l)) (List.rev !cp_libs) in
  791. cp_libs := [];
  792. List.iter (fun l -> Hashtbl.add added_libs l ()) libs;
  793. (* immediately process the arguments to insert them at the place -lib was defined *)
  794. match add_libs com libs with
  795. | [] -> ()
  796. | args -> (!process_ref) args
  797. in
  798. let basic_args_spec = [
  799. ("-cp",Arg.String (fun path ->
  800. process_libs();
  801. com.class_path <- normalize_path path :: com.class_path
  802. ),"<path> : add a directory to find source files");
  803. ("-js",Arg.String (set_platform Js),"<file> : compile code to JavaScript file");
  804. ("-swf",Arg.String (set_platform Flash),"<file> : compile code to Flash SWF file");
  805. ("-as3",Arg.String (fun dir ->
  806. set_platform Flash dir;
  807. gen_as3 := true;
  808. Common.define com Define.As3;
  809. Common.define com Define.NoInline;
  810. ),"<directory> : generate AS3 code into target directory");
  811. ("-neko",Arg.String (set_platform Neko),"<file> : compile code to Neko Binary");
  812. ("-php",Arg.String (fun dir ->
  813. classes := (["php"],"Boot") :: !classes;
  814. set_platform Php dir;
  815. ),"<directory> : generate PHP code into target directory");
  816. ("-cpp",Arg.String (fun dir ->
  817. set_platform Cpp dir;
  818. ),"<directory> : generate C++ code into target directory");
  819. ("-cs",Arg.String (fun dir ->
  820. set_platform Cs dir;
  821. ),"<directory> : generate C# code into target directory");
  822. ("-java",Arg.String (fun dir ->
  823. cp_libs := "hxjava" :: !cp_libs;
  824. set_platform Java dir;
  825. ),"<directory> : generate Java code into target directory");
  826. ("-xml",Arg.String (fun file ->
  827. Parser.use_doc := true;
  828. xml_out := Some file
  829. ),"<file> : generate XML types description");
  830. ("-main",Arg.String (fun cl ->
  831. if com.main_class <> None then raise (Arg.Bad "Multiple -main");
  832. let cpath = make_path cl in
  833. com.main_class <- Some cpath;
  834. classes := cpath :: !classes
  835. ),"<class> : select startup class");
  836. ("-lib",Arg.String (fun l ->
  837. cp_libs := l :: !cp_libs;
  838. Common.raw_define com l;
  839. ),"<library[:version]> : use a haxelib library");
  840. ("-D",Arg.String (fun var ->
  841. if var = fst (Define.infos Define.UseRttiDoc) then Parser.use_doc := true;
  842. if var = fst (Define.infos Define.NoOpt) then com.foptimize <- false;
  843. if List.mem var reserved_flags then raise (Arg.Bad (var ^ " is a reserved compiler flag and cannot be defined from command line"));
  844. Common.raw_define com var
  845. ),"<var> : define a conditional compilation flag");
  846. ("-v",Arg.Unit (fun () ->
  847. com.verbose <- true
  848. ),": turn on verbose mode");
  849. ("-debug", Arg.Unit (fun() ->
  850. Common.define com Define.Debug;
  851. com.debug <- true;
  852. ), ": add debug information to the compiled code");
  853. ] in
  854. let adv_args_spec = [
  855. ("-dce", Arg.String (fun mode ->
  856. (match mode with
  857. | "std" | "full" | "no" -> ()
  858. | _ -> raise (Arg.Bad "Invalid DCE mode, expected std | full | no"));
  859. Common.define_value com Define.Dce mode
  860. ),"[std|full|no] : set the dead code elimination mode");
  861. ("-swf-version",Arg.Float (fun v ->
  862. com.flash_version <- v;
  863. ),"<version> : change the SWF version (6 to 10)");
  864. ("-swf-header",Arg.String (fun h ->
  865. try
  866. swf_header := Some (match ExtString.String.nsplit h ":" with
  867. | [width; height; fps] ->
  868. (int_of_string width,int_of_string height,float_of_string fps,0xFFFFFF)
  869. | [width; height; fps; color] ->
  870. let color = if ExtString.String.starts_with color "0x" then color else "0x" ^ color in
  871. (int_of_string width, int_of_string height, float_of_string fps, int_of_string color)
  872. | _ -> raise Exit)
  873. with
  874. _ -> raise (Arg.Bad "Invalid SWF header format, expected width:height:fps[:color]")
  875. ),"<header> : define SWF header (width:height:fps:color)");
  876. ("-swf-lib",Arg.String (fun file ->
  877. process_libs(); (* linked swf order matters, and lib might reference swf as well *)
  878. Genswf.add_swf_lib com file false
  879. ),"<file> : add the SWF library to the compiled SWF");
  880. ("-swf-lib-extern",Arg.String (fun file ->
  881. Genswf.add_swf_lib com file true
  882. ),"<file> : use the SWF library for type checking");
  883. ("-java-lib",Arg.String (fun file ->
  884. Genjava.add_java_lib com file false
  885. ),"<file> : add an external JAR or class directory library");
  886. ("-x", Arg.String (fun file ->
  887. let neko_file = file ^ ".n" in
  888. set_platform Neko neko_file;
  889. if com.main_class = None then begin
  890. let cpath = make_path file in
  891. com.main_class <- Some cpath;
  892. classes := cpath :: !classes
  893. end;
  894. cmds := ("neko " ^ neko_file) :: !cmds;
  895. ),"<file> : shortcut for compiling and executing a neko file");
  896. ("-resource",Arg.String (fun res ->
  897. let file, name = (match ExtString.String.nsplit res "@" with
  898. | [file; name] -> file, name
  899. | [file] -> file, file
  900. | _ -> raise (Arg.Bad "Invalid Resource format, expected file@name")
  901. ) in
  902. let file = (try Common.find_file com file with Not_found -> file) in
  903. let data = (try
  904. let s = Std.input_file ~bin:true file in
  905. if String.length s > 12000000 then raise Exit;
  906. s;
  907. with
  908. | Sys_error _ -> failwith ("Resource file not found : " ^ file)
  909. | _ -> failwith ("Resource '" ^ file ^ "' excess the maximum size of 12MB")
  910. ) in
  911. if Hashtbl.mem com.resources name then failwith ("Duplicate resource name " ^ name);
  912. Hashtbl.add com.resources name data
  913. ),"<file>[@name] : add a named resource file");
  914. ("-prompt", Arg.Unit (fun() -> prompt := true),": prompt on error");
  915. ("-cmd", Arg.String (fun cmd ->
  916. cmds := unquote cmd :: !cmds
  917. ),": run the specified command after successful compilation");
  918. ("--flash-strict", define Define.FlashStrict, ": more type strict flash API");
  919. ("--no-traces", define Define.NoTraces, ": don't compile trace calls in the program");
  920. ("--gen-hx-classes", Arg.Unit (fun() ->
  921. force_typing := true;
  922. pre_compilation := (fun() ->
  923. List.iter (fun (_,_,extract) ->
  924. Hashtbl.iter (fun n _ -> classes := n :: !classes) (extract())
  925. ) com.swf_libs;
  926. ) :: !pre_compilation;
  927. xml_out := Some "hx"
  928. ),": generate hx headers for all input classes");
  929. ("--next", Arg.Unit (fun() -> assert false), ": separate several haxe compilations");
  930. ("--display", Arg.String (fun file_pos ->
  931. match file_pos with
  932. | "classes" ->
  933. pre_compilation := (fun() -> raise (Parser.TypePath (["."],None))) :: !pre_compilation;
  934. | "keywords" ->
  935. complete_fields (Hashtbl.fold (fun k _ acc -> (k,"","") :: acc) Lexer.keywords [])
  936. | _ ->
  937. let file, pos = try ExtString.String.split file_pos "@" with _ -> failwith ("Invalid format : " ^ file_pos) in
  938. let file = unquote file in
  939. let pos = try int_of_string pos with _ -> failwith ("Invalid format : " ^ pos) in
  940. com.display <- true;
  941. Common.display_default := true;
  942. Common.define com Define.Display;
  943. Parser.use_doc := true;
  944. Parser.resume_display := {
  945. Ast.pfile = Common.unique_full_path file;
  946. Ast.pmin = pos;
  947. Ast.pmax = pos;
  948. };
  949. ),": display code tips");
  950. ("--no-output", Arg.Unit (fun() -> no_output := true),": compiles but does not generate any file");
  951. ("--times", Arg.Unit (fun() -> measure_times := true),": measure compilation times");
  952. ("--no-inline", define Define.NoInline, ": disable inlining");
  953. ("--no-opt", Arg.Unit (fun() ->
  954. com.foptimize <- false;
  955. Common.define com Define.NoOpt;
  956. ), ": disable code optimizations");
  957. ("--php-front",Arg.String (fun f ->
  958. if com.php_front <> None then raise (Arg.Bad "Multiple --php-front");
  959. com.php_front <- Some f;
  960. ),"<filename> : select the name for the php front file");
  961. ("--php-lib",Arg.String (fun f ->
  962. if com.php_lib <> None then raise (Arg.Bad "Multiple --php-lib");
  963. com.php_lib <- Some f;
  964. ),"<filename> : select the name for the php lib folder");
  965. ("--php-prefix", Arg.String (fun f ->
  966. if com.php_prefix <> None then raise (Arg.Bad "Multiple --php-prefix");
  967. com.php_prefix <- Some f;
  968. Common.define com Define.PhpPrefix;
  969. ),"<name> : prefix all classes with given name");
  970. ("--remap", Arg.String (fun s ->
  971. let pack, target = (try ExtString.String.split s ":" with _ -> raise (Arg.Bad "Invalid remap format, expected source:target")) in
  972. com.package_rules <- PMap.add pack (Remap target) com.package_rules;
  973. ),"<package:target> : remap a package to another one");
  974. ("--interp", Arg.Unit (fun() ->
  975. Common.define com Define.Interp;
  976. set_platform Neko "";
  977. no_output := true;
  978. interp := true;
  979. ),": interpret the program using internal macro system");
  980. ("--macro", Arg.String (fun e ->
  981. force_typing := true;
  982. config_macros := e :: !config_macros
  983. )," : call the given macro before typing anything else");
  984. ("--wait", Arg.String (fun hp ->
  985. let host, port = (try ExtString.String.split hp ":" with _ -> "127.0.0.1", hp) in
  986. wait_loop com host (try int_of_string port with _ -> raise (Arg.Bad "Invalid port"))
  987. ),"<[host:]port> : wait on the given port for commands to run)");
  988. ("--connect",Arg.String (fun _ ->
  989. assert false
  990. ),"<[host:]port> : connect on the given port and run commands there)");
  991. ("--cwd", Arg.String (fun dir ->
  992. (try Unix.chdir dir with _ -> raise (Arg.Bad "Invalid directory"))
  993. ),"<dir> : set current working directory");
  994. ("-version",Arg.Unit (fun() ->
  995. message ctx (Printf.sprintf "%d.%d.%d" (version / 100) ((version mod 100)/10) (version mod 10)) Ast.null_pos;
  996. did_something := true;
  997. ),": print version and exit");
  998. ("--help-defines", Arg.Unit (fun() ->
  999. let rec loop i =
  1000. let d = Obj.magic i in
  1001. if d <> Define.Last then begin
  1002. let t, doc = Define.infos d in
  1003. let str = String.concat "-" (ExtString.String.nsplit t "_") ^ " : " ^ doc in
  1004. str :: loop (i + 1)
  1005. end else
  1006. []
  1007. in
  1008. let all = List.sort String.compare (loop 0) in
  1009. List.iter (fun msg -> ctx.com.print (msg ^ "\n")) all;
  1010. did_something := true
  1011. ),": print help for all compiler specific defines");
  1012. ("--help-metas", Arg.Unit (fun() ->
  1013. let rec loop i =
  1014. let d = Obj.magic i in
  1015. if d <> Meta.Last then begin
  1016. let t, (doc,flags) = MetaInfo.to_string d in
  1017. if not (List.mem MetaInfo.Internal flags) then begin
  1018. let params = ref [] and used = ref [] and pfs = ref [] in
  1019. List.iter (function
  1020. | MetaInfo.HasParam s -> params := s :: !params
  1021. | MetaInfo.Platform f -> pfs := f :: !pfs
  1022. | MetaInfo.Platforms fl -> pfs := fl @ !pfs
  1023. | MetaInfo.UsedOn u -> used := u :: !used
  1024. | MetaInfo.UsedOnEither ul -> used := ul @ !used
  1025. | MetaInfo.Internal -> assert false
  1026. ) flags;
  1027. let params = (match List.rev !params with
  1028. | [] -> ""
  1029. | l -> "(" ^ String.concat "," l ^ ")"
  1030. ) in
  1031. let pfs = (match List.rev !pfs with
  1032. | [] -> ""
  1033. | [p] -> " (" ^ platform_name p ^ " only)"
  1034. | pl -> " (for " ^ String.concat "," (List.map platform_name pl) ^ ")"
  1035. ) in
  1036. let str = "@" ^ t ^ params ^ " : " ^ doc ^ pfs in
  1037. str :: loop (i + 1)
  1038. end else
  1039. loop (i + 1)
  1040. end else
  1041. []
  1042. in
  1043. let all = List.sort String.compare (loop 0) in
  1044. List.iter (fun msg -> ctx.com.print (msg ^ "\n")) all;
  1045. did_something := true
  1046. ),": print help for all compiler metadatas");
  1047. ] in
  1048. let args_callback cl = classes := make_path cl :: !classes in
  1049. let process args =
  1050. let current = ref 0 in
  1051. Arg.parse_argv ~current (Array.of_list ("" :: List.map expand_env args)) (basic_args_spec @ adv_args_spec) args_callback usage
  1052. in
  1053. process_ref := process;
  1054. process ctx.com.args;
  1055. process_libs();
  1056. (try ignore(Common.find_file com "mt/Include.hx"); Common.raw_define com "mt"; with Not_found -> ());
  1057. if com.display then begin
  1058. let mode = Common.defined_value_safe com Define.DisplayMode in
  1059. if mode = "usage" then begin
  1060. com.display <- false;
  1061. Common.display_default := false;
  1062. end;
  1063. com.warning <- message ctx;
  1064. com.error <- error ctx;
  1065. com.main_class <- None;
  1066. let real = Extc.get_real_path (!Parser.resume_display).Ast.pfile in
  1067. classes := lookup_classes com real;
  1068. if !classes = [] then begin
  1069. if not (Sys.file_exists real) then failwith "Display file does not exists";
  1070. (match List.rev (ExtString.String.nsplit real "\\") with
  1071. | file :: _ when file.[0] >= 'a' && file.[1] <= 'z' -> failwith ("Display file '" ^ file ^ "' should not start with a lowercase letter")
  1072. | _ -> ());
  1073. failwith "Display file was not found in class path";
  1074. end;
  1075. Common.log com ("Display file : " ^ real);
  1076. Common.log com ("Classes found : [" ^ (String.concat "," (List.map Ast.s_type_path !classes)) ^ "]");
  1077. end;
  1078. let add_std dir =
  1079. com.class_path <- List.filter (fun s -> not (List.mem s com.std_path)) com.class_path @ List.map (fun p -> p ^ dir ^ "/_std/") com.std_path @ com.std_path
  1080. in
  1081. let ext = (match com.platform with
  1082. | Cross ->
  1083. (* no platform selected *)
  1084. set_platform Cross "";
  1085. "?"
  1086. | Flash8 | Flash ->
  1087. if com.flash_version >= 9. then begin
  1088. let rec loop = function
  1089. | [] -> ()
  1090. | (v,_) :: _ when v > com.flash_version -> ()
  1091. | (v,def) :: l ->
  1092. Common.raw_define com ("flash" ^ def);
  1093. loop l
  1094. in
  1095. loop Common.flash_versions;
  1096. Common.raw_define com "flash";
  1097. com.defines <- PMap.remove "flash8" com.defines;
  1098. com.package_rules <- PMap.remove "flash" com.package_rules;
  1099. add_std "flash";
  1100. end else begin
  1101. com.package_rules <- PMap.add "flash" (Directory "flash8") com.package_rules;
  1102. com.package_rules <- PMap.add "flash8" Forbidden com.package_rules;
  1103. Common.raw_define com "flash";
  1104. Common.raw_define com ("flash" ^ string_of_int (int_of_float com.flash_version));
  1105. com.platform <- Flash8;
  1106. add_std "flash8";
  1107. end;
  1108. "swf"
  1109. | Neko ->
  1110. add_std "neko";
  1111. "n"
  1112. | Js ->
  1113. add_std "js";
  1114. "js"
  1115. | Php ->
  1116. add_std "php";
  1117. "php"
  1118. | Cpp ->
  1119. add_std "cpp";
  1120. "cpp"
  1121. | Cs ->
  1122. Gencs.before_generate com;
  1123. add_std "cs"; "cs"
  1124. | Java ->
  1125. let old_flush = ctx.flush in
  1126. ctx.flush <- (fun () ->
  1127. List.iter (fun (_,_,close,_,_) -> close()) com.java_libs;
  1128. old_flush()
  1129. );
  1130. Genjava.before_generate com;
  1131. add_std "java"; "java"
  1132. ) in
  1133. (* if we are at the last compilation step, allow all packages accesses - in case of macros or opening another project file *)
  1134. if com.display && not ctx.has_next then com.package_rules <- PMap.foldi (fun p r acc -> match r with Forbidden -> acc | _ -> PMap.add p r acc) com.package_rules PMap.empty;
  1135. com.config <- get_config com; (* make sure to adapt all flags changes defined after platform *)
  1136. (* check file extension. In case of wrong commandline, we don't want
  1137. to accidentaly delete a source file. *)
  1138. if not !no_output && file_extension com.file = ext then delete_file com.file;
  1139. List.iter (fun f -> f()) (List.rev (!pre_compilation));
  1140. if !classes = [([],"Std")] && not !force_typing then begin
  1141. if !cmds = [] && not !did_something then Arg.usage basic_args_spec usage;
  1142. end else begin
  1143. ctx.setup();
  1144. Common.log com ("Classpath : " ^ (String.concat ";" com.class_path));
  1145. Common.log com ("Defines : " ^ (String.concat ";" (PMap.foldi (fun v _ acc -> v :: acc) com.defines [])));
  1146. let t = Common.timer "typing" in
  1147. Typecore.type_expr_ref := (fun ctx e with_type -> Typer.type_expr ctx e with_type);
  1148. let tctx = Typer.create com in
  1149. List.iter (Typer.call_init_macro tctx) (List.rev !config_macros);
  1150. List.iter (fun cpath -> ignore(tctx.Typecore.g.Typecore.do_load_module tctx cpath Ast.null_pos)) (List.rev !classes);
  1151. Typer.finalize tctx;
  1152. t();
  1153. if ctx.has_error then raise Abort;
  1154. if com.display then begin
  1155. if ctx.has_next then raise Abort;
  1156. failwith "No completion point was found";
  1157. end;
  1158. let t = Common.timer "filters" in
  1159. let main, types, modules = Typer.generate tctx in
  1160. com.main <- main;
  1161. com.types <- types;
  1162. com.modules <- modules;
  1163. let filters = [
  1164. Codegen.Abstract.handle_abstract_casts tctx;
  1165. if com.foptimize then (fun e -> Optimizer.reduce_expression tctx (Optimizer.inline_constructors tctx e)) else Optimizer.sanitize tctx;
  1166. Codegen.check_local_vars_init;
  1167. Codegen.captured_vars com;
  1168. Codegen.rename_local_vars com;
  1169. ] in
  1170. List.iter (Codegen.post_process filters) com.types;
  1171. Codegen.post_process_end();
  1172. List.iter (fun f -> f()) (List.rev com.filters);
  1173. List.iter (Codegen.save_class_state tctx) com.types;
  1174. if Common.defined_value_safe com Define.DisplayMode = "usage" then
  1175. Codegen.detect_usage com;
  1176. let dce_mode = (try Common.defined_value com Define.Dce with _ -> "no") in
  1177. if not (!gen_as3 || dce_mode = "no" || Common.defined com Define.DocGen) then Dce.run com main (dce_mode = "full" && not !interp);
  1178. let type_filters = [
  1179. Codegen.check_private_path;
  1180. Codegen.remove_generic_base;
  1181. Codegen.apply_native_paths;
  1182. Codegen.add_rtti;
  1183. Codegen.remove_extern_fields;
  1184. (match ctx.com.platform with | Java | Cs -> (fun _ _ -> ()) | _ -> Codegen.add_field_inits);
  1185. Codegen.add_meta_field;
  1186. Codegen.check_remove_metadata;
  1187. Codegen.check_void_field;
  1188. ] in
  1189. let type_filters = if ctx.com.platform = Java then Codegen.promote_abstract_parameters :: type_filters else type_filters in
  1190. List.iter (fun t -> List.iter (fun f -> f tctx t) type_filters) com.types;
  1191. if ctx.has_error then raise Abort;
  1192. (match !xml_out with
  1193. | None -> ()
  1194. | Some "hx" ->
  1195. Genxml.generate_hx com
  1196. | Some file ->
  1197. Common.log com ("Generating xml : " ^ file);
  1198. Genxml.generate com file);
  1199. if com.platform = Flash || com.platform = Cpp then List.iter (Codegen.fix_overrides com) com.types;
  1200. if Common.defined com Define.Dump then Codegen.dump_types com;
  1201. if Common.defined com Define.DumpDependencies then Codegen.dump_dependencies com;
  1202. t();
  1203. (match com.platform with
  1204. | _ when !no_output ->
  1205. if !interp then begin
  1206. let ctx = Interp.create com (Typer.make_macro_api tctx Ast.null_pos) in
  1207. Interp.add_types ctx com.types (fun t -> ());
  1208. (match com.main with
  1209. | None -> ()
  1210. | Some e -> ignore(Interp.eval_expr ctx e));
  1211. end;
  1212. | Cross ->
  1213. ()
  1214. | Flash8 | Flash when !gen_as3 ->
  1215. Common.log com ("Generating AS3 in : " ^ com.file);
  1216. Genas3.generate com;
  1217. | Flash8 | Flash ->
  1218. Common.log com ("Generating swf : " ^ com.file);
  1219. Genswf.generate com !swf_header;
  1220. | Neko ->
  1221. Common.log com ("Generating neko : " ^ com.file);
  1222. Genneko.generate com;
  1223. | Js ->
  1224. Common.log com ("Generating js : " ^ com.file);
  1225. Genjs.generate com
  1226. | Php ->
  1227. Common.log com ("Generating PHP in : " ^ com.file);
  1228. Genphp.generate com;
  1229. | Cpp ->
  1230. Common.log com ("Generating Cpp in : " ^ com.file);
  1231. Gencpp.generate com;
  1232. | Cs ->
  1233. Common.log com ("Generating Cs in : " ^ com.file);
  1234. Gencs.generate com;
  1235. | Java ->
  1236. Common.log com ("Generating Java in : " ^ com.file);
  1237. Genjava.generate com;
  1238. );
  1239. end;
  1240. Sys.catch_break false;
  1241. if not !no_output then List.iter (fun c ->
  1242. let r = run_command ctx c in
  1243. if r <> 0 then failwith ("Command failed with error " ^ string_of_int r)
  1244. ) (List.rev !cmds)
  1245. with
  1246. | Abort | Typecore.Fatal_error ->
  1247. ()
  1248. | Common.Abort (m,p) ->
  1249. error ctx m p
  1250. | Lexer.Error (m,p) ->
  1251. error ctx (Lexer.error_msg m) p
  1252. | Parser.Error (m,p) ->
  1253. error ctx (Parser.error_msg m) p
  1254. | Typecore.Forbid_package ((pack,m,p),pl,pf) ->
  1255. if !Common.display_default && ctx.has_next then begin
  1256. ctx.has_error <- false;
  1257. ctx.messages <- [];
  1258. end else begin
  1259. error ctx (Printf.sprintf "You cannot access the %s package while %s (for %s)" pack (if pf = "macro" then "in a macro" else "targeting " ^ pf) (Ast.s_type_path m) ) p;
  1260. List.iter (error ctx " referenced here") (List.rev pl);
  1261. end
  1262. | Typecore.Error (m,p) ->
  1263. error ctx (Typecore.error_msg m) p
  1264. | Interp.Error (msg,p :: l) ->
  1265. message ctx msg p;
  1266. List.iter (message ctx "Called from") l;
  1267. error ctx "Aborted" Ast.null_pos;
  1268. | Arg.Bad msg ->
  1269. error ctx ("Error: " ^ msg) Ast.null_pos
  1270. | Failure msg when not (is_debug_run()) ->
  1271. error ctx ("Error: " ^ msg) Ast.null_pos
  1272. | Arg.Help msg ->
  1273. message ctx msg Ast.null_pos
  1274. | Typer.DisplayFields fields ->
  1275. let ctx = print_context() in
  1276. let fields = List.map (fun (name,t,doc) -> name, s_type ctx t, (match doc with None -> "" | Some d -> d)) fields in
  1277. let fields = if !measure_times then begin
  1278. close_times();
  1279. let tot = ref 0. in
  1280. Hashtbl.iter (fun _ t -> tot := !tot +. t.total) Common.htimers;
  1281. let fields = ("@TOTAL", Printf.sprintf "%.3fs" (get_time() -. !start_time), "") :: fields in
  1282. if !tot > 0. then
  1283. Hashtbl.fold (fun _ t acc ->
  1284. ("@TIME " ^ t.name, Printf.sprintf "%.3fs (%.0f%%)" t.total (t.total *. 100. /. !tot), "") :: acc
  1285. ) Common.htimers fields
  1286. else fields
  1287. end else
  1288. fields
  1289. in
  1290. complete_fields fields
  1291. | Typecore.DisplayTypes tl ->
  1292. let ctx = print_context() in
  1293. let b = Buffer.create 0 in
  1294. List.iter (fun t ->
  1295. Buffer.add_string b "<type>\n";
  1296. Buffer.add_string b (htmlescape (s_type ctx t));
  1297. Buffer.add_string b "\n</type>\n";
  1298. ) tl;
  1299. raise (Completion (Buffer.contents b))
  1300. | Typecore.DisplayPosition pl ->
  1301. let b = Buffer.create 0 in
  1302. let error_printer file line = sprintf "%s:%d:" (Common.unique_full_path file) line in
  1303. List.iter (fun p ->
  1304. let epos = Lexer.get_error_pos error_printer p in
  1305. Buffer.add_string b "<pos>\n";
  1306. Buffer.add_string b epos;
  1307. Buffer.add_string b "\n</pos>\n";
  1308. ) pl;
  1309. raise (Completion (Buffer.contents b))
  1310. | Typer.DisplayMetadata m ->
  1311. let b = Buffer.create 0 in
  1312. List.iter (fun (m,el,p) ->
  1313. Buffer.add_string b ("<meta name=\"" ^ (fst (MetaInfo.to_string m)) ^ "\"");
  1314. if el = [] then Buffer.add_string b "/>" else begin
  1315. Buffer.add_string b ">\n";
  1316. List.iter (fun e -> Buffer.add_string b ((htmlescape (Genxml.sexpr e)) ^ "\n")) el;
  1317. Buffer.add_string b "</meta>\n";
  1318. end
  1319. ) m;
  1320. raise (Completion (Buffer.contents b))
  1321. | Parser.TypePath (p,c) ->
  1322. (match c with
  1323. | None ->
  1324. let packs, classes = read_type_path com p in
  1325. if packs = [] && classes = [] then
  1326. error ctx ("No classes found in " ^ String.concat "." p) Ast.null_pos
  1327. else
  1328. complete_fields (List.map (fun f -> f,"","") (packs @ classes))
  1329. | Some (c,cur_package) ->
  1330. try
  1331. let ctx = Typer.create com in
  1332. let rec lookup p =
  1333. try
  1334. Typeload.load_module ctx (p,c) Ast.null_pos
  1335. with e ->
  1336. if cur_package then
  1337. match List.rev p with
  1338. | [] -> raise e
  1339. | _ :: p -> lookup (List.rev p)
  1340. else
  1341. raise e
  1342. in
  1343. let m = lookup p in
  1344. complete_fields (List.map (fun t -> snd (t_path t),"","") (List.filter (fun t -> not (t_infos t).mt_private) m.m_types))
  1345. with Completion c ->
  1346. raise (Completion c)
  1347. | _ ->
  1348. error ctx ("Could not load module " ^ (Ast.s_type_path (p,c))) Ast.null_pos)
  1349. | e when (try Sys.getenv "OCAMLRUNPARAM" <> "b" || !global_cache <> None with _ -> true) && not (is_debug_run()) ->
  1350. error ctx (Printexc.to_string e) Ast.null_pos
  1351. ;;
  1352. let other = Common.timer "other" in
  1353. Sys.catch_break true;
  1354. let args = List.tl (Array.to_list Sys.argv) in
  1355. (try
  1356. let server = Sys.getenv "HAXE_COMPILATION_SERVER" in
  1357. let host, port = (try ExtString.String.split server ":" with _ -> "127.0.0.1", server) in
  1358. do_connect host (try int_of_string port with _ -> failwith "Invalid HAXE_COMPILATION_SERVER port") args
  1359. with Not_found -> try
  1360. process_params create_context args
  1361. with Completion c ->
  1362. prerr_endline c;
  1363. exit 0
  1364. );
  1365. other();
  1366. if !measure_times then report_times prerr_endline