瀏覽代碼

[display] diagnostics as json rpc (#11412)

* [diagnostics] implement diagnostics as json rpc

* [tests] use json rpc diagnostics

* [tests] add tests for json rpc diagnostics

* [diagnostics] no need for its own exception

* [compiler] fix run_or_diagnose weird edge case

* [diagnostics] no need for after_compilation callback anymore
Rudy Ges 1 年之前
父節點
當前提交
a270435a45

+ 16 - 10
src/compiler/compiler.ml

@@ -2,29 +2,35 @@ open Globals
 open Common
 open Common
 open CompilationContext
 open CompilationContext
 
 
-let run_or_diagnose ctx f arg =
+let run_or_diagnose ctx f =
 	let com = ctx.com in
 	let com = ctx.com in
-	let handle_diagnostics ?(depth = 0) msg p kind =
+	let handle_diagnostics msg p kind =
 		ctx.has_error <- true;
 		ctx.has_error <- true;
-		add_diagnostics_message ~depth com msg p kind Error;
-		DisplayOutput.emit_diagnostics ctx.com
+		add_diagnostics_message com msg p kind Error;
+		match com.report_mode with
+		| RMLegacyDiagnostics _ -> DisplayOutput.emit_legacy_diagnostics ctx.com
+		| RMDiagnostics _ -> DisplayOutput.emit_diagnostics ctx.com
+		| _ -> die "" __LOC__
 	in
 	in
 	if is_diagnostics com then begin try
 	if is_diagnostics com then begin try
-			f arg
+			f ()
 		with
 		with
 		| Error.Error err ->
 		| Error.Error err ->
 			ctx.has_error <- true;
 			ctx.has_error <- true;
 			Error.recurse_error (fun depth err ->
 			Error.recurse_error (fun depth err ->
 				add_diagnostics_message ~depth com (Error.error_msg err.err_message) err.err_pos DKCompilerMessage Error
 				add_diagnostics_message ~depth com (Error.error_msg err.err_message) err.err_pos DKCompilerMessage Error
 			) err;
 			) err;
-			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__)
 		| Parser.Error(msg,p) ->
 		| Parser.Error(msg,p) ->
 			handle_diagnostics (Parser.error_msg msg) p DKParserError
 			handle_diagnostics (Parser.error_msg msg) p DKParserError
 		| Lexer.Error(msg,p) ->
 		| Lexer.Error(msg,p) ->
 			handle_diagnostics (Lexer.error_msg msg) p DKParserError
 			handle_diagnostics (Lexer.error_msg msg) p DKParserError
 		end
 		end
 	else
 	else
-		f arg
+		f ()
 
 
 let run_command ctx cmd =
 let run_command ctx cmd =
 	let t = Timer.timer ["command";cmd] in
 	let t = Timer.timer ["command";cmd] in
@@ -297,7 +303,7 @@ let do_type ctx mctx actx display_file_dot_path macro_cache_enabled =
 			if com.display.dms_kind <> DMNone then DisplayTexpr.check_display_file tctx cs;
 			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);
 			List.iter (fun cpath -> ignore(tctx.Typecore.g.Typecore.do_load_module tctx cpath null_pos)) (List.rev actx.classes);
 			Finalization.finalize tctx;
 			Finalization.finalize tctx;
-		) ();
+		);
 	end with TypeloadParse.DisplayInMacroBlock ->
 	end with TypeloadParse.DisplayInMacroBlock ->
 		ignore(DisplayProcessing.load_display_module_in_macro tctx display_file_dot_path true)
 		ignore(DisplayProcessing.load_display_module_in_macro tctx display_file_dot_path true)
 	);
 	);
@@ -317,7 +323,7 @@ let finalize_typing ctx tctx =
 	let com = ctx.com in
 	let com = ctx.com in
 	enter_stage com CFilteringStart;
 	enter_stage com CFilteringStart;
 	ServerMessage.compiler_stage com;
 	ServerMessage.compiler_stage com;
-	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.main <- main;
 	com.types <- types;
 	com.types <- types;
 	com.modules <- modules;
 	com.modules <- modules;
@@ -326,7 +332,7 @@ let finalize_typing ctx tctx =
 let filter ctx tctx before_destruction =
 let filter ctx tctx before_destruction =
 	let t = Timer.timer ["filters"] in
 	let t = Timer.timer ["filters"] in
 	DeprecationCheck.run ctx.com;
 	DeprecationCheck.run ctx.com;
