2
0
Эх сурвалжийг харах

change handling of com.display

Instead of checking individual display modes in many places we introduce something similar to the platform config which is handled in a central place.
Simon Krajewski 9 жил өмнө
parent
commit
15b621d255

+ 9 - 8
src/display/display.ml

@@ -1,5 +1,6 @@
 open Ast
 open Ast
 open Common
 open Common
+open Common.DisplayMode
 open Type
 open Type
 open Typecore
 open Typecore
 
 
@@ -95,7 +96,7 @@ let find_before_pos com e =
 let display_type dm t p =
 let display_type dm t p =
 	try
 	try
 		let mt = module_type_of_type t in
 		let mt = module_type_of_type t in
-		begin match dm with
+		begin match dm.dms_kind with
 			| DMPosition -> raise (DisplayPosition [(t_infos mt).mt_pos]);
 			| DMPosition -> raise (DisplayPosition [(t_infos mt).mt_pos]);
 			| DMUsage _ ->
 			| DMUsage _ ->
 				let ti = t_infos mt in
 				let ti = t_infos mt in
@@ -114,7 +115,7 @@ let check_display_type ctx t p =
 		if ctx.is_display_file && is_display_position p then
 		if ctx.is_display_file && is_display_position p then
 			display_type ctx.com.display t p
 			display_type ctx.com.display t p
 	in
 	in
-	match ctx.com.display with
+	match ctx.com.display.dms_kind with
 	| DMStatistics -> add_type_hint()
 	| DMStatistics -> add_type_hint()
 	| DMUsage _ -> add_type_hint(); maybe_display_type()
 	| DMUsage _ -> add_type_hint(); maybe_display_type()
 	| _ -> maybe_display_type()
 	| _ -> maybe_display_type()
@@ -122,19 +123,19 @@ let check_display_type ctx t p =
 let display_module_type dm mt =
 let display_module_type dm mt =
 	display_type dm (type_of_module_type mt)
 	display_type dm (type_of_module_type mt)
 
 
-let display_variable dm v p = match dm with
+let display_variable dm v p = match dm.dms_kind with
 	| DMPosition -> raise (DisplayPosition [v.v_pos])
 	| DMPosition -> raise (DisplayPosition [v.v_pos])
 	| DMUsage _ -> v.v_meta <- (Meta.Usage,[],v.v_pos) :: v.v_meta;
 	| DMUsage _ -> v.v_meta <- (Meta.Usage,[],v.v_pos) :: v.v_meta;
 	| DMType -> raise (DisplayType (v.v_type,p))
 	| DMType -> raise (DisplayType (v.v_type,p))
 	| _ -> ()
 	| _ -> ()
 
 
-let display_field dm cf p = match dm with
+let display_field dm cf p = match dm.dms_kind with
 	| DMPosition -> raise (DisplayPosition [cf.cf_pos]);
 	| DMPosition -> raise (DisplayPosition [cf.cf_pos]);
 	| DMUsage _ -> cf.cf_meta <- (Meta.Usage,[],cf.cf_pos) :: cf.cf_meta;
 	| DMUsage _ -> cf.cf_meta <- (Meta.Usage,[],cf.cf_pos) :: cf.cf_meta;
 	| DMType -> raise (DisplayType (cf.cf_type,p))
 	| DMType -> raise (DisplayType (cf.cf_type,p))
 	| _ -> ()
 	| _ -> ()
 
 
-let display_enum_field dm ef p = match dm with
+let display_enum_field dm ef p = match dm.dms_kind with
 	| DMPosition -> raise (DisplayPosition [p]);
 	| DMPosition -> raise (DisplayPosition [p]);
 	| DMUsage _ -> ef.ef_meta <- (Meta.Usage,[],p) :: ef.ef_meta;
 	| DMUsage _ -> ef.ef_meta <- (Meta.Usage,[],p) :: ef.ef_meta;
 	| DMType -> raise (DisplayType (ef.ef_type,p))
 	| DMType -> raise (DisplayType (ef.ef_type,p))
@@ -339,7 +340,7 @@ let convert_import_to_something_usable pt path =
 	in
 	in
 	loop [] None None path
 	loop [] None None path
 
 
-let process_expr com e = match com.display with
+let process_expr com e = match com.display.dms_kind with
 	| DMToplevel -> find_enclosing com e
 	| DMToplevel -> find_enclosing com e
 	| DMPosition | DMUsage _ | DMType -> find_before_pos com e
 	| DMPosition | DMUsage _ | DMType -> find_before_pos com e
 	| _ -> e
 	| _ -> e
@@ -529,7 +530,7 @@ module Diagnostics = struct
 		write_json (Buffer.add_string b) js;
 		write_json (Buffer.add_string b) js;
 		Buffer.contents b
 		Buffer.contents b
 
 
-	let is_diagnostics_run ctx = match ctx.com.display with
+	let is_diagnostics_run ctx = match ctx.com.display.dms_kind with
 		| DMDiagnostics true -> true
 		| DMDiagnostics true -> true
 		| DMDiagnostics false -> ctx.is_display_file
 		| DMDiagnostics false -> ctx.is_display_file
 		| _ -> false
 		| _ -> false
@@ -728,7 +729,7 @@ module Statistics = struct
 					()
 					()
 			) paths
 			) paths
 		in
 		in
-		deal_with_imports ctx.com.shared.shared_display_information.import_positions;
+		if false then deal_with_imports ctx.com.shared.shared_display_information.import_positions;
 		symbols,relations
 		symbols,relations
 end
 end
 
 

+ 1 - 1
src/generators/genswf.ml

@@ -481,7 +481,7 @@ let parse_swf com file =
 	IO.close_in ch;
 	IO.close_in ch;
 	List.iter (fun t ->
 	List.iter (fun t ->
 		match t.tdata with
 		match t.tdata with
-		| TActionScript3 (id,as3) when not com.debug && com.display = DMNone ->
+		| TActionScript3 (id,as3) when not com.debug && not com.display.DisplayMode.dms_display ->
 			t.tdata <- TActionScript3 (id,remove_debug_infos as3)
 			t.tdata <- TActionScript3 (id,remove_debug_infos as3)
 		| _ -> ()
 		| _ -> ()
 	) tags;
 	) tags;

+ 45 - 55
src/main.ml

@@ -46,6 +46,7 @@ open Printf
 open Ast
 open Ast
 open Genswf
 open Genswf
 open Common
 open Common
