Parcourir la source

[Hxb] Optimistic display requests (#11866)

* [hxb] load less dependencies in display requests

Can be disabled with -D disable-hxb-optimizations

* [hxb] only load up to EOF if at least one field is accessed (or full typing)

* [hxb] read/write field metadata earlier

* [hxb] disable hxb optimizations when hxb cache is disabled..

* [tests] update test

* [CI] run server tests with different cache configurations

* [hxb] delay to PForce pass

* Reduce diff and cleanup a bit

* Revert "[hxb] only load up to EOF if at least one field is accessed (or full typing)"

This reverts commit 091cd94c3f95375ad89545f0b61f9c2c566bef82.

* Only delay make_lazy_type with PForce; use PConnectField for delaying chunks reading

* [hxb] disable lazy wrapping for abstracts for now

Something's wrong there, getting Dynamic fields in display requests.
Need to investigate and add that lazy wrapping again in another PR.

* Extract typer_pass to avoid extra dependencies
Rudy Ges il y a 6 mois
Parent
commit
30769c6257

+ 5 - 0
src-json/define.json

@@ -71,6 +71,11 @@
 		"define": "disable-hxb-cache",
 		"doc": "Use in-memory cache instead of hxb powered cache."
 	},
+	{
+		"name": "DisableHxbOptimizations",
+		"define": "disable-hxb-optimizations",
+		"doc": "Disable shortcuts used by hxb cache to speed up display requests."
+	},
 	{
 		"name": "DisableUnicodeStrings",
 		"define": "disable-unicode-strings",

+ 1 - 1
src/compiler/compilationCache.ml

@@ -93,7 +93,7 @@ class context_cache (index : int) (sign : Digest.t) = object(self)
 				mc_path = path;
 				mc_id = m.m_id;
 				mc_chunks = chunks;
-				mc_extra = { m.m_extra with m_cache_state = MSGood }
+				mc_extra = { m.m_extra with m_cache_state = MSGood; m_display_deps = None }
 			}
 
 	method cache_module_in_memory path m =

+ 26 - 19
src/compiler/hxb/hxbReader.ml

@@ -152,7 +152,7 @@ class hxb_reader
 	(timers_enabled : bool)
 = object(self)
 	val mutable api = Obj.magic ""
-	val mutable minimal_restore = false
+	val mutable full_restore = true
 	val mutable current_module = null_module
 
 	val mutable ch = BytesWithPosition.create (Bytes.create 0)
@@ -179,7 +179,13 @@ class hxb_reader
 
 	method resolve_type pack mname tname =
 		try
-			api#resolve_type pack mname tname
+			let mt = api#resolve_type pack mname tname in
+			if not full_restore then begin
+				let mdep = (t_infos mt).mt_module in
+				if mdep != null_module && current_module.m_path != mdep.m_path then
+					current_module.m_extra.m_display_deps <- Some (PMap.add mdep.m_id (create_dependency mdep MDepFromTyping) (Option.get current_module.m_extra.m_display_deps))
+			end;
+			mt
 		with Not_found ->
 			dump_backtrace();
 			error (Printf.sprintf "[HXB] [%s] Cannot resolve type %s" (s_type_path current_module.m_path) (s_type_path ((pack @ [mname]),tname)))
@@ -763,9 +769,9 @@ class hxb_reader
 			)
 		| 12 ->
 			let a = self#read_abstract_ref in
-			self#make_lazy_type_dynamic (fun () ->
+			(* self#make_lazy_type_dynamic (fun () -> *)
 				TType(abstract_module_type (Lazy.force a) [],[])
-			)
+			(* ) *)
 		| 13 ->
 			let e = self#read_expr in
 			let c = {null_class with cl_kind = KExpr e; cl_module = current_module } in
@@ -892,28 +898,28 @@ class hxb_reader
 			)
 		| 70 ->
 			let a = self#read_abstract_ref in
-			self#make_lazy_type_dynamic (fun () ->
+			(* self#make_lazy_type_dynamic (fun () -> *)
 				TAbstract(Lazy.force a,[])
-			)
+			(* ) *)
 		| 71 ->
 			let a = self#read_abstract_ref in
 			let t1 = self#read_type_instance in
-			self#make_lazy_type_dynamic (fun () ->
+			(* self#make_lazy_type_dynamic (fun () -> *)
 				TAbstract(Lazy.force a,[t1])
-			)
+			(* ) *)
 		| 72 ->
 			let a = self#read_abstract_ref in
 			let t1 = self#read_type_instance in
 			let t2 = self#read_type_instance in
