Przeglądaj źródła

[4.3.5] Backport Json RPC diagnostics (#11707)

* [display] diagnostics as json rpc (Backport #11412)

* [tests] use json rpc diagnostics

* [tests] Add test for 11695

* [tests] Update diagnostics tests

* Run some filters in diagnostics (#11220)

* let's see how much breaks

* [tests] enable diagnostics tests for 11177 and 11184

* [tests] Update test for 5306

* Don't cache/run filters for find reference/implementation requests (#11226)

* Only run filters and save cache on diagnostics, not usage requests

* [tests] Update test for 11184

* disable test

* add VUsedByTyper to avoid bad unused local errors

* revert @:compilerGenerated change

---------

Co-authored-by: Rudy Ges <[email protected]>

* [display] get rid of TypeloadParse.current_stdin

* [display] fix -D display-stdin handling

* [display] generalize fileContents behavior to other json rpc display calls

* [display] fix range of pattern variables

Note: not including texprConverter changes

see https://github.com/HaxeFoundation/haxe/commit/160a49095d5e54fe65345c896c7d02d18369b9ce
see #7282

* [tests] add test for #7282

* [tests] add test for #7931

* Remove populateCacheFromDisplay config

Legacy diagnostics = false, json rpc diagnostics = true

* [std] Diagnostics request doc

* [tests] Test Json RPC diagnostics with several open files

* [diagnostics] fix multi display files (#11722)

* [diagnostics] fix json rpc diagnostics display config

* [tests] Server tests: do not fail silently when runHaxeJsonCb errors

* [tests] add more diagnostics tests

* [display] rework multiple display files handling

* clean up a bit...

* [diagnostics] handle a.b.c.hx case, even if pointless

* [diagnostics] do not skip errors during DisplayProcessing.process_display_file

* Enable display tests again...

* [tests] fix display tests

---------

Co-authored-by: Simon Krajewski <[email protected]>
Rudy Ges 1 rok temu
rodzic
commit
034695552c
49 zmienionych plików z 677 dodań i 191 usunięć
  1. 19 10
      src/compiler/compiler.ml
  2. 11 1
      src/compiler/displayOutput.ml
  3. 43 36
      src/compiler/displayProcessing.ml
  4. 13 10
      src/compiler/server.ml
  5. 0 1
      src/compiler/serverConfig.ml
  6. 5 2
      src/context/common.ml
  7. 7 11
      src/context/display/diagnostics.ml
  8. 2 2
      src/context/display/diagnosticsPrinter.ml
  9. 46 15
      src/context/display/displayJson.ml
  10. 20 5
      src/core/display/displayPosition.ml
  11. 0 1
      src/core/displayTypes.ml
  12. 6 1
      src/core/tType.ml
  13. 4 2
      src/filters/filters.ml
  14. 3 3
      src/optimization/analyzer.ml
  15. 0 1
      src/optimization/inline.ml
  16. 0 1
      src/typing/callUnification.ml
  17. 16 16
      src/typing/typeloadParse.ml
  18. 2 2
      src/typing/typer.ml
  19. 6 4
      src/typing/typerBase.ml
  20. 18 1
      std/haxe/display/Display.hx
  21. 0 1
      std/haxe/display/Server.hx
  22. 1 1
      tests/display/build.hxml
  23. 10 3
      tests/display/src/cases/Issue5306.hx
  24. 27 14
      tests/server/src/TestCase.hx
  25. 172 5
      tests/server/src/cases/ServerTests.hx
  26. 14 8
      tests/server/src/cases/display/issues/Issue10635.hx
  27. 6 3
      tests/server/src/cases/issues/Issue10653.hx
  28. 16 15
      tests/server/src/cases/issues/Issue11177.hx
  29. 18 12
      tests/server/src/cases/issues/Issue11184.hx
  30. 23 0
      tests/server/src/cases/issues/Issue11203.hx
  31. 39 0
      tests/server/src/cases/issues/Issue11695.hx
  32. 22 0
      tests/server/src/cases/issues/Issue7282.hx
  33. 13 0
      tests/server/src/cases/issues/Issue7931.hx
  34. 5 4
      tests/server/src/cases/issues/Issue8687.hx
  35. 5 0
      tests/server/test/templates/diagnostics/multi-files/File1.hx
  36. 5 0
      tests/server/test/templates/diagnostics/multi-files/File2.hx
  37. 5 0
      tests/server/test/templates/diagnostics/multi-files/File3.hx
  38. 4 0
      tests/server/test/templates/diagnostics/multi-files/Main.hx
  39. 16 0
      tests/server/test/templates/issues/Issue11203/MainAbstract.hx
  40. 15 0
      tests/server/test/templates/issues/Issue11203/MainClass.hx
  41. 1 0
      tests/server/test/templates/issues/Issue11695/Macro1.hx
  42. 1 0
      tests/server/test/templates/issues/Issue11695/Macro2.hx
  43. 3 0
      tests/server/test/templates/issues/Issue11695/Main.hx
  44. 10 0
      tests/server/test/templates/issues/Issue7282/Main.hx
  45. 6 0
      tests/server/test/templates/issues/Issue7931/Main.hx
  46. 5 0
      tests/server/test/templates/issues/Issue9134/Main.hx
  47. 6 0
      tests/server/test/templates/issues/Issue9134/Main2.hx
  48. 2 0
      tests/server/test/templates/issues/Issue9134/Other.hx
  49. 6 0
      tests/server/test/templates/issues/Issue9134/Other2.hx

+ 19 - 10
src/compiler/compiler.ml

@@ -2,15 +2,18 @@ open Globals
 open Common
 open CompilationContext
 
-let run_or_diagnose ctx f arg =
+let run_or_diagnose ctx f =
 	let com = ctx.com in
 	let handle_diagnostics ?(depth = 0) msg kind =
 		ctx.has_error <- true;
 		add_diagnostics_message ~depth com msg kind Error;
-		DisplayOutput.emit_diagnostics ctx.com
+		match com.report_mode with
+		| RMLegacyDiagnostics _ -> DisplayOutput.emit_legacy_diagnostics ctx.com
+		| RMDiagnostics _ -> DisplayOutput.emit_diagnostics ctx.com
+		| _ -> die "" __LOC__
 	in
 	if is_diagnostics com then begin try
-			f arg
+			f ()
 		with
 		| Error.Error(msg,p,depth) ->
 			handle_diagnostics ~depth (Error.error_msg p msg) DKCompilerMessage
@@ -20,7 +23,7 @@ let run_or_diagnose ctx f arg =
 			handle_diagnostics (located (Lexer.error_msg msg) p) DKParserError
 		end
 	else
-		f arg
+		f ()
 
 let run_command ctx cmd =
 	let t = Timer.timer ["command";cmd] in
@@ -279,7 +282,7 @@ let do_type ctx tctx actx =
 		if com.display.dms_kind <> DMNone then DisplayTexpr.check_display_file tctx cs;
 		List.iter (fun cpath -> ignore(tctx.Typecore.g.Typecore.do_load_module tctx cpath null_pos)) (List.rev actx.classes);
 		Finalization.finalize tctx;
-	) ();
+	);
 	com.stage <- CTypingDone;
 	(* If we are trying to find references, let's syntax-explore everything we know to check for the
 		identifier we are interested in. We then type only those modules that contain the identifier. *)
@@ -293,23 +296,25 @@ let finalize_typing ctx tctx =
 	let t = Timer.timer ["finalize"] in
 	let com = ctx.com in
 	com.stage <- CFilteringStart;
-	let main, types, modules = run_or_diagnose ctx Finalization.generate tctx in
+	let main, types, modules = run_or_diagnose ctx (fun () -> Finalization.generate tctx) in
 	com.main <- main;
 	com.types <- types;
 	com.modules <- modules;
 	t()
 
-let filter ctx tctx =
+let filter ctx tctx before_destruction =
 	let t = Timer.timer ["filters"] in
 	DeprecationCheck.run ctx.com;
-	Filters.run ctx.com tctx ctx.com.main;
+	run_or_diagnose ctx (fun () -> Filters.run tctx ctx.com.main before_destruction);
 	t()
 
 let compile ctx actx =
 	let com = ctx.com in
 	(* Set up display configuration *)
 	DisplayProcessing.process_display_configuration ctx;
+	let restore = disable_report_mode com in
 	let display_file_dot_path = DisplayProcessing.process_display_file com actx in
+	restore ();
 	(* Initialize target: This allows access to the appropriate std packages and sets the -D defines. *)
 	let ext = Setup.initialize_target ctx com actx in
 	com.config <- get_config com; (* make sure to adapt all flags changes defined after platform *)
@@ -331,8 +336,12 @@ let compile ctx actx =
 		end;
 		DisplayProcessing.handle_display_after_typing ctx tctx display_file_dot_path;
 		finalize_typing ctx tctx;
-		DisplayProcessing.handle_display_after_finalization ctx tctx display_file_dot_path;
-		filter ctx tctx;
+		if is_diagnostics com then
+			filter ctx tctx (fun () -> DisplayProcessing.handle_display_after_finalization ctx tctx display_file_dot_path)
+		else begin
+			DisplayProcessing.handle_display_after_finalization ctx tctx display_file_dot_path;
+			filter ctx tctx (fun () -> ());
+		end;
 		if ctx.has_error then raise Abort;
 		Generate.check_auxiliary_output com actx;
 		com.stage <- CGenerationStart;

+ 11 - 1
src/compiler/displayOutput.ml

@@ -372,12 +372,22 @@ let handle_type_path_exception ctx p c is_import pos =
 		api.send_result (DisplayException.fields_to_json ctx fields kind (DisplayTypes.make_subject None pos));
 	end
 
-let emit_diagnostics com =
+let emit_legacy_diagnostics com =
 	let dctx = Diagnostics.run com in
 	let s = Json.string_of_json (DiagnosticsPrinter.json_of_diagnostics com dctx) in
 	DisplayPosition.display_position#reset;
 	raise (Completion s)
 
+let emit_diagnostics com =
+	(match com.Common.json_out with
+	| None -> die "" __LOC__
+	| Some api ->
+		let dctx = Diagnostics.run com in
+		let diagnostics = DiagnosticsPrinter.json_of_diagnostics com dctx in
+		DisplayPosition.display_position#reset;
+		api.send_result diagnostics;
+		raise Abort (* not reached because send_result always raises *))
+
 let emit_statistics tctx =
 	let stats = Statistics.collect_statistics tctx [SFFile (DisplayPosition.display_position#get).pfile] true in
 	let s = Statistics.Printer.print_statistics stats in

+ 43 - 36
src/compiler/displayProcessing.ml

@@ -22,7 +22,7 @@ let handle_display_argument_old com file_pos actx =
 		actx.did_something <- true;
 		(try Memory.display_memory com with e -> prerr_endline (Printexc.get_backtrace ()));
 	| "diagnostics" ->
-		com.report_mode <- RMDiagnostics []
+		com.report_mode <- RMLegacyDiagnostics []
 	| _ ->
 		let file, pos = try ExtString.String.split file_pos "@" with _ -> failwith ("Invalid format: " ^ file_pos) in
 		let file = Helper.unquote file in
@@ -46,9 +46,9 @@ let handle_display_argument_old com file_pos actx =
 			| "module-symbols" ->
 				create (DMModuleSymbols None)
 			| "diagnostics" ->
-				com.report_mode <- RMDiagnostics [file_unique];
+				com.report_mode <- RMLegacyDiagnostics [file_unique];
 				let dm = create DMNone in
-				{dm with dms_display_file_policy = DFPAlso; dms_per_file = true; dms_populate_cache = !ServerConfig.populate_cache_from_display}
+				{dm with dms_display_file_policy = DFPAlso; dms_per_file = true}
 			| "statistics" ->
 				com.report_mode <- RMStatistics;
 				let dm = create DMNone in
@@ -142,11 +142,11 @@ let process_display_file com actx =
 		| DFPOnly when (DisplayPosition.display_position#get).pfile = file_input_marker ->
 			actx.classes <- [];
 			com.main_class <- None;
-			begin match !TypeloadParse.current_stdin with
-			| Some input ->
-				TypeloadParse.current_stdin := None;
+			begin match com.file_contents with
+			| [_, Some input] ->
+				com.file_contents <- [];
 				DPKInput input
-			| None ->
+			| _ ->
 				DPKNone
 			end
 		| dfp ->
@@ -154,36 +154,41 @@ let process_display_file com actx =
 				actx.classes <- [];
 				com.main_class <- None;
 			end;
-			let real = Path.get_real_path (DisplayPosition.display_position#get).pfile in
-			let path = match get_module_path_from_file_path com real with
-			| Some path ->
-				if com.display.dms_kind = DMPackage then DisplayException.raise_package (fst path);
-				let path = match ExtString.String.nsplit (snd path) "." with
-					| [name;"macro"] ->
-						(* If we have a .macro.hx path, don't add the file to classes because the compiler won't find it.
-						   This can happen if we're completing in such a file. *)
-						DPKMacro (fst path,name)
-					| [name] ->
-						actx.classes <- path :: actx.classes;
-						DPKNormal path
-					| [name;target] ->
-						let path = fst path, name in
-						actx.classes <- path :: actx.classes;
-						DPKNormal path
-					| e ->
-						die "" __LOC__
+			let dpk = List.map (fun file_key ->
+				let real = Path.get_real_path (Path.UniqueKey.to_string file_key) in
+				let dpk = match get_module_path_from_file_path com real with
+				| Some path ->
+					if com.display.dms_kind = DMPackage then DisplayException.raise_package (fst path);
+					let dpk = match ExtString.String.nsplit (snd path) "." with
+						| [name;"macro"] ->
+							(* If we have a .macro.hx path, don't add the file to classes because the compiler won't find it.
+								 This can happen if we're completing in such a file. *)
+							DPKMacro (fst path,name)
+						| [name] ->
+							actx.classes <- path :: actx.classes;
+							DPKNormal path
+						| [name;target] ->
+							let path = fst path, name in
+							actx.classes <- path :: actx.classes;
+							DPKNormal path
+						| _ ->
+							failwith ("Invalid display file '" ^ real ^ "'")
+					in
+					dpk
+				| None ->
+					if not (Sys.file_exists real) then failwith "Display file does not exist";
+					(match List.rev (ExtString.String.nsplit real Path.path_sep) with
+					| file :: _ when file.[0] >= 'a' && file.[0] <= 'z' -> failwith ("Display file '" ^ file ^ "' should not start with a lowercase letter")
+					| _ -> ());
+					DPKDirect real
 				in
-				path
-			| None ->
-				if not (Sys.file_exists real) then failwith "Display file does not exist";
-				(match List.rev (ExtString.String.nsplit real Path.path_sep) with
-				| file :: _ when file.[0] >= 'a' && file.[0] <= 'z' -> failwith ("Display file '" ^ file ^ "' should not start with a lowercase letter")
-				| _ -> ());
-				DPKDirect real
-			in
-			Common.log com ("Display file : " ^ real);
+				Common.log com ("Display file : " ^ real);
+				dpk
+			) DisplayPosition.display_position#get_files in
 			Common.log com ("Classes found : ["  ^ (String.concat "," (List.map s_type_path actx.classes)) ^ "]");
-			path
+			match dpk with
+				| [dfile] -> dfile
+				| _ -> DPKNone
 
 (* 3. Loaders for display file that might be called *)
 
@@ -348,10 +353,12 @@ let handle_display_after_finalization ctx tctx display_file_dot_path =
 	end;
 	process_global_display_mode com tctx;
 	begin match com.report_mode with
+	| RMLegacyDiagnostics _ ->
+		DisplayOutput.emit_legacy_diagnostics com
 	| RMDiagnostics _ ->
 		DisplayOutput.emit_diagnostics com
 	| RMStatistics ->
 		DisplayOutput.emit_statistics tctx
 	| RMNone ->
 		()
-	end
+	end

+ 13 - 10
src/compiler/server.ml

@@ -18,15 +18,7 @@ let has_error ctx =
 	ctx.has_error || ctx.com.Common.has_error
 
 let check_display_flush ctx f_otherwise = match ctx.com.json_out with
-	| None ->
-		if is_diagnostics ctx.com then begin
-			List.iter (fun cm ->
-				add_diagnostics_message ~depth:cm.cm_depth ctx.com (located cm.cm_message cm.cm_pos) cm.cm_kind cm.cm_severity
-			) (List.rev ctx.messages);
-			raise (Completion (Diagnostics.print ctx.com))
-		end else
-			f_otherwise ()
-	| Some api ->
+	| Some api when not (is_diagnostics ctx.com) ->
 		if has_error ctx then begin
 			let errors = List.map (fun cm ->
 				JObject [
@@ -37,6 +29,17 @@ let check_display_flush ctx f_otherwise = match ctx.com.json_out with
 			) (List.rev ctx.messages) in
 			api.send_error errors
 		end
+	| _ ->
+		if is_diagnostics ctx.com then begin
+			List.iter (fun cm ->
+				add_diagnostics_message ~depth:cm.cm_depth ctx.com (located cm.cm_message cm.cm_pos) cm.cm_kind cm.cm_severity
+			) (List.rev ctx.messages);
+			(match ctx.com.report_mode with
+			| RMDiagnostics _ -> ()
+			| RMLegacyDiagnostics _ -> raise (Completion (Diagnostics.print ctx.com))
+			| _ -> die "" __LOC__)
+		end else
+			f_otherwise ()
 
 let current_stdin = ref None
 
@@ -46,7 +49,7 @@ let parse_file cs com file p =
 	and fkey = com.file_keys#get file in
 	let is_display_file = DisplayPosition.display_position#is_in_file (com.file_keys#get ffile) in
 	match is_display_file, !current_stdin with
-	| true, Some stdin when Common.defined com Define.DisplayStdin ->
+	| true, Some stdin when (com.file_contents <> [] || Common.defined com Define.DisplayStdin) ->
 		TypeloadParse.parse_file_from_string com file p stdin
 	| _ ->
 		let ftime = file_time ffile in

+ 0 - 1
src/compiler/serverConfig.ml

@@ -1,3 +1,2 @@
 let do_not_check_modules = ref false
-let populate_cache_from_display = ref true
 let legacy_completion = ref false

+ 5 - 2
src/context/common.ml

@@ -272,7 +272,8 @@ type compiler_stage =
 
 type report_mode =
 	| RMNone
-	| RMDiagnostics of Path.UniqueKey.t list
+	| RMLegacyDiagnostics of (Path.UniqueKey.t list)
+	| RMDiagnostics of (Path.UniqueKey.t list)
 	| RMStatistics
 
 class virtual ['key,'value] lookup = object(self)
@@ -382,6 +383,7 @@ type context = {
 	display_information : display_information;
 	file_lookup_cache : (string,string option) lookup;
 	file_keys : file_keys;
+	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;
 	module_to_file : (path,string) lookup;
@@ -852,6 +854,7 @@ let create compilation_step cs version args =
 		};
 		file_lookup_cache = new hashtbl_lookup;
 		file_keys = new file_keys;
+		file_contents = [];
 		readdir_cache = new hashtbl_lookup;
 		module_to_file = new hashtbl_lookup;
 		stored_typed_exprs = new hashtbl_lookup;
@@ -867,7 +870,7 @@ let create compilation_step cs version args =
 	com
 
 let is_diagnostics com = match com.report_mode with
-	| RMDiagnostics _ -> true
+	| RMLegacyDiagnostics _ | RMDiagnostics _ -> true
 	| _ -> false
 
 let disable_report_mode com =

+ 7 - 11
src/context/display/diagnostics.ml

@@ -20,13 +20,14 @@ let find_unused_variables com e =
 	let vars = Hashtbl.create 0 in
 	let pmin_map = Hashtbl.create 0 in
 	let rec loop e = match e.eexpr with
-		| TVar({v_kind = VUser _} as v,eo) when v.v_name <> "_" ->
+		| TVar({v_kind = VUser origin} as v,eo) when v.v_name <> "_" && not (has_var_flag v VUsedByTyper) ->
 			Hashtbl.add pmin_map e.epos.pmin v;
 			let p = match eo with
-				| None -> e.epos
-				| Some e1 ->
-					loop e1;
-					{ e.epos with pmax = e1.epos.pmin }
+			| Some e1 when origin <> TVOPatternVariable ->
+				loop e1;
+				{ e.epos with pmax = e1.epos.pmin }
+			| _ ->
+				e.epos
 			in
 			Hashtbl.replace vars v.v_id (v,p);
 		| TLocal ({v_kind = VUser _} as v) ->
@@ -179,15 +180,10 @@ let prepare com =
 	dctx.unresolved_identifiers <- com.display_information.unresolved_identifiers;
 	dctx
 
-let secure_generated_code ctx e =
-	(* This causes problems and sucks in general... need a different solution. But I forgot which problem this solved anyway. *)
-	(* mk (TMeta((Meta.Extern,[],e.epos),e)) e.etype e.epos *)
-	e
-
 let print com =
 	let dctx = prepare com in
 	Json.string_of_json (DiagnosticsPrinter.json_of_diagnostics com dctx)
 
 let run com =
 	let dctx = prepare com in
-	dctx
+	dctx

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

@@ -25,8 +25,8 @@ let make_diagnostic kd p sev args = {
 
 let is_diagnostics_file com file_key =
 	match com.report_mode with
-	| RMDiagnostics [] -> true
-	| RMDiagnostics file_keys -> List.exists (fun key' -> file_key = key') file_keys
+	| RMLegacyDiagnostics [] | RMDiagnostics [] -> true
+	| RMLegacyDiagnostics file_keys | RMDiagnostics file_keys -> List.mem file_key file_keys
 	| _ -> false
 
 module UnresolvedIdentifierSuggestion = struct

+ 46 - 15
src/context/display/displayJson.ml

@@ -60,18 +60,49 @@ class display_handler (jsonrpc : jsonrpc_handler) com (cs : CompilationCache.t)
 			let file = jsonrpc#get_string_param "file" in
 			Path.get_full_path file
 		) file_input_marker in
-		let pos = if requires_offset then jsonrpc#get_int_param "offset" else (-1) in
-		TypeloadParse.current_stdin := jsonrpc#get_opt_param (fun () ->
+		let contents = jsonrpc#get_opt_param (fun () ->
 			let s = jsonrpc#get_string_param "contents" in
-			Common.define com Define.DisplayStdin; (* TODO: awkward *)
 			Some s
-		) None;
+		) None in
+
+		let pos = if requires_offset then jsonrpc#get_int_param "offset" else (-1) in
 		Parser.was_auto_triggered := was_auto_triggered;
-		DisplayPosition.display_position#set {
-			pfile = file;
-			pmin = pos;
-			pmax = pos;
-		}
+
+		if file <> file_input_marker then begin
+			let file_unique = com.file_keys#get file in
+
+			DisplayPosition.display_position#set {
+				pfile = file;
+				pmin = pos;
+				pmax = pos;
+			};
+
+			com.file_contents <- [file_unique, contents];
+		end else begin
+			let file_contents = jsonrpc#get_opt_param (fun () ->
+				jsonrpc#get_opt_param (fun () -> jsonrpc#get_array_param "fileContents") []
+			) [] in
+
+			let file_contents = List.map (fun fc -> match fc with
+				| JObject fl ->
+					let file = jsonrpc#get_string_field "fileContents" "file" fl in
+					let file = Path.get_full_path file in
+					let file_unique = com.file_keys#get file in
+					let contents = jsonrpc#get_opt_param (fun () ->
+						let s = jsonrpc#get_string_field "fileContents" "contents" fl in
+						Some s
+					) None in
+					(file_unique, contents)
+				| _ -> invalid_arg "fileContents"
+			) file_contents in
+
+			let files = (List.map (fun (k, _) -> k) file_contents) in
+			com.file_contents <- file_contents;
+
+			match files with
+			| [] -> DisplayPosition.display_position#set { pfile = file; pmin = pos; pmax = pos; };
+			| _ -> DisplayPosition.display_position#set_files files;
+		end
 end
 
 type handler_context = {
@@ -126,6 +157,12 @@ let handler =
 			hctx.display#set_display_file false true;
 			hctx.display#enable_display DMDefinition;
 		);
+		"display/diagnostics", (fun hctx ->
+			hctx.display#set_display_file false false;
+			hctx.display#enable_display DMNone;
+			hctx.com.display <- { hctx.com.display with dms_display_file_policy = DFPAlso; dms_per_file = true; dms_populate_cache = true };
+			hctx.com.report_mode <- RMDiagnostics (List.map (fun (f,_) -> f) hctx.com.file_contents);
+		);
 		"display/implementation", (fun hctx ->
 			hctx.display#set_display_file false true;
 			hctx.display#enable_display (DMImplementation);
@@ -362,12 +399,6 @@ let handler =
 				l := jstring ("Legacy completion " ^ (if b then "enabled" else "disabled")) :: !l;
 				()
 			) ();
-			hctx.jsonrpc#get_opt_param (fun () ->
-				let b = hctx.jsonrpc#get_bool_param "populateCacheFromDisplay" in
-				ServerConfig.populate_cache_from_display := b;
-				l := jstring ("Compilation cache refill from display " ^ (if b then "enabled" else "disabled")) :: !l;
-				()
-			) ();
 			hctx.send_result (jarray !l)
 		);
 		"server/memory",(fun hctx ->

+ 20 - 5
src/core/display/displayPosition.ml

@@ -11,6 +11,7 @@ class display_position_container =
 		(** Current display position *)
 		val mutable pos = null_pos
 		val mutable file_key = None
+		val mutable file_keys = []
 		(**
 			Display position value which was set with the latest `display_position#set p` call.
 			Kept even after `display_position#reset` call.
@@ -22,7 +23,15 @@ class display_position_container =
 		method set p =
 			pos <- p;
 			last_pos <- p;
-			file_key <- None
+			file_key <- None;
+			file_keys <- if p.pfile = DisplayProcessingGlobals.file_input_marker then [] else [Path.UniqueKey.create p.pfile]
+
+		method set_files files =
+			file_keys <- files
+
+		method get_files =
+			file_keys
+
 		(**
 			Get current display position
 		*)
@@ -43,7 +52,8 @@ class display_position_container =
 		*)
 		method reset =
 			pos <- null_pos;
-			file_key <- None
+			file_key <- None;
+			file_keys <- []
 		(**
 			Check if `p` contains current display position
 		*)
@@ -53,8 +63,13 @@ class display_position_container =
 			Check if a file with `file_key` contains current display position
 		*)
 		method is_in_file file_key =
-			pos.pfile <> "?"
-			&& self#get_file_key = file_key
+			(pos.pfile <> "?" && self#get_file_key = file_key) || self#has_file file_key
+		(**
+			This is a hack; currently used by Diagnostics.collect_diagnostics when sending multiple files
+			to run diagnostics on via json rpc
+		*)
+		method has_file file_key =
+			List.mem file_key file_keys
 		(**
 			Cut `p` at the position of the latest `display_position#set pos` call.
 		*)
@@ -75,4 +90,4 @@ class display_position_container =
 			{p with pmin = last_pos.pmin; pmax = last_pos.pmax}
 	end
 
-let display_position = new display_position_container
+let display_position = new display_position_container

+ 0 - 1
src/core/displayTypes.ml

@@ -235,7 +235,6 @@ module DisplayMode = struct
 		| DMDefault | DMDefinition | DMTypeDefinition | DMPackage | DMHover | DMSignature -> settings
 		| DMUsage _ | DMImplementation -> { settings with
 				dms_full_typing = true;
-				dms_populate_cache = !ServerConfig.populate_cache_from_display;
 				dms_force_macro_typing = true;
 				dms_display_file_policy = DFPAlso;
 				dms_exit_during_typing = false

+ 6 - 1
src/core/tType.ml

@@ -442,7 +442,12 @@ let flag_tclass_field_names = [
 type flag_tvar =
 	| VCaptured
 	| VFinal
-	| VUsed (* used by the analyzer *)
+	| VAnalyzed
 	| VAssigned
 	| VCaught
 	| VStatic
+	| VUsedByTyper (* Set if the typer looked up this variable *)
+
+let flag_tvar_names = [
+	"VCaptured";"VFinal";"VAnalyzed";"VAssigned";"VCaught";"VStatic";"VUsedByTyper"
+]

+ 4 - 2
src/filters/filters.ml

@@ -916,7 +916,8 @@ let save_class_state ctx t =
 			a.a_meta <- List.filter (fun (m,_,_) -> m <> Meta.ValueUsed) a.a_meta
 		)
 
-let run com tctx main =
+let run tctx main before_destruction =
+	let com = tctx.com in
 	let detail_times = Common.defined com DefineList.FilterTimes in
 	let new_types = List.filter (fun t ->
 		let cached = is_cached com t in
@@ -1025,4 +1026,5 @@ let run com tctx main =
 	let t = filter_timer detail_times ["callbacks"] in
 	com.callbacks#run com.callbacks#get_after_save; (* macros onGenerate etc. *)
 	t();
-	destruction tctx detail_times main locals
+	before_destruction();
+	destruction tctx detail_times main locals

+ 3 - 3
src/optimization/analyzer.ml

@@ -661,14 +661,14 @@ module LocalDce = struct
 
 	let rec apply ctx =
 		let is_used v =
-			has_var_flag v VUsed
+			has_var_flag v VAnalyzed
 		in
 		let keep v =
 			is_used v || ((match v.v_kind with VUser _ | VInlined -> true | _ -> false) && not ctx.config.local_dce) || ExtType.has_reference_semantics v.v_type || has_var_flag v VCaptured || Meta.has Meta.This v.v_meta
 		in
 		let rec use v =
 			if not (is_used v) then begin
-				add_var_flag v VUsed;
+				add_var_flag v VAnalyzed;
 				(try expr (get_var_value ctx.graph v) with Not_found -> ());
 				begin match Ssa.get_reaching_def ctx.graph v with
 					| None ->
@@ -676,7 +676,7 @@ module LocalDce = struct
 						   reaching definition (issue #10972). Simply marking it as being used should be sufficient. *)
 						let v' = get_var_origin ctx.graph v in
 						if not (is_used v') then
-							add_var_flag v' VUsed
+							add_var_flag v' VAnalyzed
 					| Some v ->
 						use v;
 				end

+ 0 - 1
src/optimization/inline.ml

@@ -589,7 +589,6 @@ class inline_state ctx ethis params cf f p = object(self)
 				mk (TBlock (DynArray.to_list el)) tret e.epos
 		in
 		let e = inline_metadata e cf.cf_meta in
-		let e = Diagnostics.secure_generated_code ctx e in
 		if has_params then begin
 			let mt = map_type cf.cf_type in
 			let unify_func () = unify_raise mt (TFun (tl,tret)) p in

+ 0 - 1
src/typing/callUnification.ml

@@ -488,7 +488,6 @@ object(self)
 			!ethis_f();
 			raise exc
 		in
-		let e = Diagnostics.secure_generated_code ctx e in
 		ctx.com.located_error <- old;
 		!ethis_f();
 		e

+ 16 - 16
src/typing/typeloadParse.ml

@@ -59,23 +59,23 @@ let parse_file_from_lexbuf com file p lexbuf =
 let parse_file_from_string com file p string =
 	parse_file_from_lexbuf com file p (Sedlexing.Utf8.from_string string)
 
-let current_stdin = ref None (* TODO: we're supposed to clear this at some point *)
-
 let parse_file com file p =
-	let use_stdin = (Common.defined com Define.DisplayStdin) && DisplayPosition.display_position#is_in_file (com.file_keys#get file) in
-	if use_stdin then
-		let s =
-			match !current_stdin with
-			| Some s ->
-				s
-			| None ->
-				let s = Std.input_all stdin in
-				close_in stdin;
-				current_stdin := Some s;
-				s
-		in
+	let file_key = com.file_keys#get file in
+	let contents = match com.file_contents with
+		| [] when (Common.defined com Define.DisplayStdin) && DisplayPosition.display_position#is_in_file file_key ->
+			let s = Std.input_all stdin in
+			close_in stdin;
+			com.file_contents <- [file_key, Some s];
+			Some s
+		| [] -> None
+		| files ->
+			(try List.assoc file_key files with Not_found -> None)
+	in
+
+	match contents with
+	| Some s ->
 		parse_file_from_string com file p s
-	else
+	| _ ->
 		let ch = try open_in_bin file with _ -> 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)
 
@@ -342,4 +342,4 @@ let parse_module ctx m p =
 
 (* let parse_module ctx m p =
 	let timer = Timer.timer ["typing";"parse_module"] in
-	Std.finally timer (parse_module ctx m) p *)
+	Std.finally timer (parse_module ctx m) p *)

+ 2 - 2
src/typing/typer.ml

@@ -350,6 +350,7 @@ let rec type_ident_raise ctx i p mode with_type =
 	| _ ->
 	try
 		let v = PMap.find i ctx.locals in
+		add_var_flag v VUsedByTyper;
 		(match v.v_extra with
 		| Some ve ->
 			let (params,e) = (ve.v_params,ve.v_expr) in
@@ -1130,7 +1131,7 @@ and type_new ctx path el with_type force_inline p =
 		typing_error (s_type (print_context()) t ^ " cannot be constructed") p
 	end with Error(No_constructor _ as err,p,depth) when ctx.com.display.dms_kind <> DMNone ->
 		located_display_error ~depth ctx.com (error_msg p err);
-		Diagnostics.secure_generated_code ctx (mk (TConst TNull) t p)
+		mk (TConst TNull) t p
 
 and type_try ctx e1 catches with_type p =
 	let e1 = type_expr ctx (Expr.ensure_block e1) with_type in
@@ -1796,7 +1797,6 @@ and type_call_builtin ctx e el mode with_type p =
 		| _ ->
 			let e = type_expr ctx e WithType.value in
 			warning ctx WInfo (s_type (print_context()) e.etype) e.epos;
-			let e = Diagnostics.secure_generated_code ctx e in
 			e
 		end
 	| (EField(e,"match",efk_todo),p), [epat] ->

+ 6 - 4
src/typing/typerBase.ml

@@ -155,9 +155,11 @@ let get_this ctx p =
 	| FunMemberClassLocal | FunMemberAbstractLocal ->
 		let v = match ctx.vthis with
 			| None ->
-				let v = if ctx.curfun = FunMemberAbstractLocal then
-					PMap.find "this" ctx.locals
-				else
+				let v = if ctx.curfun = FunMemberAbstractLocal then begin
+					let v = PMap.find "this" ctx.locals in
+					add_var_flag v VUsedByTyper;
+					v
+				end else
 					add_local ctx VGenerated "`this" ctx.tthis p
 				in
 				ctx.vthis <- Some v;
@@ -347,4 +349,4 @@ let get_abstract_froms ctx a pl =
 				acc)
 		| _ ->
 			acc
-	) l a.a_from_field
+	) l a.a_from_field

+ 18 - 1
std/haxe/display/Display.hx

@@ -25,6 +25,7 @@ package haxe.display;
 import haxe.display.JsonModuleTypes;
 import haxe.display.Position;
 import haxe.display.Protocol;
+import haxe.ds.ReadOnlyArray;
 
 /**
 	Methods of the JSON-RPC-based `--display` protocol in Haxe 4.
@@ -32,6 +33,12 @@ import haxe.display.Protocol;
 **/
 @:publicFields
 class DisplayMethods {
+
+	/**
+		The request is sent from the client to Haxe to get diagnostics for a specific file, a list of files or the whole project.
+	**/
+	static inline var Diagnostics = new HaxeRequestMethod<DiagnosticsParams, DiagnosticsResult>("display/diagnostics");
+
 	/**
 		The completion request is sent from the client to Haxe to request code completion.
 		Haxe automatically determines the type of completion to use based on the passed position, see `CompletionResultKind`.
@@ -92,7 +99,6 @@ class DisplayMethods {
 		TODO:
 
 		- finish completion
-		- diagnostics
 		- codeLens
 		- workspaceSymbols ("project/symbol"?)
 	 */
@@ -438,6 +444,17 @@ typedef PatternCompletion<T> = ToplevelCompletion<T> & {
 	var isOutermostPattern:Bool;
 }
 
+typedef DiagnosticsParams = {
+	var ?file:FsPath;
+	var ?contents:String;
+	var ?fileContents:Array<{file:FsPath, ?contents:String}>;
+}
+
+typedef DiagnosticsResult = Response<ReadOnlyArray<{
+	var file:FsPath;
+	var diagnostics:ReadOnlyArray<Diagnostic<Any>>;
+}>>
+
 enum abstract CompletionModeKind<T>(Int) {
 	var Field:CompletionModeKind<FieldCompletionSubject<Dynamic>>;
 	var StructureField;

+ 0 - 1
std/haxe/display/Server.hx

@@ -73,7 +73,6 @@ typedef ConfigurePrintParams = {
 
 typedef ConfigureParams = {
 	final ?noModuleChecks:Bool;
-	final ?populateCacheFromDisplay:Bool;
 	final ?legacyCompletion:Bool;
 	final ?print:ConfigurePrintParams;
 }

+ 1 - 1
tests/display/build.hxml

@@ -5,4 +5,4 @@
 -lib haxeserver
 --interp
 -D use-rtti-doc
--D test=11285
+# -D test=11285

+ 10 - 3
tests/display/src/cases/Issue5306.hx

@@ -7,8 +7,8 @@ class Issue5306 extends DisplayTestCase {
 		class Main {
 			static function main() {
 				var ib:Array<Int>;
-				ib[0] = 0; ib[1] = 1; ib[2]
-				{-5-}trace{-6-}("test");
+				{-5-}ib{-6-}[0] = 0; ib[1] = 1; ib[2]
+				{-7-}trace{-8-}("test");
 			}
 		}
 	**/
@@ -22,7 +22,7 @@ class Issue5306 extends DisplayTestCase {
 			// },
 			{
 				kind: DKParserError,
-				range: diagnosticsRange(pos(5), pos(6)),
+				range: diagnosticsRange(pos(7), pos(8)),
 				severity: Error,
 				relatedInformation: [],
 				args: "Missing ;"
@@ -33,6 +33,13 @@ class Issue5306 extends DisplayTestCase {
 				severity: Error,
 				relatedInformation: [],
 				args: "Type not found : InvalidType"
+			},
+			{
+				kind: DKCompilerError,
+				range: diagnosticsRange(pos(5), pos(6)),
+				severity: Error,
+				relatedInformation: [],
+				args: "Local variable ib used without being initialized"
 			}
 		];
 		arrayEq(expected, diagnostics());

+ 27 - 14
tests/server/src/TestCase.hx

@@ -62,22 +62,26 @@ class TestCase implements ITest {
 		server.stop();
 	}
 
+	function handleResult(result) {
+		lastResult = result;
+		debugLastResult = {
+			hasError: lastResult.hasError,
+			prints: lastResult.prints,
+			stderr: lastResult.stderr,
+			stdout: lastResult.stdout
+		}
+		sendLogMessage(result.stdout);
+		for (print in result.prints) {
+			var line = print.trim();
+			messages.push('Haxe print: $line');
+		}
+	}
+
 	function runHaxe(args:Array<String>, done:() -> Void) {
 		messages = [];
 		errorMessages = [];
 		server.rawRequest(args, null, function(result) {
-			lastResult = result;
-			debugLastResult = {
-				hasError: lastResult.hasError,
-				prints: lastResult.prints,
-				stderr: lastResult.stderr,
-				stdout: lastResult.stdout
-			}
-			sendLogMessage(result.stdout);
-			for (print in result.prints) {
-				var line = print.trim();
-				messages.push('Haxe print: $line');
-			}
+			handleResult(result);
 			if (result.hasError) {
 				sendErrorMessage(result.stderr);
 			}
@@ -92,11 +96,20 @@ class TestCase implements ITest {
 	}
 
 	function runHaxeJsonCb<TParams, TResponse>(args:Array<String>, method:HaxeRequestMethod<TParams, Response<TResponse>>, methodArgs:TParams,
-			callback:TResponse->Void, done:() -> Void) {
+			callback:TResponse->Void, done:() -> Void, ?pos:PosInfos) {
 		var methodArgs = {method: method, id: 1, params: methodArgs};
 		args = args.concat(['--display', Json.stringify(methodArgs)]);
+		messages = [];
+		errorMessages = [];
 		server.rawRequest(args, null, function(result) {
-			callback(Json.parse(result.stderr).result.result);
+			handleResult(result);
+			var json = try Json.parse(result.stderr) catch(e) {result: null, error: e.message};
+
+			if (json.result != null) {
+				callback(json.result?.result);
+			} else {
+				Assert.fail('Error: ' + json.error, pos);
+			}
 			done();
 		}, function(msg) {
 			sendErrorMessage(msg);

+ 172 - 5
tests/server/src/cases/ServerTests.hx

@@ -1,7 +1,9 @@
 package cases;
 
+import haxe.display.Diagnostic;
 import haxe.display.Display;
 import haxe.display.FsPath;
+import haxe.display.Position.Range;
 import haxe.display.Server;
 import haxe.io.Path;
 import utest.Assert;
@@ -97,7 +99,9 @@ class ServerTests extends TestCase {
 		var args = ["-main", "BrokenSyntax.hx", "--interp", "--no-output"];
 		runHaxe(args);
 		assertErrorMessage("Expected }");
-		runHaxe(args.concat(["--display", "Empty.hx@0@diagnostics"]));
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {file: new FsPath("Empty.hx")}, res -> {
+			Assert.equals(0, res.length);
+		});
 		runHaxe(args);
 		assertErrorMessage("Expected }");
 	}
@@ -143,6 +147,80 @@ class ServerTests extends TestCase {
 		assertSuccess();
 	}
 
+	function testDiagnosticsFileContents() {
+		vfs.putContent("Main.hx", getTemplate("issues/Issue9134/Main.hx"));
+		vfs.putContent("Other.hx", getTemplate("issues/Issue9134/Other.hx"));
+		var args = ["-main", "Main", "Other"];
+
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {fileContents: [
+			{file: new FsPath("Other.hx")},
+			{file: new FsPath("Main.hx")},
+		]}, res -> {
+			Assert.equals(1, res.length);
+			Assert.equals(1, res[0].diagnostics.length);
+			var arg = res[0].diagnostics[0].args;
+			Assert.equals("Unused variable", (cast arg).description);
+			Assert.stringContains("Main.hx", res[0].file.toString());
+		});
+
+		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Main.hx")});
+		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Other.hx")});
+
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {fileContents: [
+			{file: new FsPath("Main.hx"), contents: getTemplate("issues/Issue9134/Main2.hx")},
+			{file: new FsPath("Other.hx"), contents: getTemplate("issues/Issue9134/Other2.hx")}
+		]}, res -> {
+			Assert.equals(1, res.length);
+			Assert.equals(1, res[0].diagnostics.length);
+			var arg = res[0].diagnostics[0].args;
+			Assert.equals("Unused variable", (cast arg).description);
+			Assert.stringContains("Other.hx", res[0].file.toString());
+		});
+
+		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Main.hx")});
+		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Other.hx")});
+
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {fileContents: [
+			{file: new FsPath("Main.hx"), contents: getTemplate("issues/Issue9134/Main.hx")},
+			{file: new FsPath("Other.hx"), contents: getTemplate("issues/Issue9134/Other2.hx")}
+		]}, res -> {
+			Assert.equals(2, res.length);
+
+			for (i in 0...2) {
+				Assert.equals(1, res[i].diagnostics.length);
+				var arg = res[i].diagnostics[0].args;
+				Assert.equals("Unused variable", (cast arg).description);
+			}
+		});
+
+		// Currently, haxe compilation server will have this content anyway
+		// because of diagnostics with file contents, but that behavior may not
+		// be obvious in tests
+		vfs.putContent("Other.hx", getTemplate("issues/Issue9134/Other2.hx"));
+		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Other.hx")});
+
+		// Running project wide diagnostics; checks here aren't great since
+		// results will depend on haxe std which may change without updating
+		// this test everytime..
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {}, res -> {
+			var hasMain = false;
+			var hasOther = false;
+
+			for (result in res) {
+				var file = result.file.toString();
+				if (StringTools.endsWith(file, "Main.hx")) hasMain = true;
+				else if (StringTools.endsWith(file, "Other.hx")) hasOther = true;
+				else continue;
+
+				var arg = result.diagnostics[0].args;
+				Assert.equals("Unused variable", (cast arg).description);
+			}
+
+			Assert.isTrue(hasMain);
+			Assert.isTrue(hasOther);
+		});
+	}
+
 	function testDiagnosticsRecache() {
 		vfs.putContent("HelloWorld.hx", getTemplate("HelloWorld.hx"));
 		var args = ["--main", "HelloWorld", "--interp"];
@@ -152,7 +230,25 @@ class ServerTests extends TestCase {
 		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("HelloWorld.hx")});
 		runHaxe(args);
 		assertSkipping("HelloWorld", Tainted("server/invalidate"));
-		runHaxe(args.concat(["--display", "HelloWorld.hx@0@diagnostics"]));
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {file: new FsPath("HelloWorld.hx")}, res -> {
+			Assert.equals(0, res.length);
+		});
+		runHaxe(args);
+		assertReuse("HelloWorld");
+	}
+
+	function testDiagnosticsRecache1() {
+		vfs.putContent("HelloWorld.hx", getTemplate("HelloWorld.hx"));
+		var args = ["--main", "HelloWorld", "--interp"];
+		runHaxe(args);
+		runHaxe(args);
+		assertReuse("HelloWorld");
+		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("HelloWorld.hx")});
+		runHaxe(args);
+		assertSkipping("HelloWorld", Tainted("server/invalidate"));
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {fileContents: [{file: new FsPath("HelloWorld.hx")}]}, res -> {
+			Assert.equals(0, res.length);
+		});
 		runHaxe(args);
 		assertReuse("HelloWorld");
 	}
@@ -160,7 +256,9 @@ class ServerTests extends TestCase {
 	function testDiagnosticsRecache2() {
 		vfs.putContent("HelloWorld.hx", getTemplate("HelloWorld.hx"));
 		var args = ["--main", "HelloWorld", "--interp"];
-		runHaxe(args.concat(["--display", "HelloWorld.hx@0@diagnostics"]));
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {file: new FsPath("HelloWorld.hx")}, res -> {
+			Assert.equals(0, res.length);
+		});
 		runHaxe(args);
 		assertReuse("HelloWorld");
 	}
@@ -172,11 +270,80 @@ class ServerTests extends TestCase {
 		runHaxe(args);
 		assertReuse("HelloWorld");
 		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("HelloWorld.hx")});
-		runHaxe(args.concat(["--display", "HelloWorld.hx@0@diagnostics"]));
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {file: new FsPath("HelloWorld.hx")}, res -> {
+			Assert.equals(0, res.length);
+		});
 		runHaxe(args.concat(["--display", "HelloWorld.hx@0@hover"]));
 		assertReuse("HelloWorld");
 	}
 
+	function testDiagnosticsMultipleOpenFiles() {
+		vfs.putContent("Main.hx", getTemplate("diagnostics/multi-files/Main.hx"));
+		vfs.putContent("File1.hx", getTemplate("diagnostics/multi-files/File1.hx"));
+		vfs.putContent("File2.hx", getTemplate("diagnostics/multi-files/File2.hx"));
+		vfs.putContent("File3.hx", getTemplate("diagnostics/multi-files/File3.hx"));
+
+		var args = ["--main", "Main", "--interp"];
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {fileContents: [
+			{file: new FsPath("Main.hx")},
+			{file: new FsPath("File1.hx")}
+		]}, res -> {
+			Assert.equals(2, res.length); // Asked diagnostics for 2 files
+
+			for (fileDiagnostics in res) {
+				final path = ~/[\/|\\]/g.split(fileDiagnostics.file.toString()).pop();
+
+				switch (path) {
+					case "Main.hx":
+						Assert.equals(2, fileDiagnostics.diagnostics.length);
+						for (diag in fileDiagnostics.diagnostics) {
+							Assert.equals(diag.kind, DKUnusedImport);
+						}
+
+					case "File1.hx":
+						Assert.equals(1, fileDiagnostics.diagnostics.length);
+						var diag:Diagnostic<{description:String, range:Range}> = fileDiagnostics.diagnostics[0];
+						Assert.equals(diag.kind, DKRemovableCode);
+						Assert.equals(diag.args.description, "Unused variable");
+
+					case _: throw 'Did not expect diagnostics for $path';
+				}
+			}
+		});
+
+		// Check that File2 was reached
+		var context = null;
+		runHaxeJsonCb(args, ServerMethods.Contexts, null, res -> context = res.find(ctx -> ctx.desc == "after_init_macros"));
+		runHaxeJsonCb(args, ServerMethods.Type, {signature: context.signature, modulePath: "File2", typeName: "File2"}, res -> Assert.equals(res.pos.file, "File2.hx"));
+
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {fileContents: [
+			{file: new FsPath("Main.hx")},
+			{file: new FsPath("File3.hx")}, // Not reached by normal compilation
+		]}, res -> {
+			Assert.equals(2, res.length); // Asked diagnostics for 2 files
+
+			for (fileDiagnostics in res) {
+				final path = ~/[\/|\\]/g.split(fileDiagnostics.file.toString()).pop();
+
+				switch (path) {
+					case "Main.hx":
+						Assert.equals(2, fileDiagnostics.diagnostics.length);
+						for (diag in fileDiagnostics.diagnostics) {
+							Assert.equals(diag.kind, DKUnusedImport);
+						}
+
+					case "File3.hx":
+						Assert.equals(1, fileDiagnostics.diagnostics.length);
+						var diag:Diagnostic<{description:String, range:Range}> = fileDiagnostics.diagnostics[0];
+						Assert.equals(diag.kind, DKRemovableCode);
+						Assert.equals(diag.args.description, "Unused variable");
+
+					case _: throw 'Did not expect diagnostics for $path';
+				}
+			}
+		});
+	}
+
 	function testSyntaxCache() {
 		vfs.putContent("HelloWorld.hx", getTemplate("HelloWorld.hx"));
 		runHaxeJson(["-cp", "."], ServerMethods.ReadClassPaths, null);
@@ -397,7 +564,7 @@ class ServerTests extends TestCase {
 		var runs = 0;
 
 		function runLoop() {
-			runHaxe(args.concat(["--display", "Empty.hx@0@diagnostics"]), () -> {
+			runHaxeJson(args, DisplayMethods.Diagnostics, {file: new FsPath("Empty.hx")}, () -> {
 				runHaxe(args.concat(["-D", "compile-only-define"]), () -> {
 					if (assertSuccess() && ++runs < 20) runLoop();
 					else async.done();

+ 14 - 8
tests/server/src/cases/display/issues/Issue10635.hx

@@ -14,12 +14,15 @@ class Issue10635 extends DisplayTestCase {
 		}
 	**/
 	function test(_) {
-		var args = ["-main", "Main", "--display", "Main.hx@0@diagnostics"];
+		var args = ["-main", "Main"];
 		vfs.putContent("Something.hx", getTemplate("issues/Issue10635/Something.hx"));
-		runHaxe(args);
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {file: new FsPath("Main.hx")}, res -> {
+			Assert.equals(0, res.length);
+		});
 		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Main.hx")});
-		runHaxe(args);
-		Assert.isTrue(lastResult.stderr.length == 2); // dumb, but we don't have a proper diagnostics structure in these tests
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {file: new FsPath("Main.hx")}, res -> {
+			Assert.equals(0, res.length);
+		});
 	}
 
 	/**
@@ -32,12 +35,15 @@ class Issue10635 extends DisplayTestCase {
 		}
 	**/
 	function testGenericClassPerMethod(_) {
-		var args = ["-main", "Main", "--display", "Main.hx@0@diagnostics"];
+		var args = ["-main", "Main"];
 		vfs.putContent("Something.hx", "@:genericClassPerMethod " + getTemplate("issues/Issue10635/Something.hx"));
-		runHaxe(args);
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {file: new FsPath("Main.hx")}, res -> {
+			Assert.equals(0, res.length);
+		});
 		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Main.hx")});
-		runHaxe(args);
-		Assert.isTrue(lastResult.stderr.length == 2); // dumb, but we don't have a proper diagnostics structure in these tests
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {file: new FsPath("Main.hx")}, res -> {
+			Assert.equals(0, res.length);
+		});
 	}
 
 	function testGenericAddition(_) {

+ 6 - 3
tests/server/src/cases/issues/Issue10653.hx

@@ -8,9 +8,12 @@ class Issue10653 extends TestCase {
 		runHaxe(args);
 		vfs.putContent("Main.hx", getTemplate("issues/Issue10653/MainAfter.hx"));
 		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Main.hx")});
-		runHaxe(args.concat(["--display", "Main.hx@0@diagnostics"]));
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {file: new FsPath("Main.hx")}, res -> {
+			Assert.equals(0, res.length);
+		});
 		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Main.hx")});
-		runHaxe(args.concat(["--display", "Main.hx@0@diagnostics"]));
-		Assert.isTrue(lastResult.stderr.length == 2);
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {file: new FsPath("Main.hx")}, res -> {
+			Assert.equals(0, res.length);
+		});
 	}
 }

+ 16 - 15
tests/server/src/cases/issues/Issue11177.hx

@@ -1,26 +1,27 @@
 package cases.issues;
 
 class Issue11177 extends TestCase {
-	// Disabled for now until #11177 is actually fixed, likely by #11220
-	// function test(_) {
-	// 	vfs.putContent("Main.hx", getTemplate("issues/Issue11177/Main.hx"));
-	// 	vfs.putContent("Buttons.hx", getTemplate("issues/Issue11177/Buttons.hx"));
-	// 	vfs.putContent("KeyCode.hx", getTemplate("issues/Issue11177/KeyCode.hx"));
-	// 	var args = ["-main", "Main", "--interp"];
-	// 	runHaxe(args.concat(["--display", "Buttons.hx@0@diagnostics"]));
-	// 	vfs.putContent("Main.hx", getTemplate("issues/Issue11177/Main2.hx"));
-	// 	runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Main.hx")});
-	// 	runHaxe(args);
-	// 	runHaxe(args.concat(["--display", "Buttons.hx@0@diagnostics"]));
-	// 	Assert.isTrue(lastResult.stderr.length == 2);
-	// }
+	function test(_) {
+		vfs.putContent("Main.hx", getTemplate("issues/Issue11177/Main.hx"));
+		vfs.putContent("Buttons.hx", getTemplate("issues/Issue11177/Buttons.hx"));
+		vfs.putContent("KeyCode.hx", getTemplate("issues/Issue11177/KeyCode.hx"));
+		var args = ["-main", "Main", "--interp"];
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {file: new FsPath("Buttons.hx")}, res -> {
+			Assert.equals(0, res.length);
+		});
+		vfs.putContent("Main.hx", getTemplate("issues/Issue11177/Main2.hx"));
+		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Main.hx")});
+		runHaxe(args);
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {file: new FsPath("Buttons.hx")}, res -> {
+			Assert.equals(0, res.length);
+		});
+	}
 
-	function testWithoutCacheFromDisplay(_) {
+	function testLegacyDiagnostics(_) {
 		vfs.putContent("Main.hx", getTemplate("issues/Issue11177/Main.hx"));
 		vfs.putContent("Buttons.hx", getTemplate("issues/Issue11177/Buttons.hx"));
 		vfs.putContent("KeyCode.hx", getTemplate("issues/Issue11177/KeyCode.hx"));
 		var args = ["-main", "Main", "--interp"];
-		runHaxeJson([], ServerMethods.Configure, {populateCacheFromDisplay: false});
 		runHaxe(args.concat(["--display", "Buttons.hx@0@diagnostics"]));
 		vfs.putContent("Main.hx", getTemplate("issues/Issue11177/Main2.hx"));
 		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Main.hx")});

+ 18 - 12
tests/server/src/cases/issues/Issue11184.hx

@@ -1,22 +1,28 @@
 package cases.issues;
 
 class Issue11184 extends TestCase {
-	// Disabled for now until #11184 is actually fixed, likely by #11220
-	// function test(_) {
-	// 	vfs.putContent("Main.hx", getTemplate("issues/Issue11184/Main.hx"));
-	// 	var args = ["-main", "Main", "-js", "bin/test.js"];
-	// 	runHaxe(args.concat(["--display", "Main.hx@0@diagnostics"]));
-	// 	runHaxe(args);
-	// 	Assert.isTrue(hasErrorMessage("Cannot use Void as value"));
-	// 	runHaxe(args);
-	// 	Assert.isTrue(hasErrorMessage("Cannot use Void as value"));
-	// }
+	function testDiagnostics(_) {
+		vfs.putContent("Main.hx", getTemplate("issues/Issue11184/Main.hx"));
+		var args = ["-main", "Main", "-js", "bin/test.js"];
+
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {file: new FsPath("Main.hx")}, res -> {
+			Assert.equals(1, res.length);
+			Assert.equals(1, res[0].diagnostics.length);
+			Assert.equals(res[0].diagnostics[0].args, "Cannot use Void as value");
+		});
+
+		runHaxe(args);
+		Assert.isTrue(hasErrorMessage("Cannot use Void as value"));
+		runHaxe(args);
+		Assert.isTrue(hasErrorMessage("Cannot use Void as value"));
+	}
 
-	function testWithoutCacheFromDisplay(_) {
+	function testLegacyDiagnostics(_) {
 		vfs.putContent("Main.hx", getTemplate("issues/Issue11184/Main.hx"));
 		var args = ["-main", "Main", "-js", "bin/test.js"];
-		runHaxeJson([], ServerMethods.Configure, {populateCacheFromDisplay: false});
 		runHaxe(args.concat(["--display", "Main.hx@0@diagnostics"]));
+		final diagnostics = haxe.Json.parse(lastResult.stderr)[0].diagnostics;
+		Assert.equals(diagnostics[0].args, "Cannot use Void as value");
 		runHaxe(args);
 		Assert.isTrue(hasErrorMessage("Cannot use Void as value"));
 		runHaxe(args);

+ 23 - 0
tests/server/src/cases/issues/Issue11203.hx

@@ -0,0 +1,23 @@
+package cases.issues;
+
+class Issue11203 extends TestCase {
+	function testClass(_) {
+		vfs.putContent("Main.hx", getTemplate("issues/Issue11203/MainClass.hx"));
+		var args = ["Main", "--interp"];
+		runHaxe(args);
+		runHaxe(args.concat(["--display", "Main.hx@0@diagnostics"]));
+
+		var diag = parseDiagnostics();
+		Assert.isTrue(diag.length == 0);
+	}
+
+	function testAbstract(_) {
+		vfs.putContent("Main.hx", getTemplate("issues/Issue11203/MainAbstract.hx"));
+		var args = ["Main", "--interp"];
+		runHaxe(args);
+		runHaxe(args.concat(["--display", "Main.hx@0@diagnostics"]));
+
+		var diag = parseDiagnostics();
+		Assert.isTrue(diag.length == 0);
+	}
+}

+ 39 - 0
tests/server/src/cases/issues/Issue11695.hx

@@ -0,0 +1,39 @@
+package cases.issues;
+
+class Issue11695 extends TestCase {
+	function test(_) {
+		vfs.putContent("Main.hx", getTemplate("issues/Issue11695/Main.hx"));
+		vfs.putContent("Macro.hx", getTemplate("issues/Issue11695/Macro1.hx"));
+		var args = ["-main", "Main", "--interp"];
+		runHaxe(args);
+		assertHasPrint("Macro.hx:1: before");
+
+		// Note: this is needed because modification time is currently checked with second precision
+		Sys.sleep(1);
+
+		vfs.putContent("Macro.hx", getTemplate("issues/Issue11695/Macro2.hx"));
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {file: new FsPath("Macro.hx")}, res -> {
+			Assert.equals(0, res.length);
+		});
+
+		runHaxe(args);
+		assertHasPrint("Macro.hx:1: after");
+	}
+
+	function testLegacyDiagnostics(_) {
+		vfs.putContent("Main.hx", getTemplate("issues/Issue11695/Main.hx"));
+		vfs.putContent("Macro.hx", getTemplate("issues/Issue11695/Macro1.hx"));
+		var args = ["-main", "Main", "--interp"];
+		runHaxe(args);
+		assertHasPrint("Macro.hx:1: before");
+
+		// Note: this is needed because modification time is currently checked with second precision
+		Sys.sleep(1);
+
+		vfs.putContent("Macro.hx", getTemplate("issues/Issue11695/Macro2.hx"));
+		runHaxe(args.concat(["--display", "Macro.hx@0@diagnostics"]));
+
+		runHaxe(args);
+		assertHasPrint("Macro.hx:1: after");
+	}
+}

+ 22 - 0
tests/server/src/cases/issues/Issue7282.hx

@@ -0,0 +1,22 @@
+package cases.issues;
+
+import haxe.display.Diagnostic;
+import haxe.display.Position.Range;
+
+class Issue7282 extends TestCase {
+	function test(_) {
+		var content = getTemplate("issues/Issue7282/Main.hx");
+		var transform = Markers.parse(content);
+
+		vfs.putContent("Main.hx", transform.source);
+		var args = ["-main", "Main"];
+		runHaxe(args);
+		assertSuccess();
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {file: new FsPath("Main.hx")}, res -> {
+			var arg:{description:String, range:Range} = res[0].diagnostics[0].args;
+			Assert.equals("Unused variable", arg.description);
+			Assert.same(transform.range(1,2), res[0].diagnostics[0].range);
+			Assert.same(transform.range(1,2), arg.range);
+		});
+	}
+}

+ 13 - 0
tests/server/src/cases/issues/Issue7931.hx

@@ -0,0 +1,13 @@
+package cases.issues;
+
+class Issue7931 extends TestCase {
+	function test(_) {
+		vfs.putContent("Main.hx", getTemplate("issues/Issue7931/Main.hx"));
+		var args = ["-main", "Main"];
+		runHaxe(args);
+		assertErrorMessage("Local variable s used without being initialized");
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {file: new FsPath("Main.hx")}, res -> {
+			Assert.equals("Local variable s used without being initialized", res[0].diagnostics[0].args);
+		});
+	}
+}

+ 5 - 4
tests/server/src/cases/issues/Issue8687.hx

@@ -4,9 +4,10 @@ class Issue8687 extends TestCase {
 	function test(_) {
 		vfs.putContent("Main.hx", getTemplate("issues/Issue8687/Main.hx"));
 		var args = ["-main", "Main", "--interp"];
-		runHaxe(args.concat(["--display", "Main.hx@0@diagnostics"]));
-
-		var diag = parseDiagnostics();
-		Assert.equals("Invalid version string \"foo\". Should follow SemVer.", diag[0].args);
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {file: new FsPath("Main.hx")}, res -> {
+			Assert.equals(1, res.length);
+			Assert.equals(1, res[0].diagnostics.length);
+			Assert.equals(res[0].diagnostics[0].args, "Invalid version string \"foo\". Should follow SemVer.");
+		});
 	}
 }

+ 5 - 0
tests/server/test/templates/diagnostics/multi-files/File1.hx

@@ -0,0 +1,5 @@
+class File1 {
+	static function test() {
+		var foo = 42;
+	}
+}

+ 5 - 0
tests/server/test/templates/diagnostics/multi-files/File2.hx

@@ -0,0 +1,5 @@
+class File2 {
+	static function test() {
+		var foo = 42;
+	}
+}

+ 5 - 0
tests/server/test/templates/diagnostics/multi-files/File3.hx

@@ -0,0 +1,5 @@
+class File3 {
+	static function test() {
+		var foo = 42;
+	}
+}

+ 4 - 0
tests/server/test/templates/diagnostics/multi-files/Main.hx

@@ -0,0 +1,4 @@
+import File1;
+import File2;
+
+function main() {}

+ 16 - 0
tests/server/test/templates/issues/Issue11203/MainAbstract.hx

@@ -0,0 +1,16 @@
+class Main {
+	static function main() {
+		var future = new Future();
+		future.eager();
+	}
+}
+
+abstract Future({}) from {} {
+	public function new()
+		this = {};
+
+	public inline function eager():Future {
+		trace("much side effect!");
+		return this;
+	}
+}

+ 15 - 0
tests/server/test/templates/issues/Issue11203/MainClass.hx

@@ -0,0 +1,15 @@
+class Main {
+	static function main() {
+		var future = new Future();
+		future.eager();
+	}
+}
+
+class Future {
+	public function new() {}
+
+	public inline function eager():Future {
+		trace("much side effect!");
+		return this;
+	}
+}

+ 1 - 0
tests/server/test/templates/issues/Issue11695/Macro1.hx

@@ -0,0 +1 @@
+macro function test() return macro trace("before");

+ 1 - 0
tests/server/test/templates/issues/Issue11695/Macro2.hx

@@ -0,0 +1 @@
+macro function test() return macro trace("after");

+ 3 - 0
tests/server/test/templates/issues/Issue11695/Main.hx

@@ -0,0 +1,3 @@
+function main() {
+	Macro.test();
+}

+ 10 - 0
tests/server/test/templates/issues/Issue7282/Main.hx

@@ -0,0 +1,10 @@
+import haxe.ds.Option;
+
+class Main {
+	public static function main() {
+		switch ((null:Option<Int>)) {
+			case Some({-1-}value{-2-}):
+			case None:
+		}
+	}
+}

+ 6 - 0
tests/server/test/templates/issues/Issue7931/Main.hx

@@ -0,0 +1,6 @@
+class Main {
+	static function main() {
+		var s:String;
+		s += "test";
+	}
+}

+ 5 - 0
tests/server/test/templates/issues/Issue9134/Main.hx

@@ -0,0 +1,5 @@
+class Main {
+	static function main() {
+		var unused = null;
+	}
+}

+ 6 - 0
tests/server/test/templates/issues/Issue9134/Main2.hx

@@ -0,0 +1,6 @@
+class Main {
+	static function main() {
+		var unused = null;
+		if (unused != null) trace("wat");
+	}
+}

+ 2 - 0
tests/server/test/templates/issues/Issue9134/Other.hx

@@ -0,0 +1,2 @@
+class Other {
+}

+ 6 - 0
tests/server/test/templates/issues/Issue9134/Other2.hx

@@ -0,0 +1,6 @@
+class Other {
+	static function foo() {
+		// var foo = trace("wat");
+		var unused = null;
+	}
+}