-	run_or_diagnose ctx Filters.run tctx ctx.com.main before_destruction;
+	run_or_diagnose ctx (fun () -> Filters.run tctx ctx.com.main before_destruction);
 	t()
 	t()
 
 
 let compile ctx actx callbacks =
 let compile ctx actx callbacks =

+ 11 - 1
src/compiler/displayOutput.ml

@@ -368,12 +368,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));
 		api.send_result (DisplayException.fields_to_json ctx fields kind (DisplayTypes.make_subject None pos));
 	end
 	end
 
 
-let emit_diagnostics com =
+let emit_legacy_diagnostics com =
 	let dctx = Diagnostics.run com in
 	let dctx = Diagnostics.run com in
 	let s = Json.string_of_json (DiagnosticsPrinter.json_of_diagnostics com dctx) in
 	let s = Json.string_of_json (DiagnosticsPrinter.json_of_diagnostics com dctx) in
 	DisplayPosition.display_position#reset;
 	DisplayPosition.display_position#reset;
 	raise (Completion s)
 	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 emit_statistics tctx =
 	let stats = Statistics.collect_statistics tctx [SFFile (DisplayPosition.display_position#get).pfile] true in
 	let stats = Statistics.collect_statistics tctx [SFFile (DisplayPosition.display_position#get).pfile] true in
 	let s = Statistics.Printer.print_statistics stats in
 	let s = Statistics.Printer.print_statistics stats in

+ 4 - 2
src/compiler/displayProcessing.ml

@@ -22,7 +22,7 @@ let handle_display_argument_old com file_pos actx =
 		actx.did_something <- true;
 		actx.did_something <- true;
 		(try Memory.display_memory com with e -> prerr_endline (Printexc.get_backtrace ()));
 		(try Memory.display_memory com with e -> prerr_endline (Printexc.get_backtrace ()));
 	| "diagnostics" ->
 	| "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, pos = try ExtString.String.split file_pos "@" with _ -> failwith ("Invalid format: " ^ file_pos) in
 		let file = Helper.unquote file in
 		let file = Helper.unquote file in
@@ -46,7 +46,7 @@ let handle_display_argument_old com file_pos actx =
 			| "module-symbols" ->
 			| "module-symbols" ->
 				create (DMModuleSymbols None)
 				create (DMModuleSymbols None)
 			| "diagnostics" ->
 			| "diagnostics" ->
-				com.report_mode <- RMDiagnostics [file_unique];
+				com.report_mode <- RMLegacyDiagnostics [file_unique];
 				let dm = create DMNone in
 				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; dms_populate_cache = !ServerConfig.populate_cache_from_display}
 			| "statistics" ->
 			| "statistics" ->
@@ -348,6 +348,8 @@ let handle_display_after_finalization ctx tctx display_file_dot_path =
 	end;
 	end;
 	process_global_display_mode com tctx;
 	process_global_display_mode com tctx;
 	begin match com.report_mode with
 	begin match com.report_mode with
+	| RMLegacyDiagnostics _ ->
+		DisplayOutput.emit_legacy_diagnostics com
 	| RMDiagnostics _ ->
 	| RMDiagnostics _ ->
 		DisplayOutput.emit_diagnostics com
 		DisplayOutput.emit_diagnostics com
 	| RMStatistics ->
 	| RMStatistics ->

+ 12 - 9
src/compiler/server.ml

@@ -16,15 +16,7 @@ let has_error ctx =
 	ctx.has_error || ctx.com.Common.has_error
 	ctx.has_error || ctx.com.Common.has_error
 
 
 let check_display_flush ctx f_otherwise = match ctx.com.json_out with
 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 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
 		if has_error ctx then begin
 			let errors = List.map (fun cm ->
 			let errors = List.map (fun cm ->
 				JObject [
 				JObject [
@@ -35,6 +27,17 @@ let check_display_flush ctx f_otherwise = match ctx.com.json_out with
 			) (List.rev ctx.messages) in
 			) (List.rev ctx.messages) in
 			api.send_error errors
 			api.send_error errors
 		end
 		end
+	| _ ->
+		if is_diagnostics ctx.com then begin
+			List.iter (fun cm ->
+				add_diagnostics_message ~depth:cm.cm_depth ctx.com 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
 let current_stdin = ref None
 
 

+ 3 - 2
src/context/common.ml

@@ -289,7 +289,8 @@ let s_compiler_stage = function
 
 
 type report_mode =
 type report_mode =
 	| RMNone
 	| RMNone
-	| RMDiagnostics of Path.UniqueKey.t list
+	| RMLegacyDiagnostics of (Path.UniqueKey.t list)
+	| RMDiagnostics of (Path.UniqueKey.t * string option (* file contents *)) list
 	| RMStatistics
 	| RMStatistics
 
 
 class virtual ['key,'value] lookup = object(self)
 class virtual ['key,'value] lookup = object(self)
@@ -890,7 +891,7 @@ let create compilation_step cs version args =
 	com
 	com
 
 
 let is_diagnostics com = match com.report_mode with
 let is_diagnostics com = match com.report_mode with
-	| RMDiagnostics _ -> true
+	| RMLegacyDiagnostics _ | RMDiagnostics _ -> true
 	| _ -> false
 	| _ -> false
 
 
 let disable_report_mode com =
 let disable_report_mode com =

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

@@ -26,8 +26,9 @@ let make_diagnostic kd p sev code args = {
 
 
 let is_diagnostics_file com file_key =
 let is_diagnostics_file com file_key =
 	match com.report_mode with
 	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 -> List.exists (fun key' -> file_key = key') file_keys
+	| RMDiagnostics file_keys -> List.exists (fun (key',_) -> file_key = key') file_keys
 	| _ -> false
 	| _ -> false
 
 
 module UnresolvedIdentifierSuggestion = struct
 module UnresolvedIdentifierSuggestion = struct

+ 49 - 0
src/context/display/displayJson.ml

@@ -125,6 +125,55 @@ let handler =
 			hctx.display#set_display_file false true;
 			hctx.display#set_display_file false true;
 			hctx.display#enable_display DMDefinition;
 			hctx.display#enable_display DMDefinition;
 		);
 		);
+		"display/diagnostics", (fun hctx ->
+			hctx.display#enable_display DMNone;
+
+			let file = hctx.jsonrpc#get_opt_param (fun () ->
+				let file = hctx.jsonrpc#get_string_param "file" in
+				Path.get_full_path file
+			) file_input_marker in
+
+			if file <> file_input_marker then begin
+				let file_unique = hctx.com.file_keys#get file in
+
+				let contents = hctx.jsonrpc#get_opt_param (fun () ->
+					let s = hctx.jsonrpc#get_string_param "contents" in
+					Some s
+				) None in
+
+				DisplayPosition.display_position#set {
+					pfile = file;
+					pmin = -1;
+					pmax = -1;
+				};
+
+				hctx.com.report_mode <- RMDiagnostics [file_unique, contents];
+				hctx.com.display <- { hctx.com.display with dms_display_file_policy = DFPAlso; dms_per_file = true; dms_populate_cache = !ServerConfig.populate_cache_from_display};
+			end else begin
+				let file_contents = hctx.jsonrpc#get_opt_param (fun () ->
+					hctx.jsonrpc#get_opt_param (fun () -> hctx.jsonrpc#get_array_param "fileContents") []
+				) [] in
+
+				if (List.length file_contents) = 0 then begin
+					hctx.com.report_mode <- RMDiagnostics []
+				end else
+					let file_contents = List.map (fun fc -> match fc with
+						| JObject fl ->
+							let file = hctx.jsonrpc#get_string_field "fileContents" "file" fl in
+							let file = Path.get_full_path file in
+							let file_unique = hctx.com.file_keys#get file in
+							let contents = hctx.jsonrpc#get_opt_param (fun () ->
+								let s = hctx.jsonrpc#get_string_field "fileContents" "contents" fl in
+								Some s
+							) None in
+							(file_unique, contents)
+						| _ -> invalid_arg "fileContents"
+					) file_contents in
+
+					DisplayPosition.display_position#set_files (List.map (fun (k, _) -> k) file_contents);
+					hctx.com.report_mode <- RMDiagnostics file_contents
+			end
+		);
 		"display/implementation", (fun hctx ->
 		"display/implementation", (fun hctx ->
 			hctx.display#set_display_file false true;
 			hctx.display#set_display_file false true;
 			hctx.display#enable_display (DMImplementation);
 			hctx.display#enable_display (DMImplementation);

+ 16 - 3
src/core/display/displayPosition.ml

@@ -11,6 +11,7 @@ class display_position_container =
 		(** Current display position *)
 		(** Current display position *)
 		val mutable pos = null_pos
 		val mutable pos = null_pos
 		val mutable file_key = None
 		val mutable file_key = None
+		val mutable file_keys = []
 		(**
 		(**
 			Display position value which was set with the latest `display_position#set p` call.
 			Display position value which was set with the latest `display_position#set p` call.
 			Kept even after `display_position#reset` call.
 			Kept even after `display_position#reset` call.
@@ -23,6 +24,10 @@ class display_position_container =
 			pos <- p;
 			pos <- p;
 			last_pos <- p;
 			last_pos <- p;
 			file_key <- None
 			file_key <- None
+
+		method set_files files =
+			file_keys <- files
+
 		(**
 		(**
 			Get current display position
 			Get current display position
 		*)
 		*)
@@ -43,7 +48,8 @@ class display_position_container =
 		*)
 		*)
 		method reset =
 		method reset =
 			pos <- null_pos;
 			pos <- null_pos;
-			file_key <- None
+			file_key <- None;
+			file_keys <- []
 		(**
 		(**
 			Check if `p` contains current display position
 			Check if `p` contains current display position
 		*)
 		*)
@@ -53,8 +59,15 @@ class display_position_container =
 			Check if a file with `file_key` contains current display position
 			Check if a file with `file_key` contains current display position
 		*)
 		*)
 		method is_in_file file_key =
 		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.
 			Cut `p` at the position of the latest `display_position#set pos` call.
 		*)
 		*)

