Răsfoiți Sursa

add haxe.macro.CompilationServer (#5700)

* add haxe.macro.CompilationServer

* keep track of changed directories to speed up module-shadow checks

* add option to set which context is affected

* always affect existing modules as well

* fix typo [skip ci]
Simon Krajewski 9 ani în urmă
părinte
comite
75092868d4

+ 18 - 3
src/context/common.ml

@@ -313,9 +313,10 @@ let get_signature com =
 
 module CompilationServer = struct
 	type cache = {
-		mutable c_haxelib : (string list, string list) Hashtbl.t;
-		mutable c_files : ((string * string), float * Ast.package) Hashtbl.t;
-		mutable c_modules : (path * string, module_def) Hashtbl.t;
+		c_haxelib : (string list, string list) Hashtbl.t;
+		c_files : ((string * string), float * Ast.package) Hashtbl.t;
+		c_modules : (path * string, module_def) Hashtbl.t;
+		c_directories : (string, (string * float ref) list) Hashtbl.t;
 	}
 
 	type t = {
@@ -323,12 +324,18 @@ module CompilationServer = struct
 		mutable signs : (string * string) list;
 	}
 
+	type context_options =
+		| NormalContext
+		| MacroContext
+		| NormalAndMacroContext
+
 	let instance : t option ref = ref None
 
 	let create_cache () = {
 		c_haxelib = Hashtbl.create 0;
 		c_files = Hashtbl.create 0;
 		c_modules = Hashtbl.create 0;
+		c_directories = Hashtbl.create 0;
 	}
 
 	let create () =
@@ -393,6 +400,14 @@ module CompilationServer = struct
 
 	let cache_haxelib cs key value =
 		Hashtbl.replace cs.cache.c_haxelib key value
+
+	(* directories *)
+
+	let find_directories cs key =
+		Hashtbl.find cs.cache.c_directories key
+
+	let add_directories cs key value =
+		Hashtbl.replace cs.cache.c_directories key value
 end
 
 module Define = struct

+ 2 - 2
src/generators/gencommon.ml

@@ -662,11 +662,11 @@ let new_ctx con =
 		gadd_type = (fun md should_filter ->
 			if should_filter then begin
 				gen.gtypes_list <- md :: gen.gtypes_list;
-				gen.gmodules <- { m_id = alloc_mid(); m_path = (t_path md); m_types = [md]; m_extra = module_extra "" "" 0. MFake } :: gen.gmodules;
+				gen.gmodules <- { m_id = alloc_mid(); m_path = (t_path md); m_types = [md]; m_extra = module_extra "" "" 0. MFake [] } :: gen.gmodules;
 				Hashtbl.add gen.gtypes (t_path md) md;
 			end else gen.gafter_filters_ended <- (fun () ->
 				gen.gtypes_list <- md :: gen.gtypes_list;
-				gen.gmodules <- { m_id = alloc_mid(); m_path = (t_path md); m_types = [md]; m_extra = module_extra "" "" 0. MFake } :: gen.gmodules;
+				gen.gmodules <- { m_id = alloc_mid(); m_path = (t_path md); m_types = [md]; m_extra = module_extra "" "" 0. MFake [] } :: gen.gmodules;
 				Hashtbl.add gen.gtypes (t_path md) md;
 			) :: gen.gafter_filters_ended;
 		);

+ 28 - 1
src/macro/interp.ml

@@ -131,6 +131,7 @@ type extern_api = {
 	format_string : string -> Globals.pos -> Ast.expr;
 	cast_or_unify : Type.t -> texpr -> Globals.pos -> Type.texpr;
 	add_global_metadata : string -> string -> (bool * bool * bool) -> unit;
+	add_module_check_policy : string list -> int list -> bool -> int -> unit;
 }
 
 type callstack = {
@@ -2795,6 +2796,32 @@ let macro_lib =
 			| _ ->
 				error()
 		);
+		(* Compilation server *)
+		"server_add_module_check_policy", Fun4 (fun filter policy recursive context_options ->
+			match filter,policy,recursive,context_options with
+			| VArray vl1, VArray vl2, VBool b, VInt i ->
+				let sl = Array.fold_left (fun acc v -> match v with VString s -> (s :: acc) | _ -> error()) [] vl1 in
+				let il = Array.fold_left (fun acc v -> match v with VInt i -> (i :: acc) | _ -> error()) [] vl2 in
+				(get_ctx()).curapi.add_module_check_policy sl il b i;
+				VNull
+			| _ ->
+				error()
+		);
+		"server_invalidate_files", Fun1 (fun a -> match a with
+			| VArray vl ->
+				let cs = match CompilationServer.get() with Some cs -> cs | None -> failwith "compilation server not running" in
+				Array.iter (fun v -> match v with
+					| VString s ->
+						let s = Path.unique_full_path s in
+						CompilationServer.taint_modules cs s;
+						CompilationServer.remove_files cs s;
+					| _ ->
+						error()
+				) vl;
+				VNull
+			| _ ->
+				error()
+		);
 	]
 
 (* ---------------------------------------------------------------------- *)