-			self#make_lazy_type_dynamic (fun () ->
+			(* self#make_lazy_type_dynamic (fun () -> *)
 				TAbstract(Lazy.force a,[t1;t2])
-			)
+			(* ) *)
 		| 79 ->
 			let a = self#read_abstract_ref in
 			let tl = self#read_types in
-			self#make_lazy_type_dynamic (fun () ->
+			(* self#make_lazy_type_dynamic (fun () -> *)
 				TAbstract(Lazy.force a,tl)
-			)
+			(* ) *)
 		| 80 ->
 			empty_anon
 		| 81 ->
@@ -1382,8 +1388,9 @@ class hxb_reader
 	method read_class_field_forward =
 		let name = self#read_string in
 		let pos,name_pos = self#read_pos_pair in
+		let cf_meta = self#read_metadata in
 		let overloads = self#read_list (fun () -> self#read_class_field_forward) in
-		{ null_field with cf_name = name; cf_pos = pos; cf_name_pos = name_pos; cf_overloads = overloads }
+		{ null_field with cf_name = name; cf_pos = pos; cf_name_pos = name_pos; cf_overloads = overloads; cf_meta = cf_meta }
 
 	method start_texpr =
 		begin match read_byte ch with
@@ -1441,7 +1448,6 @@ class hxb_reader
 		let flags = read_uleb128 ch in
 
 		let doc = self#read_option (fun () -> self#read_documentation) in
-		cf.cf_meta <- self#read_metadata;
 		let kind = self#read_field_kind in
 
 		let expr,expr_unoptimized = match read_byte ch with
@@ -2020,11 +2026,12 @@ class hxb_reader
 			assert(has_string_pool);
 			current_module <- self#read_mdf;
 			incr stats.modules_partially_restored;
+			if not full_restore then current_module.m_extra.m_display_deps <- Some PMap.empty
 		| MTF ->
 			current_module.m_types <- self#read_mtf;
 			api#add_module current_module;
 		| IMP ->
-			if not minimal_restore then self#read_imports;
+			if full_restore then self#read_imports;
 		| CLR ->
 			self#read_clr;
 		| ENR ->
@@ -2092,11 +2099,11 @@ class hxb_reader
 		close()
 
 	method read_chunks (new_api : hxb_reader_api) (chunks : cached_chunks) =
