Browse Source

[display] merge changes from display branch

Simon Krajewski 7 years ago
parent
commit
8cff76fd23
51 changed files with 2144 additions and 1538 deletions
  1. 1 1
      Makefile
  2. 19 201
      src/compiler/displayOutput.ml
  3. 32 9
      src/compiler/main.ml
  4. 13 9
      src/compiler/server.ml
  5. 17 8
      src/context/common.ml
  6. 0 852
      src/context/display.ml
  7. 86 0
      src/context/display/deprecationCheck.ml
  8. 217 0
      src/context/display/diagnostics.ml
  9. 110 0
      src/context/display/display.ml
  10. 123 0
      src/context/display/displayEmitter.ml
  11. 71 0
      src/context/display/displayException.ml
  12. 6 3
      src/context/display/displayFields.ml
  13. 44 15
      src/context/display/displayJson.ml
  14. 170 111
      src/context/display/displayToplevel.ml
  15. 123 0
      src/context/display/documentSymbols.ml
  16. 57 0
      src/context/display/importHandling.ml
  17. 281 0
      src/context/display/statistics.ml
  18. 6 2
      src/core/ast.ml
  19. 266 0
      src/core/display/completionItem.ml
  20. 8 165
      src/core/displayTypes.ml
  21. 37 14
      src/core/json/genjson.ml
  22. 12 0
      src/core/path.ml
  23. 5 0
      src/core/type.ml
  24. 2 0
      src/macro/macroApi.ml
  25. 1 1
      src/optimization/optimizer.ml
  26. 51 36
      src/syntax/grammar.mly
  27. 10 2
      src/syntax/parser.ml
  28. 1 1
      src/typing/calls.ml
  29. 1 1
      src/typing/fields.ml
  30. 2 2
      src/typing/macroContext.ml
  31. 3 3
      src/typing/matcher.ml
  32. 63 17
      src/typing/typeload.ml
  33. 30 10
      src/typing/typeloadCheck.ml
  34. 25 25
      src/typing/typeloadFields.ml
  35. 7 3
      src/typing/typeloadFunction.ml
  36. 10 10
      src/typing/typeloadModule.ml
  37. 8 4
      src/typing/typeloadParse.ml
  38. 13 13
      src/typing/typer.ml
  39. 1 1
      src/typing/typerBase.ml
  40. 24 8
      src/typing/typerDisplay.ml
  41. 9 2
      std/haxe/display/JsonModuleTypes.hx
  42. 2 2
      std/haxe/display/JsonModuleTypesPrinter.hx
  43. 1 0
      std/haxe/macro/Expr.hx
  44. 2 0
      tests/display/src/DisplayTestCase.hx
  45. 9 0
      tests/display/src/DisplayTestContext.hx
  46. 129 0
      tests/display/src/cases/Issue7029.hx
  47. 14 0
      tests/display/src/cases/Signature.hx
  48. 7 5
      tests/display/src/cases/Toplevel.hx
  49. 13 0
      tests/display/src/cases/VsHaxeIssue198.hx
  50. 1 1
      tests/misc/projects/Issue6005/Main.hx
  51. 1 1
      tests/misc/projects/Issue6005/compile1.hxml

+ 1 - 1
Makefile

@@ -29,7 +29,7 @@ STATICLINK?=0
 # Configuration
 
 # Modules in these directories should only depend on modules that are in directories to the left
-HAXE_DIRECTORIES=core core/json syntax context codegen codegen/gencommon generators optimization filters macro macro/eval typing compiler
+HAXE_DIRECTORIES=core core/json core/display syntax context context/display codegen codegen/gencommon generators optimization filters macro macro/eval typing compiler
 EXTLIB_LIBS=extlib-leftovers extc neko javalib swflib ttflib ilib objsize pcre ziplib
 OCAML_LIBS=unix str threads dynlink
 OPAM_LIBS=sedlex xml-light extlib rope ptmap sha

+ 19 - 201
src/compiler/displayOutput.ml

@@ -1,9 +1,10 @@
 open Globals
 open Common
+open Common.CompilationServer
 open Timer
 open DisplayTypes.DisplayMode
-open DisplayTypes.CompletionKind
-open Display.DisplayException
+open CompletionItem
+open DisplayException
 open Type
 open Display
 open DisplayTypes
@@ -42,7 +43,7 @@ let print_fields fields =
 	let b = Buffer.create 0 in
 	Buffer.add_string b "<list>\n";
 	let convert k = match k with
-		| ITClassMember cf | ITClassStatic cf | ITEnumAbstractField(_,cf) ->
+		| ITClassField(cf,_) | ITEnumAbstractField(_,cf) ->
 			let kind = match cf.cf_kind with
 				| Method _ -> "method"
 				| Var _ -> "var"
@@ -54,15 +55,16 @@ let print_fields fields =
 				| _ -> "var"
 			in
 			kind,ef.ef_name,s_type (print_context()) ef.ef_type,ef.ef_doc
-		| ITType(path,_,_) ->
+		| ITType(cm,_) ->
+			let path = CompletionItem.CompletionModuleType.get_path cm in
 			"type",snd path,s_type_path path,None
 		| ITPackage s -> "package",s,"",None
 		| ITModule s -> "type",s,"",None
 		| ITMetadata(s,doc) -> "metadata",s,"",doc
 		| ITTimer(name,value) -> "timer",name,"",Some value
-		| ITGlobal(_,s,t) -> "global",s,s_type (print_context()) t,None
 		| 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
 	in
 	let fields = List.sort (fun k1 k2 -> compare (legacy_sort k1) (legacy_sort k2)) fields in
 	let fields = List.map convert fields in
@@ -92,17 +94,16 @@ 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);
-		| ITClassMember cf ->
+		| ITClassField(cf,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);
-		| ITClassStatic cf ->
+		| ITClassField(cf,(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) ->
 			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) ->
 			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);
-		| ITGlobal(mt,s,t) ->
-			if check_ident s then Buffer.add_string b (Printf.sprintf "<i k=\"global\" p=\"%s\" t=\"%s\">%s</i>\n" (s_type_path (t_infos mt).mt_path) (s_type t) s);
-		| ITType(path,_,rm) ->
+		| ITType(cm,rm) ->
+			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
@@ -116,7 +117,7 @@ let print_toplevel il =
 			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 _ ->
+		| ITMetadata _ | ITModule _ | ITKeyword _ ->
 			(* compat: don't add *)
 			()
 	) il;
@@ -409,11 +410,11 @@ module TypePathHandler = struct
 					[]
 				else
 					List.map (fun mt ->
-						ITType((t_infos mt).mt_path, DisplayTypes.CompletionItemKind.of_module_type mt,RMOtherModule m.m_path)
+						ITType(CompletionItem.CompletionModuleType.of_module_type ImportStatus.Imported mt,RMOtherModule m.m_path)
 					) public_types
 			in
 			let make_field_doc cf =
-				ITClassStatic cf
+				ITClassField(cf,CFSStatic)
 			in
 			let fields = match !statics with
 				| None -> types
@@ -459,188 +460,6 @@ let print_signature tl display_arg =
 	] in
 	string_of_json jo
 
-module StatisticsPrinter = struct
-	open Statistics
-
-	let relation_to_string = function
-		| Implemented -> "implementers"
-		| Extended -> "subclasses"
-		| Overridden -> "overrides"
-		| Referenced -> "references"
-
-	let symbol_to_string = function
-		| SKClass _ -> "class type"
-		| SKInterface _ -> "interface type"
-		| SKEnum _ -> "enum type"
-		| SKTypedef _ -> "typedef"
-		| SKAbstract _ -> "abstract"
-		| SKField _ -> "class field"
-		| SKEnumField _ -> "enum field"
-		| SKVariable _ -> "variable"
-
-	let print_statistics (kinds,relations) =
-		let files = Hashtbl.create 0 in
-		Hashtbl.iter (fun p rl ->
-			let file = Path.get_real_path p.pfile in
-			try
-				Hashtbl.replace files file ((p,rl) :: Hashtbl.find files file)
-			with Not_found ->
-				Hashtbl.add files file [p,rl]
-		) relations;
-		let ja = Hashtbl.fold (fun file relations acc ->
-			let l = List.map (fun (p,rl) ->
-				let h = Hashtbl.create 0 in
-				List.iter (fun (r,p) ->
-					let s = relation_to_string r in
-					let jo = JObject [
-						"range",Genjson.generate_pos_as_range p;
-						"file",JString (Path.get_real_path p.pfile);
-					] in
-					try Hashtbl.replace h s (jo :: Hashtbl.find h s)
-					with Not_found -> Hashtbl.add h s [jo]
-				) rl;
-				let l = Hashtbl.fold (fun s js acc -> (s,JArray js) :: acc) h [] in
-				let l = ("range",Genjson.generate_pos_as_range p) :: l in
-				let l = try ("kind",JString (symbol_to_string (Hashtbl.find kinds p))) :: l with Not_found -> l in
-				JObject l
-			) relations in
-			(JObject [
-				"file",JString file;
-				"statistics",JArray l
-			]) :: acc
-		) files [] in
-		string_of_json (JArray ja)
-end
-
-module DiagnosticsPrinter = struct
-	open Diagnostics
-	open Diagnostics.DiagnosticsKind
-	open DisplayTypes
-
-	type t = DiagnosticsKind.t * pos
-
-	module UnresolvedIdentifierSuggestion = struct
-		type t =
-			| UISImport
-			| UISTypo
-
-		let to_int = function
-			| UISImport -> 0
-			| UISTypo -> 1
-	end
-
-	let print_diagnostics ctx global =
-		let com = ctx.com in
-		let diag = Hashtbl.create 0 in
-		let add dk p sev args =
-			let file = Path.get_real_path p.pfile in
-			let diag = try
-				Hashtbl.find diag file
-			with Not_found ->
-				let d = DynArray.create() in
-				Hashtbl.add diag file d;
-				d
-			in
-			DynArray.add diag (dk,p,sev,args)
-		in
-		let add dk p sev args =
-			if global || is_display_file p.pfile then add dk p sev args
-		in
-		let find_type i =
-			let types = ref [] in
-			Hashtbl.iter (fun _ m ->
-				List.iter (fun mt ->
-					let s_full_type_path (p,s) n = s_type_path (p,s) ^ if (s <> n) then "." ^ n else "" in
-					let tinfos = t_infos mt in
-					if snd tinfos.mt_path = i then
-						types := JObject [
-							"kind",JInt (UnresolvedIdentifierSuggestion.to_int UnresolvedIdentifierSuggestion.UISImport);
-							"name",JString (s_full_type_path m.m_path i)
-						] :: !types
-				) m.m_types;
-			) ctx.g.modules;
-			!types
-		in
-		List.iter (fun (s,p,suggestions) ->
-			let suggestions = List.map (fun (s,_) ->
-				JObject [
-					"kind",JInt (UnresolvedIdentifierSuggestion.to_int UnresolvedIdentifierSuggestion.UISTypo);
-					"name",JString s
-				]
-			) suggestions in
-			add DKUnresolvedIdentifier p DiagnosticsSeverity.Error (JArray (suggestions @ (find_type s)));
-		) com.display_information.unresolved_identifiers;
-		PMap.iter (fun p (r,_) ->
-			if not !r then add DKUnusedImport p DiagnosticsSeverity.Warning (JArray [])
-		) com.shared.shared_display_information.import_positions;
-		List.iter (fun (s,p,sev) ->
-			add DKCompilerError p sev (JString s)
-		) com.shared.shared_display_information.diagnostics_messages;
-		List.iter (fun (s,p,prange) ->
-			add DKRemovableCode p DiagnosticsSeverity.Warning (JObject ["description",JString s;"range",if prange = null_pos then JNull else Genjson.generate_pos_as_range prange])
-		) com.shared.shared_display_information.removable_code;
-		let jl = Hashtbl.fold (fun file diag acc ->
-			let jl = DynArray.fold_left (fun acc (dk,p,sev,jargs) ->
-				(JObject [
-					"kind",JInt (to_int dk);
-					"severity",JInt (DiagnosticsSeverity.to_int sev);
-					"range",Genjson.generate_pos_as_range p;
-					"args",jargs
-				]) :: acc
-			) [] diag in
-			(JObject [
-				"file",JString file;
-				"diagnostics",JArray jl
-			]) :: acc
-		) diag [] in
-		let js = JArray jl in
-		string_of_json js
-end
-
-module ModuleSymbolsPrinter = struct
-	open DisplayTypes.SymbolKind
-	open DisplayTypes.SymbolInformation
-
-	let print_module_symbols com symbols filter =
-		let regex = Option.map Str.regexp_case_fold filter in
-		let reported = Hashtbl.create 0 in
-		let add si =
-			if Hashtbl.mem reported si.pos then false
-			else begin
-				let b = match regex with
-					| None -> true
-					| Some regex -> (try ignore(Str.search_forward regex si.name 0); true with Not_found -> false)
-				in
-				Hashtbl.replace reported si.pos true;
-				b
-			end
-		in
-		let ja = List.fold_left (fun acc (file,l) ->
-			let jl = ExtList.List.filter_map (fun si ->
-				if not (add si) then
-					None
-				else begin
-					let l =
-						("name",JString si.name) ::
-						("kind",JInt (to_int si.kind)) ::
-						("range", Genjson.generate_pos_as_range si.pos) ::
-						(match si.container_name with None -> [] | Some s -> ["containerName",JString s])
-					in
-					Some (JObject l)
-				end
-			) (DynArray.to_list l) in
-			if jl = [] then
-				acc
-			else
-				(JObject [
-					"file",JString file;
-					"symbols",JArray jl
-				]) :: acc
-		) [] symbols in
-		let js = JArray ja in
-		string_of_json js
-end
-
 (* Mode processing *)
 
 exception Completion of string
@@ -666,7 +485,6 @@ let handle_display_argument com file_pos pre_compilation did_something =
 		let file, pos = try ExtString.String.split file_pos "@" with _ -> failwith ("Invalid format: " ^ file_pos) in
 		let file = unquote file in
 		let pos, smode = try ExtString.String.split pos "@" with _ -> pos,"" in
-		Parser.had_resume := false;
 		let offset = ref 0 in
 		let mode = match smode with
 			| "position" ->
@@ -795,24 +613,24 @@ let process_global_display_mode com tctx = match com.display.dms_kind with
 		raise_position usages
 	| DMDiagnostics global ->
 		Diagnostics.prepare com global;
-		raise_diagnostics (DiagnosticsPrinter.print_diagnostics tctx global)
+		raise_diagnostics (Diagnostics.Printer.print_diagnostics tctx global)
 	| DMStatistics ->
 		let stats = Statistics.collect_statistics tctx in
-		raise_statistics (StatisticsPrinter.print_statistics stats)
+		raise_statistics (Statistics.Printer.print_statistics stats)
 	| DMModuleSymbols filter ->
 		let symbols = com.shared.shared_display_information.document_symbols in
 		let symbols = match CompilationServer.get() with
 			| None -> symbols
 			| 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
