2
0

main.ml 57 KB

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