+ 19 - 13
src/typing/typeloadParse.ml

@@ -61,20 +61,26 @@ let parse_file_from_string com file p string =
 let current_stdin = ref None (* TODO: we're supposed to clear this at some point *)
 let current_stdin = ref None (* TODO: we're supposed to clear this at some point *)
 
 
 let parse_file com file p =
 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 contents = match com.report_mode with
+		| RMDiagnostics files ->
+			(try List.assoc (com.file_keys#get file) files with Not_found -> None)
+		| _ when (Common.defined com Define.DisplayStdin) && DisplayPosition.display_position#is_in_file (com.file_keys#get file) ->
+			Some (match !current_stdin with
+				| Some s ->
+					s
+				| None ->
+					let s = Std.input_all stdin in
+					close_in stdin;
+					current_stdin := Some s;
+					s
+			)
+		| _ -> None
+	in
+
+	match contents with
+	| Some s ->
 		parse_file_from_string com file p s
 		parse_file_from_string com file p s
-	else
+	| _ ->
 		let ch = try open_in_bin file with _ -> raise_typing_error ("Could not open " ^ file) p in
 		let ch = try open_in_bin file with _ -> raise_typing_error ("Could not open " ^ file) p in
 		Std.finally (fun() -> close_in ch) (parse_file_from_lexbuf com file p) (Sedlexing.Utf8.from_channel ch)
 		Std.finally (fun() -> close_in ch) (parse_file_from_lexbuf com file p) (Sedlexing.Utf8.from_channel ch)
 
 

+ 17 - 0
std/haxe/display/Display.hx

@@ -25,6 +25,7 @@ package haxe.display;
 import haxe.display.JsonModuleTypes;
 import haxe.display.JsonModuleTypes;
 import haxe.display.Position;
 import haxe.display.Position;
 import haxe.display.Protocol;
 import haxe.display.Protocol;
+import haxe.ds.ReadOnlyArray;
 
 
 /**
 /**
 	Methods of the JSON-RPC-based `--display` protocol in Haxe 4.
 	Methods of the JSON-RPC-based `--display` protocol in Haxe 4.
@@ -32,6 +33,11 @@ import haxe.display.Protocol;
 **/
 **/
 @:publicFields
 @:publicFields
 class DisplayMethods {
 class DisplayMethods {
+	/**
+		TODO documentation
+	**/
+	static inline var Diagnostics = new HaxeRequestMethod<DiagnosticsParams, DiagnosticsResult>("display/diagnostics");
+
 	/**
 	/**
 		The completion request is sent from the client to Haxe to request code completion.
 		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`.
 		Haxe automatically determines the type of completion to use based on the passed position, see `CompletionResultKind`.
@@ -438,6 +444,17 @@ typedef PatternCompletion<T> = ToplevelCompletion<T> & {
 	var isOutermostPattern:Bool;
 	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) {
 enum abstract CompletionModeKind<T>(Int) {
 	var Field:CompletionModeKind<FieldCompletionSubject<Dynamic>>;
 	var Field:CompletionModeKind<FieldCompletionSubject<Dynamic>>;
 	var StructureField;
 	var StructureField;

+ 19 - 12
tests/server/src/TestCase.hx

@@ -79,22 +79,26 @@ class TestCase implements ITest {
 		server.stop();
 		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) {
 	function runHaxe(args:Array<String>, done:() -> Void) {
 		messages = [];
 		messages = [];
 		errorMessages = [];
 		errorMessages = [];
 		server.rawRequest(args, null, function(result) {
 		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) {
 			if (result.hasError) {
 				sendErrorMessage(result.stderr);
 				sendErrorMessage(result.stderr);
 			}
 			}
@@ -112,7 +116,10 @@ class TestCase implements ITest {
 			callback:TResponse->Void, done:() -> Void) {
 			callback:TResponse->Void, done:() -> Void) {
 		var methodArgs = {method: method, id: 1, params: methodArgs};
 		var methodArgs = {method: method, id: 1, params: methodArgs};
 		args = args.concat(['--display', Json.stringify(methodArgs)]);
 		args = args.concat(['--display', Json.stringify(methodArgs)]);
+		messages = [];
+		errorMessages = [];
 		server.rawRequest(args, null, function(result) {
 		server.rawRequest(args, null, function(result) {
+			handleResult(result);
 			callback(Json.parse(result.stderr).result.result);
 			callback(Json.parse(result.stderr).result.result);
 			done();
 			done();
 		}, function(msg) {
 		}, function(msg) {

+ 59 - 4
tests/server/src/cases/ServerTests.hx

@@ -97,7 +97,9 @@ class ServerTests extends TestCase {
 		var args = ["-main", "BrokenSyntax.hx", "--interp", "--no-output"];
 		var args = ["-main", "BrokenSyntax.hx", "--interp", "--no-output"];
 		runHaxe(args);
 		runHaxe(args);
 		assertErrorMessage("Expected }");
 		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);
 		runHaxe(args);
 		assertErrorMessage("Expected }");
 		assertErrorMessage("Expected }");
 	}
 	}
@@ -143,6 +145,53 @@ class ServerTests extends TestCase {
 		assertSuccess();
 		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);
+			}
+		});
+	}
+
 	function testDiagnosticsRecache() {
 	function testDiagnosticsRecache() {
 		vfs.putContent("HelloWorld.hx", getTemplate("HelloWorld.hx"));
 		vfs.putContent("HelloWorld.hx", getTemplate("HelloWorld.hx"));
 		var args = ["--main", "HelloWorld", "--interp"];
 		var args = ["--main", "HelloWorld", "--interp"];
@@ -152,7 +201,9 @@ class ServerTests extends TestCase {
 		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("HelloWorld.hx")});
 		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("HelloWorld.hx")});
 		runHaxe(args);
 		runHaxe(args);
 		assertSkipping("HelloWorld", Tainted("server/invalidate"));
 		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);
 		runHaxe(args);
 		assertReuse("HelloWorld");
 		assertReuse("HelloWorld");
 	}
 	}
@@ -160,7 +211,9 @@ class ServerTests extends TestCase {
 	function testDiagnosticsRecache2() {
 	function testDiagnosticsRecache2() {
 		vfs.putContent("HelloWorld.hx", getTemplate("HelloWorld.hx"));
 		vfs.putContent("HelloWorld.hx", getTemplate("HelloWorld.hx"));
 		var args = ["--main", "HelloWorld", "--interp"];
 		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);
 		runHaxe(args);
 		assertReuse("HelloWorld");
 		assertReuse("HelloWorld");
 	}
 	}
@@ -172,7 +225,9 @@ class ServerTests extends TestCase {
 		runHaxe(args);
 		runHaxe(args);
 		assertReuse("HelloWorld");
 		assertReuse("HelloWorld");
 		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("HelloWorld.hx")});
 		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"]));
 		runHaxe(args.concat(["--display", "HelloWorld.hx@0@hover"]));
 		assertReuse("HelloWorld");
 		assertReuse("HelloWorld");
 	}
 	}

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

@@ -14,12 +14,15 @@ class Issue10635 extends DisplayTestCase {
 		}
 		}
 	**/
 	**/
 	function test(_) {
 	function test(_) {
-		var args = ["-main", "Main", "--display", "Main.hx@0@diagnostics"];
+		var args = ["-main", "Main"];
 		vfs.putContent("Something.hx", getTemplate("issues/Issue10635/Something.hx"));
 		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")});
 		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(_) {
 	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"));
 		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")});
 		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(_) {
 	function testGenericAddition(_) {

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

@@ -4,9 +4,10 @@ class Issue8687 extends TestCase {
 	function test(_) {
 	function test(_) {
 		vfs.putContent("Main.hx", getTemplate("issues/Issue8687/Main.hx"));
 		vfs.putContent("Main.hx", getTemplate("issues/Issue8687/Main.hx"));
 		var args = ["-main", "Main", "--interp"];
 		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.");
+		});
 	}
 	}
 }
 }

+ 7 - 5
tests/server/src/cases/display/issues/Issue9705.hx

@@ -6,11 +6,13 @@ class Issue9705 extends TestCase {
 	function test(_) {
 	function test(_) {
 		vfs.putContent("Main.hx", getTemplate("issues/Issue9705/Main.hx"));
 		vfs.putContent("Main.hx", getTemplate("issues/Issue9705/Main.hx"));
 		var args = ["Main", "--interp"];
 		var args = ["Main", "--interp"];
-		runHaxe(args.concat(["--display", "Main.hx@0@diagnostics"]));
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {file: new FsPath("Main.hx")}, res -> {
+			Assert.equals(1, res.length);
+			Assert.equals(1, res[0].diagnostics.length);
+			Assert.equals(DKUnresolvedIdentifier, res[0].diagnostics[0].kind);
 
 
-		var diag = parseDiagnostics();
-		var range = diag[0].range;
-		Assert.equals(DKUnresolvedIdentifier, diag[0].kind);
-		Assert.equals("Arrey".length, range.end.character - range.start.character);
+			var range = res[0].diagnostics[0].range;
+			Assert.equals("Arrey".length, range.end.character - range.start.character);
+		});
 	}
 	}
 }
 }

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

@@ -8,9 +8,12 @@ class Issue10653 extends TestCase {
 		runHaxe(args);
 		runHaxe(args);
 		vfs.putContent("Main.hx", getTemplate("issues/Issue10653/MainAfter.hx"));
 		vfs.putContent("Main.hx", getTemplate("issues/Issue10653/MainAfter.hx"));
 		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Main.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")});
 		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);
+		});
 	}
 	}
 }
 }