@@ -5122,7 +5149,7 @@ let rec make_const e =
 		| TBool b -> VBool b
 		| TNull -> VNull
 		| TThis | TSuper -> raise Exit)
-	| TParenthesis e | TMeta(_,e) ->
+	| TParenthesis e | TMeta(_,e) | TCast(e,None) ->
 		make_const e
 	| TObjectDecl el ->
 		VObject (obj (hash_field (get_ctx())) (List.map (fun (f,e) -> f, make_const e) el))

+ 35 - 1
src/path.ml

@@ -110,4 +110,38 @@ let add_trailing_slash p =
 		"./"
 	else match p.[l-1] with
 		| '\\' | '/' -> p
-		| _ -> p ^ "/"
+		| _ -> p ^ "/"
+
+let rec remove_trailing_slash p =
+	let l = String.length p in
+	if l = 0 then
+		"./"
+	else match p.[l-1] with
+		| '\\' | '/' -> remove_trailing_slash (String.sub p 0 (l - 1))
+		| _ -> p
+
+open Globals
+
+let find_directories target paths =
+	let target_dirs = List.map platform_name platforms in
+	let rec loop acc dir =
+		try
+			let entries = Sys.readdir dir in
+			Array.fold_left (fun acc file ->
+				match file with
+					| "." | ".." ->
+						acc
+					| _ when Sys.is_directory (dir ^ file) && file.[0] >= 'a' && file.[0] <= 'z' ->
+						if List.mem file target_dirs && file <> target then
+							acc
+						else begin
+							let full = (dir ^ file) in
+							loop (full :: acc) (full ^ "/")
+						end
+					| _ ->
+						acc
+			) acc entries;
+		with Sys_error _ ->
+			acc
+	in
+	List.fold_left (fun acc dir -> loop acc dir) [] paths

+ 128 - 42
src/server.ml

@@ -178,11 +178,65 @@ let rec wait_loop process_params verbose accept =
 				if verbose then print_endline (Printf.sprintf "%sparsed %s (%s)" (sign_string com2) ffile info);
 				data
 	);
-	let check_module_path com m p =
-		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
+	let check_module_shadowing com paths m =
+		List.iter (fun (path,_) ->
+			let file = (path ^ (snd m.m_path)) ^ ".hx" in
+			if Sys.file_exists file then begin
+				let time = file_time file in
+				if time > m.m_extra.m_time then begin
+					if verbose then print_endline (Printf.sprintf "%smodule path might have changed: %s\n\twas: %2.0f %s\n\tnow: %2.0f %s"
+						(sign_string com) (s_type_path m.m_path) m.m_extra.m_time m.m_extra.m_file time file);
+					raise Not_found
+				end
+			end
+		) paths
+	in
+	let delays = ref [] in
+	let changed_directories = Hashtbl.create 0 in
+	let get_changed_directories (ctx : Typecore.typer) =
+		let t = Common.timer ["server";"module cache";"changed dirs"] in
+		let sign = get_signature ctx.Typecore.com in
+		let dirs = try
+			(* First, check if we already have determined changed directories for current compilation. *)
+			Hashtbl.find changed_directories sign
+		with Not_found ->
+			let dirs = try
+				(* Next, get all directories from the cache and filter the ones that haven't changed. *)
+				List.filter (fun (dir,time) ->
+					try
+						let time' = (Unix.stat (Path.remove_trailing_slash dir)).Unix.st_mtime in
+						if !time < time' then (time := time'; true) else false
+					with Unix.Unix_error _ ->
+						false
+				) (CompilationServer.find_directories cs sign)
+			with Not_found ->
+				(* There were no directories in the cache, so this must be a new context. Let's add
+				   an empty list to make sure no crazy recursion happens. *)
+				CompilationServer.add_directories cs sign [];
+				(* Register the delay that is going to populate the cache dirs. *)
+				delays := (fun () ->
+					let dirs = ref [] in
+					let add_dir path =
+						try
+							let time = (Unix.stat (Path.remove_trailing_slash path)).Unix.st_mtime in
+							dirs := (path,ref time) :: !dirs
+						with Unix.Unix_error _ ->
+							()
+					in
+					List.iter add_dir ctx.Typecore.com.class_path;
+					List.iter add_dir (Path.find_directories (platform_name ctx.Typecore.com.platform) ctx.Typecore.com.class_path);
+					if verbose then print_endline (Printf.sprintf "%sfound %i directories" (sign_string ctx.Typecore.com) (List.length !dirs));
+					CompilationServer.add_directories cs sign !dirs
+				) :: !delays;
+				(* Returning [] should be fine here because it's a new context, so we won't do any
+				   shadowing checks anyway. *)
+				[]
+			in
+			Hashtbl.add changed_directories sign dirs;
+			dirs
+		in
+		t();
+		dirs
 	in
 	let compilation_step = ref 0 in
 	let compilation_mark = ref 0 in