+open Common.DisplayMode
 open Type
 open Type
 
 
 type context = {
 type context = {
@@ -402,7 +403,7 @@ let add_libs com libs =
 			| Some cache ->
 			| Some cache ->
 				(try
 				(try
 					(* if we are compiling, really call haxelib since library path might have changed *)
 					(* if we are compiling, really call haxelib since library path might have changed *)
-					if com.display = DMNone then raise Not_found;
+					if not com.display.dms_display then raise Not_found;
 					Hashtbl.find cache.c_haxelib libs
 					Hashtbl.find cache.c_haxelib libs
 				with Not_found ->
 				with Not_found ->
 					let lines = call_haxelib() in
 					let lines = call_haxelib() in
@@ -822,12 +823,9 @@ and wait_loop verbose accept =
 		let read, write, close = accept() in
 		let read, write, close = accept() in
 		let t0 = get_time() in
 		let t0 = get_time() in
 		let rec cache_context com =
 		let rec cache_context com =
-			begin match com.display with
-				| DMNone | DMDiagnostics true ->
-					List.iter cache_module com.modules;
-					if verbose then print_endline ("Cached " ^ string_of_int (List.length com.modules) ^ " modules");
-				| _ ->
-					()
+			if com.display.dms_full_typing then begin
+				List.iter cache_module com.modules;
+				if verbose then print_endline ("Cached " ^ string_of_int (List.length com.modules) ^ " modules");
 			end;
 			end;
 			match com.get_macros() with
 			match com.get_macros() with
 			| None -> ()
 			| None -> ()
@@ -848,16 +846,13 @@ and wait_loop verbose accept =
 					print_endline ("Using signature " ^ Digest.to_hex (get_signature ctx.com));
 					print_endline ("Using signature " ^ Digest.to_hex (get_signature ctx.com));
 				end;
 				end;
 				Parser.display_error := (fun e p -> has_parse_error := true; ctx.com.error (Parser.error_msg e) p);
 				Parser.display_error := (fun e p -> has_parse_error := true; ctx.com.error (Parser.error_msg e) p);
-				begin match ctx.com.display with
-					| DMNone | DMDiagnostics true ->
-						()
-					| _ ->
-						let file = (!Parser.resume_display).Ast.pfile in
-						let fkey = file ^ "!" ^ get_signature ctx.com in
-						(* force parsing again : if the completion point have been changed *)
-						Hashtbl.remove cache.c_files fkey;
-						(* force module reloading (if cached) *)
-						Hashtbl.iter (fun _ m -> if m.m_extra.m_file = file then m.m_extra.m_dirty <- true) cache.c_modules
+				if ctx.com.display.dms_display then begin
+					let file = (!Parser.resume_display).Ast.pfile in
+					let fkey = file ^ "!" ^ get_signature ctx.com in
+					(* force parsing again : if the completion point have been changed *)
+					Hashtbl.remove cache.c_files fkey;
+					(* force module reloading (if cached) *)
+					Hashtbl.iter (fun _ m -> if m.m_extra.m_file = file then m.m_extra.m_dirty <- true) cache.c_modules
 				end
 				end
 			);
 			);
 			ctx.com.print <- (fun str -> write ("\x01" ^ String.concat "\x01" (ExtString.String.nsplit str "\n") ^ "\n"));
 			ctx.com.print <- (fun str -> write ("\x01" ^ String.concat "\x01" (ExtString.String.nsplit str "\n") ^ "\n"));
@@ -1281,7 +1276,7 @@ try
 				(try display_memory ctx with e -> prerr_endline (Printexc.get_backtrace ()));
 				(try display_memory ctx with e -> prerr_endline (Printexc.get_backtrace ()));
 			| "diagnostics" ->
 			| "diagnostics" ->
 				Common.define com Define.NoCOpt;
 				Common.define com Define.NoCOpt;
-				com.display <- DMDiagnostics true;
+				com.display <- DisplayMode.create (DMDiagnostics true);
 				Common.display_default := DMDiagnostics true;
 				Common.display_default := DMDiagnostics true;
 			| _ ->
 			| _ ->
 				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
@@ -1325,7 +1320,7 @@ try
 								DMDefault
 								DMDefault
 				in
 				in
 				let pos = try int_of_string pos with _ -> failwith ("Invalid format : "  ^ pos) in
 				let pos = try int_of_string pos with _ -> failwith ("Invalid format : "  ^ pos) in
-				com.display <- mode;
+				com.display <- DisplayMode.create mode;
 				Common.display_default := mode;
 				Common.display_default := mode;
 				Common.define_value com Define.Display (if smode <> "" then smode else "1");
 				Common.define_value com Define.Display (if smode <> "" then smode else "1");
 				Parser.use_doc := true;
 				Parser.use_doc := true;
@@ -1478,31 +1473,32 @@ try
 	process_ref := process;
 	process_ref := process;
 	process ctx.com.args;
 	process ctx.com.args;
 	process_libs();
 	process_libs();
-	begin match com.display with
-	| DMNone | DMDiagnostics true ->
-		()
-	| _ ->
-		com.warning <- if com.display = DMDiagnostics false then (fun s p -> add_diagnostics_message com s p DiagnosticsSeverity.Warning) else message ctx;
+	if com.display.dms_display then begin
+		com.warning <- if com.display.dms_error_policy = EPCollect then (fun s p -> add_diagnostics_message com s p DiagnosticsSeverity.Warning) else message ctx;
 		com.error <- error ctx;
 		com.error <- error ctx;
-		com.main_class <- None;
-		begin match com.display with
-			| DMUsage _ | DMStatistics -> ()
-			| _ -> classes := []
-		end;
-		let real = get_real_path (!Parser.resume_display).Ast.pfile in
-		(match get_module_path_from_file_path com real with
-		| Some path ->
-			if com.display = DMPackage then raise (Display.DisplayPackage (fst path));
-			classes := path :: !classes
-		| None ->
-			if not (Sys.file_exists real) then failwith "Display file does not exist";
-			(match List.rev (ExtString.String.nsplit real path_sep) with
-			| file :: _ when file.[0] >= 'a' && file.[1] <= 'z' -> failwith ("Display file '" ^ file ^ "' should not start with a lowercase letter")
-			| _ -> ());
-			failwith "Display file was not found in class path"
-		);
-		Common.log com ("Display file : " ^ real);
-		Common.log com ("Classes found : ["  ^ (String.concat "," (List.map Ast.s_type_path !classes)) ^ "]");
+	end;
+	begin match com.display.dms_display_file_policy with
+		| DFPNo ->
+			()
+		| dfp ->
+			if dfp = DFPOnly then begin
+				classes := [];
+				com.main_class <- None;
+			end;
+			let real = get_real_path (!Parser.resume_display).Ast.pfile in
+			(match get_module_path_from_file_path com real with
+			| Some path ->
+				if com.display.dms_kind = DMPackage then raise (Display.DisplayPackage (fst path));
+				classes := path :: !classes
+			| None ->
+				if not (Sys.file_exists real) then failwith "Display file does not exist";
+				(match List.rev (ExtString.String.nsplit real path_sep) with
+				| file :: _ when file.[0] >= 'a' && file.[1] <= 'z' -> failwith ("Display file '" ^ file ^ "' should not start with a lowercase letter")
+				| _ -> ());
+				failwith "Display file was not found in class path"
+			);
+			Common.log com ("Display file : " ^ real);
+			Common.log com ("Classes found : ["  ^ (String.concat "," (List.map Ast.s_type_path !classes)) ^ "]");
 	end;
 	end;
 	let add_std dir =
 	let add_std dir =
 		com.class_path <- List.filter (fun s -> not (List.mem s com.std_path)) com.class_path @ List.map (fun p -> p ^ dir ^ "/_std/") com.std_path @ com.std_path
 		com.class_path <- List.filter (fun s -> not (List.mem s com.std_path)) com.class_path @ List.map (fun p -> p ^ dir ^ "/_std/") com.std_path @ com.std_path
@@ -1586,11 +1582,8 @@ try
 			"hl"
 			"hl"
 	) in
 	) in
 	(* if we are at the last compilation step, allow all packages accesses - in case of macros or opening another project file *)
 	(* if we are at the last compilation step, allow all packages accesses - in case of macros or opening another project file *)