+ 12 - 6
tests/server/src/cases/issues/Issue11177.hx

@@ -6,12 +6,15 @@ class Issue11177 extends TestCase {
 		vfs.putContent("Buttons.hx", getTemplate("issues/Issue11177/Buttons.hx"));
 		vfs.putContent("Buttons.hx", getTemplate("issues/Issue11177/Buttons.hx"));
 		vfs.putContent("KeyCode.hx", getTemplate("issues/Issue11177/KeyCode.hx"));
 		vfs.putContent("KeyCode.hx", getTemplate("issues/Issue11177/KeyCode.hx"));
 		var args = ["-main", "Main", "--interp"];
 		var args = ["-main", "Main", "--interp"];
-		runHaxe(args.concat(["--display", "Buttons.hx@0@diagnostics"]));
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {file: new FsPath("Buttons.hx")}, res -> {
+			Assert.equals(0, res.length);
+		});
 		vfs.putContent("Main.hx", getTemplate("issues/Issue11177/Main2.hx"));
 		vfs.putContent("Main.hx", getTemplate("issues/Issue11177/Main2.hx"));
 		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Main.hx")});
 		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Main.hx")});
 		runHaxe(args);
 		runHaxe(args);
-		runHaxe(args.concat(["--display", "Buttons.hx@0@diagnostics"]));
-		Assert.isTrue(lastResult.stderr.length == 2);
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {file: new FsPath("Buttons.hx")}, res -> {
+			Assert.equals(0, res.length);
+		});
 	}
 	}
 
 
 	function testWithoutCacheFromDisplay(_) {
 	function testWithoutCacheFromDisplay(_) {
@@ -20,11 +23,14 @@ class Issue11177 extends TestCase {
 		vfs.putContent("KeyCode.hx", getTemplate("issues/Issue11177/KeyCode.hx"));
 		vfs.putContent("KeyCode.hx", getTemplate("issues/Issue11177/KeyCode.hx"));
 		var args = ["-main", "Main", "--interp"];
 		var args = ["-main", "Main", "--interp"];
 		runHaxeJson([], ServerMethods.Configure, {populateCacheFromDisplay: false});
 		runHaxeJson([], ServerMethods.Configure, {populateCacheFromDisplay: false});
-		runHaxe(args.concat(["--display", "Buttons.hx@0@diagnostics"]));
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {file: new FsPath("Buttons.hx")}, res -> {
+			Assert.equals(0, res.length);
+		});
 		vfs.putContent("Main.hx", getTemplate("issues/Issue11177/Main2.hx"));
 		vfs.putContent("Main.hx", getTemplate("issues/Issue11177/Main2.hx"));
 		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Main.hx")});
 		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Main.hx")});
 		runHaxe(args);
 		runHaxe(args);
-		runHaxe(args.concat(["--display", "Buttons.hx@0@diagnostics"]));
-		Assert.isTrue(lastResult.stderr.length == 2);
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {file: new FsPath("Buttons.hx")}, res -> {
+			Assert.equals(0, res.length);
+		});
 	}
 	}
 }
 }