@@ -191,11 +245,69 @@ let rec wait_loop process_params verbose accept =
 		let t = Common.timer ["server";"module cache"] in
 		let com2 = ctx.Typecore.com in
 		let sign = get_signature com2 in
+		let content_changed m file =
+			let ffile = Path.unique_full_path file in
+			let fkey = (ffile,sign) in
+			try
+				let _, old_data = CompilationServer.find_file cs fkey in
+				(* We must use the module path here because the file path is absolute and would cause
+				   positions in the parsed declarations to differ. *)
+				let new_data = Typeload.parse_module ctx m.m_path p in
+				snd old_data <> snd new_data
+			with Not_found ->
+				true
+		in
 		let dep = ref None in
 		incr mark_loop;
 		let mark = !mark_loop in
 		let start_mark = !compilation_mark in
 		let rec check m =
+			let check_module_path () =
+				let directories = get_changed_directories ctx in
+				match m.m_extra.m_kind with
+				| MFake | MSub | MImport -> () (* don't get classpath *)
+				| MExtern ->
+					(* if we have a file then this will override our extern type *)
+					let has_file = (try check_module_shadowing com2 directories m; true with Not_found -> false) in
+					if has_file then begin
+						if verbose then print_endline ("A file is masking the library file " ^ s_type_path m.m_path);
+						raise Not_found;
+					end;
+					let rec loop = function
+						| [] ->
+							if verbose then print_endline ("No library file was found for " ^ s_type_path m.m_path);
+							raise Not_found (* no extern registration *)
+						| load :: l ->
+							match load m.m_path p with
+							| None -> loop l
+							| Some (file,_) ->
+								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
+					in
+					loop com2.load_extern_type
+				| MCode -> check_module_shadowing com2 directories m
+				| MMacro when ctx.Typecore.in_macro -> check_module_shadowing com2 directories m
+				| MMacro ->
+					let _, mctx = Typer.get_macro_context ctx p in
+					check_module_shadowing mctx.Typecore.com (get_changed_directories mctx) m
+			in
+			let has_policy policy = List.mem policy m.m_extra.m_check_policy in
+			let check_file () =
+				if file_time m.m_extra.m_file <> m.m_extra.m_time then begin
+					if has_policy CheckFileContentModification && not (content_changed m m.m_extra.m_file) then begin
+						if verbose then print_endline (Printf.sprintf "%s%s changed time not but content, reusing" (sign_string com2) m.m_extra.m_file)
+					end else begin
+						if verbose then print_endline (Printf.sprintf "%s%s not cached (%s)" (sign_string com2) (s_type_path m.m_path) (if m.m_extra.m_time = -1. then "macro-in-macro" else "modified"));
+						if m.m_extra.m_kind = MFake then Hashtbl.remove Typecore.fake_modules m.m_extra.m_file;
+						raise Not_found;
+					end
+				end
+			in
+			let check_dependencies () =
+				PMap.iter (fun _ m2 -> if not (check m2) then begin dep := Some m2; raise Not_found end) m.m_extra.m_deps;
+			in
 			if m.m_extra.m_dirty then begin
 				dep := Some m;
 				false
@@ -203,43 +315,11 @@ let rec wait_loop process_params verbose accept =
 				true
 			else try
 				if m.m_extra.m_mark <= start_mark then begin
-					(match m.m_extra.m_kind with
-					| MFake | MSub | MImport -> () (* don't get classpath *)
-					| MExtern ->
-						(* if we have a file then this will override our extern type *)
-						let has_file = (try ignore(Typeload.resolve_module_file com2 m.m_path (ref[]) p); true with Not_found -> false) in
-						if has_file then begin
-							if verbose then print_endline ("A file is masking the library file " ^ s_type_path m.m_path);
-							raise Not_found;
-						end;
-						let rec loop = function
-							| [] ->
-								if verbose then print_endline ("No library file was found for " ^ s_type_path m.m_path);
-								raise Not_found (* no extern registration *)
-							| load :: l ->
-								match load m.m_path p with
-								| None -> loop l
-								| Some (file,_) ->
-									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
-						in
-						loop com2.load_extern_type
-					| MCode -> check_module_path com2 m p
-					| MMacro when ctx.Typecore.in_macro -> check_module_path com2 m p
-					| MMacro ->
-						let _, mctx = Typer.get_macro_context ctx p in
-						check_module_path mctx.Typecore.com m p
-					);
-					if file_time m.m_extra.m_file <> m.m_extra.m_time then begin
-						if verbose then print_endline (Printf.sprintf "%s%s not cached (%s)" (sign_string com2) (s_type_path m.m_path) (if m.m_extra.m_time = -1. then "macro-in-macro" else "modified"));
-						if m.m_extra.m_kind = MFake then Hashtbl.remove Typecore.fake_modules m.m_extra.m_file;
-						raise Not_found;
-					end;
+					if not (has_policy NoCheckShadowing) then check_module_path();
+					if not (has_policy NoCheckFileTimeModification) then check_file();
 				end;
 				m.m_extra.m_mark <- mark;
-				PMap.iter (fun _ m2 -> if not (check m2) then begin dep := Some m2; raise Not_found end) m.m_extra.m_deps;
+				if not (has_policy NoCheckDependencies) then check_dependencies();
 				true
 			with Not_found ->
 				m.m_extra.m_dirty <- true;
@@ -272,8 +352,10 @@ let rec wait_loop process_params verbose accept =
 					) m.m_types;
 					if m.m_extra.m_kind <> MSub then Typeload.add_module ctx m p;
 					PMap.iter (Hashtbl.replace com2.resources) m.m_extra.m_binded_res;
-					PMap.iter (fun _ m2 -> add_modules (tabs ^ "  ") m0 m2) m.m_extra.m_deps);
+					if ctx.Typecore.in_macro || com2.display.dms_full_typing then
+						PMap.iter (fun _ m2 -> add_modules (tabs ^ "  ") m0 m2) m.m_extra.m_deps;
 					List.iter (Typer.call_init_macro ctx) m.m_extra.m_macro_calls
