Ver código fonte

Merge branch 'development' into hxb_server_cache_simn_cleanup

# Conflicts:
#	src/context/common.ml
#	src/core/tFunctions.ml
Simon Krajewski 1 ano atrás
pai
commit
74ff1ed578

+ 6 - 3
src/compiler/args.ml

@@ -116,19 +116,22 @@ let parse_args com =
 				| None -> com.main_class <- Some cpath);
 				| None -> com.main_class <- Some cpath);
 			actx.classes <- cpath :: actx.classes;
 			actx.classes <- cpath :: actx.classes;
 			Common.define com Define.Interp;
 			Common.define com Define.Interp;
-			set_platform com (!Globals.macro_platform) "";
+			set_platform com Eval "";
 			actx.interp <- true;
 			actx.interp <- true;
 		),"<class>","interpret the program using internal macro system");
 		),"<class>","interpret the program using internal macro system");
 		("Target",["--interp"],[], Arg.Unit (fun() ->
 		("Target",["--interp"],[], Arg.Unit (fun() ->
 			Common.define com Define.Interp;
 			Common.define com Define.Interp;
-			set_platform com (!Globals.macro_platform) "";
+			set_platform com Eval "";
 			actx.interp <- true;
 			actx.interp <- true;
 		),"","interpret the program using internal macro system");
 		),"","interpret the program using internal macro system");
 		("Target",["--run"],[], Arg.Unit (fun() ->
 		("Target",["--run"],[], Arg.Unit (fun() ->
 			raise (Arg.Bad "--run requires an argument: a Haxe module name")
 			raise (Arg.Bad "--run requires an argument: a Haxe module name")
 		), "<module> [args...]","interpret a Haxe module with command line arguments");
 		), "<module> [args...]","interpret a Haxe module with command line arguments");
 		("Compilation",["-p";"--class-path"],["-cp"],Arg.String (fun path ->
 		("Compilation",["-p";"--class-path"],["-cp"],Arg.String (fun path ->
-			com.class_path <- Path.add_trailing_slash path :: com.class_path
+			com.class_paths#add (new ClassPath.directory_class_path (Path.add_trailing_slash path) User);
+		),"<path>","add a directory to find source files");
+		("Compilation",[],["-libcp"],Arg.String (fun path ->
+			com.class_paths#add (new ClassPath.directory_class_path (Path.add_trailing_slash path) Lib);
 		),"<path>","add a directory to find source files");
 		),"<path>","add a directory to find source files");
 		("Compilation",["--hxb-lib"],["-hxb-lib"],Arg.String (fun file ->
 		("Compilation",["--hxb-lib"],["-hxb-lib"],Arg.String (fun file ->
 			let lib = create_native_lib file false HxbLib in
 			let lib = create_native_lib file false HxbLib in

+ 4 - 3
src/compiler/compilationCache.ml

@@ -1,11 +1,12 @@
 open Globals
 open Globals
 open Ast
 open Ast
+open Path
 open Json
 open Json
 open Type
 open Type
 open Define
 open Define
 
 
 type cached_file = {
 type cached_file = {
-	c_file_path : string;
+	c_file_path : ClassPaths.resolved_file;
 	c_time : float;
 	c_time : float;
 	c_package : string list;
 	c_package : string list;
 	c_decls : type_decl list;
 	c_decls : type_decl list;
@@ -155,13 +156,13 @@ class cache = object(self)
 			Hashtbl.add contexts sign cache;
 			Hashtbl.add contexts sign cache;
 			cache
 			cache
 
 
-	method add_info sign desc platform class_path defines =
+	method add_info sign desc platform (class_paths : ClassPaths.class_paths) defines =
 		let cc = self#get_context sign in
 		let cc = self#get_context sign in
 		let jo = JObject [
 		let jo = JObject [
 			"index",JInt cc#get_index;
 			"index",JInt cc#get_index;
 			"desc",JString desc;
 			"desc",JString desc;
 			"platform",JString (platform_name platform);
 			"platform",JString (platform_name platform);
-			"classPaths",JArray (List.map (fun s -> JString s) class_path);
+			"classPaths",JArray (List.map (fun s -> JString s) class_paths#as_string_list);
 			"signature",JString (Digest.to_hex sign);
 			"signature",JString (Digest.to_hex sign);
 			"defines",JArray (PMap.foldi (fun k v acc -> JObject [
 			"defines",JArray (PMap.foldi (fun k v acc -> JObject [
 				"key",JString k;
 				"key",JString k;

+ 26 - 17
src/compiler/compiler.ml

@@ -78,8 +78,15 @@ let run_command ctx cmd =
 module Setup = struct
 module Setup = struct
 	let initialize_target ctx com actx =
 	let initialize_target ctx com actx =
 		init_platform com;
 		init_platform com;
+		com.class_paths#lock_context (platform_name com.platform) false;
 		let add_std dir =
 		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
+			com.class_paths#modify_inplace (fun cp -> match cp#scope with
+				| Std ->
+					let cp' = new ClassPath.directory_class_path (cp#path ^ dir ^ "/_std/") StdTarget in
+					cp :: [cp']
+				| _ ->
+					[cp]
+			);
 		in
 		in
 		match com.platform with
 		match com.platform with
 			| Cross ->
 			| Cross ->
@@ -170,7 +177,6 @@ module Setup = struct
 
 
 	let create_typer_context ctx macros =
 	let create_typer_context ctx macros =
 		let com = ctx.com in
 		let com = ctx.com in
-		Common.log com ("Classpath: " ^ (String.concat ";" com.class_path));
 		let buffer = Buffer.create 64 in
 		let buffer = Buffer.create 64 in
 		Buffer.add_string buffer "Defines: ";
 		Buffer.add_string buffer "Defines: ";
 		PMap.iter (fun k v -> match v with
 		PMap.iter (fun k v -> match v with
@@ -185,6 +191,8 @@ module Setup = struct
 	let executable_path() =
 	let executable_path() =
 		Extc.executable_path()
 		Extc.executable_path()
 
 
+	open ClassPath
+
 	let get_std_class_paths () =
 	let get_std_class_paths () =
 		try
 		try
 			let p = Sys.getenv "HAXE_STD_PATH" in
 			let p = Sys.getenv "HAXE_STD_PATH" in
@@ -198,7 +206,7 @@ module Setup = struct
 					l
 					l
 			in
 			in
 			let parts = Str.split_delim (Str.regexp "[;:]") p in
 			let parts = Str.split_delim (Str.regexp "[;:]") p in
-			"" :: List.map Path.add_trailing_slash (loop parts)
+			List.map (fun s -> Path.add_trailing_slash s,Std) (loop parts)
 		with Not_found ->
 		with Not_found ->
 			let base_path = Path.get_real_path (try executable_path() with _ -> "./") in
 			let base_path = Path.get_real_path (try executable_path() with _ -> "./") in
 			if Sys.os_type = "Unix" then
 			if Sys.os_type = "Unix" then
@@ -206,17 +214,22 @@ module Setup = struct
 				let lib_path = Filename.concat prefix_path "lib" in
 				let lib_path = Filename.concat prefix_path "lib" in
 				let share_path = Filename.concat prefix_path "share" in
 				let share_path = Filename.concat prefix_path "share" in
 				[
 				[
-					"";
-					Path.add_trailing_slash (Filename.concat share_path "haxe/std");
-					Path.add_trailing_slash (Filename.concat lib_path "haxe/std");
-					Path.add_trailing_slash (Filename.concat base_path "std");
+					(Path.add_trailing_slash (Filename.concat share_path "haxe/std"),Std);
+					(Path.add_trailing_slash (Filename.concat lib_path "haxe/std"),Std);
+					(Path.add_trailing_slash (Filename.concat base_path "std"),Std);
 				]
 				]
 			else
 			else
 				[
 				[
-					"";
-					Path.add_trailing_slash (Filename.concat base_path "std");
+					(Path.add_trailing_slash (Filename.concat base_path "std"),Std);
 				]
 				]
 
 
+	let init_std_class_paths com =
+		com.class_paths#add com.empty_class_path;
+		List.iter (fun (s,scope) ->
+			let cp = new ClassPath.directory_class_path s scope in
+			com.class_paths#add cp
+		) (List.rev (get_std_class_paths ()))
+
 	let setup_common_context ctx =
 	let setup_common_context ctx =
 		let com = ctx.com in
 		let com = ctx.com in
 		ctx.com.print <- ctx.comm.write_out;
 		ctx.com.print <- ctx.comm.write_out;
@@ -256,8 +269,7 @@ module Setup = struct
 		) (filter_messages false (fun _ -> true))));
 		) (filter_messages false (fun _ -> true))));
 		com.filter_messages <- (fun predicate -> (ctx.messages <- (List.rev (filter_messages true predicate))));
 		com.filter_messages <- (fun predicate -> (ctx.messages <- (List.rev (filter_messages true predicate))));
 		com.run_command <- run_command ctx;
 		com.run_command <- run_command ctx;
-		com.class_path <- get_std_class_paths ();
-		com.std_path <- List.filter (fun p -> ExtString.String.ends_with p "std/" || ExtString.String.ends_with p "std\\") com.class_path
+		init_std_class_paths com
 
 
 end
 end
 
 
@@ -274,7 +286,7 @@ let check_defines com =
 	end
 	end
 
 
 (** Creates the typer context and types [classes] into it. *)
 (** Creates the typer context and types [classes] into it. *)
-let do_type ctx mctx actx display_file_dot_path macro_cache_enabled =
+let do_type ctx mctx actx display_file_dot_path =
 	let com = ctx.com in
 	let com = ctx.com in
 	let t = Timer.timer ["typing"] in
 	let t = Timer.timer ["typing"] in
 	let cs = com.cs in
 	let cs = com.cs in
@@ -287,7 +299,6 @@ let do_type ctx mctx actx display_file_dot_path macro_cache_enabled =
 	) mctx (List.rev actx.config_macros) in
 	) mctx (List.rev actx.config_macros) in
 	enter_stage com CInitMacrosDone;
 	enter_stage com CInitMacrosDone;
 	ServerMessage.compiler_stage com;
 	ServerMessage.compiler_stage com;
-	MacroContext.macro_enable_cache := macro_cache_enabled;
 
 
 	let macros = match mctx with None -> None | Some mctx -> mctx.g.macros in
 	let macros = match mctx with None -> None | Some mctx -> mctx.g.macros in
 	Setup.init_native_libs com actx.native_libs;
 	Setup.init_native_libs com actx.native_libs;
@@ -339,8 +350,6 @@ let compile ctx actx callbacks =
 	(* Set up display configuration *)
 	(* Set up display configuration *)
 	DisplayProcessing.process_display_configuration ctx;
 	DisplayProcessing.process_display_configuration ctx;
 	let display_file_dot_path = DisplayProcessing.process_display_file com actx in
 	let display_file_dot_path = DisplayProcessing.process_display_file com actx in
-	let macro_cache_enabled = !MacroContext.macro_enable_cache in
-	MacroContext.macro_enable_cache := true;
 	let mctx = match com.platform with
 	let mctx = match com.platform with
 		| CustomTarget name ->
 		| CustomTarget name ->
 			begin try
 			begin try
@@ -365,7 +374,7 @@ let compile ctx actx callbacks =
 		if actx.cmds = [] && not actx.did_something then actx.raise_usage();
 		if actx.cmds = [] && not actx.did_something then actx.raise_usage();
 	end else begin
 	end else begin
 		(* Actual compilation starts here *)
 		(* Actual compilation starts here *)
-		let (tctx,display_file_dot_path) = do_type ctx mctx actx display_file_dot_path macro_cache_enabled in
+		let (tctx,display_file_dot_path) = do_type ctx mctx actx display_file_dot_path in
 		DisplayProcessing.handle_display_after_typing ctx tctx display_file_dot_path;
 		DisplayProcessing.handle_display_after_typing ctx tctx display_file_dot_path;
 		finalize_typing ctx tctx;
 		finalize_typing ctx tctx;
 		let is_diagnostics = is_diagnostics com in
 		let is_diagnostics = is_diagnostics com in
@@ -540,7 +549,7 @@ module HighLevel = struct
 				if l = "" then
 				if l = "" then
 					acc
 					acc
 				else if l.[0] <> '-' then
 				else if l.[0] <> '-' then
-					"-cp" :: l :: acc
+					"-libcp" :: l :: acc
 				else match (try ExtString.String.split l " " with _ -> l, "") with
 				else match (try ExtString.String.split l " " with _ -> l, "") with
 				| ("-L",dir) ->
 				| ("-L",dir) ->
 					"--neko-lib-path" :: (String.sub l 3 (String.length l - 3)) :: acc
 					"--neko-lib-path" :: (String.sub l 3 (String.length l - 3)) :: acc

+ 5 - 4
src/compiler/displayProcessing.ml

@@ -121,6 +121,7 @@ let process_display_file com actx =
 		let rec loop = function
 		let rec loop = function
 			| [] -> None
 			| [] -> None
 			| cp :: l ->
 			| cp :: l ->
+				let cp = cp#path in
 				let cp = (if cp = "" then "./" else cp) in
 				let cp = (if cp = "" then "./" else cp) in
 				let c = Path.add_trailing_slash (Path.get_real_path cp) in
 				let c = Path.add_trailing_slash (Path.get_real_path cp) in
 				let clen = String.length c in
 				let clen = String.length c in
@@ -135,7 +136,7 @@ let process_display_file com actx =
 				end else
 				end else
 					loop l
 					loop l
 		in
 		in
-		loop com.class_path
+		loop com.class_paths#as_list
 	in
 	in
 	match com.display.dms_display_file_policy with
 	match com.display.dms_display_file_policy with
 		| DFPNo ->
 		| DFPNo ->
@@ -223,7 +224,7 @@ let load_display_module_in_macro tctx display_file_dot_path clear = match displa
 
 
 let load_display_file_standalone (ctx : Typecore.typer) file =
 let load_display_file_standalone (ctx : Typecore.typer) file =
 	let com = ctx.com in
 	let com = ctx.com in
-	let pack,decls = TypeloadParse.parse_module_file com file null_pos in
+	let pack,decls = TypeloadParse.parse_module_file com (ClassPaths.create_resolved_file file ctx.com.empty_class_path) null_pos in
 	let path = Path.FilePath.parse file in
 	let path = Path.FilePath.parse file in
 	let name = match path.file_name with
 	let name = match path.file_name with
 		| None -> "?DISPLAY"
 		| None -> "?DISPLAY"
@@ -236,7 +237,7 @@ let load_display_file_standalone (ctx : Typecore.typer) file =
 			let parts = ExtString.String.nsplit dir (if path.backslash then "\\" else "/") in
 			let parts = ExtString.String.nsplit dir (if path.backslash then "\\" else "/") in
 			let parts = List.rev (ExtList.List.drop (List.length pack) (List.rev parts)) in
 			let parts = List.rev (ExtList.List.drop (List.length pack) (List.rev parts)) in
 			let dir = ExtString.String.join (if path.backslash then "\\" else "/") parts in
 			let dir = ExtString.String.join (if path.backslash then "\\" else "/") parts in
-			com.class_path <- dir :: com.class_path
+			com.class_paths#add (new ClassPath.directory_class_path dir User)
 	end;
 	end;
 	ignore(TypeloadModule.type_module ctx (pack,name) file ~dont_check_path:true decls null_pos)
 	ignore(TypeloadModule.type_module ctx (pack,name) file ~dont_check_path:true decls null_pos)
 
 
@@ -318,7 +319,7 @@ let process_global_display_mode com tctx =
 		let symbols =
 		let symbols =
 			let l = cs#get_context_files ((Define.get_signature com.defines) :: (match com.get_macros() with None -> [] | Some com -> [Define.get_signature com.defines])) in
 			let l = cs#get_context_files ((Define.get_signature com.defines) :: (match com.get_macros() with None -> [] | Some com -> [Define.get_signature com.defines])) in
 			List.fold_left (fun acc (file_key,cfile) ->
 			List.fold_left (fun acc (file_key,cfile) ->
-				let file = cfile.c_file_path in
+				let file = cfile.c_file_path.file in
 				if (filter <> None || DisplayPosition.display_position#is_in_file (com.file_keys#get file)) then
 				if (filter <> None || DisplayPosition.display_position#is_in_file (com.file_keys#get file)) then
 					(file,DocumentSymbols.collect_module_symbols (Some (file,get_module_name_of_cfile file cfile)) (filter = None) (cfile.c_package,cfile.c_decls)) :: acc
 					(file,DocumentSymbols.collect_module_symbols (Some (file,get_module_name_of_cfile file cfile)) (filter = None) (cfile.c_package,cfile.c_decls)) :: acc
 				else
 				else

+ 7 - 7
src/compiler/messageReporting.ml

@@ -54,13 +54,13 @@ let resolve_source file l1 p1 l2 p2 =
 	List.rev !lines
 	List.rev !lines
 
 
 let resolve_file ctx f =
 let resolve_file ctx f =
-		let ext = Common.extension f in
-		let second_ext = Common.extension (Common.remove_extension f) in
-		let platform_ext = "." ^ (platform_name_macro ctx) in
-		if platform_ext = second_ext then
-			(Common.remove_extension (Common.remove_extension f)) ^ ext
-		else
-			f
+	let ext = StringHelper.extension f in
+	let second_ext = StringHelper.extension (StringHelper.remove_extension f) in
+	let platform_ext = "." ^ (platform_name_macro ctx) in
+	if platform_ext = second_ext then
+		(StringHelper.remove_extension (StringHelper.remove_extension f)) ^ ext
+	else
+		f
 
 
 let error_printer file line = Printf.sprintf "%s:%d:" file line
 let error_printer file line = Printf.sprintf "%s:%d:" file line
 
 

+ 13 - 11
src/compiler/server.ml

@@ -42,9 +42,10 @@ let check_display_flush ctx f_otherwise = match ctx.com.json_out with
 
 
 let current_stdin = ref None
 let current_stdin = ref None
 
 
-let parse_file cs com file p =
+let parse_file cs com (rfile : ClassPaths.resolved_file) p =
 	let cc = CommonCache.get_cache com in
 	let cc = CommonCache.get_cache com in
-	let ffile = Path.get_full_path file
+	let file = rfile.file in
+	let ffile = Path.get_full_path rfile.file
 	and fkey = com.file_keys#get file in
 	and fkey = com.file_keys#get file in
 	let is_display_file = DisplayPosition.display_position#is_in_file (com.file_keys#get ffile) in
 	let is_display_file = DisplayPosition.display_position#is_in_file (com.file_keys#get ffile) in
 	match is_display_file, !current_stdin with
 	match is_display_file, !current_stdin with
@@ -58,7 +59,7 @@ let parse_file cs com file p =
 				if cfile.c_time <> ftime then raise Not_found;
 				if cfile.c_time <> ftime then raise Not_found;
 				Parser.ParseSuccess((cfile.c_package,cfile.c_decls),false,cfile.c_pdi)
 				Parser.ParseSuccess((cfile.c_package,cfile.c_decls),false,cfile.c_pdi)
 			with Not_found ->
 			with Not_found ->
-				let parse_result = TypeloadParse.parse_file com file p in
+				let parse_result = TypeloadParse.parse_file com rfile p in
 				let info,is_unusual = match parse_result with
 				let info,is_unusual = match parse_result with
 					| ParseError(_,_,_) -> "not cached, has parse error",true
 					| ParseError(_,_,_) -> "not cached, has parse error",true
 					| ParseSuccess(data,is_display_file,pdi) ->
 					| ParseSuccess(data,is_display_file,pdi) ->
@@ -66,7 +67,7 @@ let parse_file cs com file p =
 							if pdi.pd_errors <> [] then
 							if pdi.pd_errors <> [] then
 								"not cached, is display file with parse errors",true
 								"not cached, is display file with parse errors",true
 							else if com.display.dms_per_file then begin
 							else if com.display.dms_per_file then begin
-								cc#cache_file fkey ffile ftime data pdi;
+								cc#cache_file fkey rfile ftime data pdi;
 								"cached, is intact display file",true
 								"cached, is intact display file",true
 							end else
 							end else
 								"not cached, is display file",true
 								"not cached, is display file",true
@@ -77,7 +78,7 @@ let parse_file cs com file p =
 							let ident = Hashtbl.find Parser.special_identifier_files fkey in
 							let ident = Hashtbl.find Parser.special_identifier_files fkey in
 							Printf.sprintf "not cached, using \"%s\" define" ident,true
 							Printf.sprintf "not cached, using \"%s\" define" ident,true
 						with Not_found ->
 						with Not_found ->
-							cc#cache_file fkey ffile ftime data pdi;
+							cc#cache_file fkey rfile ftime data pdi;
 							"cached",false
 							"cached",false
 						end
 						end
 				in
 				in
@@ -209,8 +210,9 @@ let get_changed_directories sctx (ctx : Typecore.typer) =
 					with Unix.Unix_error _ ->
 					with Unix.Unix_error _ ->
 						()
 						()
 				in
 				in
-				List.iter add_dir com.class_path;
-				List.iter add_dir (Path.find_directories (platform_name com.platform) true com.class_path);
+				let class_path_strings = com.class_paths#as_string_list in
+				List.iter add_dir class_path_strings;
+				List.iter add_dir (Path.find_directories (platform_name com.platform) true class_path_strings);
 				ServerMessage.found_directories com "" !dirs;
 				ServerMessage.found_directories com "" !dirs;
 				cs#add_directories sign !dirs
 				cs#add_directories sign !dirs
 			) :: sctx.delays;
 			) :: sctx.delays;
@@ -578,15 +580,16 @@ let after_target_init sctx ctx =
 	ServerMessage.defines com "";
 	ServerMessage.defines com "";
 	ServerMessage.signature com "" sign;
 	ServerMessage.signature com "" sign;
 	ServerMessage.display_position com "" (DisplayPosition.display_position#get);
 	ServerMessage.display_position com "" (DisplayPosition.display_position#get);
+	let class_path_strings = com.class_paths#as_string_list in
 	try
 	try
-		if (Hashtbl.find sctx.class_paths sign) <> com.class_path then begin
+		if (Hashtbl.find sctx.class_paths sign) <> class_path_strings then begin
 			ServerMessage.class_paths_changed com "";
 			ServerMessage.class_paths_changed com "";
-			Hashtbl.replace sctx.class_paths sign com.class_path;
+			Hashtbl.replace sctx.class_paths sign class_path_strings;
 			cs#clear_directories sign;
 			cs#clear_directories sign;
 			(cs#get_context sign)#set_initialized false;
 			(cs#get_context sign)#set_initialized false;
 		end;
 		end;
 	with Not_found ->
 	with Not_found ->
-		Hashtbl.add sctx.class_paths sign com.class_path;
+		Hashtbl.add sctx.class_paths sign class_path_strings;
 		()
 		()
 
 
 let after_save sctx ctx =
 let after_save sctx ctx =
@@ -728,7 +731,6 @@ let do_connect ip port args =
 
 
 let enable_cache_mode sctx =
 let enable_cache_mode sctx =
 	TypeloadModule.type_module_hook := type_module sctx;
 	TypeloadModule.type_module_hook := type_module sctx;
-	MacroContext.macro_enable_cache := true;
 	ServerCompilationContext.ensure_macro_setup sctx;
 	ServerCompilationContext.ensure_macro_setup sctx;
 	TypeloadParse.parse_hook := parse_file sctx.cs
 	TypeloadParse.parse_hook := parse_file sctx.cs
 
 

+ 0 - 1
src/compiler/serverCompilationContext.ml

@@ -46,7 +46,6 @@ let reset sctx =
 	Hashtbl.clear sctx.changed_directories;
 	Hashtbl.clear sctx.changed_directories;
 	sctx.was_compilation <- false;
 	sctx.was_compilation <- false;
 	Parser.reset_state();
 	Parser.reset_state();
-	return_partial_type := false;
 	measure_times := false;
 	measure_times := false;
 	Hashtbl.clear DeprecationCheck.warned_positions;
 	Hashtbl.clear DeprecationCheck.warned_positions;
 	close_times();
 	close_times();

+ 10 - 112
src/context/common.ml

@@ -357,9 +357,8 @@ type context = {
 	mutable foptimize : bool;
 	mutable foptimize : bool;
 	mutable platform : platform;
 	mutable platform : platform;
 	mutable config : platform_config;
 	mutable config : platform_config;
-	mutable std_path : string list;
-	mutable class_path : string list;
-	mutable binary_class_path : string list;
+	empty_class_path : ClassPath.class_path;
+	class_paths : ClassPaths.class_paths;
 	mutable main_class : path option;
 	mutable main_class : path option;
 	mutable package_rules : (string,package_rule) PMap.t;
 	mutable package_rules : (string,package_rule) PMap.t;
 	mutable report_mode : report_mode;
 	mutable report_mode : report_mode;
@@ -386,12 +385,10 @@ type context = {
 	mutable global_metadata : (string list * metadata_entry * (bool * bool * bool)) list;
 	mutable global_metadata : (string list * metadata_entry * (bool * bool * bool)) list;
 	shared : shared_context;
 	shared : shared_context;
 	display_information : display_information;
 	display_information : display_information;
-	file_lookup_cache : (string,string option) lookup;
 	file_keys : file_keys;
 	file_keys : file_keys;
 	mutable file_contents : (Path.UniqueKey.t * string option) list;
 	mutable file_contents : (Path.UniqueKey.t * string option) list;
-	readdir_cache : (string * string,(string array) option) lookup;
 	parser_cache : (string,(type_def * pos) list) lookup;
 	parser_cache : (string,(type_def * pos) list) lookup;
-	module_to_file : (path,string) lookup;
+	module_to_file : (path,ClassPaths.resolved_file) lookup;
 	cached_macros : (path * string,(((string * bool * t) list * t * tclass * Type.tclass_field) * module_def)) lookup;
 	cached_macros : (path * string,(((string * bool * t) list * t * tclass * Type.tclass_field) * module_def)) lookup;
 	stored_typed_exprs : (int, texpr) lookup;
 	stored_typed_exprs : (int, texpr) lookup;
 	overload_cache : ((path * string),(Type.t * tclass_field) list) lookup;
 	overload_cache : ((path * string),(Type.t * tclass_field) list) lookup;
@@ -820,9 +817,8 @@ let create compilation_step cs version args display_mode =
 		print = (fun s -> print_string s; flush stdout);
 		print = (fun s -> print_string s; flush stdout);
 		run_command = Sys.command;
 		run_command = Sys.command;
 		run_command_args = (fun s args -> com.run_command (Printf.sprintf "%s %s" s (String.concat " " args)));
 		run_command_args = (fun s args -> com.run_command (Printf.sprintf "%s %s" s (String.concat " " args)));
-		std_path = [];
-		class_path = [];
-		binary_class_path = [];
+		empty_class_path = new ClassPath.directory_class_path "" User;
+		class_paths = new ClassPaths.class_paths;
 		main_class = None;
 		main_class = None;
 		package_rules = PMap.empty;
 		package_rules = PMap.empty;
 		file = "";
 		file = "";
@@ -869,10 +865,8 @@ let create compilation_step cs version args display_mode =
 			tarray = (fun _ -> die "Could not locate class Array<T> (was it redefined?)" __LOC__);
 			tarray = (fun _ -> die "Could not locate class Array<T> (was it redefined?)" __LOC__);
 		};
 		};
 		std = null_class;
 		std = null_class;
-		file_lookup_cache = new hashtbl_lookup;
 		file_keys = new file_keys;
 		file_keys = new file_keys;
 		file_contents = [];
 		file_contents = [];
-		readdir_cache = new hashtbl_lookup;
 		module_to_file = new hashtbl_lookup;
 		module_to_file = new hashtbl_lookup;
 		stored_typed_exprs = new hashtbl_lookup;
 		stored_typed_exprs = new hashtbl_lookup;
 		cached_macros = new hashtbl_lookup;
 		cached_macros = new hashtbl_lookup;
@@ -925,8 +919,6 @@ let clone com is_macro_context =
 		};
 		};
 		native_libs = create_native_libs();
 		native_libs = create_native_libs();
 		is_macro_context = is_macro_context;
 		is_macro_context = is_macro_context;
-		file_lookup_cache = new hashtbl_lookup;
-		readdir_cache = new hashtbl_lookup;
 		parser_cache = new hashtbl_lookup;
 		parser_cache = new hashtbl_lookup;
 		module_to_file = new hashtbl_lookup;
 		module_to_file = new hashtbl_lookup;
 		overload_cache = new hashtbl_lookup;
 		overload_cache = new hashtbl_lookup;
@@ -934,6 +926,8 @@ let clone com is_macro_context =
 		hxb_reader_stats = HxbReader.create_hxb_reader_stats ();
 		hxb_reader_stats = HxbReader.create_hxb_reader_stats ();
 		hxb_writer_stats = HxbWriter.create_hxb_writer_stats ();
 		hxb_writer_stats = HxbWriter.create_hxb_writer_stats ();
 		std = null_class;
 		std = null_class;
+		empty_class_path = new ClassPath.directory_class_path "" User;
+		class_paths = new ClassPaths.class_paths;
 	}
 	}
 
 
 let file_time file = Extc.filetime file
 let file_time file = Extc.filetime file
@@ -1079,104 +1073,8 @@ let platform_name_macro com =
 	if defined com Define.Macro then "macro"
 	if defined com Define.Macro then "macro"
 	else platform_name com.platform
 	else platform_name com.platform
 
 
-let remove_extension file =
-	try String.sub file 0 (String.rindex file '.')
-	with Not_found -> file
-
-let extension file =
-	try
-		let dot_pos = String.rindex file '.' in
-		String.sub file dot_pos (String.length file - dot_pos)
-	with Not_found -> file
-
-let cache_directory ctx class_path dir f_dir =
-	let platform_ext = "." ^ (platform_name_macro ctx)
-	and is_loading_core_api = defined ctx Define.CoreApi in
-	let dir_listing =
-		try Some (Sys.readdir dir);
-		with Sys_error _ -> None
-	in
-	ctx.readdir_cache#add (class_path,dir) dir_listing;
-	(*
-		This function is invoked for each file in the `dir`.
-		Each file is checked if it's specific for current platform
-		(e.g. ends with `.js.hx` while compiling for JS).
-		If it's not platform-specific:
-			Check the lookup cache and if the file is not there store full file path in the cache.
-		If the file is platform-specific:
-			Store the full file path in the lookup cache probably replacing the cached path to a
-			non-platform-specific file.
-	*)
-	let prepare_file file_own_name =
-		let relative_to_classpath = if f_dir = "." then file_own_name else f_dir ^ "/" ^ file_own_name in
-		(* `representation` is how the file is referenced to. E.g. when it's deduced from a module path. *)
-		let is_platform_specific,representation =
-			(* Platform specific file extensions are not allowed for loading @:coreApi types. *)
-			if is_loading_core_api then
-				false,relative_to_classpath
-			else begin
-				let ext = extension relative_to_classpath in
-				let second_ext = extension (remove_extension relative_to_classpath) in
-				(* The file contains double extension and the secondary one matches current platform *)
-				if platform_ext = second_ext then
-					true,(remove_extension (remove_extension relative_to_classpath)) ^ ext
-				else
-					false,relative_to_classpath
-			end
-		in
-		(*
-			Store current full path for `representation` if
-			- we're loading @:coreApi
-			- or this is a platform-specific file for `representation`
-			- this `representation` was never found before
-		*)
-		if is_loading_core_api || is_platform_specific || not (ctx.file_lookup_cache#mem representation) then begin
-			let full_path = if dir = "." then file_own_name else dir ^ "/" ^ file_own_name in
-			ctx.file_lookup_cache#add representation (Some full_path);
-		end
-	in
-	Option.may (Array.iter prepare_file) dir_listing
-
-let find_file ctx ?(class_path=ctx.class_path) f =
-	try
-		match ctx.file_lookup_cache#find f with
-		| None -> raise Exit
-		| Some f -> f
-	with
-	| Exit ->
-		raise Not_found
-	| Not_found when Path.is_absolute_path f ->
-		ctx.file_lookup_cache#add f (Some f);
-		f
-	| Not_found ->
-		let f_dir = Filename.dirname f in
-		let rec loop had_empty = function
-			| [] when had_empty -> raise Not_found
-			| [] -> loop true [""]
-			| p :: l ->
-				let file = p ^ f in
-				let dir = Filename.dirname file in
-				(* If we have seen the directory before, we can assume that the file isn't in there because the else case
-				   below would have added it to `file_lookup_cache`, which we check before we get here. *)
-				if ctx.readdir_cache#mem (p,dir) then
-					loop (had_empty || p = "") l
-				else begin
-					cache_directory ctx p dir f_dir;
-					(* Caching might have located the file we're looking for, so check the lookup cache again. *)
-					try
-						begin match ctx.file_lookup_cache#find f with
-						| Some f -> f
-						| None -> raise Not_found
-						end
-					with Not_found ->
-						loop (had_empty || p = "") l
-				end
-		in
-		let r = try Some (loop false class_path) with Not_found -> None in
-		ctx.file_lookup_cache#add f r;
-		match r with
-		| None -> raise Not_found
-		| Some f -> f
+let find_file ctx f =
+	(ctx.class_paths#find_file f).file
 
 
 (* let find_file ctx f =
 (* let find_file ctx f =
 	let timer = Timer.timer ["find_file"] in
 	let timer = Timer.timer ["find_file"] in
@@ -1305,7 +1203,7 @@ let adapt_defines_to_macro_context defines =
 		defines_signature = None
 		defines_signature = None
 	} in
 	} in
 	Define.define macro_defines Define.Macro;
 	Define.define macro_defines Define.Macro;
-	Define.raw_define macro_defines (platform_name !Globals.macro_platform);
+	Define.raw_define macro_defines (platform_name Eval);
 	macro_defines
 	macro_defines
 
 
 let adapt_defines_to_display_context defines =
 let adapt_defines_to_display_context defines =

+ 1 - 1
src/context/commonCache.ml

@@ -94,7 +94,7 @@ let rec cache_context cs com =
 
 
 let maybe_add_context_sign cs com desc =
 let maybe_add_context_sign cs com desc =
 	let sign = Define.get_signature com.defines in
 	let sign = Define.get_signature com.defines in
-	ignore(cs#add_info sign desc com.platform com.class_path com.defines)
+	ignore(cs#add_info sign desc com.platform com.class_paths com.defines)
 
 
 let lock_signature com name =
 let lock_signature com name =
 	let cs = com.cs in
 	let cs = com.cs in

+ 1 - 1
src/context/display/diagnostics.ml

@@ -121,7 +121,7 @@ let collect_diagnostics dctx com =
 				ParserEntry.is_true (ParserEntry.eval defines e)
 				ParserEntry.is_true (ParserEntry.eval defines e)
 			in
 			in
 			Hashtbl.iter (fun file_key cfile ->
 			Hashtbl.iter (fun file_key cfile ->
-				if DisplayPosition.display_position#is_in_file (com.file_keys#get cfile.c_file_path) then begin
+				if DisplayPosition.display_position#is_in_file (com.file_keys#get cfile.c_file_path.file) then begin
 					let dead_blocks = cfile.c_pdi.pd_dead_blocks in
 					let dead_blocks = cfile.c_pdi.pd_dead_blocks in
 					let dead_blocks = List.filter (fun (_,e) -> not (is_true display_defines e)) dead_blocks in
 					let dead_blocks = List.filter (fun (_,e) -> not (is_true display_defines e)) dead_blocks in
 					try
 					try

+ 7 - 7
src/context/display/displayEmitter.ml

@@ -54,9 +54,9 @@ let rec display_type ctx t p =
 	try
 	try
 		display_module_type ctx (module_type_of_type t) p
 		display_module_type ctx (module_type_of_type t) p
 	with Exit ->
 	with Exit ->
-		match follow t,follow !t_dynamic_def with
+		match follow t,follow ctx.g.t_dynamic_def with
 		| _,TDynamic _ -> () (* sanity check in case it's still t_dynamic *)
 		| _,TDynamic _ -> () (* sanity check in case it's still t_dynamic *)
-		| TDynamic _,_ -> display_type ctx !t_dynamic_def p
+		| TDynamic _,_ -> display_type ctx ctx.g.t_dynamic_def p
 		| _ ->
 		| _ ->
 			match dm.dms_kind with
 			match dm.dms_kind with
 			| DMHover ->
 			| DMHover ->
@@ -77,14 +77,14 @@ let check_display_type ctx t ptp =
 	add_type_hint();
 	add_type_hint();
 	maybe_display_type()
 	maybe_display_type()
 
 
-let raise_position_of_type t =
+let raise_position_of_type ctx t =
 	let mt =
 	let mt =
 		let rec follow_null t =
 		let rec follow_null t =
 			match t with
 			match t with
 				| TMono r -> (match r.tm_type with None -> raise_positions [null_pos] | Some t -> follow_null t)
 				| TMono r -> (match r.tm_type with None -> raise_positions [null_pos] | Some t -> follow_null t)
 				| TLazy f -> follow_null (lazy_type f)
 				| TLazy f -> follow_null (lazy_type f)
 				| TAbstract({a_path = [],"Null"},[t]) -> follow_null t
 				| TAbstract({a_path = [],"Null"},[t]) -> follow_null t
-				| TDynamic _ -> !t_dynamic_def
+				| TDynamic _ -> ctx.g.t_dynamic_def
 				| _ -> t
 				| _ -> t
 		in
 		in
 		try
 		try
@@ -96,7 +96,7 @@ let raise_position_of_type t =
 
 
 let display_variable ctx v p = match ctx.com.display.dms_kind with
 let display_variable ctx v p = match ctx.com.display.dms_kind with
 	| DMDefinition -> raise_positions [v.v_pos]
 	| DMDefinition -> raise_positions [v.v_pos]
-	| DMTypeDefinition -> raise_position_of_type v.v_type
+	| DMTypeDefinition -> raise_position_of_type ctx v.v_type
 	| DMUsage _ -> ReferencePosition.set (v.v_name,v.v_pos,SKVariable v)
 	| DMUsage _ -> ReferencePosition.set (v.v_name,v.v_pos,SKVariable v)
 	| DMHover ->
 	| DMHover ->
 		let ct = CompletionType.from_type (get_import_status ctx) ~values:(get_value_meta v.v_meta) v.v_type in
 		let ct = CompletionType.from_type (get_import_status ctx) ~values:(get_value_meta v.v_meta) v.v_type in
@@ -105,7 +105,7 @@ let display_variable ctx v p = match ctx.com.display.dms_kind with
 
 
 let display_field ctx origin scope cf p = match ctx.com.display.dms_kind with
 let display_field ctx origin scope cf p = match ctx.com.display.dms_kind with
 	| DMDefinition -> raise_positions [cf.cf_name_pos]
 	| DMDefinition -> raise_positions [cf.cf_name_pos]
-	| DMTypeDefinition -> raise_position_of_type cf.cf_type
+	| DMTypeDefinition -> raise_position_of_type ctx cf.cf_type
 	| DMUsage _ | DMImplementation ->
 	| DMUsage _ | DMImplementation ->
 		let name,kind = match cf.cf_name,origin with
 		let name,kind = match cf.cf_name,origin with
 			| "new",(Self (TClassDecl c) | Parent(TClassDecl c)) ->
 			| "new",(Self (TClassDecl c) | Parent(TClassDecl c)) ->
@@ -136,7 +136,7 @@ let maybe_display_field ctx origin scope cf p =
 
 
 let display_enum_field ctx en ef p = match ctx.com.display.dms_kind with
 let display_enum_field ctx en ef p = match ctx.com.display.dms_kind with
 	| DMDefinition -> raise_positions [ef.ef_name_pos]
 	| DMDefinition -> raise_positions [ef.ef_name_pos]
-	| DMTypeDefinition -> raise_position_of_type ef.ef_type
+	| DMTypeDefinition -> raise_position_of_type ctx ef.ef_type
 	| DMUsage _ -> ReferencePosition.set (ef.ef_name,ef.ef_name_pos,SKEnumField ef)
 	| DMUsage _ -> ReferencePosition.set (ef.ef_name,ef.ef_name_pos,SKEnumField ef)
 	| DMHover ->
 	| DMHover ->
 		let ct = CompletionType.from_type (get_import_status ctx) ef.ef_type in
 		let ct = CompletionType.from_type (get_import_status ctx) ef.ef_type in

+ 2 - 2
src/context/display/displayFields.ml

@@ -39,9 +39,9 @@ let collect_static_extensions ctx items e p =
 	let opt_type t =
 	let opt_type t =
 		match t with
 		match t with
 		| TLazy f ->
 		| TLazy f ->
-			return_partial_type := true;
+			ctx.g.return_partial_type <- true;
 			let t = lazy_type f in
 			let t = lazy_type f in
-			return_partial_type := false;
+			ctx.g.return_partial_type <- false;
 			t
 			t
 		| _ ->
 		| _ ->
 			t
 			t

+ 2 - 2
src/context/display/displayJson.ml

@@ -398,7 +398,7 @@ let handler =
 			let key = hctx.com.file_keys#get file in
 			let key = hctx.com.file_keys#get file in
 			let cs = hctx.display#get_cs in
 			let cs = hctx.display#get_cs in
 			List.iter (fun cc ->
 			List.iter (fun cc ->
-				Hashtbl.replace cc#get_removed_files key file
+				Hashtbl.replace cc#get_removed_files key (ClassPaths.create_resolved_file file hctx.com.empty_class_path)
 			) cs#get_contexts;
 			) cs#get_contexts;
 			hctx.send_result (jstring file);
 			hctx.send_result (jstring file);
 		);
 		);
@@ -409,7 +409,7 @@ let handler =
 			let files = List.sort (fun (file1,_) (file2,_) -> compare file1 file2) files in
 			let files = List.sort (fun (file1,_) (file2,_) -> compare file1 file2) files in
 			let files = List.map (fun (fkey,cfile) ->
 			let files = List.map (fun (fkey,cfile) ->
 				jobject [
 				jobject [
-					"file",jstring cfile.c_file_path;
+					"file",jstring cfile.c_file_path.file;
 					"time",jfloat cfile.c_time;
 					"time",jfloat cfile.c_time;
 					"pack",jstring (String.concat "." cfile.c_package);
 					"pack",jstring (String.concat "." cfile.c_package);
 					"moduleName",jopt jstring cfile.c_module_name;
 					"moduleName",jopt jstring cfile.c_module_name;

+ 3 - 2
src/context/display/displayPath.ml

@@ -32,7 +32,8 @@ module TypePathHandler = struct
 					Not_found -> p)
 					Not_found -> p)
 			| _ -> p
 			| _ -> p
 		) in
 		) in
-		List.iter (fun path ->
+		com.class_paths#iter (fun path ->
+			let path = path#path in
 			let dir = path ^ String.concat "/" p in
 			let dir = path ^ String.concat "/" p in
 			let r = (try Sys.readdir dir with _ -> [||]) in
 			let r = (try Sys.readdir dir with _ -> [||]) in
 			Array.iter (fun f ->
 			Array.iter (fun f ->
@@ -59,7 +60,7 @@ module TypePathHandler = struct
 						if String.length c < 2 || String.sub c (String.length c - 2) 2 <> "__" then classes := c :: !classes;
 						if String.length c < 2 || String.sub c (String.length c - 2) 2 <> "__" then classes := c :: !classes;
 				end;
 				end;
 			) r;
 			) r;
-		) com.class_path;
+		);
 		let process_lib lib =
 		let process_lib lib =
 			List.iter (fun (path,name) ->
 			List.iter (fun (path,name) ->
 				if path = p then classes := name :: !classes else
 				if path = p then classes := name :: !classes else

+ 9 - 5
src/context/display/displayToplevel.ml

@@ -111,8 +111,12 @@ let explore_class_paths com timer class_paths recursive f_pack f_module =
 	let cs = com.cs in
 	let cs = com.cs in
 	let t = Timer.timer (timer @ ["class path exploration"]) in
 	let t = Timer.timer (timer @ ["class path exploration"]) in
 	let checked = Hashtbl.create 0 in
 	let checked = Hashtbl.create 0 in
-	let tasks = List.map (fun dir ->
-		new explore_class_path_task com checked recursive f_pack f_module dir []
+	let tasks = ExtList.List.filter_map (fun path ->
+		match path#get_directory_path with
+			| Some path ->
+				Some (new explore_class_path_task com checked recursive f_pack f_module path [])
+			| None ->
+				None
 	) class_paths in
 	) class_paths in
 	let task = new arbitrary_task ["explore"] 50 (fun () ->
 	let task = new arbitrary_task ["explore"] 50 (fun () ->
 		List.iter (fun task -> task#run) tasks
 		List.iter (fun task -> task#run) tasks
@@ -121,10 +125,10 @@ let explore_class_paths com timer class_paths recursive f_pack f_module =
 	t()
 	t()
 
 
 let read_class_paths com timer =
 let read_class_paths com timer =
-	explore_class_paths com timer (List.filter ((<>) "") com.class_path) true (fun _ -> ()) (fun file path ->
+	explore_class_paths com timer (com.class_paths#filter (fun cp -> cp#path <> "")) true (fun _ -> ()) (fun file path ->
 		(* Don't parse the display file as that would maybe overwrite the content from stdin with the file contents. *)
 		(* Don't parse the display file as that would maybe overwrite the content from stdin with the file contents. *)
 		if not (DisplayPosition.display_position#is_in_file (com.file_keys#get file)) then begin
 		if not (DisplayPosition.display_position#is_in_file (com.file_keys#get file)) then begin
-			let file,_,pack,_ = Display.parse_module' com path Globals.null_pos in
+			let rfile,_,pack,_ = Display.parse_module' com path Globals.null_pos in
 			if pack <> fst path then begin
 			if pack <> fst path then begin
 				let file_key = com.file_keys#get file in
 				let file_key = com.file_keys#get file in
 				(CommonCache.get_cache com)#remove_file_for_real file_key
 				(CommonCache.get_cache com)#remove_file_for_real file_key
@@ -475,7 +479,7 @@ let collect ctx tk with_type sort =
 		| s :: sl -> add_package (List.rev sl,s)
 		| s :: sl -> add_package (List.rev sl,s)
 	in
 	in
 	List.iter (fun ((file_key,cfile),_) ->
 	List.iter (fun ((file_key,cfile),_) ->
-		let module_name = CompilationCache.get_module_name_of_cfile cfile.c_file_path cfile in
+		let module_name = CompilationCache.get_module_name_of_cfile cfile.c_file_path.file cfile in
 		let dot_path = s_type_path (cfile.c_package,module_name) in
 		let dot_path = s_type_path (cfile.c_package,module_name) in
 		(* In legacy mode we only show toplevel types. *)
 		(* In legacy mode we only show toplevel types. *)
 		if is_legacy_completion && cfile.c_package <> [] then begin
 		if is_legacy_completion && cfile.c_package <> [] then begin

+ 1 - 1
src/context/display/syntaxExplorer.ml

@@ -167,7 +167,7 @@ let explore_uncached_modules tctx cs symbols =
 	let modules = cc#get_modules in
 	let modules = cc#get_modules in
 	let t = Timer.timer ["display";"references";"candidates"] in
 	let t = Timer.timer ["display";"references";"candidates"] in
 	let acc = Hashtbl.fold (fun file_key cfile acc ->
 	let acc = Hashtbl.fold (fun file_key cfile acc ->
-		let module_name = get_module_name_of_cfile cfile.c_file_path cfile in
+		let module_name = get_module_name_of_cfile cfile.c_file_path.file cfile in
 		if Hashtbl.mem modules (cfile.c_package,module_name) then
 		if Hashtbl.mem modules (cfile.c_package,module_name) then
 			acc
 			acc
 		else try
 		else try

+ 45 - 59
src/context/typecore.ml

@@ -60,6 +60,12 @@ type typer_pass =
 	| PForce				(* usually ensure that lazy have been evaluated *)
 	| PForce				(* usually ensure that lazy have been evaluated *)
 	| PFinal				(* not used, only mark for finalize *)
 	| PFinal				(* not used, only mark for finalize *)
 
 
+let all_typer_passes = [
+	PBuildModule;PBuildClass;PConnectField;PTypeField;PCheckConstraint;PForce;PFinal
+]
+
+let all_typer_passes_length = List.length all_typer_passes
+
 type typer_module = {
 type typer_module = {
 	curmod : module_def;
 	curmod : module_def;
 	import_resolution : resolution_list;
 	import_resolution : resolution_list;
@@ -69,11 +75,6 @@ type typer_module = {
 	mutable import_statements : import list;
 	mutable import_statements : import list;
 }
 }
 
 
-type delay = {
-	delay_pass : typer_pass;
-	delay_functions : (unit -> unit) list;
-}
-
 type build_kind =
 type build_kind =
 	| BuildNormal
 	| BuildNormal
 	| BuildGeneric of tclass
 	| BuildGeneric of tclass
@@ -93,8 +94,13 @@ type macro_result =
 	| MError
 	| MError
 	| MMacroInMacro
 	| MMacroInMacro
 
 
+type typer_pass_tasks = {
+	mutable tasks : (unit -> unit) list;
+}
+
 type typer_globals = {
 type typer_globals = {
-	mutable delayed : delay list;
+	mutable delayed : typer_pass_tasks Array.t;
+	mutable delayed_min_index : int;
 	mutable debug_delayed : (typer_pass * ((unit -> unit) * (string * string list) * typer) list) list;
 	mutable debug_delayed : (typer_pass * ((unit -> unit) * (string * string list) * typer) list) list;
 	doinline : bool;
 	doinline : bool;
 	retain_meta : bool;
 	retain_meta : bool;
@@ -109,6 +115,9 @@ type typer_globals = {
 	mutable type_hints : (module_def_display * pos * t) list;
 	mutable type_hints : (module_def_display * pos * t) list;
 	mutable load_only_cached_modules : bool;
 	mutable load_only_cached_modules : bool;
 	functional_interface_lut : (path,tclass_field) lookup;
 	functional_interface_lut : (path,tclass_field) lookup;
+	mutable return_partial_type : bool;
+	mutable build_count : int;
+	mutable t_dynamic_def : Type.t;
 	(* api *)
 	(* api *)
 	do_macro : typer -> macro_mode -> path -> string -> expr list -> pos -> macro_result;
 	do_macro : typer -> macro_mode -> path -> string -> expr list -> pos -> macro_result;
 	do_load_macro : typer -> bool -> path -> string -> pos -> ((string * bool * t) list * t * tclass * Type.tclass_field);
 	do_load_macro : typer -> bool -> path -> string -> pos -> ((string * bool * t) list * t * tclass * Type.tclass_field);
@@ -222,8 +231,6 @@ exception WithTypeError of error
 
 
 let memory_marker = [|Unix.time()|]
 let memory_marker = [|Unix.time()|]
 
 
-let locate_macro_error = ref true
-
 let make_call_ref : (typer -> texpr -> texpr list -> t -> ?force_inline:bool -> pos -> texpr) ref = ref (fun _ _ _ _ ?force_inline:bool _ -> die "" __LOC__)
 let make_call_ref : (typer -> texpr -> texpr list -> t -> ?force_inline:bool -> pos -> texpr) ref = ref (fun _ _ _ _ ?force_inline:bool _ -> die "" __LOC__)
 let type_expr_ref : (?mode:access_mode -> typer -> expr -> WithType.t -> texpr) ref = ref (fun ?(mode=MGet) _ _ _ -> die "" __LOC__)
 let type_expr_ref : (?mode:access_mode -> typer -> expr -> WithType.t -> texpr) ref = ref (fun ?(mode=MGet) _ _ _ -> die "" __LOC__)
 let type_block_ref : (typer -> expr list -> WithType.t -> pos -> texpr) ref = ref (fun _ _ _ _ -> die "" __LOC__)
 let type_block_ref : (typer -> expr list -> WithType.t -> pos -> texpr) ref = ref (fun _ _ _ _ -> die "" __LOC__)
@@ -323,7 +330,7 @@ let add_local ctx k n t p =
 			begin try
 			begin try
 				let v' = PMap.find n ctx.locals in
 				let v' = PMap.find n ctx.locals in
 				(* ignore std lib *)
 				(* ignore std lib *)
-				if not (List.exists (ExtLib.String.starts_with p.pfile) ctx.com.std_path) then begin
+				if not (List.exists (fun path -> ExtLib.String.starts_with p.pfile (path#path)) ctx.com.class_paths#get_std_paths) then begin
 					warning ctx WVarShadow "This variable shadows a previously declared variable" p;
 					warning ctx WVarShadow "This variable shadows a previously declared variable" p;
 					warning ~depth:1 ctx WVarShadow (compl_msg "Previous variable was here") v'.v_pos
 					warning ~depth:1 ctx WVarShadow (compl_msg "Previous variable was here") v'.v_pos
 				end
 				end
@@ -401,36 +408,19 @@ let is_gen_local v = match v.v_kind with
 	| _ ->
 	| _ ->
 		false
 		false
 
 
-let make_delay pass fl = {
-	delay_pass = pass;
-	delay_functions = fl;
-}
-
 let delay ctx p f =
 let delay ctx p f =
-	let rec loop = function
-		| [] ->
-			[make_delay p [f]]
-		| delay :: rest ->
-			if delay.delay_pass = p then
-				(make_delay p (f :: delay.delay_functions)) :: rest
-			else if delay.delay_pass < p then
-				delay :: loop rest
-			else
-				(make_delay p [f]) :: delay :: rest
-	in
-	ctx.g.delayed <- loop ctx.g.delayed
+	let p = Obj.magic p in
+	let tasks = ctx.g.delayed.(p) in
+	tasks.tasks <- f :: tasks.tasks;
+	if p < ctx.g.delayed_min_index then
+		ctx.g.delayed_min_index <- p
 
 
 let delay_late ctx p f =
 let delay_late ctx p f =
-	let rec loop = function
-		| [] ->
-			[make_delay p [f]]
-		| delay :: rest ->
-			if delay.delay_pass <= p then
-				delay :: loop rest
-			else
-				(make_delay p [f]) :: delay :: rest
-	in
-	ctx.g.delayed <- loop ctx.g.delayed
+	let p = Obj.magic p in
+	let tasks = ctx.g.delayed.(p) in
+	tasks.tasks <- tasks.tasks @ [f];
+	if p < ctx.g.delayed_min_index then
+		ctx.g.delayed_min_index <- p
 
 
 let delay_if_mono ctx p t f = match follow t with
 let delay_if_mono ctx p t f = match follow t with
 	| TMono _ ->
 	| TMono _ ->
@@ -439,17 +429,24 @@ let delay_if_mono ctx p t f = match follow t with
 		f()
 		f()
 
 
 let rec flush_pass ctx p where =
 let rec flush_pass ctx p where =
-	match ctx.g.delayed with
-	| delay :: rest when delay.delay_pass <= p ->
-		(match delay.delay_functions with
-		| [] ->
-			ctx.g.delayed <- rest;
-		| f :: l ->
-			ctx.g.delayed <- (make_delay delay.delay_pass l) :: rest;
-			f());
-		flush_pass ctx p where
-	| _ ->
-		()
+	let rec loop i =
+		if i > (Obj.magic p) then
+			()
+		else begin
+			let tasks = ctx.g.delayed.(i) in
+			match tasks.tasks with
+			| f :: l ->
+				tasks.tasks <- l;
+				f();
+				flush_pass ctx p where
+			| [] ->
+				(* Done with this pass (for now), update min index to next one *)
+				let i = i + 1 in
+				ctx.g.delayed_min_index <- i;
+				loop i
+		end
+	in
+	loop ctx.g.delayed_min_index
 
 
 let make_pass ctx f = f
 let make_pass ctx f = f
 
 
@@ -701,18 +698,7 @@ let safe_mono_close ctx m p =
 			raise_or_display ctx l p
 			raise_or_display ctx l p
 
 
 let relative_path ctx file =
 let relative_path ctx file =
-	let slashes path = String.concat "/" (ExtString.String.nsplit path "\\") in
-	let fpath = slashes (Path.get_full_path file) in
-	let fpath_lower = String.lowercase_ascii fpath in
-	let flen = String.length fpath_lower in
-	let rec loop = function
-		| [] -> file
-		| path :: l ->
-			let spath = String.lowercase_ascii (slashes path) in
-			let slen = String.length spath in
-			if slen > 0 && slen < flen && String.sub fpath_lower 0 slen = spath then String.sub fpath slen (flen - slen) else loop l
-	in
-	loop ctx.com.Common.class_path
+	ctx.com.class_paths#relative_path file
 
 
 let mk_infos ctx p params =
 let mk_infos ctx p params =
 	let file = if ctx.com.is_macro_context then p.pfile else if Common.defined ctx.com Define.AbsolutePath then Path.get_full_path p.pfile else relative_path ctx p.pfile in
 	let file = if ctx.com.is_macro_context then p.pfile else if Common.defined ctx.com Define.AbsolutePath then Path.get_full_path p.pfile else relative_path ctx p.pfile in

+ 62 - 0
src/core/classPath.ml

@@ -0,0 +1,62 @@
+type class_path_scope =
+	| Std
+	| StdTarget
+	| Lib
+	| User
+
+type file_kind =
+	| FFile
+
+class virtual class_path (path : string) (scope : class_path_scope) (file_kind : file_kind) = object(self)
+	method path = path;
+	method scope = scope;
+	method file_kind = file_kind;
+
+	method virtual clone : class_path
+	method virtual clear_cache : unit
+	method virtual get_directory_path : string option
+	method virtual get_uncached_dir_listing : string -> (string * string array) option
+	method virtual dump : unit
+
+	method is_std_path = match scope with
+		| Std -> true
+		| _ -> false
+
+	method scope_string = match scope with
+		| Std -> "Std"
+		| StdTarget -> "StdTarget"
+		| Lib -> "Lib"
+		| User -> "User"
+end
+
+class directory_class_path (path : string) (scope : class_path_scope) = object(self)
+	inherit class_path path scope FFile
+
+	val readdir_cache = new Lookup.hashtbl_lookup
+
+	method clear_cache =
+		readdir_cache#clear
+
+	method get_directory_path =
+		Some path
+
+	method clone =
+		new directory_class_path path scope
+
+	method get_uncached_dir_listing (f : string) =
+		let file = path ^ f in
+		let dir = Filename.dirname file in
+		if readdir_cache#mem dir then
+			None
+		else begin
+			let dir_listing =
+				try Some (dir,Sys.readdir dir);
+				with Sys_error _ -> None
+			in
+			readdir_cache#add dir dir_listing;
+			dir_listing
+		end
+
+	method dump =
+		print_endline (Printf.sprintf "    dir %-9s: %s" (self#scope_string) path)
+end

+ 169 - 0
src/core/classPaths.ml

@@ -0,0 +1,169 @@
+open StringHelper
+open ClassPath
+
+type resolved_file = {
+	file : string;
+	class_path : class_path;
+}
+
+let create_resolved_file file class_path = {
+	file;
+	class_path;
+}
+
+class class_paths = object(self)
+	val mutable l = []
+	val file_lookup_cache = new Lookup.hashtbl_lookup;
+	val mutable platform_ext = ""
+	val mutable is_loading_core_api = false
+
+	method lock_context (platform_name : string) (core_api : bool) : unit =
+		platform_ext <- "." ^ platform_name;
+		is_loading_core_api <- core_api;
+		self#clear_cache
+
+	method as_string_list =
+		List.map (fun cp -> cp#path) l
+
+	method add (cp : class_path) =
+		l <- cp :: l;
+		file_lookup_cache#clear
+
+	method push (cp : class_path) =
+		l <- l @ [cp];
+		file_lookup_cache#clear
+
+	method find (f : class_path -> bool) =
+		List.find f l
+
+	method iter (f : class_path -> unit) =
+		List.iter f l
+
+	method exists (f : class_path -> bool) =
+		List.exists f l
+
+	method filter (f : class_path -> bool) =
+		List.filter f l
+
+	method modify (f : class_path -> class_path list) (cpl : class_path list) =
+		let rec loop acc l = match l with
+			| [] ->
+				List.rev acc
+			| cp :: l ->
+				let cpl = f cp in
+				loop (cpl @ acc) l
+		in
+		l <- loop [] cpl;
+		file_lookup_cache#clear
+
+	method modify_inplace (f : class_path -> class_path list) =
+		self#modify f l
+
+	method get_std_paths =
+		self#filter (fun cp -> cp#is_std_path)
+
+	method as_list =
+		l
+
+	method clear_cache =
+		file_lookup_cache#clear;
+		List.iter (fun cp -> cp#clear_cache) l
+
+	method cache_directory (cp : class_path) (dir : string) (f_search : string) (dir_listing : string array) =
+		(*
+			This function is invoked for each file in the `dir`.
+			Each file is checked if it's specific for current platform
+			(e.g. ends with `.js.hx` while compiling for JS).
+			If it's not platform-specific:
+				Check the lookup cache and if the file is not there store full file path in the cache.
+			If the file is platform-specific:
+				Store the full file path in the lookup cache probably replacing the cached path to a
+				non-platform-specific file.
+		*)
+		let found = ref None in
+		let f_dir = Filename.dirname f_search in
+		let prepare_file file_own_name =
+			let relative_to_classpath = if f_dir = "." then file_own_name else f_dir ^ "/" ^ file_own_name in
+			(* `representation` is how the file is referenced to. E.g. when it's deduced from a module path. *)
+			let is_platform_specific,representation =
+				(* Platform specific file extensions are not allowed for loading @:coreApi types. *)
+				if is_loading_core_api then
+					false,relative_to_classpath
+				else begin
+					let ext = extension relative_to_classpath in
+					let second_ext = extension (remove_extension relative_to_classpath) in
+					(* The file contains double extension and the secondary one matches current platform *)
+					if platform_ext = second_ext then
+						true,(remove_extension (remove_extension relative_to_classpath)) ^ ext
+					else
+						false,relative_to_classpath
+				end
+			in
+			(*
+				Store current full path for `representation` if
+				- we're loading @:coreApi
+				- or this is a platform-specific file for `representation`
+				- this `representation` was never found before
+			*)
+			if is_loading_core_api || is_platform_specific || not (file_lookup_cache#mem representation) then begin
+				let full_path = if dir = "." then file_own_name else dir ^ "/" ^ file_own_name in
+				let full_path = Some(create_resolved_file full_path cp) in
+				file_lookup_cache#add representation full_path;
+				if representation = f_search then found := full_path
+			end
+		in
+		Array.iter prepare_file dir_listing;
+		!found
+
+	method find_file_noraise (f : string) =
+		try
+			match file_lookup_cache#find f with
+			| None ->
+				None
+			| Some f ->
+				Some f
+		with Not_found ->
+			let rec loop = function
+				| [] ->
+					None
+				| cp :: l ->
+					begin match cp#get_uncached_dir_listing f with
+						| None ->
+							loop l
+						| Some(dir,dir_listing) ->
+							match self#cache_directory cp dir f dir_listing with
+								| Some f ->
+									Some f
+								| None ->
+									loop l
+					end
+			in
+			let r = loop l in
+			file_lookup_cache#add f r;
+			r
+
+	method find_file (f : string) =
+		match self#find_file_noraise f with
+		| None -> raise Not_found
+		| Some f -> f
+
+	method relative_path file =
+		let slashes path = String.concat "/" (ExtString.String.nsplit path "\\") in
+		let fpath = slashes (Path.get_full_path file) in
+		let fpath_lower = String.lowercase_ascii fpath in
+		let flen = String.length fpath_lower in
+		let rec loop = function
+			| [] ->
+				file
+			| path :: l ->
+				let path = path#path in
+				let spath = String.lowercase_ascii (slashes path) in
+				let slen = String.length spath in
+				if slen > 0 && slen < flen && String.sub fpath_lower 0 slen = spath then String.sub fpath slen (flen - slen) else loop l
+		in
+		loop l
+
+	method dump =
+		print_endline (Printf.sprintf "Class paths for %s%s:" platform_ext (if is_loading_core_api then " (coreApi)" else ""));
+		List.iter (fun cp -> cp#dump) l
+end

+ 0 - 4
src/core/globals.ml

@@ -68,10 +68,6 @@ let trace_call_stack ?(n:int = 5) () =
 		Option.may (fun loc -> print_endline (Printf.sprintf "  called from %s" (loc_to_string loc))) loc;
 		Option.may (fun loc -> print_endline (Printf.sprintf "  called from %s" (loc_to_string loc))) loc;
 	done
 	done
 
 
-let macro_platform = ref Neko
-
-let return_partial_type = ref false
-
 let is_windows = Sys.os_type = "Win32" || Sys.os_type = "Cygwin"
 let is_windows = Sys.os_type = "Win32" || Sys.os_type = "Cygwin"
 
 
 let max_custom_target_len = 16
 let max_custom_target_len = 16

+ 0 - 2
src/core/json/genjson.ml

@@ -215,9 +215,7 @@ let rec generate_type ctx t =
 			| Some t -> loop t
 			| Some t -> loop t
 			end
 			end
 		| TLazy f ->
 		| TLazy f ->
-			(* return_partial_type := true; *)
 			let t = lazy_type f in
 			let t = lazy_type f in
-			(* return_partial_type := false; *)
 			loop t
 			loop t
 		| TDynamic None -> "TDynamic", Some jnull
 		| TDynamic None -> "TDynamic", Some jnull
 		| TDynamic (Some t) -> "TDynamic",Some (generate_type ctx t)
 		| TDynamic (Some t) -> "TDynamic",Some (generate_type ctx t)

+ 12 - 1
src/core/stringHelper.ml

@@ -57,4 +57,15 @@ let escape_res_name name allowed =
 		else if List.mem chr allowed then
 		else if List.mem chr allowed then
 			Char.escaped chr
 			Char.escaped chr
 		else
 		else
-			"-x" ^ (string_of_int (Char.code chr))) name
+			"-x" ^ (string_of_int (Char.code chr))) name
+
+let remove_extension file =
+	try String.sub file 0 (String.rindex file '.')
+	with Not_found -> file
+
+let extension file =
+	try
+		let dot_pos = String.rindex file '.' in
+		String.sub file dot_pos (String.length file - dot_pos)
+	with Not_found ->
+		file

+ 0 - 6
src/core/tFunctions.ml

@@ -101,12 +101,6 @@ let mk_anon ?fields status =
 	let fields = match fields with Some fields -> fields | None -> PMap.empty in
 	let fields = match fields with Some fields -> fields | None -> PMap.empty in
 	TAnon { a_fields = fields; a_status = status; }
 	TAnon { a_fields = fields; a_status = status; }
 
 
-(* We use this for display purposes because otherwise we never see the Dynamic type that
-   is defined in StdTypes.hx. This is set each time a typer is created, but this is fine
-   because Dynamic is the same in all contexts. If this ever changes we'll have to review
-   how we handle this. *)
-let t_dynamic_def = ref t_dynamic
-
 let tfun pl r = TFun (List.map (fun t -> "",false,t) pl,r)
 let tfun pl r = TFun (List.map (fun t -> "",false,t) pl,r)
 
 
 let fun_args l = List.map (fun (a,c,t) -> a, c <> None, t) l
 let fun_args l = List.map (fun (a,c,t) -> a, c <> None, t) l

+ 5 - 12
src/generators/gencpp.ml

@@ -1322,17 +1322,7 @@ exception PathFound of string;;
 
 
 let strip_file ctx file = (match Common.defined ctx Common.Define.AbsolutePath with
 let strip_file ctx file = (match Common.defined ctx Common.Define.AbsolutePath with
    | true -> file
    | true -> file
-   | false -> let flen = String.length file in
-   (* Not quite right - should probably test is file exists *)
-   try
-      List.iter (fun path ->
-         let plen = String.length path in
-         if (flen>plen && path=(String.sub file 0 plen ))
-            then raise (PathFound (String.sub file plen (flen-plen)) ) )
-         (ctx.class_path @ ctx.std_path);
-      file;
-   with PathFound tail ->
-      tail)
+   | false -> ctx.class_paths#relative_path file)
 ;;
 ;;
 
 
 let with_debug ctx metadata run =
 let with_debug ctx metadata run =
@@ -8679,7 +8669,10 @@ let generate_source ctx =
          | "true" | "sys" | "dce" | "cpp" | "debug" -> ();
          | "true" | "sys" | "dce" | "cpp" | "debug" -> ();
          | _ -> cmd := !cmd @ [Printf.sprintf "-D%s=\"%s\"" name (escape_command value)];
          | _ -> cmd := !cmd @ [Printf.sprintf "-D%s=\"%s\"" name (escape_command value)];
       ) common_ctx.defines.values;
       ) common_ctx.defines.values;
-      List.iter (fun path -> cmd := !cmd @ [Printf.sprintf "-I%s" (escape_command path)]) common_ctx.class_path;
+      common_ctx.class_paths#iter (fun path ->
+		let path = path#path in
+		cmd := !cmd @ [Printf.sprintf "-I%s" (escape_command path)]
+	  );
       common_ctx.print ("haxelib " ^ (String.concat " " !cmd) ^ "\n");
       common_ctx.print ("haxelib " ^ (String.concat " " !cmd) ^ "\n");
       if common_ctx.run_command_args "haxelib" !cmd <> 0 then failwith "Build failed";
       if common_ctx.run_command_args "haxelib" !cmd <> 0 then failwith "Build failed";
       Sys.chdir old_dir;
       Sys.chdir old_dir;

+ 4 - 3
src/generators/genhl.ml

@@ -329,11 +329,12 @@ let make_debug ctx arr =
 		| false -> try
 		| false -> try
 			(* lookup relative path *)
 			(* lookup relative path *)
 			let len = String.length p.pfile in
 			let len = String.length p.pfile in
-			let base = List.find (fun path ->
+			let base = ctx.com.class_paths#find (fun path ->
+				let path = path#path in
 				let l = String.length path in
 				let l = String.length path in
 				len > l && String.sub p.pfile 0 l = path
 				len > l && String.sub p.pfile 0 l = path
-			) ctx.com.Common.class_path in
-			let l = String.length base in
+			) in
+			let l = String.length base#path in
 			String.sub p.pfile l (len - l)
 			String.sub p.pfile l (len - l)
 		with Not_found ->
 		with Not_found ->
 			p.pfile
 			p.pfile

+ 4 - 3
src/generators/genneko.ml

@@ -57,11 +57,12 @@ let pos ctx p =
 				| false -> try
 				| false -> try
 					(* lookup relative path *)
 					(* lookup relative path *)
 					let len = String.length p.pfile in
 					let len = String.length p.pfile in
-					let base = List.find (fun path ->
+					let base = ctx.com.class_paths#find (fun path ->
+						let path = path#path in
 						let l = String.length path in
 						let l = String.length path in
 						len > l && String.sub p.pfile 0 l = path
 						len > l && String.sub p.pfile 0 l = path
-					) ctx.com.Common.class_path in
-					let l = String.length base in
+					) in
+					let l = String.length base#path in
 					String.sub p.pfile l (len - l)
 					String.sub p.pfile l (len - l)
 
 
 					with Not_found -> p.pfile
 					with Not_found -> p.pfile

+ 1 - 2
src/macro/eval/evalMain.ml

@@ -379,8 +379,7 @@ let setup get_api =
 	let api = get_api (fun() -> (get_ctx()).curapi.get_com()) (fun() -> (get_ctx()).curapi) in
 	let api = get_api (fun() -> (get_ctx()).curapi.get_com()) (fun() -> (get_ctx()).curapi) in
 	List.iter (fun (n,v) ->
 	List.iter (fun (n,v) ->
 		Hashtbl.replace GlobalState.macro_lib n v
 		Hashtbl.replace GlobalState.macro_lib n v
-	) api;
-	Globals.macro_platform := Globals.Eval
+	) api
 
 
 let do_reuse ctx api =
 let do_reuse ctx api =
 	ctx.curapi <- api;
 	ctx.curapi <- api;

+ 8 - 10
src/macro/macroApi.ml

@@ -53,7 +53,6 @@ type 'value compiler_api = {
 	define_module : string -> 'value list -> ((string * Globals.pos) list * Ast.import_mode) list -> Ast.type_path list -> unit;
 	define_module : string -> 'value list -> ((string * Globals.pos) list * Ast.import_mode) list -> Ast.type_path list -> unit;
 	module_dependency : string -> string -> unit;
 	module_dependency : string -> string -> unit;
 	current_module : unit -> module_def;
 	current_module : unit -> module_def;
-	use_cache : unit -> bool;
 	format_string : string -> Globals.pos -> Ast.expr;
 	format_string : string -> Globals.pos -> Ast.expr;
 	cast_or_unify : Type.t -> texpr -> Globals.pos -> bool;
 	cast_or_unify : Type.t -> texpr -> Globals.pos -> bool;
 	add_global_metadata : string -> string -> (bool * bool * bool) -> pos -> unit;
 	add_global_metadata : string -> string -> (bool * bool * bool) -> pos -> unit;
@@ -1846,7 +1845,7 @@ let macro_api ccom get_api =
 			vnull
 			vnull
 		);
 		);
 		"class_path", vfun0 (fun() ->
 		"class_path", vfun0 (fun() ->
-			encode_array (List.map encode_string (ccom()).class_path);
+			encode_array (List.map encode_string (ccom()).class_paths#as_string_list);
 		);
 		);
 		"resolve_path", vfun1 (fun file ->
 		"resolve_path", vfun1 (fun file ->
 			let file = decode_string file in
 			let file = decode_string file in
@@ -2069,8 +2068,7 @@ let macro_api ccom get_api =
 		);
 		);
 		"flush_disk_cache", vfun0 (fun () ->
 		"flush_disk_cache", vfun0 (fun () ->
 			let com = (get_api()).get_com() in
 			let com = (get_api()).get_com() in
-			com.file_lookup_cache#clear;
-			com.readdir_cache#clear;
+			com.class_paths#clear_cache;
 			vnull
 			vnull
 		);
 		);
 		"get_pos_infos", vfun1 (fun p ->
 		"get_pos_infos", vfun1 (fun p ->
@@ -2169,15 +2167,15 @@ let macro_api ccom get_api =
 		"add_class_path", vfun1 (fun cp ->
 		"add_class_path", vfun1 (fun cp ->
 			let com = ccom() in
 			let com = ccom() in
 			let cp = decode_string cp in
 			let cp = decode_string cp in
-			let cp = Path.add_trailing_slash cp in
-			com.class_path <- cp :: com.class_path;
+			let path = Path.add_trailing_slash cp in
+			let cp = new ClassPath.directory_class_path path User in
+			com.class_paths#add cp;
 			(match com.get_macros() with
 			(match com.get_macros() with
 			| Some(mcom) ->
 			| Some(mcom) ->
-				mcom.class_path <- cp :: mcom.class_path;
+				mcom.class_paths#add cp#clone;
 			| None ->
 			| None ->
 				());
 				());
-			com.file_lookup_cache#clear;
-			com.readdir_cache#clear;
+			com.class_paths#clear_cache;
 			vnull
 			vnull
 		);
 		);
 		"add_native_lib", vfun1 (fun file ->
 		"add_native_lib", vfun1 (fun file ->
@@ -2254,7 +2252,7 @@ let macro_api ccom get_api =
 				"foptimize", vbool com.foptimize;
 				"foptimize", vbool com.foptimize;
 				"platform", encode_platform com.platform;
 				"platform", encode_platform com.platform;
 				"platformConfig", encode_platform_config com.config;
 				"platformConfig", encode_platform_config com.config;
-				"stdPath", encode_array (List.map encode_string com.std_path);
+				"stdPath", encode_array (List.map (fun path -> encode_string path#path) com.class_paths#get_std_paths);
 				"mainClass", (match com.main_class with None -> vnull | Some path -> encode_path path);
 				"mainClass", (match com.main_class with None -> vnull | Some path -> encode_path path);
 				"packageRules", encode_string_map encode_package_rule com.package_rules;
 				"packageRules", encode_string_map encode_package_rule com.package_rules;
 			]
 			]

+ 1 - 1
src/optimization/dce.ml

@@ -868,7 +868,7 @@ let run com main mode =
 		com = com;
 		com = com;
 		full = full;
 		full = full;
 		dependent_types = Hashtbl.create 0;
 		dependent_types = Hashtbl.create 0;
-		std_dirs = if full then [] else List.map Path.get_full_path com.std_path;
+		std_dirs = if full then [] else List.map (fun path -> Path.get_full_path path#path) com.class_paths#get_std_paths;
 		debug = Common.defined com Define.DceDebug;
 		debug = Common.defined com Define.DceDebug;
 		added_fields = [];
 		added_fields = [];
 		follow_expr = expr;
 		follow_expr = expr;

+ 0 - 2
src/typing/callUnification.ml

@@ -513,9 +513,7 @@ object(self)
 			let ep = err.err_pos in
 			let ep = err.err_pos in
 			(* display additional info in the case the error is not part of our original call *)
 			(* display additional info in the case the error is not part of our original call *)
 			if ep.pfile <> p.pfile || ep.pmax < p.pmin || ep.pmin > p.pmax then begin
 			if ep.pfile <> p.pfile || ep.pmax < p.pmin || ep.pmin > p.pmax then begin
-				locate_macro_error := false;
 				old (if (ep = null_pos) then { err with err_pos = p } else err);
 				old (if (ep = null_pos) then { err with err_pos = p } else err);
-				locate_macro_error := true;
 				(* TODO add as sub for above error *)
 				(* TODO add as sub for above error *)
 				if ep <> null_pos then old (make_error ~depth:(err.err_depth+1) (Custom (compl_msg "Called from macro here")) p);
 				if ep <> null_pos then old (make_error ~depth:(err.err_depth+1) (Custom (compl_msg "Called from macro here")) p);
 			end else
 			end else

+ 16 - 11
src/typing/macroContext.ml

@@ -34,7 +34,6 @@ module Interp = struct
 	include BuiltApi
 	include BuiltApi
 end
 end
 
 
-let macro_enable_cache = ref false
 let macro_interp_cache = ref None
 let macro_interp_cache = ref None
 
 
 let safe_decode com v expected t p f =
 let safe_decode com v expected t p f =
@@ -270,9 +269,6 @@ let make_macro_com_api com mcom p =
 		current_module = (fun() ->
 		current_module = (fun() ->
 			null_module
 			null_module
 		);
 		);
-		use_cache = (fun() ->
-			!macro_enable_cache
-		);
 		format_string = (fun s p ->
 		format_string = (fun s p ->
 			FormatString.format_string com.defines s p (fun e p -> (e,p))
 			FormatString.format_string com.defines s p (fun e p -> (e,p))
 		);
 		);
@@ -610,9 +606,7 @@ let init_macro_interp mctx mint =
 	ignore(TypeloadModule.load_module mctx (["haxe";"macro"],"Expr") p);
 	ignore(TypeloadModule.load_module mctx (["haxe";"macro"],"Expr") p);
 	ignore(TypeloadModule.load_module mctx (["haxe";"macro"],"Type") p);
 	ignore(TypeloadModule.load_module mctx (["haxe";"macro"],"Type") p);
 	Interp.init mint;
 	Interp.init mint;
-	if !macro_enable_cache && not (Common.defined mctx.com Define.NoMacroCache) then begin
-		macro_interp_cache := Some mint;
-	end
+	macro_interp_cache := Some mint
 
 
 and flush_macro_context mint mctx =
 and flush_macro_context mint mctx =
 	let t = macro_timer mctx.com ["flush"] in
 	let t = macro_timer mctx.com ["flush"] in
@@ -711,13 +705,24 @@ let create_macro_context com =
 	com2.main_class <- None;
 	com2.main_class <- None;
 	(* Inherit most display settings, but require normal typing. *)
 	(* Inherit most display settings, but require normal typing. *)
 	com2.display <- {com.display with dms_kind = DMNone; dms_full_typing = true; dms_force_macro_typing = true; dms_inline = true; };
 	com2.display <- {com.display with dms_kind = DMNone; dms_full_typing = true; dms_force_macro_typing = true; dms_inline = true; };
-	com2.class_path <- List.filter (fun s -> not (ExtString.String.exists s "/_std/")) com2.class_path;
-	let name = platform_name !Globals.macro_platform in
-	com2.class_path <- List.map (fun p -> p ^ name ^ "/_std/") com2.std_path @ com2.class_path;
+	com2.class_paths#lock_context "macro" false;
+	let name = platform_name Eval in
+	let eval_std = ref None in
+	com2.class_paths#modify (fun cp -> match cp#scope with
+		| StdTarget ->
+			[]
+		| Std ->
+			eval_std := Some (new ClassPath.directory_class_path (cp#path ^ name ^ "/_std/") StdTarget);
+			[cp#clone]
+		| _ ->
+			[cp#clone]
+	) com.class_paths#as_list;
+	(* Eval _std must be in front so we don't look into hxnodejs or something. *)
+	com2.class_paths#add (Option.get !eval_std);
 	let defines = adapt_defines_to_macro_context com2.defines; in
 	let defines = adapt_defines_to_macro_context com2.defines; in
 	com2.defines.values <- defines.values;
 	com2.defines.values <- defines.values;
 	com2.defines.defines_signature <- None;
 	com2.defines.defines_signature <- None;
-	com2.platform <- !Globals.macro_platform;
+	com2.platform <- Eval;
 	Common.init_platform com2;
 	Common.init_platform com2;
 	let mctx = !create_context_ref com2 None in
 	let mctx = !create_context_ref com2 None in
 	mctx.is_display_file <- false;
 	mctx.is_display_file <- false;

+ 7 - 3
src/typing/typeload.ml

@@ -33,8 +33,6 @@ open Typecore
 open Error
 open Error
 open Globals
 open Globals
 
 
-let build_count = ref 0
-
 let type_function_params_ref = ref (fun _ _ _ _ _ -> die "" __LOC__)
 let type_function_params_ref = ref (fun _ _ _ _ _ -> die "" __LOC__)
 
 
 let check_field_access ctx cff =
 let check_field_access ctx cff =
@@ -806,7 +804,13 @@ let load_core_class ctx c =
 			Common.define com2 Define.Sys;
 			Common.define com2 Define.Sys;
 			Define.raw_define_value com2.defines "target.threaded" "true"; (* hack because we check this in sys.thread classes *)
 			Define.raw_define_value com2.defines "target.threaded" "true"; (* hack because we check this in sys.thread classes *)
 			if ctx.com.is_macro_context then Common.define com2 Define.Macro;
 			if ctx.com.is_macro_context then Common.define com2 Define.Macro;
-			com2.class_path <- ctx.com.std_path;
+			com2.class_paths#lock_context (platform_name_macro ctx.com) true;
+			com2.class_paths#modify (fun cp -> match cp#scope with
+				| Std ->
+					[cp#clone]
+				| _ ->
+					[]
+			) ctx.com.class_paths#as_list;
 			if com2.display.dms_check_core_api then com2.display <- {com2.display with dms_check_core_api = false};
 			if com2.display.dms_check_core_api then com2.display <- {com2.display with dms_check_core_api = false};
 			CommonCache.lock_signature com2 "load_core_class";
 			CommonCache.lock_signature com2 "load_core_class";
 			let ctx2 = !create_context_ref com2 ctx.g.macros in
 			let ctx2 = !create_context_ref com2 ctx.g.macros in

+ 2 - 3
src/typing/typeloadFields.ml

@@ -560,7 +560,6 @@ let create_class_context c p =
 	cctx
 	cctx
 
 
 let create_typer_context_for_class ctx cctx p =
 let create_typer_context_for_class ctx cctx p =
-	locate_macro_error := true;
 	incr stats.s_classes_built;
 	incr stats.s_classes_built;
 	let c = cctx.tclass in
 	let c = cctx.tclass in
 	if cctx.is_lib && not (has_class_flag c CExtern) then ctx.com.error "@:libType can only be used in extern classes" c.cl_pos;
 	if cctx.is_lib && not (has_class_flag c CExtern) then ctx.com.error "@:libType can only be used in extern classes" c.cl_pos;
@@ -858,7 +857,7 @@ module TypeBinding = struct
 		in
 		in
 		let r = make_lazy ~force:false ctx t (fun r ->
 		let r = make_lazy ~force:false ctx t (fun r ->
 			(* type constant init fields (issue #1956) *)
 			(* type constant init fields (issue #1956) *)
-			if not !return_partial_type || (match fst e with EConst _ -> true | _ -> false) then begin
+			if not ctx.g.return_partial_type || (match fst e with EConst _ -> true | _ -> false) then begin
 				enter_field_typing_pass ctx ("bind_var_expression",fst ctx.curclass.cl_path @ [snd ctx.curclass.cl_path;ctx.curfield.cf_name]);
 				enter_field_typing_pass ctx ("bind_var_expression",fst ctx.curclass.cl_path @ [snd ctx.curclass.cl_path;ctx.curfield.cf_name]);
 				if (Meta.has (Meta.Custom ":debug.typing") (c.cl_meta @ cf.cf_meta)) then ctx.com.print (Printf.sprintf "Typing field %s.%s\n" (s_type_path c.cl_path) cf.cf_name);
 				if (Meta.has (Meta.Custom ":debug.typing") (c.cl_meta @ cf.cf_meta)) then ctx.com.print (Printf.sprintf "Typing field %s.%s\n" (s_type_path c.cl_path) cf.cf_name);
 				let e = type_var_field ctx t e fctx.is_static fctx.is_display_field p in
 				let e = type_var_field ctx t e fctx.is_static fctx.is_display_field p in
@@ -987,7 +986,7 @@ module TypeBinding = struct
 			end;
 			end;
 		in
 		in
 		let maybe_bind r =
 		let maybe_bind r =
-			if not !return_partial_type then bind r;
+			if not ctx.g.return_partial_type then bind r;
 			t
 			t
 		in
 		in
 		let r = make_lazy ~force:false ctx t maybe_bind "type_fun" in
 		let r = make_lazy ~force:false ctx t maybe_bind "type_fun" in

+ 7 - 6
src/typing/typeloadModule.ml

@@ -295,7 +295,7 @@ module ModuleLevel = struct
 				r
 				r
 			with Not_found ->
 			with Not_found ->
 				if Sys.file_exists path then begin
 				if Sys.file_exists path then begin
-					let _,r = match !TypeloadParse.parse_hook com path p with
+					let _,r = match !TypeloadParse.parse_hook com (ClassPaths.create_resolved_file path ctx.com.empty_class_path) p with
 						| ParseSuccess(data,_,_) -> data
 						| ParseSuccess(data,_,_) -> data
 						| ParseError(_,(msg,p),_) -> Parser.error msg p
 						| ParseError(_,(msg,p),_) -> Parser.error msg p
 					in
 					in
@@ -393,7 +393,7 @@ module TypeLevel = struct
 				add_class_flag c CFinal;
 				add_class_flag c CFinal;
 			end
 			end
 		) d.d_meta;
 		) d.d_meta;
-		let prev_build_count = ref (!build_count - 1) in
+		let prev_build_count = ref (ctx.g.build_count - 1) in
 		let build() =
 		let build() =
 			c.cl_build <- (fun()-> Building [c]);
 			c.cl_build <- (fun()-> Building [c]);
 			let fl = TypeloadCheck.Inheritance.set_heritance ctx c herits p in
 			let fl = TypeloadCheck.Inheritance.set_heritance ctx c herits p in
@@ -403,7 +403,7 @@ module TypeLevel = struct
 					List.iter (fun f -> f()) fl;
 					List.iter (fun f -> f()) fl;
 					TypeloadFields.init_class ctx c p d.d_flags d.d_data;
 					TypeloadFields.init_class ctx c p d.d_flags d.d_data;
 					c.cl_build <- (fun()-> Built);
 					c.cl_build <- (fun()-> Built);
-					incr build_count;
+					ctx.g.build_count <- ctx.g.build_count + 1;
 					List.iter (fun tp -> ignore(follow tp.ttp_type)) c.cl_params;
 					List.iter (fun tp -> ignore(follow tp.ttp_type)) c.cl_params;
 					Built;
 					Built;
 				with TypeloadCheck.Build_canceled state ->
 				with TypeloadCheck.Build_canceled state ->
@@ -414,8 +414,8 @@ module TypeLevel = struct
 					(match state with
 					(match state with
 					| Built -> die "" __LOC__
 					| Built -> die "" __LOC__
 					| Building cl ->
 					| Building cl ->
-						if !build_count = !prev_build_count then raise_typing_error ("Loop in class building prevent compiler termination (" ^ String.concat "," (List.map (fun c -> s_type_path c.cl_path) cl) ^ ")") c.cl_pos;
-						prev_build_count := !build_count;
+						if ctx.g.build_count = !prev_build_count then raise_typing_error ("Loop in class building prevent compiler termination (" ^ String.concat "," (List.map (fun c -> s_type_path c.cl_path) cl) ^ ")") c.cl_pos;
+						prev_build_count := ctx.g.build_count;
 						rebuild();
 						rebuild();
 						Building (c :: cl)
 						Building (c :: cl)
 					| BuildMacro f ->
 					| BuildMacro f ->
@@ -850,7 +850,8 @@ and load_module' ctx m p =
 			let is_extern = ref false in
 			let is_extern = ref false in
 			let file, decls = try
 			let file, decls = try
 				(* Try parsing *)
 				(* Try parsing *)
-				TypeloadParse.parse_module ctx m p
+				let rfile,decls = TypeloadParse.parse_module ctx m p in
+				rfile.file,decls
 			with Not_found ->
 			with Not_found ->
 				(* Nothing to parse, try loading extern type *)
 				(* Nothing to parse, try loading extern type *)
 				let rec loop = function
 				let rec loop = function

+ 30 - 25
src/typing/typeloadParse.ml

@@ -58,8 +58,8 @@ let parse_file_from_lexbuf com file p lexbuf =
 let parse_file_from_string com file p string =
 let parse_file_from_string com file p string =
 	parse_file_from_lexbuf com file p (Sedlexing.Utf8.from_string string)
 	parse_file_from_lexbuf com file p (Sedlexing.Utf8.from_string string)
 
 
-let parse_file com file p =
-	let file_key = com.file_keys#get file in
+let parse_file com rfile p =
+	let file_key = com.file_keys#get rfile.ClassPaths.file in
 	let contents = match com.file_contents with
 	let contents = match com.file_contents with
 		| [] when (Common.defined com Define.DisplayStdin) && DisplayPosition.display_position#is_in_file file_key ->
 		| [] when (Common.defined com Define.DisplayStdin) && DisplayPosition.display_position#is_in_file file_key ->
 			let s = Std.input_all stdin in
 			let s = Std.input_all stdin in
@@ -73,10 +73,13 @@ let parse_file com file p =
 
 
 	match contents with
 	match contents with
 	| Some s ->
 	| Some s ->
-		parse_file_from_string com file p s
+		parse_file_from_string com rfile.file p s
 	| _ ->
 	| _ ->
-		let ch = try open_in_bin file with _ -> raise_typing_error ("Could not open " ^ file) p in
-		Std.finally (fun() -> close_in ch) (parse_file_from_lexbuf com file p) (Sedlexing.Utf8.from_channel ch)
+		match rfile.class_path#file_kind with
+		| FFile ->
+			let file = rfile.file in
+			let ch = try open_in_bin file with _ -> raise_typing_error ("Could not open " ^ file) p in
+			Std.finally (fun() -> close_in ch) (parse_file_from_lexbuf com file p) (Sedlexing.Utf8.from_channel ch)
 
 
 let parse_hook = ref parse_file
 let parse_hook = ref parse_file
 
 
@@ -95,21 +98,23 @@ let resolve_module_file com m remap p =
 			String.concat "/" (x :: l) ^ "/" ^ name
 			String.concat "/" (x :: l) ^ "/" ^ name
 		) ^ ".hx"
 		) ^ ".hx"
 	in
 	in
-	let file = Common.find_file com compose_path in
-	let file = (match ExtString.String.lowercase (snd m) with
-	| "con" | "aux" | "prn" | "nul" | "com1" | "com2" | "com3" | "lpt1" | "lpt2" | "lpt3" when Sys.os_type = "Win32" ->
-		(* these names are reserved by the OS - old DOS legacy, such files cannot be easily created but are reported as visible *)
-		if (try (Unix.stat file).Unix.st_size with _ -> 0) > 0 then file else raise Not_found
-	| _ -> file
-	) in
+	let rfile = com.class_paths#find_file compose_path in
+	begin match rfile.class_path#file_kind with
+		| FFile -> (match ExtString.String.lowercase (snd m) with
+			| "con" | "aux" | "prn" | "nul" | "com1" | "com2" | "com3" | "lpt1" | "lpt2" | "lpt3" when Sys.os_type = "Win32" ->
+				(* these names are reserved by the OS - old DOS legacy, such files cannot be easily created but are reported as visible *)
+				if (try (Unix.stat rfile.file).Unix.st_size with _ -> 0) > 0 then () else raise Not_found
+			| _ ->
+				())
+	end;
 	(* if we try to load a std.xxxx class and resolve a real std file, the package name is not valid, ignore *)
 	(* 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
 	(match fst m with
 	| "std" :: _ ->
 	| "std" :: _ ->
-		let file_key = com.file_keys#get file in
-		if List.exists (fun path -> Path.UniqueKey.starts_with file_key (com.file_keys#get path)) com.std_path then raise Not_found;
+		let file_key = com.file_keys#get rfile.file in
+		if List.exists (fun path -> Path.UniqueKey.starts_with file_key (com.file_keys#get path#path)) com.class_paths#get_std_paths then raise Not_found;
 	| _ -> ());
 	| _ -> ());
 	if !forbid then begin
 	if !forbid then begin
-		let parse_result = (!parse_hook) com file p in
+		let parse_result = (!parse_hook) com rfile p in
 		let rec loop decls = match decls with
 		let rec loop decls = match decls with
 			| ((EImport _,_) | (EUsing _,_)) :: decls -> loop decls
 			| ((EImport _,_) | (EUsing _,_)) :: decls -> loop decls
 			| (EClass d,_) :: _ -> d.d_meta
 			| (EClass d,_) :: _ -> d.d_meta
@@ -128,15 +133,15 @@ let resolve_module_file com m remap p =
 			raise (Forbid_package ((x,m,p),[],platform_name_macro com));
 			raise (Forbid_package ((x,m,p),[],platform_name_macro com));
 		end;
 		end;
 	end;
 	end;
-	file
+	rfile
 
 
 let resolve_module_file com m remap p =
 let resolve_module_file com m remap p =
 	try
 	try
 		com.module_to_file#find m
 		com.module_to_file#find m
 	with Not_found ->
 	with Not_found ->
-		let file = resolve_module_file com m remap p in
-		com.module_to_file#add m file;
-		file
+		let rfile = resolve_module_file com m remap p in
+		com.module_to_file#add m rfile;
+		rfile
 
 
 (* let resolve_module_file com m remap p =
 (* let resolve_module_file com m remap p =
 	let timer = Timer.timer ["typing";"resolve_module_file"] in
 	let timer = Timer.timer ["typing";"resolve_module_file"] in
@@ -287,20 +292,20 @@ let parse_module_file com file p =
 
 
 let parse_module' com m p =
 let parse_module' com m p =
 	let remap = ref (fst m) in
 	let remap = ref (fst m) in
-	let file = resolve_module_file com m remap p in
-	let pack,decls = parse_module_file com file p in
-	file,remap,pack,decls
+	let rfile = resolve_module_file com m remap p in
+	let pack,decls = parse_module_file com rfile p in
+	rfile,remap,pack,decls
 
 
 let parse_module ctx m p =
 let parse_module ctx m p =
-	let file,remap,pack,decls = parse_module' ctx.com m p in
+	let rfile,remap,pack,decls = parse_module' ctx.com m p in
 	if pack <> !remap then begin
 	if pack <> !remap then begin
 		let spack m = if m = [] then "`package;`" else "`package " ^ (String.concat "." m) ^ ";`" in
 		let spack m = if m = [] then "`package;`" else "`package " ^ (String.concat "." m) ^ ";`" in
 		if p == null_pos then
 		if p == null_pos then
 			display_error ctx.com ("Invalid commandline class : " ^ s_type_path m ^ " should be " ^ s_type_path (pack,snd m)) p
 			display_error ctx.com ("Invalid commandline class : " ^ s_type_path m ^ " should be " ^ s_type_path (pack,snd m)) p
 		else
 		else
-			display_error ctx.com (spack pack ^ " in " ^ file ^ " should be " ^ spack (fst m)) {p with pmax = p.pmin}
+			display_error ctx.com (spack pack ^ " in " ^ rfile.file ^ " should be " ^ spack (fst m)) {p with pmax = p.pmin}
 	end;
 	end;
-	file, if !remap <> fst m then
+	rfile, if !remap <> fst m then
 		(* build typedefs to redirect to real package *)
 		(* build typedefs to redirect to real package *)
 		List.rev (List.fold_left (fun acc (t,p) ->
 		List.rev (List.fold_left (fun acc (t,p) ->
 			let build f d =
 			let build f d =

+ 1 - 1
src/typing/typerDisplay.ml

@@ -490,7 +490,7 @@ and display_expr ctx e_ast e dk mode with_type p =
 		let pl = loop e in
 		let pl = loop e in
 		raise_positions pl
 		raise_positions pl
 	| DMTypeDefinition ->
 	| DMTypeDefinition ->
-		raise_position_of_type e.etype
+		raise_position_of_type ctx e.etype
 	| DMDefault when not (!Parser.had_resume)->
 	| DMDefault when not (!Parser.had_resume)->
 		let display_fields e_ast e1 so =
 		let display_fields e_ast e1 so =
 			let l = match so with None -> 0 | Some s -> String.length s in
 			let l = match so with None -> 0 | Some s -> String.length s in

+ 6 - 2
src/typing/typerEntry.ml

@@ -15,7 +15,8 @@ let create com macros =
 			macros = macros;
 			macros = macros;
 			type_patches = Hashtbl.create 0;
 			type_patches = Hashtbl.create 0;
 			module_check_policies = [];
 			module_check_policies = [];
-			delayed = [];
+			delayed = Array.init all_typer_passes_length (fun _ -> { tasks = []});
+			delayed_min_index = 0;
 			debug_delayed = [];
 			debug_delayed = [];
 			doinline = com.display.dms_inline && not (Common.defined com Define.NoInline);
 			doinline = com.display.dms_inline && not (Common.defined com Define.NoInline);
 			retain_meta = Common.defined com Define.RetainUntypedMeta;
 			retain_meta = Common.defined com Define.RetainUntypedMeta;
@@ -24,6 +25,9 @@ let create com macros =
 			complete = false;
 			complete = false;
 			type_hints = [];
 			type_hints = [];
 			load_only_cached_modules = false;
 			load_only_cached_modules = false;
+			return_partial_type = false;
+			build_count = 0;
+			t_dynamic_def = t_dynamic;
 			functional_interface_lut = new Lookup.pmap_lookup;
 			functional_interface_lut = new Lookup.pmap_lookup;
 			do_macro = MacroContext.type_macro;
 			do_macro = MacroContext.type_macro;
 			do_load_macro = MacroContext.load_macro';
 			do_load_macro = MacroContext.load_macro';
@@ -107,7 +111,7 @@ let create com macros =
 				Type.unify t ctx.t.tbool;
 				Type.unify t ctx.t.tbool;
 				ctx.t.tbool <- t
 				ctx.t.tbool <- t
 			| "Dynamic" ->
 			| "Dynamic" ->
-				t_dynamic_def := TAbstract(a,extract_param_types a.a_params);
+				ctx.g.t_dynamic_def <- TAbstract(a,extract_param_types a.a_params);
 			| "Null" ->
 			| "Null" ->
 				let mk_null t =
 				let mk_null t =
 					try
 					try