-	begin match com.display with
-		| DMNone | DMToplevel ->
-			()
-		| _ ->
-			if not ctx.has_next then com.package_rules <- PMap.foldi (fun p r acc -> match r with Forbidden -> acc | _ -> PMap.add p r acc) com.package_rules PMap.empty;
+	if com.display.dms_display then begin
+		if not ctx.has_next then com.package_rules <- PMap.foldi (fun p r acc -> match r with Forbidden -> acc | _ -> PMap.add p r acc) com.package_rules PMap.empty;
 	end;
 	end;
 	com.config <- get_config com; (* make sure to adapt all flags changes defined after platform *)
 	com.config <- get_config com; (* make sure to adapt all flags changes defined after platform *)
 
 
@@ -1617,19 +1610,16 @@ try
 		Typer.finalize tctx;
 		Typer.finalize tctx;
 		t();
 		t();
 		if ctx.has_error then raise Abort;
 		if ctx.has_error then raise Abort;
-		begin match ctx.com.display with
-			| DMNone | DMUsage _ | DMDiagnostics true | DMStatistics ->
-				()
-			| _ ->
-				if ctx.has_next then raise Abort;
-				failwith "No completion point was found";
+		if ctx.com.display.dms_exit_during_typing then begin
+			if ctx.has_next then raise Abort;
+			failwith "No completion point was found";
 		end;
 		end;
 		let t = Common.timer "filters" in
 		let t = Common.timer "filters" in
 		let main, types, modules = Typer.generate tctx in
 		let main, types, modules = Typer.generate tctx in
 		com.main <- main;
 		com.main <- main;
 		com.types <- types;
 		com.types <- types;
 		com.modules <- modules;
 		com.modules <- modules;
-		begin match com.display with
+		begin match com.display.dms_kind with
 			| DMUsage with_definition ->
 			| DMUsage with_definition ->
 				let symbols,relations = Display.Statistics.collect_statistics tctx in
 				let symbols,relations = Display.Statistics.collect_statistics tctx in
 				let rec loop acc relations = match relations with
 				let rec loop acc relations = match relations with

+ 1 - 1
src/optimization/optimizer.ml

@@ -675,7 +675,7 @@ let rec type_inline ctx cf f ethis params tret config p ?(self_calling_closure=f
 			| _ -> e
 			| _ -> e
 		in
 		in
 		let e = List.fold_left inline_meta e cf.cf_meta in
 		let e = List.fold_left inline_meta e cf.cf_meta in
-		let e = match ctx.com.display with DMDiagnostics _ -> mk (TMeta((Meta.Extern,[],e.epos),e)) e.etype e.epos | _ -> e in
+		let e = if ctx.com.display.DisplayMode.dms_is_diagnostics_run then mk (TMeta((Meta.Extern,[],e.epos),e)) e.etype e.epos else e in
 		(* we need to replace type-parameters that were used in the expression *)
 		(* we need to replace type-parameters that were used in the expression *)
 		if not has_params then
 		if not has_params then
 			Some e
 			Some e

+ 100 - 16
src/typing/common.ml

@@ -90,18 +90,102 @@ type platform_config = {
 	pf_reserved_type_paths : path list;
 	pf_reserved_type_paths : path list;
 }
 }
 
 
