Pārlūkot izejas kodu

add path.ml, put main.ml on another diet

Simon Krajewski 9 gadi atpakaļ
vecāks
revīzija
1ab9a0bc5e

+ 15 - 15
Makefile

@@ -52,7 +52,7 @@ CC_PARSER_CMD = $(COMPILER) -pp camlp4o $(ALL_CFLAGS) -c src/syntax/parser.ml
 
 RELDIR=../../..
 
-MODULES=json syntax/ast display/displayTypes typing/type syntax/lexer typing/common generators/genxml syntax/parser \
+MODULES=json path syntax/ast display/displayTypes typing/type syntax/lexer typing/common generators/genxml syntax/parser \
 	typing/typecore display/display \
 	optimization/optimizer typing/typeload generators/codegen generators/gencommon generators/genas3 \
 	generators/gencpp generators/genjs generators/genneko generators/genphp generators/genswf9 \
@@ -134,7 +134,7 @@ uninstall:
 
 # display
 
-src/display/display.$(MODULE_EXT): src/syntax/ast.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/typing/type.$(MODULE_EXT) src/typing/typecore.$(MODULE_EXT) src/syntax/parser.$(MODULE_EXT) src/display/displayTypes.$(MODULE_EXT)
+src/display/display.$(MODULE_EXT): src/path.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/typing/type.$(MODULE_EXT) src/typing/typecore.$(MODULE_EXT) src/syntax/parser.$(MODULE_EXT) src/display/displayTypes.$(MODULE_EXT)
 
 src/display/displayTypes.$(MODULE_EXT) : src/syntax/ast.$(MODULE_EXT)
 
@@ -144,15 +144,15 @@ src/generators/codegen.$(MODULE_EXT): src/typing/typecore.$(MODULE_EXT) src/typi
 
 src/generators/genas3.$(MODULE_EXT): src/typing/type.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/generators/codegen.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT)
 
-src/generators/gencommon.$(MODULE_EXT): src/typing/type.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/generators/codegen.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT) src/typing/typeload.$(MODULE_EXT) libs/ilib/il.$(LIB_EXT)
+src/generators/gencommon.$(MODULE_EXT): src/path.$(MODULE_EXT) src/typing/type.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/generators/codegen.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT) src/typing/typeload.$(MODULE_EXT) libs/ilib/il.$(LIB_EXT)
 
-src/generators/gencpp.$(MODULE_EXT): src/typing/type.$(MODULE_EXT) src/syntax/lexer.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/generators/codegen.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT)
+src/generators/gencpp.$(MODULE_EXT): src/path.$(MODULE_EXT) src/typing/type.$(MODULE_EXT) src/syntax/lexer.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/generators/codegen.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT)
 
-src/generators/gencs.$(MODULE_EXT): src/typing/type.$(MODULE_EXT) src/syntax/lexer.$(MODULE_EXT) src/generators/gencommon.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/generators/codegen.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT) libs/ilib/il.$(LIB_EXT)
+src/generators/gencs.$(MODULE_EXT): src/path.$(MODULE_EXT) src/typing/type.$(MODULE_EXT) src/syntax/lexer.$(MODULE_EXT) src/generators/gencommon.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/generators/codegen.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT) libs/ilib/il.$(LIB_EXT)
 
-src/generators/genjava.$(MODULE_EXT): src/typing/type.$(MODULE_EXT) src/generators/gencommon.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/generators/codegen.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT)
+src/generators/genjava.$(MODULE_EXT): src/path.$(MODULE_EXT) src/typing/type.$(MODULE_EXT) src/generators/gencommon.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/generators/codegen.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT)
 
-src/generators/genjs.$(MODULE_EXT): src/typing/type.$(MODULE_EXT) src/syntax/lexer.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/generators/codegen.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT)
+src/generators/genjs.$(MODULE_EXT): src/path.$(MODULE_EXT) src/typing/type.$(MODULE_EXT) src/syntax/lexer.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/generators/codegen.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT)
 
 src/generators/genneko.$(MODULE_EXT): src/typing/type.$(MODULE_EXT) src/syntax/lexer.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/generators/codegen.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT)
 
@@ -166,13 +166,13 @@ src/generators/genswf.$(MODULE_EXT): src/typing/type.$(MODULE_EXT) src/generator
 
 src/generators/genhl.$(MODULE_EXT): src/typing/type.$(MODULE_EXT) src/syntax/lexer.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/generators/codegen.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT) src/macro/interp.$(MODULE_EXT)
 
-src/generators/genswf9.$(MODULE_EXT): src/typing/type.$(MODULE_EXT) src/syntax/lexer.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/generators/codegen.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT)
+src/generators/genswf9.$(MODULE_EXT): src/path.$(MODULE_EXT) src/typing/type.$(MODULE_EXT) src/syntax/lexer.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/generators/codegen.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT)
 
 src/generators/genxml.$(MODULE_EXT): src/typing/type.$(MODULE_EXT) src/syntax/lexer.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT)
 
 # macro
 
-src/macro/interp.$(MODULE_EXT): src/typing/typecore.$(MODULE_EXT) src/typing/type.$(MODULE_EXT) src/syntax/lexer.$(MODULE_EXT) src/generators/genneko.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/generators/codegen.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT) src/generators/genswf.$(MODULE_EXT) src/generators/genjava.$(MODULE_EXT) src/generators/gencs.$(MODULE_EXT) src/syntax/parser.$(MODULE_EXT) libs/ilib/il.$(LIB_EXT)
+src/macro/interp.$(MODULE_EXT): src/path.$(MODULE_EXT) src/typing/typecore.$(MODULE_EXT) src/typing/type.$(MODULE_EXT) src/syntax/lexer.$(MODULE_EXT) src/generators/genneko.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/generators/codegen.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT) src/generators/genswf.$(MODULE_EXT) src/generators/genjava.$(MODULE_EXT) src/generators/gencs.$(MODULE_EXT) src/syntax/parser.$(MODULE_EXT) libs/ilib/il.$(LIB_EXT)
 
 # optimization
 
@@ -186,7 +186,7 @@ src/optimization/analyzerTexprTransformer.$(MODULE_EXT): src/syntax/ast.$(MODULE
 
 src/optimization/analyzerTypes.$(MODULE_EXT): src/syntax/ast.$(MODULE_EXT) src/typing/type.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/optimization/analyzerConfig.$(MODULE_EXT)
 
-src/optimization/dce.$(MODULE_EXT): src/syntax/ast.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/generators/codegen.$(MODULE_EXT) src/typing/type.$(MODULE_EXT)
+src/optimization/dce.$(MODULE_EXT): src/path.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/generators/codegen.$(MODULE_EXT) src/typing/type.$(MODULE_EXT)
 
 src/optimization/filters.$(MODULE_EXT): src/syntax/ast.$(MODULE_EXT) src/optimization/analyzer.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/typing/type.$(MODULE_EXT) src/optimization/dce.$(MODULE_EXT) src/generators/codegen.$(MODULE_EXT) src/typing/typecore.$(MODULE_EXT)
 
@@ -198,7 +198,7 @@ src/syntax/ast.$(MODULE_EXT):
 
 src/syntax/lexer.$(MODULE_EXT): src/syntax/lexer.ml src/syntax/ast.$(MODULE_EXT)
 
-src/syntax/parser.$(MODULE_EXT): src/syntax/parser.ml src/syntax/lexer.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT)
+src/syntax/parser.$(MODULE_EXT): src/path.$(MODULE_EXT) src/syntax/parser.ml src/syntax/lexer.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT)
 	$(CC_PARSER_CMD)
 
 # typing
@@ -209,16 +209,16 @@ src/typing/matcher.$(MODULE_EXT): src/optimization/optimizer.$(MODULE_EXT) src/g
 
 src/typing/type.$(MODULE_EXT): src/syntax/ast.$(MODULE_EXT) src/json.$(MODULE_EXT)
 
-src/typing/typecore.$(MODULE_EXT): src/typing/type.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT)
+src/typing/typecore.$(MODULE_EXT): src/path.$(MODULE_EXT) src/typing/type.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT)
 
