Browse Source

[display] merge display branch

closes #7071
closes #7073
closes #7077
Simon Krajewski 7 years ago
parent
commit
4528442f71

+ 27 - 24
src/compiler/displayOutput.ml

@@ -1,15 +1,19 @@
 open Globals
 open Ast
 open Common
-open Common.CompilationServer
+open CompilationServer
 open Timer
 open DisplayTypes.DisplayMode
 open DisplayTypes.CompletionResultKind
 open CompletionItem
+open CompletionClassField
+open CompletionEnumField
+open ClassFieldOrigin
 open DisplayException
 open Type
 open Display
 open DisplayTypes
+open CompletionModuleType
 open Typecore
 open Genjson
 
@@ -46,13 +50,14 @@ let print_fields fields =
 	let b = Buffer.create 0 in
 	Buffer.add_string b "<list>\n";
 	let convert k = match k with
-		| ITClassField(cf,_) | ITEnumAbstractField(_,cf) ->
+		| ITClassField({field = cf}) | ITEnumAbstractField(_,{field = cf}) ->
 			let kind = match cf.cf_kind with
 				| Method _ -> "method"
 				| Var _ -> "var"
 			in
 			kind,cf.cf_name,s_type (print_context()) cf.cf_type,cf.cf_doc
-		| ITEnumField(en,ef) ->
+		| ITEnumField ef ->
+			let ef = ef.efield in
 			let kind = match follow ef.ef_type with
 				| TFun _ -> "method"
 				| _ -> "var"
@@ -61,13 +66,14 @@ let print_fields fields =
 		| ITType(cm,_) ->
 			let path = CompletionItem.CompletionModuleType.get_path cm in
 			"type",snd path,s_type_path path,None
-		| ITPackage s -> "package",s,"",None
+		| ITPackage(path,_) -> "package",snd path,"",None
 		| ITModule s -> "type",s,"",None
 		| ITMetadata(s,doc) -> "metadata",s,"",doc
 		| ITTimer(name,value) -> "timer",name,"",Some value
 		| ITLiteral(s,t) -> "literal",s,s_type (print_context()) t,None
 		| ITLocal v -> "local",v.v_name,s_type (print_context()) v.v_type,None
 		| ITKeyword kwd -> "keyword",Ast.s_keyword kwd,"",None
+		| ITExpression _ | ITAnonymous _ -> assert false
 	in
 	let fields = List.sort (fun k1 k2 -> compare (legacy_sort k1) (legacy_sort k2)) fields in
 	let fields = List.map convert fields in