+				)
 			end
 		in
 		try
@@ -352,6 +434,7 @@ let rec wait_loop process_params verbose accept =
 			let data = parse_hxml_data hxml in
 			if verbose then print_endline ("Processing Arguments [" ^ String.concat "," data ^ "]");
 			(try
+				Hashtbl.clear changed_directories;
 				Common.display_default := DMNone;
 				Parser.resume_display := null_pos;
 				Typeload.return_partial_type := false;
@@ -376,10 +459,13 @@ let rec wait_loop process_params verbose accept =
 			| Arg.Bad msg ->
 				prerr_endline ("Error: " ^ msg);
 			);
+			let fl = !delays in
+			delays := [];
+			List.iter (fun f -> f()) fl;
 			if verbose then begin
 				print_endline (Printf.sprintf "Stats = %d files, %d classes, %d methods, %d macros" !(stats.s_files_parsed) !(stats.s_classes_built) !(stats.s_methods_typed) !(stats.s_macros_called));
 				print_endline (Printf.sprintf "Time spent : %.3fs" (get_time() -. t0));
-			end
+			end;
 		with Unix.Unix_error _ ->
 			if verbose then print_endline "Connection Aborted"
 		| e ->

+ 10 - 2
src/typing/type.ml

@@ -46,6 +46,12 @@ and method_kind =
 	| MethDynamic
 	| MethMacro
 