-src/typing/typeload.$(MODULE_EXT): src/typing/typecore.$(MODULE_EXT) src/typing/type.$(MODULE_EXT) src/syntax/parser.$(MODULE_EXT) src/optimization/optimizer.$(MODULE_EXT) src/syntax/lexer.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT) src/json.$(MODULE_EXT) src/display/display.$(MODULE_EXT)
+src/typing/typeload.$(MODULE_EXT): src/path.$(MODULE_EXT) src/typing/typecore.$(MODULE_EXT) src/typing/type.$(MODULE_EXT) src/syntax/parser.$(MODULE_EXT) src/optimization/optimizer.$(MODULE_EXT) src/syntax/lexer.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT) src/json.$(MODULE_EXT) src/display/display.$(MODULE_EXT)
 
-src/typing/typer.$(MODULE_EXT): src/typing/typeload.$(MODULE_EXT) src/typing/typecore.$(MODULE_EXT) src/typing/type.$(MODULE_EXT) src/syntax/parser.$(MODULE_EXT) src/optimization/optimizer.$(MODULE_EXT) src/syntax/lexer.$(MODULE_EXT) src/macro/interp.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/generators/codegen.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT) src/optimization/filters.$(MODULE_EXT) src/generators/genjs.$(MODULE_EXT) src/generators/genlua.$(MODULE_EXT) src/display/display.$(MODULE_EXT)
+src/typing/typer.$(MODULE_EXT): src/path.$(MODULE_EXT) src/typing/typeload.$(MODULE_EXT) src/typing/typecore.$(MODULE_EXT) src/typing/type.$(MODULE_EXT) src/syntax/parser.$(MODULE_EXT) src/optimization/optimizer.$(MODULE_EXT) src/syntax/lexer.$(MODULE_EXT) src/macro/interp.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/generators/codegen.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT) src/optimization/filters.$(MODULE_EXT) src/generators/genjs.$(MODULE_EXT) src/generators/genlua.$(MODULE_EXT) src/display/display.$(MODULE_EXT)
 
 
 # main
 
-src/main.$(MODULE_EXT): src/optimization/filters.$(MODULE_EXT) src/typing/matcher.$(MODULE_EXT) src/typing/typer.$(MODULE_EXT) src/typing/typeload.$(MODULE_EXT) src/typing/typecore.$(MODULE_EXT) src/typing/type.$(MODULE_EXT) src/syntax/parser.$(MODULE_EXT) src/optimization/optimizer.$(MODULE_EXT) src/syntax/lexer.$(MODULE_EXT) src/macro/interp.$(MODULE_EXT) src/generators/genxml.$(MODULE_EXT) src/generators/genswf.$(MODULE_EXT) src/generators/genphp.$(MODULE_EXT) src/generators/genneko.$(MODULE_EXT) src/generators/genjs.$(MODULE_EXT) src/generators/genlua.$(MODULE_EXT) src/generators/gencpp.$(MODULE_EXT) src/generators/genas3.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/generators/codegen.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT) src/generators/genjava.$(MODULE_EXT) src/generators/gencs.$(MODULE_EXT) src/generators/genpy.$(MODULE_EXT) src/generators/genhl.$(MODULE_EXT) src/version.$(MODULE_EXT) src/display/display.$(MODULE_EXT) libs/ilib/il.$(LIB_EXT)
+src/main.$(MODULE_EXT): src/path.$(MODULE_EXT) src/optimization/filters.$(MODULE_EXT) src/typing/matcher.$(MODULE_EXT) src/typing/typer.$(MODULE_EXT) src/typing/typeload.$(MODULE_EXT) src/typing/typecore.$(MODULE_EXT) src/typing/type.$(MODULE_EXT) src/syntax/parser.$(MODULE_EXT) src/optimization/optimizer.$(MODULE_EXT) src/syntax/lexer.$(MODULE_EXT) src/macro/interp.$(MODULE_EXT) src/generators/genxml.$(MODULE_EXT) src/generators/genswf.$(MODULE_EXT) src/generators/genphp.$(MODULE_EXT) src/generators/genneko.$(MODULE_EXT) src/generators/genjs.$(MODULE_EXT) src/generators/genlua.$(MODULE_EXT) src/generators/gencpp.$(MODULE_EXT) src/generators/genas3.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/generators/codegen.$(MODULE_EXT) src/syntax/ast.$(MODULE_EXT) src/generators/genjava.$(MODULE_EXT) src/generators/gencs.$(MODULE_EXT) src/generators/genpy.$(MODULE_EXT) src/generators/genhl.$(MODULE_EXT) src/version.$(MODULE_EXT) src/display/display.$(MODULE_EXT) libs/ilib/il.$(LIB_EXT)
 
 src/version.$(MODULE_EXT):
 	$(MAKE) -f Makefile.version_extra -s --no-print-directory ADD_REVISION=$(ADD_REVISION) BRANCH=$(BRANCH) COMMIT_SHA=$(COMMIT_SHA) COMMIT_DATE=$(COMMIT_DATE) > src/version.ml

+ 98 - 7
src/display/display.ml

@@ -25,7 +25,7 @@ exception DisplayToplevel of IdentifierType.t list
 exception DisplayPackage of string list
 
 let is_display_file file =
-	file <> "?" && Common.unique_full_path file = (!Parser.resume_display).pfile
+	file <> "?" && Path.unique_full_path file = (!Parser.resume_display).pfile
 
 let encloses_position p_target p =
 	p.pmin <= p_target.pmin && p.pmax >= p_target.pmax
@@ -205,7 +205,7 @@ let print_type t p =
 	if p = null_pos then
 		Buffer.add_string b "<type>\n"
 	else begin
-		let error_printer file line = Printf.sprintf "%s:%d:" (Common.unique_full_path file) line in
+		let error_printer file line = Printf.sprintf "%s:%d:" (Path.unique_full_path file) line in
 		let epos = Lexer.get_error_pos error_printer p in
 		Buffer.add_string b ("<type p=\"" ^ (htmlescape epos) ^ "\">\n")
 	end;
@@ -226,7 +226,7 @@ let print_signatures tl =
 
 let print_positions pl =
 	let b = Buffer.create 0 in