-				List.fold_left (fun acc (file,data) ->
+				List.fold_left (fun acc (file,cfile) ->
 					if (filter <> None || is_display_file file) then
-						(file,DocumentSymbols.collect_module_symbols data) :: acc
+						(file,DocumentSymbols.collect_module_symbols (cfile.c_package,cfile.c_decls)) :: acc
 					else
 						acc
 				) symbols l
 		in
-		raise_module_symbols (ModuleSymbolsPrinter.print_module_symbols com symbols filter)
+		raise_module_symbols (DocumentSymbols.Printer.print_module_symbols com symbols filter)
 	| _ -> ()
 
 let find_doc t =

+ 32 - 9
src/compiler/main.ml

@@ -46,7 +46,7 @@ open Printf
 open Common
 open DisplayTypes.DisplayMode
 open DisplayTypes.CompletionResultKind
-open Display.DisplayException
+open DisplayException
 open Type
 open Server
 open Globals
@@ -688,7 +688,7 @@ try
 		("Services",["--display"],[], Arg.String (fun input ->
 			let input = String.trim input in
 			if String.length input > 0 && (input.[0] = '[' || input.[0] = '{') then begin
-				DisplayJson.parse_input com input measure_times did_something
+				DisplayJson.parse_input com input measure_times pre_compilation did_something
 			end else
 				DisplayOutput.handle_display_argument com input pre_compilation did_something;
 		),"","display code tips");
@@ -813,7 +813,9 @@ try
 		| _ -> if not ctx.has_next then com.package_rules <- PMap.foldi (fun p r acc -> match r with Forbidden -> acc | _ -> PMap.add p r acc) com.package_rules PMap.empty;
 	end;
 	com.config <- get_config com; (* make sure to adapt all flags changes defined after platform *)
+	let t = Timer.timer ["init"] in
 	List.iter (fun f -> f()) (List.rev (!pre_compilation));
+	t();
 	if !classes = [([],"Std")] && not !force_typing then begin
 		if !cmds = [] && not !did_something then raise (HelpMessage (usage_string basic_args_spec usage));
 	end else begin
@@ -824,6 +826,7 @@ try
 		Typecore.type_expr_ref := (fun ctx e with_type -> Typer.type_expr ctx e with_type);
 		let tctx = Typer.create com in
 		List.iter (MacroContext.call_init_macro tctx) (List.rev !config_macros);
+		List.iter (fun f -> f ()) (List.rev com.callbacks.after_init_macros);
 		List.iter (fun cpath -> ignore(tctx.Typecore.g.Typecore.do_load_module tctx cpath null_pos)) (List.rev !classes);
 		Finalization.finalize tctx;
 		t();
@@ -882,7 +885,7 @@ try
 		end;
 		DisplayOutput.process_global_display_mode com tctx;
 		if not (Common.defined com Define.NoDeprecationWarnings) then
-			Display.DeprecationCheck.run com;
+			DeprecationCheck.run com;
 		Filters.run com tctx main;
 		t();
 		if ctx.has_error then raise Abort;
@@ -945,9 +948,11 @@ with
 		error ctx ("Error: " ^ msg) null_pos
 	| HelpMessage msg ->
 		message ctx (CMInfo(msg,null_pos))
-	| DisplayException(DisplayType _ | 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 match ctx.com.json_out with
-		| Some (f,_) -> f (Display.DisplayException.to_json de)
+		| Some (f,_) ->
+			let ctx = DisplayJson.create_json_context() in
+			f (DisplayException.to_json ctx de)
 		| _ -> assert false
 		end
 	| DisplayException(DisplayPackage pack) ->
@@ -956,13 +961,29 @@ with
 		let fields = if !measure_times then begin
 			Timer.close_times();
 			(List.map (fun (name,value) ->
-				DisplayTypes.CompletionKind.ITTimer("@TIME " ^ name,value)
+				CompletionItem.ITTimer("@TIME " ^ name,value)
 			) (DisplayOutput.get_timer_fields !start_time)) @ fields
 		end else
 			fields
 		in
-		raise (DisplayOutput.Completion (match cr with CRToplevel -> DisplayOutput.print_toplevel fields | _ -> DisplayOutput.print_fields fields))
-	| DisplayException(DisplayType (t,p,doc)) ->
+		let s = match cr with
+			| CRToplevel
+			| CRTypeHint
+			| CRExtends
+			| CRImplements
+			| CRStructExtension
+			| CRImport
+			| CRUsing
+			| CRNew
+			| CRPattern ->
+				DisplayOutput.print_toplevel fields
+			| CRField
+			| CRStructureField
+			| CRMetadata ->
+				DisplayOutput.print_fields fields
+		in
+		raise (DisplayOutput.Completion s)
+	| DisplayException(DisplayHover (Some t,p,doc)) ->
 		let doc = match doc with Some _ -> doc | None -> DisplayOutput.find_doc t in
 		raise (DisplayOutput.Completion (DisplayOutput.print_type t p doc))
 	| DisplayException(DisplaySignatures(signatures,_,display_arg)) ->
@@ -987,7 +1008,9 @@ with
 		| None -> ()
 		| Some fields ->
 			begin match ctx.com.json_out with
-			| Some (f,_) -> f (Display.DisplayException.to_json (DisplayFields(fields,CRField,None,false)))
+			| Some (f,_) ->
+				let ctx = DisplayJson.create_json_context() in
+				f (DisplayException.to_json ctx (DisplayFields(fields,CRField,None,false)))
 			| _ -> raise (DisplayOutput.Completion (DisplayOutput.print_fields fields))
 			end
 		end

+ 13 - 9
src/compiler/server.ml

@@ -2,6 +2,7 @@ open Printf
 open Globals
 open Ast
 open Common
+open Common.CompilationServer
 open DisplayTypes.DisplayMode
 open Timer
 open Type
@@ -121,10 +122,11 @@ let rec wait_loop process_params verbose accept =
 			let sign = Define.get_signature com2.defines in
 			let ftime = file_time ffile in
 			let fkey = (ffile,sign) in
-			try
-				let time, data = CompilationServer.find_file cs fkey in
-				if time <> ftime then raise Not_found;
-				data
+			let t = Timer.timer ["server";"parser cache"] in
+			let data = try
+				let cfile = CompilationServer.find_file cs fkey in
+				if cfile.c_time <> ftime then raise Not_found;
+				cfile.c_package,cfile.c_decls
 			with Not_found ->
 				has_parse_error := false;
 				let data = TypeloadParse.parse_file com2 file p in
@@ -137,11 +139,14 @@ let rec wait_loop process_params verbose accept =
 						let ident = Hashtbl.find Parser.special_identifier_files ffile in
 						Printf.sprintf "not cached, using \"%s\" define" ident,true
 					with Not_found ->
-						CompilationServer.cache_file cs fkey (ftime,data);
+						CompilationServer.cache_file cs fkey ftime data;
 						"cached",false
 				end in
 				if is_unusual then ServerMessage.parsed com2 "" (ffile,info);
 				data
+			in
+			t();
+			data
 	);
 	let check_module_shadowing com paths m =
 		List.iter (fun (path,_) ->
@@ -235,11 +240,11 @@ let rec wait_loop process_params verbose accept =
 			let ffile = Path.unique_full_path file in
 			let fkey = (ffile,sign) in
 			try
-				let _, old_data = CompilationServer.find_file cs fkey in
+				let cfile = CompilationServer.find_file cs fkey in
 				(* We must use the module path here because the file path is absolute and would cause
 				   positions in the parsed declarations to differ. *)
 				let new_data = TypeloadParse.parse_module ctx m.m_path p in
-				snd old_data <> snd new_data
+				cfile.c_decls <> snd new_data
 			with Not_found ->
 				true
 		in
@@ -441,8 +446,7 @@ let rec wait_loop process_params verbose accept =
 			ServerMessage.arguments data;
 			(try
 				Hashtbl.clear changed_directories;
-				Parser.display_mode := DMNone;
-				Parser.resume_display := null_pos;
+				Parser.reset_state();
 				return_partial_type := false;
 				measure_times := false;
 				close_times();

+ 17 - 8
src/context/common.ml

@@ -97,6 +97,7 @@ type platform_config = {
 }
 
 type compiler_callback = {
+	mutable after_init_macros : (unit -> unit) list;
 	mutable after_typing : (module_type list -> unit) list;
 	mutable before_dce : (unit -> unit) list;
 	mutable after_generation : (unit -> unit) list;
@@ -110,7 +111,7 @@ type shared_display_information = {
 }
 
 type display_information = {
-	mutable unresolved_identifiers : (string * pos * (string * DisplayTypes.CompletionKind.t) list) list;
+	mutable unresolved_identifiers : (string * pos * (string * CompletionItem.t) list) list;
 	mutable interface_field_implementations : (tclass * tclass_field * tclass * tclass_field option) list;
 }
 
@@ -174,9 +175,16 @@ 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), float * Ast.package) 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;
 	}
@@ -225,8 +233,8 @@ module CompilationServer = struct
 		cs.initialized <- true
 
 	let get_context_files cs signs =
-		Hashtbl.fold (fun (file,sign) (_,data) acc ->
-			if (List.mem sign signs) then (file,data) :: acc
+		Hashtbl.fold (fun (file,sign) cfile acc ->
+			if (List.mem sign signs) then (file,cfile) :: acc
 			else acc
 		) cs.cache.c_files []
 
@@ -266,18 +274,18 @@ module CompilationServer = struct
 	let find_file cs key =
 		Hashtbl.find cs.cache.c_files key
 
-	let cache_file cs key value =
-		Hashtbl.replace cs.cache.c_files key value
+	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 (sign,file)) cs.signs
+		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 (_,sign') file -> if sign = sign' then f file) cs.cache.c_files
+		Hashtbl.iter (fun (file,sign') decls -> if sign = sign' then f file decls) cs.cache.c_files
 
 	(* haxelibs *)
 
@@ -485,6 +493,7 @@ let memory_marker = [|Unix.time()|]
 
 let create_callbacks () =
 	{
+		after_init_macros = [];
 		after_typing = [];
 		before_dce = [];
 		after_generation = [];

+ 0 - 852
src/context/display.ml

@@ -1,852 +0,0 @@
-open Ast
-open Common
-open DisplayTypes
-open DisplayMode
-open CompletionKind
-open CompletionResultKind
-open Type
-open Typecore
-open Globals
-open Genjson
-
-let reference_position = ref null_pos
-
-module DisplayException = struct
-	type kind =
-		| Diagnostics of string
-		| Statistics of string
-		| ModuleSymbols of string
-		| Metadata of string
-		| DisplaySignatures of (tsignature * documentation) list * int * int
-		| DisplayType of t * pos * string option
-		| DisplayPosition of pos list
-		| DisplayFields of CompletionKind.t list * CompletionResultKind.t * pos option (* insert pos *) * bool (* sorted? *)
-		| DisplayPackage of string list
-
-	exception DisplayException of kind
-
-	let raise_diagnostics s = raise (DisplayException(Diagnostics s))
-	let raise_statistics s = raise (DisplayException(Statistics s))
-	let raise_module_symbols s = raise (DisplayException(ModuleSymbols s))
-	let raise_metadata s = raise (DisplayException(Metadata s))
-	let raise_signatures l isig iarg = raise (DisplayException(DisplaySignatures(l,isig,iarg)))
-	let raise_type t p so = raise (DisplayException(DisplayType(t,p,so)))
-	let raise_position pl = raise (DisplayException(DisplayPosition pl))
-	let raise_fields ckl cr po b = raise (DisplayException(DisplayFields(ckl,cr,po,b)))
-	let raise_package sl = raise (DisplayException(DisplayPackage sl))
-
-	let to_json de = match de with
-		| Diagnostics _
-		| Statistics _
-		| ModuleSymbols _
-		| Metadata _ -> assert false
-		| DisplaySignatures(sigs,isig,iarg) ->
-			let ctx = Genjson.create_context () in
-			let fsig ((tl,tr),doc) =
-				let fl = generate_function_signature ctx tl tr in
-				let fl = (match doc with None -> fl | Some s -> ("documentation",jstring s) :: fl) in
-				jobject fl
-			in
-			jobject [
-				"activeSignature",jint isig;
-				"activeParameter",jint iarg;
-				"signatures",jlist fsig sigs;
-			]
-		| DisplayType(t,p,doc) ->
-			jobject [
-				"documentation",jopt jstring doc;
-				"range",generate_pos_as_range p;
-				"type",generate_type (create_context ()) t;
-			]
-		| DisplayPosition pl ->
-			jarray (List.map generate_pos_as_location pl)
-		| DisplayFields(fields,kind,po,sorted) ->
-			let ja = List.map (DisplayTypes.CompletionKind.to_json (Genjson.create_context ())) fields in
-			let fl =
-				("items",jarray ja) ::
-				("kind",jint (Obj.magic kind)) ::
-				("sorted",jbool sorted) ::
-				(match po with None -> [] | Some p -> ["replaceRange",generate_pos_as_range p]) in
-			jobject fl
-		| DisplayPackage pack ->
-			jarray (List.map jstring pack)
-end
-
-open DisplayException
-
-let is_display_file file =
-	file <> "?" && Path.unique_full_path file = (!Parser.resume_display).pfile
-
-let encloses_position p_target p =
-	p.pmin < p_target.pmin && p.pmax >= p_target.pmax
-
-let is_display_position p =
-	encloses_position !Parser.resume_display p
-
-module ExprPreprocessing = struct
-	let find_before_pos com is_completion e =
-		let display_pos = ref (!Parser.resume_display) in
-		let is_annotated p = encloses_position !display_pos p in
-		let annotate e dk =
-			display_pos := { pfile = ""; pmin = -2; pmax = -2 };
-			(EDisplay(e,dk),pos e)
-		in
-		let annotate_marked e = annotate e DKMarked in
-		let mk_null p = annotate_marked ((EConst(Ident "null")),p) in
-		let loop_el el =
-			let pr = !Parser.resume_display in
-			let rec loop el = match el with
-				| [] -> [mk_null pr]
-				| e :: el ->
-					if (pos e).pmin >= pr.pmax then (mk_null pr) :: e :: el
-					else e :: loop el
-			in
-			(* print_endline (Printf.sprintf "%i-%i: PR" pr.pmin pr.pmax);
-			List.iter (fun e ->
-				print_endline (Printf.sprintf "%i-%i: %s" (pos e).pmin (pos e).pmax (Ast.s_expr e));
-			) el; *)
-			match el with
-			| [] -> [mk_null pr]
-			| e :: el ->
-				if (pos e).pmin >= pr.pmax then (mk_null pr) :: e :: el
-				else loop (e :: el)
-		in
-		let loop e =
-			(* print_endline (Printf.sprintf "%i-%i: %s" (pos e).pmin (pos e).pmax (Ast.s_expr e)); *)
-			match fst e with
-			| EVars vl ->
-				if List.exists (fun ((_,p),_,_) -> is_annotated p) vl then
-					annotate_marked e
-				else
-					e
-			| EBlock [] when is_annotated (pos e) ->
-				annotate e DKStructure
-			| EBlock el when is_annotated (pos e) && is_completion ->
-				let el = loop_el el in
-				EBlock el,(pos e)
-			| ECall(e1,el) when is_annotated (pos e) && is_completion ->
-				let el = loop_el el in
-				ECall(e1,el),(pos e)
-			| ENew((tp,pp),el) when is_annotated (pos e) && is_completion ->
-				if is_annotated pp || pp.pmax >= !Parser.resume_display.pmax then
-					annotate_marked e
-				else begin
-					let el = loop_el el in
-					ENew((tp,pp),el),(pos e)
-				end
-			| EArrayDecl el when is_annotated (pos e) && is_completion ->
-				let el = loop_el el in
-				EArrayDecl el,(pos e)
-			| EDisplay _ ->
-				raise Exit
-			| _ ->
-				if is_annotated (pos e) then
-					annotate_marked e
-				else
-					e
-		in
-		let rec map e =
-			loop (Ast.map_expr map e)
-		in
-		try map e with Exit -> e
-
-	let find_display_call e =
-		let loop e = match fst e with
-			| ECall _ | ENew _ when is_display_position (pos e) -> Parser.mk_display_expr e DKCall
-			| _ -> e
-		in
-		let rec map e = loop (Ast.map_expr map e) in
-		map e
-
-
-	let process_expr com e = match com.display.dms_kind with
-		| DMDefinition | DMUsage _ | DMHover -> find_before_pos com false e
-		| DMDefault -> find_before_pos com true e
-		| DMSignature -> find_display_call e
-		| _ -> e
-end
-
-module DisplayEmitter = struct
-
-	let requires_import ctx path =
-		try
-			let mt' = ctx.g.do_load_type_def ctx null_pos {tpackage = []; tname = snd path; tparams = []; tsub = None} in
-			path <> (t_infos mt').mt_path
-		with _ ->
-			true
-
-	let patch_type ctx t =
-		let rec patch t = match t with
-			| TInst(c,tl) when not (requires_import ctx c.cl_path) -> TInst({c with cl_path = ([],snd c.cl_path)},List.map patch tl)
-			| TEnum(en,tl) when not (requires_import ctx en.e_path) -> TEnum({en with e_path = ([],snd en.e_path)},List.map patch tl)
-			| TType(td,tl) when not (requires_import ctx td.t_path) -> TType({td with t_path = ([],snd td.t_path)},List.map patch tl)
-			| TAbstract(a,tl) when not (requires_import ctx a.a_path) -> TAbstract({a with a_path = ([],snd a.a_path)},List.map patch tl)
-			| _ -> Type.map patch t
-		in
-		patch t
-
-	let display_module_type ctx mt p = match ctx.com.display.dms_kind with
-		| DMDefinition -> raise_position [(t_infos mt).mt_name_pos];
-		| DMUsage _ -> reference_position := (t_infos mt).mt_name_pos
-		| DMHover -> raise_type (patch_type ctx (type_of_module_type mt)) p (t_infos mt).mt_doc
-		| _ -> ()
-
-	let rec display_type ctx t p =
-		let dm = ctx.com.display in
-		match dm.dms_kind with
-		| DMHover ->
-			raise_type (patch_type ctx t) p None
-		| _ ->
-			try display_module_type ctx (module_type_of_type t) p
-			with Exit -> match follow t,follow !t_dynamic_def with
-				| _,TDynamic _ -> () (* sanity check in case it's still t_dynamic *)
-				| TDynamic _,_ -> display_type ctx !t_dynamic_def p
-				| _ -> ()
-
-	let check_display_type ctx t p =
-		let add_type_hint () =
-			let md = ctx.m.curmod.m_extra.m_display in
-			md.m_type_hints <- (p,t) :: md.m_type_hints;
-		in
-		let maybe_display_type () =
-			if ctx.is_display_file && is_display_position p then
-				display_type ctx t p
-		in
-		match ctx.com.display.dms_kind with
-		| DMStatistics -> add_type_hint()
-		| DMUsage _ -> add_type_hint(); maybe_display_type()
-		| _ -> maybe_display_type()
-
-	let display_variable ctx v p = match ctx.com.display.dms_kind with
-		| DMDefinition -> raise_position [v.v_pos]
-		| DMUsage _ -> reference_position := v.v_pos
-		| DMHover -> raise_type (patch_type ctx v.v_type) p None
-		| _ -> ()
-
-	let display_field ctx c cf p = match ctx.com.display.dms_kind with
-		| DMDefinition -> raise_position [cf.cf_name_pos]
-		| DMUsage _ -> reference_position := cf.cf_name_pos
-		| DMHover ->
-			let t = if Meta.has Meta.Impl cf.cf_meta then
-				(prepare_using_field cf).cf_type
-			else
-				cf.cf_type
-			in
-			let t = match c,follow t with
-				| Some c,TFun(tl,_) when cf.cf_name = "new" -> TFun(tl,TInst(c,List.map snd c.cl_params))
-				| _ -> t
-			in
-			raise_type (patch_type ctx t) p cf.cf_doc
-		| _ -> ()
-
-	let maybe_display_field ctx c cf p =
-		if is_display_position p then display_field ctx c cf p
-
-	let display_enum_field ctx ef p = match ctx.com.display.dms_kind with
-		| DMDefinition -> raise_position [ef.ef_name_pos]
-		| DMUsage _ -> reference_position := ef.ef_name_pos
-		| DMHover -> raise_type (patch_type ctx ef.ef_type) p ef.ef_doc
-		| _ -> ()
-
-	let display_meta com meta = match com.display.dms_kind with
-		| DMHover ->
-			begin match meta with
-			| Meta.Custom _ | Meta.Dollar _ -> ()
-			| _ -> match Meta.get_documentation meta with
-				| None -> ()
-				| Some (_,s) ->
-					(* TODO: hack until we support proper output for hover display mode *)
-					if com.json_out = None then
-						raise_metadata ("<metadata>" ^ s ^ "</metadata>")
-					else
-						raise_type t_dynamic null_pos (Some s)
-			end
-		| DMDefault ->
-			let all,_ = Meta.get_documentation_list() in
-			let all = List.map (fun (s,doc) ->
-				ITMetadata(s,Some doc)
-			) all in
-			raise_fields all CRMetadata None false
-		| _ ->
-			()
-
-	let check_display_metadata ctx meta =
-		List.iter (fun (meta,args,p) ->
-			if is_display_position p then display_meta ctx.com meta;
-			List.iter (fun e ->
-				if is_display_position (pos e) then begin
-					let e = ExprPreprocessing.process_expr ctx.com e in
-					delay ctx PTypeField (fun _ -> ignore(type_expr ctx e Value));
-				end
-			) args
-		) meta
-end
-
-module DocumentSymbols = struct
-	open DisplayTypes.SymbolKind
-
-	let collect_module_symbols (pack,decls) =
-		let l = DynArray.create() in
-		let add name kind location parent =
-			let si = DisplayTypes.SymbolInformation.make name kind location (if parent = "" then None else Some parent) in
-			DynArray.add l si;
-		in
-		let rec expr parent (e,p) =
-			let add name kind location = add name kind location parent in
-			begin match e with
-			| EVars vl ->
-				List.iter (fun ((s,p),_,eo) ->
-					add s Variable p;
-					expr_opt parent eo
-				) vl
-			| ETry(e1,catches) ->
-				expr parent e1;
-				List.iter (fun ((s,p),_,e,_) ->
-					add s Variable p;
-					expr parent e
-				) catches;
-			| EFunction(Some s,f) ->
-				add s Function p;
-				func parent f
-			| EBinop(OpIn,(EConst(Ident s),p),e2) ->
-				add s Variable p;
-				expr parent e2;
-			| _ ->
-				iter_expr (expr parent) (e,p)
-			end
-		and expr_opt parent eo = match eo with
-			| None -> ()
-			| Some e -> expr parent e
-		and func parent f =
-			List.iter (fun ((s,p),_,_,_,eo) ->
-				add s Variable p parent;
-				expr_opt parent eo
-			) f.f_args;
-			expr_opt parent f.f_expr
-		in
-		let field parent cff =
-			let field_parent = parent ^ "." ^ (fst cff.cff_name) in
-			match cff.cff_kind with
-			| FVar(_,eo) ->
-				add (fst cff.cff_name) Field cff.cff_pos parent;
-				expr_opt field_parent eo
-			| FFun f ->
-				add (fst cff.cff_name) (if fst cff.cff_name = "new" then Constructor else Method) cff.cff_pos parent;
-				func field_parent f
-			| FProp(_,_,_,eo) ->
-				add (fst cff.cff_name) Property cff.cff_pos parent;
-				expr_opt field_parent eo
-		in
-		List.iter (fun (td,p) -> match td with
-			| EImport _ | EUsing _ ->
-				() (* TODO: Can we do anything with these? *)
-			| EClass d ->
-				add (fst d.d_name) (if List.mem HInterface d.d_flags then Interface else Class) p "";
-				List.iter (field (fst d.d_name)) d.d_data
-			| EEnum d ->
-				add (fst d.d_name) Enum p "";
-				List.iter (fun ef ->
-					add (fst ef.ec_name) Method ef.ec_pos (fst d.d_name)
-				) d.d_data
-			| ETypedef d ->
-				add (fst d.d_name) Typedef p "";
-				(match d.d_data with
-				| CTAnonymous fields,_ ->
-					List.iter (field (fst d.d_name)) fields
-				| _ -> ())
-			| EAbstract d ->
-				add (fst d.d_name) Abstract p "";
-				List.iter (field (fst d.d_name)) d.d_data
-		) decls;
-		l
-end
-
-module DeprecationCheck = struct
-
-	let curclass = ref null_class
-
-	let warned_positions = Hashtbl.create 0
-
-	let print_deprecation_message com meta s p_usage =
-		let s = match meta with
-			| _,[EConst(String s),_],_ -> s
-			| _ -> Printf.sprintf "Usage of this %s is deprecated" s
-		in
-		if not (Hashtbl.mem warned_positions p_usage) then begin
-			Hashtbl.replace warned_positions p_usage true;
-			com.warning s p_usage;
-		end
-
-	let check_meta com meta s p_usage =
-		try
-			print_deprecation_message com (Meta.get Meta.Deprecated meta) s p_usage;
-		with Not_found ->
-			()
-
-	let check_cf com cf p = check_meta com cf.cf_meta "field" p
-
-	let check_class com c p = if c != !curclass then check_meta com c.cl_meta "class" p
-
-	let check_enum com en p = check_meta com en.e_meta "enum" p
-
-	let check_ef com ef p = check_meta com ef.ef_meta "enum field" p
-
-	let check_typedef com t p = check_meta com t.t_meta "typedef" p
-
-	let check_module_type com mt p = match mt with
-		| TClassDecl c -> check_class com c p
-		| TEnumDecl en -> check_enum com en p
-		| _ -> ()
-
-	let run_on_expr com e =
-		let rec expr e = match e.eexpr with
-			| TField(e1,fa) ->
-				expr e1;
-				begin match fa with
-					| FStatic(c,cf) | FInstance(c,_,cf) ->
-						check_class com c e.epos;
-						check_cf com cf e.epos
-					| FAnon cf ->
-						check_cf com cf e.epos
-					| FClosure(co,cf) ->
-						(match co with None -> () | Some (c,_) -> check_class com c e.epos);
-						check_cf com cf e.epos
-					| FEnum(en,ef) ->
-						check_enum com en e.epos;
-						check_ef com ef e.epos;
-					| _ ->
-						()
-				end
-			| TNew(c,_,el) ->
-				List.iter expr el;
-				check_class com c e.epos;
-				(match c.cl_constructor with None -> () | Some cf -> check_cf com cf e.epos)
-			| TTypeExpr(mt) | TCast(_,Some mt) ->
-				check_module_type com mt e.epos
-			| TMeta((Meta.Deprecated,_,_) as meta,e1) ->
-				print_deprecation_message com meta "field" e1.epos;
-				expr e1;
-			| _ ->
-				Type.iter expr e
-		in
-		expr e
-
-	let run_on_field com cf = match cf.cf_expr with None -> () | Some e -> run_on_expr com e
-
-	let run com =
-		List.iter (fun t -> match t with
-			| TClassDecl c ->
-				curclass := c;
-				(match c.cl_constructor with None -> () | Some cf -> run_on_field com cf);
-				(match c.cl_init with None -> () | Some e -> run_on_expr com e);
-				List.iter (run_on_field com) c.cl_ordered_statics;
-				List.iter (run_on_field com) c.cl_ordered_fields;
-			| _ ->
-				()
-		) com.types
-end
-
-module Diagnostics = struct
-	module DiagnosticsKind = struct
-		type t =
-			| DKUnusedImport
-			| DKUnresolvedIdentifier
-			| DKCompilerError
-			| DKRemovableCode
-
-		let to_int = function
-			| DKUnusedImport -> 0
-			| DKUnresolvedIdentifier -> 1
-			| DKCompilerError -> 2
-			| DKRemovableCode -> 3
-	end
-
-	open DiagnosticsKind
-	open DisplayTypes
-
-	let add_removable_code com s p prange =
-		let di = com.shared.shared_display_information in
-		di.removable_code <- (s,p,prange) :: di.removable_code
-
-	let find_unused_variables com e =
-		let vars = Hashtbl.create 0 in
-		let pmin_map = Hashtbl.create 0 in
-		let rec loop e = match e.eexpr with
-			| TVar(v,eo) when Meta.has Meta.UserVariable v.v_meta ->
-				Hashtbl.add pmin_map e.epos.pmin v;
-				let p = match eo with
-					| None -> e.epos
-					| Some e1 ->
-						loop e1;
-						{ e.epos with pmax = e1.epos.pmin }
-				in
-				Hashtbl.replace vars v.v_id (v,p);
-			| TLocal v when Meta.has Meta.UserVariable v.v_meta ->
-				Hashtbl.remove vars v.v_id;
-			| _ ->
-				Type.iter loop e
-		in
-		loop e;
-		Hashtbl.iter (fun _ (v,p) ->
-			let p = match (Hashtbl.find_all pmin_map p.pmin) with [_] -> p | _ -> null_pos in
-			add_removable_code com "Unused variable" v.v_pos p
-		) vars
-
-	let check_other_things com e =
-		let had_effect = ref false in
-		let no_effect p =
-			add_diagnostics_message com "This code has no effect" p DiagnosticsSeverity.Warning;
-		in
-		let pointless_compound s p =
-			add_diagnostics_message com (Printf.sprintf "This %s has no effect, but some of its sub-expressions do" s) p DiagnosticsSeverity.Warning;
-		in
-		let rec compound s el p =
-			let old = !had_effect in
-			had_effect := false;
-			List.iter (loop true) el;
-			if not !had_effect then no_effect p else pointless_compound s p;
-			had_effect := old;
-		and loop in_value e = match e.eexpr with
-			| TBlock el ->
-				let rec loop2 el = match el with
-					| [] -> ()
-					| [e] -> loop in_value e
-					| e :: el -> loop false e; loop2 el
-				in
-				loop2 el
-			| TMeta((Meta.Extern,_,_),_) ->
-				(* This is so something like `[inlineFunc()]` is not reported. *)
-				had_effect := true;
-			| TLocal v when not (Meta.has Meta.UserVariable v.v_meta) ->
-				()
-			| TConst _ | TLocal _ | TTypeExpr _ | TFunction _ | TIdent _ when not in_value ->
-				no_effect e.epos;
-			| TConst _ | TLocal _ | TTypeExpr _ | TEnumParameter _ | TEnumIndex _ | TVar _ | TIdent _ ->
-				()
-			| TFunction tf ->
-				loop false tf.tf_expr
-			| TCall({eexpr = TField(e1,fa)},el) when not in_value && PurityState.is_pure_field_access fa -> compound "call" el e.epos
-			| TNew _ | TCall _ | TBinop ((Ast.OpAssignOp _ | Ast.OpAssign),_,_) | TUnop ((Ast.Increment | Ast.Decrement),_,_)
-			| TReturn _ | TBreak | TContinue | TThrow _ | TCast (_,Some _)
-			| TIf _ | TTry _ | TSwitch _ | TWhile _ | TFor _ ->
-				had_effect := true;
-				Type.iter (loop true) e
-			| TParenthesis e1 | TMeta(_,e1) ->
-				loop in_value e1
-			| TArray _ | TCast (_,None) | TBinop _ | TUnop _
-			| TField _ | TArrayDecl _ | TObjectDecl _ when in_value ->
-				Type.iter (loop true) e;
-			| TArray(e1,e2) -> compound "array access" [e1;e2] e.epos
-			| TCast(e1,None) -> compound "cast" [e1] e.epos
-			| TBinop(op,e1,e2) -> compound (Printf.sprintf "'%s' operator" (s_binop op)) [e1;e2] e.epos
-			| TUnop(op,_,e1) -> compound (Printf.sprintf "'%s' operator" (s_unop op)) [e1] e.epos
-			| TField(e1,_) -> compound "field access" [e1] e.epos
-			| TArrayDecl el -> compound "array declaration" el e.epos
-			| TObjectDecl fl -> compound "object declaration" (List.map snd fl) e.epos
-		in
-		loop true e
-
-	let prepare_field com cf = match cf.cf_expr with
-		| None -> ()
-		| Some e ->
-			find_unused_variables com e;
-			check_other_things com e;
-			DeprecationCheck.run_on_expr com e
-
-	let prepare com global =
-		List.iter (function
-			| TClassDecl c when global || is_display_file c.cl_pos.pfile ->
-				List.iter (prepare_field com) c.cl_ordered_fields;
-				List.iter (prepare_field com) c.cl_ordered_statics;
-				(match c.cl_constructor with None -> () | Some cf -> prepare_field com cf);
-			| _ ->
-				()
-		) com.types
-
-	let is_diagnostics_run ctx = match ctx.com.display.dms_kind with
-		| DMDiagnostics true -> true
-		| DMDiagnostics false -> ctx.is_display_file
-		| _ -> false
-
-	let secure_generated_code ctx e =
-		if is_diagnostics_run ctx then mk (TMeta((Meta.Extern,[],e.epos),e)) e.etype e.epos else e
-end
-
-module ImportHandling = struct
-	type import_display_kind =
-		| IDKPackage of string list
-		| IDKModule of string list * string
-		| IDKSubType of string list * string * string
-		| IDKModuleField of string list * string * string
-		| IDKSubTypeField of string list * string * string * string
-		| IDK
-
-	type import_display = import_display_kind * pos
-
-	let convert_import_to_something_usable pt path =
-		let rec loop pack m t = function
-			| (s,p) :: l ->
-				let is_lower = is_lower_ident s in
-				let is_display_pos = encloses_position pt p in
-				begin match is_lower,m,t with
-					| _,None,Some _ ->
-						assert false (* impossible, I think *)
-					| true,Some m,None ->
-						if is_display_pos then (IDKModuleField(List.rev pack,m,s),p)
-						else (IDK,p) (* assume that we're done *)
-					| _,Some m,Some t ->
-						if is_display_pos then (IDKSubTypeField(List.rev pack,m,t,s),p)
-						else (IDK,p)
-					| true,None,None ->
-						if is_display_pos then (IDKPackage (List.rev (s :: pack)),p)
-						else loop (s :: pack) m t l
-					| false,Some sm,None ->
-						if is_display_pos then (IDKSubType (List.rev pack,sm,s),p)
-						else loop pack m (Some s) l
-					| false,None,None ->
-						if is_display_pos then (IDKModule (List.rev pack,s),p)
-						else loop pack (Some s) None l
-				end
-			| [] ->
-				(IDK,null_pos)
-		in
-		loop [] None None path
-
-	let add_import_position com p path =
-		com.shared.shared_display_information.import_positions <- PMap.add p (ref false,path) com.shared.shared_display_information.import_positions
-
-	let mark_import_position com p =
-		try
-			let r = fst (PMap.find p com.shared.shared_display_information.import_positions) in
-			r := true
-		with Not_found ->
-			()
-
-	let maybe_mark_import_position ctx p =
-		if Diagnostics.is_diagnostics_run ctx then mark_import_position ctx.com p
-end
-
-module Statistics = struct
-	open ImportHandling
-
-	type relation =
-		| Implemented
-		| Extended
-		| Overridden
-		| Referenced
-
-	type symbol =
-		| SKClass of tclass
-		| SKInterface of tclass
-		| SKEnum of tenum
-		| SKTypedef of tdef
-		| SKAbstract of tabstract
-		| SKField of tclass_field
-		| SKEnumField of tenum_field
-		| SKVariable of tvar
-
-	let collect_statistics ctx =
-		let relations = Hashtbl.create 0 in
-		let symbols = Hashtbl.create 0 in
-		let handled_modules = Hashtbl.create 0 in
-		let add_relation pos r =
-			if pos <> null_pos then try
-				let l = Hashtbl.find relations pos in
-				if not (List.mem r l) then
-					Hashtbl.replace relations pos (r :: l)
-			with Not_found ->
-				Hashtbl.add relations pos [r]
-		in
-		let declare kind p =
-			if p <> null_pos then begin
-				if not (Hashtbl.mem relations p) then Hashtbl.add relations p [];
-				Hashtbl.replace symbols p kind;
-			end
-		in
-		let collect_overrides c =
-			List.iter (fun cf ->
-				let rec loop c = match c.cl_super with
-					| Some (c,_) ->
-						begin try
-							let cf' = PMap.find cf.cf_name c.cl_fields in
-							add_relation cf'.cf_name_pos (Overridden,cf.cf_pos)
-						with Not_found ->
-							loop c
-						end
-					| _ ->
-						()
-				in
-				loop c
-			) c.cl_overrides
-		in
-		let rec find_real_constructor c = match c.cl_constructor,c.cl_super with
-			(* The pos comparison might be a bit weak, not sure... *)
-			| Some cf,_ when not (Meta.has Meta.CompilerGenerated cf.cf_meta) && c.cl_pos <> cf.cf_pos -> cf
-			| _,Some(c,_) -> find_real_constructor c
-			| _,None -> raise Not_found
-		in
-		let var_decl v = declare (SKVariable v) v.v_pos in
-		let patch_string_pos p s = { p with pmin = p.pmax - String.length s } in
-		let field_reference cf p =
-			add_relation cf.cf_name_pos (Referenced,patch_string_pos p cf.cf_name)
-		in
-		let collect_references c e =
-			let rec loop e = match e.eexpr with
-				| TField(e1,fa) ->
-					(* Check if the sub-expression is actually shorter than the whole one. This should
-					   detect cases where it was automatically generated. *)
-					if e1.epos.pmin = e.epos.pmin && e1.epos.pmax <> e.epos.pmax then
-						loop e1;
-					begin match fa with
-						| FStatic(_,cf) | FInstance(_,_,cf) | FClosure(_,cf) ->
-							field_reference cf e.epos
-						| FAnon cf ->
-							declare  (SKField cf) cf.cf_name_pos;
-							field_reference cf e.epos
-						| FEnum(_,ef) ->
-							add_relation ef.ef_name_pos (Referenced,patch_string_pos e.epos ef.ef_name)
-						| FDynamic _ ->
-							()
-					end
-				| TTypeExpr mt ->
-					let tinfos = t_infos mt in
-					add_relation tinfos.mt_name_pos (Referenced,patch_string_pos e.epos (snd tinfos.mt_path))
-				| TNew(c,_,el) ->
-					List.iter loop el;
-					(try add_relation (find_real_constructor c).cf_name_pos (Referenced,e.epos) with Not_found -> ());
-				| TCall({eexpr = TConst TSuper},el) ->
-					List.iter loop el;
-					begin match c.cl_super with
-						| Some(c,_) -> (try add_relation (find_real_constructor c).cf_name_pos (Referenced,e.epos) with Not_found -> ())
-						| None -> ()
-					end
-				| TVar(v,eo) ->
-					Option.may loop eo;
-					var_decl v;
-				| TFor(v,e1,e2) ->
-					var_decl v;
-					loop e1;
-					loop e2;
-				| TFunction tf ->
-					List.iter (fun (v,_) -> var_decl v) tf.tf_args;
-					loop tf.tf_expr;
-				| TLocal v when e.epos.pmax - e.epos.pmin = String.length v.v_name ->
-					add_relation v.v_pos (Referenced,e.epos)
-				| _ ->
-					Type.iter loop e
-			in
-			loop e
-		in
-		let rec explore_type_hint (p,t) =
-			match t with
-			| TMono r -> (match !r with None -> () | Some t -> explore_type_hint (p,t))
-			| TLazy f -> explore_type_hint (p,lazy_type f)
-			| TInst(({cl_name_pos = pn;cl_path = (_,name)}),_)
-			| TEnum(({e_name_pos = pn;e_path = (_,name)}),_)
-			| TType(({t_name_pos = pn;t_path = (_,name)}),_)
-			| TAbstract(({a_name_pos = pn;a_path = (_,name)}),_) ->
-				add_relation pn (Referenced,p)
-			| TDynamic _ -> ()
-			| TFun _ | TAnon _ -> ()
-		in
-		let check_module m =
-			if not (Hashtbl.mem handled_modules m.m_path) then begin
-				Hashtbl.add handled_modules m.m_path true;
-				List.iter (fun (p1,p2) ->
-					add_relation p1 (Referenced,p2)
-				) m.m_extra.m_display.m_inline_calls;
-				List.iter explore_type_hint m.m_extra.m_display.m_type_hints
-			end
-		in
-		let f = function
-			| TClassDecl c ->
-				check_module c.cl_module;
-				declare (if c.cl_interface then (SKInterface c) else (SKClass c)) c.cl_name_pos;
-				List.iter (fun (c',_) -> add_relation c'.cl_name_pos ((if c.cl_interface then Extended else Implemented),c.cl_name_pos)) c.cl_implements;
-				begin match c.cl_super with
-					| None -> ()
-					| Some (c',_) -> add_relation c'.cl_name_pos (Extended,c.cl_name_pos);
-				end;
-				collect_overrides c;
-				let field cf =
-					if cf.cf_pos.pmin > c.cl_name_pos.pmin then declare (SKField cf) cf.cf_name_pos;
-					let _ = follow cf.cf_type in
-					match cf.cf_expr with None -> () | Some e -> collect_references c e
-				in
-				Option.may field c.cl_constructor;
-				List.iter field c.cl_ordered_fields;
-				List.iter field c.cl_ordered_statics;
-			| TEnumDecl en ->
-				check_module en.e_module;
-				declare (SKEnum en) en.e_name_pos;
-				PMap.iter (fun _ ef -> declare (SKEnumField ef) ef.ef_name_pos) en.e_constrs
-			| TTypeDecl td ->
-				check_module td.t_module;
-				declare (SKTypedef td) td.t_name_pos
-			| TAbstractDecl a ->
-				check_module a.a_module;
-				declare (SKAbstract a) a.a_name_pos
-		in
-		begin match CompilationServer.get () with
-			| None ->
-				let rec loop com =
-					List.iter f com.types;
-					Option.may loop (com.get_macros())
-				in
-				loop ctx.com
-			| Some cs ->
-				let rec loop com =
-					(* CompilationServer.cache_context cs com; *)
-					CompilationServer.iter_modules cs com (fun m -> List.iter f m.m_types);
-					Option.may loop (com.get_macros())
-				in
-				loop ctx.com
-		end;
-		let l = List.fold_left (fun acc (_,cfi,_,cfo) -> match cfo with
-			| Some cf -> if List.mem_assoc cf.cf_name_pos acc then acc else (cf.cf_name_pos,cfi.cf_name_pos) :: acc
-			| None -> acc
-		) [] ctx.com.display_information.interface_field_implementations in
-		List.iter (fun (p,p') -> add_relation p' (Implemented,p)) l;
-		(* let deal_with_imports paths =
-			let check_subtype m s p =
-				try
-					let mt = List.find (fun mt -> snd (t_infos mt).mt_path = s) m.m_types in
-					add_relation (t_infos mt).mt_name_pos (Referenced,p);
-					Some mt
-				with Not_found ->
-					None
-			in
-			let check_module path p =
-				let m = ctx.g.do_load_module ctx path p in
-				m
-			in
-			let check_field c s p =
-				let cf = PMap.find s c.cl_statics in
-				add_relation cf.cf_name_pos (Referenced,p)
-			in
-			let check_subtype_field m ssub psub sfield pfield = match check_subtype m ssub psub with
-				| Some (TClassDecl c) -> check_field c sfield pfield
-				| _ -> ()
-			in
-			PMap.iter (fun p (_,path) ->
-				match ImportHandling.convert_import_to_something_usable { p with pmin = p.pmax - 1; pmax = p.pmax - 1 } path,List.rev path with
-				| (IDKSubType(sl,s1,s2),_),(_,psubtype) :: (_,pmodule) :: _ ->
-					let m = check_module (sl,s1) pmodule in
-					(*ignore(check_subtype m s1 pmodule);*)
-					ignore(check_subtype m s2 psubtype)
-				| (IDKModuleField(sl,s1,s2),_),(_,pfield) :: (_,pmodule) :: _ ->
-					let m = check_module (sl,s1) pmodule in
-					check_subtype_field m s1 pmodule s2 pfield
-				| (IDKSubTypeField(sl,s1,s2,s3),_),(_,pfield) :: (_,psubtype) :: (_,pmodule) :: _ ->
-					let m = check_module (sl,s1) pmodule in
-					check_subtype_field m s2 psubtype s3 pfield
-				| (IDKModule(sl,s),_),(_,pmodule) :: _ ->
-					let m = check_module (sl,s) pmodule in
-					ignore(check_subtype m s pmodule);
-				| _ ->
-					()
-			) paths
-		in
-		if false then deal_with_imports ctx.com.shared.shared_display_information.import_positions; *)
-		symbols,relations
-end

+ 86 - 0
src/context/display/deprecationCheck.ml

@@ -0,0 +1,86 @@
+open Globals
+open Type
+open Common
+open Ast
+
+let curclass = ref null_class
+
+let warned_positions = Hashtbl.create 0
+
+let print_deprecation_message com meta s p_usage =
+	let s = match meta with
+		| _,[EConst(String s),_],_ -> s
+		| _ -> Printf.sprintf "Usage of this %s is deprecated" s
+	in
+	if not (Hashtbl.mem warned_positions p_usage) then begin
+		Hashtbl.replace warned_positions p_usage true;
+		com.warning s p_usage;
+	end
+
+let check_meta com meta s p_usage =
+	try
+		print_deprecation_message com (Meta.get Meta.Deprecated meta) s p_usage;
+	with Not_found ->
+		()
+
+let check_cf com cf p = check_meta com cf.cf_meta "field" p
+
+let check_class com c p = if c != !curclass then check_meta com c.cl_meta "class" p
+
+let check_enum com en p = check_meta com en.e_meta "enum" p
+
+let check_ef com ef p = check_meta com ef.ef_meta "enum field" p
+
+let check_typedef com t p = check_meta com t.t_meta "typedef" p
+
+let check_module_type com mt p = match mt with
+	| TClassDecl c -> check_class com c p
+	| TEnumDecl en -> check_enum com en p
+	| _ -> ()
+
+let run_on_expr com e =
+	let rec expr e = match e.eexpr with
+		| TField(e1,fa) ->
+			expr e1;
+			begin match fa with
+				| FStatic(c,cf) | FInstance(c,_,cf) ->
+					check_class com c e.epos;
+					check_cf com cf e.epos
+				| FAnon cf ->
+					check_cf com cf e.epos
+				| FClosure(co,cf) ->
+					(match co with None -> () | Some (c,_) -> check_class com c e.epos);
+					check_cf com cf e.epos
+				| FEnum(en,ef) ->
+					check_enum com en e.epos;
+					check_ef com ef e.epos;
+				| _ ->
+					()
+			end
+		| TNew(c,_,el) ->
+			List.iter expr el;
+			check_class com c e.epos;
+			(match c.cl_constructor with None -> () | Some cf -> check_cf com cf e.epos)
+		| TTypeExpr(mt) | TCast(_,Some mt) ->
+			check_module_type com mt e.epos
+		| TMeta((Meta.Deprecated,_,_) as meta,e1) ->
+			print_deprecation_message com meta "field" e1.epos;
+			expr e1;
+		| _ ->
+			Type.iter expr e
+	in
+	expr e
+
+let run_on_field com cf = match cf.cf_expr with None -> () | Some e -> run_on_expr com e
+
+let run com =
+	List.iter (fun t -> match t with
+		| TClassDecl c ->
+			curclass := c;
+			(match c.cl_constructor with None -> () | Some cf -> run_on_field com cf);
+			(match c.cl_init with None -> () | Some e -> run_on_expr com e);
+			List.iter (run_on_field com) c.cl_ordered_statics;
+			List.iter (run_on_field com) c.cl_ordered_fields;
+		| _ ->
+			()
+	) com.types

+ 217 - 0
src/context/display/diagnostics.ml

@@ -0,0 +1,217 @@
+open Globals
+open Ast
+open Type
+open Typecore
+open Common
+open Display
+open DisplayTypes.DisplayMode
+
+module DiagnosticsKind = struct
+	type t =
+		| DKUnusedImport
+		| DKUnresolvedIdentifier
+		| DKCompilerError
+		| DKRemovableCode
+
+	let to_int = function
+		| DKUnusedImport -> 0
+		| DKUnresolvedIdentifier -> 1
+		| DKCompilerError -> 2
+		| DKRemovableCode -> 3
+end
+
+open DiagnosticsKind
+open DisplayTypes
+
+let add_removable_code com s p prange =
+	let di = com.shared.shared_display_information in
+	di.removable_code <- (s,p,prange) :: di.removable_code
+
+let find_unused_variables com e =
+	let vars = Hashtbl.create 0 in
+	let pmin_map = Hashtbl.create 0 in
+	let rec loop e = match e.eexpr with
+		| TVar(v,eo) when Meta.has Meta.UserVariable v.v_meta ->
+			Hashtbl.add pmin_map e.epos.pmin v;
+			let p = match eo with
+				| None -> e.epos
+				| Some e1 ->
+					loop e1;
+					{ e.epos with pmax = e1.epos.pmin }
+			in
+			Hashtbl.replace vars v.v_id (v,p);
+		| TLocal v when Meta.has Meta.UserVariable v.v_meta ->
+			Hashtbl.remove vars v.v_id;
+		| _ ->
+			Type.iter loop e
+	in
+	loop e;
+	Hashtbl.iter (fun _ (v,p) ->
+		let p = match (Hashtbl.find_all pmin_map p.pmin) with [_] -> p | _ -> null_pos in
+		add_removable_code com "Unused variable" v.v_pos p
+	) vars
+
+let check_other_things com e =
+	let had_effect = ref false in
+	let no_effect p =
+		add_diagnostics_message com "This code has no effect" p DiagnosticsSeverity.Warning;
+	in
+	let pointless_compound s p =
+		add_diagnostics_message com (Printf.sprintf "This %s has no effect, but some of its sub-expressions do" s) p DiagnosticsSeverity.Warning;
+	in
+	let rec compound s el p =
+		let old = !had_effect in
+		had_effect := false;
+		List.iter (loop true) el;
+		if not !had_effect then no_effect p else pointless_compound s p;
+		had_effect := old;
+	and loop in_value e = match e.eexpr with
+		| TBlock el ->
+			let rec loop2 el = match el with
+				| [] -> ()
+				| [e] -> loop in_value e
+				| e :: el -> loop false e; loop2 el
+			in
+			loop2 el
+		| TMeta((Meta.Extern,_,_),_) ->
+			(* This is so something like `[inlineFunc()]` is not reported. *)
+			had_effect := true;
+		| TLocal v when not (Meta.has Meta.UserVariable v.v_meta) ->
+			()
+		| TConst _ | TLocal _ | TTypeExpr _ | TFunction _ | TIdent _ when not in_value ->
+			no_effect e.epos;
+		| TConst _ | TLocal _ | TTypeExpr _ | TEnumParameter _ | TEnumIndex _ | TVar _ | TIdent _ ->
+			()
+		| TFunction tf ->
+			loop false tf.tf_expr
+		| TCall({eexpr = TField(e1,fa)},el) when not in_value && PurityState.is_pure_field_access fa -> compound "call" el e.epos
+		| TNew _ | TCall _ | TBinop ((Ast.OpAssignOp _ | Ast.OpAssign),_,_) | TUnop ((Ast.Increment | Ast.Decrement),_,_)
+		| TReturn _ | TBreak | TContinue | TThrow _ | TCast (_,Some _)
+		| TIf _ | TTry _ | TSwitch _ | TWhile _ | TFor _ ->
+			had_effect := true;
+			Type.iter (loop true) e
+		| TParenthesis e1 | TMeta(_,e1) ->
+			loop in_value e1
+		| TArray _ | TCast (_,None) | TBinop _ | TUnop _
+		| TField _ | TArrayDecl _ | TObjectDecl _ when in_value ->
+			Type.iter (loop true) e;
+		| TArray(e1,e2) -> compound "array access" [e1;e2] e.epos
+		| TCast(e1,None) -> compound "cast" [e1] e.epos
+		| TBinop(op,e1,e2) -> compound (Printf.sprintf "'%s' operator" (s_binop op)) [e1;e2] e.epos
+		| TUnop(op,_,e1) -> compound (Printf.sprintf "'%s' operator" (s_unop op)) [e1] e.epos
+		| TField(e1,_) -> compound "field access" [e1] e.epos
+		| TArrayDecl el -> compound "array declaration" el e.epos
+		| TObjectDecl fl -> compound "object declaration" (List.map snd fl) e.epos
+	in
+	loop true e
+
+let prepare_field com cf = match cf.cf_expr with
+	| None -> ()
+	| Some e ->
+		find_unused_variables com e;
+		check_other_things com e;
+		DeprecationCheck.run_on_expr com e
+
+let prepare com global =
+	List.iter (function
+		| TClassDecl c when global || is_display_file c.cl_pos.pfile ->
+			List.iter (prepare_field com) c.cl_ordered_fields;
+			List.iter (prepare_field com) c.cl_ordered_statics;
+			(match c.cl_constructor with None -> () | Some cf -> prepare_field com cf);
+		| _ ->
+			()
+	) com.types
+
+let is_diagnostics_run p = match (!Parser.display_mode) with
+	| DMDiagnostics true -> true
+	| DMDiagnostics false -> is_display_file p.pfile
+	| _ -> false
+
+let secure_generated_code ctx e =
+	if is_diagnostics_run e.epos then mk (TMeta((Meta.Extern,[],e.epos),e)) e.etype e.epos else e
+
+
+module Printer = struct
+	open Json
+	open DiagnosticsKind
+	open DisplayTypes
+
+	type t = DiagnosticsKind.t * pos
+
+	module UnresolvedIdentifierSuggestion = struct
+		type t =
+			| UISImport
+			| UISTypo
+
+		let to_int = function
+			| UISImport -> 0
+			| UISTypo -> 1
+	end
+
+	let print_diagnostics ctx global =
+		let com = ctx.com in
+		let diag = Hashtbl.create 0 in
+		let add dk p sev args =
+			let file = Path.get_real_path p.pfile in
+			let diag = try
+				Hashtbl.find diag file
+			with Not_found ->
+				let d = DynArray.create() in
+				Hashtbl.add diag file d;
+				d
+			in
+			DynArray.add diag (dk,p,sev,args)
+		in
+		let add dk p sev args =
+			if global || is_display_file p.pfile then add dk p sev args
+		in
+		let find_type i =
+			let types = ref [] in
+			Hashtbl.iter (fun _ m ->
+				List.iter (fun mt ->
+					let s_full_type_path (p,s) n = s_type_path (p,s) ^ if (s <> n) then "." ^ n else "" in
+					let tinfos = t_infos mt in
+					if snd tinfos.mt_path = i then
+						types := JObject [
+							"kind",JInt (UnresolvedIdentifierSuggestion.to_int UnresolvedIdentifierSuggestion.UISImport);
+							"name",JString (s_full_type_path m.m_path i)
+						] :: !types
+				) m.m_types;
+			) ctx.g.modules;
+			!types
+		in
+		List.iter (fun (s,p,suggestions) ->
+			let suggestions = List.map (fun (s,_) ->
+				JObject [
+					"kind",JInt (UnresolvedIdentifierSuggestion.to_int UnresolvedIdentifierSuggestion.UISTypo);
+					"name",JString s
+				]
+			) suggestions in
+			add DKUnresolvedIdentifier p DiagnosticsSeverity.Error (JArray (suggestions @ (find_type s)));
+		) com.display_information.unresolved_identifiers;
+		PMap.iter (fun p (r,_) ->
+			if not !r then add DKUnusedImport p DiagnosticsSeverity.Warning (JArray [])
+		) com.shared.shared_display_information.import_positions;
+		List.iter (fun (s,p,sev) ->
+			add DKCompilerError p sev (JString s)
+		) com.shared.shared_display_information.diagnostics_messages;
+		List.iter (fun (s,p,prange) ->
+			add DKRemovableCode p DiagnosticsSeverity.Warning (JObject ["description",JString s;"range",if prange = null_pos then JNull else Genjson.generate_pos_as_range prange])
+		) com.shared.shared_display_information.removable_code;
+		let jl = Hashtbl.fold (fun file diag acc ->
+			let jl = DynArray.fold_left (fun acc (dk,p,sev,jargs) ->
+				(JObject [
+					"kind",JInt (to_int dk);
+					"severity",JInt (DiagnosticsSeverity.to_int sev);
+					"range",Genjson.generate_pos_as_range p;
+					"args",jargs
+				]) :: acc
+			) [] diag in
+			(JObject [
+				"file",JString file;
+				"diagnostics",JArray jl
+			]) :: acc
+		) diag [] in
+		let js = JArray jl in
+		string_of_json js
+end

+ 110 - 0
src/context/display/display.ml

@@ -0,0 +1,110 @@
+open Ast
+open Common
+open DisplayTypes
+open DisplayMode
+open CompletionItem
+open CompletionResultKind
+open Type
+open Typecore
+open Globals
+open Genjson
+
+let reference_position = ref null_pos
+
+let is_display_file file =
+	file <> "?" && Path.unique_full_path file = (!Parser.resume_display).pfile
+
+let encloses_position p_target p =
+	p.pmin < p_target.pmin && p.pmax >= p_target.pmax
+
+let is_display_position p =
+	encloses_position !Parser.resume_display p
+
+module ExprPreprocessing = struct
+	let find_before_pos com is_completion e =
+		let display_pos = ref (!Parser.resume_display) in
+		let is_annotated p = encloses_position !display_pos p in
+		let annotate e dk =
+			display_pos := { pfile = ""; pmin = -2; pmax = -2 };
+			(EDisplay(e,dk),pos e)
+		in
+		let annotate_marked e = annotate e DKMarked in
+		let mk_null p = annotate_marked ((EConst(Ident "null")),p) in
+		let loop_el el =
+			let pr = !Parser.resume_display in
+			let rec loop el = match el with
+				| [] -> [mk_null pr]
+				| e :: el ->
+					if (pos e).pmin >= pr.pmax then (mk_null pr) :: e :: el
+					else e :: loop el
+			in
+			(* print_endline (Printf.sprintf "%i-%i: PR" pr.pmin pr.pmax);
+			List.iter (fun e ->
+				print_endline (Printf.sprintf "%i-%i: %s" (pos e).pmin (pos e).pmax (Ast.s_expr e));
+			) el; *)
+			match el with
+			| [] -> [mk_null pr]
+			| e :: el ->
+				if (pos e).pmin >= pr.pmax then (mk_null pr) :: e :: el
+				else loop (e :: el)
+		in
+		let loop e =
+			(* print_endline (Printf.sprintf "%i-%i: %s" (pos e).pmin (pos e).pmax (Ast.s_expr e)); *)
+			match fst e with
+			| EVars vl ->
+				if List.exists (fun ((_,p),_,_) -> is_annotated p) vl then
+					annotate_marked e
+				else
+					e
+			| EBlock [] when is_annotated (pos e) ->
+				annotate e DKStructure
+			| EBlock el when is_annotated (pos e) && is_completion ->
+				let el = loop_el el in
+				EBlock el,(pos e)
+			| ECall(e1,el) when is_annotated (pos e) && is_completion ->
+				let el = loop_el el in
+				ECall(e1,el),(pos e)
+			| ENew((tp,pp),el) when is_annotated (pos e) && is_completion ->
+				if is_annotated pp || pp.pmax >= !Parser.resume_display.pmax then
+					annotate_marked e
+				else begin
+					let el = loop_el el in
+					ENew((tp,pp),el),(pos e)
+				end
+			| EArrayDecl el when is_annotated (pos e) && is_completion ->
+				let el = loop_el el in
+				EArrayDecl el,(pos e)
+			| EDisplay _ ->
+				raise Exit
+			| EConst (String _) when (not (Lexer.is_fmt_string (pos e)) || !Parser.was_auto_triggered) && is_annotated (pos e) && is_completion ->
+				(* TODO: check if this makes any sense *)
+				raise Exit
+			| _ ->
+				if is_annotated (pos e) then
+					annotate_marked e
+				else
+					e
+		in
+		let rec map e =
+			loop (Ast.map_expr map e)
+		in
+		try map e with Exit -> e
+
+	let find_display_call e =
+		let found = ref false in
+		let loop e = match fst e with
+			| ECall _ | ENew _ when not !found && is_display_position (pos e) ->
+				found := true;
+				Parser.mk_display_expr e DKCall
+			| _ -> e
+		in
+		let rec map e = loop (Ast.map_expr map e) in
+		map e
+
+
+	let process_expr com e = match com.display.dms_kind with
+		| DMDefinition | DMUsage _ | DMHover -> find_before_pos com false e
+		| DMDefault -> find_before_pos com true e
+		| DMSignature -> find_display_call e
+		| _ -> e
+end

+ 123 - 0
src/context/display/displayEmitter.ml

@@ -0,0 +1,123 @@
+open Globals
+open Ast
+open Type
+open Typecore
+open DisplayException
+open DisplayTypes.DisplayMode
+open CompletionItem
+open DisplayTypes.CompletionResultKind
+open Common
+open Display
+
+let requires_import ctx path =
+	try
+		let mt' = ctx.g.do_load_type_def ctx null_pos {tpackage = []; tname = snd path; tparams = []; tsub = None} in
+		path <> (t_infos mt').mt_path
+	with _ ->
+		true
+
+let patch_type ctx t =
+	let rec patch t = match t with
+		| TInst(c,tl) when not (requires_import ctx c.cl_path) -> TInst({c with cl_path = ([],snd c.cl_path)},List.map patch tl)
+		| TEnum(en,tl) when not (requires_import ctx en.e_path) -> TEnum({en with e_path = ([],snd en.e_path)},List.map patch tl)
+		| TType(td,tl) when not (requires_import ctx td.t_path) -> TType({td with t_path = ([],snd td.t_path)},List.map patch tl)
+		| TAbstract(a,tl) when not (requires_import ctx a.a_path) -> TAbstract({a with a_path = ([],snd a.a_path)},List.map patch tl)
+		| _ -> Type.map patch t
+	in
+	patch t
+
+let display_module_type ctx mt p = match ctx.com.display.dms_kind with
+	| DMDefinition -> raise_position [(t_infos mt).mt_name_pos];
+	| DMUsage _ -> reference_position := (t_infos mt).mt_name_pos
+	| DMHover -> raise_hover (Some (patch_type ctx (type_of_module_type mt))) p (t_infos mt).mt_doc
+	| _ -> ()
+
+let rec display_type ctx t p =
+	let dm = ctx.com.display in
+	match dm.dms_kind with
+	| DMHover ->
+		raise_hover (Some (patch_type ctx t)) p None
+	| _ ->
+		try display_module_type ctx (module_type_of_type t) p
+		with Exit -> match follow t,follow !t_dynamic_def with
+			| _,TDynamic _ -> () (* sanity check in case it's still t_dynamic *)
+			| TDynamic _,_ -> display_type ctx !t_dynamic_def p
+			| _ -> ()
+
+let check_display_type ctx t p =
+	let add_type_hint () =
+		let md = ctx.m.curmod.m_extra.m_display in
+		md.m_type_hints <- (p,t) :: md.m_type_hints;
+	in
+	let maybe_display_type () =
+		if ctx.is_display_file && is_display_position p then
+			display_type ctx t p
+	in
+	match ctx.com.display.dms_kind with
+	| DMStatistics -> add_type_hint()
+	| DMUsage _ -> add_type_hint(); maybe_display_type()
+	| _ -> maybe_display_type()
+
+let display_variable ctx v p = match ctx.com.display.dms_kind with
+	| DMDefinition -> raise_position [v.v_pos]
+	| DMUsage _ -> reference_position := v.v_pos
+	| DMHover -> raise_hover (Some (patch_type ctx v.v_type)) p None
+	| _ -> ()
+
+let display_field ctx c cf p = match ctx.com.display.dms_kind with
+	| DMDefinition -> raise_position [cf.cf_name_pos]
+	| DMUsage _ -> reference_position := cf.cf_name_pos
+	| DMHover ->
+		let t = if Meta.has Meta.Impl cf.cf_meta then
+			(prepare_using_field cf).cf_type
+		else
+			cf.cf_type
+		in
+		let t = match c,follow t with
+			| Some c,TFun(tl,_) when cf.cf_name = "new" -> TFun(tl,TInst(c,List.map snd c.cl_params))
+			| _ -> t
+		in
+		raise_hover (Some (patch_type ctx t)) p cf.cf_doc
+	| _ -> ()
+
+let maybe_display_field ctx c cf p =
+	if is_display_position p then display_field ctx c cf p
+
+let display_enum_field ctx ef p = match ctx.com.display.dms_kind with
+	| DMDefinition -> raise_position [ef.ef_name_pos]
+	| DMUsage _ -> reference_position := ef.ef_name_pos
+	| DMHover -> raise_hover (Some (patch_type ctx ef.ef_type)) p ef.ef_doc
+	| _ -> ()
+
+let display_meta com meta p = match com.display.dms_kind with
+	| DMHover ->
+		begin match meta with
+		| Meta.Custom _ | Meta.Dollar _ -> ()
+		| _ -> match Meta.get_documentation meta with
+			| None -> ()
+			| Some (_,s) ->
+				(* TODO: hack until we support proper output for hover display mode *)
+				if com.json_out = None then
+					raise_metadata ("<metadata>" ^ s ^ "</metadata>")
+				else
+					raise_hover None null_pos (Some s)
+		end
+	| DMDefault ->
+		let all,_ = Meta.get_documentation_list() in
+		let all = List.map (fun (s,doc) ->
+			ITMetadata(s,Some doc)
+		) all in
+		raise_fields all CRMetadata (Some p) false
+	| _ ->
+		()
+
+let check_display_metadata ctx meta =
+	List.iter (fun (meta,args,p) ->
+		if is_display_position p then display_meta ctx.com meta p;
+		List.iter (fun e ->
+			if is_display_position (pos e) then begin
+				let e = ExprPreprocessing.process_expr ctx.com e in
+				delay ctx PTypeField (fun _ -> ignore(type_expr ctx e Value));
+			end
+		) args
+	) meta

+ 71 - 0
src/context/display/displayException.ml

@@ -0,0 +1,71 @@
+open Globals
+open Ast
+open DisplayTypes
+open CompletionItem
+open Type
+open Genjson
+
+type kind =
+	| Diagnostics of string
+	| Statistics of string
+	| ModuleSymbols of string
+	| Metadata of string
+	| DisplaySignatures of (tsignature * documentation) list * int * int
+	| DisplayHover of t option * pos * string option
+	| DisplayPosition of pos list
+	| DisplayFields of CompletionItem.t list * CompletionResultKind.t * pos option (* insert pos *) * bool (* sorted? *)
+	| DisplayPackage of string list
+
+exception DisplayException of kind
+
+let raise_diagnostics s = raise (DisplayException(Diagnostics s))
+let raise_statistics s = raise (DisplayException(Statistics s))
+let raise_module_symbols s = raise (DisplayException(ModuleSymbols s))
+let raise_metadata s = raise (DisplayException(Metadata s))
+let raise_signatures l isig iarg = raise (DisplayException(DisplaySignatures(l,isig,iarg)))
+let raise_hover t p so = raise (DisplayException(DisplayHover(t,p,so)))
+let raise_position pl = raise (DisplayException(DisplayPosition pl))
+let raise_fields ckl cr po b = raise (DisplayException(DisplayFields(ckl,cr,po,b)))
+let raise_package sl = raise (DisplayException(DisplayPackage sl))
+
+(* global state *)
+let last_completion_result = ref (Array.make 0 (ITModule ""))
+
+let to_json ctx de =
+	match de with
+	| Diagnostics _
+	| Statistics _
+	| ModuleSymbols _
+	| Metadata _ -> assert false
+	| DisplaySignatures(sigs,isig,iarg) ->
+		(* We always want full info for signatures *)
+		let ctx = Genjson.create_context GMFull in
+		let fsig ((tl,tr),doc) =
+			let fl = generate_function_signature ctx tl tr in
+			let fl = (match doc with None -> fl | Some s -> ("documentation",jstring s) :: fl) in
+			jobject fl
+		in
+		jobject [
+			"activeSignature",jint isig;
+			"activeParameter",jint iarg;
+			"signatures",jlist fsig sigs;
+		]
+	| DisplayHover(t,p,doc) ->
+		jobject [
+			"documentation",jopt jstring doc;
+			"range",generate_pos_as_range p;
+			"type",jopt (generate_type ctx) t;
+		]
+	| DisplayPosition pl ->
+		jarray (List.map generate_pos_as_location pl)
+	| DisplayFields(fields,kind,po,sorted) ->
+		let ja = List.map (CompletionItem.to_json ctx) fields in
+		last_completion_result := Array.of_list fields;
+		let fl =
+			("items",jarray ja) ::
+			("kind",jint (Obj.magic kind)) ::
+			("sorted",jbool sorted) ::
+			(match po with None -> [] | Some p -> ["replaceRange",generate_pos_as_range p]) in
+		jobject fl
+	| DisplayPackage pack ->
+		jarray (List.map jstring pack)

+ 6 - 3
src/context/displayFields.ml → src/context/display/displayFields.ml

@@ -21,12 +21,15 @@ open Globals
 open Error
 open Typecore
 open Type
-open DisplayTypes.CompletionKind
+open CompletionItem
 
 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 -> ITType((t_infos mt).mt_path,DisplayTypes.CompletionItemKind.of_module_type mt,RMOtherModule m.m_path)) tl in
+	let tl = List.map (fun mt ->
+		let is = ImportStatus.Imported in
+		ITType(CompletionItem.CompletionModuleType.of_module_type is mt,RMOtherModule m.m_path)
+	) tl in
 	tl
 
 let collect ctx e_ast e dk with_type p =
@@ -185,7 +188,7 @@ let collect ctx e_ast e dk with_type p =
 	let get_field acc f =
 		List.fold_left (fun acc f ->
 			if not f.cf_public then acc
-			else (ITClassMember f) :: acc
+			else (ITClassField(f,CFSMember)) :: acc
 		) acc (f :: f.cf_overloads)
 	in
 	let fields = List.fold_left get_field [] fields in

+ 44 - 15
src/context/displayJson.ml → src/context/display/displayJson.ml

@@ -13,8 +13,8 @@ type haxe_json_error =
 	| BadType of string * string
 
 let raise_haxe_json_error id = function
-	| MissingField(name,on) -> raise_custom id 1 (Printf.sprintf "Missing param %s on %s" name on)
-	| BadType(desc,expected) -> raise_custom id 2 (Printf.sprintf "Unexpected value for %s, expected %s" desc expected)
+	| MissingField(name,on) -> raise_custom id 1 (Printf.sprintf "Missing param \"%s\" on \"%s\"" name on)
+	| BadType(desc,expected) -> raise_custom id 2 (Printf.sprintf "Unexpected value for \"%s\", expected %s" desc expected)
 
 let get_capabilities () =
 	JObject [
@@ -23,12 +23,13 @@ let get_capabilities () =
 		"completionProvider",JBool true;
 		"packageProvider",JBool true;
 		"signatureHelpProvider",JBool true;
+		"completionResolveProvider",JBool true;
 	]
 
 (* Generate the JSON of our times. *)
 let json_of_times root =
 	let rec loop node =
-		if node.time > 0.0009 then begin
+		if node == root || node.time > 0.0009 then begin
 			let children = ExtList.List.filter_map loop node.children in
 			let fl = [
 				"name",jstring node.name;
@@ -50,8 +51,12 @@ let json_of_times root =
 	loop root
 
 let debug_context_sign = ref None
+let supports_resolve = ref false
 
-let parse_input com input report_times did_something =
+let create_json_context () =
+	Genjson.create_context (if !supports_resolve then GMMinimum else GMFull)
+
+let parse_input com input report_times pre_compilation did_something =
 	let send_string j = raise (DisplayOutput.Completion j) in
 	let send_json json = send_string (string_of_json json) in
 	let process () =
@@ -59,8 +64,10 @@ let parse_input com input report_times did_something =
 		let f_result json =
 			let fl = [
 				"result",json;
+				"timestamp",jfloat (Unix.gettimeofday ());
 			] in
 			let fl = if !report_times then begin
+				close_times();
 				let _,_,root = Timer.build_times_tree () in
 				begin match json_of_times root with
 				| None -> fl
@@ -107,12 +114,12 @@ let parse_input com input report_times did_something =
 		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_string_param name = get_string_field "param" name params in
-		let get_int_param name = get_int_field "param" name params in
-		let get_bool_param name = get_bool_field "param" name params in
-		let get_array_param name = get_array_field "param" name params in
-		(* let get_object_param name = get_object_field "param" name params 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_opt_param f def = try f() with JsonRpc_error _ -> def in
 		let enable_display mode =
 			com.display <- create mode;
 			Parser.display_mode := mode;
@@ -122,6 +129,11 @@ let parse_input com input report_times did_something =
 		let read_display_file was_auto_triggered requires_offset is_completion =
 			let file = get_string_param "file" in
 			let pos = if requires_offset then get_int_param "offset" else (-1) in
+			TypeloadParse.current_stdin := get_opt_param (fun () ->
+				let s = get_string_param "contents" in
+				Common.define com Define.DisplayStdin; (* TODO: awkward *)
+				Some s
+			) None;
 			Parser.was_auto_triggered := was_auto_triggered;
 			let pos = if pos <> (-1) && not is_completion then pos + 1 else pos in
 			Parser.resume_display := {
@@ -137,27 +149,44 @@ let parse_input com input report_times did_something =
 		in
 		let f () = match name with
 			| "initialize" ->
+				supports_resolve := get_opt_param (fun () -> get_bool_param "supportsResolve") false;
 				f_result (JObject [
 					"capabilities",get_capabilities()
 				])
-			| "textDocument/completion" ->
+			| "display/completionItem/resolve" ->
+				let i = get_int_param "index" in
+				begin try
+					let item = (!DisplayException.last_completion_result).(i) in
+					let ctx = Genjson.create_context GMFull in
+					f_result (jobject ["item",CompletionItem.to_json ctx item])
+				with Invalid_argument _ ->
+					f_error [jstring (Printf.sprintf "Invalid index: %i" i)]
+				end
+			| "display/completion" ->
 				read_display_file (get_bool_param "wasAutoTriggered") true true;
 				enable_display DMDefault;
-			| "textDocument/definition" ->
+			| "display/definition" ->
 				Common.define com Define.NoCOpt;
 				read_display_file false true false;
 				enable_display DMDefinition;
-			| "textDocument/hover" ->
+			| "display/hover" ->
 				Common.define com Define.NoCOpt;
 				read_display_file false true false;
 				enable_display DMHover;
-			| "textDocument/package" ->
+			| "display/package" ->
 				read_display_file false false false;
 				enable_display DMPackage;
-			| "textDocument/signatureHelp" ->
+			| "display/signatureHelp" ->
 				read_display_file (get_bool_param "wasAutoTriggered") true false;
 				enable_display DMSignature
 			(* server *)
+			| "server/readClassPaths" ->
+				com.callbacks.after_init_macros <- (fun () ->
+					let cs = CompilationServer.force() in
+					CompilationServer.set_initialized cs;
+					DisplayToplevel.read_class_paths com ["init"];
+					f_result (jstring "class paths read");
+				) :: com.callbacks.after_init_macros;
 			| "server/contexts" ->
 				let cs = CompilationServer.force() in
 				let l = List.map (fun (sign,index) -> jobject [

+ 170 - 111
src/context/displayToplevel.ml → src/context/display/displayToplevel.ml

@@ -18,12 +18,14 @@
 *)
 open Ast
 open Common
+open Common.CompilationServer
 open Type
 open Typecore
-open DisplayTypes.CompletionKind
-open DisplayTypes.CompletionItemKind
+open CompletionItem
+open DisplayTypes
+open Genjson
 
-let explore_class_paths ctx class_paths recusive f_pack f_module =
+let explore_class_paths com timer class_paths recusive f_pack f_module =
 	let rec loop dir pack =
 		try
 			let entries = Sys.readdir dir in
@@ -33,7 +35,7 @@ let explore_class_paths ctx class_paths recusive f_pack f_module =
 						()
 					| _ when Sys.is_directory (dir ^ file) && file.[0] >= 'a' && file.[0] <= 'z' ->
 						begin try
-							begin match PMap.find file ctx.com.package_rules with
+							begin match PMap.find file com.package_rules with
 								| Forbidden -> ()
 								| _ -> raise Not_found
 							end
@@ -55,24 +57,121 @@ let explore_class_paths ctx class_paths recusive f_pack f_module =
 		with Sys_error _ ->
 			()
 	in
-	List.iter (fun dir -> loop dir []) class_paths
+	let t = Timer.timer (timer @ ["class path exploration"]) in
+	List.iter (fun dir -> loop dir []) class_paths;
+	t()
+
+let read_class_paths com timer =
+	let sign = Define.get_signature com.defines in
+	explore_class_paths com timer (List.filter ((<>) "") com.class_path) true (fun _ -> ()) (fun path ->
+		let file,_,pack,_ = TypeloadParse.parse_module' com path Globals.null_pos in
+		match CompilationServer.get() with
+		| Some cs when pack <> fst path ->
+			let file = Path.unique_full_path file in
+			CompilationServer.remove_file cs (file,sign)
+		| _ ->
+			()
+	)
+
+module CollectionContext = struct
+	open ImportStatus
+
+	type t = {
+		items : CompletionItem.t DynArray.t;
+		names : (string,CompletionItem.t) Hashtbl.t;
+		paths : (Globals.path,bool) Hashtbl.t;
+	}
+
+	let create () = {
+		items = DynArray.create ();
+		names = Hashtbl.create 0;
+		paths = Hashtbl.create 0;
+	}
+
+	let add_item ctx item name =
+		DynArray.add ctx.items item;
+		Hashtbl.replace ctx.names name item
+
+	let get_import_status ctx is_import path =
+		try
+			let _ = Hashtbl.find ctx.names (snd path) in
+			(* 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 path_exists ctx path = Hashtbl.mem ctx.paths path
+	let add_path ctx path = Hashtbl.add ctx.paths path true
+end
+
+open CollectionContext
 
 let collect ctx only_types with_type =
-	let acc = DynArray.create () in
-	let add x = DynArray.add acc x in
+	let t = Timer.timer ["display";"toplevel"] in
+	let cctx = CollectionContext.create () in
+	let packages = Hashtbl.create 0 in
+	let add_package s = Hashtbl.replace packages s true in
+
+	let add item name = add_item cctx item name in
+
+	let add_type rm mt =
+		match mt with
+		| TClassDecl {cl_kind = KAbstractImpl _} -> ()
+		| _ ->
+			let path = (t_infos mt).mt_path in
+			if not (path_exists cctx path) then begin
+				(match mt with
+				| 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);
+				add_path cctx path;
+			end
+	in
+
+	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
+					| _ -> raise Exit
+				in
+				let path = (pack,tname) in
+				if not (path_exists cctx path) 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
+				end
+			with Exit ->
+				()
+			end
+		) decls in
+		if not (List.exists (fun s -> String.length s > 0 && s.[0] = '_') pack) then run()
+	in
+
+	(* Collection starts here *)
 
 	if not only_types then begin
 		(* locals *)
 		PMap.iter (fun _ v ->
 			if not (is_gen_local v) then
-				add (ITLocal v)
+				add (ITLocal v) v.v_name
 		) ctx.locals;
 
 		(* member vars *)
 		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) then add (ITClassMember 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 ->
@@ -86,29 +185,26 @@ let collect ctx only_types with_type =
 
 		(* statics *)
 		List.iter (fun cf ->
-			if not (Meta.has Meta.NoCompletion cf.cf_meta) then add (ITClassStatic cf)
+			if not (Meta.has Meta.NoCompletion cf.cf_meta) then add (ITClassField(cf,CFSStatic)) cf.cf_name
 		) ctx.curclass.cl_ordered_statics;
 
 		(* enum constructors *)
-		let seen_paths = Hashtbl.create 0 in
-		let was_proccessed path = Hashtbl.mem seen_paths path in
-		let mark_processed path = Hashtbl.add seen_paths path true in
 		let rec enum_ctors t =
 			match t with
-			| TAbstractDecl ({a_impl = Some c} as a) when Meta.has Meta.Enum a.a_meta && not (was_proccessed a.a_path) ->
-				mark_processed a.a_path;
+			| 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));
+					if (Meta.has Meta.Enum cf.cf_meta) && not (Meta.has Meta.NoCompletion cf.cf_meta) then add (ITEnumAbstractField(a,cf)) cf.cf_name;
 				) c.cl_ordered_statics
 			| TTypeDecl t ->
 				begin match follow t.t_type with
 					| TEnum (e,_) -> enum_ctors (TEnumDecl e)
 					| _ -> ()
 				end
-			| TEnumDecl e when not (was_proccessed e.e_path) ->
-				mark_processed e.e_path;
+			| TEnumDecl e when not (path_exists cctx e.e_path) ->
+				add_path cctx e.e_path;
 				PMap.iter (fun _ ef ->
-					add (ITEnumField(e,ef))
+					add (ITEnumField(e,ef)) ef.ef_name
 				) e.e_constrs;
 			| _ ->
 				()
@@ -116,6 +212,7 @@ let collect ctx only_types with_type =
 		List.iter enum_ctors ctx.m.curmod.m_types;
 		List.iter enum_ctors (List.map fst ctx.m.module_types);
 
+		(* enum constructors of expected type *)
 		begin match with_type with
 			| WithType t ->
 				(try enum_ctors (module_type_of_type t) with Exit -> ())
@@ -125,133 +222,92 @@ let collect ctx only_types with_type =
 		(* imported globals *)
 		PMap.iter (fun _ (mt,s,_) ->
 			try
-				let t = match resolve_typedef mt with
-					| TClassDecl c -> (PMap.find s c.cl_statics).cf_type
-					| TEnumDecl en -> (PMap.find s en.e_constrs).ef_type
-					| TAbstractDecl {a_impl = Some c} -> (PMap.find s c.cl_statics).cf_type
+				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
 					| _ -> raise Not_found
-				in
-				add (ITGlobal(mt,s,t))
 			with Not_found ->
 				()
 		) ctx.m.module_globals;
 
 		(* literals *)
-		add (ITLiteral("null",t_dynamic));
-		add (ITLiteral("true",ctx.com.basic.tbool));
-		add (ITLiteral("false",ctx.com.basic.tbool));
+		add (ITLiteral("null",t_dynamic)) "null";
+		add (ITLiteral("true",ctx.com.basic.tbool)) "true";
+		add (ITLiteral("false",ctx.com.basic.tbool)) "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));
+				add (ITLiteral("this",t)) "this";
 				begin match ctx.curclass.cl_super with
-					| Some(c,tl) -> add (ITLiteral("super",TInst(c,tl)))
+					| Some(c,tl) -> add (ITLiteral("super",TInst(c,tl))) "super"
 					| None -> ()
 				end
 			| _ ->
 				()
-		end
-	end;
-
-	let module_types = ref [] in
+		end;
 
-	let module_exists path =
-		List.exists (fun (mt2,_) -> (t_infos mt2).mt_path = path) !module_types
-	in
+		let kwds = [
+			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
+	end;
 
-	let add_type rm mt =
-		match mt with
-		| TClassDecl {cl_kind = KAbstractImpl _} -> ()
-		| _ ->
-			let path = (t_infos mt).mt_path in
-			if not (module_exists path) then begin
-				(match mt with
-				| TClassDecl c | TAbstractDecl { a_impl = Some c } when Meta.has Meta.CoreApi c.cl_meta ->
-					!merge_core_doc_ref ctx c
-				| _ -> ());
-				module_types := (mt,rm) :: !module_types
-			end
-	in
+	(* 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
+		| _ -> assert false
+	) ctx.type_params;
 
 	(* module types *)
 	List.iter (add_type RMLocalModule) ctx.m.curmod.m_types;
 
 	(* module imports *)
-	List.iter (add_type RMImport) (List.map fst ctx.m.module_types);
-
-	(* module using *)
-	List.iter (fun (c,_) ->
-		add_type RMUsing (TClassDecl c)
-	) ctx.m.module_using;
-
-	let packages = Hashtbl.create 0 in
-	let add_package s = Hashtbl.replace packages s true in
-
-	let class_paths = ctx.com.class_path in
-	let class_paths = List.filter (fun s -> s <> "") class_paths in
-
-	let add_syntax_type path kind rm =
-		if not (module_exists path) then add (ITType(path,kind,rm))
-	in
-
-	let process_decls pack decls =
-		List.iter (fun (d,_) -> match d with
-			| EClass d when not (List.mem HPrivate d.d_flags) ->
-				let kind = if List.mem HInterface d.d_flags then Interface else Class in
-				add_syntax_type (pack,fst d.d_name) kind (RMOtherModule (pack,fst d.d_name)) (* TODO *)
-			| EEnum d when not (List.mem EPrivate d.d_flags) ->
-				add_syntax_type (pack,fst d.d_name) Enum (RMOtherModule (pack,fst d.d_name)) (* TODO *)
-			| EAbstract d when not (List.mem AbPrivate d.d_flags) ->
-				let kind = if Meta.has Meta.Enum d.d_meta then Enum else Class in
-				add_syntax_type (pack,fst d.d_name) kind (RMOtherModule (pack,fst d.d_name)) (* TODO *)
-			| ETypedef d when not (List.mem EPrivate d.d_flags) ->
-				let kind = match fst d.d_data with
-				| CTAnonymous _ -> Struct
-				| _ -> Interface
-				in
-				add_syntax_type (pack,fst d.d_name) kind (RMOtherModule (pack,fst d.d_name)) (* TODO *)
-			| _ -> ()
-		) decls
-	in
+	List.iter (add_type RMImport) (List.rev_map fst ctx.m.module_types); (* reverse! *)
 
+	(* types from files *)
 	begin match !CompilationServer.instance with
 	| None ->
-		explore_class_paths ctx class_paths true add_package (fun path ->
-			if not (module_exists path) then begin
+		(* offline: explore class paths *)
+		let class_paths = ctx.com.class_path in
+		let class_paths = List.filter (fun s -> s <> "") class_paths in
+		explore_class_paths ctx.com ["display";"toplevel"] class_paths true add_package (fun path ->
+			if not (path_exists cctx path) then begin
 				let _,decls = TypeloadParse.parse_module ctx path Globals.null_pos in
-				process_decls (fst path) decls
+				process_decls (fst path) (snd path) decls
 			end
 		)
 	| Some cs ->
+		(* online: iter context files *)
 		if not (CompilationServer.is_initialized cs) then begin
 			CompilationServer.set_initialized cs;
-			explore_class_paths ctx class_paths true (fun _ -> ()) (fun path ->
-				if not (module_exists path) then begin
-					ignore(TypeloadParse.parse_module ctx path Globals.null_pos)
-				end
-			);
+			read_class_paths ctx.com ["display";"toplevel"];
 		end;
-		CompilationServer.iter_files cs ctx.com (fun (_,(pack,decls)) -> process_decls pack decls)
+		(* TODO: sort files so that the ones in the current module's package and its parent packages
+		   are processed first. *)
+		CompilationServer.iter_files cs ctx.com (fun file cfile ->
+			let module_name = match cfile.c_module_name with
+			| None ->
+				let name = Path.module_name_of_file file in
+				cfile.c_module_name <- Some name;
+				name
+			| Some name ->
+				name
+			in
+			process_decls cfile.c_package module_name cfile.c_decls
+		)
 	end;
 
-	(* TODO: wildcard packages. How? *)
-
-	List.iter (fun (mt,rm) ->
-		let kind = of_module_type mt in
-		add (ITType((t_infos mt).mt_path,kind,rm))
-	) !module_types;
-
 	Hashtbl.iter (fun pack _ ->
-		add (ITPackage pack)
+		add (ITPackage pack) pack
 	) packages;
 
-	(* type params *)
-	List.iter (fun (s,_) ->
-		add (ITType (([],s),TypeParameter,RMTypeParameter))
-	) ctx.type_params;
-
-	let l = DynArray.to_list acc in
-	match with_type with
+	(* sorting *)
+	let l = DynArray.to_list cctx.items in
+	let l = match with_type with
 		| WithType t ->
 			let rec comp t' =
 				if type_iseq t' t then 0 (* equal types - perfect *)
@@ -269,11 +325,14 @@ let collect ctx only_types with_type =
 			let l = List.sort (fun (_,i1) (_,i2) -> compare i1 i2) l in
 			List.map fst l
 		| _ -> l
+	in
+	t();
+	l
 
 let handle_unresolved_identifier ctx i p only_types =
 	let l = collect ctx only_types NoValue in
 	let cl = List.map (fun it ->
-		let s = DisplayTypes.CompletionKind.get_name it in
+		let s = CompletionItem.get_name it in
 		(s,it),StringError.levenshtein i s
 	) l in
 	let cl = List.sort (fun (_,c1) (_,c2) -> compare c1 c2) cl in

+ 123 - 0
src/context/display/documentSymbols.ml

@@ -0,0 +1,123 @@
+open Ast
+
+open DisplayTypes.SymbolKind
+
+let collect_module_symbols (pack,decls) =
+	let l = DynArray.create() in
+	let add name kind location parent =
+		let si = DisplayTypes.SymbolInformation.make name kind location (if parent = "" then None else Some parent) in
+		DynArray.add l si;
+	in
+	let rec expr parent (e,p) =
+		let add name kind location = add name kind location parent in
+		begin match e with
+		| EVars vl ->
+			List.iter (fun ((s,p),_,eo) ->
+				add s Variable p;
+				expr_opt parent eo
+			) vl
+		| ETry(e1,catches) ->
+			expr parent e1;
+			List.iter (fun ((s,p),_,e,_) ->
+				add s Variable p;
+				expr parent e
+			) catches;
+		| EFunction(Some s,f) ->
+			add s Function p;
+			func parent f
+		| EBinop(OpIn,(EConst(Ident s),p),e2) ->
+			add s Variable p;
+			expr parent e2;
+		| _ ->
+			iter_expr (expr parent) (e,p)
+		end
+	and expr_opt parent eo = match eo with
+		| None -> ()
+		| Some e -> expr parent e
+	and func parent f =
+		List.iter (fun ((s,p),_,_,_,eo) ->
+			add s Variable p parent;
+			expr_opt parent eo
+		) f.f_args;
+		expr_opt parent f.f_expr
+	in
+	let field parent cff =
+		let field_parent = parent ^ "." ^ (fst cff.cff_name) in
+		match cff.cff_kind with
+		| FVar(_,eo) ->
+			add (fst cff.cff_name) Field cff.cff_pos parent;
+			expr_opt field_parent eo
+		| FFun f ->
+			add (fst cff.cff_name) (if fst cff.cff_name = "new" then Constructor else Method) cff.cff_pos parent;
+			func field_parent f
+		| FProp(_,_,_,eo) ->
+			add (fst cff.cff_name) Property cff.cff_pos parent;
+			expr_opt field_parent eo
+	in
+	List.iter (fun (td,p) -> match td with
+		| EImport _ | EUsing _ ->
+			() (* TODO: Can we do anything with these? *)
+		| EClass d ->
+			add (fst d.d_name) (if List.mem HInterface d.d_flags then Interface else Class) p "";
+			List.iter (field (fst d.d_name)) d.d_data
+		| EEnum d ->
+			add (fst d.d_name) Enum p "";
+			List.iter (fun ef ->
+				add (fst ef.ec_name) Method ef.ec_pos (fst d.d_name)
+			) d.d_data
+		| ETypedef d ->
+			add (fst d.d_name) Typedef p "";
+			(match d.d_data with
+			| CTAnonymous fields,_ ->
+				List.iter (field (fst d.d_name)) fields
+			| _ -> ())
+		| EAbstract d ->
+			add (fst d.d_name) Abstract p "";
+			List.iter (field (fst d.d_name)) d.d_data
+	) decls;
+	l
+
+module Printer = struct
+	open Json
+	open DisplayTypes.SymbolKind
+	open DisplayTypes.SymbolInformation
+
+	let print_module_symbols com symbols filter =
+		let regex = Option.map Str.regexp_case_fold filter in
+		let reported = Hashtbl.create 0 in
+		let add si =
+			if Hashtbl.mem reported si.pos then false
+			else begin
+				let b = match regex with
+					| None -> true
+					| Some regex -> (try ignore(Str.search_forward regex si.name 0); true with Not_found -> false)
+				in
+				Hashtbl.replace reported si.pos true;
+				b
+			end
+		in
+		let ja = List.fold_left (fun acc (file,l) ->
+			let jl = ExtList.List.filter_map (fun si ->
+				if not (add si) then
+					None
+				else begin
+					let l =
+						("name",JString si.name) ::
+						("kind",JInt (to_int si.kind)) ::
+						("range", Genjson.generate_pos_as_range si.pos) ::
+						(match si.container_name with None -> [] | Some s -> ["containerName",JString s])
+					in
+					Some (JObject l)
+				end
+			) (DynArray.to_list l) in
+			if jl = [] then
+				acc
+			else
+				(JObject [
+					"file",JString file;
+					"symbols",JArray jl
+				]) :: acc
+		) [] symbols in
+		let js = JArray ja in
+		string_of_json js
+end

+ 57 - 0
src/context/display/importHandling.ml

@@ -0,0 +1,57 @@
+open Globals
+open Ast
+open Display
+open Common
+open Typecore
+
+type import_display_kind =
+	| IDKPackage of string list
+	| IDKModule of string list * string
+	| IDKSubType of string list * string * string
+	| IDKModuleField of string list * string * string
+	| IDKSubTypeField of string list * string * string * string
+	| IDK
+
+type import_display = import_display_kind * pos
+
+let convert_import_to_something_usable pt path =
+	let rec loop pack m t = function
+		| (s,p) :: l ->
+			let is_lower = is_lower_ident s in
+			let is_display_pos = encloses_position pt p in
+			begin match is_lower,m,t with
+				| _,None,Some _ ->
+					assert false (* impossible, I think *)
+				| true,Some m,None ->
+					if is_display_pos then (IDKModuleField(List.rev pack,m,s),p)
+					else (IDK,p) (* assume that we're done *)
+				| _,Some m,Some t ->
+					if is_display_pos then (IDKSubTypeField(List.rev pack,m,t,s),p)
+					else (IDK,p)
+				| true,None,None ->
+					if is_display_pos then (IDKPackage (List.rev (s :: pack)),p)
+					else loop (s :: pack) m t l
+				| false,Some sm,None ->
+					if is_display_pos then (IDKSubType (List.rev pack,sm,s),p)
+					else loop pack m (Some s) l
+				| false,None,None ->
+					if is_display_pos then (IDKModule (List.rev pack,s),p)
+					else loop pack (Some s) None l
+			end
+		| [] ->
+			(IDK,null_pos)
+	in
+	loop [] None None path
+
+let add_import_position com p path =
+	com.shared.shared_display_information.import_positions <- PMap.add p (ref false,path) com.shared.shared_display_information.import_positions
+
+let mark_import_position com p =
+	try
+		let r = fst (PMap.find p com.shared.shared_display_information.import_positions) in
+		r := true
+	with Not_found ->
+		()
+
+let maybe_mark_import_position ctx p =
+	if Diagnostics.is_diagnostics_run p then mark_import_position ctx.com p

+ 281 - 0
src/context/display/statistics.ml

@@ -0,0 +1,281 @@
+open Globals
+open Ast
+open Type
+open Common
+open Typecore
+
+open ImportHandling
+
+type relation =
+	| Implemented
+	| Extended
+	| Overridden
+	| Referenced
+
+type symbol =
+	| SKClass of tclass
+	| SKInterface of tclass
+	| SKEnum of tenum
+	| SKTypedef of tdef
+	| SKAbstract of tabstract
+	| SKField of tclass_field
+	| SKEnumField of tenum_field
+	| SKVariable of tvar
+
+let collect_statistics ctx =
+	let relations = Hashtbl.create 0 in
+	let symbols = Hashtbl.create 0 in
+	let handled_modules = Hashtbl.create 0 in
+	let add_relation pos r =
+		if pos <> null_pos then try
+			let l = Hashtbl.find relations pos in
+			if not (List.mem r l) then
+				Hashtbl.replace relations pos (r :: l)
+		with Not_found ->
+			Hashtbl.add relations pos [r]
+	in
+	let declare kind p =
+		if p <> null_pos then begin
+			if not (Hashtbl.mem relations p) then Hashtbl.add relations p [];
+			Hashtbl.replace symbols p kind;
+		end
+	in
+	let collect_overrides c =
+		List.iter (fun cf ->
+			let rec loop c = match c.cl_super with
+				| Some (c,_) ->
+					begin try
+						let cf' = PMap.find cf.cf_name c.cl_fields in
+						add_relation cf'.cf_name_pos (Overridden,cf.cf_pos)
+					with Not_found ->
+						loop c
+					end
+				| _ ->
+					()
+			in
+			loop c
+		) c.cl_overrides
+	in
+	let rec find_real_constructor c = match c.cl_constructor,c.cl_super with
+		(* The pos comparison might be a bit weak, not sure... *)
+		| Some cf,_ when not (Meta.has Meta.CompilerGenerated cf.cf_meta) && c.cl_pos <> cf.cf_pos -> cf
+		| _,Some(c,_) -> find_real_constructor c
+		| _,None -> raise Not_found
+	in
+	let var_decl v = declare (SKVariable v) v.v_pos in
+	let patch_string_pos p s = { p with pmin = p.pmax - String.length s } in
+	let field_reference cf p =
+		add_relation cf.cf_name_pos (Referenced,patch_string_pos p cf.cf_name)
+	in
+	let collect_references c e =
+		let rec loop e = match e.eexpr with
+			| TField(e1,fa) ->
+				(* Check if the sub-expression is actually shorter than the whole one. This should
+					detect cases where it was automatically generated. *)
+				if e1.epos.pmin = e.epos.pmin && e1.epos.pmax <> e.epos.pmax then
+					loop e1;
+				begin match fa with
+					| FStatic(_,cf) | FInstance(_,_,cf) | FClosure(_,cf) ->
+						field_reference cf e.epos
+					| FAnon cf ->
+						declare  (SKField cf) cf.cf_name_pos;
+						field_reference cf e.epos
+					| FEnum(_,ef) ->
+						add_relation ef.ef_name_pos (Referenced,patch_string_pos e.epos ef.ef_name)
+					| FDynamic _ ->
+						()
+				end
+			| TTypeExpr mt ->
+				let tinfos = t_infos mt in
+				add_relation tinfos.mt_name_pos (Referenced,patch_string_pos e.epos (snd tinfos.mt_path))
+			| TNew(c,_,el) ->
+				List.iter loop el;
+				(try add_relation (find_real_constructor c).cf_name_pos (Referenced,e.epos) with Not_found -> ());
+			| TCall({eexpr = TConst TSuper},el) ->
+				List.iter loop el;
+				begin match c.cl_super with
+					| Some(c,_) -> (try add_relation (find_real_constructor c).cf_name_pos (Referenced,e.epos) with Not_found -> ())
+					| None -> ()
+				end
+			| TVar(v,eo) ->
+				Option.may loop eo;
+				var_decl v;
+			| TFor(v,e1,e2) ->
+				var_decl v;
+				loop e1;
+				loop e2;
+			| TFunction tf ->
+				List.iter (fun (v,_) -> var_decl v) tf.tf_args;
+				loop tf.tf_expr;
+			| TLocal v when e.epos.pmax - e.epos.pmin = String.length v.v_name ->
+				add_relation v.v_pos (Referenced,e.epos)
+			| _ ->
+				Type.iter loop e
+		in
+		loop e
+	in
+	let rec explore_type_hint (p,t) =
+		match t with
+		| TMono r -> (match !r with None -> () | Some t -> explore_type_hint (p,t))
+		| TLazy f -> explore_type_hint (p,lazy_type f)
+		| TInst(({cl_name_pos = pn;cl_path = (_,name)}),_)
+		| TEnum(({e_name_pos = pn;e_path = (_,name)}),_)
+		| TType(({t_name_pos = pn;t_path = (_,name)}),_)
+		| TAbstract(({a_name_pos = pn;a_path = (_,name)}),_) ->
+			add_relation pn (Referenced,p)
+		| TDynamic _ -> ()
+		| TFun _ | TAnon _ -> ()
+	in
+	let check_module m =
+		if not (Hashtbl.mem handled_modules m.m_path) then begin
+			Hashtbl.add handled_modules m.m_path true;
+			List.iter (fun (p1,p2) ->
+				add_relation p1 (Referenced,p2)
+			) m.m_extra.m_display.m_inline_calls;
+			List.iter explore_type_hint m.m_extra.m_display.m_type_hints
+		end
+	in
+	let f = function
+		| TClassDecl c ->
+			check_module c.cl_module;
+			declare (if c.cl_interface then (SKInterface c) else (SKClass c)) c.cl_name_pos;
+			List.iter (fun (c',_) -> add_relation c'.cl_name_pos ((if c.cl_interface then Extended else Implemented),c.cl_name_pos)) c.cl_implements;
+			begin match c.cl_super with
+				| None -> ()
+				| Some (c',_) -> add_relation c'.cl_name_pos (Extended,c.cl_name_pos);
+			end;
+			collect_overrides c;
+			let field cf =
+				if cf.cf_pos.pmin > c.cl_name_pos.pmin then declare (SKField cf) cf.cf_name_pos;
+				let _ = follow cf.cf_type in
+				match cf.cf_expr with None -> () | Some e -> collect_references c e
+			in
+			Option.may field c.cl_constructor;
+			List.iter field c.cl_ordered_fields;
+			List.iter field c.cl_ordered_statics;
+		| TEnumDecl en ->
+			check_module en.e_module;
+			declare (SKEnum en) en.e_name_pos;
+			PMap.iter (fun _ ef -> declare (SKEnumField ef) ef.ef_name_pos) en.e_constrs
+		| TTypeDecl td ->
+			check_module td.t_module;
+			declare (SKTypedef td) td.t_name_pos
+		| TAbstractDecl a ->
+			check_module a.a_module;
+			declare (SKAbstract a) a.a_name_pos
+	in
+	begin match CompilationServer.get () with
+		| None ->
+			let rec loop com =
+				List.iter f com.types;
+				Option.may loop (com.get_macros())
+			in
+			loop ctx.com
+		| Some cs ->
+			let rec loop com =
+				(* CompilationServer.cache_context cs com; *)
+				CompilationServer.iter_modules cs com (fun m -> List.iter f m.m_types);
+				Option.may loop (com.get_macros())
+			in
+			loop ctx.com
+	end;
+	let l = List.fold_left (fun acc (_,cfi,_,cfo) -> match cfo with
+		| Some cf -> if List.mem_assoc cf.cf_name_pos acc then acc else (cf.cf_name_pos,cfi.cf_name_pos) :: acc
+		| None -> acc
+	) [] ctx.com.display_information.interface_field_implementations in
+	List.iter (fun (p,p') -> add_relation p' (Implemented,p)) l;
+	(* let deal_with_imports paths =
+		let check_subtype m s p =
+			try
+				let mt = List.find (fun mt -> snd (t_infos mt).mt_path = s) m.m_types in
+				add_relation (t_infos mt).mt_name_pos (Referenced,p);
+				Some mt
+			with Not_found ->
+				None
+		in
+		let check_module path p =
+			let m = ctx.g.do_load_module ctx path p in
+			m
+		in
+		let check_field c s p =
+			let cf = PMap.find s c.cl_statics in
+			add_relation cf.cf_name_pos (Referenced,p)
+		in
+		let check_subtype_field m ssub psub sfield pfield = match check_subtype m ssub psub with
+			| Some (TClassDecl c) -> check_field c sfield pfield
+			| _ -> ()
+		in
+		PMap.iter (fun p (_,path) ->
+			match ImportHandling.convert_import_to_something_usable { p with pmin = p.pmax - 1; pmax = p.pmax - 1 } path,List.rev path with
+			| (IDKSubType(sl,s1,s2),_),(_,psubtype) :: (_,pmodule) :: _ ->
+				let m = check_module (sl,s1) pmodule in
+				(*ignore(check_subtype m s1 pmodule);*)
+				ignore(check_subtype m s2 psubtype)
+			| (IDKModuleField(sl,s1,s2),_),(_,pfield) :: (_,pmodule) :: _ ->
+				let m = check_module (sl,s1) pmodule in
+				check_subtype_field m s1 pmodule s2 pfield
+			| (IDKSubTypeField(sl,s1,s2,s3),_),(_,pfield) :: (_,psubtype) :: (_,pmodule) :: _ ->
+				let m = check_module (sl,s1) pmodule in
+				check_subtype_field m s2 psubtype s3 pfield
+			| (IDKModule(sl,s),_),(_,pmodule) :: _ ->
+				let m = check_module (sl,s) pmodule in
+				ignore(check_subtype m s pmodule);
+			| _ ->
+				()
+		) paths
+	in
+	if false then deal_with_imports ctx.com.shared.shared_display_information.import_positions; *)
+	symbols,relations
+
+module Printer = struct
+	open Json
+
+	let relation_to_string = function
+		| Implemented -> "implementers"
+		| Extended -> "subclasses"
+		| Overridden -> "overrides"
+		| Referenced -> "references"
+
+	let symbol_to_string = function
+		| SKClass _ -> "class type"
+		| SKInterface _ -> "interface type"
+		| SKEnum _ -> "enum type"
+		| SKTypedef _ -> "typedef"
+		| SKAbstract _ -> "abstract"
+		| SKField _ -> "class field"
+		| SKEnumField _ -> "enum field"
+		| SKVariable _ -> "variable"
+
+	let print_statistics (kinds,relations) =
+		let files = Hashtbl.create 0 in
+		Hashtbl.iter (fun p rl ->
+			let file = Path.get_real_path p.pfile in
+			try
+				Hashtbl.replace files file ((p,rl) :: Hashtbl.find files file)
+			with Not_found ->
+				Hashtbl.add files file [p,rl]
+		) relations;
+		let ja = Hashtbl.fold (fun file relations acc ->
+			let l = List.map (fun (p,rl) ->
+				let h = Hashtbl.create 0 in
+				List.iter (fun (r,p) ->
+					let s = relation_to_string r in
+					let jo = JObject [
+						"range",Genjson.generate_pos_as_range p;
+						"file",JString (Path.get_real_path p.pfile);
+					] in
+					try Hashtbl.replace h s (jo :: Hashtbl.find h s)
+					with Not_found -> Hashtbl.add h s [jo]
+				) rl;
+				let l = Hashtbl.fold (fun s js acc -> (s,JArray js) :: acc) h [] in
+				let l = ("range",Genjson.generate_pos_as_range p) :: l in
+				let l = try ("kind",JString (symbol_to_string (Hashtbl.find kinds p))) :: l with Not_found -> l in
+				JObject l
+			) relations in
+			(JObject [
+				"file",JString file;
+				"statistics",JArray l
+			]) :: acc
+		) files [] in
+		string_of_json (JArray ja)
+end

+ 6 - 2
src/core/ast.ml

@@ -179,6 +179,7 @@ and display_kind =
 	| DKDot
 	| DKStructure
 	| DKMarked
+	| DKPattern
 
 and expr_def =
 	| EConst of constant
@@ -714,7 +715,8 @@ let s_display_kind = function
 	| DKCall -> "DKCall"
 	| DKDot -> "DKDot"
 	| DKStructure -> "DKStructure"
-	| DKMarked -> "TKMarked"
+	| DKMarked -> "DKMarked"
+	| DKPattern -> "DKPattern"
 
 let s_expr e =
 	let rec s_expr_inner tabs (e,_) =
@@ -951,7 +953,9 @@ module Expr = struct
 				add "EVars";
 				List.iter (fun ((n,p),_,eo) -> match eo with
 					| None -> ()
-					| Some e -> loop' (Printf.sprintf "%s  %s" tabs n) e
+					| Some e ->
+						add n;
+						loop' (Printf.sprintf "%s  " tabs) e
 				) vl
 			| EFunction(so,f) ->
 				add "EFunction";

+ 266 - 0
src/core/display/completionItem.ml

@@ -0,0 +1,266 @@
+open Globals
+open Ast
+open Type
+open Genjson
+
+module CompletionModuleKind = struct
+	type t =
+		| Class
+		| Interface
+		| Enum
+		| Abstract
+		| EnumAbstract
+		| TypeAlias
+		| Struct
+		| TypeParameter
+
+	let to_int = function
+		| Class -> 0
+		| Interface -> 1
+		| Enum -> 2
+		| Abstract -> 3
+		| EnumAbstract -> 4
+		| TypeAlias -> 5
+		| Struct -> 6
+		| TypeParameter -> 7
+end
+
+module ImportStatus = struct
+	type t =
+		| Imported
+		| Unimported
+		| Shadowed
+
+	let to_int = function
+		| Imported -> 0
+		| Unimported -> 1
+		| Shadowed -> 2
+end
+
+module CompletionModuleType = struct
+	open CompletionModuleKind
+
+	type t = {
+		pack : string list;
+		name : string;
+		module_name : string;
+		pos : pos;
+		is_private : bool;
+		params : Ast.type_param list;
+		meta: metadata;
+		doc : documentation;
+		is_extern : bool;
+		kind : CompletionModuleKind.t;
+		import_status : ImportStatus.t;
+	}
+
+	let of_type_decl is pack module_name (td,p) = match td with
+		| EClass d -> {
+				pack = pack;
+				name = fst d.d_name;
+				module_name = module_name;
+				pos = p;
+				is_private = List.mem HPrivate d.d_flags;
+				params = d.d_params;
+				meta = d.d_meta;
+				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;
+			}
+		| EEnum d -> {
+				pack = pack;
+				name = fst d.d_name;
+				module_name = module_name;
+				pos = p;
+				is_private = List.mem EPrivate d.d_flags;
+				params = d.d_params;
+				meta = d.d_meta;
+				doc = d.d_doc;
+				is_extern = List.mem EExtern d.d_flags;
+				kind = Enum;
+				import_status = is;
+			}
+		| ETypedef d -> {
+				pack = pack;
+				name = fst d.d_name;
+				module_name = module_name;
+				pos = p;
+				is_private = List.mem EPrivate d.d_flags;
+				params = d.d_params;
+				meta = d.d_meta;
+				doc = d.d_doc;
+				is_extern = List.mem EExtern d.d_flags;
+				kind = (match fst d.d_data with CTAnonymous _ -> Struct | _ -> TypeAlias);
+				import_status = is;
+			}
+		| EAbstract d -> {
+				pack = pack;
+				name = fst d.d_name;
+				module_name = module_name;
+				pos = p;
+				is_private = List.mem AbPrivate d.d_flags;
+				params = d.d_params;
+				meta = d.d_meta;
+				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;
+			}
+		| EImport _ | EUsing _ ->
+			raise Exit
+
+	let of_module_type is mt =
+		let is_extern,kind = match mt with
+			| TClassDecl c ->
+				c.cl_extern,if c.cl_interface then Interface else Class
+			| TEnumDecl en ->
+				en.e_extern,Enum
+			| TTypeDecl td ->
+				false,(match follow td.t_type with TAnon _ -> Struct | _ -> TypeAlias)
+			| TAbstractDecl a ->
+				false,(if Meta.has Meta.Enum a.a_meta then EnumAbstract else Abstract)
+		in
+		let infos = t_infos mt in
+		let convert_type_param (s,t) = match follow t with
+			| TInst(c,_) -> {
+				tp_name = s,null_pos;
+				tp_params = [];
+				tp_constraints = []; (* TODO? *)
+				tp_meta = c.cl_meta
+			}
+			| _ ->
+				assert false
+		in
+		{
+			pack = fst infos.mt_path;
+			name = snd infos.mt_path;
+			module_name = snd infos.mt_module.m_path;
+			pos = infos.mt_pos;
+			is_private = infos.mt_private;
+			params = List.map convert_type_param infos.mt_params;
+			meta = infos.mt_meta;
+			doc = infos.mt_doc;
+			is_extern = is_extern;
+			kind = kind;
+			import_status = is;
+		}
+
+	let get_path cm = (cm.pack,cm.name)
+
+	let to_json ctx cm =
+		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)) ::
+			(match ctx.generation_mode with
+			| GMFull | GMWithoutDoc ->
+				("pos",generate_pos ctx cm.pos) ::
+				("params",jlist (generate_ast_type_param ctx) cm.params) ::
+				("meta",generate_metadata ctx cm.meta) ::
+				("isExtern",jbool cm.is_extern) ::
+				(if ctx.generation_mode = GMFull then ["doc",jopt jstring cm.doc] else [])
+			| GMMinimum ->
+				[]
+			)
+		in
+		jobject fields
+
+end
+
+open CompletionModuleType
+
+type resolution_mode =
+	| RMLocalModule
+	| RMImport
+	| RMUsing
+	| RMTypeParameter
+	| RMClassPath
+	| RMOtherModule of path
+
+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
+	| ITModule of string
+	| ITLiteral of string * Type.t
+	| ITTimer of string * string
+	| ITMetadata of string * documentation
+	| ITKeyword of keyword
+
+let legacy_sort = function
+	| ITClassField(cf,_) | ITEnumAbstractField(_,cf) ->
+		begin match cf.cf_kind with
+		| Var _ -> 0,cf.cf_name
+		| Method _ -> 1,cf.cf_name
+		end
+	| ITEnumField(_,ef) ->
+		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
+	| ITMetadata(s,_) -> 5,s
+	| ITTimer(s,_) -> 6,s
+	| ITLocal v -> 7,v.v_name
+	| ITLiteral(s,_) -> 9,s
+	| ITKeyword kwd -> 10,s_keyword kwd
+
+let get_name = function
+	| ITLocal v -> v.v_name
+	| ITClassField(cf,_) | ITEnumAbstractField(_,cf) -> cf.cf_name
+	| ITEnumField(_,ef) -> ef.ef_name
+	| ITType(cm,_) -> cm.name
+	| ITPackage s -> s
+	| ITModule s -> s
+	| ITLiteral(s,_) -> s
+	| ITTimer(s,_) -> s
+	| ITMetadata(s,_) -> s
+	| ITKeyword kwd -> s_keyword kwd
+
+let get_type = function
+	| ITLocal v -> v.v_type
+	| ITClassField(cf,_) | ITEnumAbstractField(_,cf) -> cf.cf_type
+	| ITEnumField(_,ef) -> ef.ef_type
+	| ITType(_,_) -> t_dynamic
+	| ITPackage _ -> t_dynamic
+	| ITModule _ -> t_dynamic
+	| ITLiteral(_,t) -> t
+	| ITTimer(_,_) -> t_dynamic
+	| ITMetadata(_,_) -> t_dynamic
+	| ITKeyword _ -> t_dynamic
+
+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
+		| ITModule s -> "Module",jstring s
+		| ITLiteral(s,t) -> "Literal",jobject [
+			"name",jstring s;
+			"type",generate_type ctx t;
+		]
+		| ITTimer(s,value) -> "Timer",jobject [
+			"name",jstring s;
+			"value",jstring value;
+		]
+		| ITMetadata(s,doc) -> "Metadata",jobject [
+			"name",jstring s;
+			"doc",jopt jstring doc;
+		]
+		| ITKeyword kwd ->"Keyword",jobject [
+			"name",jstring (s_keyword kwd)
+		]
+	in
+	generate_adt ctx None kind (Some data)

+ 8 - 165
src/core/displayTypes.ml

@@ -69,171 +69,14 @@ module CompletionResultKind = struct
 		| CRStructureField
 		| CRToplevel
 		| CRMetadata
-end
-
-module CompletionItemKind = struct
-	type t =
-		| Text
-		| Method
-		| Function
-		| Constructor
-		| Field
-		| Variable
-		| Class
-		| Interface
-		| Module
-		| Property
-		| Unit
-		| Value
-		| Enum
-		| Keyword
-		| Snippet
-		| Color
-		| File
-		| Reference
-		| Folder
-		| EnumMember
-		| Constant
-		| Struct
-		| Event
-		| Operator
-		| TypeParameter
-
-	let to_int = function
-		| Text -> 1
-		| Method -> 2
-		| Function -> 3
-		| Constructor -> 4
-		| Field -> 5
-		| Variable -> 6
-		| Class -> 7
-		| Interface -> 8
-		| Module -> 9
-		| Property -> 10
-		| Unit -> 11
-		| Value -> 12
-		| Enum -> 13
-		| Keyword -> 14
-		| Snippet -> 15
-		| Color -> 16
-		| File -> 17
-		| Reference -> 18
-		| Folder -> 19
-		| EnumMember -> 20
-		| Constant -> 21
-		| Struct -> 22
-		| Event -> 23
-		| Operator -> 24
-		| TypeParameter -> 25
-
-	let of_module_type = function
-		| TClassDecl c -> if c.cl_interface then Interface else Class
-		| TAbstractDecl a when (Meta.has Meta.Enum a.a_meta) -> Enum
-		| TTypeDecl td ->
-			begin match follow td.t_type with
-				| TAnon _ -> Struct
-				| _ -> Interface
-			end
-		| TEnumDecl _ -> Enum
-		| _ -> Class
-end
-
-module CompletionKind = struct
-	type resolution_mode =
-		| RMLocalModule
-		| RMImport
-		| RMUsing
-		| RMTypeParameter
-		| RMClassPath
-		| RMOtherModule of path
-
-	type t =
-		| ITLocal of tvar
-		| ITClassMember of tclass_field
-		| ITClassStatic of tclass_field
-		| ITEnumField of tenum * tenum_field
-		| ITEnumAbstractField of tabstract * tclass_field
-		| ITGlobal of module_type * string * Type.t
-		| ITType of path * CompletionItemKind.t * resolution_mode
-		| ITPackage of string
-		| ITModule of string
-		| ITLiteral of string * Type.t
-		| ITTimer of string * string
-		| ITMetadata of string * documentation
-
-	let legacy_sort = function
-		| ITClassMember cf | ITClassStatic cf | ITEnumAbstractField(_,cf) ->
-			begin match cf.cf_kind with
-			| Var _ -> 0,cf.cf_name
-			| Method _ -> 1,cf.cf_name
-			end
-		| ITEnumField(_,ef) ->
-			begin match follow ef.ef_type with
-			| TFun _ -> 1,ef.ef_name
-			| _ -> 0,ef.ef_name
-			end
-		| ITType((_,name),_,_) -> 2,name
-		| ITModule s -> 3,s
-		| ITPackage s -> 4,s
-		| ITMetadata(s,_) -> 5,s
-		| ITTimer(s,_) -> 6,s
-		| ITLocal v -> 7,v.v_name
-		| ITGlobal(_,s,_) -> 8,s
-		| ITLiteral(s,_) -> 9,s
-
-	let get_name = function
-		| ITLocal v -> v.v_name
-		| ITClassMember cf | ITClassStatic cf | ITEnumAbstractField(_,cf) -> cf.cf_name
-		| ITEnumField(_,ef) -> ef.ef_name
-		| ITGlobal(_,s,_) -> s
-		| ITType((_,name),_,_) -> name
-		| ITPackage s -> s
-		| ITModule s -> s
-		| ITLiteral(s,_) -> s
-		| ITTimer(s,_) -> s
-		| ITMetadata(s,_) -> s
-
-	let get_type = function
-		| ITLocal v -> v.v_type
-		| ITClassMember cf | ITClassStatic cf | ITEnumAbstractField(_,cf) -> cf.cf_type
-		| ITEnumField(_,ef) -> ef.ef_type
-		| ITGlobal(_,_,t) -> t
-		| ITType(_,_,_) -> t_dynamic
-		| ITPackage _ -> t_dynamic
-		| ITModule _ -> t_dynamic
-		| ITLiteral(_,t) -> t
-		| ITTimer(_,_) -> t_dynamic
-		| ITMetadata(_,_) -> t_dynamic
-
-	let to_json ctx ck =
-		let kind,data = match ck with
-			| ITLocal v -> "Local",generate_tvar ctx v
-			| ITClassMember cf -> "Member",generate_class_field ctx cf
-			| ITClassStatic cf -> "Static",generate_class_field ctx cf
-			| ITEnumField(_,ef) -> "EnumField",generate_enum_field ctx ef
-			| ITEnumAbstractField(_,cf) -> "EnumAbstractField",generate_class_field ctx cf
-			| ITGlobal(mt,s,t) -> "Global",jobject [
-				"modulePath",generate_path (t_infos mt).mt_path;
-				"name",jstring s;
-				"type",generate_type ctx t
-			]
-			| ITType(path,kind,rm) -> "Type",jobject [
-				"path",generate_path path;
-				"kind",jint (CompletionItemKind.to_int kind);
-			]
-			| ITPackage s -> "Package",jstring s
-			| ITModule s -> "Module",jstring s
-			| ITLiteral(s,_) -> "Literal",jstring s
-			| ITTimer(s,value) -> "Timer",jobject [
-				"name",jstring s;
-				"value",jstring value;
-			]
-			| ITMetadata(s,doc) -> "Metadata",jobject [
-				"name",jstring s;
-				"doc",jopt jstring doc;
-			]
-		in
-		generate_adt ctx None kind (Some data)
+		| CRTypeHint
+		| CRExtends
+		| CRImplements
+		| CRStructExtension
+		| CRImport
+		| CRUsing
+		| CRNew
+		| CRPattern
 end
 
 module DisplayMode = struct

+ 37 - 14
src/core/json/genjson.ml

@@ -3,8 +3,13 @@ open Globals
 open Type
 open Meta
 
+type generation_mode =
+	| GMFull
+	| GMWithoutDoc
+	| GMMinimum
+
 type context = {
-	todo : unit;
+	generation_mode : generation_mode;
 }
 
 let jnull = Json.JNull
@@ -46,6 +51,10 @@ let generate_pos ctx p =
 		"max",jint p.pmax;
 	]
 
+let generate_doc ctx d = match ctx.generation_mode with
+	| GMFull -> jopt jstring d
+	| GMWithoutDoc | GMMinimum -> jnull
+
 (** return a range JSON structure for given position
     positions are 0-based and the result object looks like this:
     {
@@ -131,6 +140,15 @@ and generate_metadata ctx ml =
 	) ml in
 	jlist (generate_metadata_entry ctx) ml
 
+(* AST.ml structures *)
+
+let rec generate_ast_type_param ctx tp = jobject [
+	"name",jstring (fst tp.tp_name);
+	"params",jlist (generate_ast_type_param ctx) tp.tp_params;
+	"constraints",jtodo;
+	"metadata",generate_metadata ctx tp.tp_meta
+]
+
 (* type instance *)
 
 let rec generate_type ctx t =
@@ -140,7 +158,11 @@ let rec generate_type ctx t =
 			| None -> "TMono",None
 			| Some t -> loop t
 			end
-		| TLazy f -> loop (lazy_type f)
+		| TLazy f ->
+			return_partial_type := true;
+			let t = lazy_type f in
+			return_partial_type := false;
+			loop t
 		| TDynamic t -> "TDynamic",Some (if t == t_dynamic then jnull else generate_type ctx t)
 		| TInst(c,tl) -> "TInst",Some (generate_path_with_params ctx c.cl_path tl)
 		| TEnum(en,tl) -> "TEnum",Some (generate_path_with_params ctx en.e_path tl)
@@ -150,7 +172,7 @@ let rec generate_type ctx t =
 		| 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 cf :: acc) an.a_fields [] in
+			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 () =
@@ -229,7 +251,7 @@ and generate_texpr ctx e =
 
 (* fields *)
 
-and generate_class_field ctx cf =
+and generate_class_field ctx cfs cf =
 	let generate_class_kind () =
 		let generate_var_access va =
 			let name,args = match va with
@@ -268,8 +290,9 @@ and generate_class_field ctx cf =
 		"kind",generate_class_kind ();
 		"expr",jopt (generate_texpr ctx) cf.cf_expr;
 		"pos",generate_pos ctx cf.cf_pos;
-		"doc",jopt jstring cf.cf_doc;
+		"doc",generate_doc ctx cf.cf_doc;
 		"overloads",jlist (classfield_ref ctx) cf.cf_overloads;
+		"scope",jint (Obj.magic cfs);
 	]
 
 let generate_enum_field ctx ef =
@@ -279,7 +302,7 @@ let generate_enum_field ctx ef =
 		"pos",generate_pos ctx ef.ef_pos;
 		"meta",generate_metadata ctx ef.ef_meta;
 		"index",jint ef.ef_index;
-		"doc",jopt jstring ef.ef_doc;
+		"doc",generate_doc ctx ef.ef_doc;
 		"params",jlist (generate_type_parameter ctx) ef.ef_params;
 	]
 
@@ -289,12 +312,12 @@ let generate_module_type_fields ctx inf =
 	[
 		"pack",jlist jstring (fst inf.mt_path);
 		"name",jstring (snd inf.mt_path);
-		"module",jstring (snd inf.mt_module.m_path);
+		"moduleName",jstring (snd inf.mt_module.m_path);
 		"pos",generate_pos ctx inf.mt_pos;
 		"isPrivate",jbool inf.mt_private;
 		"params",jlist (generate_type_parameter ctx) inf.mt_params;
 		"meta",generate_metadata ctx inf.mt_meta;
-		"doc",jopt jstring inf.mt_doc;
+		"doc",generate_doc ctx inf.mt_doc;
 	]
 
 let generate_class ctx c =
@@ -322,9 +345,9 @@ let generate_class ctx c =
 		"isInterface",jbool c.cl_interface;
 		"superClass",jopt generate_class_relation c.cl_super;
 		"interfaces",jlist generate_class_relation c.cl_implements;
-		"fields",jlist (generate_class_field ctx) c.cl_ordered_fields;
-		"statics",jlist (generate_class_field ctx) c.cl_ordered_statics;
-		"constructor",jopt (generate_class_field ctx) c.cl_constructor;
+		"fields",jlist (generate_class_field ctx CFSMember) c.cl_ordered_fields;
+		"statics",jlist (generate_class_field ctx CFSStatic) c.cl_ordered_statics;
+		"constructor",jopt (generate_class_field ctx CFSConstructor) c.cl_constructor;
 		"init",jopt (generate_texpr ctx) c.cl_init;
 		"overrides",jlist (classfield_ref ctx) c.cl_overrides;
 		"isExtern",jbool c.cl_extern;
@@ -405,13 +428,13 @@ let generate_module ctx m =
 		"sign",jstring (Digest.to_hex m.m_extra.m_sign);
 	]
 
-let create_context () = {
-	todo = ()
+let create_context gm = {
+	generation_mode = gm;
 }
 
 let generate types file =
 	let t = Timer.timer ["generate";"json";"construct"] in
-	let ctx = create_context () in
+	let ctx = create_context GMFull in
 	let json = jarray (List.map (generate_module_type ctx) types) in
 	t();
 	let t = Timer.timer ["generate";"json";"write"] in

+ 12 - 0
src/core/path.ml

@@ -159,6 +159,18 @@ let make_valid_filename s =
 	let r = Str.regexp "[^A-Za-z0-9_\\-\\.,]" in
 	Str.global_substitute r (fun s -> "_") s
 
+let module_name_of_file file =
+	match List.rev (Str.split path_regex (get_real_path file)) with
+	| s :: _ ->
+		let s = match List.rev (ExtString.String.nsplit s ".") with
+		| [s] -> s
+		| _ :: sl -> String.concat "." (List.rev sl)
+		| [] -> ""
+		in
+		s
+	| [] ->
+		assert false
+
 let rec create_file bin ext acc = function
 	| [] -> assert false
 	| d :: [] ->

+ 5 - 0
src/core/type.ml

@@ -353,6 +353,11 @@ type basic_types = {
 	mutable tarray : t -> t;
 }
 
+type class_field_scope =
+	| CFSStatic
+	| CFSMember
+	| CFSConstructor
+
 (* ======= General utility ======= *)
 
 let alloc_var =

+ 2 - 0
src/macro/macroApi.ml

@@ -475,6 +475,7 @@ and encode_display_kind dk =
 	| DKDot -> 1
 	| DKStructure -> 2
 	| DKMarked -> 3
+	| DKPattern -> 4
 	in
 	encode_enum ~pos:None ICType tag []
 
@@ -762,6 +763,7 @@ and decode_display_kind v = match fst (decode_enum v) with
 	| 1 -> DKDot
 	| 2 -> DKStructure
 	| 3 -> DKMarked
+	| 4 -> DKPattern
 	| _ -> raise Invalid_expr
 
 and decode_expr v =

+ 1 - 1
src/optimization/optimizer.ml

@@ -624,7 +624,7 @@ let rec type_inline ctx cf f ethis params tret config p ?(self_calling_closure=f
 			| _ -> e
 		in
 		let e = List.fold_left inline_meta e cf.cf_meta in
-		let e = Display.Diagnostics.secure_generated_code ctx e in
+		let e = Diagnostics.secure_generated_code ctx e in
 		if Meta.has (Meta.Custom ":inlineDebug") ctx.meta then begin
 			let se t = s_expr_pretty true t true (s_type (print_context())) in
 			print_endline (Printf.sprintf "Inline %s:\n\tArgs: %s\n\tExpr: %s\n\tResult: %s"

+ 51 - 36
src/syntax/grammar.mly

@@ -38,6 +38,14 @@ let rec psep sep f = parser
 		v :: loop s
 	| [< >] -> []
 
+let expect_unless_resume f = parser
+	| [< _ = f >] -> ()
+	| [< >] -> if do_resume() then () else serror()
+
+let expect_unless_resume_p f = parser
+	| [< p = f >] -> p
+	| [< s >] -> if do_resume() then pos (next_token s) else serror()
+
 let ident = parser
 	| [< '(Const (Ident i),p) >] -> i,p
 
@@ -62,9 +70,15 @@ let property_ident = parser
 	| [< '(Kwd Default,p) >] -> "default",p
 	| [< '(Kwd Null,p) >] -> "null",p
 
+let bropen = parser
+	| [< '(BrOpen,_) >] -> ()
+
 let comma = parser
 	| [< '(Comma,_) >] -> ()
 
+let colon = parser
+	| [< '(DblDot,p) >] -> p
+
 let semicolon s =
 	if fst (last_token s) = BrClose then
 		match s with parser
@@ -143,7 +157,9 @@ and parse_type_decl s =
 					d_data = l
 				}, punion p1 p2)
 			end
-		| [< n , p1 = parse_class_flags; name = type_name; tl = parse_constraint_params; hl = plist parse_class_herit; '(BrOpen,_); fl, p2 = parse_class_fields false p1 >] ->
+		| [< n , p1 = parse_class_flags; name = type_name; tl = parse_constraint_params; hl = plist parse_class_herit; >] ->
+			expect_unless_resume bropen s;
+			let fl, p2 = parse_class_fields false p1 s in
 			(EClass {
 				d_name = name;
 				d_doc = doc;
@@ -198,9 +214,6 @@ and parse_import s p1 =
 				loop (("extern",p) :: acc)
 			| [< '(Binop OpMult,_); '(Semicolon,p2) >] ->
 				p2, List.rev acc, IAll
-			| [< '(Binop OpOr,_) when do_resume() >] ->
-				set_resume p;
-				resume()
 			| [< >] ->
 				serror());
 		| [< '(Semicolon,p2) >] ->
@@ -423,8 +436,21 @@ and parse_complex_type_maybe_named allow_named = parser
 		parse_complex_type_next t s
 
 and parse_structural_extension = parser
-	| [< '(Binop OpGt,_); t = parse_type_path; '(Comma,_); s >] ->
-		t
+	| [< '(Binop OpGt,p1); s >] ->
+		match s with parser
+		| [< t = parse_type_path >] ->
+			begin match s with parser
+				| [< '(Comma,_) >] -> t
+				| [< >] -> if do_resume() then t else serror()
+			end;
+		| [< >] ->
+			if would_skip_resume p1 s then begin
+				begin match s with parser
+					| [< '(Comma,_) >] -> ()
+					| [< >] -> ()
+				end;
+				{ tpackage = []; tname = ""; tparams = []; tsub = None },null_pos
+			end else raise Stream.Failure
 
 and parse_complex_type_inner allow_named = parser
 	| [< '(POpen,p1); t = parse_complex_type; '(PClose,p2) >] -> CTParent t,punion p1 p2
@@ -458,8 +484,6 @@ and parse_type_path s = parse_type_path1 None [] s
 and parse_type_path1 p0 pack = parser
 	| [< name, p1 = dollar_ident_macro pack; s >] ->
 		parse_type_path2 p0 pack name p1 s
-	| [< '(Binop OpOr,_) when do_resume() >] ->
-		raise (TypePath (List.rev pack,None,false))
 
 and parse_type_path2 p0 pack name p1 s =
 	if is_lower_ident name then
@@ -478,9 +502,6 @@ and parse_type_path2 p0 pack name p1 s =
 					(fun () -> raise (TypePath (List.rev pack,Some (name,false),false)))
 					(fun () -> match s with parser
 					| [< '(Const (Ident name),p2) when not (is_lower_ident name) >] -> Some name,p2
-					| [< '(Binop OpOr,_) when do_resume() >] ->
-						set_resume p;
-						raise (TypePath (List.rev pack,Some (name,false),false))
 					| [< >] -> serror()))
 			| [< >] -> None,p1
 		) in
@@ -611,7 +632,7 @@ and parse_var_field_assignment = parser
 and parse_class_field s =
 	let doc = get_doc s in
 	match s with parser
-	| [< meta = parse_meta; al = parse_cf_rights true []; s >] ->
+	| [< meta = parse_meta; al = plist parse_cf_rights; s >] ->
 		let name, pos, k, al = (match s with parser
 		| [< '(Kwd Var,p1); name = dollar_ident; s >] ->
 			begin match s with parser
@@ -626,8 +647,8 @@ and parse_class_field s =
 		| [< '(Kwd Final,p1) >] ->
 			begin match s with parser
 			| [< name = dollar_ident; t = popt parse_type_hint; e,p2 = parse_var_field_assignment >] ->
-				name,punion p1 p2,FVar(t,e),((AFinal,p1) :: al)
-			| [< al = parse_cf_rights (not (List.mem_assoc AStatic al)) ((AFinal,p1) :: al); f = parse_function_field doc meta al >] ->
+				name,punion p1 p2,FVar(t,e),(al @ [AFinal,p1])
+			| [< al2 = plist parse_cf_rights; f = parse_function_field doc meta (al @ ((AFinal,p1) :: al2)) >] ->
 				f
 			| [< >] ->
 				serror()
@@ -637,7 +658,7 @@ and parse_class_field s =
 		| [< >] ->
 			if al = [] then raise Stream.Failure else serror()
 		) in
-		let pos = match List.rev al with
+		let pos = match al with
 			| [] -> pos
 			| (_,p) :: _ -> punion p pos
 		in
@@ -650,16 +671,15 @@ and parse_class_field s =
 			cff_kind = k;
 		}
 
-and parse_cf_rights allow_static l = parser
-	| [< '(Kwd Static,p) when allow_static; l = parse_cf_rights false ((AStatic,p) :: l) >] -> l
-	| [< '(Kwd Macro,p) when not(List.mem_assoc AMacro l); l = parse_cf_rights allow_static ((AMacro,p) :: l) >] -> l
-	| [< '(Kwd Public,p) when not(List.mem_assoc APublic l || List.mem_assoc APrivate l); l = parse_cf_rights allow_static ((APublic,p) :: l) >] -> l
-	| [< '(Kwd Private,p) when not(List.mem_assoc APublic l || List.mem_assoc APrivate l); l = parse_cf_rights allow_static ((APrivate,p) :: l) >] -> l
-	| [< '(Kwd Override,p) when not (List.mem_assoc AOverride l); l = parse_cf_rights false ((AOverride,p) :: l) >] -> l
-	| [< '(Kwd Dynamic,p) when not (List.mem_assoc ADynamic l); l = parse_cf_rights allow_static ((ADynamic,p) :: l) >] -> l
-	| [< '(Kwd Inline,p); l = parse_cf_rights allow_static ((AInline,p) :: l) >] -> l
-	| [< '(Kwd Extern,p); l = parse_cf_rights allow_static ((AExtern,p) :: l) >] -> l
-	| [< >] -> l
+and parse_cf_rights = parser
+	| [< '(Kwd Static,p) >] -> AStatic,p
+	| [< '(Kwd Macro,p) >] -> AMacro,p
+	| [< '(Kwd Public,p) >] -> APublic,p
+	| [< '(Kwd Private,p) >] -> APrivate,p
+	| [< '(Kwd Override,p) >] -> AOverride,p
+	| [< '(Kwd Dynamic,p) >] -> ADynamic,p
+	| [< '(Kwd Inline,p) >] -> AInline,p
+	| [< '(Kwd Extern,p) >] -> AExtern,p
 
 and parse_fun_name = parser
 	| [< name,p = dollar_ident >] -> name,p
@@ -705,7 +725,7 @@ and parse_constraint_param = parser
 
 and parse_type_path_or_resume p1 s = match s with parser
 	| [< t = parse_type_path >] -> t
-	| [< >] -> if would_skip_resume p1 s then { tpackage = []; tname = ""; tparams = []; tsub = None },null_pos else raise Stream.Failure
+	| [< >] -> if would_skip_resume p1 s then { tpackage = []; tname = ""; tparams = []; tsub = None },punion_next p1 s else raise Stream.Failure
 
 and parse_class_herit = parser
 	| [< '(Kwd Extends,p1); t = parse_type_path_or_resume p1 >] -> HExtends t
@@ -944,9 +964,6 @@ and expr = parser
 		end
 	| [< '(BrOpen,p1); s >] ->
 		(match s with parser
-		| [< '(Binop OpOr,p2) when do_resume() >] ->
-			set_resume p1;
-			display (EDisplay ((EObjectDecl [],p1),DKStructure),p1);
 		| [< b = block1; s >] ->
 			let p2 = match s with parser
 				| [< '(BrClose,p2) >] -> p2
@@ -988,7 +1005,7 @@ and expr = parser
 			| [< >] -> serror())
 		| [< e = secure_expr >] -> expr_next (ECast (e,None),punion p1 (pos e)) s)
 	| [< '(Kwd Throw,p); e = expr >] -> (EThrow e,p)
-	| [< '(Kwd New,p1); t = parse_type_path; s >] ->
+	| [< '(Kwd New,p1); t = parse_type_path_or_resume p1; s >] ->
 		begin match s with parser
 		| [< '(POpen,po); e = parse_call_params (fun el p2 -> (ENew(t,el)),punion p1 p2) po >] -> expr_next e s
 		| [< >] ->
@@ -1092,9 +1109,6 @@ and expr_next' e1 = parser
 		| [< '(Kwd New,p2) when p.pmax = p2.pmin; s >] -> expr_next (EField (e1,"new") , punion (pos e1) p2) s
 		| [< '(Const (Ident f),p2) when p.pmax = p2.pmin; s >] -> expr_next (EField (e1,f) , punion (pos e1) p2) s
 		| [< '(Dollar v,p2); s >] -> expr_next (EField (e1,"$"^v) , punion (pos e1) p2) s
-		| [< '(Binop OpOr,p2) when do_resume() >] ->
-			set_resume p;
-			display (EDisplay (e1,DKDot),p) (* help for debug display mode *)
 		| [< >] ->
 			(* turn an integer followed by a dot into a float *)
 			match e1 with
@@ -1140,7 +1154,7 @@ and parse_guard = parser
 
 and expr_or_var = parser
 	| [< '(Kwd Var,p1); name,p2 = dollar_ident; >] -> EVars [(name,p2),None,None],punion p1 p2
-	| [< e = expr >] -> e
+	| [< e = secure_expr >] -> e
 
 and parse_switch_cases eswitch cases = parser
 	| [< '(Kwd Default,p1); '(DblDot,_); s >] ->
@@ -1152,7 +1166,8 @@ and parse_switch_cases eswitch cases = parser
 		let l , def = parse_switch_cases eswitch cases s in
 		(match def with None -> () | Some _ -> error Duplicate_default p1);
 		l , Some b
-	| [< '(Kwd Case,p1); el = psep Comma expr_or_var; eg = popt parse_guard; '(DblDot,pdot); s >] ->
+	| [< '(Kwd Case,p1); el = psep Comma expr_or_var; eg = popt parse_guard; s >] ->
+		let pdot = expect_unless_resume_p colon s in
 		if !was_auto_triggered then check_resume pdot (fun () -> ()) (fun () -> ());
 		(match el with
 		| [] -> error (Custom "case without a pattern is not allowed") p1
@@ -1233,7 +1248,7 @@ and toplevel_expr s =
 
 and secure_expr s =
 	match s with parser
-	| [< e = expr >] -> e
+	| [< e = toplevel_expr >] -> e
 	| [< >] -> if do_resume() then mk_null_expr (punion_next (pos (last_token s)) s) else serror()
 
 and expr_or_fail fail s =

+ 10 - 2
src/syntax/parser.ml

@@ -81,6 +81,16 @@ let was_auto_triggered = ref false
 let display_mode = ref DMNone
 let resume_display = ref null_pos
 let in_macro = ref false
+let had_resume = ref false
+
+let reset_state () =
+	last_doc := None;
+	use_doc := false;
+	was_auto_triggered := false;
+	display_mode := DMNone;
+	resume_display := null_pos;
+	in_macro := false;
+	had_resume := false
 
 let last_token s =
 	let n = Stream.count s in
@@ -117,8 +127,6 @@ let is_resuming p =
 let set_resume p =
 	resume_display := { p with pfile = Path.unique_full_path p.pfile }
 
-let had_resume = ref false
-
 let encloses_resume p =
 	p.pmin < !resume_display.pmin && p.pmax >= !resume_display.pmax
 

+ 1 - 1
src/typing/calls.ml

@@ -596,7 +596,7 @@ let rec build_call ctx acc el (with_type:with_type) p =
 			!ethis_f();
 			raise (Fatal_error ((error_msg m),p))
 		in
-		let e = Display.Diagnostics.secure_generated_code ctx e in
+		let e = Diagnostics.secure_generated_code ctx e in
 		ctx.on_error <- old;
 		!ethis_f();
 		e

+ 1 - 1
src/typing/fields.ml

@@ -258,7 +258,7 @@ let rec using_field ctx mode e i p =
 						| _ -> ()
 					) monos cf.cf_params;
 					let et = type_module_type ctx (TClassDecl c) None p in
-					Display.ImportHandling.maybe_mark_import_position ctx pc;
+					ImportHandling.maybe_mark_import_position ctx pc;
 					AKUsing (mk (TField (et,FStatic (c,cf))) t p,c,cf,e)
 				| _ ->
 					raise Not_found

+ 2 - 2
src/typing/macroContext.ml

@@ -515,7 +515,7 @@ let get_macro_context ctx p =
 		Common.define com2 Define.Macro;
 		Common.init_platform com2 !Globals.macro_platform;
 		let mctx = ctx.g.do_create com2 in
-		mctx.is_display_file <- ctx.is_display_file;
+		mctx.is_display_file <- false;
 		create_macro_interp ctx mctx;
 		api, mctx
 
@@ -555,7 +555,7 @@ let load_macro ctx display cpath f p =
 		) in
 		api.MacroApi.current_macro_module <- (fun() -> mloaded);
 		if not (Common.defined ctx.com Define.NoDeprecationWarnings) then
-			Display.DeprecationCheck.check_cf mctx.com meth p;
+			DeprecationCheck.check_cf mctx.com meth p;
 		let meth = (match follow meth.cf_type with TFun (args,ret) -> args,ret,cl,meth | _ -> error "Macro call should be a method" p) in
 		mctx.com.display <- DisplayTypes.DisplayMode.create DMNone;
 		if not ctx.in_macro then flush_macro_context mint ctx;

+ 3 - 3
src/typing/matcher.ml

@@ -190,8 +190,8 @@ module Pattern = struct
 				v
 		in
 		let con_enum en ef p =
-			Display.DeprecationCheck.check_enum pctx.ctx.com en p;
-			Display.DeprecationCheck.check_ef pctx.ctx.com ef p;
+			DeprecationCheck.check_enum pctx.ctx.com en p;
+			DeprecationCheck.check_ef pctx.ctx.com ef p;
 			ConEnum(en,ef)
 		in
 		let check_expr e =
@@ -465,7 +465,7 @@ module Pattern = struct
 				PatExtractor(v,e1,pat)
 			| EDisplay(e,dk) ->
 				let pat = loop e in
-				ignore(TyperDisplay.handle_edisplay ctx e dk (WithType t));
+				ignore(TyperDisplay.handle_edisplay ctx e (if toplevel then DKPattern else dk) (WithType t));
 				pat
 			| _ ->
 				fail()

+ 63 - 17
src/typing/typeload.ml

@@ -23,6 +23,10 @@ open Ast
 open Common
 open DisplayTypes.DisplayMode
 open DisplayTypes.CompletionResultKind
+open CompletionItem
+open CompletionItem.CompletionModuleType
+open CompletionItem.CompletionModuleKind
+open DisplayException
 open Type
 open Typecore
 open Error
@@ -32,6 +36,29 @@ let build_count = ref 0
 
 let type_function_params_rec = ref (fun _ _ _ _ -> assert false)
 
+let check_field_access ctx acc =
+	ignore(List.fold_left (fun acc (access,p1) ->
+		try
+			let _,p2 = List.find (fun (access',_) -> access = access') acc in
+			if p1 <> null_pos && p2 <> null_pos then begin
+				display_error ctx (Printf.sprintf "Duplicate access modifier %s" (Ast.s_access access)) p1;
+				display_error ctx "Previously defined here" p2;
+			end;
+			acc
+		with Not_found -> match access with
+			| APublic | APrivate ->
+				begin try
+					let _,p2 = List.find (fun (access',_) -> match access' with APublic | APrivate -> true | _ -> false) acc in
+					display_error ctx (Printf.sprintf "Conflicting access modifier %s" (Ast.s_access access)) p1;
+					display_error ctx "Conflicts with this" p2;
+					acc
+				with Not_found ->
+					(access,p1) :: acc
+				end
+			| _ ->
+				(access,p1) :: acc
+	) [] acc)
+
 (** since load_type_def and load_instance are used in PASS2, they should not access the structure of a type **)
 
 (*
@@ -40,7 +67,7 @@ let type_function_params_rec = ref (fun _ _ _ _ -> assert false)
 let rec load_type_def ctx p t =
 	let no_pack = t.tpackage = [] in
 	let tname = (match t.tsub with None -> t.tname | Some n -> n) in
-	if tname = "" then Display.DisplayException.raise_fields (DisplayToplevel.collect ctx true NoValue) CRToplevel None false;
+	if tname = "" then raise_fields (DisplayToplevel.collect ctx true NoValue) CRTypeHint None false;
 	try
 		if t.tsub <> None then raise Not_found;
 		let path_matches t2 =
@@ -51,7 +78,7 @@ let rec load_type_def ctx p t =
 			List.find path_matches ctx.m.curmod.m_types
 		with Not_found ->
 			let t,pi = List.find (fun (t2,pi) -> path_matches t2) ctx.m.module_types in
-			Display.ImportHandling.mark_import_position ctx.com pi;
+			ImportHandling.mark_import_position ctx.com pi;
 			t
 	with
 		Not_found ->
@@ -79,7 +106,7 @@ let rec load_type_def ctx p t =
 					| (wp,pi) :: l ->
 						try
 							let t = load_type_def ctx p { t with tpackage = wp } in
-							Display.ImportHandling.mark_import_position ctx.com pi;
+							ImportHandling.mark_import_position ctx.com pi;
 							t
 						with
 							| Error (Module_not_found _,p2)
@@ -117,7 +144,7 @@ let rec load_type_def ctx p t =
 let resolve_position_by_path ctx path p =
 	let mt = load_type_def ctx p path in
 	let p = (t_infos mt).mt_pos in
-	Display.DisplayException.raise_position [p]
+	raise_position [p]
 
 let check_param_constraints ctx types t pl c p =
 	match follow t with
@@ -166,7 +193,7 @@ let pselect p1 p2 =
 	if p1 = null_pos then p2 else p1
 
 (* build an instance from a full type *)
-let rec load_instance ?(allow_display=false) ctx (t,pn) allow_no_params p =
+let rec load_instance' ctx (t,pn) allow_no_params p =
 	let p = pselect pn p in
 	let t = try
 		if t.tpackage <> [] || t.tsub <> None then raise Not_found;
@@ -263,9 +290,17 @@ let rec load_instance ?(allow_display=false) ctx (t,pn) allow_no_params p =
 			f params
 		end
 	in
-	if allow_display then Display.DisplayEmitter.check_display_type ctx t pn;
 	t
 
+and load_instance ctx ?(allow_display=false) (t,pn) allow_no_params p =
+	try
+		let t = load_instance' ctx (t,pn) allow_no_params p in
+		if allow_display then DisplayEmitter.check_display_type ctx t pn;
+		t
+	with Error (Module_not_found path,_) when (ctx.com.display.dms_kind = DMDefault) && Display.is_display_position pn ->
+		let s = s_type_path path in
+		raise_fields (DisplayToplevel.collect ctx false NoValue) CRTypeHint (Some {pn with pmin = pn.pmax - String.length s;}) false
+
 (*
 	build an instance from a complex type
 *)
@@ -277,7 +312,7 @@ and load_complex_type ctx allow_display p (t,pn) =
 	| CTOptional _ -> error "Optional type not allowed here" p
 	| CTNamed _ -> error "Named type not allowed here" p
 	| CTExtend (tl,l) ->
-		(match load_complex_type ctx allow_display p (CTAnonymous l,p) with
+		begin match load_complex_type ctx allow_display p (CTAnonymous l,p) with
 		| TAnon a as ta ->
 			let is_redefined cf1 a2 =
 				try
@@ -312,7 +347,16 @@ and load_complex_type ctx allow_display p (t,pn) =
 				| _ ->
 					error "Can only extend structures" p
 			in
-			let il = List.map (fun (t,pn) -> load_instance ctx ~allow_display (t,pn) false p) tl in
+			let il = List.map (fun (t,pn) ->
+				try
+					load_instance ctx ~allow_display (t,pn) false p
+				with DisplayException(DisplayFields(l,CRTypeHint,p,b)) ->
+					let l = List.filter (function
+						| ITType({kind = Struct},_) -> true
+						| _ -> false
+					) l in
+					raise_fields l CRStructExtension p b
+			) tl in
 			let tr = ref None in
 			let t = TMono tr in
 			let r = exc_protect ctx (fun r ->
@@ -327,7 +371,8 @@ and load_complex_type ctx allow_display p (t,pn) =
 				t
 			) "constraint" in
 			TLazy r
-		| _ -> assert false)
+		| _ -> assert false
+		end
 	| CTAnonymous l ->
 		let rec loop acc f =
 			let n = fst f.cff_name in
@@ -346,6 +391,7 @@ and load_complex_type ctx allow_display p (t,pn) =
 			let dyn = ref false in
 			let params = ref [] in
 			let final = ref false in
+			check_field_access ctx f.cff_access;
 			List.iter (fun a ->
 				match fst a with
 				| APublic -> ()
@@ -402,8 +448,8 @@ and load_complex_type ctx allow_display p (t,pn) =
 			} in
 			init_meta_overloads ctx None cf;
 			if ctx.is_display_file then begin
-				Display.DisplayEmitter.check_display_metadata ctx cf.cf_meta;
-				Display.DisplayEmitter.maybe_display_field ctx None cf cf.cf_name_pos;
+				DisplayEmitter.check_display_metadata ctx cf.cf_meta;
+				DisplayEmitter.maybe_display_field ctx None cf cf.cf_name_pos;
 			end;
 			PMap.add n cf acc
 		in
@@ -516,7 +562,7 @@ let load_type_hint ?(opt=false) ctx pcur t =
 			try
 				load_complex_type ctx true pcur (t,p)
 			with Error(Module_not_found(([],name)),p) as exc ->
-				if Display.Diagnostics.is_diagnostics_run ctx then DisplayToplevel.handle_unresolved_identifier ctx name p true;
+				if Diagnostics.is_diagnostics_run p then DisplayToplevel.handle_unresolved_identifier ctx name p true;
 				(* Default to Dynamic in display mode *)
 				if ctx.com.display.dms_display then t_dynamic else raise exc
 	in
@@ -568,7 +614,7 @@ let rec type_type_param ?(enum_constructor=false) ctx path get_params p tp =
 	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
 	if ctx.is_display_file && Display.is_display_position (pos tp.tp_name) then
-		Display.DisplayEmitter.display_type ctx t (pos tp.tp_name);
+		DisplayEmitter.display_type ctx t (pos tp.tp_name);
 	match tp.tp_constraints with
 	| [] ->
 		n, t
@@ -702,8 +748,8 @@ let string_list_of_expr_path (e,p) =
 	with Exit -> error "Invalid path" p
 
 let handle_path_display ctx path p =
-	let open Display.ImportHandling in
-	match Display.ImportHandling.convert_import_to_something_usable !Parser.resume_display path,ctx.com.display.dms_kind with
+	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))
 		| (IDKModule(sl,s),_),DMDefinition ->
@@ -711,7 +757,7 @@ let handle_path_display ctx path p =
 			   which might not even exist anyway. *)
 			let mt = ctx.g.do_load_module ctx (sl,s) p in
 			let p = { pfile = mt.m_extra.m_file; pmin = 0; pmax = 0} in
-			Display.DisplayException.raise_position [p]
+			DisplayException.raise_position [p]
 		| (IDKModule(sl,s),_),_ ->
 			(* TODO: wait till nadako requests @type display for these, then implement it somehow *)
 			raise (Parser.TypePath(sl,Some(s,false),true))
@@ -725,7 +771,7 @@ let handle_path_display ctx path p =
 				| TClassDecl c when snd c.cl_path = st ->
 					ignore(c.cl_build());
 					let cf = PMap.find sf c.cl_statics in
-					Display.DisplayEmitter.display_field ctx (Some c) cf p
+					DisplayEmitter.display_field ctx (Some c) cf p
 				| _ ->
 					()
 			) m.m_types;

+ 30 - 10
src/typing/typeloadCheck.ml

@@ -23,7 +23,13 @@ open Globals
 open Ast
 open Type
 open Typecore
-open DisplayTypes.DisplayMode
+open DisplayException
+open DisplayTypes
+open DisplayMode
+open CompletionItem
+open CompletionModuleKind
+open CompletionModuleType
+open CompletionResultKind
 open Common
 open Error
 
@@ -255,7 +261,7 @@ let check_global_metadata ctx meta f_add mpath tpath so =
 		let add = ((field_mode && to_fields) || (not field_mode && to_types)) && (match_path recursive sl1 sl2) in
 		if add then f_add m
 	) ctx.g.global_metadata;
-	if ctx.is_display_file then delay ctx PCheckConstraint (fun () -> Display.DisplayEmitter.check_display_metadata ctx meta)
+	if ctx.is_display_file then delay ctx PCheckConstraint (fun () -> DisplayEmitter.check_display_metadata ctx meta)
 
 let check_module_types ctx m p t =
 	let t = t_infos t in
@@ -268,13 +274,13 @@ let check_module_types ctx m p t =
 			Hashtbl.add ctx.g.types_module t.mt_path m.m_path
 
 module Inheritance = struct
+	let is_basic_class_path path = match path with
+		| ([],("Array" | "String" | "Date" | "Xml")) -> true
+		| _ -> false
+
 	let check_extends ctx c t p = match follow t with
-		| TInst ({ cl_path = [],"Array"; cl_extern = basic_extern },_)
-		| TInst ({ cl_path = [],"String"; cl_extern = basic_extern },_)
-		| TInst ({ cl_path = [],"Date"; cl_extern = basic_extern },_)
-		| TInst ({ cl_path = [],"Xml"; cl_extern = basic_extern },_) when not (c.cl_extern && basic_extern) ->
-			error "Cannot extend basic class" p;
 		| TInst (csup,params) ->
+			if is_basic_class_path csup.cl_path && not (c.cl_extern && csup.cl_extern) then error "Cannot extend basic class" p;
 			if is_parent c csup then error "Recursive class" p;
 			begin match csup.cl_kind with
 				| KTypeParameter _ ->
@@ -388,7 +394,7 @@ module Inheritance = struct
 						List.find path_matches ctx.m.curmod.m_types
 					with Not_found ->
 						let t,pi = List.find (fun (lt,_) -> path_matches lt) ctx.m.module_types in
-						Display.ImportHandling.mark_import_position ctx.com pi;
+						ImportHandling.mark_import_position ctx.com pi;
 						t
 					in
 					{ t with tpackage = fst (t_path lt) },p
@@ -449,10 +455,24 @@ module Inheritance = struct
 		in
 		let fl = ExtList.List.filter_map (fun (is_extends,t) ->
 			try
-				let t = Typeload.load_instance ~allow_display:true ctx t false p in
+				let t = try
+					Typeload.load_instance ~allow_display:true ctx t false p
+				with DisplayException(DisplayFields(l,CRTypeHint,p,b)) ->
+					(* We don't allow `implements` on interfaces. Just raise fields completion with no fields. *)
+					if not is_extends && c.cl_interface then raise_fields [] CRImplements p false;
+					let l = List.filter (function
+						| ITType({kind = Interface} as cm,_) -> (not is_extends || c.cl_interface) && CompletionModuleType.get_path cm <> c.cl_path
+						| ITType({kind = Class} as cm,_) ->
+							is_extends && not c.cl_interface && CompletionModuleType.get_path cm <> c.cl_path &&
+							(not (Meta.has Meta.Final cm.meta) || Meta.has Meta.Hack c.cl_meta) &&
+							(not (is_basic_class_path (cm.pack,cm.name)) || (c.cl_extern && cm.is_extern))
+						| _ -> false
+					) l in
+					raise_fields l (if is_extends then CRExtends else CRImplements) p b
+				in
 				Some (check_herit t is_extends)
 			with Error(Module_not_found(([],name)),p) when ctx.com.display.dms_display ->
-				if Display.Diagnostics.is_diagnostics_run ctx then DisplayToplevel.handle_unresolved_identifier ctx name p true;
+				if Diagnostics.is_diagnostics_run p then DisplayToplevel.handle_unresolved_identifier ctx name p true;
 				None
 		) herits in
 		fl

+ 25 - 25
src/typing/typeloadFields.ml

@@ -276,6 +276,17 @@ let patch_class ctx c fields =
 		in
 		List.rev (loop [] fields)
 
+let lazy_display_type ctx f =
+	(* if ctx.is_display_file then begin
+		let r = exc_protect ctx (fun r ->
+			let t = f () in
+			r := lazy_processing (fun () -> t);
+			t
+		) "" in
+		TLazy r
+	end else *)
+		f ()
+
 let build_enum_abstract ctx c a fields p =
 	List.iter (fun field ->
 		match field.cff_kind with
@@ -402,6 +413,7 @@ let create_field_context (ctx,cctx) c cff =
 		ctx with
 		pass = PBuildClass; (* will be set later to PTypeExpr *)
 	} in
+	Typeload.check_field_access ctx cff.cff_access;
 	let is_static = List.mem_assoc AStatic cff.cff_access in
 	let is_extern = List.mem_assoc AExtern cff.cff_access in
 	let is_extern = if Meta.has Meta.Extern cff.cff_meta then begin
@@ -587,7 +599,7 @@ let bind_var (ctx,cctx,fctx) cf e =
 
 	match e with
 	| None ->
-		if fctx.is_display_field then Display.DisplayEmitter.maybe_display_field ctx (Some c) cf cf.cf_name_pos;
+		if fctx.is_display_field then DisplayEmitter.maybe_display_field ctx (Some c) cf cf.cf_name_pos;
 	| Some e ->
 		if requires_value_meta ctx.com (Some c) then cf.cf_meta <- ((Meta.Value,[e],null_pos) :: cf.cf_meta);
 		let check_cast e =
@@ -674,7 +686,7 @@ let bind_var (ctx,cctx,fctx) cf e =
 				let e = check_cast e in
 				cf.cf_expr <- Some e;
 				cf.cf_type <- t;
-				if fctx.is_display_field then Display.DisplayEmitter.maybe_display_field ctx (Some c) cf cf.cf_name_pos;
+				if fctx.is_display_field then DisplayEmitter.maybe_display_field ctx (Some c) cf cf.cf_name_pos;
 			end;
 			t
 		) "bind_var" in
@@ -695,15 +707,7 @@ let create_variable (ctx,cctx,fctx) c f t eo p =
 		| None ->
 			mk_mono()
 		| Some t ->
-			(* TODO is_lib: only load complex type if needed *)
-			let old = ctx.type_params in
-			if fctx.is_static then ctx.type_params <- (match cctx.abstract with
-				| Some a -> a.a_params
-				| _ -> []
-			);
-			let t = load_complex_type ctx true p t in
-			if fctx.is_static then ctx.type_params <- old;
-			t
+			lazy_display_type ctx (fun () -> load_complex_type ctx true p t)
 	) in
 	let kind = if fctx.is_inline then
 		{ v_read = AccInline ; v_write = AccNever }
@@ -908,11 +912,7 @@ let create_method (ctx,cctx,fctx) c f fd p =
 	let parent = (if not fctx.is_static then get_parent c (fst f.cff_name) else None) in
 	let dynamic = List.mem_assoc ADynamic f.cff_access || (match parent with Some { cf_kind = Method MethDynamic } -> true | _ -> false) in
 	if fctx.is_inline && dynamic then error (fst f.cff_name ^ ": You can't have both 'inline' and 'dynamic'") p;
-	ctx.type_params <- (match cctx.abstract with
-		| Some a when fctx.is_abstract_member ->
-			params @ a.a_params
-		| _ ->
-			if fctx.is_static then params else params @ ctx.type_params);
+	ctx.type_params <- if fctx.is_static && not fctx.is_abstract_member then params else ctx.type_params @ params;
 	(* TODO is_lib: avoid forcing the return type to be typed *)
 	let ret = if fctx.field_kind = FKConstructor then ctx.t.tvoid else type_opt (ctx,cctx) p fd.f_type in
 	let rec loop args = match args with
@@ -978,7 +978,7 @@ let create_method (ctx,cctx,fctx) c f fd p =
 							begin match c.cl_super with
 							| Some(c,tl) ->
 								let _,_,cf = raw_class_field (fun cf -> cf.cf_type) c tl cf.cf_name in
-								Display.DisplayEmitter.display_field ctx (Some c) cf p
+								DisplayEmitter.display_field ctx (Some c) cf p
 							| _ ->
 								()
 							end
@@ -1004,26 +1004,22 @@ let create_method (ctx,cctx,fctx) c f fd p =
 						| _ -> c.cl_init <- Some e);
 					cf.cf_expr <- Some (mk (TFunction tf) t p);
 					cf.cf_type <- t;
-				if fctx.is_display_field then Display.DisplayEmitter.maybe_display_field ctx (Some c) cf cf.cf_name_pos
+				if fctx.is_display_field then DisplayEmitter.maybe_display_field ctx (Some c) cf cf.cf_name_pos
 			end;
 		end;
 		t
 	) "type_fun" in
 	if fctx.do_bind then bind_type (ctx,cctx,fctx) cf r (match fd.f_expr with Some e -> snd e | None -> f.cff_pos)
-	else if fctx.is_display_field then Display.DisplayEmitter.maybe_display_field ctx (Some c) cf cf.cf_name_pos;
+	else if fctx.is_display_field then DisplayEmitter.maybe_display_field ctx (Some c) cf cf.cf_name_pos;
 	cf
 
 let create_property (ctx,cctx,fctx) c f (get,set,t,eo) p =
 	let name = fst f.cff_name in
-	(match cctx.abstract with
-	| Some a when fctx.is_abstract_member ->
-		ctx.type_params <- a.a_params;
-	| _ -> ());
 	(* TODO is_lib: lazify load_complex_type *)
 	let ret = (match t, eo with
 		| None, None -> error (name ^ ": Property must either define a type or a default value") p;
 		| None, _ -> mk_mono()
-		| Some t, _ -> load_complex_type ctx true p t
+		| Some t, _ -> lazy_display_type ctx (fun () -> load_complex_type ctx true p t)
 	) in
 	let t_get,t_set = match cctx.abstract with
 		| Some a when fctx.is_abstract_member ->
@@ -1104,7 +1100,7 @@ let create_property (ctx,cctx,fctx) c f (get,set,t,eo) p =
 	let display_accessor m p =
 		try
 			let cf = match find_accessor m with [_,cf] -> cf | _ -> raise Not_found in
-			Display.DisplayEmitter.display_field ctx (Some c) cf p
+			DisplayEmitter.display_field ctx (Some c) cf p
 		with Not_found ->
 			()
 	in
@@ -1166,6 +1162,10 @@ let init_field (ctx,cctx,fctx) f =
 		| Some _ -> (match c.cl_super with None -> error ("Invalid override on field '" ^ name ^ "': class has no super class") p | _ -> ());
 		| None -> ()
 	end;
+	begin match cctx.abstract with
+		| Some a when fctx.is_abstract_member -> ctx.type_params <- a.a_params;
+		| _ -> ()
+	end;
 	match f.cff_kind with
 	| FVar (t,e) ->
 		create_variable (ctx,cctx,fctx) c f t e p

+ 7 - 3
src/typing/typeloadFunction.ml

@@ -24,7 +24,7 @@ open Ast
 open Type
 open Typecore
 open DisplayTypes.DisplayMode
-open Display.DisplayException
+open DisplayException
 open Common
 open Error
 
@@ -87,7 +87,7 @@ let type_function ctx args ret fmode f do_display p =
 		let v,c = add_local ctx n t pn, c in
 		v.v_meta <- m;
 		if do_display && Display.is_display_position pn then
-			Display.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;
 		v,c
 	) args f.f_args in
@@ -109,15 +109,19 @@ let type_function ctx args ret fmode f do_display p =
 	let e = if not do_display then
 		type_expr ctx e NoValue
 	else begin
+		let is_display_debug = Meta.has (Meta.Custom ":debug.display") ctx.curfield.cf_meta in
+		if is_display_debug then print_endline ("before processing:\n" ^ (Expr.dump_with_pos e));
 		let e = if !Parser.had_resume then e else Display.ExprPreprocessing.process_expr ctx.com e in
+		if is_display_debug then print_endline ("after processing:\n" ^ (Expr.dump_with_pos e));
 		try
 			if Common.defined ctx.com Define.NoCOpt || not !Parser.had_resume then raise Exit;
 			let e = Optimizer.optimize_completion_expr e f.f_args in
+			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 ->
 			type_expr ctx e NoValue
-		| DisplayException (DisplayType (t,_,_)) when (match follow t with TMono _ -> true | _ -> false) ->
+		| DisplayException (DisplayHover (Some t,_,_)) when (match follow t with TMono _ -> true | _ -> false) ->
 			type_expr ctx e NoValue
 	end in
 	let e = match e.eexpr with

+ 10 - 10
src/typing/typeloadModule.ml

@@ -339,9 +339,9 @@ let init_module_type ctx context_init do_init (decl,p) =
 	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. *)
 		| DMDiagnostics b when (b || Display.is_display_file p.pfile) && not (ExtString.String.ends_with p.pfile "import.hx") ->
-			Display.ImportHandling.add_import_position ctx.com p path;
+			ImportHandling.add_import_position ctx.com p path;
 		| DMStatistics | DMUsage _ ->
-			Display.ImportHandling.add_import_position ctx.com p path;
+			ImportHandling.add_import_position ctx.com p path;
 		| _ ->
 			if Display.is_display_file p.pfile then handle_path_display ctx path p
 	in
@@ -361,7 +361,7 @@ let init_module_type ctx context_init do_init (decl,p) =
 				ctx.m.wildcard_packages <- (List.map fst pack,p) :: ctx.m.wildcard_packages
 			| _ ->
 				(match List.rev path with
-				| [] -> Display.DisplayException.raise_fields (DisplayToplevel.collect ctx true NoValue) CRToplevel None false;
+				| [] -> DisplayException.raise_fields (DisplayToplevel.collect ctx true NoValue) CRImport None false;
 				| (_,p) :: _ -> error "Module name must start with an uppercase letter" p))
 		| (tname,p2) :: rest ->
 			let p1 = (match pack with [] -> p2 | (_,p1) :: _ -> p1) in
@@ -393,7 +393,7 @@ let init_module_type ctx context_init do_init (decl,p) =
 					t_type = f (List.map snd (t_infos t).mt_params);
 				} in
 				if ctx.is_display_file && Display.is_display_position p then
-					Display.DisplayEmitter.display_module_type ctx mt p;
+					DisplayEmitter.display_module_type ctx mt p;
 				mt
 			in
 			let add_static_init t name s =
@@ -473,7 +473,7 @@ let init_module_type ctx context_init do_init (decl,p) =
 			| (s1,_) :: sl ->
 				{ tpackage = List.rev (List.map fst sl); tname = s1; tsub = None; tparams = [] }
 			| [] ->
-				Display.DisplayException.raise_fields (DisplayToplevel.collect ctx true NoValue) CRToplevel None false;
+				DisplayException.raise_fields (DisplayToplevel.collect ctx true NoValue) CRUsing None false;
 		in
 		(* do the import first *)
 		let types = (match t.tsub with
@@ -505,7 +505,7 @@ let init_module_type ctx context_init do_init (decl,p) =
 	| EClass d ->
 		let c = (match get_type (fst d.d_name) with TClassDecl c -> c | _ -> assert false) in
 		if ctx.is_display_file && Display.is_display_position (pos d.d_name) then
-			Display.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;
 		let herits = d.d_flags in
 		c.cl_extern <- List.mem HExtern herits;
@@ -567,7 +567,7 @@ let init_module_type ctx context_init do_init (decl,p) =
 	| EEnum d ->
 		let e = (match get_type (fst d.d_name) with TEnumDecl e -> e | _ -> assert false) in
 		if ctx.is_display_file && Display.is_display_position (pos d.d_name) then
-			Display.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 h = (try Some (Hashtbl.find ctx.g.type_patches e.e_path) with Not_found -> None) in
 		TypeloadCheck.check_global_metadata ctx e.e_meta (fun m -> e.e_meta <- m :: e.e_meta) e.e_module.m_path e.e_path None;
@@ -671,7 +671,7 @@ let init_module_type ctx context_init do_init (decl,p) =
 				cf_params = f.ef_params;
 			} in
  			if ctx.is_display_file && Display.is_display_position f.ef_name_pos then
- 				Display.DisplayEmitter.display_enum_field ctx f p;
+ 				DisplayEmitter.display_enum_field ctx f p;
 			e.e_constrs <- PMap.add f.ef_name f e.e_constrs;
 			fields := PMap.add cf.cf_name cf !fields;
 			incr index;
@@ -698,7 +698,7 @@ let init_module_type ctx context_init do_init (decl,p) =
 	| ETypedef d ->
 		let t = (match get_type (fst d.d_name) with TTypeDecl t -> t | _ -> assert false) in
 		if ctx.is_display_file && Display.is_display_position (pos d.d_name) then
-			Display.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;
 		let ctx = { ctx with type_params = t.t_params } in
 		let tt = load_complex_type ctx true p d.d_data in
@@ -749,7 +749,7 @@ let init_module_type ctx context_init do_init (decl,p) =
 	| EAbstract d ->
 		let a = (match get_type (fst d.d_name) with TAbstractDecl a -> a | _ -> assert false) in
 		if ctx.is_display_file && Display.is_display_position (pos d.d_name) then
-			Display.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;
 		let ctx = { ctx with type_params = a.a_params } in
 		let is_type = ref false in

+ 8 - 4
src/typing/typeloadParse.ml

@@ -42,7 +42,7 @@ let parse_file_from_lexbuf com file p lexbuf =
 	in
 	begin match !Parser.display_mode with
 		| DMModuleSymbols filter when filter <> None || Display.is_display_file file ->
-			let ds = Display.DocumentSymbols.collect_module_symbols data in
+			let ds = DocumentSymbols.collect_module_symbols data in
 			com.shared.shared_display_information.document_symbols <- (file,ds) :: com.shared.shared_display_information.document_symbols;
 		| _ ->
 			()
@@ -127,10 +127,14 @@ let resolve_module_file com m remap p =
 	end;
 	file
 
-let parse_module ctx m p =
+let parse_module' com m p =
 	let remap = ref (fst m) in
-	let file = resolve_module_file ctx.com m remap p in
-	let pack, decls = (!parse_hook) ctx.com file p in
+	let file = resolve_module_file com m remap p in
+	let pack, decls = (!parse_hook) com file p in
+	file,remap,pack,decls
+
+let parse_module ctx m p =
+	let file,remap,pack,decls = parse_module' ctx.com m p in
 	if pack <> !remap then begin
 		let spack m = if m = [] then "<empty>" else String.concat "." m in
 		if p == null_pos then

+ 13 - 13
src/typing/typer.ml

@@ -173,7 +173,7 @@ let merge_core_doc ctx c =
 		| _ -> ()
 
 let check_error ctx err p = match err with
-	| Module_not_found ([],name) when Display.Diagnostics.is_diagnostics_run ctx ->
+	| Module_not_found ([],name) when Diagnostics.is_diagnostics_run p ->
 		DisplayToplevel.handle_unresolved_identifier ctx name p true
 	| _ ->
 		display_error ctx (error_msg err) p
@@ -404,7 +404,7 @@ let rec type_ident_raise ctx i p mode =
 							let et = type_module_type ctx (TClassDecl c) None p in
 							let fa = FStatic(c,cf) in
 							let t = monomorphs cf.cf_params cf.cf_type in
-							Display.ImportHandling.maybe_mark_import_position ctx pt;
+							ImportHandling.maybe_mark_import_position ctx pt;
 							begin match cf.cf_kind with
 								| Var {v_read = AccInline} -> AKInline(et,cf,fa,t)
 								| _ -> AKExpr (mk (TField(et,fa)) t p)
@@ -425,7 +425,7 @@ let rec type_ident_raise ctx i p mode =
 						let et = type_module_type ctx t None p in
 						let monos = List.map (fun _ -> mk_mono()) e.e_params in
 						let monos2 = List.map (fun _ -> mk_mono()) ef.ef_params in
-						Display.ImportHandling.maybe_mark_import_position ctx pt;
+						ImportHandling.maybe_mark_import_position ctx pt;
 						wrap (mk (TField (et,FEnum (e,ef))) (enum_field_type ctx e ef monos monos2 p) p)
 					with
 						Not_found -> loop l
@@ -434,7 +434,7 @@ let rec type_ident_raise ctx i p mode =
 	with Not_found ->
 		(* lookup imported globals *)
 		let t, name, pi = PMap.find i ctx.m.module_globals in
-		Display.ImportHandling.maybe_mark_import_position ctx pi;
+		ImportHandling.maybe_mark_import_position ctx pi;
 		let e = type_module_type ctx t None p in
 		type_field ctx e name p mode
 
@@ -1274,7 +1274,7 @@ and handle_efield ctx e p mode =
 									List.find path_match ctx.m.curmod.m_types (* types in this modules *)
 								with Not_found ->
 									let t,p = List.find (fun (t,_) -> path_match t) ctx.m.module_types in (* imported types *)
-									Display.ImportHandling.maybe_mark_import_position ctx p;
+									ImportHandling.maybe_mark_import_position ctx p;
 									t
 							in
 							get_static true t
@@ -1471,7 +1471,7 @@ and type_vars ctx vl p =
 			let v = add_local ctx v t pv in
 			v.v_meta <- (Meta.UserVariable,[],pv) :: v.v_meta;
 			if ctx.in_display && Display.is_display_position pv then
-				Display.DisplayEmitter.display_variable ctx v pv;
+				DisplayEmitter.display_variable ctx v pv;
 			v,e
 		with
 			Error (e,p) ->
@@ -1651,7 +1651,7 @@ and type_object_decl ctx fl with_type p =
 					| Some t -> t
 					| None ->
 						let cf = PMap.find n field_map in
-						if ctx.in_display && Display.is_display_position pn then Display.DisplayEmitter.display_field ctx None cf pn;
+						if ctx.in_display && Display.is_display_position pn then DisplayEmitter.display_field ctx None cf pn;
 						cf.cf_type
 				in
 				let e = type_expr ctx e (WithType t) in
@@ -1689,7 +1689,7 @@ and type_object_decl ctx fl with_type p =
 			let e = type_expr ctx e Value in
 			(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
-			if ctx.in_display && Display.is_display_position pf then Display.DisplayEmitter.display_field ctx None cf pf;
+			if ctx.in_display && Display.is_display_position pf then DisplayEmitter.display_field ctx None cf pf;
 			(((f,pf,qs),e) :: l, if is_valid then begin
 				if String.length f > 0 && f.[0] = '$' then error "Field names starting with a dollar are not allowed" p;
 				PMap.add f cf acc
@@ -1787,7 +1787,7 @@ and type_new ctx path el with_type p =
 		| mt ->
 			error ((s_type_path (t_infos mt).mt_path) ^ " cannot be constructed") p
 	in
-	Display.DisplayEmitter.check_display_type ctx t (pos path);
+	DisplayEmitter.check_display_type ctx t (pos path);
 	let build_constructor_call c tl =
 		let ct, f = get_constructor ctx c tl p in
 		if (Meta.has Meta.CompilerGenerated f.cf_meta) then display_error ctx (error_msg (No_constructor (TClassDecl c))) p;
@@ -1829,7 +1829,7 @@ and type_new ctx path el with_type p =
 		error (s_type (print_context()) t ^ " cannot be constructed") p
 	end with Error(No_constructor _ as err,p) when ctx.com.display.dms_display ->
 		display_error ctx (error_msg err) p;
-		Display.Diagnostics.secure_generated_code ctx (mk (TConst TNull) t p)
+		Diagnostics.secure_generated_code ctx (mk (TConst TNull) t p)
 
 and type_try ctx e1 catches with_type p =
 	let e1 = type_expr ctx (Expr.ensure_block e1) with_type in
@@ -1885,7 +1885,7 @@ and type_try ctx e1 catches with_type p =
 		let locals = save_locals ctx in
 		let v = add_local ctx v t pv in
 		if ctx.is_display_file && Display.is_display_position pv then
-			Display.DisplayEmitter.display_variable ctx v pv;
+			DisplayEmitter.display_variable ctx v pv;
 		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
 		   punctuation. Otherwise we wouldn't reach this point. *)
@@ -2210,7 +2210,7 @@ and type_if ctx e e1 e2 with_type p =
 		mk (TIf (e,e1,Some e2)) t p)
 
 and type_meta ctx m e1 with_type p =
-	if ctx.is_display_file then Display.DisplayEmitter.check_display_metadata ctx [m];
+	if ctx.is_display_file then DisplayEmitter.check_display_metadata ctx [m];
 	let old = ctx.meta in
 	ctx.meta <- m :: ctx.meta;
 	let e () = type_expr ctx e1 with_type in
@@ -2291,7 +2291,7 @@ and type_call ctx e el (with_type:with_type) p =
 	| (EConst (Ident "$type"),_) , [e] ->
 		let e = type_expr ctx e Value in
 		ctx.com.warning (s_type (print_context()) e.etype) e.epos;
-		let e = Display.Diagnostics.secure_generated_code ctx e in
+		let e = Diagnostics.secure_generated_code ctx e in
 		e
 	| (EField(e,"match"),p), [epat] ->
 		let et = type_expr ctx e Value in

+ 1 - 1
src/typing/typerBase.ml

@@ -125,7 +125,7 @@ let rec type_module_type ctx t tparams p =
 	| TTypeDecl s ->
 		let t = apply_params s.t_params (List.map (fun _ -> mk_mono()) s.t_params) s.t_type in
 		if not (Common.defined ctx.com Define.NoDeprecationWarnings) then
-			Display.DeprecationCheck.check_typedef ctx.com s p;
+			DeprecationCheck.check_typedef ctx.com s p;
 		(match follow t with
 		| TEnum (e,params) ->
 			type_module_type ctx (TEnumDecl e) (Some params) p

+ 24 - 8
src/typing/typerDisplay.ml

@@ -1,8 +1,12 @@
 open Globals
 open Ast
-open DisplayTypes.DisplayMode
-open DisplayTypes.CompletionResultKind
-open Display.DisplayException
+open DisplayTypes
+open DisplayMode
+open CompletionResultKind
+open CompletionItem
+open CompletionModuleKind
+open CompletionModuleType
+open DisplayException
 open Common
 open Type
 open Typecore
@@ -147,7 +151,7 @@ and display_expr ctx e_ast e dk with_type p =
 			| _ -> e.etype,None
 		in
 		let t,doc = loop e in
-		raise_type (Display.DisplayEmitter.patch_type ctx t) p doc
+		raise_hover (Some (DisplayEmitter.patch_type ctx t)) p doc
 	| DMUsage _ ->
 		let rec loop e = match e.eexpr with
 		| TField(_,FEnum(_,ef)) ->
@@ -235,11 +239,11 @@ let handle_structure_display ctx e fields =
 	| EObjectDecl fl ->
 		let fields = PMap.foldi (fun k cf acc ->
 			if Expr.field_mem_assoc k fl then acc
-			else (DisplayTypes.CompletionKind.ITClassMember cf) :: acc
+			else (CompletionItem.ITClassField(cf,CFSMember)) :: acc
 		) fields [] in
 		raise_fields fields CRStructureField None false
 	| EBlock [] ->
-		let fields = PMap.foldi (fun _ cf acc -> DisplayTypes.CompletionKind.ITClassMember cf :: acc) fields [] in
+		let fields = PMap.foldi (fun _ cf acc -> CompletionItem.ITClassField(cf,CFSMember) :: acc) fields [] in
 		raise_fields fields CRStructureField None false
 	| _ ->
 		error "Expected object expression" p
@@ -257,7 +261,7 @@ let handle_display ctx e_ast dk with_type =
 		| DMSignature ->
 			raise_signatures [((arg,mono),doc)] 0 0
 		| _ ->
-			raise_type (TFun(arg,mono)) (pos e_ast) doc
+			raise_hover (Some (TFun(arg,mono))) (pos e_ast) doc
 		end
 	| (EConst (Ident "trace"),_),_ ->
 		let doc = Some "Print given arguments" in
@@ -267,7 +271,7 @@ let handle_display ctx e_ast dk with_type =
 		| DMSignature ->
 			raise_signatures [((arg,ret),doc)] 0 0
 		| _ ->
-			raise_type (TFun(arg,ret)) (pos e_ast) doc
+			raise_hover (Some (TFun(arg,ret))) (pos e_ast) doc
 		end
 	| (EConst (Ident "_"),p),WithType t ->
 		mk (TConst TNull) t p (* This is "probably" a bind skip, let's just use the expected type *)
@@ -282,6 +286,12 @@ let handle_display ctx e_ast dk with_type =
 		with Not_found ->
 			raise err
 		end
+	| DisplayException(DisplayFields(l,CRTypeHint,p,b)) when (match fst e_ast with ENew _ -> true | _ -> false) ->
+		let l = List.filter (function
+			| ITType({kind = (Class | Abstract)},_) -> true
+			| _ -> false
+		) l in
+		raise_fields l CRNew p b
 	in
 	let p = e.epos in
 	let e = match with_type with
@@ -305,4 +315,10 @@ let handle_edisplay ctx e dk with_type =
 			| _ ->
 				handle_display ctx e dk with_type
 		end
+	| DKPattern,DMDefault ->
+		begin try
+			handle_display ctx e dk with_type
+		with DisplayException(DisplayFields(l,CRToplevel,p,b)) ->
+			raise_fields l CRPattern p b
+		end
 	| _ -> handle_display ctx e dk with_type

+ 9 - 2
std/haxe/rtti/JsonModuleTypes.hx → std/haxe/display/JsonModuleTypes.hx

@@ -19,7 +19,7 @@
  * FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER
  * DEALINGS IN THE SOFTWARE.
  */
-package haxe.rtti;
+package haxe.display;
 
 typedef JsonTodo = Dynamic;
 
@@ -190,6 +190,12 @@ typedef JsonFieldKind<T> = {
 	var args: T;
 }
 
+enum abstract JsonClassFieldScope(Int) {
+    var Static = 0;
+    var Member = 1;
+    var Constructor = 2;
+}
+
 typedef JsonClassField = {
 	var name: String;
 	var type: JsonType<Dynamic>;
@@ -201,6 +207,7 @@ typedef JsonClassField = {
 	var pos: JsonPos;
 	var doc: JsonDoc;
 	var overloads: JsonClassFields;
+    var scope: JsonClassFieldScope;
 }
 
 typedef JsonClassFields = Array<JsonClassField>;
@@ -305,7 +312,7 @@ enum abstract JsonModuleTypeKind<T>(String) {
 typedef JsonModuleType<T> = {
 	var pack: Array<String>;
 	var name: String;
-	var module: String;
+	var moduleName: String;
 	var pos: JsonPos;
 	var isPrivate: Bool;
 	var params: JsonTypeParameters;

+ 2 - 2
std/haxe/rtti/JsonModuleTypesPrinter.hx → std/haxe/display/JsonModuleTypesPrinter.hx

@@ -19,9 +19,9 @@
  * FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER
  * DEALINGS IN THE SOFTWARE.
  */
-package haxe.rtti;
+package haxe.display;
 
-import haxe.rtti.JsonModuleTypes;
+import haxe.display.JsonModuleTypes;
 using Lambda;
 
 class JsonModuleTypesPrinter {

+ 1 - 0
std/haxe/macro/Expr.hx

@@ -537,6 +537,7 @@ enum DisplayKind {
 	DKDot;
 	DKStructure;
 	DKMarked;
+	DKPattern;
 }
 
 /**

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

@@ -21,6 +21,8 @@ class DisplayTestCase {
 	inline function signature(pos1) return ctx.signature(pos1);
 	inline function metadataDoc(pos1) return ctx.metadataDoc(pos1);
 
+	inline function noCompletionPoint(f) return ctx.noCompletionPoint(f);
+
 	function assert(v:Bool) if (!v) throw "assertion failed";
 
 	function eq<T>(expected:T, actual:T, ?pos:haxe.PosInfos) {

+ 9 - 0
tests/display/src/DisplayTestContext.hx

@@ -77,6 +77,15 @@ class DisplayTestContext {
 		return extractMetadata(callHaxe('$pos@type'));
 	}
 
+	public function noCompletionPoint(f:Void -> Void):Bool {
+		return try {
+			f();
+			false;
+		} catch(exc:HaxeInvocationException) {
+			return exc.message.indexOf("No completion point") != -1;
+		}
+	}
+
 	function callHaxe(displayPart:String):String {
 		var args = [
 			"-cp", "src",

+ 129 - 0
tests/display/src/cases/Issue7029.hx

@@ -0,0 +1,129 @@
+package cases;
+
+class Issue7029 extends DisplayTestCase {
+	/**
+	class C implements {-1-}
+
+	interface IFoo { }
+	**/
+	function test1() {
+		var typesCompletion = toplevel(pos(1));
+		eq(true, hasToplevel(typesCompletion, "type", "IFoo"));
+		eq(false, hasToplevel(typesCompletion, "type", "C"));
+	}
+
+	/**
+	class C1 extends {-1-}
+
+	class C2 { }
+	interface IFoo { }
+	**/
+	function test2() {
+		var typesCompletion = toplevel(pos(1));
+		eq(true, hasToplevel(typesCompletion, "type", "C2"));
+		eq(false, hasToplevel(typesCompletion, "type", "IFoo"));
+		eq(false, hasToplevel(typesCompletion, "type", "C1"));
+	}
+
+	/**
+	class C { }
+	interface IFoo { }
+	interface IFoo2 extends {-1-} { }
+	**/
+	function test3() {
+		var typesCompletion = toplevel(pos(1));
+		eq(true, hasToplevel(typesCompletion, "type", "IFoo"));
+		eq(false, hasToplevel(typesCompletion, "type", "C"));
+		eq(false, hasToplevel(typesCompletion, "type", "IFoo2"));
+	}
+
+	/**
+	typedef T1 = { };
+	class C1 { }
+
+	typedef T2 = {
+		> {-1-}
+	}
+	**/
+	function test4() {
+		var typesCompletion = toplevel(pos(1));
+		eq(true, hasToplevel(typesCompletion, "type", "T1"));
+		eq(false, hasToplevel(typesCompletion, "type", "C1"));
+	}
+
+	/**
+	typedef T1 = { };
+	class C1 { }
+
+	typedef T2 = {
+		> T{-1-}
+	}
+	**/
+	function test5() {
+		var typesCompletion = toplevel(pos(1));
+		eq(true, hasToplevel(typesCompletion, "type", "T1"));
+		eq(false, hasToplevel(typesCompletion, "type", "C1"));
+	}
+
+	/**
+	typedef T1 = { };
+	typedef T2 = { };
+	class C1 { }
+
+	typedef T3 = {
+		> T1,
+		> {-1-}
+	}
+	**/
+	function test6() {
+		var typesCompletion = toplevel(pos(1));
+		eq(true, hasToplevel(typesCompletion, "type", "T2"));
+		eq(false, hasToplevel(typesCompletion, "type", "C1"));
+	}
+
+	/**
+	interface I1 {}
+	typedef T1 = {};
+	enum E1 {}
+	class C1 {}
+
+	class C2 {
+		static function main() {
+			new{-1-}   {-2-}
+		}
+	}
+	**/
+	function test7() {
+		var typesCompletion = toplevel(pos(1));
+		eq(true, hasToplevel(typesCompletion, "type", "C1"));
+		eq(true, hasToplevel(typesCompletion, "type", "C2"));
+		eq(false, hasToplevel(typesCompletion, "type", "I1"));
+		eq(false, hasToplevel(typesCompletion, "type", "T1"));
+		eq(false, hasToplevel(typesCompletion, "type", "E1"));
+
+		var typesCompletion = toplevel(pos(2));
+		eq(true, hasToplevel(typesCompletion, "type", "C1"));
+		eq(true, hasToplevel(typesCompletion, "type", "C2"));
+		eq(false, hasToplevel(typesCompletion, "type", "I1"));
+		eq(false, hasToplevel(typesCompletion, "type", "T1"));
+		eq(false, hasToplevel(typesCompletion, "type", "E1"));
+	}
+
+	/**
+	@:final class C1 { }
+	class C2 extends {-1-} { }
+	**/
+	function test8() {
+		var typesCompletion = toplevel(pos(1));
+		eq(false, hasToplevel(typesCompletion, "type", "C1"));
+	}
+
+	/**
+	@:final class C1 { }
+	@:hack class C2 extends {-1-} { }
+	**/
+	function test9() {
+		var typesCompletion = toplevel(pos(1));
+		eq(true, hasToplevel(typesCompletion, "type", "C1"));
+	}
+}

+ 14 - 0
tests/display/src/cases/Signature.hx

@@ -173,6 +173,20 @@ class Signature extends DisplayTestCase {
 		sigEq(0, [["a:String", "b:Int"]], signature(pos(1)));
 	}
 
+	/**
+	class Some {
+		static function main() {
+			test2(test({-1-}
+		}
+
+		static function test(a:String, b:Int) { }
+		static function test2(a:Int, b:String) { }
+	}
+	**/
+	function testNestedNotPointless() {
+		sigEq(0, [["a:String", "b:Int"]], signature(pos(1)));
+	}
+
 	/**
 	class Main {
 

+ 7 - 5
tests/display/src/cases/Toplevel.hx

@@ -97,13 +97,14 @@ class Toplevel extends DisplayTestCase {
 	}
 
 	/**
+	class C0 { }
 	class C extends {-1-} {
 	**/
 	function testTypeCompletionExtends() {
 		// TODO: this currently doesn't work if there's no token after extends
 		var typesCompletion = toplevel(pos(1));
-		eq(true, hasToplevel(typesCompletion, "type", "Array"));
-		eq(true, hasToplevel(typesCompletion, "package", "haxe"));
+		eq(true, hasToplevel(typesCompletion, "type", "C0"));
+		// eq(true, hasToplevel(typesCompletion, "package", "haxe"));
 	}
 
 	/**
@@ -111,9 +112,10 @@ class Toplevel extends DisplayTestCase {
 	**/
 	function testTypeCompletionImplements() {
 		// TODO: this currently doesn't work if there's no token after implements
-		var typesCompletion = toplevel(pos(1));
-		eq(true, hasToplevel(typesCompletion, "type", "Array"));
-		eq(true, hasToplevel(typesCompletion, "package", "haxe"));
+		// NOTE: This test is invalid, we only show interfaces after `implements`
+		// var typesCompletion = toplevel(pos(1));
+		// eq(true, hasToplevel(typesCompletion, "type", "Array"));
+		// eq(true, hasToplevel(typesCompletion, "package", "haxe"));
 	}
 
 	/**

+ 13 - 0
tests/display/src/cases/VsHaxeIssue198.hx

@@ -0,0 +1,13 @@
+package cases;
+
+class VsHaxeIssue198 extends DisplayTestCase {
+	/**
+	'foo.{-1-}${"foo.{-2-}".{-3-}}';
+	**/
+	@:funcCode function test() {
+		// TODO
+		// eq(true, noCompletionPoint(fields.bind(pos(1))));
+		// eq(true, noCompletionPoint(fields.bind(pos(2))));
+		eq(true, hasField(fields(pos(3)), "length", "Int"));
+	}
+}

+ 1 - 1
tests/misc/projects/Issue6005/Main.hx

@@ -1,6 +1,6 @@
 class Main {
 	public static function main() {
-		var foo:Struct = {|
+		var foo:Struct = {
 
 		}
 	}

+ 1 - 1
tests/misc/projects/Issue6005/compile1.hxml

@@ -1 +1 @@
---display Main.hx@0
+--display Main.hx@66