+type module_check_policy =
+	| NoCheckFileTimeModification
+	| CheckFileContentModification
+	| NoCheckDependencies
+	| NoCheckShadowing
+
 type t =
 	| TMono of t option ref
 	| TEnum of tenum * tparams
@@ -290,6 +296,7 @@ and module_def = {
 and module_def_extra = {
 	m_file : string;
 	m_sign : string;
+	mutable m_check_policy : module_check_policy list;
 	mutable m_time : float;
 	mutable m_dirty : bool;
 	mutable m_added : int;
@@ -390,7 +397,7 @@ let mk_class m path pos name_pos =
 		cl_restore = (fun() -> ());
 	}
 
-let module_extra file sign time kind =
+let module_extra file sign time kind policy =
 	{
 		m_file = file;
 		m_sign = sign;
@@ -405,6 +412,7 @@ let module_extra file sign time kind =
 		m_macro_calls = [];
 		m_if_feature = [];
 		m_features = Hashtbl.create 0;
+		m_check_policy = policy;
 	}
 
 
@@ -427,7 +435,7 @@ let null_module = {
 		m_id = alloc_mid();
 		m_path = [] , "";
 		m_types = [];
-		m_extra = module_extra "" "" 0. MFake;
+		m_extra = module_extra "" "" 0. MFake [];
 	}
 
 let null_class =

+ 2 - 1
src/typing/typecore.ml

@@ -77,6 +77,7 @@ type typer_globals = {
 	mutable hook_generate : (unit -> unit) list;
 	type_patches : (path, (string * bool, type_patch) Hashtbl.t * type_patch) Hashtbl.t;
 	mutable global_metadata : (string list * metadata_entry * (bool * bool * bool)) list;
+	mutable module_check_policies : (string list * module_check_policy list * bool) list;
 	mutable get_build_infos : unit -> (module_type * t list * class_field list) option;
 	delayed_macros : (unit -> unit) DynArray.t;
 	mutable global_using : (tclass * pos) list;
@@ -287,7 +288,7 @@ let create_fake_module ctx file =
 			m_id = alloc_mid();
 			m_path = (["$DEP"],file);
 			m_types = [];
-			m_extra = module_extra file (Common.get_signature ctx.com) (file_time file) MFake;
+			m_extra = module_extra file (Common.get_signature ctx.com) (file_time file) MFake [];
 		} in
 		Hashtbl.add fake_modules file mdep;
 		mdep

+ 6 - 2
src/typing/typeload.ml

@@ -70,12 +70,16 @@ let transform_abstract_field com this_t a_t a f =
 	| _ ->
 		f
 
+let get_policy ctx mpath =
+	let sl1 = full_dot_path mpath mpath in
+	List.fold_left (fun acc (sl2,policy,recursive) -> if match_path recursive sl1 sl2 then policy @ acc else acc) [] ctx.g.module_check_policies
+
 let make_module ctx mpath file loadp =
 	let m = {
 		m_id = alloc_mid();
 		m_path = mpath;
 		m_types = [];
-		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);
+		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) (get_policy ctx mpath);
 	} in
 	m
 
@@ -3865,7 +3869,7 @@ let rec build_generic ctx c p tl =
 			m_id = alloc_mid();
 			m_path = (pack,name);
 			m_types = [];
-			m_extra = module_extra (s_type_path (pack,name)) m.m_extra.m_sign 0. MFake;
+			m_extra = module_extra (s_type_path (pack,name)) m.m_extra.m_sign 0. MFake m.m_extra.m_check_policy;
 		} in
 		gctx.mg <- Some mg;
 		let cg = mk_class mg (pack,name) c.cl_pos null_pos in

+ 16 - 0
src/typing/typer.ml

@@ -4814,6 +4814,20 @@ let make_macro_api ctx p =
 				ctx.g.global_metadata <- (ExtString.String.nsplit s1 ".",m,config) :: ctx.g.global_metadata;
 			) meta;
 		);