+ 10 - 4
tests/server/src/cases/issues/Issue11184.hx

@@ -5,9 +5,11 @@ class Issue11184 extends TestCase {
 		vfs.putContent("Main.hx", getTemplate("issues/Issue11184/Main.hx"));
 		vfs.putContent("Main.hx", getTemplate("issues/Issue11184/Main.hx"));
 		var args = ["-main", "Main", "-js", "bin/test.js"];
 		var args = ["-main", "Main", "-js", "bin/test.js"];
 
 
-		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");
+		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);
 		runHaxe(args);
 		Assert.isTrue(hasErrorMessage("Cannot use Void as value"));
 		Assert.isTrue(hasErrorMessage("Cannot use Void as value"));
@@ -19,7 +21,11 @@ class Issue11184 extends TestCase {
 		vfs.putContent("Main.hx", getTemplate("issues/Issue11184/Main.hx"));
 		vfs.putContent("Main.hx", getTemplate("issues/Issue11184/Main.hx"));
 		var args = ["-main", "Main", "-js", "bin/test.js"];
 		var args = ["-main", "Main", "-js", "bin/test.js"];
 		runHaxeJson([], ServerMethods.Configure, {populateCacheFromDisplay: false});
 		runHaxeJson([], ServerMethods.Configure, {populateCacheFromDisplay: false});
-		runHaxe(args.concat(["--display", "Main.hx@0@diagnostics"]));
+		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);
 		runHaxe(args);
 		Assert.isTrue(hasErrorMessage("Cannot use Void as value"));
 		Assert.isTrue(hasErrorMessage("Cannot use Void as value"));
 		runHaxe(args);
 		runHaxe(args);