-		fst (self#read_chunks_until new_api chunks EOM false)
+		fst (self#read_chunks_until new_api chunks EOM true)
 
-	method read_chunks_until (new_api : hxb_reader_api) (chunks : cached_chunks) end_chunk minimal_restore' =
+	method read_chunks_until (new_api : hxb_reader_api) (chunks : cached_chunks) end_chunk full_restore' =
 		api <- new_api;
-		minimal_restore <- minimal_restore';
+		full_restore <- full_restore';
 		let rec loop = function
 			| (kind,data) :: chunks ->
 				ch <- BytesWithPosition.create data;
@@ -2109,7 +2116,7 @@ class hxb_reader
 
 	method read (new_api : hxb_reader_api) (bytes : bytes) =
 		api <- new_api;
-		minimal_restore <- false;
+		full_restore <- true;
 		ch <- BytesWithPosition.create bytes;
 		if (Bytes.to_string (read_bytes ch 3)) <> "hxb" then
 			raise (HxbFailure "magic");

+ 1 - 33
src/compiler/hxb/hxbWriter.ml

@@ -415,9 +415,6 @@ type hxb_writer = {
 	docs : StringPool.t;
 	mutable chunk : Chunk.t;
 
-	mutable in_expr : bool;
-	mutable sig_deps : module_def list;
-
 	classes : (path,tclass) Pool.t;
 	enums : (path,tenum) Pool.t;
 	typedefs : (path,tdef) Pool.t;
@@ -870,28 +867,20 @@ module HxbWriter = struct
 
 	(* References *)
 
-	let maybe_add_sig_dep writer m =
-		if not writer.in_expr && m.m_path <> writer.current_module.m_path && not (List.exists (fun m' -> m'.m_path = m.m_path) writer.sig_deps) then
-			writer.sig_deps <- m :: writer.sig_deps
-
 	let write_class_ref writer (c : tclass) =
 		let i = Pool.get_or_add writer.classes c.cl_path c in
-		maybe_add_sig_dep writer c.cl_module;
 		Chunk.write_uleb128 writer.chunk i
 
 	let write_enum_ref writer (en : tenum) =
 		let i = Pool.get_or_add writer.enums en.e_path en in
-		maybe_add_sig_dep writer en.e_module;
 		Chunk.write_uleb128 writer.chunk i
 
 	let write_typedef_ref writer (td : tdef) =
 		let i = Pool.get_or_add writer.typedefs td.t_path td in
-		maybe_add_sig_dep writer td.t_module;
 		Chunk.write_uleb128 writer.chunk i
 
 	let write_abstract_ref writer (a : tabstract) =
 		let i = Pool.get_or_add writer.abstracts a.a_path a in
-		maybe_add_sig_dep writer a.a_module;
 		Chunk.write_uleb128 writer.chunk i
 
 	let write_tmono_ref writer (mono : tmono) =
@@ -1757,6 +1746,7 @@ module HxbWriter = struct
 	and write_class_field_forward writer cf =
 		Chunk.write_string writer.chunk cf.cf_name;
 		write_pos_pair writer cf.cf_pos cf.cf_name_pos;
+		write_metadata writer cf.cf_meta;
 		Chunk.write_list writer.chunk cf.cf_overloads (fun cf ->
 			write_class_field_forward writer cf;
 		);
@@ -1805,7 +1795,6 @@ module HxbWriter = struct
 		write_type_instance writer cf.cf_type;
 		Chunk.write_uleb128 writer.chunk cf.cf_flags;
 		maybe_write_documentation writer cf.cf_doc;
-		write_metadata writer cf.cf_meta;
 		write_field_kind writer cf.cf_kind;
 		let expr_chunk = match cf.cf_expr with
 			| None ->
@@ -1814,21 +1803,15 @@ module HxbWriter = struct
 			| Some e when not write_expr_immediately ->
 				Chunk.write_u8 writer.chunk 2;
 				let fctx,close = start_texpr writer e.epos in
-				let old = writer.in_expr in
-				writer.in_expr <- true;
 				write_texpr writer fctx e;
 				Chunk.write_option writer.chunk cf.cf_expr_unoptimized (write_texpr writer fctx);
-				writer.in_expr <- old;
 				let expr_chunk = close() in
 				Some expr_chunk
 			| Some e ->
 				Chunk.write_u8 writer.chunk 1;
 				let fctx,close = start_texpr writer e.epos in
-				let old = writer.in_expr in
-				writer.in_expr <- true;
 				write_texpr writer fctx e;
 				Chunk.write_option writer.chunk cf.cf_expr_unoptimized (write_texpr writer fctx);
-				writer.in_expr <- old;
 				let expr_pre_chunk,expr_chunk = close() in
 				Chunk.export_data expr_pre_chunk writer.chunk;
 				Chunk.export_data expr_chunk writer.chunk;
@@ -2276,19 +2259,6 @@ module HxbWriter = struct
 			end;
 		end;
 
-		(* Note: this is only a start, and is still including a lot of dependencies *)
-		(* that are not actually needed for signature only. *)
-		let sig_deps = ref PMap.empty in
-		List.iter (fun mdep ->
-			let dep = {md_sign = mdep.m_extra.m_sign; md_path = mdep.m_path; md_kind = mdep.m_extra.m_kind; md_origin = MDepFromTyping} in
-			sig_deps := PMap.add mdep.m_id dep !sig_deps;
-		) writer.sig_deps;
-		PMap.iter (fun id mdep -> match mdep.md_kind, mdep.md_origin with
-			| (MCode | MExtern), MDepFromMacro when mdep.md_sign = m.m_extra.m_sign -> sig_deps := PMap.add id mdep !sig_deps;
-			| _ -> ()
-		) m.m_extra.m_deps;
-		m.m_extra.m_sig_deps <- Some !sig_deps;
-
 		start_chunk writer EOT;
 		start_chunk writer EOF;
 		start_chunk writer EOM;
@@ -2326,8 +2296,6 @@ let create config string_pool warn anon_id =
 		chunks = DynArray.create ();
 		cp = cp;
 		has_own_string_pool;
-		sig_deps = [];
-		in_expr = false;
 		docs = StringPool.create ();
 		chunk = Obj.magic ();
 		classes = Pool.create ();

+ 28 - 27
src/compiler/server.ml

@@ -226,6 +226,13 @@ let get_changed_directories sctx com =
 	t();
 	dirs
 
+let full_typing com m_extra =
+	com.is_macro_context
+	|| com.display.dms_full_typing
+	|| Define.defined com.defines Define.DisableHxbCache
+	|| Define.defined com.defines Define.DisableHxbOptimizations
+	|| DisplayPosition.display_position#is_in_file (Path.UniqueKey.lazy_key m_extra.m_file)
+
 (* Checks if module [m] can be reused from the cache and returns None in that case. Otherwise, returns
    [Some m'] where [m'] is the module responsible for [m] not being reusable. *)
 let check_module sctx com m_path m_extra p =
@@ -327,11 +334,7 @@ let check_module sctx com m_path m_extra p =
 			try
 				check_module_path();
 				if not (has_policy NoFileSystemCheck) || Path.file_extension (Path.UniqueKey.lazy_path m_extra.m_file) <> "hx" then check_file();
-				if (
-					com.is_macro_context
-					|| com.display.dms_full_typing
-					|| DisplayPosition.display_position#is_in_file (Path.UniqueKey.lazy_key m_extra.m_file)
-				) then check_dependencies();
+				if full_typing com m_extra then check_dependencies();
 				None
 			with
 			| Dirty reason ->
@@ -393,7 +396,7 @@ let check_module sctx com m_path m_extra p =
 let get_hxb_module com cc path =
 	try
 		let mc = cc#get_hxb_module path in
-		if not com.is_macro_context && not com.display.dms_full_typing && not (DisplayPosition.display_position#is_in_file (Path.UniqueKey.lazy_key mc.mc_extra.m_file)) then begin
+		if not (full_typing com mc.mc_extra) then begin
 			mc.mc_extra.m_cache_state <- MSGood;
 			BinaryModule mc
 		end else
@@ -407,7 +410,7 @@ let get_hxb_module com cc path =
 class hxb_reader_api_server
 	(com : Common.context)
 	(cc : context_cache)
-	(delay : (unit -> unit) -> unit)
+	(delay : TyperPass.typer_pass -> (unit -> unit) -> unit)
 = object(self)
 
 	method make_module (path : path) (file : string) =
@@ -419,7 +422,7 @@ class hxb_reader_api_server
 			m_statics = None;
 			(* Creating a new m_extra because if we keep the same reference, display requests *)
 			(* can alter it with bad data (for example adding dependencies that are not cached) *)
-			m_extra = { mc.mc_extra with m_deps = mc.mc_extra.m_deps }
+			m_extra = { mc.mc_extra with m_deps = mc.mc_extra.m_deps; m_display_deps = None }
 		}
 
 	method add_module (m : module_def) =
@@ -436,20 +439,21 @@ class hxb_reader_api_server
 			m
 		| BinaryModule mc ->
 			let reader = new HxbReader.hxb_reader path com.hxb_reader_stats (Some cc#get_string_pool_arr) (Common.defined com Define.HxbTimes) in
-			let is_display_file = DisplayPosition.display_position#is_in_file (Path.UniqueKey.lazy_key mc.mc_extra.m_file) in
-			let full_restore = com.is_macro_context || com.display.dms_full_typing || is_display_file in
+			let full_restore = full_typing com mc.mc_extra in
 			let f_next chunks until =
-				let t_hxb = Timer.timer ["server";"module cache";"hxb read";"until " ^ (string_of_chunk_kind until)] in
-				let r = reader#read_chunks_until (self :> HxbReaderApi.hxb_reader_api) chunks until (not full_restore) in
+				let macro = if com.is_macro_context then " (macro)" else "" in
+				let t_hxb = Timer.timer ["server";"module cache";"hxb read" ^ macro;"until " ^ (string_of_chunk_kind until)] in
+				let r = reader#read_chunks_until (self :> HxbReaderApi.hxb_reader_api) chunks until full_restore in
 				t_hxb();
 				r
 			in
+
 			let m,chunks = f_next mc.mc_chunks EOT in
 
 			(* We try to avoid reading expressions as much as possible, so we only do this for
 				 our current display file if we're in display mode. *)
 			if full_restore then ignore(f_next chunks EOM)
-			else delay (fun () -> ignore(f_next chunks EOF));
+			else delay PConnectField (fun () -> ignore(f_next chunks EOF));
 			m
 		| BadModule reason ->
 			die (Printf.sprintf "Unexpected BadModule %s (%s)" (s_type_path path) (Printer.s_module_skip_reason reason)) __LOC__
@@ -468,12 +472,11 @@ class hxb_reader_api_server
 		i
 
 	method read_expression_eagerly (cf : tclass_field) =
-		com.display.dms_full_typing
+		com.is_macro_context || com.display.dms_full_typing || Define.defined com.defines Define.DisableHxbOptimizations
 
 	method make_lazy_type t f =
 		let r = make_unforced_lazy t f "server-api" in
-		 (* TODO: This should probably use the PForce pass, not PConnectField *)
-		delay (fun () -> ignore(lazy_type r));
+		delay PForce (fun () -> ignore(lazy_type r));
 		TLazy r
 end
 
@@ -508,11 +511,7 @@ let rec add_modules sctx com delay (m : module_def) (from_binary : bool) (p : po
 				if not from_binary || m != m then
 					com.module_lut#add m.m_path m;
 				handle_cache_bound_objects com m.m_extra.m_cache_bound_objects;
-				let full_restore =
-					com.is_macro_context
-					|| com.display.dms_full_typing
-					|| DisplayPosition.display_position#is_in_file (Path.UniqueKey.lazy_key m.m_extra.m_file)
-				in
+				let full_restore = full_typing com m.m_extra in
 				PMap.iter (fun _ mdep ->
 					let mpath = mdep.md_path in
 					if mdep.md_sign = own_sign then begin
@@ -531,7 +530,7 @@ let rec add_modules sctx com delay (m : module_def) (from_binary : bool) (p : po
 						in
 						add_modules (tabs ^ "  ") m0 m2
 					end
-				) (if full_restore then m.m_extra.m_deps else Option.default m.m_extra.m_deps m.m_extra.m_sig_deps)
+				) (if full_restore then m.m_extra.m_deps else Option.default m.m_extra.m_deps m.m_extra.m_display_deps)
 			)
 		end
 	in
@@ -584,8 +583,7 @@ and type_module sctx com delay mpath p =
 			begin match check_module sctx mpath mc.mc_extra p with
 				| None ->
 					let reader = new HxbReader.hxb_reader mpath com.hxb_reader_stats (Some cc#get_string_pool_arr) (Common.defined com Define.HxbTimes) in
-					let is_display_file = DisplayPosition.display_position#is_in_file (Path.UniqueKey.lazy_key mc.mc_extra.m_file) in
-					let full_restore = com.is_macro_context || com.display.dms_full_typing || is_display_file in
+					let full_restore = full_typing com mc.mc_extra in
 					let api = match com.hxb_reader_api with
 						| Some api ->
 							api
@@ -595,16 +593,19 @@ and type_module sctx com delay mpath p =
 							api
 					in
 					let f_next chunks until =
-						let t_hxb = Timer.timer ["server";"module cache";"hxb read";"until " ^ (string_of_chunk_kind until)] in
-						let r = reader#read_chunks_until api chunks until (not full_restore) in
+						let macro = if com.is_macro_context then " (macro)" else "" in
+						let t_hxb = Timer.timer ["server";"module cache";"hxb read" ^ macro;"until " ^ (string_of_chunk_kind until)] in
+						let r = reader#read_chunks_until api chunks until full_restore in
 						t_hxb();
 						r
 					in
+
 					let m,chunks = f_next mc.mc_chunks EOT in
+
 					(* We try to avoid reading expressions as much as possible, so we only do this for
 					   our current display file if we're in display mode. *)
 					if full_restore then ignore(f_next chunks EOM)
-					else delay (fun () -> ignore(f_next chunks EOF));
+					else delay PConnectField (fun () -> ignore(f_next chunks EOF));
 					add_modules true m;
 				| Some reason ->
 					skip mpath reason

+ 9 - 8
src/context/display/displayJson.ml

@@ -105,7 +105,7 @@ class display_handler (jsonrpc : jsonrpc_handler) com (cs : CompilationCache.t)
 end
 
 class hxb_reader_api_com
-	~(minimal_restore : bool)
+	~(full_restore : bool)
 	(com : Common.context)
 	(cc : CompilationCache.context_cache)
 = object(self)
@@ -118,7 +118,7 @@ class hxb_reader_api_com
 			m_statics = None;
 			(* Creating a new m_extra because if we keep the same reference, display requests *)
 			(* can alter it with bad data (for example adding dependencies that are not cached) *)
-			m_extra = { mc.mc_extra with m_deps = mc.mc_extra.m_deps }
+			m_extra = { mc.mc_extra with m_deps = mc.mc_extra.m_deps; m_display_deps = None }
 		}
 
 	method add_module (m : module_def) =
@@ -140,7 +140,7 @@ class hxb_reader_api_com
 		with Not_found ->
 			let mc = cc#get_hxb_module m_path in
 			let reader = new HxbReader.hxb_reader mc.mc_path com.hxb_reader_stats (Some cc#get_string_pool_arr) (Common.defined com Define.HxbTimes) in
-			fst (reader#read_chunks_until (self :> HxbReaderApi.hxb_reader_api) mc.mc_chunks (if minimal_restore then MTF else EOM) minimal_restore)
+			fst (reader#read_chunks_until (self :> HxbReaderApi.hxb_reader_api) mc.mc_chunks (if full_restore then EOM else MTF) full_restore)
 
 	method basic_types =
 		com.basic
@@ -155,8 +155,8 @@ class hxb_reader_api_com
 		TLazy (make_unforced_lazy t f "com-api")
 end
 
-let find_module ~(minimal_restore : bool) com cc path =
-	(new hxb_reader_api_com ~minimal_restore com cc)#find_module path
+let find_module ~(full_restore : bool) com cc path =
+	(new hxb_reader_api_com ~full_restore com cc)#find_module path
 
 type handler_context = {
 	com : Common.context;
@@ -350,12 +350,13 @@ let handler =
 			let path = Path.parse_path (hctx.jsonrpc#get_string_param "path") in
 			let cs = hctx.display#get_cs in
 			let cc = cs#get_context sign in
+			let full_restore = Define.defined hctx.com.defines Define.DisableHxbOptimizations in
 			let m = try
-				find_module ~minimal_restore:true hctx.com cc path
+				find_module ~full_restore hctx.com cc path
 			with Not_found ->
 				hctx.send_error [jstring "No such module"]
 			in
-			hctx.send_result (generate_module (cc#get_hxb) (find_module ~minimal_restore:true hctx.com cc) m)
+			hctx.send_result (generate_module (cc#get_hxb) (find_module ~full_restore hctx.com cc) m)
 		);
 		"server/type", (fun hctx ->
 			let sign = Digest.from_hex (hctx.jsonrpc#get_string_param "signature") in
@@ -363,7 +364,7 @@ let handler =
 			let typeName = hctx.jsonrpc#get_string_param "typeName" in
 			let cc = hctx.display#get_cs#get_context sign in
 			let m = try
-				find_module ~minimal_restore:true hctx.com cc path
+				find_module ~full_restore:true hctx.com cc path
 			with Not_found ->
 				hctx.send_error [jstring "No such module"]
 			in

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

@@ -174,7 +174,7 @@ let check_display_file ctx cs =
 			let m = try
 				ctx.com.module_lut#find path
 			with Not_found ->
-				begin match !TypeloadCacheHook.type_module_hook ctx.com (delay ctx.g PConnectField) path null_pos with
+				begin match !TypeloadCacheHook.type_module_hook ctx.com (delay ctx.g) path null_pos with
 				| NoModule | BadModule _ -> raise Not_found
 				| BinaryModule mc ->
 					let api = (new TypeloadModule.hxb_reader_api_typeload ctx.com ctx.g TypeloadModule.load_module' p :> HxbReaderApi.hxb_reader_api) in

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

@@ -177,7 +177,7 @@ let explore_uncached_modules tctx cs symbols =
 			begin try
 				let m = tctx.g.do_load_module tctx (cfile.c_package,module_name) null_pos in
 				(* We have to flush immediately so we catch exceptions from weird modules *)
-				Typecore.flush_pass tctx.g Typecore.PFinal ("final",cfile.c_package @ [module_name]);
+				Typecore.flush_pass tctx.g PFinal ("final",cfile.c_package @ [module_name]);
 				m :: acc
 			with _ ->
 				acc

+ 2 - 16
src/context/typecore.ml

@@ -21,6 +21,7 @@ open Globals
 open Ast
 open Common
 open Type
+open TyperPass
 open Error
 open Resolution
 open FieldCallCandidate
@@ -50,21 +51,6 @@ type access_mode =
 	| MSet of Ast.expr option (* rhs, if exists *)
 	| MCall of Ast.expr list (* call arguments *)
 
-type typer_pass =
-	| PBuildModule			(* build the module structure and setup module type parameters *)
-	| PBuildClass			(* build the class structure *)
-	| PConnectField			(* handle associated fields, which may affect each other. E.g. a property and its getter *)
-	| PTypeField			(* type the class field, allow access to types structures *)
-	| PCheckConstraint		(* perform late constraint checks with inferred types *)
-	| PForce				(* usually ensure that lazy have been evaluated *)
-	| 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 = {
 	curmod : module_def;
 	import_resolution : resolution_list;
@@ -484,7 +470,7 @@ let delay_if_mono g p t f = match follow t with
 	| _ ->
 		f()
 
-let rec flush_pass g p where =
+let rec flush_pass g (p : typer_pass) where =
 	let rec loop i =
 		if i > (Obj.magic p) then
 			()

+ 14 - 0
src/context/typerPass.ml

@@ -0,0 +1,14 @@
+type typer_pass =
+	| PBuildModule			(* build the module structure and setup module type parameters *)
+	| PBuildClass			(* build the class structure *)
+	| PConnectField			(* handle associated fields, which may affect each other. E.g. a property and its getter *)
+	| PTypeField			(* type the class field, allow access to types structures *)
+	| PCheckConstraint		(* perform late constraint checks with inferred types *)
+	| PForce				(* usually ensure that lazy have been evaluated *)
+	| 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

+ 5 - 2
src/core/tFunctions.ml

@@ -183,7 +183,7 @@ let module_extra file sign time kind added policy =
 		m_time = time;
 		m_processed = 0;
 		m_deps = PMap.empty;
-		m_sig_deps = None;
+		m_display_deps = None;
 		m_kind = kind;
 		m_cache_bound_objects = DynArray.create ();
 		m_features = Hashtbl.create 0;
@@ -303,13 +303,16 @@ let null_abstract = {
 	a_enum = false;
 }
 
+let create_dependency mdep origin =
+	{md_sign = mdep.m_extra.m_sign; md_path = mdep.m_path; md_kind = mdep.m_extra.m_kind; md_origin = origin}
+
 let add_dependency ?(skip_postprocess=false) m mdep = function
 	(* These module dependency origins should not add as a dependency *)
 	| MDepFromMacroInclude -> ()
 
 	| origin ->
 		if m != null_module && mdep != null_module && (m.m_path != mdep.m_path || m.m_extra.m_sign != mdep.m_extra.m_sign) then begin
-			m.m_extra.m_deps <- PMap.add mdep.m_id ({md_sign = mdep.m_extra.m_sign; md_path = mdep.m_path; md_kind = mdep.m_extra.m_kind; md_origin = origin}) m.m_extra.m_deps;
+			m.m_extra.m_deps <- PMap.add mdep.m_id (create_dependency mdep origin) m.m_extra.m_deps;
 			(* In case the module is cached, we'll have to run post-processing on it again (issue #10635) *)
 			if not skip_postprocess then m.m_extra.m_processed <- 0
 		end

+ 1 - 1
src/core/tType.ml

@@ -434,7 +434,7 @@ and module_def_extra = {
 	mutable m_checked : int;
 	mutable m_processed : int;
 	mutable m_deps : (int,module_dep) PMap.t;
-	mutable m_sig_deps : (int,module_dep) PMap.t option;
+	mutable m_display_deps : (int,module_dep) PMap.t option;
 	mutable m_kind : module_kind;
 	mutable m_cache_bound_objects : cache_bound_object DynArray.t;
 	mutable m_features : (string,bool) Hashtbl.t;

+ 2 - 1
src/typing/typeloadCacheHook.ml

@@ -1,5 +1,6 @@
 open Globals
 open TType
+open TyperPass
 open Common
 open TFunctions
 
@@ -9,7 +10,7 @@ type find_module_result =
 	| BinaryModule of HxbData.module_cache
 	| NoModule
 
-let type_module_hook : (Common.context -> ((unit -> unit) -> unit) -> path -> pos -> find_module_result) ref = ref (fun _ _ _ _ -> NoModule)
+let type_module_hook : (Common.context -> (typer_pass -> (unit -> unit) -> unit) -> path -> pos -> find_module_result) ref = ref (fun _ _ _ _ -> NoModule)
 
 let fake_modules = Hashtbl.create 0
 

+ 1 - 1
src/typing/typeloadModule.ml

@@ -813,7 +813,7 @@ and load_module' com g m p =
 		com.module_lut#find m
 	with Not_found ->
 		(* Check cache *)
-		match !TypeloadCacheHook.type_module_hook com (delay g PConnectField) m p with
+		match !TypeloadCacheHook.type_module_hook com (delay g) m p with
 		| GoodModule m ->
 			m
 		| BinaryModule _ ->

+ 1 - 1
src/typing/typerEntry.ml

@@ -14,7 +14,7 @@ let create com macros =
 			core_api = None;
 			macros = macros;
 			module_check_policies = [];
-			delayed = Array.init all_typer_passes_length (fun _ -> { tasks = []});
+			delayed = Array.init TyperPass.all_typer_passes_length (fun _ -> { tasks = []});
 			delayed_min_index = 0;
 			debug_delayed = [];
 			doinline = com.display.dms_inline && not (Common.defined com Define.NoInline);

+ 2 - 0
tests/runci/targets/Js.hx

@@ -126,6 +126,8 @@ class Js {
 		changeDirectory(serverDir);
 		runCommand("haxe", ["build.hxml"]);
 		runCommand("node", ["test.js"]);
+		runCommand("haxe", ["build.hxml", "-D", "disable-hxb-optimizations"]);
+		runCommand("node", ["test.js"]);
 		runCommand("haxe", ["build.hxml", "-D", "disable-hxb-cache"]);
 		runCommand("node", ["test.js"]);
 

+ 5 - 0
tests/server/src/Main.hx

@@ -17,6 +17,11 @@ class Main {
 		var server:HaxeServerAsync = null;
 		runner.onComplete.add(_ -> server.stop());
 		server = new HaxeServerAsync(() -> new HaxeServerProcessNode("haxe", ["-v"], {}, () -> {
+			var defaultArgs = [];
+			#if disable_hxb_cache defaultArgs = defaultArgs.concat(["-D", "disable-hxb-cache"]); #end
+			#if optimistic_display_requests defaultArgs = defaultArgs.concat(["-D", "optimistic-display-requests"]); #end
+			if (defaultArgs.length > 0) server.setDefaultRequestArguments(defaultArgs);
+
 			TestCase.server = server;
 			TestCase.rootCwd = cwd;
 			runner.run();

+ 0 - 1
tests/server/src/TestCase.hx

@@ -100,7 +100,6 @@ class TestCase implements ITest implements ITestCase {
 	}
 
 	function runHaxe(args:Array<String>, done:() -> Void) {
-		#if disable-hxb-cache args = ["-D", "disable-hxb-cache"].concat(args); #end
 		messages = [];
 		errorMessages = [];
 		server.rawRequest(args, null, function(result) {

+ 15 - 8
tests/server/src/cases/CsSafeTypeBuilding.hx

@@ -2,8 +2,10 @@ package cases;
 
 import haxe.display.Display;
 import haxe.display.FsPath;
+import haxe.display.Protocol;
 import haxe.display.Server;
 import utest.Assert;
+import utils.Vfs;
 
 using StringTools;
 using Lambda;
@@ -12,7 +14,8 @@ class CsSafeTypeBuilding extends TestCase {
 	var originalContent:String;
 
 	override public function setup(async:utest.Async) {
-		super.setup(async);
+		testDir = "test/cases/" + @:privateAccess TestCase.i++;
+		vfs = new Vfs(testDir);
 
 		originalContent = "";
 		vfs.putContent("Bar.hx", getTemplate("csSafeTypeBuilding/Bar.hx"));
@@ -20,6 +23,10 @@ class CsSafeTypeBuilding extends TestCase {
 		vfs.putContent("Foo.hx", getTemplate("csSafeTypeBuilding/Foo.hx"));
 		vfs.putContent("Macro.macro.hx", getTemplate("csSafeTypeBuilding/Macro.macro.hx"));
 		vfs.putContent("Main.hx", getTemplate("csSafeTypeBuilding/Main.hx"));
+
+		runHaxeJson(["--cwd", TestCase.rootCwd, "--cwd", testDir], Methods.ResetCache, {}, () -> {
+			async.done();
+		});
 	}
 
 	#if debug
@@ -120,33 +127,33 @@ class CsSafeTypeBuilding extends TestCase {
 		runHaxe(args);
 		assertResult(target);
 
-		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Baz.hx")});
+		runHaxeJson(args, ServerMethods.Invalidate, {file: new FsPath("Baz.hx")});
 		runHaxe(args);
 		assertBuilt(["Baz"]);
 		assertResult(target);
 
-		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Main.hx")});
+		runHaxeJson(args, ServerMethods.Invalidate, {file: new FsPath("Main.hx")});
 		runHaxe(args);
 		assertBuilt(["Main"]);
 		assertResult(target);
 
-		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Bar.hx")});
-		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Main.hx")});
+		runHaxeJson(args, ServerMethods.Invalidate, {file: new FsPath("Bar.hx")});
+		runHaxeJson(args, ServerMethods.Invalidate, {file: new FsPath("Main.hx")});
 		runHaxe(args);
 		assertBuilt(["Main", "Bar"]);
 		assertResult(target);
 
-		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Bar.hx")});
+		runHaxeJson(args, ServerMethods.Invalidate, {file: new FsPath("Bar.hx")});
 		runHaxe(args);
 		assertBuilt(["Main", "Bar", "Baz"]);
 		assertResult(target);
 
-		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Foo.hx")});
+		runHaxeJson(args, ServerMethods.Invalidate, {file: new FsPath("Foo.hx")});
 		runHaxe(args);
 		assertBuilt(["Main", "Bar", "Baz"]);
 		assertResult(target);
 
-		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Macro.macro.hx")});
+		runHaxeJson(args, ServerMethods.Invalidate, {file: new FsPath("Macro.macro.hx")});
 		runHaxe(args);
 		assertBuilt(["Main", "Bar", "Baz"], true);
 		assertResult(target);