Browse Source

[display] refactored display_position handling; fixes #8136 (#8137)

Alexander Kuzmenko 6 years ago
parent
commit
b30fd9fa83

+ 5 - 5
src/compiler/displayOutput.ml

@@ -503,7 +503,7 @@ module TypePathHandler = struct
 			(* This is a bit wacky: We want to reset the display position so that revisiting the display file
 			(* This is a bit wacky: We want to reset the display position so that revisiting the display file
 			   does not raise another TypePath exception. However, we still want to have it treated like the
 			   does not raise another TypePath exception. However, we still want to have it treated like the
 			   display file, so we just set the position to 0 (#6558). *)
 			   display file, so we just set the position to 0 (#6558). *)
-			DisplayPosition.display_position := {!DisplayPosition.display_position with pmin = 0; pmax = 0};
+			DisplayPosition.display_position#set {DisplayPosition.display_position#get with pmin = 0; pmax = 0};
 			let rec lookup p =
 			let rec lookup p =
 				try
 				try
 					TypeloadModule.load_module ctx (p,s_module) null_pos
 					TypeloadModule.load_module ctx (p,s_module) null_pos
@@ -666,7 +666,7 @@ let handle_display_argument com file_pos pre_compilation did_something =
 		com.display <- DisplayMode.create mode;
 		com.display <- DisplayMode.create mode;
 		Parser.display_mode := mode;
 		Parser.display_mode := mode;
 		if not com.display.dms_full_typing then Common.define_value com Define.Display (if smode <> "" then smode else "1");
 		if not com.display.dms_full_typing then Common.define_value com Define.Display (if smode <> "" then smode else "1");
-		DisplayPosition.display_position := {
+		DisplayPosition.display_position#set {
 			pfile = Path.unique_full_path file;
 			pfile = Path.unique_full_path file;
 			pmin = pos;
 			pmin = pos;
 			pmax = pos;
 			pmax = pos;
@@ -701,7 +701,7 @@ let process_display_file com classes =
 				classes := [];
 				classes := [];
 				com.main_class <- None;
 				com.main_class <- None;
 			end;
 			end;
-			let real = Path.get_real_path (!DisplayPosition.display_position).pfile in
+			let real = Path.get_real_path (DisplayPosition.display_position#get).pfile in
 			let path = match get_module_path_from_file_path com real with
 			let path = match get_module_path_from_file_path com real with
 			| Some path ->
 			| Some path ->
 				if com.display.dms_kind = DMPackage then raise_package (fst path);
 				if com.display.dms_kind = DMPackage then raise_package (fst path);
@@ -724,7 +724,7 @@ let process_global_display_mode com tctx = match com.display.dms_kind with
 	| DMDiagnostics global ->
 	| DMDiagnostics global ->
 		Diagnostics.run com global
 		Diagnostics.run com global
 	| DMStatistics ->
 	| DMStatistics ->
-		let stats = Statistics.collect_statistics tctx (SFFile !DisplayPosition.display_position.pfile) in
+		let stats = Statistics.collect_statistics tctx (SFFile (DisplayPosition.display_position#get).pfile) in
 		raise_statistics (Statistics.Printer.print_statistics stats)
 		raise_statistics (Statistics.Printer.print_statistics stats)
 	| DMModuleSymbols (Some "") -> ()
 	| DMModuleSymbols (Some "") -> ()
 	| DMModuleSymbols filter ->
 	| DMModuleSymbols filter ->
@@ -733,7 +733,7 @@ let process_global_display_mode com tctx = match com.display.dms_kind with
 			| Some cs ->
 			| Some cs ->
 				let l = CompilationServer.get_context_files cs ((Define.get_signature com.defines) :: (match com.get_macros() with None -> [] | Some com -> [Define.get_signature com.defines])) in
 				let l = CompilationServer.get_context_files cs ((Define.get_signature com.defines) :: (match com.get_macros() with None -> [] | Some com -> [Define.get_signature com.defines])) in
 				List.fold_left (fun acc (file,cfile) ->
 				List.fold_left (fun acc (file,cfile) ->
-					if (filter <> None || DisplayPosition.is_display_file file) then
+					if (filter <> None || DisplayPosition.display_position#is_in_file file) then
 						(file,DocumentSymbols.collect_module_symbols (filter = None) (cfile.c_package,cfile.c_decls)) :: acc
 						(file,DocumentSymbols.collect_module_symbols (filter = None) (cfile.c_package,cfile.c_decls)) :: acc
 					else
 					else
 						acc
 						acc

+ 9 - 9
src/compiler/main.ml

@@ -814,12 +814,12 @@ try
 	end;
 	end;
 	Lexer.old_format := Common.defined com Define.OldErrorFormat;
 	Lexer.old_format := Common.defined com Define.OldErrorFormat;
 	if !Lexer.old_format && !Parser.in_display then begin
 	if !Lexer.old_format && !Parser.in_display then begin
-		let p = !DisplayPosition.display_position in
+		let p = DisplayPosition.display_position#get in
 		(* convert byte position to utf8 position *)
 		(* convert byte position to utf8 position *)
 		try
 		try
 			let content = Std.input_file ~bin:true (Path.get_real_path p.pfile) in
 			let content = Std.input_file ~bin:true (Path.get_real_path p.pfile) in
 			let pos = UTF8.length (String.sub content 0 p.pmin) in
 			let pos = UTF8.length (String.sub content 0 p.pmin) in
-			DisplayPosition.display_position := { p with pmin = pos; pmax = pos }
+			DisplayPosition.display_position#set { p with pmin = pos; pmax = pos }
 		with _ ->
 		with _ ->
 			() (* ignore *)
 			() (* ignore *)
 	end;
 	end;
@@ -1004,7 +1004,7 @@ with
 		message ctx (CMInfo(msg,null_pos))
 		message ctx (CMInfo(msg,null_pos))
 	| DisplayException(DisplayHover _ | DisplayPosition _ | DisplayFields _ | DisplayPackage _  | DisplaySignatures _ as de) when ctx.com.json_out <> None ->
 	| DisplayException(DisplayHover _ | DisplayPosition _ | DisplayFields _ | DisplayPackage _  | DisplaySignatures _ as de) when ctx.com.json_out <> None ->
 		begin
 		begin
-			DisplayPosition.display_position := null_pos;
+			DisplayPosition.display_position#reset;
 			match ctx.com.json_out with
 			match ctx.com.json_out with
 			| Some (f,_) ->
 			| Some (f,_) ->
 				let ctx = DisplayJson.create_json_context (match de with DisplayFields _ -> true | _ -> false) in
 				let ctx = DisplayJson.create_json_context (match de with DisplayFields _ -> true | _ -> false) in
@@ -1021,10 +1021,10 @@ with
 		| _ -> assert false
 		| _ -> assert false
 		end *)
 		end *)
 	| DisplayException(DisplayPackage pack) ->
 	| DisplayException(DisplayPackage pack) ->
-		DisplayPosition.display_position := null_pos;
+		DisplayPosition.display_position#reset;
 		raise (DisplayOutput.Completion (String.concat "." pack))
 		raise (DisplayOutput.Completion (String.concat "." pack))
 	| DisplayException(DisplayFields(fields,cr,_)) ->
 	| DisplayException(DisplayFields(fields,cr,_)) ->
-		DisplayPosition.display_position := null_pos;
+		DisplayPosition.display_position#reset;
 		let fields = if !measure_times then begin
 		let fields = if !measure_times then begin
 			Timer.close_times();
 			Timer.close_times();
 			(List.map (fun (name,value) ->
 			(List.map (fun (name,value) ->
@@ -1054,17 +1054,17 @@ with
 		in
 		in
 		raise (DisplayOutput.Completion s)
 		raise (DisplayOutput.Completion s)
 	| DisplayException(DisplayHover ({hitem = {CompletionItem.ci_type = Some (t,_)}} as hover)) ->
 	| DisplayException(DisplayHover ({hitem = {CompletionItem.ci_type = Some (t,_)}} as hover)) ->
-		DisplayPosition.display_position := null_pos;
+		DisplayPosition.display_position#reset;
 		let doc = CompletionItem.get_documentation hover.hitem in
 		let doc = CompletionItem.get_documentation hover.hitem in
 		raise (DisplayOutput.Completion (DisplayOutput.print_type t hover.hpos doc))
 		raise (DisplayOutput.Completion (DisplayOutput.print_type t hover.hpos doc))
 	| DisplayException(DisplaySignatures(signatures,_,display_arg,_)) ->
 	| DisplayException(DisplaySignatures(signatures,_,display_arg,_)) ->
-		DisplayPosition.display_position := null_pos;
+		DisplayPosition.display_position#reset;
 		if ctx.com.display.dms_kind = DMSignature then
 		if ctx.com.display.dms_kind = DMSignature then
 			raise (DisplayOutput.Completion (DisplayOutput.print_signature signatures display_arg))
 			raise (DisplayOutput.Completion (DisplayOutput.print_signature signatures display_arg))
 		else
 		else
 			raise (DisplayOutput.Completion (DisplayOutput.print_signatures signatures))
 			raise (DisplayOutput.Completion (DisplayOutput.print_signatures signatures))
 	| DisplayException(DisplayPosition pl) ->
 	| DisplayException(DisplayPosition pl) ->
-		DisplayPosition.display_position := null_pos;
+		DisplayPosition.display_position#reset;
 		raise (DisplayOutput.Completion (DisplayOutput.print_positions pl))
 		raise (DisplayOutput.Completion (DisplayOutput.print_positions pl))
 	| Parser.TypePath (p,c,is_import,pos) ->
 	| Parser.TypePath (p,c,is_import,pos) ->
 		let fields =
 		let fields =
@@ -1096,7 +1096,7 @@ with
 		DisplayOutput.handle_syntax_completion com kind pos;
 		DisplayOutput.handle_syntax_completion com kind pos;
 		error ctx ("Error: No completion point was found") null_pos
 		error ctx ("Error: No completion point was found") null_pos
 	| DisplayException(ModuleSymbols s | Diagnostics s | Statistics s | Metadata s) ->
 	| DisplayException(ModuleSymbols s | Diagnostics s | Statistics s | Metadata s) ->
-		DisplayPosition.display_position := null_pos;
+		DisplayPosition.display_position#reset;
 		raise (DisplayOutput.Completion s)
 		raise (DisplayOutput.Completion s)
 	| EvalExceptions.Sys_exit i | Hlinterp.Sys_exit i ->
 	| EvalExceptions.Sys_exit i | Hlinterp.Sys_exit i ->
 		ctx.flush();
 		ctx.flush();

+ 3 - 3
src/compiler/server.ml

@@ -132,7 +132,7 @@ let rec wait_loop process_params verbose accept =
 	let current_stdin = ref None in
 	let current_stdin = ref None in
 	TypeloadParse.parse_hook := (fun com2 file p ->
 	TypeloadParse.parse_hook := (fun com2 file p ->
 		let ffile = Path.unique_full_path file in
 		let ffile = Path.unique_full_path file in
-		let is_display_file = ffile = (!DisplayPosition.display_position).pfile in
+		let is_display_file = ffile = (DisplayPosition.display_position#get).pfile in
 
 
 		match is_display_file, !current_stdin with
 		match is_display_file, !current_stdin with
 		| true, Some stdin when Common.defined com2 Define.DisplayStdin ->
 		| true, Some stdin when Common.defined com2 Define.DisplayStdin ->
@@ -436,11 +436,11 @@ let rec wait_loop process_params verbose accept =
 				let sign = Define.get_signature ctx.com.defines in
 				let sign = Define.get_signature ctx.com.defines in
 				ServerMessage.defines ctx.com "";
 				ServerMessage.defines ctx.com "";
 				ServerMessage.signature ctx.com "" sign;
 				ServerMessage.signature ctx.com "" sign;
-				ServerMessage.display_position ctx.com "" (!DisplayPosition.display_position);
+				ServerMessage.display_position ctx.com "" (DisplayPosition.display_position#get);
 				(* Special case for diagnostics: It's not treated as a display mode, but we still want to invalidate the
 				(* Special case for diagnostics: It's not treated as a display mode, but we still want to invalidate the
 				   current file in order to run diagnostics on it again. *)
 				   current file in order to run diagnostics on it again. *)
 				if ctx.com.display.dms_display || (match ctx.com.display.dms_kind with DMDiagnostics _ -> true | _ -> false) then begin
 				if ctx.com.display.dms_display || (match ctx.com.display.dms_kind with DMDiagnostics _ -> true | _ -> false) then begin
-					let file = (!DisplayPosition.display_position).pfile in
+					let file = (DisplayPosition.display_position#get).pfile in
 					let fkey = (file,sign) in
 					let fkey = (file,sign) in
 					(* force parsing again : if the completion point have been changed *)
 					(* force parsing again : if the completion point have been changed *)
 					CompilationServer.remove_file cs fkey;
 					CompilationServer.remove_file cs fkey;

+ 3 - 3
src/context/display/diagnostics.ml

@@ -105,7 +105,7 @@ let prepare com global =
 		com = com;
 		com = com;
 	} in
 	} in
 	List.iter (function
 	List.iter (function
-		| TClassDecl c when global || DisplayPosition.is_display_file c.cl_pos.pfile ->
+		| TClassDecl c when global || DisplayPosition.display_position#is_in_file c.cl_pos.pfile ->
 			List.iter (prepare_field dctx) c.cl_ordered_fields;
 			List.iter (prepare_field dctx) c.cl_ordered_fields;
 			List.iter (prepare_field dctx) c.cl_ordered_statics;
 			List.iter (prepare_field dctx) c.cl_ordered_statics;
 			(match c.cl_constructor with None -> () | Some cf -> prepare_field dctx cf);
 			(match c.cl_constructor with None -> () | Some cf -> prepare_field dctx cf);
@@ -116,7 +116,7 @@ let prepare com global =
 
 
 let is_diagnostics_run p = match (!Parser.display_mode) with
 let is_diagnostics_run p = match (!Parser.display_mode) with
 	| DMDiagnostics true -> true
 	| DMDiagnostics true -> true
-	| DMDiagnostics false -> DisplayPosition.is_display_file p.pfile
+	| DMDiagnostics false -> DisplayPosition.display_position#is_in_file p.pfile
 	| _ -> false
 	| _ -> false
 
 
 let secure_generated_code ctx e =
 let secure_generated_code ctx e =
@@ -158,7 +158,7 @@ module Printer = struct
 				Hashtbl.add diag p (dk,p,sev,args)
 				Hashtbl.add diag p (dk,p,sev,args)
 		in
 		in
 		let add dk p sev args =
 		let add dk p sev args =
-			if global || p = null_pos || DisplayPosition.is_display_file p.pfile then add dk p sev args
+			if global || p = null_pos || DisplayPosition.display_position#is_in_file p.pfile then add dk p sev args
 		in
 		in
 		List.iter (fun (s,p,suggestions) ->
 		List.iter (fun (s,p,suggestions) ->
 			let suggestions = ExtList.List.filter_map (fun (s,item,r) ->
 			let suggestions = ExtList.List.filter_map (fun (s,item,r) ->

+ 5 - 5
src/context/display/display.ml

@@ -19,7 +19,7 @@ end
 module ExprPreprocessing = struct
 module ExprPreprocessing = struct
 	let find_before_pos dm e =
 	let find_before_pos dm e =
 
 
-		let display_pos = ref (!DisplayPosition.display_position) in
+		let display_pos = ref (DisplayPosition.display_position#get) in
 		let was_annotated = ref false in
 		let was_annotated = ref false in
 		let is_annotated,is_completion = match dm with
 		let is_annotated,is_completion = match dm with
 			| DMDefault -> (fun p -> not !was_annotated && encloses_position !display_pos p),true
 			| DMDefault -> (fun p -> not !was_annotated && encloses_position !display_pos p),true
@@ -33,7 +33,7 @@ module ExprPreprocessing = struct
 		let annotate_marked e = annotate e DKMarked in
 		let annotate_marked e = annotate e DKMarked in
 		let mk_null p = annotate_marked ((EConst(Ident "null")),p) in
 		let mk_null p = annotate_marked ((EConst(Ident "null")),p) in
 		let loop_el el =
 		let loop_el el =
-			let pr = !DisplayPosition.display_position in
+			let pr = DisplayPosition.display_position#get in
 			let rec loop el = match el with
 			let rec loop el = match el with
 				| [] -> [mk_null pr]
 				| [] -> [mk_null pr]
 				| e :: el ->
 				| e :: el ->
@@ -113,7 +113,7 @@ module ExprPreprocessing = struct
 				let el = loop_el el in
 				let el = loop_el el in
 				ECall(e1,el),(pos e)
 				ECall(e1,el),(pos e)
 			| ENew((tp,pp),el) when is_annotated (pos e) && is_completion ->
 			| ENew((tp,pp),el) when is_annotated (pos e) && is_completion ->
-				if is_annotated pp || pp.pmax >= !DisplayPosition.display_position.pmax then
+				if is_annotated pp || pp.pmax >= (DisplayPosition.display_position#get).pmax then
 					annotate_marked e
 					annotate_marked e
 				else begin
 				else begin
 					let el = loop_el el in
 					let el = loop_el el in
@@ -180,9 +180,9 @@ module ExprPreprocessing = struct
 				e
 				e
 		in
 		in
 		let loop e = match fst e with
 		let loop e = match fst e with
-			| ECall(_,el) | ENew(_,el) when not !found && encloses_display_position (pos e) ->
+			| ECall(_,el) | ENew(_,el) when not !found && display_position#enclosed_in (pos e) ->
 				handle_el e el
 				handle_el e el
-			| EArray(e1,e2) when not !found && encloses_display_position (pos e2) ->
+			| EArray(e1,e2) when not !found && display_position#enclosed_in (pos e2) ->
 				handle_el e [e2]
 				handle_el e [e2]
 			| EDisplay(_,DKCall) ->
 			| EDisplay(_,DKCall) ->
 				raise Exit
 				raise Exit

+ 5 - 5
src/context/display/displayEmitter.ml

@@ -180,7 +180,7 @@ let check_display_type ctx t p =
 		md.m_type_hints <- (p,t) :: md.m_type_hints;
 		md.m_type_hints <- (p,t) :: md.m_type_hints;
 	in
 	in
 	let maybe_display_type () =
 	let maybe_display_type () =
-		if ctx.is_display_file && encloses_display_position p then
+		if ctx.is_display_file && display_position#enclosed_in p then
 			display_type ctx t p
 			display_type ctx t p
 	in
 	in
 	add_type_hint();
 	add_type_hint();
@@ -239,7 +239,7 @@ let display_field ctx origin scope cf p = match ctx.com.display.dms_kind with
 	| _ -> ()
 	| _ -> ()
 
 
 let maybe_display_field ctx origin scope cf p =
 let maybe_display_field ctx origin scope cf p =
-	if encloses_display_position p then display_field ctx origin scope cf p
+	if display_position#enclosed_in p then display_field ctx origin scope cf p
 
 
 let display_enum_field ctx en ef p = match ctx.com.display.dms_kind with
 let display_enum_field ctx en ef p = match ctx.com.display.dms_kind with
 	| DMDefinition -> raise_position [ef.ef_name_pos]
 	| DMDefinition -> raise_position [ef.ef_name_pos]
@@ -271,9 +271,9 @@ let display_meta com meta p = match com.display.dms_kind with
 
 
 let check_display_metadata ctx meta =
 let check_display_metadata ctx meta =
 	List.iter (fun (meta,args,p) ->
 	List.iter (fun (meta,args,p) ->
-		if encloses_display_position p then display_meta ctx.com meta p;
+		if display_position#enclosed_in p then display_meta ctx.com meta p;
 		List.iter (fun e ->
 		List.iter (fun e ->
-			if encloses_display_position (pos e) then begin
+			if display_position#enclosed_in (pos e) then begin
 				let e = ExprPreprocessing.process_expr ctx.com e in
 				let e = ExprPreprocessing.process_expr ctx.com e in
 				delay ctx PTypeField (fun _ -> ignore(type_expr ctx e WithType.value));
 				delay ctx PTypeField (fun _ -> ignore(type_expr ctx e WithType.value));
 			end
 			end
@@ -282,7 +282,7 @@ let check_display_metadata ctx meta =
 
 
 let check_field_modifiers ctx c cf override display_modifier =
 let check_field_modifiers ctx c cf override display_modifier =
 	match override,display_modifier with
 	match override,display_modifier with
-		| Some p,_ when encloses_display_position p && ctx.com.display.dms_kind = DMDefinition ->
+		| Some p,_ when display_position#enclosed_in p && ctx.com.display.dms_kind = DMDefinition ->
 			begin match c.cl_super with
 			begin match c.cl_super with
 			| Some(c,tl) ->
 			| Some(c,tl) ->
 				let _,_,cf = raw_class_field (fun cf -> cf.cf_type) c tl cf.cf_name in
 				let _,_,cf = raw_class_field (fun cf -> cf.cf_type) c tl cf.cf_name in

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

@@ -66,7 +66,7 @@ class display_handler (jsonrpc : jsonrpc_handler) com cs = object(self)
 			Some s
 			Some s
 		) None;
 		) None;
 		Parser.was_auto_triggered := was_auto_triggered;
 		Parser.was_auto_triggered := was_auto_triggered;
-		DisplayPosition.display_position := {
+		DisplayPosition.display_position#set {
 			pfile = file;
 			pfile = file;
 			pmin = pos;
 			pmin = pos;
 			pmax = pos;
 			pmax = pos;

+ 45 - 9
src/core/display/displayPosition.ml

@@ -1,15 +1,51 @@
 open Globals
 open Globals
 
 
-let display_position = ref null_pos
-
-let is_display_file file =
-	file <> "?" && Path.unique_full_path file = !display_position.pfile
-
 let encloses_position p_target p =
 let encloses_position p_target p =
-	p.pmin <> -1 && p.pmax <> -1 && p.pmin <= p_target.pmin && p.pmax >= p_target.pmax
+	p_target.pmin <> -1 && p_target.pmax <> -1 && p.pmin <= p_target.pmin && p.pmax >= p_target.pmax
 
 
 let encloses_position_gt p_target p =
 let encloses_position_gt p_target p =
-	p.pmin <= p_target.pmin && p.pmax > p_target.pmax
+	p_target.pmin <> -1 && p_target.pmax <> -1 && p.pmin <= p_target.pmin && p.pmax > p_target.pmax
+
+class display_position_container =
+	object (self)
+		(** Current display position *)
+		val mutable pos = null_pos
+		(**
+			Display position value which was set with the latest `display_position#set p` call.
+			Kept even after `display_position#reset` call.
+		*)
+		val mutable last_pos = null_pos
+		(**
+			Set current display position
+		*)
+		method set p =
+			pos <- p;
+			last_pos <- p
+		(**
+			Get current display position
+		*)
+		method get =
+			pos
+		(**
+			Clears current display position.
+		*)
+		method reset =
+			pos <- null_pos
+		(**
+			Check if `p` contains current display position
+		*)
+		method enclosed_in p =
+			encloses_position pos p
+		(**
+			Check if `file` contains current display position
+		*)
+		method is_in_file file =
+			file <> "?" && Path.unique_full_path file = pos.pfile
+		(**
+			Cut `p` at the position of the latest `display_position#set pos` call.
+		*)
+		method cut p =
+			{ p with pmax = last_pos.pmax }
+	end
 
 
-let encloses_display_position p =
-	encloses_position !display_position p
+let display_position = new display_position_container

+ 3 - 3
src/macro/eval/evalDebugSocket.ml

@@ -440,15 +440,15 @@ module ValueCompletion = struct
 	let get_completion ctx text column env =
 	let get_completion ctx text column env =
 		let p = { pmin = 0; pmax = 0; pfile = "" } in
 		let p = { pmin = 0; pmax = 0; pfile = "" } in
 		let save =
 		let save =
-			let old = !Parser.display_mode,!DisplayPosition.display_position in
+			let old = !Parser.display_mode,DisplayPosition.display_position#get in
 			(fun () ->
 			(fun () ->
 				Parser.display_mode := fst old;
 				Parser.display_mode := fst old;
-				DisplayPosition.display_position := snd old;
+				DisplayPosition.display_position#set (snd old);
 			)
 			)
 		in
 		in
 		Parser.display_mode := DMDefault;
 		Parser.display_mode := DMDefault;
 		let offset = column + (String.length "class X{static function main() ") - 1 (* this is retarded *) in
 		let offset = column + (String.length "class X{static function main() ") - 1 (* this is retarded *) in
-		DisplayPosition.display_position := {p with pmin = offset; pmax = offset};
+		DisplayPosition.display_position#set {p with pmin = offset; pmax = offset};
 		begin try
 		begin try
 			let e = parse_expr ctx text p in
 			let e = parse_expr ctx text p in
 			let e = Display.ExprPreprocessing.find_before_pos DMDefault e in
 			let e = Display.ExprPreprocessing.find_before_pos DMDefault e in

+ 1 - 1
src/macro/macroApi.ml

@@ -1818,7 +1818,7 @@ let macro_api ccom get_api =
 			vnull
 			vnull
 		);
 		);
 		"get_display_pos", vfun0 (fun() ->
 		"get_display_pos", vfun0 (fun() ->
-			let p = !DisplayPosition.display_position in
+			let p = DisplayPosition.display_position#get in
 			if p = Globals.null_pos then
 			if p = Globals.null_pos then
 				vnull
 				vnull
 			else
 			else

+ 5 - 5
src/optimization/optimizer.ml

@@ -645,7 +645,7 @@ let optimize_completion_expr e args =
 			let el = List.fold_left (fun acc e ->
 			let el = List.fold_left (fun acc e ->
 				typing_side_effect := false;
 				typing_side_effect := false;
 				let e = loop e in
 				let e = loop e in
-				if !typing_side_effect || DisplayPosition.encloses_display_position (pos e) then begin told := true; e :: acc end else acc
+				if !typing_side_effect || DisplayPosition.display_position#enclosed_in (pos e) then begin told := true; e :: acc end else acc
 			) [] el in
 			) [] el in
 			old();
 			old();
 			typing_side_effect := !told;
 			typing_side_effect := !told;
@@ -696,11 +696,11 @@ let optimize_completion_expr e args =
 		| EReturn _ ->
 		| EReturn _ ->
 			typing_side_effect := true;
 			typing_side_effect := true;
 			map e
 			map e
-		| ESwitch (e1,cases,def) when DisplayPosition.encloses_display_position p ->
+		| ESwitch (e1,cases,def) when DisplayPosition.display_position#enclosed_in p ->
 			let e1 = loop e1 in
 			let e1 = loop e1 in
 			hunt_idents e1;
 			hunt_idents e1;
 			(* Prune all cases that aren't our display case *)
 			(* Prune all cases that aren't our display case *)
-			let cases = List.filter (fun (_,_,_,p) -> DisplayPosition.encloses_display_position p) cases in
+			let cases = List.filter (fun (_,_,_,p) -> DisplayPosition.display_position#enclosed_in p) cases in
 			(* Don't throw away the switch subject when we optimize in a case expression because we might need it *)
 			(* Don't throw away the switch subject when we optimize in a case expression because we might need it *)
 			let cases = List.map (fun (el,eg,eo,p) ->
 			let cases = List.map (fun (el,eg,eo,p) ->
 				List.iter hunt_idents el;
 				List.iter hunt_idents el;
@@ -741,10 +741,10 @@ let optimize_completion_expr e args =
 				(n,pn), (t,pt), e, p
 				(n,pn), (t,pt), e, p
 			) cl in
 			) cl in
 			(ETry (et,cl),p)
 			(ETry (et,cl),p)
-		| ECall(e1,el) when DisplayPosition.encloses_display_position p ->
+		| ECall(e1,el) when DisplayPosition.display_position#enclosed_in p ->
 			let e1 = loop e1 in
 			let e1 = loop e1 in
 			let el = List.map (fun e ->
 			let el = List.map (fun e ->
-				if DisplayPosition.encloses_display_position (pos e) then
+				if DisplayPosition.display_position#enclosed_in (pos e) then
 					(try loop e with Return e -> e)
 					(try loop e with Return e -> e)
 				else
 				else
 					(EConst (Ident "null"),(pos e))
 					(EConst (Ident "null"),(pos e))

+ 3 - 3
src/syntax/grammar.mly

@@ -186,7 +186,7 @@ and parse_type_decl mode s =
 		| [< n , p1 = parse_class_flags; name = type_name; tl = parse_constraint_params >] ->
 		| [< n , p1 = parse_class_flags; name = type_name; tl = parse_constraint_params >] ->
 			let rec loop had_display p0 acc =
 			let rec loop had_display p0 acc =
 				let check_display p1 =
 				let check_display p1 =
-					if not had_display && !in_display_file && encloses_display_position p1 then syntax_completion (if List.mem HInterface n then SCInterfaceRelation else SCClassRelation) p0
+					if not had_display && !in_display_file && display_position#enclosed_in p1 then syntax_completion (if List.mem HInterface n then SCInterfaceRelation else SCClassRelation) p0
 				in
 				in
 				match s with parser
 				match s with parser
 				| [< '(Kwd Extends,p1); t,b = parse_type_path_or_resume p1 >] ->
 				| [< '(Kwd Extends,p1); t,b = parse_type_path_or_resume p1 >] ->
@@ -313,7 +313,7 @@ and parse_using s p1 =
 
 
 and parse_abstract_relations s =
 and parse_abstract_relations s =
 	let check_display p1 (ct,p2) =
 	let check_display p1 (ct,p2) =
-		if !in_display_file && p1.pmax < !display_position.pmin && p2.pmin >= !display_position.pmax then
+		if !in_display_file && p1.pmax < (display_position#get).pmin && p2.pmin >= (display_position#get).pmax then
 			(* This means we skipped the display position between the to/from and the type-hint we parsed.
 			(* This means we skipped the display position between the to/from and the type-hint we parsed.
 			   Very weird case, it was probably a {} like in #7137. Let's discard it and use magic. *)
 			   Very weird case, it was probably a {} like in #7137. Let's discard it and use magic. *)
 			((CTPath magic_type_path,p2))
 			((CTPath magic_type_path,p2))
@@ -904,7 +904,7 @@ and parse_constraint_param s =
 and parse_type_path_or_resume p1 s =
 and parse_type_path_or_resume p1 s =
 	let pnext = next_pos s in
 	let pnext = next_pos s in
 	let check_resume exc =
 	let check_resume exc =
-		if !in_display_file && encloses_display_position (punion p1 pnext) then
+		if !in_display_file && display_position#enclosed_in (punion p1 pnext) then
 			(magic_type_path,punion_next p1 s),true
 			(magic_type_path,punion_next p1 s),true
 		else
 		else
 			raise exc
 			raise exc

+ 9 - 9
src/syntax/parser.ml

@@ -140,7 +140,7 @@ let reset_state () =
 	in_display := false;
 	in_display := false;
 	was_auto_triggered := false;
 	was_auto_triggered := false;
 	display_mode := DMNone;
 	display_mode := DMNone;
-	display_position := null_pos;
+	display_position#reset;
 	in_macro := false;
 	in_macro := false;
 	had_resume := false;
 	had_resume := false;
 	code_ref := Sedlexing.Utf8.from_string "";
 	code_ref := Sedlexing.Utf8.from_string "";
@@ -193,11 +193,11 @@ let type_path sl in_import p = match sl with
 
 
 let would_skip_display_position p1 s =
 let would_skip_display_position p1 s =
 	if !in_display_file then match Stream.npeek 1 s with
 	if !in_display_file then match Stream.npeek 1 s with
-		| [ (_,p2) ] -> encloses_display_position (punion p1 p2)
+		| [ (_,p2) ] -> display_position#enclosed_in (punion p1 p2)
 		| _ -> false
 		| _ -> false
 	else false
 	else false
 
 
-let cut_pos_at_display p = { p with pmax = !display_position.pmax }
+let cut_pos_at_display p = display_position#cut p
 
 
 let is_dollar_ident e = match fst e with
 let is_dollar_ident e = match fst e with
 	| EConst (Ident n) when starts_with n '$' ->
 	| EConst (Ident n) when starts_with n '$' ->
@@ -293,7 +293,7 @@ let is_signature_display () =
 	!display_mode = DMSignature
 	!display_mode = DMSignature
 
 
 let check_resume p fyes fno =
 let check_resume p fyes fno =
-	if is_completion () && !in_display_file && p.pmax = !display_position.pmin then begin
+	if is_completion () && !in_display_file && p.pmax = (display_position#get).pmin then begin
 		had_resume := true;
 		had_resume := true;
 		fyes()
 		fyes()
 	end else
 	end else
@@ -302,7 +302,7 @@ let check_resume p fyes fno =
 let check_resume_range p s fyes fno =
 let check_resume_range p s fyes fno =
 	if is_completion () && !in_display_file then begin
 	if is_completion () && !in_display_file then begin
 		let pnext = next_pos s in
 		let pnext = next_pos s in
-		if p.pmin < !display_position.pmin && pnext.pmin >= !display_position.pmax then
+		if p.pmin < (display_position#get).pmin && pnext.pmin >= (display_position#get).pmax then
 			fyes pnext
 			fyes pnext
 		else
 		else
 			fno()
 			fno()
@@ -334,8 +334,8 @@ let check_type_decl_completion mode pmax s =
 			| Some tk -> (pos tk).pmin
 			| Some tk -> (pos tk).pmin
 		in
 		in
 		(* print_endline (Printf.sprintf "(%i <= %i) (%i >= %i)" pmax !display_position.pmin pmin !display_position.pmax); *)
 		(* print_endline (Printf.sprintf "(%i <= %i) (%i >= %i)" pmax !display_position.pmin pmin !display_position.pmax); *)
-		if pmax <= !display_position.pmin && pmin >= !display_position.pmax then
-			delay_syntax_completion (SCTypeDecl mode) !display_position
+		if pmax <= (display_position#get).pmin && pmin >= (display_position#get).pmax then
+			delay_syntax_completion (SCTypeDecl mode) display_position#get
 	end
 	end
 
 
 let check_signature_mark e p1 p2 =
 let check_signature_mark e p1 p2 =
@@ -343,10 +343,10 @@ let check_signature_mark e p1 p2 =
 	else begin
 	else begin
 		let p = punion p1 p2 in
 		let p = punion p1 p2 in
 		if true || not !was_auto_triggered then begin (* TODO: #6383 *)
 		if true || not !was_auto_triggered then begin (* TODO: #6383 *)
-			if encloses_position_gt !display_position p then (mk_display_expr e DKMarked)
+			if encloses_position_gt display_position#get p then (mk_display_expr e DKMarked)
 			else e
 			else e
 		end else begin
 		end else begin
-			if !display_position.pmin = p1.pmax then (mk_display_expr e DKMarked)
+			if (display_position#get).pmin = p1.pmax then (mk_display_expr e DKMarked)
 			else e
 			else e
 		end
 		end
 	end
 	end

+ 6 - 6
src/syntax/parserEntry.ml

@@ -88,8 +88,8 @@ let parse ctx code file =
 	let old_code = !code_ref in
 	let old_code = !code_ref in
 	let old_macro = !in_macro in
 	let old_macro = !in_macro in
 	code_ref := code;
 	code_ref := code;
-	in_display := !display_position <> null_pos;
-	in_display_file := !in_display && Path.unique_full_path file = !display_position.pfile;
+	in_display := display_position#get <> null_pos;
+	in_display_file := !in_display && Path.unique_full_path file = (display_position#get).pfile;
 	syntax_errors := [];
 	syntax_errors := [];
 	let restore =
 	let restore =
 		(fun () ->
 		(fun () ->
@@ -117,7 +117,7 @@ let parse ctx code file =
 			if l > 0 && s.[0] = '*' then last_doc := Some (String.sub s 1 (l - (if l > 1 && s.[l-1] = '*' then 2 else 1)), (snd tk).pmin);
 			if l > 0 && s.[0] = '*' then last_doc := Some (String.sub s 1 (l - (if l > 1 && s.[l-1] = '*' then 2 else 1)), (snd tk).pmin);
 			tk
 			tk
 		| CommentLine s ->
 		| CommentLine s ->
-			if !in_display_file && encloses_display_position (pos tk) then syntax_completion SCComment (pos tk);
+			if !in_display_file && display_position#enclosed_in (pos tk) then syntax_completion SCComment (pos tk);
 			next_token()
 			next_token()
 		| Sharp "end" ->
 		| Sharp "end" ->
 			(match !mstack with
 			(match !mstack with
@@ -209,7 +209,7 @@ let parse ctx code file =
 let parse_string com s p error inlined =
 let parse_string com s p error inlined =
 	let old = Lexer.save() in
 	let old = Lexer.save() in
 	let old_file = (try Some (Hashtbl.find Lexer.all_files p.pfile) with Not_found -> None) in
 	let old_file = (try Some (Hashtbl.find Lexer.all_files p.pfile) with Not_found -> None) in
-	let old_display = !display_position in
+	let old_display = display_position#get in
 	let old_in_display_file = !in_display_file in
 	let old_in_display_file = !in_display_file in
 	let old_syntax_errors = !syntax_errors in
 	let old_syntax_errors = !syntax_errors in
 	syntax_errors := [];
 	syntax_errors := [];
@@ -218,7 +218,7 @@ let parse_string com s p error inlined =
 		| None -> ()
 		| None -> ()
 		| Some f -> Hashtbl.replace Lexer.all_files p.pfile f);
 		| Some f -> Hashtbl.replace Lexer.all_files p.pfile f);
 		if not inlined then begin
 		if not inlined then begin
-			display_position := old_display;
+			display_position#set old_display;
 			in_display_file := old_in_display_file;
 			in_display_file := old_in_display_file;
 		end;
 		end;
 		syntax_errors := old_syntax_errors;
 		syntax_errors := old_syntax_errors;
@@ -226,7 +226,7 @@ let parse_string com s p error inlined =
 	in
 	in
 	Lexer.init p.pfile true;
 	Lexer.init p.pfile true;
 	if not inlined then begin
 	if not inlined then begin
-		display_position := null_pos;
+		display_position#reset;
 		in_display_file := false;
 		in_display_file := false;
 	end;
 	end;
 	let result = try
 	let result = try

+ 1 - 1
src/typing/matcher.ml

@@ -574,7 +574,7 @@ module Case = struct
 		ctx.ret <- old_ret;
 		ctx.ret <- old_ret;
 		List.iter (fun (v,t) -> v.v_type <- t) old_types;
 		List.iter (fun (v,t) -> v.v_type <- t) old_types;
 		save();
 		save();
-		if ctx.is_display_file && DisplayPosition.encloses_display_position p then begin match eo,eo_ast with
+		if ctx.is_display_file && DisplayPosition.display_position#enclosed_in p then begin match eo,eo_ast with
 			| Some e,Some e_ast -> ignore(TyperDisplay.display_expr ctx e_ast e DKMarked with_type p)
 			| Some e,Some e_ast -> ignore(TyperDisplay.display_expr ctx e_ast e DKMarked with_type p)
 			| None,None -> ignore(TyperDisplay.display_expr ctx (EBlock [],p) (mk (TBlock []) ctx.t.tvoid p) DKMarked with_type p)
 			| None,None -> ignore(TyperDisplay.display_expr ctx (EBlock [],p) (mk (TBlock []) ctx.t.tvoid p) DKMarked with_type p)
 			| _ -> assert false
 			| _ -> assert false

+ 6 - 6
src/typing/typeload.ml

@@ -43,7 +43,7 @@ let check_field_access ctx cff =
 	let rec loop p0 acc l =
 	let rec loop p0 acc l =
 		let check_display p1 =
 		let check_display p1 =
 			let pmid = {p0 with pmin = p0.pmax; pmax = p1.pmin} in
 			let pmid = {p0 with pmin = p0.pmax; pmax = p1.pmin} in
-			if DisplayPosition.encloses_display_position pmid then match acc with
+			if DisplayPosition.display_position#enclosed_in pmid then match acc with
 			| access :: _ -> display_access := Some access;
 			| access :: _ -> display_access := Some access;
 			| [] -> ()
 			| [] -> ()
 		in
 		in
@@ -353,7 +353,7 @@ and load_instance ctx ?(allow_display=false) (t,pn) allow_no_params =
 		let t = load_instance' ctx (t,pn) allow_no_params in
 		let t = load_instance' ctx (t,pn) allow_no_params in
 		if allow_display then DisplayEmitter.check_display_type ctx t pn;
 		if allow_display then DisplayEmitter.check_display_type ctx t pn;
 		t
 		t
-	with Error (Module_not_found path,_) when (ctx.com.display.dms_kind = DMDefault) && DisplayPosition.encloses_display_position pn ->
+	with Error (Module_not_found path,_) when (ctx.com.display.dms_kind = DMDefault) && DisplayPosition.display_position#enclosed_in pn ->
 		let s = s_type_path path in
 		let s = s_type_path path in
 		raise_fields (DisplayToplevel.collect ctx TKType NoValue) CRTypeHint (Some {pn with pmin = pn.pmax - String.length s;});
 		raise_fields (DisplayToplevel.collect ctx TKType NoValue) CRTypeHint (Some {pn with pmin = pn.pmax - String.length s;});
 
 
@@ -516,7 +516,7 @@ and load_complex_type' ctx allow_display (t,p) =
 			init_meta_overloads ctx None cf;
 			init_meta_overloads ctx None cf;
 			if ctx.is_display_file then begin
 			if ctx.is_display_file then begin
 				DisplayEmitter.check_display_metadata ctx cf.cf_meta;
 				DisplayEmitter.check_display_metadata ctx cf.cf_meta;
-				if DisplayPosition.encloses_display_position cf.cf_name_pos then displayed_field := Some cf;
+				if DisplayPosition.display_position#enclosed_in cf.cf_name_pos then displayed_field := Some cf;
 			end;
 			end;
 			PMap.add n cf acc
 			PMap.add n cf acc
 		in
 		in
@@ -546,7 +546,7 @@ and load_complex_type ctx allow_display (t,pn) =
 		if Diagnostics.is_diagnostics_run p then begin
 		if Diagnostics.is_diagnostics_run p then begin
 			delay ctx PForce (fun () -> DisplayToplevel.handle_unresolved_identifier ctx name p true);
 			delay ctx PForce (fun () -> DisplayToplevel.handle_unresolved_identifier ctx name p true);
 			t_dynamic
 			t_dynamic
-		end else if ctx.com.display.dms_display && not (DisplayPosition.encloses_display_position pn) then
+		end else if ctx.com.display.dms_display && not (DisplayPosition.display_position#enclosed_in pn) then
 			t_dynamic
 			t_dynamic
 		else
 		else
 			raise exc
 			raise exc
@@ -693,7 +693,7 @@ let rec type_type_param ?(enum_constructor=false) ctx path get_params p tp =
 	c.cl_meta <- tp.Ast.tp_meta;
 	c.cl_meta <- tp.Ast.tp_meta;
 	if enum_constructor then c.cl_meta <- (Meta.EnumConstructorParam,[],null_pos) :: c.cl_meta;
 	if enum_constructor then c.cl_meta <- (Meta.EnumConstructorParam,[],null_pos) :: c.cl_meta;
 	let t = TInst (c,List.map snd c.cl_params) in
 	let t = TInst (c,List.map snd c.cl_params) in
-	if ctx.is_display_file && DisplayPosition.encloses_display_position (pos tp.tp_name) then
+	if ctx.is_display_file && DisplayPosition.display_position#enclosed_in (pos tp.tp_name) then
 		DisplayEmitter.display_type ctx t (pos tp.tp_name);
 		DisplayEmitter.display_type ctx t (pos tp.tp_name);
 	match tp.tp_constraints with
 	match tp.tp_constraints with
 	| None ->
 	| None ->
@@ -844,7 +844,7 @@ let handle_path_display ctx path p =
 		in
 		in
 		DisplayEmitter.display_field ctx origin CFSStatic cf p
 		DisplayEmitter.display_field ctx origin CFSStatic cf p
 	in
 	in
-	match ImportHandling.convert_import_to_something_usable !DisplayPosition.display_position path,ctx.com.display.dms_kind with
+	match ImportHandling.convert_import_to_something_usable DisplayPosition.display_position#get path,ctx.com.display.dms_kind with
 		| (IDKPackage [_],p),DMDefault ->
 		| (IDKPackage [_],p),DMDefault ->
 			let fields = DisplayToplevel.collect ctx TKType WithType.no_value in
 			let fields = DisplayToplevel.collect ctx TKType WithType.no_value in
 			raise_fields fields CRImport (Some p)
 			raise_fields fields CRImport (Some p)

+ 4 - 4
src/typing/typeloadFields.ml

@@ -492,7 +492,7 @@ let create_field_context (ctx,cctx) c cff =
 		is_macro = is_macro;
 		is_macro = is_macro;
 		is_extern = !is_extern;
 		is_extern = !is_extern;
 		is_final = !is_final;
 		is_final = !is_final;
-		is_display_field = ctx.is_display_file && DisplayPosition.encloses_display_position cff.cff_pos;
+		is_display_field = ctx.is_display_file && DisplayPosition.display_position#enclosed_in cff.cff_pos;
 		is_field_debug = cctx.is_class_debug || Meta.has (Meta.Custom ":debug.typeload") cff.cff_meta;
 		is_field_debug = cctx.is_class_debug || Meta.has (Meta.Custom ":debug.typeload") cff.cff_meta;
 		display_modifier = display_modifier;
 		display_modifier = display_modifier;
 		is_abstract_member = cctx.abstract <> None && Meta.has Meta.Impl cff.cff_meta;
 		is_abstract_member = cctx.abstract <> None && Meta.has Meta.Impl cff.cff_meta;
@@ -1105,7 +1105,7 @@ let create_method (ctx,cctx,fctx) c f fd p =
 				else
 				else
 					ignore(TypeloadFunction.process_function_arg ctx n t ct fctx.is_display_field pn)
 					ignore(TypeloadFunction.process_function_arg ctx n t ct fctx.is_display_field pn)
 				end;
 				end;
-				if fctx.is_display_field && DisplayPosition.encloses_display_position pn then begin
+				if fctx.is_display_field && DisplayPosition.display_position#enclosed_in pn then begin
 					let v = add_local_with_origin ctx TVOArgument n t pn in
 					let v = add_local_with_origin ctx TVOArgument n t pn in
 					DisplayEmitter.display_variable ctx v pn;
 					DisplayEmitter.display_variable ctx v pn;
 				end
 				end
@@ -1213,7 +1213,7 @@ let create_property (ctx,cctx,fctx) c f (get,set,t,eo) p =
 		| "default",_ -> AccNormal
 		| "default",_ -> AccNormal
 		| "get",pget ->
 		| "get",pget ->
 			let get = "get_" ^ name in
 			let get = "get_" ^ name in
-			if fctx.is_display_field && DisplayPosition.encloses_display_position pget then delay ctx PTypeField (fun () -> display_accessor get pget);
+			if fctx.is_display_field && DisplayPosition.display_position#enclosed_in pget then delay ctx PTypeField (fun () -> display_accessor get pget);
 			if not cctx.is_lib then delay_check (fun() -> check_method get t_get);
 			if not cctx.is_lib then delay_check (fun() -> check_method get t_get);
 			AccCall
 			AccCall
 		| _,pget ->
 		| _,pget ->
@@ -1232,7 +1232,7 @@ let create_property (ctx,cctx,fctx) c f (get,set,t,eo) p =
 		| "default",_ -> AccNormal
 		| "default",_ -> AccNormal
 		| "set",pset ->
 		| "set",pset ->
 			let set = "set_" ^ name in
 			let set = "set_" ^ name in
-			if fctx.is_display_field && DisplayPosition.encloses_display_position pset then delay ctx PTypeField (fun () -> display_accessor set pset);
+			if fctx.is_display_field && DisplayPosition.display_position#enclosed_in pset then delay ctx PTypeField (fun () -> display_accessor set pset);
 			if not cctx.is_lib then delay_check (fun() -> check_method set t_set);
 			if not cctx.is_lib then delay_check (fun() -> check_method set t_set);
 			AccCall
 			AccCall
 		| _,pset ->
 		| _,pset ->

+ 1 - 1
src/typing/typeloadFunction.ml

@@ -94,7 +94,7 @@ let type_function ctx args ret fmode f do_display p =
 		let c = process_function_arg ctx n t c do_display pn in
 		let c = process_function_arg ctx n t c do_display pn in
 		let v = add_local_with_origin ctx TVOArgument n t pn in
 		let v = add_local_with_origin ctx TVOArgument n t pn in
 		v.v_meta <- v.v_meta @ m;
 		v.v_meta <- v.v_meta @ m;
-		if do_display && DisplayPosition.encloses_display_position pn then
+		if do_display && DisplayPosition.display_position#enclosed_in pn then
 			DisplayEmitter.display_variable ctx v pn;
 			DisplayEmitter.display_variable ctx v pn;
 		if n = "this" then v.v_meta <- (Meta.This,[],null_pos) :: v.v_meta;
 		if n = "this" then v.v_meta <- (Meta.This,[],null_pos) :: v.v_meta;
 		v,c
 		v,c

+ 10 - 10
src/typing/typeloadModule.ml

@@ -349,15 +349,15 @@ let init_module_type ctx context_init do_init (decl,p) =
 	in
 	in
 	let check_path_display path p = match ctx.com.display.dms_kind 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 || DisplayPosition.is_display_file p.pfile) && Filename.basename p.pfile <> "import.hx" ->
+		| DMDiagnostics b when (b || DisplayPosition.display_position#is_in_file p.pfile) && Filename.basename p.pfile <> "import.hx" ->
 			ImportHandling.add_import_position ctx.com p path;
 			ImportHandling.add_import_position ctx.com p path;
 		| DMStatistics ->
 		| DMStatistics ->
 			ImportHandling.add_import_position ctx.com p path;
 			ImportHandling.add_import_position ctx.com p path;
 		| DMUsage _ ->
 		| DMUsage _ ->
 			ImportHandling.add_import_position ctx.com p path;
 			ImportHandling.add_import_position ctx.com p path;
-			if DisplayPosition.is_display_file p.pfile then handle_path_display ctx path p
+			if DisplayPosition.display_position#is_in_file p.pfile then handle_path_display ctx path p
 		| _ ->
 		| _ ->
-			if DisplayPosition.is_display_file p.pfile then handle_path_display ctx path p
+			if DisplayPosition.display_position#is_in_file p.pfile then handle_path_display ctx path p
 	in
 	in
 	match decl with
 	match decl with
 	| EImport (path,mode) ->
 	| EImport (path,mode) ->
@@ -407,7 +407,7 @@ let init_module_type ctx context_init do_init (decl,p) =
 					t_using = [];
 					t_using = [];
 					t_type = f (List.map snd (t_infos t).mt_params);
 					t_type = f (List.map snd (t_infos t).mt_params);
 				} in
 				} in
-				if ctx.is_display_file && DisplayPosition.encloses_display_position p then
+				if ctx.is_display_file && DisplayPosition.display_position#enclosed_in p then
 					DisplayEmitter.display_module_type ctx mt p;
 					DisplayEmitter.display_module_type ctx mt p;
 				mt
 				mt
 			in
 			in
@@ -487,7 +487,7 @@ let init_module_type ctx context_init do_init (decl,p) =
 		context_init := (fun() -> ctx.m.module_using <- filter_classes types @ ctx.m.module_using) :: !context_init
 		context_init := (fun() -> ctx.m.module_using <- filter_classes types @ ctx.m.module_using) :: !context_init
 	| EClass d ->
 	| EClass d ->
 		let c = (match get_type (fst d.d_name) with TClassDecl c -> c | _ -> assert false) in
 		let c = (match get_type (fst d.d_name) with TClassDecl c -> c | _ -> assert false) in
-		if ctx.is_display_file && DisplayPosition.encloses_display_position (pos d.d_name) then
+		if ctx.is_display_file && DisplayPosition.display_position#enclosed_in (pos d.d_name) then
 			DisplayEmitter.display_module_type ctx (match c.cl_kind with KAbstractImpl a -> TAbstractDecl a | _ -> TClassDecl c) (pos d.d_name);
 			DisplayEmitter.display_module_type ctx (match c.cl_kind with KAbstractImpl a -> TAbstractDecl a | _ -> TClassDecl c) (pos d.d_name);
 		TypeloadCheck.check_global_metadata ctx c.cl_meta (fun m -> c.cl_meta <- m :: c.cl_meta) c.cl_module.m_path c.cl_path None;
 		TypeloadCheck.check_global_metadata ctx c.cl_meta (fun m -> c.cl_meta <- m :: c.cl_meta) c.cl_module.m_path c.cl_path None;
 		let herits = d.d_flags in
 		let herits = d.d_flags in
@@ -554,7 +554,7 @@ let init_module_type ctx context_init do_init (decl,p) =
 			);
 			);
 	| EEnum d ->
 	| EEnum d ->
 		let e = (match get_type (fst d.d_name) with TEnumDecl e -> e | _ -> assert false) in
 		let e = (match get_type (fst d.d_name) with TEnumDecl e -> e | _ -> assert false) in
-		if ctx.is_display_file && DisplayPosition.encloses_display_position (pos d.d_name) then
+		if ctx.is_display_file && DisplayPosition.display_position#enclosed_in (pos d.d_name) then
 			DisplayEmitter.display_module_type ctx (TEnumDecl e) (pos d.d_name);
 			DisplayEmitter.display_module_type ctx (TEnumDecl e) (pos d.d_name);
 		let ctx = { ctx with type_params = e.e_params } in
 		let ctx = { ctx with type_params = e.e_params } in
 		let h = (try Some (Hashtbl.find ctx.g.type_patches e.e_path) with Not_found -> None) in
 		let h = (try Some (Hashtbl.find ctx.g.type_patches e.e_path) with Not_found -> None) in
@@ -658,7 +658,7 @@ let init_module_type ctx context_init do_init (decl,p) =
 				cf_doc = f.ef_doc;
 				cf_doc = f.ef_doc;
 				cf_params = f.ef_params;
 				cf_params = f.ef_params;
 			} in
 			} in
- 			if ctx.is_display_file && DisplayPosition.encloses_display_position f.ef_name_pos then
+ 			if ctx.is_display_file && DisplayPosition.display_position#enclosed_in f.ef_name_pos then
  				DisplayEmitter.display_enum_field ctx e f p;
  				DisplayEmitter.display_enum_field ctx e f p;
 			e.e_constrs <- PMap.add f.ef_name f e.e_constrs;
 			e.e_constrs <- PMap.add f.ef_name f e.e_constrs;
 			fields := PMap.add cf.cf_name cf !fields;
 			fields := PMap.add cf.cf_name cf !fields;
@@ -685,7 +685,7 @@ let init_module_type ctx context_init do_init (decl,p) =
 			);
 			);
 	| ETypedef d ->
 	| ETypedef d ->
 		let t = (match get_type (fst d.d_name) with TTypeDecl t -> t | _ -> assert false) in
 		let t = (match get_type (fst d.d_name) with TTypeDecl t -> t | _ -> assert false) in
-		if ctx.is_display_file && DisplayPosition.encloses_display_position (pos d.d_name) then
+		if ctx.is_display_file && DisplayPosition.display_position#enclosed_in (pos d.d_name) then
 			DisplayEmitter.display_module_type ctx (TTypeDecl t) (pos d.d_name);
 			DisplayEmitter.display_module_type ctx (TTypeDecl t) (pos d.d_name);
 		TypeloadCheck.check_global_metadata ctx t.t_meta (fun m -> t.t_meta <- m :: t.t_meta) t.t_module.m_path t.t_path None;
 		TypeloadCheck.check_global_metadata ctx t.t_meta (fun m -> t.t_meta <- m :: t.t_meta) t.t_module.m_path t.t_path None;
 		let ctx = { ctx with type_params = t.t_params } in
 		let ctx = { ctx with type_params = t.t_params } in
@@ -736,7 +736,7 @@ let init_module_type ctx context_init do_init (decl,p) =
 			);
 			);
 	| EAbstract d ->
 	| EAbstract d ->
 		let a = (match get_type (fst d.d_name) with TAbstractDecl a -> a | _ -> assert false) in
 		let a = (match get_type (fst d.d_name) with TAbstractDecl a -> a | _ -> assert false) in
-		if ctx.is_display_file && DisplayPosition.encloses_display_position (pos d.d_name) then
+		if ctx.is_display_file && DisplayPosition.display_position#enclosed_in (pos d.d_name) then
 			DisplayEmitter.display_module_type ctx (TAbstractDecl a) (pos d.d_name);
 			DisplayEmitter.display_module_type ctx (TAbstractDecl a) (pos d.d_name);
 		TypeloadCheck.check_global_metadata ctx a.a_meta (fun m -> a.a_meta <- m :: a.a_meta) a.a_module.m_path a.a_path None;
 		TypeloadCheck.check_global_metadata ctx a.a_meta (fun m -> a.a_meta <- m :: a.a_meta) a.a_module.m_path a.a_path None;
 		let ctx = { ctx with type_params = a.a_params } in
 		let ctx = { ctx with type_params = a.a_params } in
@@ -839,7 +839,7 @@ let type_types_into_module ctx m tdecls p =
 			wildcard_packages = [];
 			wildcard_packages = [];
 			module_imports = [];
 			module_imports = [];
 		};
 		};
-		is_display_file = (ctx.com.display.dms_kind <> DMNone && DisplayPosition.is_display_file m.m_extra.m_file);
+		is_display_file = (ctx.com.display.dms_kind <> DMNone && DisplayPosition.display_position#is_in_file m.m_extra.m_file);
 		meta = [];
 		meta = [];
 		this_stack = [];
 		this_stack = [];
 		with_type_stack = [];
 		with_type_stack = [];

+ 2 - 2
src/typing/typeloadParse.ml

@@ -43,7 +43,7 @@ let parse_file_from_lexbuf com file p lexbuf =
 	in
 	in
 	begin match !Parser.display_mode,parse_result with
 	begin match !Parser.display_mode,parse_result with
 		| DMModuleSymbols (Some ""),_ -> ()
 		| DMModuleSymbols (Some ""),_ -> ()
-		| DMModuleSymbols filter,(ParseSuccess data | ParseDisplayFile(data,_)) when filter = None && DisplayPosition.is_display_file file ->
+		| DMModuleSymbols filter,(ParseSuccess data | ParseDisplayFile(data,_)) when filter = None && DisplayPosition.display_position#is_in_file file ->
 			let ds = DocumentSymbols.collect_module_symbols (filter = None) data in
 			let ds = DocumentSymbols.collect_module_symbols (filter = None) data in
 			DisplayException.raise_module_symbols (DocumentSymbols.Printer.print_module_symbols com [file,ds] filter);
 			DisplayException.raise_module_symbols (DocumentSymbols.Printer.print_module_symbols com [file,ds] filter);
 		| _ ->
 		| _ ->
@@ -59,7 +59,7 @@ 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.is_display_file file in
+	let use_stdin = (Common.defined com Define.DisplayStdin) && DisplayPosition.display_position#is_in_file file in
 	if use_stdin then
 	if use_stdin then
 		let s =
 		let s =
 			match !current_stdin with
 			match !current_stdin with

+ 6 - 6
src/typing/typer.ml

@@ -1436,7 +1436,7 @@ and type_vars ctx vl p =
 			if starts_with v '$' then display_error ctx "Variables names starting with a dollar are not allowed" p;
 			if starts_with v '$' then display_error ctx "Variables names starting with a dollar are not allowed" p;
 			let v = add_local_with_origin ctx TVOLocalVariable v t pv in
 			let v = add_local_with_origin ctx TVOLocalVariable v t pv in
 			if final then v.v_final <- true;
 			if final then v.v_final <- true;
-			if ctx.in_display && DisplayPosition.encloses_display_position pv then
+			if ctx.in_display && DisplayPosition.display_position#enclosed_in pv then
 				DisplayEmitter.display_variable ctx v pv;
 				DisplayEmitter.display_variable ctx v pv;
 			v,e
 			v,e
 		with
 		with
@@ -1457,7 +1457,7 @@ and format_string ctx s p =
 	let min = ref (p.pmin + 1) in
 	let min = ref (p.pmin + 1) in
 	let add_expr (enext,p) len =
 	let add_expr (enext,p) len =
 		min := !min + len;
 		min := !min + len;
-		let enext = if ctx.in_display && DisplayPosition.encloses_display_position p then
+		let enext = if ctx.in_display && DisplayPosition.display_position#enclosed_in p then
 			Display.ExprPreprocessing.process_expr ctx.com (enext,p)
 			Display.ExprPreprocessing.process_expr ctx.com (enext,p)
 		else
 		else
 			enext,p
 			enext,p
@@ -1611,7 +1611,7 @@ and type_object_decl ctx fl with_type p =
 					| None ->
 					| None ->
 						let cf = PMap.find n field_map in
 						let cf = PMap.find n field_map in
 						if (has_class_field_flag cf CfFinal) then is_final := true;
 						if (has_class_field_flag cf CfFinal) then is_final := true;
-						if ctx.in_display && DisplayPosition.encloses_display_position pn then DisplayEmitter.display_field ctx Unknown CFSMember cf pn;
+						if ctx.in_display && DisplayPosition.display_position#enclosed_in pn then DisplayEmitter.display_field ctx Unknown CFSMember cf pn;
 						cf.cf_type
 						cf.cf_type
 				in
 				in
 				let e = type_expr ctx e (WithType.with_structure_field t n) in
 				let e = type_expr ctx e (WithType.with_structure_field t n) in
@@ -1650,7 +1650,7 @@ and type_object_decl ctx fl with_type p =
 			let e = type_expr ctx e (WithType.named_structure_field f) in
 			let e = type_expr ctx e (WithType.named_structure_field f) in
 			(match follow e.etype with TAbstract({a_path=[],"Void"},_) -> error "Fields of type Void are not allowed in structures" e.epos | _ -> ());
 			(match follow e.etype with TAbstract({a_path=[],"Void"},_) -> error "Fields of type Void are not allowed in structures" e.epos | _ -> ());
 			let cf = mk_field f e.etype (punion pf e.epos) pf in
 			let cf = mk_field f e.etype (punion pf e.epos) pf in
-			if ctx.in_display && DisplayPosition.encloses_display_position pf then DisplayEmitter.display_field ctx Unknown CFSMember cf pf;
+			if ctx.in_display && DisplayPosition.display_position#enclosed_in pf then DisplayEmitter.display_field ctx Unknown CFSMember cf pf;
 			(((f,pf,qs),e) :: l, if is_valid then begin
 			(((f,pf,qs),e) :: l, if is_valid then begin
 				if starts_with f '$' then error "Field names starting with a dollar are not allowed" p;
 				if starts_with f '$' then error "Field names starting with a dollar are not allowed" p;
 				PMap.add f cf acc
 				PMap.add f cf acc
@@ -1842,12 +1842,12 @@ and type_try ctx e1 catches with_type p =
 		check_unreachable acc1 t2 (pos e_ast);
 		check_unreachable acc1 t2 (pos e_ast);
 		let locals = save_locals ctx in
 		let locals = save_locals ctx in
 		let v = add_local_with_origin ctx TVOCatchVariable v t pv in
 		let v = add_local_with_origin ctx TVOCatchVariable v t pv in
-		if ctx.is_display_file && DisplayPosition.encloses_display_position pv then
+		if ctx.is_display_file && DisplayPosition.display_position#enclosed_in pv then
 			DisplayEmitter.display_variable ctx v pv;
 			DisplayEmitter.display_variable ctx v pv;
 		let e = type_expr ctx e_ast with_type in
 		let e = type_expr ctx e_ast with_type in
 		(* If the catch position is the display position it means we get completion on the catch keyword or some
 		(* If the catch position is the display position it means we get completion on the catch keyword or some
 		   punctuation. Otherwise we wouldn't reach this point. *)
 		   punctuation. Otherwise we wouldn't reach this point. *)
-		if ctx.is_display_file && DisplayPosition.encloses_display_position pc then ignore(TyperDisplay.display_expr ctx e_ast e DKMarked with_type pc);
+		if ctx.is_display_file && DisplayPosition.display_position#enclosed_in pc then ignore(TyperDisplay.display_expr ctx e_ast e DKMarked with_type pc);
 		v.v_type <- t2;
 		v.v_type <- t2;
 		locals();
 		locals();
 		if PMap.mem name ctx.locals then error ("Local variable " ^ name ^ " is preventing usage of this type here") e.epos;
 		if PMap.mem name ctx.locals then error ("Local variable " ^ name ^ " is preventing usage of this type here") e.epos;