+ 6 - 8
tests/server/src/cases/issues/Issue11203.hx

@@ -5,19 +5,17 @@ class Issue11203 extends TestCase {
 		vfs.putContent("Main.hx", getTemplate("issues/Issue11203/MainClass.hx"));
 		vfs.putContent("Main.hx", getTemplate("issues/Issue11203/MainClass.hx"));
 		var args = ["Main", "--interp"];
 		var args = ["Main", "--interp"];
 		runHaxe(args);
 		runHaxe(args);
-		runHaxe(args.concat(["--display", "Main.hx@0@diagnostics"]));
-
-		var diag = parseDiagnostics();
-		Assert.isTrue(diag.length == 0);
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {file: new FsPath("Main.hx")}, res -> {
+			Assert.equals(0, res.length);
+		});
 	}
 	}
 
 
 	function testAbstract(_) {
 	function testAbstract(_) {
 		vfs.putContent("Main.hx", getTemplate("issues/Issue11203/MainAbstract.hx"));
 		vfs.putContent("Main.hx", getTemplate("issues/Issue11203/MainAbstract.hx"));
 		var args = ["Main", "--interp"];
 		var args = ["Main", "--interp"];
 		runHaxe(args);
 		runHaxe(args);
-		runHaxe(args.concat(["--display", "Main.hx@0@diagnostics"]));
-
-		var diag = parseDiagnostics();
-		Assert.isTrue(diag.length == 0);
+		runHaxeJsonCb(args, DisplayMethods.Diagnostics, {file: new FsPath("Main.hx")}, res -> {
+			Assert.equals(0, res.length);
+		});
 	}
 	}
 }
 }

+ 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;
+	}
+}