+		Interp.add_module_check_policy = (fun sl il b i ->
+			let add ctx =
+				ctx.g.module_check_policies <- (List.fold_left (fun acc s -> (ExtString.String.nsplit s ".",List.map Obj.magic il,b) :: acc) ctx.g.module_check_policies sl);
+				Hashtbl.iter (fun _ m -> m.m_extra.m_check_policy <- Typeload.get_policy ctx m.m_path) ctx.g.modules;
+			in
+			let add_macro ctx = match ctx.g.macros with
+				| None -> ()
+				| Some(_,mctx) -> add mctx;
+			in
+			match Obj.magic i with
+			| CompilationServer.NormalContext -> add ctx
+			| CompilationServer.MacroContext -> add_macro ctx
+			| CompilationServer.NormalAndMacroContext -> add ctx; add_macro ctx;
+		);
 	}
 
 let rec init_macro_interp ctx mctx mint =
@@ -5184,6 +5198,7 @@ let call_init_macro ctx e =
 		in
 		let path, meth = (match loop e with
 		| [meth] -> (["haxe";"macro"],"Compiler"), meth
+		| [meth;"server"] -> (["haxe";"macro"],"CompilationServer"), meth
 		| meth :: cl :: path -> (List.rev path,cl), meth
 		| _ -> error "Invalid macro call" p) in
 		ignore(call_macro ctx path meth args p);
@@ -5204,6 +5219,7 @@ let rec create com =
 			types_module = Hashtbl.create 0;
 			type_patches = Hashtbl.create 0;
 			global_metadata = [];
+			module_check_policies = [];
 			delayed = [];
 			debug_delayed = [];
 			delayed_macros = DynArray.create();

+ 86 - 0
std/haxe/macro/CompilationServer.hx

@@ -0,0 +1,86 @@
+package haxe.macro;
+
+import haxe.macro.Compiler;
+
+@:enum
+abstract ModuleCheckPolicy(Int) {
+	/**
+		Disables file modification checks, avoiding some filesystem operations.
+	**/
+	var NoCheckFileTimeModification = 0;
+
+	/**
+		If a file is modified, also checks if its content changed. This check
+		is not free, but useful when .hx files are auto-generated.
+	**/
+	var CheckFileContentModification = 1;
+
+	/**
+		Disables dependency checks of the module.
+	**/
+	var NoCheckDependencies = 2;
+
+	/**
+		Disables file shadowing checks. Shadowing can occur when a new file
+		is added to a class-path that has higher priority than the class-path
+		of the current module file.
+	**/
+	var NoCheckShadowing = 3;
+}
+
+@:enum abstract ContextOptions(Int) {
+	/**
+		Affects only the normal context.
+	**/
+	var NormalContext = 0;
+
+	/**
+		Affects only the macro context.
+	**/
+	var MacroContext = 1;
+
+	/**
+		Affects the normal and macro contexts.
+	**/
+	var NormalAndMacroContext = 2;
+}
+
+/**
+	This class provides some methods which can be invoked from command line using
+	`--macro server.field(args)`.
+**/
+class CompilationServer {
+	#if neko
+
+	/**
+		Sets the `ModuleCheckPolicy` of all files whose dot-path matches an
+		element of `pathFilters`.
+
+		If `recursive` is true, a dot-path is considered matched if it starts
+		with the path filter. This automatically applies to path filters of
+		packages. Otherwise an exact match is required.
+
+		If an element in `pathFilters` is the empty String `""` it matches
+		everything (if `recursive = true`) or only top-level types (if
+		`recursive = false`).
+
+		The argument `contextOptions` determines which context (normal, macro
+		or both) this affects.
+
+		If a call to this function is added to the compilation parameters, the
+		compilation server should be restarted to ensure it takes effect.
+	**/
+	static public function setModuleCheckPolicy(pathFilters:Array<String>, policy:Array<ModuleCheckPolicy>, ?recursive = true, ?contextOptions:ContextOptions = NormalContext) {
+		pathFilters = [for (pathFilter in pathFilters) untyped pathFilter.__s];
+		@:privateAccess Compiler.load("server_add_module_check_policy", 4)(untyped pathFilters.__neko(), policy.__neko(), recursive, contextOptions);
+	}
+
+	/**
+		Invalidates all files given in `filePaths`, removing them from the cache.
+	**/
+	static public function invalidateFiles(filePaths:Array<String>) {
+		filePaths = [for (filePath in filePaths) untyped filePath.__s];
+		@:privateAccess Compiler.load("server_invalidate_files", 1)(untyped filePaths.__neko());
+	}
+	#end
+}