-	let error_printer file line = Printf.sprintf "%s:%d:" (get_real_path file) line in
+	let error_printer file line = Printf.sprintf "%s:%d:" (Path.get_real_path file) line in
 	Buffer.add_string b "<list>\n";
 	List.iter (fun p ->
 		let epos = Lexer.get_error_pos error_printer p in
@@ -542,7 +542,7 @@ module Diagnostics = struct
 		let com = ctx.com in
 		let diag = Hashtbl.create 0 in
 		let add dk p sev args =
-			let file = get_real_path p.pfile in
+			let file = Path.get_real_path p.pfile in
 			let diag = try
 				Hashtbl.find diag file
 			with Not_found ->
@@ -826,7 +826,7 @@ module StatisticsPrinter = struct
 	let print_statistics (kinds,relations) =
 		let files = Hashtbl.create 0 in
 		Hashtbl.iter (fun p rl ->
-			let file = get_real_path p.pfile in
+			let file = Path.get_real_path p.pfile in
 			try
 				Hashtbl.replace files file ((p,rl) :: Hashtbl.find files file)
 			with Not_found ->
@@ -839,7 +839,7 @@ module StatisticsPrinter = struct
 					let s = relation_to_string r in
 					let jo = JObject [
 						"range",pos_to_json_range p;
-						"file",JString (get_real_path p.pfile);
+						"file",JString (Path.get_real_path p.pfile);
 					] in
 					try Hashtbl.replace h s (jo :: Hashtbl.find h s)
 					with Not_found -> Hashtbl.add h s [jo]
@@ -857,4 +857,95 @@ module StatisticsPrinter = struct
 		let b = Buffer.create 0 in
 		write_json (Buffer.add_string b) (JArray ja);
 		Buffer.contents b
-end
+end
+
+let process_display_file com classes =
+	let get_module_path_from_file_path com spath =
+		let rec loop = function
+			| [] -> None
+			| cp :: l ->
+				let cp = (if cp = "" then "./" else cp) in
+				let c = Path.add_trailing_slash (Path.get_real_path cp) in
+				let clen = String.length c in
+				if clen < String.length spath && String.sub spath 0 clen = c then begin
+					let path = String.sub spath clen (String.length spath - clen) in
+					(try
+						let path = Path.parse_type_path path in
+						(match loop l with
+						| Some x as r when String.length (Ast.s_type_path x) < String.length (Ast.s_type_path path) -> r
+						| _ -> Some path)
+					with _ -> loop l)
+				end else
+					loop l
+		in
+		loop com.class_path
+	in
+	match com.display.dms_display_file_policy with
+		| DFPNo ->
+			()
+		| dfp ->
+			if dfp = DFPOnly then begin
+				classes := [];
+				com.main_class <- None;
+			end;
+			let real = Path.get_real_path (!Parser.resume_display).Ast.pfile in
+			(match get_module_path_from_file_path com real with
+			| Some path ->
+				if com.display.dms_kind = DMPackage then raise (DisplayPackage (fst path));
+				classes := path :: !classes
+			| None ->
+				if not (Sys.file_exists real) then failwith "Display file does not exist";
+				(match List.rev (ExtString.String.nsplit real Path.path_sep) with
+				| file :: _ when file.[0] >= 'a' && file.[1] <= 'z' -> failwith ("Display file '" ^ file ^ "' should not start with a lowercase letter")
+				| _ -> ());
+				failwith "Display file was not found in class path"
+			);
+			Common.log com ("Display file : " ^ real);
+			Common.log com ("Classes found : ["  ^ (String.concat "," (List.map Ast.s_type_path !classes)) ^ "]")
+
+let process_global_display_mode com tctx = match com.display.dms_kind with
+	| DMUsage with_definition ->
+		let symbols,relations = Statistics.collect_statistics tctx in
+		let rec loop acc relations = match relations with
+			| (Statistics.Referenced,p) :: relations -> loop (p :: acc) relations
+			| _ :: relations -> loop acc relations
+			| [] -> acc
+		in
+		let usages = Hashtbl.fold (fun p sym acc ->
+			if Statistics.is_usage_symbol sym then begin
+				let acc = if with_definition then p :: acc else acc in
+				(try loop acc (Hashtbl.find relations p)
+				with Not_found -> acc)
+			end else
+				acc
+		) symbols [] in
+		let usages = List.sort (fun p1 p2 ->
+			let c = compare p1.pfile p2.pfile in
+			if c <> 0 then c else compare p1.pmin p2.pmin
+		) usages in
+		raise (DisplayPosition usages)
+	| DMDiagnostics global ->
+		Diagnostics.prepare com global;
+		raise (Diagnostics (Diagnostics.print_diagnostics tctx global))
+	| DMStatistics ->
+		let stats = Statistics.collect_statistics tctx in
+		raise (Statistics (StatisticsPrinter.print_statistics stats))
+	| DMModuleSymbols filter ->
+		let symbols = com.shared.shared_display_information.document_symbols in
+		let symbols = match !global_cache with
+			| None -> symbols
+			| Some cache ->
+				let rec loop acc com =
+					let com_sign = get_signature com in
+					let acc = Hashtbl.fold (fun (file,sign) (_,data) acc ->
+						if (filter <> None || is_display_file file) && com_sign = sign then
+							(file,DocumentSymbols.collect_module_symbols data) :: acc
+						else
+							acc
+					) cache.c_files acc in
+					match com.get_macros() with None -> acc | Some com -> loop acc com
+				in
+				loop symbols com
+		in
+		raise (ModuleSymbols(DocumentSymbols.print_module_symbols com symbols filter))
+	| _ -> ()

+ 2 - 2
src/generators/gencommon.ml

@@ -886,7 +886,7 @@ let write_file gen w source_dir path extension out_files =
 		close_out f
 	end;
 
-	out_files := (unique_full_path s_path) :: !out_files;
+	out_files := (Path.unique_full_path s_path) :: !out_files;
 
 	t()
 
@@ -901,7 +901,7 @@ let clean_files path excludes verbose =
 				let pack = pack @ [file] in
 				iter_files (pack) (Unix.opendir filepath) filepath;
 				try Unix.rmdir filepath with Unix.Unix_error (ENOTEMPTY,_,_) -> ();
-			else if not (String.ends_with filepath ".meta") && not (List.mem (unique_full_path filepath) excludes) then begin
+			else if not (String.ends_with filepath ".meta") && not (List.mem (Path.unique_full_path filepath) excludes) then begin
 				if verbose then print_endline ("Removing " ^ filepath);
 			 	Sys.remove filepath
 			end

+ 5 - 5
src/generators/gencpp.ml

@@ -402,7 +402,7 @@ let get_meta_string_path meta key =
               else
                  pos.pfile
               in
-              normalize_path (Filename.concat (Filename.dirname base) (String.sub name 2 ((String.length name) -2)  ))
+              Path.normalize_path (Filename.concat (Filename.dirname base) (String.sub name 2 ((String.length name) -2)  ))
            end else
               name
            with Invalid_argument _ -> name)
@@ -417,7 +417,7 @@ let get_meta_string_full_filename meta key =
       | [] -> ""
       | (k,_, pos) :: _  when k=key->
            if (Filename.is_relative pos.pfile) then
-              normalize_path (Filename.concat (Sys.getcwd()) pos.pfile)
+              Path.normalize_path (Filename.concat (Sys.getcwd()) pos.pfile)
            else
               pos.pfile
       | _ :: l -> loop l
@@ -428,7 +428,7 @@ let get_meta_string_full_filename meta key =
 let get_meta_string_full_dirname meta key =
    let name = get_meta_string_full_filename meta key in
    try
-      normalize_path (Filename.dirname name)
+      Path.normalize_path (Filename.dirname name)
    with Invalid_argument _ -> ""
 ;;
 
@@ -4417,7 +4417,7 @@ let generate_files common_ctx file_info =
    output_files "const char *__hxcpp_all_files_fullpath[] = {\n";
    output_files "#ifdef HXCPP_DEBUGGER\n";
    List.iter ( fun file -> output_files ((const_char_star (
-      Common.get_full_path (try Common.find_file common_ctx file with Not_found -> file)
+      Path.get_full_path (try Common.find_file common_ctx file with Not_found -> file)
       ))^",\n" ) )
       ( List.sort String.compare ( pmap_keys !file_info) );
    output_files "#endif\n";
@@ -7030,7 +7030,7 @@ let generate_source ctx =
 
          (* Output file info too *)
          List.iter ( fun file ->
-               let full_path = Common.get_full_path (try Common.find_file common_ctx file with Not_found -> file) in
+               let full_path = Path.get_full_path (try Common.find_file common_ctx file with Not_found -> file) in
                if file <> "?" then
                   out ("file " ^ (escape file) ^ " " ^ (escape full_path) ^"\n") )
             ( List.sort String.compare ( pmap_keys !(ctx.ctx_file_info) ) );

+ 2 - 2
src/generators/gencs.ml

@@ -1136,7 +1136,7 @@ let configure gen =
 		else fun w p ->
 			if p.pfile <> Ast.null_pos.pfile then (* Compiler Error CS1560 https://msdn.microsoft.com/en-us/library/z3t5e5sw(v=vs.90).aspx *)
 			let cur_line = Lexer.get_error_line p in
-			let file = Common.get_full_path p.pfile in
+			let file = Path.get_full_path p.pfile in
 			if cur_line <> ((!last_line)+1) then
 				let line = Ast.s_escape file in
 				if String.length line <= 256 then
@@ -3163,7 +3163,7 @@ let configure gen =
 			output_string f v;
 			close_out f;
 
-			out_files := (unique_full_path full_path) :: !out_files
+			out_files := (Path.unique_full_path full_path) :: !out_files
 		) gen.gcon.resources;
 	end;
 	(* add resources array *)

+ 2 - 2
src/generators/genjava.ml

@@ -1203,7 +1203,7 @@ let configure gen =
 			fun w p -> ()
 		else fun w p ->
 			let cur_line = Lexer.get_error_line p in
-			let file = Common.get_full_path p.pfile in
+			let file = Path.get_full_path p.pfile in
 			print w "//line %d \"%s\"" cur_line (Ast.s_escape file); newline w
 	in
 
@@ -2429,7 +2429,7 @@ let configure gen =
 		output_string f v;
 		close_out f;
 
-		out_files := (unique_full_path full_path) :: !out_files
+		out_files := (Path.unique_full_path full_path) :: !out_files
 	) gen.gcon.resources;
 	(try
 		let c = get_cl (Hashtbl.find gen.gtypes (["haxe"], "Resource")) in

+ 1 - 1
src/generators/genjs.ml

@@ -240,7 +240,7 @@ let write_mappings ctx =
 	let channel = open_out_bin (ctx.com.file ^ ".map") in
 	let sources = DynArray.to_list ctx.smap.sources in
 	let to_url file =
-		ExtString.String.map (fun c -> if c == '\\' then '/' else c) (Common.get_full_path file)
+		ExtString.String.map (fun c -> if c == '\\' then '/' else c) (Path.get_full_path file)
 	in
 	output_string channel "{\n";
 	output_string channel "\"version\":3,\n";

+ 1 - 1
src/generators/genswf9.ml

@@ -617,7 +617,7 @@ let debug_infos ?(is_min=true) ctx p =
 	if ctx.debug then begin
 		let line = Lexer.get_error_line (if is_min then p else { p with pmin = p.pmax }) in
 		if ctx.last_file <> p.pfile then begin
-			write ctx (HDebugFile (if ctx.debugger then Common.get_full_path p.pfile else p.pfile));
+			write ctx (HDebugFile (if ctx.debugger then Path.get_full_path p.pfile else p.pfile));
 			ctx.last_file <- p.pfile;
 			ctx.last_line <- -1;
 		end;

+ 3 - 3
src/macro/interp.ml

@@ -511,7 +511,7 @@ let rec dlopen dls =
 		None
 
 let neko =
-	match dlopen (if is_windows then
+	match dlopen (if Path.is_windows then
 		["neko.dll"]
 	else
 		(*
@@ -2371,7 +2371,7 @@ let macro_lib =
 				try
 					Hashtbl.find hfiles f
 				with Not_found ->
-					let ff = Common.unique_full_path f in
+					let ff = Path.unique_full_path f in
 					Hashtbl.add hfiles f ff;
 					ff
 			in
@@ -2642,7 +2642,7 @@ let macro_lib =
 			match v with
 			| VString cp ->
 				let com = ccom() in
-				let cp = Common.add_trailing_slash cp in
+				let cp = Path.add_trailing_slash cp in
 				com.class_path <- cp :: com.class_path;
 				(match com.get_macros() with
 					| Some(mcom) ->

+ 195 - 322
src/main.ml

@@ -161,50 +161,6 @@ let report_times print =
 		List.iter (fun t -> print (Printf.sprintf "  %s : %.3fs, %.0f%%" t.name t.total (t.total *. 100. /. !tot))) timers
 	end
 
-let make_path f =
-	let cl = get_path_parts f in
-	let error msg =
-		let msg = "Could not process argument " ^ f ^ "\n" ^ msg in
-		failwith msg
-	in
-	let invalid_char x =
-		for i = 1 to String.length x - 1 do
-			match x.[i] with
-			| 'A'..'Z' | 'a'..'z' | '0'..'9' | '_' -> ()
-			| c -> error ("invalid character: " ^ (String.make 1 c))
-		done
-	in
-	let rec loop = function
-		| [] ->
-			error "empty part"
-		| [x] ->
-			invalid_char x;
-			[],x
-		| x :: l ->
-			if String.length x = 0 then
-				error "empty part"
-			else if x.[0] < 'a' || x.[0] > 'z' then
-				error "Package name must start with a lower case character";
-			invalid_char x;
-			let path,name = loop l in
-			x :: path,name
-	in
-	loop cl
-
-let starts_uppercase x =
-	x.[0] = '_' || (x.[0] >= 'A' && x.[0] <= 'Z')
-
-let check_uppercase x =
-	if String.length x = 0 then
-		failwith "empty part"
-	else if not (starts_uppercase x) then
-		failwith "Class name must start with uppercase character"
-
-let make_type_path f =
-	let pack,name = make_path f in
-	check_uppercase name;
-	pack,name
-
 let unique l =
 	let rec _unique = function
 		| [] -> []
@@ -400,26 +356,6 @@ let parse_hxml file =
 	IO.close_in ch;
 	parse_hxml_data data
 
-let get_module_path_from_file_path com spath =
-	let rec loop = function
-		| [] -> None
-		| cp :: l ->
-			let cp = (if cp = "" then "./" else cp) in
-			let c = add_trailing_slash (get_real_path cp) in
-			let clen = String.length c in
-			if clen < String.length spath && String.sub spath 0 clen = c then begin
-				let path = String.sub spath clen (String.length spath - clen) in
-				(try
-					let path = make_type_path path in
-					(match loop l with
-					| Some x as r when String.length (Ast.s_type_path x) < String.length (Ast.s_type_path path) -> r
-					| _ -> Some path)
-				with _ -> loop l)
-			end else
-				loop l
-	in
-	loop com.class_path
-
 let add_libs com libs =
 	let call_haxelib() =
 		let t = Common.timer "haxelib" in
@@ -479,7 +415,7 @@ let run_command ctx cmd =
 		0
 	end else
 	let binary_string s =
-		if not is_windows then s else String.concat "\n" (Str.split (Str.regexp "\r\n") s)
+		if not Path.is_windows then s else String.concat "\n" (Str.split (Str.regexp "\r\n") s)
 	in
 	let pout, pin, perr = Unix.open_process_full cmd (Unix.environment()) in
 	let iout = Unix.descr_of_in_channel pout in
@@ -638,26 +574,170 @@ let display_memory ctx =
 		if !mcount > 0 then print ("*** " ^ string_of_int !mcount ^ " modules have leaks !");
 		print "Cache dump complete")
 
+module Initialize = struct
+	let default_flush ctx =
+		List.iter prerr_endline (List.rev ctx.messages);
+		if ctx.has_error && !prompt then begin
+			print_endline "Press enter to exit...";
+			ignore(read_line());
+		end;
+		if ctx.has_error then exit 1
 
-let default_flush ctx =
-	List.iter prerr_endline (List.rev ctx.messages);
-	if ctx.has_error && !prompt then begin
-		print_endline "Press enter to exit...";
-		ignore(read_line());
-	end;
-	if ctx.has_error then exit 1
+	let create_context params =
+		let ctx = {
+			com = Common.create version s_version params;
+			flush = (fun()->());
+			setup = (fun()->());
+			messages = [];
+			has_next = false;
+			has_error = false;
+		} in
+		ctx.flush <- (fun() -> default_flush ctx);
+		ctx
 
-let create_context params =
-	let ctx = {
-		com = Common.create version s_version params;
-		flush = (fun()->());
-		setup = (fun()->());
-		messages = [];
-		has_next = false;
-		has_error = false;
-	} in
-	ctx.flush <- (fun() -> default_flush ctx);
-	ctx
+	let set_platform com pf file =
+		if com.platform <> Cross then failwith "Multiple targets";
+		Common.init_platform com pf;
+		com.file <- file;
+		if (pf = Flash) && file_extension file = "swc" then Common.define com Define.Swc
+
+	let initialize_target ctx com classes =
+		let add_std dir =
+			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
+		in
+		match com.platform with
+			| Cross ->
+				(* no platform selected *)
+				set_platform com Cross "";
+				"?"
+			| Flash ->
+				let rec loop = function
+					| [] -> ()
+					| (v,_) :: _ when v > com.flash_version -> ()
+					| (v,def) :: l ->
+						Common.raw_define com ("flash" ^ def);
+						loop l
+				in
+				loop Common.flash_versions;
+				Common.raw_define com "flash";
+				com.package_rules <- PMap.remove "flash" com.package_rules;
+				add_std "flash";
+				"swf"
+			| Neko ->
+				add_std "neko";
+				"n"
+			| Js ->
+				if not (PMap.exists (fst (Define.infos Define.JqueryVer)) com.defines) then
+					Common.define_value com Define.JqueryVer "11204";
+
+				let es_version =
+					try
+						int_of_string (Common.defined_value com Define.JsEs)
+					with
+					| Not_found ->
+						(Common.define_value com Define.JsEs "5"; 5)
+					| _ ->
+						0
+				in
+
+				if es_version < 3 || es_version = 4 then (* we don't support ancient and there's no 4th *)
+					failwith "Invalid -D js-es value";
+
+				if es_version >= 5 then Common.raw_define com "js-es5"; (* backward-compatibility *)
+
+				add_std "js";
+				"js"
+			| Lua ->
+				add_std "lua";
+				"lua"
+			| Php ->
+				add_std "php";
+				"php"
+			| Cpp ->
+				Common.define_value com Define.HxcppApiLevel "330";
+				add_std "cpp";
+				if Common.defined com Define.Cppia then
+					classes := (Path.parse_path "cpp.cppia.HostClasses" ) :: !classes;
+				"cpp"
+			| Cs ->
+				let old_flush = ctx.flush in
+				ctx.flush <- (fun () ->
+					com.net_libs <- [];
+					old_flush()
+				);
+				Gencs.before_generate com;
+				add_std "cs"; "cs"
+			| Java ->
+				let old_flush = ctx.flush in
+				ctx.flush <- (fun () ->
+					List.iter (fun (_,_,close,_,_) -> close()) com.java_libs;
+					com.java_libs <- [];
+					old_flush()
+				);
+				Genjava.before_generate com;
+				add_std "java"; "java"
+			| Python ->
+				add_std "python";
+				"python"
+			| Hl ->
+				add_std "hl";
+				"hl"
+end
+
+let generate tctx ext xml_out interp swf_header =
+	let com = tctx.Typecore.com in
+	(* check file extension. In case of wrong commandline, we don't want
+		to accidentaly delete a source file. *)
+	if file_extension com.file = ext then delete_file com.file;
+	if com.platform = Flash || com.platform = Cpp then List.iter (Codegen.fix_overrides com) com.types;
+	if Common.defined com Define.Dump then Codegen.Dump.dump_types com;
+	if Common.defined com Define.DumpDependencies then Codegen.Dump.dump_dependencies com;
+	begin match com.platform with
+		| Neko when interp -> ()
+		| Cpp when Common.defined com Define.Cppia -> ()
+		| Cpp | Cs | Java | Php -> Common.mkdir_from_path (com.file ^ "/.")
+		| _ -> Common.mkdir_from_path com.file
+	end;
+	if interp then begin
+		let ctx = Interp.create com (Typer.make_macro_api tctx Ast.null_pos) in
+		Interp.add_types ctx com.types (fun t -> ());
+		(match com.main with
+		| None -> ()
+		| Some e -> ignore(Interp.eval_expr ctx e));
+	end else if com.platform = Cross then
+		()
+	else begin
+		let generate,name = match com.platform with
+		| Flash when Common.defined com Define.As3 ->
+			Genas3.generate,"AS3"
+		| Flash ->
+			Genswf.generate swf_header,"swf"
+		| Neko ->
+			Genneko.generate,"neko"
+		| Js ->
+			Genjs.generate,"js"
+		| Lua ->
+			Genlua.generate,"lua"
+		| Php ->
+			Genphp.generate,"php"
+		| Cpp ->
+			Gencpp.generate,"cpp"
+		| Cs ->
+			Gencs.generate,"cs"
+		| Java ->
+			Genjava.generate,"java"
+		| Python ->
+			Genpy.generate,"python"
+		| Hl ->
+			Genhl.generate,"hl"
+		| Cross ->
+			assert false
+		in
+		Common.log com ("Generating " ^ name ^ ": " ^ com.file);
+		let t = Common.timer ("generate " ^ name) in
+		generate com;
+		t()
+	end
 
 let rec process_params create pl =
 	let each_params = ref [] in
@@ -722,7 +802,7 @@ and wait_loop verbose accept =
 	Typer.macro_enable_cache := true;
 	let current_stdin = ref None in
 	Typeload.parse_hook := (fun com2 file p ->
-		let ffile = Common.unique_full_path file in
+		let ffile = Path.unique_full_path file in
 		let is_display_file = ffile = (!Parser.resume_display).Ast.pfile in
 
 		match is_display_file, !current_stdin with
@@ -747,7 +827,7 @@ and wait_loop verbose accept =
 		Hashtbl.replace cache.c_modules (m.m_path,m.m_extra.m_sign) m;
 	in
 	let check_module_path com m p =
-		if m.m_extra.m_file <> Common.unique_full_path (Typeload.resolve_module_file com m.m_path (ref[]) p) then begin
+		if m.m_extra.m_file <> Path.unique_full_path (Typeload.resolve_module_file com m.m_path (ref[]) p) then begin
 			if verbose then print_endline ("Module path " ^ s_type_path m.m_path ^ " has been changed");
 			raise Not_found;
 		end
@@ -788,7 +868,7 @@ and wait_loop verbose accept =
 								match load m.m_path p with
 								| None -> loop l
 								| Some (file,_) ->
-									if Common.unique_full_path file <> m.m_extra.m_file then begin
+									if Path.unique_full_path file <> m.m_extra.m_file then begin
 										if verbose then print_endline ("Library file was changed for " ^ s_type_path m.m_path);
 										raise Not_found;
 									end
@@ -871,7 +951,7 @@ and wait_loop verbose accept =
 			| Some com -> cache_context com
 		in
 		let create params =
-			let ctx = create_context params in
+			let ctx = Initialize.create_context params in
 			ctx.flush <- (fun() ->
 				incr compilation_step;
 				compilation_mark := !mark_loop;
@@ -1105,21 +1185,15 @@ try
 				l
 		in
 		let parts = Str.split_delim (Str.regexp "[;:]") p in
-		com.class_path <- "" :: List.map add_trailing_slash (loop parts)
+		com.class_path <- "" :: List.map Path.add_trailing_slash (loop parts)
 	with
 		Not_found ->
 			if Sys.os_type = "Unix" then
 				com.class_path <- ["/usr/lib/haxe/std/";"/usr/share/haxe/std/";"/usr/local/lib/haxe/std/";"/usr/lib/haxe/extraLibs/";"/usr/local/lib/haxe/extraLibs/";""]
 			else
-				let base_path = add_trailing_slash (get_real_path (try executable_path() with _ -> "./")) in
+				let base_path = Path.add_trailing_slash (Path.get_real_path (try executable_path() with _ -> "./")) in
 				com.class_path <- [base_path ^ "std/";base_path ^ "extraLibs/";""]);
 	com.std_path <- List.filter (fun p -> ExtString.String.ends_with p "std/" || ExtString.String.ends_with p "std\\") com.class_path;
-	let set_platform pf file =
-		if com.platform <> Cross then failwith "Multiple targets";
-		Common.init_platform com pf;
-		com.file <- file;
-		if (pf = Flash) && file_extension file = "swc" then Common.define com Define.Swc;
-	in
 	let define f = Arg.Unit (fun () -> Common.define com f) in
 	let process_ref = ref (fun args -> ()) in
 	let process_libs() =
@@ -1135,41 +1209,41 @@ try
 	let basic_args_spec = [
 		("-cp",Arg.String (fun path ->
 			process_libs();
-			com.class_path <- add_trailing_slash path :: com.class_path
+			com.class_path <- Path.add_trailing_slash path :: com.class_path
 		),"<path> : add a directory to find source files");
-		("-js",Arg.String (set_platform Js),"<file> : compile code to JavaScript file");
-		("-lua",Arg.String (set_platform Lua),"<file> : compile code to Lua file");
-		("-swf",Arg.String (set_platform Flash),"<file> : compile code to Flash SWF file");
+		("-js",Arg.String (Initialize.set_platform com Js),"<file> : compile code to JavaScript file");
+		("-lua",Arg.String (Initialize.set_platform com Lua),"<file> : compile code to Lua file");
+		("-swf",Arg.String (Initialize.set_platform com Flash),"<file> : compile code to Flash SWF file");
 		("-as3",Arg.String (fun dir ->
-			set_platform Flash dir;
+			Initialize.set_platform com Flash dir;
 			Common.define com Define.As3;
 			Common.define com Define.NoInline;
 		),"<directory> : generate AS3 code into target directory");
-		("-neko",Arg.String (set_platform Neko),"<file> : compile code to Neko Binary");
+		("-neko",Arg.String (Initialize.set_platform com Neko),"<file> : compile code to Neko Binary");
 		("-php",Arg.String (fun dir ->
 			classes := (["php"],"Boot") :: !classes;
-			set_platform Php dir;
+			Initialize.set_platform com Php dir;
 		),"<directory> : generate PHP code into target directory");
 		("-cpp",Arg.String (fun dir ->
-			set_platform Cpp dir;
+			Initialize.set_platform com Cpp dir;
 		),"<directory> : generate C++ code into target directory");
 		("-cppia",Arg.String (fun file ->
-			set_platform Cpp file;
+			Initialize.set_platform com Cpp file;
 			Common.define com Define.Cppia;
 		),"<file> : generate Cppia code into target file");
 		("-cs",Arg.String (fun dir ->
 			cp_libs := "hxcs" :: !cp_libs;
-			set_platform Cs dir;
+			Initialize.set_platform com Cs dir;
 		),"<directory> : generate C# code into target directory");
 		("-java",Arg.String (fun dir ->
 			cp_libs := "hxjava" :: !cp_libs;
-			set_platform Java dir;
+			Initialize.set_platform com Java dir;
 		),"<directory> : generate Java code into target directory");
 		("-python",Arg.String (fun dir ->
-			set_platform Python dir;
+			Initialize.set_platform com Python dir;
 		),"<file> : generate Python code as target file");
 		("-hl",Arg.String (fun file ->
-			set_platform Hl file;
+			Initialize.set_platform com Hl file;
 		),"<file> : compile HL code as target file");
 		("-xml",Arg.String (fun file ->
 			Parser.use_doc := true;
@@ -1177,7 +1251,7 @@ try
 		),"<file> : generate XML types description");
 		("-main",Arg.String (fun cl ->
 			if com.main_class <> None then raise (Arg.Bad "Multiple -main");
-			let cpath = make_type_path cl in
+			let cpath = Path.parse_type_path cl in
 			com.main_class <- Some cpath;
 			classes := cpath :: !classes
 		),"<class> : select startup class");
@@ -1253,9 +1327,9 @@ try
 		),"<arg> : pass option <arg> to the native Java/C# compiler");
 		("-x", Arg.String (fun file ->
 			let neko_file = file ^ ".n" in
-			set_platform Neko neko_file;
+			Initialize.set_platform com Neko neko_file;
 			if com.main_class = None then begin
-				let cpath = make_type_path file in
+				let cpath = Path.parse_type_path file in
 				com.main_class <- Some cpath;
 				classes := cpath :: !classes
 			end;
@@ -1367,7 +1441,7 @@ try
 				Common.define_value com Define.Display (if smode <> "" then smode else "1");
 				Parser.use_doc := true;
 				Parser.resume_display := {
-					Ast.pfile = Common.unique_full_path file;
+					Ast.pfile = Path.unique_full_path file;
 					Ast.pmin = pos;
 					Ast.pmax = pos;
 				};
@@ -1398,7 +1472,7 @@ try
 		),"<package:target> : remap a package to another one");
 		("--interp", Arg.Unit (fun() ->
 			Common.define com Define.Interp;
-			set_platform Neko "";
+			Initialize.set_platform com Neko "";
 			interp := true;
 		),": interpret the program using internal macro system");
 		("--macro", Arg.String (fun e ->
@@ -1454,8 +1528,8 @@ try
 		),": print help for all compiler metadatas");
 	] in
 	let args_callback cl =
-		let path,name = make_path cl in
-		if starts_uppercase name then
+		let path,name = Path.parse_path cl in
+		if Path.starts_uppercase name then
 			classes := (path,name) :: !classes
 		else begin
 			force_typing := true;
@@ -1487,110 +1561,8 @@ try
 		com.warning <- if com.display.dms_error_policy = EPCollect then (fun s p -> add_diagnostics_message com s p DisplayTypes.DiagnosticsSeverity.Warning) else message ctx;
 		com.error <- error ctx;
 	end;
-	begin match com.display.dms_display_file_policy with
-		| DFPNo ->
-			()
-		| dfp ->
-			if dfp = DFPOnly then begin
-				classes := [];
-				com.main_class <- None;
-			end;
-			let real = get_real_path (!Parser.resume_display).Ast.pfile in
-			(match get_module_path_from_file_path com real with
-			| Some path ->
-				if com.display.dms_kind = DMPackage then raise (Display.DisplayPackage (fst path));
-				classes := path :: !classes
-			| None ->
-				if not (Sys.file_exists real) then failwith "Display file does not exist";
-				(match List.rev (ExtString.String.nsplit real path_sep) with
-				| file :: _ when file.[0] >= 'a' && file.[1] <= 'z' -> failwith ("Display file '" ^ file ^ "' should not start with a lowercase letter")
-				| _ -> ());
-				failwith "Display file was not found in class path"
-			);
-			Common.log com ("Display file : " ^ real);
-			Common.log com ("Classes found : ["  ^ (String.concat "," (List.map Ast.s_type_path !classes)) ^ "]");
-	end;
-	let add_std dir =
-		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
-	in
-	let ext = (match com.platform with
-		| Cross ->
-			(* no platform selected *)
-			set_platform Cross "";
-			"?"
-		| Flash ->
-			let rec loop = function
-				| [] -> ()
-				| (v,_) :: _ when v > com.flash_version -> ()
-				| (v,def) :: l ->
-					Common.raw_define com ("flash" ^ def);
-					loop l
-			in
-			loop Common.flash_versions;
-			Common.raw_define com "flash";
-			com.package_rules <- PMap.remove "flash" com.package_rules;
-			add_std "flash";
-			"swf"
-		| Neko ->
-			add_std "neko";
-			"n"
-		| Js ->
-			if not (PMap.exists (fst (Define.infos Define.JqueryVer)) com.defines) then
-				Common.define_value com Define.JqueryVer "11204";
-
-			let es_version =
-				try
-					int_of_string (Common.defined_value com Define.JsEs)
-				with
-				| Not_found ->
-					(Common.define_value com Define.JsEs "5"; 5)
-				| _ ->
-					0
-			in
-
-			if es_version < 3 || es_version = 4 then (* we don't support ancient and there's no 4th *)
-				failwith "Invalid -D js-es value";
-
-			if es_version >= 5 then Common.raw_define com "js-es5"; (* backward-compatibility *)
-
-			add_std "js";
-			"js"
-		| Lua ->
-			add_std "lua";
-			"lua"
-		| Php ->
-			add_std "php";
-			"php"
-		| Cpp ->
-			Common.define_value com Define.HxcppApiLevel "330";
-			add_std "cpp";
-			if Common.defined com Define.Cppia then
-				classes := (make_path "cpp.cppia.HostClasses" ) :: !classes;
-			"cpp"
-		| Cs ->
-			let old_flush = ctx.flush in
-			ctx.flush <- (fun () ->
-				com.net_libs <- [];
-				old_flush()
-			);
-			Gencs.before_generate com;
-			add_std "cs"; "cs"
-		| Java ->
-			let old_flush = ctx.flush in
-			ctx.flush <- (fun () ->
-				List.iter (fun (_,_,close,_,_) -> close()) com.java_libs;
-				com.java_libs <- [];
-				old_flush()
-			);
-			Genjava.before_generate com;
-			add_std "java"; "java"
-		| Python ->
-			add_std "python";
-			"python"
-		| Hl ->
-			add_std "hl";
-			"hl"
-	) in
+	Display.process_display_file com classes;
+	let ext = Initialize.initialize_target ctx com classes in
 	(* if we are at the last compilation step, allow all packages accesses - in case of macros or opening another project file *)
 	if com.display.dms_display then begin
 		if 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;
@@ -1629,58 +1601,10 @@ try
 		com.main <- main;
 		com.types <- types;
 		com.modules <- modules;
-		begin match com.display.dms_kind with
-			| DMUsage with_definition ->
-				let symbols,relations = Display.Statistics.collect_statistics tctx in
-				let rec loop acc relations = match relations with
-					| (Display.Statistics.Referenced,p) :: relations -> loop (p :: acc) relations
-					| _ :: relations -> loop acc relations
-					| [] -> acc
-				in
-				let usages = Hashtbl.fold (fun p sym acc ->
-					if Display.Statistics.is_usage_symbol sym then begin
-						let acc = if with_definition then p :: acc else acc in
-						(try loop acc (Hashtbl.find relations p)
-						with Not_found -> acc)
-					end else
-						acc
-				) symbols [] in
-				let usages = List.sort (fun p1 p2 ->
-					let c = compare p1.pfile p2.pfile in
-					if c <> 0 then c else compare p1.pmin p2.pmin
-				) usages in
-				raise (Display.DisplayPosition usages)
-			| DMDiagnostics global ->
-				Display.Diagnostics.prepare com global;
-				raise (Display.Diagnostics (Display.Diagnostics.print_diagnostics tctx global))
-			| DMStatistics ->
-				let stats = Display.Statistics.collect_statistics tctx in
-				raise (Display.Statistics (Display.StatisticsPrinter.print_statistics stats))
-			| DMModuleSymbols filter ->
-				let symbols = com.shared.shared_display_information.document_symbols in
-				let symbols = match !global_cache with
-					| None -> symbols
-					| Some cache ->
-						let rec loop acc com =
-							let com_sign = get_signature com in
-							let acc = Hashtbl.fold (fun (file,sign) (_,data) acc ->
-								if (filter <> None || Display.is_display_file file) && com_sign = sign then
-									(file,Display.DocumentSymbols.collect_module_symbols data) :: acc
-								else
-									acc
-							) cache.c_files acc in
-							match com.get_macros() with None -> acc | Some com -> loop acc com
-						in
-						loop symbols com
-				in
-				raise (Display.ModuleSymbols(Display.DocumentSymbols.print_module_symbols com symbols filter))
-			| _ -> ()
-		end;
+		Display.process_global_display_mode com tctx;
 		Filters.run com tctx main;
+		t();
 		if ctx.has_error then raise Abort;
-		(* check file extension. In case of wrong commandline, we don't want
-			to accidentaly delete a source file. *)
-		if not !no_output && file_extension com.file = ext then delete_file com.file;
 		(match !xml_out with
 		| None -> ()
 		| Some "hx" ->
@@ -1689,58 +1613,7 @@ try
 			Common.log com ("Generating xml : " ^ file);
 			Common.mkdir_from_path file;
 			Genxml.generate com file);
-		if com.platform = Flash || com.platform = Cpp then List.iter (Codegen.fix_overrides com) com.types;
-		if Common.defined com Define.Dump then Codegen.Dump.dump_types com;
-		if Common.defined com Define.DumpDependencies then Codegen.Dump.dump_dependencies com;
-		t();
-		if not !no_output then begin match com.platform with
-			| Neko when !interp -> ()
-			| Cpp when Common.defined com Define.Cppia -> ()
-			| Cpp | Cs | Java | Php -> Common.mkdir_from_path (com.file ^ "/.")
-			| _ -> Common.mkdir_from_path com.file
-		end;
-		if not !no_output then begin
-			if !interp then begin
-				let ctx = Interp.create com (Typer.make_macro_api tctx Ast.null_pos) in
-				Interp.add_types ctx com.types (fun t -> ());
-				(match com.main with
-				| None -> ()
-				| Some e -> ignore(Interp.eval_expr ctx e));
-			end else if com.platform = Cross then
-				()
-			else begin
-				let generate,name = match com.platform with
-				| Flash when Common.defined com Define.As3 ->
-					Genas3.generate,"AS3"
-				| Flash ->
-					Genswf.generate !swf_header,"swf"
-				| Neko ->
-					Genneko.generate,"neko"
-				| Js ->
-					Genjs.generate,"js"
-				| Lua ->
-					Genlua.generate,"lua"
-				| Php ->
-					Genphp.generate,"php"
-				| Cpp ->
-					Gencpp.generate,"cpp"
-				| Cs ->
-					Gencs.generate,"cs"
-				| Java ->
-					Genjava.generate,"java"
-				| Python ->
-					Genpy.generate,"python"
-				| Hl ->
-					Genhl.generate,"hl"
-				| Cross ->
-					assert false
-				in
-				Common.log com ("Generating " ^ name ^ ": " ^ com.file);
-				let t = Common.timer ("generate " ^ name) in
-				generate com;
-				t()
-			end
-		end
+		if not !no_output then generate tctx ext !xml_out !interp !swf_header;
 	end;
 	Sys.catch_break false;
 	List.iter (fun f -> f()) (List.rev com.callbacks.after_generation);
@@ -1835,7 +1708,7 @@ let args = List.tl (Array.to_list Sys.argv) in
 	let host, port = (try ExtString.String.split server ":" with _ -> "127.0.0.1", server) in
 	do_connect host (try int_of_string port with _ -> failwith "Invalid HAXE_COMPILATION_SERVER port") args
 with Not_found -> try
-	process_params create_context args
+	process_params Initialize.create_context args
 with Completion c ->
 	prerr_endline c;
 	exit 0

+ 1 - 1
src/optimization/dce.ml

@@ -570,7 +570,7 @@ let run com main full =
 	let dce = {
 		com = com;
 		full = full;
-		std_dirs = if full then [] else List.map Common.unique_full_path com.std_path;
+		std_dirs = if full then [] else List.map Path.unique_full_path com.std_path;
 		debug = Common.defined com Define.DceDebug;
 		added_fields = [];
 		follow_expr = expr;

+ 114 - 0
src/path.ml

@@ -0,0 +1,114 @@
+let get_path_parts f =
+	(*
+		this function is quite weird: it tries to determine whether the given
+		argument is a .hx file path with slashes or a dotted module path and
+		based on that it returns path "parts", which are basically a list of
+		either folders or packages (which are folders too) appended by the module name
+
+		TODO: i started doubting my sanity while writing this comment, let's somehow
+		refactor this stuff so it doesn't mix up file and module paths and doesn't introduce
+		the weird "path part" entity.
+	*)
+	let l = String.length f in
+	if l > 3 && (String.sub f (l-3) 3) = ".hx" then
+		let f = String.sub f 0 (l-3) in (* strip the .hx *)
+		ExtString.String.nsplit (String.concat "/" (ExtString.String.nsplit f "\\")) "/" (* TODO: wouldn't it be faster to Str.split here? *)
+	else
+		ExtString.String.nsplit f "."
+
+let parse_path f =
+	let cl = get_path_parts f in
+	let error msg =
+		let msg = "Could not process argument " ^ f ^ "\n" ^ msg in
+		failwith msg
+	in
+	let invalid_char x =
+		for i = 1 to String.length x - 1 do
+			match x.[i] with
+			| 'A'..'Z' | 'a'..'z' | '0'..'9' | '_' -> ()
+			| c -> error ("invalid character: " ^ (String.make 1 c))
+		done
+	in
+	let rec loop = function
+		| [] ->
+			error "empty part"
+		| [x] ->
+			invalid_char x;
+			[],x
+		| x :: l ->
+			if String.length x = 0 then
+				error "empty part"
+			else if x.[0] < 'a' || x.[0] > 'z' then
+				error "Package name must start with a lower case character";
+			invalid_char x;
+			let path,name = loop l in
+			x :: path,name
+	in
+	loop cl
+
+let starts_uppercase x =
+	x.[0] = '_' || (x.[0] >= 'A' && x.[0] <= 'Z')
+
+let check_uppercase x =
+	if String.length x = 0 then
+		failwith "empty part"
+	else if not (starts_uppercase x) then
+		failwith "Class name must start with uppercase character"
+
+let parse_type_path s =
+	let pack,name = parse_path s in
+	check_uppercase name;
+	pack,name
+
+let path_regex = Str.regexp "[/\\]+"
+let normalize_path path =
+	let rec normalize acc m =
+		match m with
+		| [] ->
+			List.rev acc
+		| Str.Text "." :: Str.Delim _ :: tl when acc = [] ->
+			normalize [] tl
+		| Str.Text ".." :: Str.Delim _ :: tl ->
+			(match acc with
+			| [] -> raise Exit
+			| _ :: acc -> normalize acc tl)
+		| Str.Text t :: Str.Delim _ :: tl ->
+			normalize (t :: acc) tl
+		| Str.Delim _ :: tl ->
+			normalize ("" :: acc) tl
+		| Str.Text t :: [] ->
+			List.rev (t :: acc)
+		| Str.Text _ :: Str.Text  _ :: _ ->
+			assert false
+	in
+	String.concat "/" (normalize [] (Str.full_split path_regex path))
+
+let is_windows = Sys.os_type = "Win32" || Sys.os_type = "Cygwin"
+let path_sep = if is_windows then "\\" else "/"
+
+(** Returns absolute path. Doesn't fix path case on Windows. *)
+let get_full_path f = try Extc.get_full_path f with _ -> f
+
+(** Returns absolute path (on Windows ensures proper case with drive letter upper-cased)
+    Use for returning positions from IDE support functions *)
+let get_real_path =
+	if is_windows then
+		(fun p -> try Extc.get_real_path p with _ -> p)
+	else
+		get_full_path
+
+(** Returns absolute path guaranteed to be the same for different letter case.
+    Use where equality comparison is required, lowercases the path on Windows *)
+let unique_full_path =
+	if is_windows then
+		(fun f -> String.lowercase (get_full_path f))
+	else
+		get_full_path
+
+let add_trailing_slash p =
+	let l = String.length p in
+	if l = 0 then
+		"./"
+	else match p.[l-1] with
+		| '\\' | '/' -> p
+		| _ -> p ^ "/"

+ 3 - 3
src/syntax/parser.ml

@@ -90,10 +90,10 @@ let type_path sl in_import = match sl with
 
 let is_resuming p =
 	let p2 = !resume_display in
-	p.pmax = p2.pmin && Common.unique_full_path p.pfile = p2.pfile
+	p.pmax = p2.pmin && Path.unique_full_path p.pfile = p2.pfile
 
 let set_resume p =
-	resume_display := { p with pfile = Common.unique_full_path p.pfile }
+	resume_display := { p with pfile = Path.unique_full_path p.pfile }
 
 let is_dollar_ident e = match fst e with
 	| EConst (Ident n) when n.[0] = '$' ->
@@ -1631,7 +1631,7 @@ let parse ctx code =
 	and enter_macro p =
 		let tk, e = parse_macro_cond false sraw in
 		let tk = (match tk with None -> Lexer.token code | Some tk -> tk) in
-		if is_true (eval ctx e) || (match fst e with EConst (Ident "macro") when Common.unique_full_path p.pfile = (!resume_display).pfile -> true | _ -> false) then begin
+		if is_true (eval ctx e) || (match fst e with EConst (Ident "macro") when Path.unique_full_path p.pfile = (!resume_display).pfile -> true | _ -> false) then begin
 			mstack := p :: !mstack;
 			tk
 		end else

+ 0 - 71
src/typing/common.ml

@@ -1167,77 +1167,6 @@ let find_file ctx f =
 		| None -> raise Not_found
 		| Some f -> f)
 
-let is_windows = Sys.os_type = "Win32" || Sys.os_type = "Cygwin"
-let path_sep = if is_windows then "\\" else "/"
-
-(** Returns absolute path. Doesn't fix path case on Windows. *)
-let get_full_path f = try Extc.get_full_path f with _ -> f
-
-(** Returns absolute path (on Windows ensures proper case with drive letter upper-cased)
-    Use for returning positions from IDE support functions *)
-let get_real_path =
-	if is_windows then
-		(fun p -> try Extc.get_real_path p with _ -> p)
-	else
-		get_full_path
-
-(** Returns absolute path guaranteed to be the same for different letter case.
-    Use where equality comparison is required, lowercases the path on Windows *)
-let unique_full_path =
-	if is_windows then
-		(fun f -> String.lowercase (get_full_path f))
-	else
-		get_full_path
-
-let get_path_parts f =
-	(*
-		this function is quite weird: it tries to determine whether the given
-		argument is a .hx file path with slashes or a dotted module path and
-		based on that it returns path "parts", which are basically a list of
-		either folders or packages (which are folders too) appended by the module name
-
-		TODO: i started doubting my sanity while writing this comment, let's somehow
-		refactor this stuff so it doesn't mix up file and module paths and doesn't introduce
-		the weird "path part" entity.
-	*)
-	let l = String.length f in
-	if l > 3 && (String.sub f (l-3) 3) = ".hx" then
-		let f = String.sub f 0 (l-3) in (* strip the .hx *)
-		ExtString.String.nsplit (String.concat "/" (ExtString.String.nsplit f "\\")) "/" (* TODO: wouldn't it be faster to Str.split here? *)
-	else
-		ExtString.String.nsplit f "."
-
-let add_trailing_slash p =
-	let l = String.length p in
-	if l = 0 then
-		"./"
-	else match p.[l-1] with
-		| '\\' | '/' -> p
-		| _ -> p ^ "/"
-
-let path_regex = Str.regexp "[/\\]+"
-let normalize_path path =
-	let rec normalize acc m =
-		match m with
-		| [] ->
-			List.rev acc
-		| Str.Text "." :: Str.Delim _ :: tl when acc = [] ->
-			normalize [] tl
-		| Str.Text ".." :: Str.Delim _ :: tl ->
-			(match acc with
-			| [] -> raise Exit
-			| _ :: acc -> normalize acc tl)
-		| Str.Text t :: Str.Delim _ :: tl ->
-			normalize (t :: acc) tl
-		| Str.Delim _ :: tl ->
-			normalize ("" :: acc) tl
-		| Str.Text t :: [] ->
-			List.rev (t :: acc)
-		| Str.Text _ :: Str.Text  _ :: _ ->
-			assert false
-	in
-	String.concat "/" (normalize [] (Str.full_split path_regex path))
-
 let rec mkdir_recursive base dir_list =
 	match dir_list with
 	| [] -> ()

+ 1 - 1
src/typing/typecore.ml

@@ -370,7 +370,7 @@ let exc_protect ctx f (where:string) =
 
 let fake_modules = Hashtbl.create 0
 let create_fake_module ctx file =
-	let file = Common.unique_full_path file in
+	let file = Path.unique_full_path file in
 	let mdep = (try Hashtbl.find fake_modules file with Not_found ->
 		let mdep = {
 			m_id = alloc_mid();

+ 5 - 5
src/typing/typeload.ml

@@ -73,7 +73,7 @@ let make_module ctx mpath file loadp =
 		m_id = alloc_mid();
 		m_path = mpath;
 		m_types = [];
-		m_extra = module_extra (Common.unique_full_path file) (Common.get_signature ctx.com) (file_time file) (if ctx.in_macro then MMacro else MCode);
+		m_extra = module_extra (Path.unique_full_path file) (Common.get_signature ctx.com) (file_time file) (if ctx.in_macro then MMacro else MCode);
 	} in
 	m
 
@@ -3488,8 +3488,8 @@ let type_types_into_module ctx m tdecls p =
 	ctx
 
 let handle_import_hx ctx m decls p =
-	let path_split = List.tl (List.rev (get_path_parts m.m_extra.m_file)) in
-	let join l = String.concat path_sep (List.rev ("import.hx" :: l)) in
+	let path_split = List.tl (List.rev (Path.get_path_parts m.m_extra.m_file)) in
+	let join l = String.concat Path.path_sep (List.rev ("import.hx" :: l)) in
 	let rec loop path pack = match path,pack with
 		| _,[] -> [join path]
 		| (p :: path),(_ :: pack) -> (join (p :: path)) :: (loop path pack)
@@ -3567,8 +3567,8 @@ let resolve_module_file com m remap p =
 	(* if we try to load a std.xxxx class and resolve a real std file, the package name is not valid, ignore *)
 	(match fst m with
 	| "std" :: _ ->
-		let file = Common.unique_full_path file in
-		if List.exists (fun path -> ExtString.String.starts_with file (try Common.unique_full_path path with _ -> path)) com.std_path then raise Not_found;
+		let file = Path.unique_full_path file in
+		if List.exists (fun path -> ExtString.String.starts_with file (try Path.unique_full_path path with _ -> path)) com.std_path then raise Not_found;
 	| _ -> ());
 	if !forbid then begin
 		let _, decls = (!parse_hook) com file p in

+ 1 - 1
src/typing/typer.ml

@@ -52,7 +52,7 @@ type object_decl_kind =
 let build_call_ref : (typer -> access_kind -> expr list -> with_type -> pos -> texpr) ref = ref (fun _ _ _ _ _ -> assert false)
 
 let mk_infos ctx p params =
-	let file = if ctx.in_macro then p.pfile else if Common.defined ctx.com Define.AbsolutePath then Common.get_full_path p.pfile else Filename.basename p.pfile in
+	let file = if ctx.in_macro then p.pfile else if Common.defined ctx.com Define.AbsolutePath then Path.get_full_path p.pfile else Filename.basename p.pfile in
 	(EObjectDecl (
 		("fileName" , (EConst (String file) , p)) ::
 		("lineNumber" , (EConst (Int (string_of_int (Lexer.get_error_line p))),p)) ::