-type display_mode =
-	| DMNone
-	| DMDefault
-	| DMUsage of bool (* true = also report definition *)
-	| DMPosition
-	| DMToplevel
-	| DMResolve of string
-	| DMPackage
-	| DMType
-	| DMModuleSymbols
-	| DMDiagnostics of bool (* true = global, false = only in display file *)
-	| DMStatistics
+module DisplayMode = struct
+	type t =
+		| DMNone
+		| DMDefault
+		| DMUsage of bool (* true = also report definition *)
+		| DMPosition
+		| DMToplevel
+		| DMResolve of string
+		| DMPackage
+		| DMType
+		| DMModuleSymbols
+		| DMDiagnostics of bool (* true = global, false = only in display file *)
+		| DMStatistics
+
+	type error_policy =
+		| EPIgnore
+		| EPCollect
+		| EPShow
+
+	type display_file_policy =
+		| DFPOnly
+		| DFPAlso
+		| DFPNo
+
+	type settings = {
+		dms_kind : t;
+		dms_display : bool;
+		dms_full_typing : bool;
+		dms_error_policy : error_policy;
+		dms_is_diagnostics_run : bool;
+		dms_collect_data : bool;
+		dms_check_core_api : bool;
+		dms_inline : bool;
+		dms_display_file_policy : display_file_policy;
+		dms_exit_during_typing : bool;
+	}
+
+	let default_display_settings = {
+		dms_kind = DMDefault;
+		dms_display = true;
+		dms_full_typing = false;
+		dms_error_policy = EPIgnore;
+		dms_is_diagnostics_run = false;
+		dms_collect_data = false;
+		dms_check_core_api = false;
+		dms_inline = false;
+		dms_display_file_policy = DFPOnly;
+		dms_exit_during_typing = true;
+	}
+
+	let default_compilation_settings = {
+		dms_kind = DMNone;
+		dms_display = false;
+		dms_full_typing = true;
+		dms_error_policy = EPShow;
+		dms_is_diagnostics_run = false;
+		dms_collect_data = false;
+		dms_check_core_api = true;
+		dms_inline = true;
+		dms_display_file_policy = DFPNo;
+		dms_exit_during_typing = false;
+	}
+
+	let create dm =
+		let settings = { default_display_settings with dms_kind = dm } in
+		match dm with
+		| DMNone -> default_compilation_settings
+		| DMDefault | DMPosition | DMResolve _ | DMPackage | DMType -> settings
+		| DMUsage _ -> { settings with
+				dms_full_typing = true;
+				dms_collect_data = true;
+				dms_display_file_policy = DFPAlso;
+				dms_exit_during_typing = false
+			}
+		| DMToplevel -> { settings with dms_full_typing = true; }
+		| DMModuleSymbols -> { settings with
+				dms_display_file_policy = DFPAlso;
+				dms_exit_during_typing = false
+			}
+		| DMDiagnostics _ -> { settings with
+				dms_full_typing = true;
+				dms_error_policy = EPCollect;
+				dms_is_diagnostics_run = true;
+				dms_collect_data = true;
+				dms_inline = false;
+				dms_display_file_policy = DFPAlso;
+				dms_exit_during_typing = false;
+			}
+		| DMStatistics -> { settings with
+				dms_full_typing = true;
+				dms_collect_data = true;
+				dms_inline = false;
+				dms_display_file_policy = DFPAlso;
+				dms_exit_during_typing = false
+			}
+end
 
 
 type compiler_callback = {
 type compiler_callback = {
 	mutable after_typing : (module_type list -> unit) list;
 	mutable after_typing : (module_type list -> unit) list;
@@ -165,7 +249,7 @@ type context = {
 	shared : shared_context;
 	shared : shared_context;
 	display_information : display_information;
 	display_information : display_information;
 	mutable sys_args : string list;
 	mutable sys_args : string list;
-	mutable display : display_mode;
+	mutable display : DisplayMode.settings;
 	mutable debug : bool;
 	mutable debug : bool;
 	mutable verbose : bool;
 	mutable verbose : bool;
 	mutable foptimize : bool;
 	mutable foptimize : bool;
@@ -215,7 +299,7 @@ type context = {
 
 
 exception Abort of string * Ast.pos
 exception Abort of string * Ast.pos
 
 
-let display_default = ref DMNone
+let display_default = ref DisplayMode.DMNone
 
 
 type cache = {
 type cache = {
 	mutable c_haxelib : (string list, string list) Hashtbl.t;
 	mutable c_haxelib : (string list, string list) Hashtbl.t;
@@ -738,7 +822,7 @@ let create version s_version args =
 	let defines =
 	let defines =
 		PMap.add "true" "1" (
 		PMap.add "true" "1" (
 		PMap.add "source-header" ("Generated by Haxe " ^ s_version) (
 		PMap.add "source-header" ("Generated by Haxe " ^ s_version) (
-		if !display_default <> DMNone then PMap.add "display" "1" PMap.empty else PMap.empty))
+		if !display_default <> DisplayMode.DMNone then PMap.add "display" "1" PMap.empty else PMap.empty))
 	in
 	in
 	{
 	{
 		version = version;
 		version = version;
@@ -756,7 +840,7 @@ let create version s_version args =
 		};
 		};
 		sys_args = args;
 		sys_args = args;
 		debug = false;
 		debug = false;
-		display = !display_default;
+		display = DisplayMode.create !display_default;
 		verbose = false;
 		verbose = false;
 		foptimize = true;
 		foptimize = true;
 		features = Hashtbl.create 0;
 		features = Hashtbl.create 0;

+ 4 - 4
src/typing/matcher.ml

@@ -1242,7 +1242,7 @@ module TexprConverter = struct
 		let p = dt.dt_pos in
 		let p = dt.dt_pos in
 		let c_type = match follow (Typeload.load_instance ctx ({ tpackage = ["std"]; tname="Type"; tparams=[]; tsub = None},null_pos) true p) with TInst(c,_) -> c | t -> assert false in
 		let c_type = match follow (Typeload.load_instance ctx ({ tpackage = ["std"]; tname="Type"; tparams=[]; tsub = None},null_pos) true p) with TInst(c,_) -> c | t -> assert false in
 		let mk_index_call e =
 		let mk_index_call e =
-			if ctx.com.display <> DMNone then
+			if not ctx.com.display.DisplayMode.dms_full_typing then
 				(* If we are in display mode there's a chance that these fields don't exist. Let's just use a
 				(* If we are in display mode there's a chance that these fields don't exist. Let's just use a
 				   (correctly typed) neutral value because it doesn't actually matter. *)
 				   (correctly typed) neutral value because it doesn't actually matter. *)
 				mk (TConst (TInt (Int32.of_int 0))) ctx.t.tint e.epos
 				mk (TConst (TInt (Int32.of_int 0))) ctx.t.tint e.epos
@@ -1251,7 +1251,7 @@ module TexprConverter = struct
 				make_static_call ctx c_type cf (fun t -> t) [e] com.basic.tint e.epos
 				make_static_call ctx c_type cf (fun t -> t) [e] com.basic.tint e.epos
 		in
 		in
 		let mk_name_call e =
 		let mk_name_call e =
-			if ctx.com.display <> DMNone then
+			if not ctx.com.display.DisplayMode.dms_full_typing then
 				mk (TConst (TString "")) ctx.t.tstring e.epos
 				mk (TConst (TString "")) ctx.t.tstring e.epos
 			else
 			else
 				let cf = PMap.find "enumConstructor" c_type.cl_statics in
 				let cf = PMap.find "enumConstructor" c_type.cl_statics in
@@ -1273,7 +1273,7 @@ module TexprConverter = struct
 					with Not_exhaustive -> match with_type,finiteness with
 					with Not_exhaustive -> match with_type,finiteness with
 						| NoValue,Infinite -> None
 						| NoValue,Infinite -> None
 						| _,CompileTimeFinite when unmatched = [] -> None
 						| _,CompileTimeFinite when unmatched = [] -> None
-						| _ when ctx.com.display <> DMNone -> None
+						| _ when ctx.com.display.DisplayMode.dms_error_policy = DisplayMode.EPIgnore -> None
 						| _ -> report_not_exhaustive e_subject unmatched
 						| _ -> report_not_exhaustive e_subject unmatched
 				in
 				in
 				let cases = ExtList.List.filter_map (fun (con,_,dt) -> match unify_constructor ctx params e_subject.etype con with
 				let cases = ExtList.List.filter_map (fun (con,_,dt) -> match unify_constructor ctx params e_subject.etype con with
@@ -1346,7 +1346,7 @@ module TexprConverter = struct
 					)
 					)
 				with Not_exhaustive ->
 				with Not_exhaustive ->
 					if toplevel then (fun () -> loop false params dt2)
 					if toplevel then (fun () -> loop false params dt2)
-					else if ctx.com.display <> DMNone then (fun () -> mk (TConst TNull) (mk_mono()) dt2.dt_pos)
+					else if ctx.com.display.DisplayMode.dms_error_policy = DisplayMode.EPIgnore then (fun () -> mk (TConst TNull) (mk_mono()) dt2.dt_pos)
 					else report_not_exhaustive e [ConConst TNull,dt.dt_pos]
 					else report_not_exhaustive e [ConConst TNull,dt.dt_pos]
 				in
 				in
 				f()
 				f()

+ 3 - 3
src/typing/typecore.ml

@@ -231,9 +231,9 @@ let pass_name = function
 	| PForce -> "force"
 	| PForce -> "force"
 	| PFinal -> "final"
 	| PFinal -> "final"
 
 
-let display_error ctx msg p = match ctx.com.display with
-	| DMDiagnostics _ -> add_diagnostics_message ctx.com msg p DiagnosticsSeverity.Error
-	| _ -> ctx.on_error ctx msg p
+let display_error ctx msg p = match ctx.com.display.DisplayMode.dms_error_policy with
+	| DisplayMode.EPShow | DisplayMode.EPIgnore -> ctx.on_error ctx msg p
+	| DisplayMode.EPCollect -> add_diagnostics_message ctx.com msg p DiagnosticsSeverity.Error
 
 
 let error msg p = raise (Error (Custom msg,p))
 let error msg p = raise (Error (Custom msg,p))
 
 

+ 44 - 48
src/typing/typeload.ml

@@ -18,8 +18,9 @@
  *)
  *)
 
 
 open Ast
 open Ast
-open Type
 open Common
 open Common
+open Common.DisplayMode
+open Type
 open Typecore
 open Typecore
 
 
 exception Build_canceled of build_state
 exception Build_canceled of build_state
@@ -236,7 +237,7 @@ let parse_file_from_lexbuf com file p lexbuf =
 	Lexer.init file true;
 	Lexer.init file true;
 	incr stats.s_files_parsed;
 	incr stats.s_files_parsed;
 	let data = (try Parser.parse com lexbuf with e -> t(); raise e) in
 	let data = (try Parser.parse com lexbuf with e -> t(); raise e) in
-	if com.display = DMModuleSymbols && Display.is_display_file file then
+	if com.display.dms_kind = DMModuleSymbols && Display.is_display_file file then
 		raise (Display.ModuleSymbols(Display.print_module_symbols data));
 		raise (Display.ModuleSymbols(Display.print_module_symbols data));
 	t();
 	t();
 	Common.log com ("Parsed " ^ file);
 	Common.log com ("Parsed " ^ file);
@@ -450,7 +451,7 @@ let rec load_instance ?(allow_display=false) ctx (t,pn) allow_no_params p =
 			| [TPType t] -> TDynamic (load_complex_type ctx false p t)
 			| [TPType t] -> TDynamic (load_complex_type ctx false p t)
 			| _ -> error "Too many parameters for Dynamic" p
 			| _ -> error "Too many parameters for Dynamic" p
 		else begin
 		else begin
-			if not is_rest && ctx.com.display = DMNone && List.length types <> List.length t.tparams then error ("Invalid number of type parameters for " ^ s_type_path path) p;
+			if not is_rest && ctx.com.display.dms_error_policy <> EPIgnore && List.length types <> List.length t.tparams then error ("Invalid number of type parameters for " ^ s_type_path path) p;
 			let tparams = List.map (fun t ->
 			let tparams = List.map (fun t ->
 				match t with
 				match t with
 				| TPExpr e ->
 				| TPExpr e ->
@@ -498,7 +499,7 @@ let rec load_instance ?(allow_display=false) ctx (t,pn) allow_no_params p =
 					[]
 					[]
 				| [],["Rest",_] when is_generic_build ->
 				| [],["Rest",_] when is_generic_build ->
 					[]
 					[]
-				| [],(_,t) :: tl when ctx.com.display <> DMNone ->
+				| [],(_,t) :: tl when ctx.com.display.dms_error_policy = EPIgnore ->
 					t :: loop [] tl is_rest
 					t :: loop [] tl is_rest
 				| [],_ ->
 				| [],_ ->
 					error ("Not enough type parameters for " ^ s_type_path path) p
 					error ("Not enough type parameters for " ^ s_type_path path) p
@@ -1090,7 +1091,7 @@ let type_function_arg_value ctx t c =
 				| TConst c -> Some c
 				| TConst c -> Some c
 				| TCast(e,None) -> loop e
 				| TCast(e,None) -> loop e
 				| _ ->
 				| _ ->
-					if ctx.com.display = DMNone then display_error ctx "Parameter default value should be constant" p;
+					if not ctx.com.display.dms_display || ctx.com.display.dms_error_policy = EPCollect then display_error ctx "Parameter default value should be constant" p;
 					None
 					None
 			in
 			in
 			loop e
 			loop e
@@ -1408,11 +1409,9 @@ module Inheritance = struct
 					else
 					else
 						t2, f2
 						t2, f2
 				in
 				in
-				begin match ctx.com.display with
-					| DMUsage _ | DMStatistics ->
+				if ctx.com.display.dms_collect_data then begin
 						let h = ctx.com.display_information in
 						let h = ctx.com.display_information in
 						h.interface_field_implementations <- (intf,f,c,Some f2) :: h.interface_field_implementations;
 						h.interface_field_implementations <- (intf,f,c,Some f2) :: h.interface_field_implementations;
-					| _ ->	()
 				end;
 				end;
 				ignore(follow f2.cf_type); (* force evaluation *)
 				ignore(follow f2.cf_type); (* force evaluation *)
 				let p = (match f2.cf_expr with None -> p | Some e -> e.epos) in
 				let p = (match f2.cf_expr with None -> p | Some e -> e.epos) in
@@ -1634,7 +1633,7 @@ let type_function ctx args ret fmode f do_display p =
 		| Parser.TypePath (_,None,_) | Exit ->
 		| Parser.TypePath (_,None,_) | Exit ->
 			type_expr ctx e NoValue
 			type_expr ctx e NoValue
 		| Display.DisplayType (t,_) | Display.DisplaySignatures [(t,_)] when (match follow t with TMono _ -> true | _ -> false) ->
 		| Display.DisplayType (t,_) | Display.DisplaySignatures [(t,_)] when (match follow t with TMono _ -> true | _ -> false) ->
-			type_expr ctx (if ctx.com.display = DMToplevel then Display.find_enclosing ctx.com e else e) NoValue
+			type_expr ctx (if ctx.com.display.dms_kind = DMToplevel then Display.find_enclosing ctx.com e else e) NoValue
 	end in
 	end in
 	let e = match e.eexpr with
 	let e = match e.eexpr with
 		| TMeta((Meta.MergeBlock,_,_), ({eexpr = TBlock el} as e1)) -> e1
 		| TMeta((Meta.MergeBlock,_,_), ({eexpr = TBlock el} as e1)) -> e1
@@ -1657,7 +1656,7 @@ let type_function ctx args ret fmode f do_display p =
 		   can _not_ use type_iseq to avoid the Void check above because that
 		   can _not_ use type_iseq to avoid the Void check above because that
 		   would turn Dynamic returns to Void returns. *)
 		   would turn Dynamic returns to Void returns. *)
 		| TMono t when not (has_return e) -> ignore(link t ret ctx.t.tvoid)
 		| TMono t when not (has_return e) -> ignore(link t ret ctx.t.tvoid)
-		| _ when ctx.com.display <> DMNone -> ()
+		| _ when ctx.com.display.dms_error_policy = EPIgnore -> ()
 		| _ -> (try return_flow ctx e with Exit -> ())
 		| _ -> (try return_flow ctx e with Exit -> ())
 	end;
 	end;
 	let rec loop e =
 	let rec loop e =
@@ -2133,8 +2132,7 @@ module ClassInitializer = struct
 				cctx.delayed_expr <- (ctx,Some r) :: cctx.delayed_expr;
 				cctx.delayed_expr <- (ctx,Some r) :: cctx.delayed_expr;
 			end
 			end
 		in
 		in
-		begin match ctx.com.display with
-			| DMNone | DMUsage _ | DMDiagnostics true | DMStatistics ->
+		if ctx.com.display.dms_full_typing then begin
 				if fctx.is_macro && not ctx.in_macro then
 				if fctx.is_macro && not ctx.in_macro then
 					()
 					()
 				else begin
 				else begin
@@ -2142,17 +2140,18 @@ module ClassInitializer = struct
 					(* is_lib ? *)
 					(* is_lib ? *)
 					cctx.delayed_expr <- (ctx,Some r) :: cctx.delayed_expr;
 					cctx.delayed_expr <- (ctx,Some r) :: cctx.delayed_expr;
 				end
 				end
-			| DMDiagnostics false ->
+		end else begin
+			(*| DMDiagnostics false ->
 				handle_display_field()
 				handle_display_field()
-			| _ ->
-				if fctx.is_display_field then begin
-					handle_display_field()
-				end else begin
-					if not (is_full_type cf.cf_type) then begin
-						cctx.delayed_expr <- (ctx, None) :: cctx.delayed_expr;
-						cf.cf_type <- TLazy r;
-					end;
-				end
+			| _ ->*)
+			if fctx.is_display_field then begin
+				handle_display_field()
+			end else begin
+				if not (is_full_type cf.cf_type) then begin
+					cctx.delayed_expr <- (ctx, None) :: cctx.delayed_expr;
+					cf.cf_type <- TLazy r;
+				end;
+			end
 		end
 		end
 
 
 	let bind_var (ctx,cctx,fctx) cf e =
 	let bind_var (ctx,cctx,fctx) cf e =
@@ -2213,7 +2212,7 @@ module ClassInitializer = struct
 						| _ -> !analyzer_run_on_expr_ref ctx.com e
 						| _ -> !analyzer_run_on_expr_ref ctx.com e
 					in
 					in
 					let require_constant_expression e msg =
 					let require_constant_expression e msg =
-						if ctx.com.display <> DMNone then
+						if ctx.com.display.dms_display && ctx.com.display.dms_error_policy <> EPCollect then
 							e
 							e
 						else match Optimizer.make_constant_expression ctx (maybe_run_analyzer e) with
 						else match Optimizer.make_constant_expression ctx (maybe_run_analyzer e) with
 						| Some e -> e
 						| Some e -> e
@@ -2232,23 +2231,20 @@ module ClassInitializer = struct
 						(* disallow initialization of non-physical fields (issue #1958) *)
 						(* disallow initialization of non-physical fields (issue #1958) *)
 						display_error ctx "This field cannot be initialized because it is not a real variable" p; e
 						display_error ctx "This field cannot be initialized because it is not a real variable" p; e
 					| Var v when not fctx.is_static ->
 					| Var v when not fctx.is_static ->
-						let e = match ctx.com.display with
-							| DMNone ->
-								begin match Optimizer.make_constant_expression ctx (maybe_run_analyzer e) with
-									| Some e -> e
-									| None ->
-										let rec has_this e = match e.eexpr with
-											| TConst TThis ->
-												display_error ctx "Cannot access this or other member field in variable initialization" e.epos;
-											| TLocal v when (match ctx.vthis with Some v2 -> v == v2 | None -> false) ->
-												display_error ctx "Cannot access this or other member field in variable initialization" e.epos;
-											| _ ->
-											Type.iter has_this e
-										in
-										has_this e;
-										e
-								end
-							| _ ->
+						let e = if ctx.com.display.dms_display && ctx.com.display.dms_error_policy <> EPCollect then
+							e
+						else match Optimizer.make_constant_expression ctx (maybe_run_analyzer e) with
+							| Some e -> e
+							| None ->
+								let rec has_this e = match e.eexpr with
+									| TConst TThis ->
+										display_error ctx "Cannot access this or other member field in variable initialization" e.epos;
+									| TLocal v when (match ctx.vthis with Some v2 -> v == v2 | None -> false) ->
+										display_error ctx "Cannot access this or other member field in variable initialization" e.epos;
+									| _ ->
+									Type.iter has_this e
+								in
+								has_this e;
 								e
 								e
 						in
 						in
 						e
 						e
@@ -2609,7 +2605,7 @@ module ClassInitializer = struct
 			| _ -> tfun [] ret, TFun(["value",false,ret],ret)
 			| _ -> tfun [] ret, TFun(["value",false,ret],ret)
 		in
 		in
 		let check_method m t req_name =
 		let check_method m t req_name =
-			if ctx.com.display <> DMNone then () else
+			if ctx.com.display.dms_error_policy = EPIgnore then () else
 			try
 			try
 				let overloads =
 				let overloads =
 					(* on pf_overload platforms, the getter/setter may have been defined as an overloaded function; get all overloads *)
 					(* on pf_overload platforms, the getter/setter may have been defined as an overloaded function; get all overloads *)
@@ -2725,7 +2721,7 @@ module ClassInitializer = struct
 		let name = fst f.cff_name in
 		let name = fst f.cff_name in
 		check_global_metadata ctx (fun m -> f.cff_meta <- m :: f.cff_meta) c.cl_module.m_path c.cl_path (Some name);
 		check_global_metadata ctx (fun m -> f.cff_meta <- m :: f.cff_meta) c.cl_module.m_path c.cl_path (Some name);
 		let p = f.cff_pos in
 		let p = f.cff_pos in
-		if name.[0] = '$' && ctx.com.display = DMNone then error "Field names starting with a dollar are not allowed" p;
+		if name.[0] = '$' then display_error ctx "Field names starting with a dollar are not allowed" p;
 		List.iter (fun acc ->
 		List.iter (fun acc ->
 			match (acc, f.cff_kind) with
 			match (acc, f.cff_kind) with
 			| APublic, _ | APrivate, _ | AStatic, _ -> ()
 			| APublic, _ | APrivate, _ | AStatic, _ -> ()
@@ -2746,7 +2742,7 @@ module ClassInitializer = struct
 		let ctx,cctx = create_class_context ctx c context_init p in
 		let ctx,cctx = create_class_context ctx c context_init p in
 		let fields = patch_class ctx c fields in
 		let fields = patch_class ctx c fields in
 		let fields = build_fields (ctx,cctx) c fields in
 		let fields = build_fields (ctx,cctx) c fields in
-		if cctx.is_core_api && ctx.com.display = DMNone then delay ctx PForce (fun() -> init_core_api ctx c);
+		if cctx.is_core_api && ctx.com.display.dms_check_core_api then delay ctx PForce (fun() -> init_core_api ctx c);
 		if not cctx.is_lib then begin
 		if not cctx.is_lib then begin
 			(match c.cl_super with None -> () | Some _ -> delay_late ctx PForce (fun() -> check_overriding ctx c));
 			(match c.cl_super with None -> () | Some _ -> delay_late ctx PForce (fun() -> check_overriding ctx c));
 			if ctx.com.config.pf_overload then delay ctx PForce (fun() -> check_overloads ctx c)
 			if ctx.com.config.pf_overload then delay ctx PForce (fun() -> check_overloads ctx c)
@@ -2896,7 +2892,7 @@ let add_module ctx m p =
 	Hashtbl.add ctx.g.modules m.m_path m
 	Hashtbl.add ctx.g.modules m.m_path m
 
 
 let handle_path_display ctx path p =
 let handle_path_display ctx path p =
-	match Display.convert_import_to_something_usable !Parser.resume_display path,ctx.com.display with
+	match Display.convert_import_to_something_usable !Parser.resume_display path,ctx.com.display.dms_kind with
 		| (Display.IDKPackage sl,_),_ ->
 		| (Display.IDKPackage sl,_),_ ->
 			raise (Parser.TypePath(sl,None,true))
 			raise (Parser.TypePath(sl,None,true))
 		| (Display.IDKModule(sl,s),_),DMPosition ->
 		| (Display.IDKModule(sl,s),_),DMPosition ->
@@ -2934,7 +2930,7 @@ let init_module_type ctx context_init do_init (decl,p) =
 	let get_type name =
 	let get_type name =
 		try List.find (fun t -> snd (t_infos t).mt_path = name) ctx.m.curmod.m_types with Not_found -> assert false
 		try List.find (fun t -> snd (t_infos t).mt_path = name) ctx.m.curmod.m_types with Not_found -> assert false
 	in
 	in
-	let check_path_display path p = match ctx.com.display with
+	let check_path_display path p = match ctx.com.display.dms_kind with
 		(* We cannot use ctx.is_display_file because the import could come from an import.hx file. *)
 		(* We cannot use ctx.is_display_file because the import could come from an import.hx file. *)
 		| DMDiagnostics b when (b && not (ExtString.String.ends_with p.pfile "import.hx")) || Display.is_display_file p.pfile ->
 		| DMDiagnostics b when (b && not (ExtString.String.ends_with p.pfile "import.hx")) || Display.is_display_file p.pfile ->
 			Display.add_import_position ctx.com p path;
 			Display.add_import_position ctx.com p path;
@@ -3434,7 +3430,7 @@ let type_types_into_module ctx m tdecls p =
 			wildcard_packages = [];
 			wildcard_packages = [];
 			module_imports = [];
 			module_imports = [];
 		};
 		};
-		is_display_file = (match ctx.com.display with DMNone -> false | _ -> Display.is_display_file m.m_extra.m_file);
+		is_display_file = (ctx.com.display.dms_display && Display.is_display_file m.m_extra.m_file);
 		meta = [];
 		meta = [];
 		this_stack = [];
 		this_stack = [];
 		with_type_stack = [];
 		with_type_stack = [];
@@ -3513,7 +3509,7 @@ let type_module ctx mpath file ?(is_extern=false) tdecls p =
 	let tdecls = handle_import_hx ctx m tdecls p in
 	let tdecls = handle_import_hx ctx m tdecls p in
 	let ctx = type_types_into_module ctx m tdecls p in
 	let ctx = type_types_into_module ctx m tdecls p in
 	if is_extern then m.m_extra.m_kind <- MExtern;
 	if is_extern then m.m_extra.m_kind <- MExtern;
-	begin if ctx.is_display_file then match ctx.com.display with
+	begin if ctx.is_display_file then match ctx.com.display.dms_kind with
 		| DMDiagnostics false ->
 		| DMDiagnostics false ->
 			flush_pass ctx PBuildClass "diagnostics";
 			flush_pass ctx PBuildClass "diagnostics";
 			List.iter (fun mt -> match mt with
 			List.iter (fun mt -> match mt with
@@ -3878,7 +3874,7 @@ let rec build_generic ctx c p tl =
 			()
 			()
 	in
 	in
 	List.iter check_recursive tl;
 	List.iter check_recursive tl;
-	if !recurse || ctx.com.display <> DMNone then begin
+	if !recurse || not (ctx.com.display.dms_full_typing) then begin
 		TInst (c,tl) (* build a normal instance *)
 		TInst (c,tl) (* build a normal instance *)
 	end else begin
 	end else begin
 	let gctx = make_generic ctx c.cl_params tl p in
 	let gctx = make_generic ctx c.cl_params tl p in

+ 46 - 43
src/typing/typer.ml

@@ -18,8 +18,9 @@
  *)
  *)
 
 
 open Ast
 open Ast
-open Type
+open Common.DisplayMode
 open Common
 open Common
+open Type
 open Typecore
 open Typecore
 
 
 (* ---------------------------------------------------------------------- *)
 (* ---------------------------------------------------------------------- *)
@@ -836,7 +837,7 @@ let unify_field_call ctx fa el args ret p inline =
 		begin try
 		begin try
 			let el,tf,mk_call = attempt_call t cf in
 			let el,tf,mk_call = attempt_call t cf in
 			List.map fst el,tf,mk_call
 			List.map fst el,tf,mk_call
-		with Error _ when ctx.com.display <> DMNone ->
+		with Error _ when ctx.com.display.dms_error_policy = EPIgnore ->
 			fail_fun();
 			fail_fun();
 		end
 		end
 	| _ ->
 	| _ ->
@@ -1003,7 +1004,7 @@ let make_call ctx e params t p =
 
 
 let mk_array_get_call ctx (cf,tf,r,e1,e2o) c ebase p = match cf.cf_expr with
 let mk_array_get_call ctx (cf,tf,r,e1,e2o) c ebase p = match cf.cf_expr with
 	| None ->
 	| None ->
-		if not (Meta.has Meta.NoExpr cf.cf_meta) && ctx.com.display = DMNone then display_error ctx "Recursive array get method" p;
+		if not (Meta.has Meta.NoExpr cf.cf_meta) then display_error ctx "Recursive array get method" p;
 		mk (TArray(ebase,e1)) r p
 		mk (TArray(ebase,e1)) r p
 	| Some _ ->
 	| Some _ ->
 		let et = type_module_type ctx (TClassDecl c) None p in
 		let et = type_module_type ctx (TClassDecl c) None p in
@@ -1014,7 +1015,7 @@ let mk_array_set_call ctx (cf,tf,r,e1,e2o) c ebase p =
 	let evalue = match e2o with None -> assert false | Some e -> e in
 	let evalue = match e2o with None -> assert false | Some e -> e in
 	match cf.cf_expr with
 	match cf.cf_expr with
 		| None ->
 		| None ->
-			if not (Meta.has Meta.NoExpr cf.cf_meta) && ctx.com.display = DMNone then display_error ctx "Recursive array set method" p;
+			if not (Meta.has Meta.NoExpr cf.cf_meta) then display_error ctx "Recursive array set method" p;
 			let ea = mk (TArray(ebase,e1)) r p in
 			let ea = mk (TArray(ebase,e1)) r p in
 			mk (TBinop(OpAssign,ea,evalue)) r p
 			mk (TBinop(OpAssign,ea,evalue)) r p
 		| Some _ ->
 		| Some _ ->
@@ -1065,7 +1066,7 @@ let rec acc_get ctx g p =
 		let cmode = (match fmode with FStatic _ -> fmode | FInstance (c,tl,f) -> FClosure (Some (c,tl),f) | _ -> assert false) in
 		let cmode = (match fmode with FStatic _ -> fmode | FInstance (c,tl,f) -> FClosure (Some (c,tl),f) | _ -> assert false) in
 		ignore(follow f.cf_type); (* force computing *)
 		ignore(follow f.cf_type); (* force computing *)
 		(match f.cf_expr with
 		(match f.cf_expr with
-		| _ when ctx.com.display <> DMNone ->
+		| _ when ctx.com.display.dms_display ->
 			mk (TField (e,cmode)) t p
 			mk (TField (e,cmode)) t p
 		| None ->
 		| None ->
 			error "Recursive inline is not supported" p
 			error "Recursive inline is not supported" p
@@ -1367,7 +1368,7 @@ let rec type_ident_raise ctx i p mode =
 		| Some (params,e) ->
 		| Some (params,e) ->
 			let t = monomorphs params v.v_type in
 			let t = monomorphs params v.v_type in
 			(match e with
 			(match e with
-			| Some ({ eexpr = TFunction f } as e) when (match ctx.com.display with DMNone | DMDiagnostics _ -> true | _ -> false) ->
+			| Some ({ eexpr = TFunction f } as e) when ctx.com.display.dms_full_typing ->
 				begin match mode with
 				begin match mode with
 					| MSet -> error "Cannot set inline closure" p
 					| MSet -> error "Cannot set inline closure" p
 					| MGet -> error "Cannot create closure on inline closure" p
 					| MGet -> error "Cannot create closure on inline closure" p
@@ -2646,38 +2647,39 @@ and type_ident ctx i p mode =
 				AKExpr (mk (TLocal v) t p)
 				AKExpr (mk (TLocal v) t p)
 		end else begin
 		end else begin
 			if ctx.curfun = FunStatic && PMap.mem i ctx.curclass.cl_fields then error ("Cannot access " ^ i ^ " in static function") p;
 			if ctx.curfun = FunStatic && PMap.mem i ctx.curclass.cl_fields then error ("Cannot access " ^ i ^ " in static function") p;
-			let err = Unknown_ident i in
-			if ctx.in_display then raise (Error (err,p));
-			match ctx.com.display with
-				| DMNone ->
-					let e = try
-						let t = List.find (fun (i2,_) -> i2 = i) ctx.type_params in
-						let c = match follow (snd t) with TInst(c,_) -> c | _ -> assert false in
-						if Typeload.is_generic_parameter ctx c && Meta.has Meta.Const c.cl_meta then
-							AKExpr (type_module_type ctx (TClassDecl c) None p)
-						else begin
-							display_error ctx ("Type parameter " ^ i ^ " is only available at compilation and is not a runtime value") p;
-							AKExpr (mk (TConst TNull) t_dynamic p)
-						end
-					with Not_found ->
+			begin try
+				let t = List.find (fun (i2,_) -> i2 = i) ctx.type_params in
+				let c = match follow (snd t) with TInst(c,_) -> c | _ -> assert false in
+				if Typeload.is_generic_parameter ctx c && Meta.has Meta.Const c.cl_meta then
+					AKExpr (type_module_type ctx (TClassDecl c) None p)
+				else begin
+					display_error ctx ("Type parameter " ^ i ^ " is only available at compilation and is not a runtime value") p;
+					AKExpr (mk (TConst TNull) t_dynamic p)
+				end
+			with Not_found ->
+				let err = Unknown_ident i in
+				if ctx.in_display then begin
+					raise (Error (err,p))
+				end;
+				match ctx.com.display.dms_kind with
+					| DMNone ->
 						raise (Error(err,p))
 						raise (Error(err,p))
-					in
-					e
-				| DMDiagnostics b when b || ctx.is_display_file ->
-					let l = ToplevelCollecter.run ctx in
-					let cl = List.map (fun it ->
-						let s = IdentifierType.get_name it in
-						(s,it),StringError.levenshtein i s
-					) l in
-					let cl = List.sort (fun (_,c1) (_,c2) -> compare c1 c2) cl in
-					let cl = StringError.filter_similar (fun (s,_) r -> r > 0 && r <= (min (String.length s) (String.length i)) / 3) cl in
-					ctx.com.display_information.unresolved_identifiers <- (i,p,cl) :: ctx.com.display_information.unresolved_identifiers;
-					let t = mk_mono() in
-					AKExpr (mk (TLocal (add_local ctx i t p)) t p)
-				| _ ->
-					display_error ctx (error_msg err) p;
-					let t = mk_mono() in
-					AKExpr (mk (TLocal (add_local ctx i t p)) t p)
+					| DMDiagnostics b when b || ctx.is_display_file ->
+						let l = ToplevelCollecter.run ctx in
+						let cl = List.map (fun it ->
+							let s = IdentifierType.get_name it in
+							(s,it),StringError.levenshtein i s
+						) l in
+						let cl = List.sort (fun (_,c1) (_,c2) -> compare c1 c2) cl in
+						let cl = StringError.filter_similar (fun (s,_) r -> r > 0 && r <= (min (String.length s) (String.length i)) / 3) cl in
+						ctx.com.display_information.unresolved_identifiers <- (i,p,cl) :: ctx.com.display_information.unresolved_identifiers;
+						let t = mk_mono() in
+						AKExpr (mk (TLocal (add_local ctx i t p)) t p)
+					| _ ->
+						display_error ctx (error_msg err) p;
+						let t = mk_mono() in
+						AKExpr (mk (TLocal (add_local ctx i t p)) t p)
+			end
 		end
 		end
 
 
 (* MORDOR *)
 (* MORDOR *)
@@ -2895,7 +2897,7 @@ and type_vars ctx vl p =
 					let e = Codegen.AbstractCast.cast_or_unify ctx t e p in
 					let e = Codegen.AbstractCast.cast_or_unify ctx t e p in
 					Some e
 					Some e
 			) in
 			) in
-			if v.[0] = '$' && ctx.com.display = DMNone then error "Variables names starting with a dollar are not allowed" p;
+			if v.[0] = '$' then display_error ctx "Variables names starting with a dollar are not allowed" p;
 			let v = add_local ctx v t pv in
 			let v = add_local ctx v t pv in
 			v.v_meta <- (Meta.UserVariable,[],pv) :: v.v_meta;
 			v.v_meta <- (Meta.UserVariable,[],pv) :: v.v_meta;
 			if ctx.in_display && Display.is_display_position pv then
 			if ctx.in_display && Display.is_display_position pv then
@@ -3869,7 +3871,7 @@ and handle_display ctx e_ast iscall with_type =
 			let _, f = get_constructor ctx c params p in
 			let _, f = get_constructor ctx c params p in
 			f
 			f
 	in
 	in
-	match ctx.com.display with
+	match ctx.com.display.dms_kind with
 	| DMResolve _ | DMPackage ->
 	| DMResolve _ | DMPackage ->
 		assert false
 		assert false
 	| DMType ->
 	| DMType ->
@@ -4605,7 +4607,8 @@ let typing_timer ctx need_type f =
 	(*
 	(*
 		disable resumable errors... unless we are in display mode (we want to reach point of completion)
 		disable resumable errors... unless we are in display mode (we want to reach point of completion)
 	*)
 	*)
-	if ctx.com.display = DMNone then ctx.com.error <- (fun e p -> raise (Error(Custom e,p)));
+	(*if ctx.com.display = DMNone then ctx.com.error <- (fun e p -> raise (Error(Custom e,p)));*) (* TODO: review this... *)
+	ctx.com.error <- (fun e p -> raise (Error(Custom e,p)));
 	if need_type && ctx.pass < PTypeField then ctx.pass <- PTypeField;
 	if need_type && ctx.pass < PTypeField then ctx.pass <- PTypeField;
 	let exit() =
 	let exit() =
 		t();
 		t();
@@ -4992,7 +4995,7 @@ let get_macro_context ctx p =
 		ctx.com.get_macros <- (fun() -> Some com2);
 		ctx.com.get_macros <- (fun() -> Some com2);
 		com2.package_rules <- PMap.empty;
 		com2.package_rules <- PMap.empty;
 		com2.main_class <- None;
 		com2.main_class <- None;
-		com2.display <- DMNone;
+		com2.display <- DisplayMode.create DMNone;
 		List.iter (fun p -> com2.defines <- PMap.remove (platform_name p) com2.defines) platforms;
 		List.iter (fun p -> com2.defines <- PMap.remove (platform_name p) com2.defines) platforms;
 		com2.defines_signature <- None;
 		com2.defines_signature <- None;
 		com2.class_path <- List.filter (fun s -> not (ExtString.String.exists s "/_std/")) com2.class_path;
 		com2.class_path <- List.filter (fun s -> not (ExtString.String.exists s "/_std/")) com2.class_path;
@@ -5043,7 +5046,7 @@ let load_macro ctx display cpath f p =
 			| _ -> error "Macro should be called on a class" p
 			| _ -> error "Macro should be called on a class" p
 		) in
 		) in
 		let meth = (match follow meth.cf_type with TFun (args,ret) -> args,ret,cl,meth | _ -> error "Macro call should be a method" p) in
 		let meth = (match follow meth.cf_type with TFun (args,ret) -> args,ret,cl,meth | _ -> error "Macro call should be a method" p) in
-		mctx.com.display <- DMNone;
+		mctx.com.display <- DisplayMode.create DMNone;
 		if not ctx.in_macro then flush_macro_context mint ctx;
 		if not ctx.in_macro then flush_macro_context mint ctx;
 		Hashtbl.add mctx.com.cached_macros (cpath,f) meth;
 		Hashtbl.add mctx.com.cached_macros (cpath,f) meth;
 		mctx.m <- {
 		mctx.m <- {
@@ -5300,7 +5303,7 @@ let rec create com =
 			delayed = [];
 			delayed = [];
 			debug_delayed = [];
 			debug_delayed = [];
 			delayed_macros = DynArray.create();
 			delayed_macros = DynArray.create();
-			doinline = not (Common.defined com Define.NoInline || (match com.display with DMNone | DMDiagnostics _ -> false | _ -> true));
+			doinline = com.display.dms_inline && not (Common.defined com Define.NoInline);
 			hook_generate = [];
 			hook_generate = [];
 			get_build_infos = (fun() -> None);
 			get_build_infos = (fun() -> None);
 			std = null_module;
 			std = null_module;