@@ -97,30 +103,26 @@ let print_toplevel il =
 	List.iter (fun id -> match id with
 		| ITLocal v ->
 			if check_ident v.v_name then Buffer.add_string b (Printf.sprintf "<i k=\"local\" t=\"%s\">%s</i>\n" (s_type v.v_type) v.v_name);
-		| ITClassField(cf,CFSMember) ->
+		| ITClassField({field = cf;scope = CFSMember}) ->
 			if check_ident cf.cf_name then Buffer.add_string b (Printf.sprintf "<i k=\"member\" t=\"%s\"%s>%s</i>\n" (s_type cf.cf_type) (s_doc cf.cf_doc) cf.cf_name);
-		| ITClassField(cf,(CFSStatic | CFSConstructor)) ->
+		| ITClassField({field = cf;scope = (CFSStatic | CFSConstructor)}) ->
 			if check_ident cf.cf_name then Buffer.add_string b (Printf.sprintf "<i k=\"static\" t=\"%s\"%s>%s</i>\n" (s_type cf.cf_type) (s_doc cf.cf_doc) cf.cf_name);
-		| ITEnumField(en,ef) ->
+		| ITEnumField ef ->
+			let ef = ef.efield in
 			if check_ident ef.ef_name then Buffer.add_string b (Printf.sprintf "<i k=\"enum\" t=\"%s\"%s>%s</i>\n" (s_type ef.ef_type) (s_doc ef.ef_doc) ef.ef_name);
 		| ITEnumAbstractField(a,cf) ->
+			let cf = cf.field in
 			if check_ident cf.cf_name then Buffer.add_string b (Printf.sprintf "<i k=\"enumabstract\" t=\"%s\"%s>%s</i>\n" (s_type cf.cf_type) (s_doc cf.cf_doc) cf.cf_name);
-		| ITType(cm,rm) ->
+		| ITType(cm,_) ->
 			let path = CompletionItem.CompletionModuleType.get_path cm in
-			let import,name = match rm with
-				| RMOtherModule path ->
-					let label_path = if path = path then path else (fst path @ [snd path],snd path) in
-					Printf.sprintf " import=\"%s\"" (s_type_path path),s_type_path label_path
-				| _ -> "",(snd path)
-			in
-			Buffer.add_string b (Printf.sprintf "<i k=\"type\" p=\"%s\"%s%s>%s</i>\n" (s_type_path path) import ("") name);
-		| ITPackage s ->
-			Buffer.add_string b (Printf.sprintf "<i k=\"package\">%s</i>\n" s)
+			Buffer.add_string b (Printf.sprintf "<i k=\"type\" p=\"%s\"%s>%s</i>\n" (s_type_path path) ("") cm.name);
+		| ITPackage(path,_) ->
+			Buffer.add_string b (Printf.sprintf "<i k=\"package\">%s</i>\n" (snd path))
 		| ITLiteral(s,_) ->
 			Buffer.add_string b (Printf.sprintf "<i k=\"literal\">%s</i>\n" s)
 		| ITTimer(s,_) ->
 			Buffer.add_string b (Printf.sprintf "<i k=\"timer\">%s</i>\n" s)
-		| ITMetadata _ | ITModule _ | ITKeyword _ ->
+		| ITMetadata _ | ITModule _ | ITKeyword _ | ITAnonymous _ | ITExpression _ ->
 			(* compat: don't add *)
 			()
 	) il;
@@ -369,7 +371,7 @@ module TypePathHandler = struct
 		if packs = [] && modules = [] then
 			(abort ("No classes found in " ^ String.concat "." p) null_pos)
 		else
-			let packs = List.map (fun n -> ITPackage n) packs in
+			let packs = List.map (fun n -> ITPackage((p,n),[])) packs in
 			let modules = List.map (fun n -> ITModule n) modules in
 			Some (packs @ modules)
 
@@ -413,11 +415,11 @@ module TypePathHandler = struct
 					[]
 				else
 					List.map (fun mt ->
-						ITType(CompletionItem.CompletionModuleType.of_module_type ImportStatus.Imported mt,RMOtherModule m.m_path)
+						ITType(CompletionItem.CompletionModuleType.of_module_type mt,ImportStatus.Imported)
 					) public_types
 			in
 			let make_field_doc cf =
-				ITClassField(cf,CFSStatic)
+				ITClassField (CompletionClassField.make cf CFSStatic (Self (TClassDecl null_class)) true)
 			in
 			let fields = match !statics with
 				| None -> types
@@ -425,7 +427,7 @@ module TypePathHandler = struct
 			in
 			let fields = match !enum_statics with
 				| None -> fields
-				| Some en -> PMap.fold (fun ef acc -> ITEnumField(en,ef) :: acc) en.e_constrs fields
+				| Some en -> PMap.fold (fun ef acc -> ITEnumField(CompletionEnumField.make ef (Self (TEnumDecl en)) true) :: acc) en.e_constrs fields
 			in
 			Some fields
 		with _ ->
@@ -474,7 +476,7 @@ let unquote v =
 let handle_display_argument com file_pos pre_compilation did_something =
 	match file_pos with
 	| "classes" ->
-		pre_compilation := (fun() -> raise (Parser.TypePath (["."],None,true))) :: !pre_compilation;
+		pre_compilation := (fun() -> raise (Parser.TypePath (["."],None,true,null_pos))) :: !pre_compilation;
 	| "keywords" ->
 		raise (Completion (print_keywords ()))
 	| "memory" ->
@@ -538,7 +540,7 @@ let handle_display_argument com file_pos pre_compilation did_something =
 		let pos = try int_of_string pos with _ -> failwith ("Invalid format: "  ^ pos) in
 		com.display <- DisplayMode.create mode;
 		Parser.display_mode := mode;
-		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");
 		Parser.use_doc := true;
 		Parser.resume_display := {
 			pfile = Path.unique_full_path file;
@@ -616,6 +618,7 @@ let process_global_display_mode com tctx = match com.display.dms_kind with
 		raise_position usages
 	| DMDiagnostics global ->
 		let dctx = Diagnostics.prepare com global in
+		Option.may (fun cs -> CompilationServer.cache_context cs com) (CompilationServer.get());
 		raise_diagnostics (Diagnostics.Printer.print_diagnostics dctx tctx global)
 	| DMStatistics ->
 		let stats = Statistics.collect_statistics tctx in

+ 14 - 3
src/compiler/main.ml

@@ -955,6 +955,15 @@ with
 			f (DisplayException.to_json ctx de)
 		| _ -> assert false
 		end
+	(* | Parser.TypePath (_,_,_,p) when ctx.com.json_out <> None ->
+		begin match com.json_out with
+		| Some (f,_) ->
+			let tctx = Typer.create ctx.com in
+			let fields = DisplayToplevel.collect tctx true Typecore.NoValue in
+			let jctx = Genjson.create_context Genjson.GMMinimum in
+			f (DisplayException.fields_to_json jctx fields CRImport (Some (Parser.cut_pos_at_display p)) false)
+		| _ -> assert false
+		end *)
 	| DisplayException(DisplayPackage pack) ->
 		raise (DisplayOutput.Completion (String.concat "." pack))
 	| DisplayException(DisplayFields(fields,cr,_,_)) ->
@@ -978,7 +987,7 @@ with
 			| CRPattern
 			| CRTypeRelation ->
 				DisplayOutput.print_toplevel fields
-			| CRField
+			| CRField _
 			| CRStructureField
 			| CRMetadata
 			| CROverride ->
@@ -995,7 +1004,7 @@ with
 			raise (DisplayOutput.Completion (DisplayOutput.print_signatures signatures))
 	| DisplayException(DisplayPosition pl) ->
 		raise (DisplayOutput.Completion (DisplayOutput.print_positions pl))
-	| Parser.TypePath (p,c,is_import) ->
+	| Parser.TypePath (p,c,is_import,pos) ->
 		let fields =
 			try begin match c with
 				| None ->
@@ -1012,7 +1021,9 @@ with
 			begin match ctx.com.json_out with
 			| Some (f,_) ->
 				let ctx = DisplayJson.create_json_context() in
-				f (DisplayException.to_json ctx (DisplayFields(fields,CRField,None,false)))
+				let pos = Parser.cut_pos_at_display pos in
+				let kind = CRField ((CompletionItem.ITModule((String.concat "." p)),pos)) in
+				f (DisplayException.fields_to_json ctx fields kind None false);
 			| _ -> raise (DisplayOutput.Completion (DisplayOutput.print_fields fields))
 			end
 		end

+ 17 - 14
src/compiler/server.ml

@@ -2,7 +2,7 @@ open Printf
 open Globals
 open Ast
 open Common
-open Common.CompilationServer
+open CompilationServer
 open DisplayTypes.DisplayMode
 open Timer
 open Type
@@ -149,8 +149,8 @@ let rec wait_loop process_params verbose accept =
 			data
 	);
 	let check_module_shadowing com paths m =
-		List.iter (fun (path,_) ->
-			let file = (path ^ (snd m.m_path)) ^ ".hx" in
+		List.iter (fun dir ->
+			let file = (dir.c_path ^ (snd m.m_path)) ^ ".hx" in
 			if Sys.file_exists file then begin
 				let time = file_time file in
 				if time > m.m_extra.m_time then begin
@@ -177,25 +177,25 @@ let rec wait_loop process_params verbose accept =
 			let dirs = try
 				(* Next, get all directories from the cache and filter the ones that haven't changed. *)
 				let all_dirs = CompilationServer.find_directories cs sign in
-				let dirs = List.fold_left (fun acc (dir,time) ->
+				let dirs = List.fold_left (fun acc dir ->
 					try
-						let time' = stat dir in
-						if !time < time' then begin
-							time := time';
-							let sub_dirs = Path.find_directories (platform_name com.platform) false [dir] in
+						let time' = stat dir.c_path in
+						if dir.c_mtime < time' then begin
+							dir.c_mtime <- time';
+							let sub_dirs = Path.find_directories (platform_name com.platform) false [dir.c_path] in
 							List.iter (fun dir ->
 								if not (CompilationServer.has_directory cs sign dir) then begin
 									let time = stat dir in
 									ServerMessage.added_directory com "" dir;
-									CompilationServer.add_directory cs sign (dir,ref time)
+									CompilationServer.add_directory cs sign (CompilationServer.create_directory dir time)
 								end;
 							) sub_dirs;
-							(dir,time') :: acc
+							(CompilationServer.create_directory dir.c_path time') :: acc
 						end else
 							acc
 					with Unix.Unix_error _ ->
-						CompilationServer.remove_directory cs sign dir;
-						ServerMessage.removed_directory com "" dir;
+						CompilationServer.remove_directory cs sign dir.c_path;
+						ServerMessage.removed_directory com "" dir.c_path;
 						acc
 				) [] all_dirs in
 				ServerMessage.changed_directories com "" dirs;
@@ -210,7 +210,7 @@ let rec wait_loop process_params verbose accept =
 					let add_dir path =
 						try
 							let time = stat path in
-							dirs := (path,ref time) :: !dirs
+							dirs := CompilationServer.create_directory path time :: !dirs
 						with Unix.Unix_error _ ->
 							()
 					in
@@ -283,7 +283,10 @@ let rec wait_loop process_params verbose accept =
 					let _, mctx = MacroContext.get_macro_context ctx p in
 					check_module_shadowing mctx.Typecore.com (get_changed_directories mctx) m
 			in
-			let has_policy policy = List.mem policy m.m_extra.m_check_policy in
+			let has_policy policy = List.mem policy m.m_extra.m_check_policy || match policy with
+				| NoCheckShadowing | NoCheckFileTimeModification when !ServerConfig.do_not_check_modules -> true
+				| _ -> false
+			in
 			let check_file () =
 				if file_time m.m_extra.m_file <> m.m_extra.m_time then begin
 					if has_policy CheckFileContentModification && not (content_changed m m.m_extra.m_file) then begin

+ 1 - 0
src/compiler/serverConfig.ml

@@ -0,0 +1 @@
+let do_not_check_modules = ref false

+ 2 - 1
src/compiler/serverMessage.ml

@@ -1,5 +1,6 @@
 open Globals
 open Common
+open CompilationServer
 open Type
 open Json
 
@@ -73,7 +74,7 @@ let found_directories com tabs dirs =
 	if config.print_found_directories then print_endline (Printf.sprintf "%sfound %i directories" (sign_string com) (List.length dirs))
 
 let changed_directories com tabs dirs =
-	if config.print_changed_directories then print_endline (Printf.sprintf "%schanged directories: [%s]" (sign_string com) (String.concat ", " (List.map (fun (s,_) -> "\"" ^ s ^ "\"") dirs)))
+	if config.print_changed_directories then print_endline (Printf.sprintf "%schanged directories: [%s]" (sign_string com) (String.concat ", " (List.map (fun dir -> "\"" ^ dir.c_path ^ "\"") dirs)))
 
 let module_path_changed com tabs (m,time,file) =
 	if config.print_module_path_changed then print_endline (Printf.sprintf "%smodule path might have changed: %s\n\twas: %2.0f %s\n\tnow: %2.0f %s"

+ 2 - 166
src/context/common.ml

@@ -173,170 +173,6 @@ type context = {
 
 exception Abort of string * pos
 
-module CompilationServer = struct
-	type cached_file = {
-		c_time : float;
-		c_package : string list;
-		c_decls : type_decl list;
-		mutable c_module_name : string option;
-	}
-
-	type cache = {
-		c_haxelib : (string list, string list) Hashtbl.t;
-		c_files : ((string * string), cached_file) Hashtbl.t;
-		c_modules : (path * string, module_def) Hashtbl.t;
-		c_directories : (string, (string * float ref) list) Hashtbl.t;
-	}
-
-	type t = {
-		cache : cache;
-		mutable signs : (string * string) list;
-		mutable initialized : bool;
-	}
-
-	type context_options =
-		| NormalContext
-		| MacroContext
-		| NormalAndMacroContext
-
-	let instance : t option ref = ref None
-
-	let create_cache () = {
-		c_haxelib = Hashtbl.create 0;
-		c_files = Hashtbl.create 0;
-		c_modules = Hashtbl.create 0;
-		c_directories = Hashtbl.create 0;
-	}
-
-	let create () =
-		let cs = {
-			cache = create_cache();
-			signs = [];
-			initialized = false;
-		} in
-		instance := Some cs;
-		cs
-
-	let get () =
-		!instance
-
-	let runs () =
-		!instance <> None
-
-	let force () = match !instance with None -> assert false | Some i -> i
-
-	let is_initialized cs =
-		cs.initialized = true
-
-	let set_initialized cs =
-		cs.initialized <- true
-
-	let get_context_files cs signs =
-		Hashtbl.fold (fun (file,sign) cfile acc ->
-			if (List.mem sign signs) then (file,cfile) :: acc
-			else acc
-		) cs.cache.c_files []
-
-	(* signatures *)
-
-	let get_sign cs sign =
-		List.assoc sign cs.signs
-
-	let get_sign_by_index cs index =
-		List.find (fun (_,i) -> i = index) cs.signs
-
-	let add_sign cs sign =
-		let i = string_of_int (List.length cs.signs) in
-		cs.signs <- (sign,i) :: cs.signs;
-		i
-
-	let get_signs cs =
-		cs.signs
-
-	(* modules *)
-
-	let find_module cs key =
-		Hashtbl.find cs.cache.c_modules key
-
-	let cache_module cs key value =
-		Hashtbl.replace cs.cache.c_modules key value
-
-	let taint_modules cs file =
-		Hashtbl.iter (fun _ m -> if m.m_extra.m_file = file then m.m_extra.m_dirty <- Some m) cs.cache.c_modules
-
-	let iter_modules cs com f =
-		let sign = Define.get_signature com.defines in
-		Hashtbl.iter (fun (_,sign') m -> if sign = sign' then f m) cs.cache.c_modules
-
-	(* files *)
-
-	let find_file cs key =
-		Hashtbl.find cs.cache.c_files key
-
-	let cache_file cs key time data =
-		Hashtbl.replace cs.cache.c_files key { c_time = time; c_package = fst data; c_decls = snd data; c_module_name = None }
-
-	let remove_file cs key =
-		Hashtbl.remove cs.cache.c_files key
-
-	let remove_files cs file =
-		List.iter (fun (sign,_) -> remove_file cs (file,sign)) cs.signs
-
-	let iter_files cs com f =
-		let sign = Define.get_signature com.defines in
-		Hashtbl.iter (fun (file,sign') decls -> if sign = sign' then f file decls) cs.cache.c_files
-
-	(* haxelibs *)
-
-	let find_haxelib cs key =
-		Hashtbl.find cs.cache.c_haxelib key
-
-	let cache_haxelib cs key value =
-		Hashtbl.replace cs.cache.c_haxelib key value
-
-	(* directories *)
-
-	let find_directories cs key =
-		Hashtbl.find cs.cache.c_directories key
-
-	let add_directories cs key value =
-		Hashtbl.replace cs.cache.c_directories key value
-
-	let remove_directory cs key value =
-		try
-			let current = find_directories cs key in
-			Hashtbl.replace cs.cache.c_directories key (List.filter (fun (s,_) -> s <> value) current);
-		with Not_found ->
-			()
-
-	let has_directory cs key value =
-		try
-			List.mem_assoc value (find_directories cs key)
-		with Not_found ->
-			false
-
-	let add_directory cs key value =
-		try
-			let current = find_directories cs key in
-			add_directories cs key (value :: current)
-		with Not_found ->
-			add_directories cs key [value]
-
-	let clear_directories cs key =
-		Hashtbl.remove cs.cache.c_directories key
-
-	(* context *)
-
-	let rec cache_context cs com =
-		let cache_module m =
-			cache_module cs (m.m_path,m.m_extra.m_sign) m;
-		in
-		List.iter cache_module com.modules;
-		match com.get_macros() with
-		| None -> ()
-		| Some com -> cache_context cs com
-end
-
 (* Defines *)
 
 module Define = Define
@@ -502,8 +338,8 @@ let create version s_version args =
 	let m = Type.mk_mono() in
 	let defines =
 		PMap.add "true" "1" (
-		PMap.add "source-header" ("Generated by Haxe " ^ s_version) (
-		if !Parser.display_mode <> DisplayTypes.DisplayMode.DMNone then PMap.add "display" "1" PMap.empty else PMap.empty))
+			PMap.add "source-header" ("Generated by Haxe " ^ s_version) PMap.empty
+		)
 	in
 	{
 		version = version;

+ 176 - 0
src/context/compilationServer.ml

@@ -0,0 +1,176 @@
+open Globals
+open Ast
+open Type
+open Common
+
+type cached_file = {
+	c_time : float;
+	c_package : string list;
+	c_decls : type_decl list;
+	mutable c_module_name : string option;
+}
+
+type cached_directory = {
+	c_path : string;
+	mutable c_mtime : float;
+}
+
+type cache = {
+	c_haxelib : (string list, string list) Hashtbl.t;
+	c_files : ((string * string), cached_file) Hashtbl.t;
+	c_modules : (path * string, module_def) Hashtbl.t;
+	c_directories : (string, cached_directory list) Hashtbl.t;
+}
+
+type t = {
+	cache : cache;
+	mutable signs : (string * string) list;
+	mutable initialized : bool;
+}
+
+type context_options =
+	| NormalContext
+	| MacroContext
+	| NormalAndMacroContext
+
+let instance : t option ref = ref None
+
+let create_cache () = {
+	c_haxelib = Hashtbl.create 0;
+	c_files = Hashtbl.create 0;
+	c_modules = Hashtbl.create 0;
+	c_directories = Hashtbl.create 0;
+}
+
+let create () =
+	let cs = {
+		cache = create_cache();
+		signs = [];
+		initialized = false;
+	} in
+	instance := Some cs;
+	cs
+
+let get () =
+	!instance
+
+let runs () =
+	!instance <> None
+
+let force () = match !instance with None -> assert false | Some i -> i
+
+let is_initialized cs =
+	cs.initialized = true
+
+let set_initialized cs =
+	cs.initialized <- true
+
+let get_context_files cs signs =
+	Hashtbl.fold (fun (file,sign) cfile acc ->
+		if (List.mem sign signs) then (file,cfile) :: acc
+		else acc
+	) cs.cache.c_files []
+
+(* signatures *)
+
+let get_sign cs sign =
+	List.assoc sign cs.signs
+
+let get_sign_by_index cs index =
+	List.find (fun (_,i) -> i = index) cs.signs
+
+let add_sign cs sign =
+	let i = string_of_int (List.length cs.signs) in
+	cs.signs <- (sign,i) :: cs.signs;
+	i
+
+let get_signs cs =
+	cs.signs
+
+(* modules *)
+
+let find_module cs key =
+	Hashtbl.find cs.cache.c_modules key
+
+let cache_module cs key value =
+	Hashtbl.replace cs.cache.c_modules key value
+
+let taint_modules cs file =
+	Hashtbl.iter (fun _ m -> if m.m_extra.m_file = file then m.m_extra.m_dirty <- Some m) cs.cache.c_modules
+
+let iter_modules cs com f =
+	let sign = Define.get_signature com.defines in
+	Hashtbl.iter (fun (_,sign') m -> if sign = sign' then f m) cs.cache.c_modules
+
+(* files *)
+
+let find_file cs key =
+	Hashtbl.find cs.cache.c_files key
+
+let cache_file cs key time data =
+	Hashtbl.replace cs.cache.c_files key { c_time = time; c_package = fst data; c_decls = snd data; c_module_name = None }
+
+let remove_file cs key =
+	Hashtbl.remove cs.cache.c_files key
+
+let remove_files cs file =
+	List.iter (fun (sign,_) -> remove_file cs (file,sign)) cs.signs
+
+let iter_files cs com f =
+	let sign = Define.get_signature com.defines in
+	Hashtbl.iter (fun (file,sign') decls -> if sign = sign' then f file decls) cs.cache.c_files
+
+(* haxelibs *)
+
+let find_haxelib cs key =
+	Hashtbl.find cs.cache.c_haxelib key
+
+let cache_haxelib cs key value =
+	Hashtbl.replace cs.cache.c_haxelib key value
+
+(* directories *)
+
+let create_directory path mtime = {
+	c_path = path;
+	c_mtime = mtime;
+}
+
+let find_directories cs key =
+	Hashtbl.find cs.cache.c_directories key
+
+let add_directories cs key value =
+	Hashtbl.replace cs.cache.c_directories key value
+
+let remove_directory cs key value =
+	try
+		let current = find_directories cs key in
+		Hashtbl.replace cs.cache.c_directories key (List.filter (fun dir -> dir.c_path <> value) current);
+	with Not_found ->
+		()
+
+let has_directory cs key value =
+	try
+		List.exists (fun dir -> dir.c_path = value) (find_directories cs key)
+	with Not_found ->
+		false
+
+let add_directory cs key value =
+	try
+		let current = find_directories cs key in
+		add_directories cs key (value :: current)
+	with Not_found ->
+		add_directories cs key [value]
+
+let clear_directories cs key =
+	Hashtbl.remove cs.cache.c_directories key
+
+(* context *)
+
+let rec cache_context cs com =
+	let cache_module m =
+		cache_module cs (m.m_path,m.m_extra.m_sign) m;
+	in
+	List.iter cache_module com.modules;
+	match com.get_macros() with
+	| None -> ()
+	| Some com -> cache_context cs com

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

@@ -5,6 +5,7 @@ open Typecore
 open DisplayException
 open DisplayTypes.DisplayMode
 open CompletionItem
+open ClassFieldOrigin
 open DisplayTypes.CompletionResultKind
 open Common
 open Display
@@ -135,6 +136,9 @@ let check_field_modifiers ctx c cf override display_modifier =
 		| _,Some (AOverride,p) when ctx.com.display.dms_kind = DMDefault ->
 			let all_fields = TClass.get_all_super_fields c in
 			let missing_fields = List.fold_left (fun fields cf -> PMap.remove cf.cf_name fields) all_fields c.cl_ordered_fields in
-			let l = PMap.fold (fun cf fields -> (ITClassField(cf,CFSMember)) :: fields) missing_fields [] in
+			let l = PMap.fold (fun (c,cf) fields ->
+				let origin = Parent (TClassDecl c) in
+				(ITClassField (CompletionClassField.make cf CFSMember origin true)) :: fields
+			) missing_fields [] in
 			raise_fields l CROverride None false
 		| _ -> ()

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

@@ -36,7 +36,7 @@ let fields_to_json ctx fields kind po sorted =
 	last_completion_result := Array.of_list fields;
 	let fl =
 		("items",jarray ja) ::
-		("kind",jint (Obj.magic kind)) ::
+		("mode",CompletionResultKind.to_json ctx kind) ::
 		("sorted",jbool sorted) ::
 		(match po with None -> [] | Some p -> ["replaceRange",generate_pos_as_range p]) in
 	jobject fl

+ 135 - 129
src/context/display/displayFields.ml

@@ -22,27 +22,17 @@ open Error
 open Typecore
 open Type
 open CompletionItem
+open ClassFieldOrigin
 
 let get_submodule_fields ctx path =
 	let m = Hashtbl.find ctx.g.modules path in
 	let tl = List.filter (fun t -> path <> (t_infos t).mt_path && not (t_infos t).mt_private) m.m_types in
 	let tl = List.map (fun mt ->
-		let is = ImportStatus.Imported in
-		ITType(CompletionItem.CompletionModuleType.of_module_type is mt,RMOtherModule m.m_path)
+		ITType(CompletionItem.CompletionModuleType.of_module_type mt,ImportStatus.Imported)
 	) tl in
 	tl
 
-let collect ctx e_ast e dk with_type p =
-	let merge_core_doc = !merge_core_doc_ref in
-	let opt_args args ret = TFun(List.map(fun (n,o,t) -> n,true,t) args,ret) in
-	let e = match e.eexpr with
-		| TField (e1,fa) when field_name fa = "bind" ->
-			(match follow e1.etype with
-			| TFun(args,ret) -> {e1 with etype = opt_args args ret}
-			| _ -> e)
-		| _ ->
-			e
-	in
+let collect_static_extensions ctx items e p =
 	let opt_type t =
 		match t with
 		| TLazy f ->
@@ -53,147 +43,163 @@ let collect ctx e_ast e dk with_type p =
 		| _ ->
 			t
 	in
+	let rec loop acc = function
+		| [] ->
+			acc
+		| (c,_) :: l ->
+			let rec dup t = Type.map dup t in
+			let acc = List.fold_left (fun acc f ->
+				if Meta.has Meta.NoUsing f.cf_meta || Meta.has Meta.Impl f.cf_meta || PMap.mem f.cf_name items then
+					acc
+				else begin
+					let f = { f with cf_type = opt_type f.cf_type } in
+					let monos = List.map (fun _ -> mk_mono()) f.cf_params in
+					let map = apply_params f.cf_params monos in
+					match follow (map f.cf_type) with
+					| TFun((_,_,TType({t_path=["haxe";"macro"], "ExprOf"}, [t])) :: args, ret)
+					| TFun((_,_,t) :: args, ret) ->
+						begin try
+							unify_raise ctx (dup e.etype) t e.epos;
+							List.iter2 (fun m (name,t) -> match follow t with
+								| TInst ({ cl_kind = KTypeParameter constr },_) when constr <> [] ->
+									List.iter (fun tc -> unify_raise ctx m (map tc) e.epos) constr
+								| _ -> ()
+							) monos f.cf_params;
+							if not (can_access ctx c f true) || follow e.etype == t_dynamic && follow t != t_dynamic then
+								acc
+							else begin
+								let f = prepare_using_field f in
+								let f = { f with cf_params = []; cf_public = true; cf_type = TFun(args,ret) } in
+								let origin = StaticExtension(TClassDecl c) in
+								let item = ITClassField (CompletionClassField.make f CFSMember origin true) in
+								PMap.add f.cf_name item acc
+							end
+						with Error (Unify _,_) ->
+							acc
+						end
+					| _ ->
+						acc
+				end
+			) acc c.cl_ordered_statics in
+			loop acc l
+	in
+	match follow e.etype with
+	| TMono _ ->
+		items
+	| _ ->
+		let items = loop items ctx.m.module_using in
+		let items = loop items ctx.g.global_using in
+		items
+
+let collect ctx e_ast e dk with_type p =
+	let opt_args args ret = TFun(List.map(fun (n,o,t) -> n,true,t) args,ret) in
 	let should_access c cf stat =
-		if c != ctx.curclass && not cf.cf_public && String.length cf.cf_name > 4 then begin match String.sub cf.cf_name 0 4 with
+		if Meta.has Meta.NoCompletion cf.cf_meta then false
+		else if c != ctx.curclass && not cf.cf_public && String.length cf.cf_name > 4 then begin match String.sub cf.cf_name 0 4 with
 			| "get_" | "set_" -> false
 			| _ -> can_access ctx c cf stat
 		end else
+			(not stat || not (Meta.has Meta.Impl cf.cf_meta)) &&
 			can_access ctx c cf stat
 	in
-	let rec get_fields seen t =
-		let t = follow t in
-		if (List.exists (fast_eq t) seen) then PMap.empty
-		else match follow t with
-		| TInst (c,params) ->
-			if Meta.has Meta.CoreApi c.cl_meta then merge_core_doc ctx c;
-			let merge ?(cond=(fun _ -> true)) a b =
-				PMap.foldi (fun k f m -> if cond f then PMap.add k f m else m) a b
-			in
-			let rec loop c params =
-				let m = List.fold_left (fun m (i,params) ->
-					merge m (loop i params)
-				) PMap.empty c.cl_implements in
-				let m = (match c.cl_super with
-					| None -> m
-					| Some (csup,cparams) -> merge m (loop csup cparams)
-				) in
-				let m = merge ~cond:(fun f -> should_access c f false) c.cl_fields m in
-				let m = (match c.cl_kind with
-					| KTypeParameter pl -> List.fold_left (fun acc t' -> merge acc (get_fields (t :: seen) t')) m pl
-					| _ -> m
-				) in
-				PMap.map (fun f -> { f with cf_type = apply_params c.cl_params params (opt_type f.cf_type); cf_public = true; }) m
-			in
-			loop c params
-		| TAbstract({a_impl = Some c} as a,pl) ->
-			if Meta.has Meta.CoreApi c.cl_meta then merge_core_doc ctx c;
-			let fields = try
+	let rec loop items t =
+		let is_new_item items name = not (PMap.mem name items) in
+		match follow t with
+		| TInst ({cl_kind = KTypeParameter tl},_) ->
+			(* Type parameters can access the fields of their constraints *)
+			List.fold_left (fun acc t -> loop acc t) items tl
+		| TInst(c0,tl) ->
+			(* For classes, browse the hierarchy *)
+			let fields = TClass.get_all_fields c0 tl in
+			PMap.foldi (fun k (c,cf) acc ->
+				if should_access c cf false && is_new_item acc cf.cf_name then begin
+					let origin = if c == c0 then Self(TClassDecl c) else Parent(TClassDecl c) in
+				 	let item = ITClassField (CompletionClassField.make cf CFSMember origin true) in
+					PMap.add k item acc
+				end else
+					acc
+			) fields items
+		| TAbstract({a_impl = Some c} as a,tl) ->
+			(* Abstracts should show all their @:impl fields minus the constructor. *)
+			let items = List.fold_left (fun acc cf ->
+				if Meta.has Meta.Impl cf.cf_meta && should_access c cf false && is_new_item acc cf.cf_name then begin
+					let origin = Self(TAbstractDecl a) in
+					let cf = prepare_using_field cf in
+					let cf = if tl = [] then cf else {cf with cf_type = apply_params a.a_params tl cf.cf_type} in
+					let item = ITClassField (CompletionClassField.make cf CFSMember origin true) in
+					PMap.add cf.cf_name item acc
+				end else
+					acc
+			) items c.cl_ordered_statics in
+			begin try
+				(* If there's a @:forward, get the fields of the underlying type and filter them. *)
 				let _,el,_ = Meta.get Meta.Forward a.a_meta in
 				let sl = ExtList.List.filter_map (fun e -> match fst e with
 					| EConst(Ident s) -> Some s
 					| _ -> None
 				) el in
-				let fields = get_fields (t :: seen) (apply_params a.a_params pl a.a_this) in
-				if sl = [] then fields else PMap.fold (fun cf acc ->
-					if List.mem cf.cf_name sl then
-						PMap.add cf.cf_name cf acc
+				let forwarded_fields = loop PMap.empty (apply_params a.a_params tl a.a_this) in
+				if sl = [] then items else PMap.foldi (fun name item acc ->
+					if List.mem name sl && is_new_item acc name then
+						PMap.add name item acc
 					else
 						acc
-				) fields PMap.empty
+				) forwarded_fields items
 			with Not_found ->
-				PMap.empty
-			in
-			PMap.fold (fun f acc ->
-				if f.cf_name <> "_new" && should_access c f true && Meta.has Meta.Impl f.cf_meta && not (Meta.has Meta.Enum f.cf_meta) then begin
-					let f = prepare_using_field f in
-					let t = apply_params a.a_params pl (follow f.cf_type) in
-					PMap.add f.cf_name { f with cf_public = true; cf_type = opt_type t } acc
+				items
+			end
+		| TAnon an ->
+			(* Anons only have their own fields. *)
+			PMap.foldi (fun name cf acc ->
+				if is_new_item acc name then begin
+					let origin,check = match !(an.a_status) with
+						| Statics c -> Self (TClassDecl c),should_access c cf true
+						| EnumStatics en -> Self (TEnumDecl en),true
+						| AbstractStatics a ->
+							let check = match a.a_impl with
+								| None -> true
+								| Some c -> should_access c cf true
+							in
+							Self (TAbstractDecl a),check
+						| _ -> AnonymousStructure an,true
+					in
+					if check then PMap.add name (ITClassField (CompletionClassField.make cf CFSMember origin true)) acc
+					else acc
 				end else
 					acc
-			) c.cl_statics fields
-		| TAnon a when PMap.is_empty a.a_fields ->
-			begin match with_type with
-			| WithType t' -> get_fields (t :: seen) t'
-			| _ -> a.a_fields
-			end
-		| TAnon a ->
-			(match !(a.a_status) with
-			| Statics c ->
-				if Meta.has Meta.CoreApi c.cl_meta then merge_core_doc ctx c;
-				let is_abstract_impl = match c.cl_kind with KAbstractImpl _ -> true | _ -> false in
-				let pm = match c.cl_constructor with None -> PMap.empty | Some cf -> PMap.add "new" cf PMap.empty in
-				PMap.fold (fun f acc ->
-					if should_access c f true && (not is_abstract_impl || not (Meta.has Meta.Impl f.cf_meta) || Meta.has Meta.Enum f.cf_meta) then
-						PMap.add f.cf_name { f with cf_public = true; cf_type = opt_type f.cf_type } acc else acc
-				) a.a_fields pm
-			| _ ->
-				a.a_fields)
+			) an.a_fields items
 		| TFun (args,ret) ->
-			let t = opt_args args ret in
-			let cf = mk_field "bind" (tfun [t] t) p null_pos in
-			cf.cf_kind <- Method MethNormal;
-			PMap.add "bind" cf PMap.empty
+			(* A function has no field except the magic .bind one. *)
+			if is_new_item items "bind" then begin
+				let t = opt_args args ret in
+				let cf = mk_field "bind" (tfun [t] t) p null_pos in
+				cf.cf_kind <- Method MethNormal;
+				let item = ITClassField (CompletionClassField.make cf CFSStatic BuiltIn true) in
+				PMap.add "bind" item items
+			end else
+				items
 		| _ ->
-			PMap.empty
+			items
 	in
-	let fields = get_fields [] e.etype in
-	(*
-		add 'using' methods compatible with this type
-	*)
-	let rec loop acc = function
-		| [] -> acc
-		| (c,_) :: l ->
-			let acc = ref (loop acc l) in
-			let rec dup t = Type.map dup t in
-			List.iter (fun f ->
-				if not (Meta.has Meta.NoUsing f.cf_meta) && not (Meta.has Meta.Impl f.cf_meta) then
-				let f = { f with cf_type = opt_type f.cf_type } in
-				let monos = List.map (fun _ -> mk_mono()) f.cf_params in
-				let map = apply_params f.cf_params monos in
-				match follow (map f.cf_type) with
-				| TFun((_,_,TType({t_path=["haxe";"macro"], "ExprOf"}, [t])) :: args, ret)
-				| TFun((_,_,t) :: args, ret) ->
-					(try
-						unify_raise ctx (dup e.etype) t e.epos;
-						List.iter2 (fun m (name,t) -> match follow t with
-							| TInst ({ cl_kind = KTypeParameter constr },_) when constr <> [] ->
-								List.iter (fun tc -> unify_raise ctx m (map tc) e.epos) constr
-							| _ -> ()
-						) monos f.cf_params;
-						if not (can_access ctx c f true) || follow e.etype == t_dynamic && follow t != t_dynamic then
-							()
-						else begin
-							let f = prepare_using_field f in
-							let f = { f with cf_params = []; cf_public = true; cf_type = TFun(args,ret) } in
-							acc := PMap.add f.cf_name f (!acc)
-						end
-					with Error (Unify _,_) -> ())
-				| _ -> ()
-			) c.cl_ordered_statics;
-			!acc
-	in
-	let use_methods = match follow e.etype with TMono _ -> PMap.empty | _ -> loop (loop PMap.empty ctx.g.global_using) ctx.m.module_using in
-	let fields = PMap.fold (fun f acc -> PMap.add f.cf_name f acc) fields use_methods in
-	let fields = match fst e_ast with
+	(* Add special `.code` field if we have a string of length 1 *)
+	let items = match fst e_ast with
 		| EConst(String s) when String.length s = 1 ->
 			let cf = mk_field "code" ctx.t.tint e.epos null_pos in
 			cf.cf_doc <- Some "The character code of this character (inlined at compile-time).";
 			cf.cf_kind <- Var { v_read = AccNormal; v_write = AccNever };
-			PMap.add cf.cf_name cf fields
+			let item = ITClassField (CompletionClassField.make cf CFSStatic BuiltIn true) in
+			PMap.add cf.cf_name item PMap.empty
 		| _ ->
-			fields
-	in
-	let fields = PMap.fold (fun f acc -> if Meta.has Meta.NoCompletion f.cf_meta then acc else f :: acc) fields [] in
-	let open Display in
-	let get_field acc f =
-		List.fold_left (fun acc f ->
-			if not f.cf_public then acc
-			else (ITClassField(f,CFSMember)) :: acc
-		) acc (f :: f.cf_overloads)
+			PMap.empty
 	in
-	let fields = List.fold_left get_field [] fields in
+	(* Collect fields of the type *)
+	let items = loop items e.etype in
+	(* Add static extensions *)
+	let items = collect_static_extensions ctx items e p in
+	let items = PMap.fold (fun item acc -> item :: acc) items [] in
 	try
 		let sl = string_list_of_expr_path_raise e_ast in
-		fields @ get_submodule_fields ctx (List.tl sl,List.hd sl)
+		(* Add submodule fields *)
+		items @ get_submodule_fields ctx (List.tl sl,List.hd sl)
 	with Exit | Not_found ->
-		fields
+		items

+ 21 - 12
src/context/display/displayJson.ml

@@ -105,10 +105,10 @@ let parse_input com input report_times pre_compilation did_something =
 			| JBool b -> b
 			| _ -> raise_haxe_json_error id (BadType(desc,"Bool"))
 		in
-		let get_array desc j = match j with
+		(* let get_array desc j = match j with
 			| JArray a -> a
 			| _ -> raise_haxe_json_error id (BadType(desc,"Array"))
-		in
+		in *)
 		let get_object desc j = match j with
 			| JObject o -> o
 			| _ -> raise_haxe_json_error id (BadType(desc,"Object"))
@@ -116,13 +116,13 @@ let parse_input com input report_times pre_compilation did_something =
 		let get_string_field desc name fl = get_string desc (get_field desc fl name) in
 		let get_int_field desc name fl = get_int desc (get_field desc fl name) in
 		let get_bool_field desc name fl = get_bool desc (get_field desc fl name) in
-		let get_array_field desc name fl = get_array desc (get_field desc fl name) in
-		(* let get_object_field desc name fl = get_object desc (get_field desc fl name) in *)
+		(* let get_array_field desc name fl = get_array desc (get_field desc fl name) in *)
+		let get_object_field desc name fl = get_object desc (get_field desc fl name) in
 		let get_string_param name = get_string_field "params" name params in
 		let get_int_param name = get_int_field "params" name params in
 		let get_bool_param name = get_bool_field "params" name params in
-		let get_array_param name = get_array_field "params" name params in
-		(* let get_object_param name = get_object_field "params" name params in *)
+		(* let get_array_param name = get_array_field "params" name params in *)
+		let get_object_param name = get_object_field "params" name params in
 		let get_opt_param f def = try f() with JsonRpc_error _ -> def in
 		let enable_display mode =
 			com.display <- create mode;
@@ -215,18 +215,27 @@ let parse_input com input report_times pre_compilation did_something =
 				let path = Path.parse_path (get_string_param "path") in
 				let m = try CompilationServer.find_module cs (path,sign) with Not_found -> f_error [jstring "No such module"] in
 				f_result (generate_module () m)
+			| "server/invalidate" ->
+				let file = get_string_param "file" in
+				let file = Path.unique_full_path file in
+				CompilationServer.taint_modules cs file;
+				f_result jnull
 			| "server/configure" ->
-				let l = List.map (fun j ->
-					let fl = get_object "print param" j in
-					let name = get_string_field "print param" "name" fl in
-					let value = get_bool_field "print param" "value" fl in
+				let l = ref (List.map (fun (name,value) ->
+					let value = get_bool "value" value in
 					try
 						ServerMessage.set_by_name name value;
 						jstring (Printf.sprintf "Printing %s %s" name (if value then "enabled" else "disabled"))
 					with Not_found ->
 						f_error [jstring ("Invalid print parame name: " ^ name)]
-				) (get_array_param "print") in
-				f_result (jarray l)
+				) (get_opt_param (fun () -> (get_object_param "print")) [])) in
+				get_opt_param (fun () ->
+					let b = get_bool_param "noModuleChecks" in
+					ServerConfig.do_not_check_modules := b;
+					l := jstring ("Module checks " ^ (if b then "disabled" else "enabled")) :: !l;
+					()
+				) ();
+				f_result (jarray !l)
 			| _ -> raise_method_not_found id name
 		in
 		f();

+ 94 - 56
src/context/display/displayToplevel.ml

@@ -18,10 +18,11 @@
 *)
 open Ast
 open Common
-open Common.CompilationServer
+open CompilationServer
 open Type
 open Typecore
 open CompletionItem
+open ClassFieldOrigin
 open DisplayTypes
 open Genjson
 
@@ -40,7 +41,7 @@ let explore_class_paths com timer class_paths recusive f_pack f_module =
 								| _ -> raise Not_found
 							end
 						with Not_found ->
-							f_pack file;
+							f_pack (List.rev pack,file);
 							if recusive then loop (dir ^ file ^ "/") (file :: pack)
 						end
 					| _ ->
@@ -77,12 +78,14 @@ module CollectionContext = struct
 	open ImportStatus
 
 	type t = {
+		ctx   : typer;
 		items : CompletionItem.t DynArray.t;
 		names : (string,CompletionItem.t) Hashtbl.t;
 		paths : (Globals.path,bool) Hashtbl.t;
 	}
 
-	let create () = {
+	let create ctx = {
+		ctx = ctx;
 		items = DynArray.create ();
 		names = Hashtbl.create 0;
 		paths = Hashtbl.create 0;
@@ -90,7 +93,9 @@ module CollectionContext = struct
 
 	let add_item ctx item name =
 		DynArray.add ctx.items item;
-		Hashtbl.replace ctx.names name item
+		match name with
+		| None -> ()
+		| Some name -> Hashtbl.replace ctx.names name item
 
 	let get_import_status ctx is_import path =
 		try
@@ -98,7 +103,13 @@ module CollectionContext = struct
 			(* TODO: do we have to check if we get the same thing? *)
 			Shadowed
 		with Not_found ->
-			if is_import || (fst path = []) then Imported else Unimported
+			let check_wildcard () =
+				List.exists (fun (sl,_) -> (sl,snd path) = path) ctx.ctx.m.wildcard_packages
+			in
+			if is_import || (fst path = []) || check_wildcard () then Imported else Unimported
+
+	let is_qualified ctx name =
+		not (Hashtbl.mem ctx.names name)
 
 	let path_exists ctx path = Hashtbl.mem ctx.paths path
 	let add_path ctx path = Hashtbl.add ctx.paths path true
@@ -108,13 +119,13 @@ open CollectionContext
 
 let collect ctx only_types with_type =
 	let t = Timer.timer ["display";"toplevel"] in
-	let cctx = CollectionContext.create () in
+	let cctx = CollectionContext.create ctx in
 	let packages = Hashtbl.create 0 in
-	let add_package s = Hashtbl.replace packages s true in
+	let add_package path = Hashtbl.replace packages path true in
 
 	let add item name = add_item cctx item name in
 
-	let add_type rm mt =
+	let add_type mt =
 		match mt with
 		| TClassDecl {cl_kind = KAbstractImpl _} -> ()
 		| _ ->
@@ -124,8 +135,8 @@ let collect ctx only_types with_type =
 				| TClassDecl c | TAbstractDecl { a_impl = Some c } when Meta.has Meta.CoreApi c.cl_meta ->
 					!merge_core_doc_ref ctx c
 				| _ -> ());
-				let is = get_import_status cctx true path in
-				add (ITType(CompletionModuleType.of_module_type is mt,rm)) (snd path);
+                let is = get_import_status cctx true path in
+				add (ITType(CompletionModuleType.of_module_type mt,is)) (Some (snd path));
 				add_path cctx path;
 			end
 	in
@@ -133,19 +144,18 @@ let collect ctx only_types with_type =
 	let process_decls pack name decls =
 		let run () = List.iter (fun (d,p) ->
 			begin try
-				let tname = match d with
-					| EClass d -> fst d.d_name
-					| EEnum d -> fst d.d_name
-					| ETypedef d -> fst d.d_name
-					| EAbstract d -> fst d.d_name
+				let tname,is_private = match d with
+					| EClass d -> fst d.d_name,List.mem HPrivate d.d_flags
+					| EEnum d -> fst d.d_name,List.mem EPrivate d.d_flags
+					| ETypedef d -> fst d.d_name,List.mem EPrivate d.d_flags
+					| EAbstract d -> fst d.d_name,List.mem AbPrivate d.d_flags
 					| _ -> raise Exit
 				in
 				let path = (pack,tname) in
-				if not (path_exists cctx path) then begin
+				if not (path_exists cctx path) && not is_private then begin
 					add_path cctx path;
-					let rm = RMOtherModule(pack,name) in
 					let is = get_import_status cctx false path in
-					add (ITType(CompletionModuleType.of_type_decl is pack name (d,p),rm)) tname
+					add (ITType(CompletionModuleType.of_type_decl pack name (d,p),is)) None
 				end
 			with Exit ->
 				()
@@ -160,33 +170,43 @@ let collect ctx only_types with_type =
 		(* locals *)
 		PMap.iter (fun _ v ->
 			if not (is_gen_local v) then
-				add (ITLocal v) v.v_name
+				add (ITLocal v) (Some v.v_name)
 		) ctx.locals;
 
-		(* member vars *)
+		let add_field scope origin cf =
+			let is_qualified = is_qualified cctx cf.cf_name in
+			add (ITClassField(CompletionClassField.make cf scope origin is_qualified)) (Some cf.cf_name)
+		in
+		let maybe_add_field scope origin cf =
+			if not (Meta.has Meta.NoCompletion cf.cf_meta) then add_field scope origin cf
+		in
+		(* member fields *)
 		if ctx.curfun <> FunStatic then begin
-			let seen = ref [] in
-			let rec loop c =
-				List.iter (fun cf ->
-					if not (Meta.has Meta.NoCompletion cf.cf_meta) && not (List.mem cf.cf_name !seen) then begin
-						seen := cf.cf_name :: !seen;
-						add (ITClassField(cf,CFSStatic)) cf.cf_name
-					end;
-				) c.cl_ordered_fields;
-				match c.cl_super with
-					| None ->
-						()
-					| Some (csup,tl) ->
-						loop csup; (* TODO: type parameters *)
-			in
-			loop ctx.curclass;
+			let all_fields = Type.TClass.get_all_fields ctx.curclass (List.map snd ctx.curclass.cl_params) in
+			PMap.iter (fun _ (c,cf) ->
+				let origin = if c == ctx.curclass then Self (TClassDecl c) else Parent (TClassDecl c) in
+				maybe_add_field CFSMember origin cf
+			) all_fields;
 			(* TODO: local using? *)
 		end;
 
 		(* statics *)
-		List.iter (fun cf ->
-			if not (Meta.has Meta.NoCompletion cf.cf_meta) then add (ITClassField(cf,CFSStatic)) cf.cf_name
-		) ctx.curclass.cl_ordered_statics;
+		begin match ctx.curclass.cl_kind with
+		| KAbstractImpl ({a_impl = Some c} as a) ->
+			let origin = Self (TAbstractDecl a) in
+			List.iter (fun cf ->
+				if Meta.has Meta.Impl cf.cf_meta then begin
+					if ctx.curfun = FunStatic then ()
+					else begin
+						let cf = prepare_using_field cf in
+						maybe_add_field CFSMember origin cf
+					end
+				end else
+					maybe_add_field CFSStatic origin cf
+			) c.cl_ordered_statics
+		| _ ->
+			List.iter (maybe_add_field CFSStatic (Self (TClassDecl ctx.curclass))) ctx.curclass.cl_ordered_statics
+		end;
 
 		(* enum constructors *)
 		let rec enum_ctors t =
@@ -194,7 +214,8 @@ let collect ctx only_types with_type =
 			| TAbstractDecl ({a_impl = Some c} as a) when Meta.has Meta.Enum a.a_meta && not (path_exists cctx a.a_path) ->
 				add_path cctx a.a_path;
 				List.iter (fun cf ->
-					if (Meta.has Meta.Enum cf.cf_meta) && not (Meta.has Meta.NoCompletion cf.cf_meta) then add (ITEnumAbstractField(a,cf)) cf.cf_name;
+					let ccf = CompletionClassField.make cf CFSMember (Self (TClassDecl c)) true in
+					if (Meta.has Meta.Enum cf.cf_meta) && not (Meta.has Meta.NoCompletion cf.cf_meta) then add (ITEnumAbstractField(a,ccf)) (Some cf.cf_name);
 				) c.cl_ordered_statics
 			| TTypeDecl t ->
 				begin match follow t.t_type with
@@ -203,8 +224,10 @@ let collect ctx only_types with_type =
 				end
 			| TEnumDecl e when not (path_exists cctx e.e_path) ->
 				add_path cctx e.e_path;
+				let origin = Self (TEnumDecl e) in
 				PMap.iter (fun _ ef ->
-					add (ITEnumField(e,ef)) ef.ef_name
+					let is_qualified = is_qualified cctx ef.ef_name in
+					add (ITEnumField(CompletionEnumField.make ef origin is_qualified)) (Some ef.ef_name)
 				) e.e_constrs;
 			| _ ->
 				()
@@ -220,27 +243,38 @@ let collect ctx only_types with_type =
 		end;
 
 		(* imported globals *)
-		PMap.iter (fun _ (mt,s,_) ->
+		PMap.iter (fun name (mt,s,_) ->
 			try
+				let is_qualified = is_qualified cctx name in
+				let class_import c =
+					let cf = PMap.find s c.cl_statics in
+					let cf = if name = cf.cf_name then cf else {cf with cf_name = name} in
+					let origin = StaticImport (TClassDecl c) in
+					add (ITClassField (CompletionClassField.make cf CFSStatic origin is_qualified)) (Some name)
+				in
 				match resolve_typedef mt with
-					| TClassDecl c -> add (ITClassField ((PMap.find s c.cl_statics,CFSStatic))) s
-					| TEnumDecl en -> add (ITEnumField (en,(PMap.find s en.e_constrs))) s
-					| TAbstractDecl {a_impl = Some c} -> add (ITClassField(PMap.find s c.cl_statics,CFSStatic)) s
+					| TClassDecl c -> class_import c;
+					| TEnumDecl en ->
+						let ef = PMap.find s en.e_constrs in
+						let ef = if name = ef.ef_name then ef else {ef with ef_name = name} in
+						let origin = StaticImport (TEnumDecl en) in
+						add (ITEnumField (CompletionEnumField.make ef origin is_qualified)) (Some s)
+					| TAbstractDecl {a_impl = Some c} -> class_import c;
 					| _ -> raise Not_found
 			with Not_found ->
 				()
 		) ctx.m.module_globals;
 
 		(* literals *)
-		add (ITLiteral("null",t_dynamic)) "null";
-		add (ITLiteral("true",ctx.com.basic.tbool)) "true";
-		add (ITLiteral("false",ctx.com.basic.tbool)) "false";
+		add (ITLiteral("null",t_dynamic)) (Some "null");
+		add (ITLiteral("true",ctx.com.basic.tbool)) (Some "true");
+		add (ITLiteral("false",ctx.com.basic.tbool)) (Some "false");
 		begin match ctx.curfun with
 			| FunMember | FunConstructor | FunMemberClassLocal ->
 				let t = TInst(ctx.curclass,List.map snd ctx.curclass.cl_params) in
-				add (ITLiteral("this",t)) "this";
+				add (ITLiteral("this",t)) (Some "this");
 				begin match ctx.curclass.cl_super with
-					| Some(c,tl) -> add (ITLiteral("super",TInst(c,tl))) "super"
+					| Some(c,tl) -> add (ITLiteral("super",TInst(c,tl))) (Some "super")
 					| None -> ()
 				end
 			| _ ->
@@ -252,25 +286,25 @@ let collect ctx only_types with_type =
 			Function; Var; If; Else; While; Do; For; Break; Return; Continue; Switch;
 			Try; New; Throw; Untyped; Cast;
 		] in
-		List.iter (fun kwd -> add(ITKeyword(kwd)) (s_keyword kwd)) kwds;
+		List.iter (fun kwd -> add(ITKeyword(kwd)) (Some (s_keyword kwd))) kwds;
 
 		(* builtins *)
-		add (ITLiteral("trace", TFun(["value",false,t_dynamic],ctx.com.basic.tvoid))) "trace"
+		add (ITLiteral("trace", TFun(["value",false,t_dynamic],ctx.com.basic.tvoid))) (Some "trace")
 	end;
 
 	(* type params *)
 	List.iter (fun (s,t) -> match follow t with
 		| TInst(c,_) ->
 			(* This is weird, might want to use something else for type parameters *)
-			add (ITType (CompletionModuleType.of_module_type ImportStatus.Imported (TClassDecl c),RMTypeParameter)) s
+			add (ITType (CompletionModuleType.of_module_type (TClassDecl c),ImportStatus.Imported)) (Some s)
 		| _ -> assert false
 	) ctx.type_params;
 
 	(* module types *)
-	List.iter (add_type RMLocalModule) ctx.m.curmod.m_types;
+	List.iter add_type ctx.m.curmod.m_types;
 
 	(* module imports *)
-	List.iter (add_type RMImport) (List.rev_map fst ctx.m.module_types); (* reverse! *)
+	List.iter add_type (List.rev_map fst ctx.m.module_types); (* reverse! *)
 
 	(* types from files *)
 	begin match !CompilationServer.instance with
@@ -301,13 +335,17 @@ let collect ctx only_types with_type =
 			| Some name ->
 				name
 			in
+			begin match List.rev cfile.c_package with
+				| [] -> ()
+				| s :: sl -> add_package (List.rev sl,s)
+			end;
 			Hashtbl.replace ctx.com.module_to_file (cfile.c_package,module_name) file;
 			process_decls cfile.c_package module_name cfile.c_decls
 		)
 	end;
 
-	Hashtbl.iter (fun pack _ ->
-		add (ITPackage pack) pack
+	Hashtbl.iter (fun path _ ->
+		add (ITPackage(path,[])) (Some (snd path))
 	) packages;
 
 	(* sorting *)

+ 130 - 41
src/core/display/completionItem.ml

@@ -56,11 +56,10 @@ module CompletionModuleType = struct
 		doc : documentation;
 		is_extern : bool;
 		kind : CompletionModuleKind.t;
-		import_status : ImportStatus.t;
 		has_constructor : not_bool;
 	}
 
-	let of_type_decl is pack module_name (td,p) = match td with
+	let of_type_decl pack module_name (td,p) = match td with
 		| EClass d ->
 			let ctor = if (List.exists (fun cff -> fst cff.cff_name = "new") d.d_data) then Yes
 				else if (List.exists (function HExtends _ -> true | _ -> false) d.d_flags) then Maybe
@@ -77,7 +76,6 @@ module CompletionModuleType = struct
 				doc = d.d_doc;
 				is_extern = List.mem HExtern d.d_flags;
 				kind = if List.mem HInterface d.d_flags then Interface else Class;
-				import_status = is;
 				has_constructor = ctor;
 			}
 		| EEnum d -> {
@@ -91,7 +89,6 @@ module CompletionModuleType = struct
 				doc = d.d_doc;
 				is_extern = List.mem EExtern d.d_flags;
 				kind = Enum;
-				import_status = is;
 				has_constructor = No;
 			}
 		| ETypedef d ->
@@ -107,7 +104,6 @@ module CompletionModuleType = struct
 				doc = d.d_doc;
 				is_extern = List.mem EExtern d.d_flags;
 				kind = kind;
-				import_status = is;
 				has_constructor = if kind = Struct then No else Maybe;
 			}
 		| EAbstract d -> {
@@ -121,13 +117,12 @@ module CompletionModuleType = struct
 				doc = d.d_doc;
 				is_extern = List.mem AbExtern d.d_flags;
 				kind = if Meta.has Meta.Enum d.d_meta then EnumAbstract else Abstract;
-				import_status = is;
 				has_constructor = if (List.exists (fun cff -> fst cff.cff_name = "new") d.d_data) then Yes else No;
 			}
 		| EImport _ | EUsing _ ->
 			raise Exit
 
-	let of_module_type is mt =
+	let of_module_type mt =
 		let is_extern,kind,has_ctor = match mt with
 			| TClassDecl c ->
 				c.cl_extern,(if c.cl_interface then Interface else Class),has_constructor c
@@ -164,20 +159,19 @@ module CompletionModuleType = struct
 			doc = infos.mt_doc;
 			is_extern = is_extern;
 			kind = kind;
-			import_status = is;
 			has_constructor = if has_ctor then Yes else No;
 		}
 
 	let get_path cm = (cm.pack,cm.name)
 
-	let to_json ctx cm =
+	let to_json ctx cm is =
 		let fields =
 			("pack",jlist jstring cm.pack) ::
 			("name",jstring cm.name) ::
 			("moduleName",jstring cm.module_name) ::
 			("isPrivate",jbool cm.is_private) ::
 			("kind",jint (to_int cm.kind)) ::
-			("importStatus",jint (ImportStatus.to_int cm.import_status)) ::
+			("importStatus",jint (ImportStatus.to_int is)) ::
 			(match ctx.generation_mode with
 			| GMFull | GMWithoutDoc ->
 				("pos",generate_pos ctx cm.pos) ::
@@ -190,31 +184,89 @@ module CompletionModuleType = struct
 			)
 		in
 		jobject fields
+end
+
+module ClassFieldOrigin = struct
+	type t =
+		| Self of module_type
+		| StaticImport of module_type
+		| Parent of module_type
+		| StaticExtension of module_type
+		| AnonymousStructure of tanon
+		| BuiltIn
 
+	let to_json ctx cfo =
+		let i,args = match cfo with
+		| Self mt -> 0,if ctx.generation_mode = GMMinimum then None else Some (generate_module_type ctx mt)
+		| StaticImport mt -> 1,if ctx.generation_mode = GMMinimum then None else Some (generate_module_type ctx mt)
+		| Parent mt -> 2,if ctx.generation_mode = GMMinimum then None else Some (generate_module_type ctx mt)
+		| StaticExtension mt -> 3,if ctx.generation_mode = GMMinimum then None else Some (generate_module_type ctx mt)
+		| AnonymousStructure an -> 4,if ctx.generation_mode = GMMinimum then None else Some (generate_anon ctx an)
+		| BuiltIn -> 5,None
+		in
+		jobject (
+			("kind",jint i) :: (match args with None -> [] | Some arg -> ["args",arg])
+		)
 end
 
-open CompletionModuleType
+module CompletionClassField = struct
+	type t = {
+		field : tclass_field;
+		scope : class_field_scope;
+		origin : ClassFieldOrigin.t;
+		is_qualified : bool;
+	}
 
-type resolution_mode =
-	| RMLocalModule
-	| RMImport
-	| RMUsing
-	| RMTypeParameter
-	| RMClassPath
-	| RMOtherModule of path
+	let make cf scope origin is_qualified = {
+		field = cf;
+		scope = scope;
+		origin = origin;
+		is_qualified = is_qualified;
+	}
+end
+
+module CompletionEnumField = struct
+	type t = {
+		efield : tenum_field;
+		eorigin : ClassFieldOrigin.t;
+		eis_qualified : bool;
+	}
+
+	let make ef origin is_qualified = {
+		efield = ef;
+		eorigin = origin;
+		eis_qualified = is_qualified;
+	}
+end
+
+module PackageContentKind = struct
+	type t =
+		| PCKModule
+		| PCKPackage
+
+	let to_int = function
+		| PCKModule -> 0
+		| PCKPackage -> 1
+end
+
+open CompletionModuleType
+open CompletionClassField
+open CompletionEnumField
 
 type t =
 	| ITLocal of tvar
-	| ITClassField of tclass_field * class_field_scope
-	| ITEnumField of tenum * tenum_field
-	| ITEnumAbstractField of tabstract * tclass_field
-	| ITType of CompletionModuleType.t * resolution_mode
-	| ITPackage of string
+	| ITClassField of CompletionClassField.t
+	| ITEnumField of CompletionEnumField.t
+	| ITEnumAbstractField of tabstract * CompletionClassField.t
+	| ITType of CompletionModuleType.t * ImportStatus.t
+	| ITPackage of path * (string * PackageContentKind.t) list
 	| ITModule of string
 	| ITLiteral of string * Type.t
 	| ITTimer of string * string
 	| ITMetadata of string * documentation
 	| ITKeyword of keyword
+	| ITAnonymous of tanon
+	| ITExpression of texpr
 
 let get_index = function
 	| ITLocal _ -> 0
@@ -228,11 +280,13 @@ let get_index = function
 	| ITTimer _ -> 8
 	| ITMetadata _ -> 9
 	| ITKeyword _ -> 10
+	| ITAnonymous _ -> 11
+	| ITExpression _ -> 12
 
 let get_sort_index = function
 	| ITLocal _ -> 0
 	| ITClassField _ -> 0
-	| ITEnumField(_,ef) -> ef.ef_index
+	| ITEnumField ef -> ef.efield.ef_index
 	| ITEnumAbstractField _ -> 0
 	| ITType _ -> 0
 	| ITPackage _ -> 0
@@ -241,59 +295,92 @@ let get_sort_index = function
 	| ITTimer _ -> 0
 	| ITMetadata _ -> 0
 	| ITKeyword _ -> 0
+	| ITAnonymous _ -> 0
+	| ITExpression _ -> 0
 
 let legacy_sort = function
-	| ITClassField(cf,_) | ITEnumAbstractField(_,cf) ->
-		begin match cf.cf_kind with
-		| Var _ -> 0,cf.cf_name
-		| Method _ -> 1,cf.cf_name
+	| ITClassField(cf) | ITEnumAbstractField(_,cf) ->
+		begin match cf.field.cf_kind with
+		| Var _ -> 0,cf.field.cf_name
+		| Method _ -> 1,cf.field.cf_name
 		end
-	| ITEnumField(_,ef) ->
+	| ITEnumField ef ->
+		let ef = ef.efield in
 		begin match follow ef.ef_type with
 		| TFun _ -> 1,ef.ef_name
 		| _ -> 0,ef.ef_name
 		end
 	| ITType(cm,_) -> 2,cm.name
 	| ITModule s -> 3,s
-	| ITPackage s -> 4,s
+	| ITPackage(path,_) -> 4,snd path
 	| ITMetadata(s,_) -> 5,s
 	| ITTimer(s,_) -> 6,s
 	| ITLocal v -> 7,v.v_name
 	| ITLiteral(s,_) -> 9,s
 	| ITKeyword kwd -> 10,s_keyword kwd
+	| ITAnonymous _ -> 11,""
+	| ITExpression _ -> 12,""
 
 let get_name = function
 	| ITLocal v -> v.v_name
-	| ITClassField(cf,_) | ITEnumAbstractField(_,cf) -> cf.cf_name
-	| ITEnumField(_,ef) -> ef.ef_name
+	| ITClassField(cf) | ITEnumAbstractField(_,cf) -> cf.field.cf_name
+	| ITEnumField ef -> ef.efield.ef_name
 	| ITType(cm,_) -> cm.name
-	| ITPackage s -> s
+	| ITPackage(path,_) -> snd path
 	| ITModule s -> s
 	| ITLiteral(s,_) -> s
 	| ITTimer(s,_) -> s
 	| ITMetadata(s,_) -> s
 	| ITKeyword kwd -> s_keyword kwd
+	| ITAnonymous _ -> ""
+	| ITExpression _ -> ""
 
 let get_type = function
 	| ITLocal v -> v.v_type
-	| ITClassField(cf,_) | ITEnumAbstractField(_,cf) -> cf.cf_type
-	| ITEnumField(_,ef) -> ef.ef_type
-	| ITType(_,_) -> t_dynamic
+	| ITClassField(cf) | ITEnumAbstractField(_,cf) -> cf.field.cf_type
+	| ITEnumField ef -> ef.efield.ef_type
+	| ITType(_,_) -> t_dynamic (* TODO: might want a type here, not sure *)
 	| ITPackage _ -> t_dynamic
 	| ITModule _ -> t_dynamic
 	| ITLiteral(_,t) -> t
 	| ITTimer(_,_) -> t_dynamic
 	| ITMetadata(_,_) -> t_dynamic
 	| ITKeyword _ -> t_dynamic
+	| ITAnonymous an -> TAnon an
+	| ITExpression e -> e.etype
 
 let to_json ctx ck =
 	let kind,data = match ck with
 		| ITLocal v -> "Local",generate_tvar ctx v
-		| ITClassField(cf,cfs) -> "ClassField",generate_class_field ctx cfs cf
-		| ITEnumField(_,ef) -> "EnumField",generate_enum_field ctx ef
-		| ITEnumAbstractField(_,cf) -> "EnumAbstractField",generate_class_field ctx CFSMember cf
-		| ITType(kind,rm) -> "Type",CompletionModuleType.to_json ctx kind
-		| ITPackage s -> "Package",jstring s
+		| ITClassField(cf) | ITEnumAbstractField(_,cf) ->
+			let name = match ck with
+				| ITClassField _ -> "ClassField"
+				| _ ->  "EnumAbstractField"
+			in
+			name,jobject [
+			"field",generate_class_field ctx cf.scope cf.field;
+			"origin",ClassFieldOrigin.to_json ctx cf.origin;
+			"resolution",jobject [
+				"isQualified",jbool cf.is_qualified;
+			]
+		]
+		| ITEnumField ef -> "EnumField",jobject [
+			"field",generate_enum_field ctx ef.efield;
+			"origin",ClassFieldOrigin.to_json ctx ef.eorigin;
+			"resolution",jobject [
+				"isQualified",jbool ef.eis_qualified;
+			]
+		]
+		| ITType(kind,is) -> "Type",CompletionModuleType.to_json ctx kind is
+		| ITPackage(path,contents) ->
+			let generate_package_content (name,kind) = jobject [
+				"name",jstring name;
+				"kind",jint (PackageContentKind.to_int kind);
+			] in
+			"Package",jobject [
+				"path",generate_path path;
+				"contents",jlist generate_package_content contents;
+			]
 		| ITModule s -> "Module",jstring s
 		| ITLiteral(s,t) -> "Literal",jobject [
 			"name",jstring s;
@@ -310,5 +397,7 @@ let to_json ctx ck =
 		| ITKeyword kwd ->"Keyword",jobject [
 			"name",jstring (s_keyword kwd)
 		]
+		| ITAnonymous an -> "AnonymousStructure",generate_anon ctx an
+		| ITExpression e -> "Expression",generate_texpr ctx e
 	in
 	generate_adt ctx None kind (Some data)

+ 29 - 6
src/core/displayTypes.ml

@@ -65,7 +65,7 @@ end
 
 module CompletionResultKind = struct
 	type t =
-		| CRField
+		| CRField of CompletionItem.t * pos
 		| CRStructureField
 		| CRToplevel
 		| CRMetadata
@@ -79,6 +79,32 @@ module CompletionResultKind = struct
 		| CRPattern
 		| CROverride
 		| CRTypeRelation
+
+	let to_json ctx kind =
+		let i,args = match kind with
+			| CRField(item,p) -> 0,Some (jobject [
+				"item",CompletionItem.to_json ctx item;
+				"range",generate_pos_as_range p;
+				"type",generate_type ctx (CompletionItem.get_type item);
+			])
+			| CRStructureField -> 1,None
+			| CRToplevel -> 2,None
+			| CRMetadata -> 3,None
+			| CRTypeHint -> 4,None
+			| CRExtends -> 5,None
+			| CRImplements -> 6,None
+			| CRStructExtension -> 7,None
+			| CRImport -> 8,None
+			| CRUsing -> 9,None
+			| CRNew -> 10,None
+			| CRPattern -> 11,None
+			| CROverride -> 12,None
+			| CRTypeRelation -> 13,None
+		in
+		jobject (
+			("kind",jint i) :: (match args with None -> [] | Some arg -> ["args",arg])
+		)
+
 end
 
 module DisplayMode = struct
@@ -161,14 +187,11 @@ module DisplayMode = struct
 				dms_exit_during_typing = false;
 				dms_force_macro_typing = false;
 			}
-		| DMDiagnostics global -> { settings with
-				dms_full_typing = true;
+		| DMDiagnostics global -> { default_compilation_settings with
+				dms_kind = DMDiagnostics global;
 				dms_error_policy = EPCollect;
 				dms_collect_data = true;
-				dms_inline = true;
-				dms_force_macro_typing = true;
 				dms_display_file_policy = if global then DFPNo else DFPAlso;
-				dms_exit_during_typing = false;
 			}
 		| DMStatistics -> { settings with
 				dms_full_typing = true;

+ 24 - 23
src/core/json/genjson.ml

@@ -168,33 +168,34 @@ let rec generate_type ctx t =
 		| TEnum(en,tl) -> "TEnum",Some (generate_path_with_params ctx en.e_path tl)
 		| TType(td,tl) -> "TType",Some (generate_path_with_params ctx td.t_path tl)
 		| TAbstract(a,tl) -> "TAbstract",Some (generate_path_with_params ctx a.a_path tl)
-		| TAnon an -> "TAnonymous", Some(generate_anon an)
+		| TAnon an -> "TAnonymous", Some(generate_anon ctx an)
 		| TFun(tl,tr) -> "TFun", Some (jobject (generate_function_signature ctx tl tr))
-	and generate_anon an =
-		let generate_anon_fields () =
-			let fields = PMap.fold (fun cf acc -> generate_class_field ctx CFSMember cf :: acc) an.a_fields [] in
-			jarray fields
-		in
-		let generate_anon_status () =
-			let name,args = match !(an.a_status) with
-				| Closed -> "AClosed",None
-				| Opened -> "AOpened",None
-				| Const -> "AConst",None
-				| Extend tl -> "AExtend", Some (generate_types ctx tl)
-				| Statics c -> "AClassStatics",Some (class_ref ctx c)
-				| EnumStatics en -> "AEnumStatics",Some (enum_ref ctx en)
-				| AbstractStatics a -> "AAbstractStatics", Some (abstract_ref ctx a)
-			in
-			generate_adt ctx None name args
-		in
-		jobject [
-			"fields",generate_anon_fields();
-			"status",generate_anon_status ();
-		]
 	in
 	let name,args = loop t in
 	generate_adt ctx None name args
 
+and generate_anon ctx an =
+	let generate_anon_fields () =
+		let fields = PMap.fold (fun cf acc -> generate_class_field ctx CFSMember cf :: acc) an.a_fields [] in
+		jarray fields
+	in
+	let generate_anon_status () =
+		let name,args = match !(an.a_status) with
+			| Closed -> "AClosed",None
+			| Opened -> "AOpened",None
+			| Const -> "AConst",None
+			| Extend tl -> "AExtend", Some (generate_types ctx tl)
+			| Statics c -> "AClassStatics",Some (class_ref ctx c)
+			| EnumStatics en -> "AEnumStatics",Some (enum_ref ctx en)
+			| AbstractStatics a -> "AAbstractStatics", Some (abstract_ref ctx a)
+		in
+		generate_adt ctx None name args
+	in
+	jobject [
+		"fields",generate_anon_fields();
+		"status",generate_anon_status ();
+	]
+
 and generate_function_argument ctx (name,opt,t) =
 	jobject [
 		"name",jstring name;
@@ -291,7 +292,7 @@ and generate_class_field ctx cfs cf =
 		"expr",jopt (generate_texpr ctx) cf.cf_expr;
 		"pos",generate_pos ctx cf.cf_pos;
 		"doc",generate_doc ctx cf.cf_doc;
-		"overloads",jlist (classfield_ref ctx) cf.cf_overloads;
+		"overloads",jlist (generate_class_field ctx cfs) cf.cf_overloads;
 		"scope",jint (Obj.magic cfs);
 	]
 

+ 10 - 7
src/core/texpr.ml

@@ -4,14 +4,13 @@ open Type
 open Error
 
 let equal_fa fa1 fa2 = match fa1,fa2 with
-	| FStatic(c1,cf1),FStatic(c2,cf2) -> c1 == c2 && cf1 == cf2
-	| FInstance(c1,tl1,cf1),FInstance(c2,tl2,cf2) -> c1 == c2 && safe_for_all2 type_iseq tl1 tl2 && cf1 == cf2
-	(* TODO: This is technically not correct but unfortunately the compiler makes a distinct tclass_field for each anon field access. *)
+	| FStatic(c1,cf1),FStatic(c2,cf2) -> c1 == c2 && cf1.cf_name == cf2.cf_name
+	| FInstance(c1,tl1,cf1),FInstance(c2,tl2,cf2) -> c1 == c2 && safe_for_all2 type_iseq tl1 tl2 && cf1.cf_name == cf2.cf_name
 	| FAnon cf1,FAnon cf2 -> cf1.cf_name = cf2.cf_name
 	| FDynamic s1,FDynamic s2 -> s1 = s2
-	| FClosure(None,cf1),FClosure(None,cf2) -> cf1 == cf2
-	| FClosure(Some(c1,tl1),cf1),FClosure(Some(c2,tl2),cf2) -> c1 == c2 && safe_for_all2 type_iseq tl1 tl2 && cf1 == cf2
-	| FEnum(en1,ef1),FEnum(en2,ef2) -> en1 == en2 && ef1 == ef2
+	| FClosure(None,cf1),FClosure(None,cf2) -> cf1.cf_name == cf2.cf_name
+	| FClosure(Some(c1,tl1),cf1),FClosure(Some(c2,tl2),cf2) -> c1 == c2 && safe_for_all2 type_iseq tl1 tl2 && cf1.cf_name == cf2.cf_name
+	| FEnum(en1,ef1),FEnum(en2,ef2) -> en1 == en2 && ef1.ef_name == ef2.ef_name
 	| _ -> false
 
 let rec equal e1 e2 = match e1.eexpr,e2.eexpr with
@@ -20,7 +19,11 @@ let rec equal e1 e2 = match e1.eexpr,e2.eexpr with
 	| TArray(eb1,ei1),TArray(eb2,ei2) -> equal eb1 eb2 && equal ei1 ei2
 	| TBinop(op1,lhs1,rhs1),TBinop(op2,lhs2,rhs2) -> op1 = op2 && equal lhs1 lhs2 && equal rhs1 rhs2
 	| TField(e1,fa1),TField(e2,fa2) -> equal e1 e2 && equal_fa fa1 fa2
-	| TTypeExpr mt1,TTypeExpr mt2 -> mt1 == mt2
+	| TTypeExpr (TClassDecl c1),TTypeExpr (TClassDecl c2) -> c1 == c2
+	| TTypeExpr (TEnumDecl e1),TTypeExpr (TEnumDecl e2) -> e1 == e2
+	| TTypeExpr (TTypeDecl t1),TTypeExpr (TTypeDecl t2) -> t1 == t2
+	| TTypeExpr (TAbstractDecl a1),TTypeExpr (TAbstractDecl a2) -> a1 == a2
+	| TTypeExpr _,TTypeExpr _ -> false
 	| TParenthesis e1,TParenthesis e2 -> equal e1 e2
 	| TObjectDecl fl1,TObjectDecl fl2 -> safe_for_all2 (fun (s1,e1) (s2,e2) -> s1 = s2 && equal e1 e2) fl1 fl2
 	| (TArrayDecl el1,TArrayDecl el2) | (TBlock el1,TBlock el2) -> safe_for_all2 equal el1 el2

+ 16 - 9
src/core/type.ml

@@ -2766,18 +2766,25 @@ let abstract_module_type a tl = {
 }
 
 module TClass = struct
-	let get_all_super_fields c =
+	let get_member_fields' self_too c0 tl =
 		let rec loop acc c tl =
-			let maybe_add acc cf = match cf.cf_kind with
-				| Method MethNormal when not (PMap.mem cf.cf_name acc) -> PMap.add cf.cf_name cf acc
-				| _ -> acc
+			let apply = apply_params c.cl_params tl in
+			let maybe_add acc cf =
+				if not (PMap.mem cf.cf_name acc) then begin
+					let cf = if tl = [] then cf else {cf with cf_type = apply cf.cf_type} in
+					PMap.add cf.cf_name (c,cf) acc
+				end else acc
 			in
-			let acc = List.fold_left maybe_add acc c.cl_ordered_fields in
+			let acc = if self_too || c != c0 then List.fold_left maybe_add acc c.cl_ordered_fields else acc in
 			match c.cl_super with
-			| Some(c,tl) -> loop acc c tl
+			| Some(c,tl) -> loop acc c (List.map apply tl)
 			| None -> acc
 		in
-		match c.cl_super with
-			| Some(c,tl) -> loop PMap.empty c tl
-			| None -> PMap.empty
+		loop PMap.empty c0 tl
+
+	let get_all_super_fields c =
+		get_member_fields' false c (List.map snd c.cl_params)
+
+	let get_all_fields c tl =
+		get_member_fields' true c tl
 end

+ 32 - 47
src/syntax/grammar.mly

@@ -111,17 +111,17 @@ and parse_type_decls pack acc s =
 		| [< v = parse_type_decl; l = parse_type_decls pack (v :: acc) >] -> l
 		| [< >] -> List.rev acc
 	with
-	| TypePath ([],Some (name,false),b) ->
+	| TypePath ([],Some (name,false),b,p) ->
 		(* resolve imports *)
 		List.iter (fun d ->
 			match fst d with
 			| EImport (t,_) ->
 				(match List.rev t with
-				| (n,_) :: path when n = name && List.for_all (fun (i,_) -> is_lower_ident i) path -> raise (TypePath (List.map fst (List.rev path),Some (name,false),b))
+				| (n,_) :: path when n = name && List.for_all (fun (i,_) -> is_lower_ident i) path -> raise (TypePath (List.map fst (List.rev path),Some (name,false),b,p))
 				| _ -> ())
 			| _ -> ()
 		) acc;
-		raise (TypePath (pack,Some(name,true),b))
+		raise (TypePath (pack,Some(name,true),b,p))
 	| Stream.Error _ when do_resume() ->
 		ignore(resume false false s);
 		parse_type_decls pack acc s
@@ -220,20 +220,20 @@ and parse_class doc meta cflags need_name s =
 		}, punion p1 p2)
 
 and parse_import s p1 =
-	let rec loop acc =
+	let rec loop pn acc =
 		match s with parser
 		| [< '(Dot,p) >] ->
 			let resume() =
-				type_path (List.map fst acc) true
+				type_path (List.map fst acc) true (punion pn p)
 			in
 			check_resume p resume (fun () -> ());
 			(match s with parser
 			| [< '(Const (Ident k),p) >] ->
-				loop ((k,p) :: acc)
+				loop pn ((k,p) :: acc)
 			| [< '(Kwd Macro,p) >] ->
-				loop (("macro",p) :: acc)
+				loop pn (("macro",p) :: acc)
 			| [< '(Kwd Extern,p) >] ->
-				loop (("extern",p) :: acc)
+				loop pn (("extern",p) :: acc)
 			| [< '(Binop OpMult,_); '(Semicolon,p2) >] ->
 				p2, List.rev acc, IAll
 			| [< >] ->
@@ -248,29 +248,29 @@ and parse_import s p1 =
 			serror()
 	in
 	let p2, path, mode = (match s with parser
-		| [< '(Const (Ident name),p) >] -> loop [name,p]
+		| [< '(Const (Ident name),p) >] -> loop p [name,p]
 		| [< >] -> if would_skip_resume p1 s then p1, [], INormal else serror()
 	) in
 	(EImport (path,mode),punion p1 p2)
 
 and parse_using s p1 =
-	let rec loop acc =
+	let rec loop pn acc =
 		match s with parser
 		| [< '(Dot,p) >] ->
-			check_resume p (fun () -> type_path (List.map fst acc) false) (fun () -> ());
+			check_resume p (fun () -> type_path (List.map fst acc) false (punion pn p)) (fun () -> ());
 			begin match s with parser
 			| [< '(Const (Ident k),p) >] ->
-				loop ((k,p) :: acc)
+				loop pn ((k,p) :: acc)
 			| [< '(Kwd Macro,p) >] ->
-				loop (("macro",p) :: acc)
+				loop pn (("macro",p) :: acc)
 			| [< '(Kwd Extern,p) >] ->
-				loop (("extern",p) :: acc)
+				loop pn (("extern",p) :: acc)
 			end
 		| [< '(Semicolon,p2) >] ->
 			p2,List.rev acc
 	in
 	let p2, path = (match s with parser
-		| [< '(Const (Ident name),p) >] -> loop [name,p]
+		| [< '(Const (Ident name),p) >] -> loop p [name,p]
 		| [< >] -> if would_skip_resume p1 s then p1, [] else serror()
 	) in
 	(EUsing path,punion p1 p2)
@@ -377,7 +377,7 @@ and parse_meta_argument_expr s =
 	with Display e -> match fst e with
 		| EDisplay(e,_) ->
 			begin try
-				type_path (string_list_of_expr_path_raise e) false
+				type_path (string_list_of_expr_path_raise e) false (pos e)
 			with Exit ->
 				e
 			end
@@ -520,7 +520,7 @@ and parse_type_path2 p0 pack name p1 s =
 		(match s with parser
 		| [< '(Dot,p) >] ->
 			check_resume p
-				(fun () -> raise (TypePath (List.rev (name :: pack),None,false)))
+				(fun () -> raise (TypePath (List.rev (name :: pack),None,false,punion (match p0 with None -> p1 | Some p0 -> p0) p)))
 				(fun () -> parse_type_path1 (match p0 with None -> Some p1 | Some _ -> p0) (name :: pack) s)
 		| [< '(Semicolon,_) >] ->
 			error (Custom "Type name should start with an uppercase letter") p1
@@ -529,7 +529,7 @@ and parse_type_path2 p0 pack name p1 s =
 		let sub,p2 = (match s with parser
 			| [< '(Dot,p); s >] ->
 				(check_resume p
-					(fun () -> raise (TypePath (List.rev pack,Some (name,false),false)))
+					(fun () -> raise (TypePath (List.rev pack,Some (name,false),false,punion (match p0 with None -> p1 | Some p0 -> p0) p)))
 					(fun () -> match s with parser
 					| [< '(Const (Ident name),p2) when not (is_lower_ident name) >] -> Some name,p2
 					| [< >] -> serror()))
@@ -1122,13 +1122,8 @@ and expr = parser
 		| [< '(Const (Int i),p); e = expr_next (EConst (Int i),p) >] -> e
 		| [< '(Const (Float f),p); e = expr_next (EConst (Float f),p) >] -> e
 		| [< >] -> serror()) */*)
-	| [< '(Kwd For,p); '(POpen,_); it = expr; '(PClose,_); s >] ->
-		(try
-			let e = secure_expr s in
-			(EFor (it,e),punion p (pos e))
-		with
-			Display e -> display (EFor (it,e),punion p (pos e)))
-	| [< '(Kwd If,p); '(POpen,_); cond = expr; '(PClose,_); e1 = expr; s >] ->
+	| [< '(Kwd For,p); '(POpen,_); it = secure_expr; '(PClose,_); e = secure_expr >] -> (EFor (it,e),punion p (pos e))
+	| [< '(Kwd If,p); '(POpen,_); cond = secure_expr; '(PClose,_); e1 = secure_expr; s >] ->
 		let e2 = (match s with parser
 			| [< '(Kwd Else,_); e2 = expr; s >] -> Some e2
 			| [< >] ->
@@ -1144,17 +1139,12 @@ and expr = parser
 	| [< '(Kwd Return,p); e = popt toplevel_expr >] -> (EReturn e, match e with None -> p | Some e -> punion p (pos e))
 	| [< '(Kwd Break,p) >] -> (EBreak,p)
 	| [< '(Kwd Continue,p) >] -> (EContinue,p)
-	| [< '(Kwd While,p1); '(POpen,_); cond = expr; '(PClose,_); s >] ->
-		(try
-			let e = secure_expr s in
-			(EWhile (cond,e,NormalWhile),punion p1 (pos e))
-		with
-			Display e -> display (EWhile (cond,e,NormalWhile),punion p1 (pos e)))
-	| [< '(Kwd Do,p1); e = expr; '(Kwd While,_); '(POpen,_); cond = expr; '(PClose,_); s >] -> (EWhile (cond,e,DoWhile),punion p1 (pos e))
-	| [< '(Kwd Switch,p1); e = expr; '(BrOpen,_); cases , def = parse_switch_cases e []; '(BrClose,p2); s >] -> (ESwitch (e,cases,def),punion p1 p2)
-	| [< '(Kwd Try,p1); e = expr; cl,p2 = parse_catches e [] (pos e) >] -> (ETry (e,cl),punion p1 p2)
+	| [< '(Kwd While,p1); '(POpen,_); cond = secure_expr; '(PClose,_); e = secure_expr >] -> (EWhile (cond,e,NormalWhile),punion p1 (pos e))
+	| [< '(Kwd Do,p1); e = secure_expr; '(Kwd While,_); '(POpen,_); cond = secure_expr; '(PClose,_); s >] -> (EWhile (cond,e,DoWhile),punion p1 (pos e))
+	| [< '(Kwd Switch,p1); e = secure_expr; '(BrOpen,_); cases , def = parse_switch_cases e []; '(BrClose,p2); s >] -> (ESwitch (e,cases,def),punion p1 p2)
+	| [< '(Kwd Try,p1); e = secure_expr; cl,p2 = parse_catches e [] (pos e) >] -> (ETry (e,cl),punion p1 p2)
 	| [< '(IntInterval i,p1); e2 = expr >] -> make_binop OpInterval (EConst (Int i),p1) e2
-	| [< '(Kwd Untyped,p1); e = expr >] -> (EUntyped e,punion p1 (pos e))
+	| [< '(Kwd Untyped,p1); e = secure_expr >] -> (EUntyped e,punion p1 (pos e))
 	| [< '(Dollar v,p); s >] -> expr_next (EConst (Ident ("$"^v)),p) s
 
 and expr_next e1 s =
@@ -1201,12 +1191,7 @@ and expr_next' e1 = parser
 			make_binop OpGte e1 (secure_expr s)
 		| [< e2 = secure_expr >] ->
 			make_binop OpGt e1 e2)
-	| [< '(Binop op,_); s >] ->
-		(try
-			let e2 = secure_expr s in
-			make_binop op e1 e2
-		with Display e2 ->
-			raise (Display (make_binop op e1 e2)))
+	| [< '(Binop op,_); e2 = secure_expr >] -> make_binop op e1 e2
 	| [< '(Unop op,p) when is_postfix e1 op; s >] ->
 		expr_next (EUnop (op,Postfix,e1), punion (pos e1) p) s
 	| [< '(Question,_); e2 = expr; '(DblDot,_); e3 = expr >] ->
@@ -1254,12 +1239,7 @@ and parse_switch_cases eswitch cases = parser
 and parse_catch etry = parser
 	| [< '(Kwd Catch,p); '(POpen,_); name, pn = dollar_ident; s >] ->
 		match s with parser
-		| [< t,pt = parse_type_hint; '(PClose,_); s >] ->
-			(try
-				let e = secure_expr s in
-				((name,pn),(t,pt),e,punion p (pos e)),(pos e)
-			with
-				Display e -> display (ETry (etry,[(name,pn),(t,pt),e,(pos e)]),punion (pos etry) (pos e)))
+		| [< t,pt = parse_type_hint; '(PClose,_); e = secure_expr >] -> ((name,pn),(t,pt),e,punion p (pos e)),(pos e)
 		| [< '(_,p) >] -> error Missing_type p
 
 and parse_catches etry catches pmax = parser
@@ -1307,17 +1287,22 @@ and parse_call_params f p1 s =
 		| [< >] -> parse_next_param [] p1
 	end
 
+(* Parses an expression and catches Display exceptions. *)
 and toplevel_expr s =
 	try
 		expr s
 	with
 		Display e -> e
 
+(* Tries to parse a toplevel expression and defaults to a null expression when in display mode.
+   This function always accepts in display mode and should only be used for expected expressions,
+   not accepted ones! *)
 and secure_expr s =
 	match s with parser
 	| [< e = toplevel_expr >] -> e
 	| [< >] -> if do_resume() then mk_null_expr (punion_next (pos (last_token s)) s) else serror()
 
+(* Like secure_expr, but with a custom fail function *)
 and expr_or_fail fail s =
 	match s with parser
 	| [< e = expr >] -> e

+ 6 - 4
src/syntax/parser.ml

@@ -37,7 +37,7 @@ type syntax_completion =
 	| SCInterfaceRelation
 
 exception Error of error_msg * pos
-exception TypePath of string list * (string * bool) option * bool (* in import *)
+exception TypePath of string list * (string * bool) option * bool (* in import *) * pos
 exception Display of expr
 exception SyntaxCompletion of syntax_completion * pos
 
@@ -127,9 +127,9 @@ let display e = raise (Display e)
 let magic_display_field_name = " - display - "
 let magic_type_path = { tpackage = []; tname = ""; tparams = []; tsub = None }
 
-let type_path sl in_import = match sl with
-	| n :: l when n.[0] >= 'A' && n.[0] <= 'Z' -> raise (TypePath (List.rev l,Some (n,false),in_import));
-	| _ -> raise (TypePath (List.rev sl,None,in_import))
+let type_path sl in_import p = match sl with
+	| n :: l when n.[0] >= 'A' && n.[0] <= 'Z' -> raise (TypePath (List.rev l,Some (n,false),in_import,p));
+	| _ -> raise (TypePath (List.rev sl,None,in_import,p))
 
 let is_resuming_file file =
 	do_resume() && Path.unique_full_path file = !resume_display.pfile
@@ -151,6 +151,8 @@ let would_skip_resume p1 s =
 	| _ ->
 		false
 
+let cut_pos_at_display p = { p with pmax = !resume_display.pmax }
+
 let is_dollar_ident e = match fst e with
 	| EConst (Ident n) when n.[0] = '$' ->
 		true

+ 6 - 6
src/typing/typeload.ml

@@ -768,8 +768,8 @@ let string_list_of_expr_path (e,p) =
 let handle_path_display ctx path p =
 	let open ImportHandling in
 	match ImportHandling.convert_import_to_something_usable !Parser.resume_display path,ctx.com.display.dms_kind with
-		| (IDKPackage sl,_),_ ->
-			raise (Parser.TypePath(sl,None,true))
+		| (IDKPackage sl,p),_ ->
+			raise (Parser.TypePath(sl,None,true,p))
 		| (IDKModule(sl,s),_),DMDefinition ->
 			(* We assume that we want to go to the module file, not a specific type
 			   which might not even exist anyway. *)
@@ -793,12 +793,12 @@ let handle_path_display ctx path p =
 			with Not_found ->
 				()
 			end
-		| (IDKModule(sl,s),_),_ ->
-			raise (Parser.TypePath(sl,Some(s,false),true))
+		| (IDKModule(sl,s),p),_ ->
+			raise (Parser.TypePath(sl,Some(s,false),true,p))
 		| (IDKSubType(sl,sm,st),p),DMDefinition ->
 			resolve_position_by_path ctx { tpackage = sl; tname = sm; tparams = []; tsub = Some st} p
-		| (IDKSubType(sl,sm,st),_),_ ->
-			raise (Parser.TypePath(sl @ [sm],Some(st,false),true))
+		| (IDKSubType(sl,sm,st),p),_ ->
+			raise (Parser.TypePath(sl @ [sm],Some(st,false),true,p))
 		| ((IDKSubTypeField(sl,sm,st,sf) | IDKModuleField(sl,(sm as st),sf)),p),_ ->
 			let m = ctx.g.do_load_module ctx (sl,sm) p in
 			List.iter (fun t -> match t with

+ 1 - 1
src/typing/typeloadFields.ml

@@ -210,7 +210,7 @@ let transform_abstract_field com this_t a_t a f =
 		let init p = (EVars [("this",null_pos),Some this_t,None],p) in
 		let cast e = (ECast(e,None)),pos e in
 		let ret p = (EReturn (Some (cast (EConst (Ident "this"),p))),p) in
-		let meta = (Meta.Impl,[],null_pos) :: f.cff_meta in
+		let meta = (Meta.Impl,[],null_pos) :: (Meta.NoCompletion,[],null_pos) :: f.cff_meta in
 		if Meta.has Meta.MultiType a.a_meta then begin
 			if List.mem_assoc AInline f.cff_access then error "MultiType constructors cannot be inline" f.cff_pos;
 			if fu.f_expr <> None then error "MultiType constructors cannot have a body" f.cff_pos;

+ 1 - 1
src/typing/typeloadFunction.ml

@@ -119,7 +119,7 @@ let type_function ctx args ret fmode f do_display p =
 			if is_display_debug then print_endline ("after optimizing:\n" ^ (Expr.dump_with_pos e));
 			type_expr ctx e NoValue
 		with
-		| Parser.TypePath (_,None,_) | Exit ->
+		| Parser.TypePath (_,None,_,_) | Exit ->
 			type_expr ctx e NoValue
 		| DisplayException (DisplayHover (Some t,_,_)) when (match follow t with TMono _ -> true | _ -> false) ->
 			type_expr ctx e NoValue

+ 7 - 1
src/typing/typer.ml

@@ -18,6 +18,8 @@
 *)
 open Ast
 open DisplayTypes.DisplayMode
+open DisplayException
+open DisplayTypes.CompletionResultKind
 open Common
 open Type
 open Typecore
@@ -1170,6 +1172,7 @@ and type_ident ctx i p mode =
 
 (* MORDOR *)
 and handle_efield ctx e p mode =
+	let p0 = p in
 	(*
 		given chain of fields as the `path` argument and an `access_mode->access_kind` getter for some starting expression as `e`,
 		return a new `access_mode->access_kind` getter for the whole field access chain.
@@ -1332,7 +1335,10 @@ and handle_efield ctx e p mode =
 							with
 								Not_found ->
 									(* if there was no module name part, last guess is that we're trying to get package completion *)
-									if ctx.in_display then raise (Parser.TypePath (List.map (fun (n,_,_) -> n) (List.rev acc),None,false));
+									if ctx.in_display then begin
+										if ctx.com.json_out = None then raise (Parser.TypePath (List.map (fun (n,_,_) -> n) (List.rev acc),None,false,p))
+										else raise_fields (DisplayToplevel.collect ctx false NoValue) CRTypeHint (Some (Parser.cut_pos_at_display p0)) false;
+									end;
 									raise e)
 		in
 		match path with

+ 56 - 13
src/typing/typerDisplay.ml

@@ -6,6 +6,7 @@ open CompletionResultKind
 open CompletionItem
 open CompletionModuleKind
 open CompletionModuleType
+open ClassFieldOrigin
 open DisplayException
 open Common
 open Type
@@ -15,6 +16,44 @@ open Fields
 open Calls
 open Error
 
+let completion_item_of_expr ctx e =
+	let retype e s t =
+		try
+			let e' = type_expr ctx (EConst(Ident s),null_pos) (WithType t) in
+			Texpr.equal e e'
+		with _ ->
+			false
+	in
+	let of_field e origin cf scope =
+		let is_qualified = retype e cf.cf_name cf.cf_type in
+		ITClassField (CompletionClassField.make cf scope origin is_qualified)
+	in
+	let of_enum_field e origin ef =
+		let is_qualified = retype e ef.ef_name ef.ef_type in
+		ITEnumField (CompletionEnumField.make ef origin is_qualified)
+	in
+	let rec loop e = match e.eexpr with
+		| TLocal v -> ITLocal v
+		| TField(_,FStatic(c,cf)) -> of_field e (Self (TClassDecl c)) cf CFSStatic
+		| TField(_,(FInstance(c,_,cf) | FClosure(Some(c,_),cf))) -> of_field e (Self (TClassDecl c)) cf CFSMember
+		| TField(_,FEnum(en,ef)) -> of_enum_field e (Self (TEnumDecl en)) ef
+		| TField(e1,FAnon cf) ->
+			begin match follow e1.etype with
+				| TAnon an -> of_field e (AnonymousStructure an) cf CFSMember
+				| _ -> ITExpression e
+			end
+		| TTypeExpr mt -> ITType(CompletionModuleType.of_module_type mt,ImportStatus.Imported) (* TODO *)
+		| TConst(ct) -> ITLiteral(s_const ct,e.etype)
+		| TObjectDecl _ ->
+			begin match follow e.etype with
+				| TAnon an -> ITAnonymous an
+				| _ -> ITExpression e
+			end
+		| TParenthesis e1 | TMeta(_,e1) | TCast(e1,_) -> loop e1
+		| _ -> ITExpression e
+	in
+	loop e
+
 let rec handle_signature_display ctx e_ast with_type =
 	ctx.in_display <- true;
 	let p = pos e_ast in
@@ -225,25 +264,27 @@ and display_expr ctx e_ast e dk with_type p =
 		begin match fst e_ast,e.eexpr with
 			| EField(e1,s),TField(e2,_) ->
 				let fields = DisplayFields.collect ctx e1 e2 dk with_type p in
-				raise_fields fields CRField (Some {e.epos with pmin = e.epos.pmax - String.length s;}) false
+				let item = completion_item_of_expr ctx e2 in
+				raise_fields fields (CRField(item,e2.epos)) (Some {e.epos with pmin = e.epos.pmax - String.length s;}) false
 			| _ ->
 				raise_fields (DisplayToplevel.collect ctx false with_type) CRToplevel None (match with_type with WithType _ -> true | _ -> false)
 		end
 	| DMDefault | DMNone | DMModuleSymbols _ | DMDiagnostics _ | DMStatistics ->
 		let fields = DisplayFields.collect ctx e_ast e dk with_type p in
-		raise_fields fields CRField None false
+		let item = completion_item_of_expr ctx e in
+		raise_fields fields (CRField(item,e.epos)) None false
 
-let handle_structure_display ctx e fields =
+let handle_structure_display ctx e an =
 	let p = pos e in
 	match fst e with
 	| EObjectDecl fl ->
 		let fields = PMap.foldi (fun k cf acc ->
 			if Expr.field_mem_assoc k fl then acc
-			else (CompletionItem.ITClassField(cf,CFSMember)) :: acc
-		) fields [] in
+			else (ITClassField(CompletionClassField.make cf CFSMember (AnonymousStructure an) true)) :: acc
+		) an.a_fields [] in
 		raise_fields fields CRStructureField None false
 	| EBlock [] ->
-		let fields = PMap.foldi (fun _ cf acc -> CompletionItem.ITClassField(cf,CFSMember) :: acc) fields [] in
+		let fields = PMap.foldi (fun _ cf acc -> ITClassField(CompletionClassField.make cf CFSMember (AnonymousStructure an) true) :: acc) an.a_fields [] in
 		raise_fields fields CRStructureField None false
 	| _ ->
 		error "Expected object expression" p
@@ -278,14 +319,16 @@ let handle_display ctx e_ast dk with_type =
 	| (_,p),_ -> try
 		type_expr ctx e_ast with_type
 	with Error (Unknown_ident n,_) ->
-		if dk = DKDot then raise (Parser.TypePath ([n],None,false))
-		else raise_fields (DisplayToplevel.collect ctx false with_type) CRToplevel (Some {p with pmin = p.pmax - String.length n;}) (match with_type with WithType _ -> true | _ -> false)
-	| Error (Type_not_found (path,_),_) as err ->
-		begin try
-			raise_fields (DisplayFields.get_submodule_fields ctx path) CRField None false
+        if dk = DKDot && ctx.com.json_out = None then raise (Parser.TypePath ([n],None,false,p))
+		else raise_fields (DisplayToplevel.collect ctx false with_type) CRToplevel (Some (Parser.cut_pos_at_display p)) (match with_type with WithType _ -> true | _ -> false)
+	| Error ((Type_not_found (path,_) | Module_not_found path),_) as err ->
+		if ctx.com.json_out = None then	begin try
+			let s = s_type_path path in
+			raise_fields (DisplayFields.get_submodule_fields ctx path) (CRField((ITModule s),p)) None false
 		with Not_found ->
 			raise err
-		end
+		end else
+			raise_fields (DisplayToplevel.collect ctx false with_type) CRToplevel (Some (Parser.cut_pos_at_display p)) (match with_type with WithType _ -> true | _ -> false)
 	| DisplayException(DisplayFields(l,CRTypeHint,p,b)) when (match fst e_ast with ENew _ -> true | _ -> false) ->
 		let timer = Timer.timer ["display";"toplevel";"filter ctors"] in
 		ctx.pass <- PBuildClass;
@@ -339,7 +382,7 @@ let handle_edisplay ctx e dk with_type =
 		begin match with_type with
 			| WithType t ->
 				begin match follow t with
-					| TAnon an -> handle_structure_display ctx e an.a_fields
+					| TAnon an -> handle_structure_display ctx e an
 					| _ -> handle_display ctx e dk with_type
 				end
 			| _ ->

+ 2 - 2
tests/display/src/DisplayTestCase.hx

@@ -77,8 +77,8 @@ class DisplayTestCase {
 		return a.exists(function(t) return t.type == type && t.name == name && (kind == null || t.kind == kind));
 	}
 
-	function hasToplevel(a:Array<ToplevelElement>, kind:String, name:String):Bool {
-		return a.exists(function(t) return t.kind == kind && t.name == name);
+	function hasToplevel(a:Array<ToplevelElement>, kind:String, name:String, ?type:String = null):Bool {
+		return a.exists(function(t) return t.kind == kind && t.name == name && (type == null || t.type == type));
 	}
 
 	function hasPath(a:Array<FieldElement>, name:String):Bool {

+ 1 - 1
tests/display/src/DisplayTestContext.hx

@@ -149,7 +149,7 @@ class DisplayTestContext {
 		}
 		var ret = [];
 		for (xml in xml.elementsNamed("i")) {
-			ret.push({kind: xml.get("k"), name: xml.firstChild().nodeValue});
+			ret.push({kind: xml.get("k"), type: xml.get("t"), name: xml.firstChild().nodeValue});
 		}
 		return ret;
 	}

+ 2 - 1
tests/display/src/Types.hx

@@ -1,6 +1,7 @@
 typedef ToplevelElement = {
 	kind: String,
-	name: String
+	name: String,
+	type: String
 }
 
 typedef FieldElement = {

+ 31 - 0
tests/display/src/cases/Abstract.hx

@@ -13,4 +13,35 @@ class Abstract extends DisplayTestCase {
 		eq(range(3, 4), position(pos(1)));
 		eq("String", type(pos(2)));
 	}
+
+	/**
+	abstract MyAbstract(String) {
+		public function new() this = "foo";
+
+		public function instanceField():Void {
+			{-1-}
+		}
+		static public function staticField():Void {
+			{-2-}
+		}
+	}
+	class MyClass {
+		static function main() {
+			MyAbstract.{-3-}
+		}
+	}
+	**/
+	function test2() {
+		var top1 = toplevel(pos(1));
+		eq(true, hasToplevel(top1, "member", "instanceField", "Void -> Void"));
+		eq(true, hasToplevel(top1, "static", "staticField", "Void -> Void"));
+
+		var top2 = toplevel(pos(2));
+		eq(false, hasToplevel(top2, "member", "instanceField", "Void -> Void"));
+		eq(true, hasToplevel(top2, "static", "staticField", "Void -> Void"));
+
+		var fields = fields(pos(3));
+		eq(false, hasField(fields, "instanceField", "Void -> Void"));
+		eq(true, hasField(fields, "staticField", "Void -> Void"));
+	}
 }

+ 19 - 0
tests/display/src/cases/Issue7071.hx

@@ -0,0 +1,19 @@
+package cases;
+
+class Issue7071 extends DisplayTestCase {
+	/**
+	enum Foo { Bar; }
+
+	class Main {
+		public static function main() {
+			var bar = Bar;
+			bar == {-1-};
+			if (bar == {-2-})
+		}
+	}
+	**/
+	function test() {
+		eq("Bar", toplevel(pos(1))[0].name);
+		eq("Bar", toplevel(pos(2))[0].name);
+	}
+}

+ 18 - 0
tests/display/src/cases/Toplevel.hx

@@ -316,4 +316,22 @@ class Toplevel extends DisplayTestCase {
 		var fields = toplevel(pos(1));
 		eq(true, hasToplevel(fields, "local", "foo"));
 	}
+
+	/**
+	class C1<T> {
+		public function f1(t:T) { }
+	}
+
+	class C2<T> extends C1<T> { }
+
+	class C3 extends C2<String> {
+		function f2() {
+			{-1-}
+		}
+	}
+	**/
+	function testTypeParameterApplication() {
+		var toplevel = toplevel(pos(1));
+		eq(true, hasToplevel(toplevel, "member", "f1", "t : String -> Void"));
+	}
 }