Browse Source

move some things around

Simon Krajewski 9 năm trước cách đây
mục cha
commit
71fceb3b16
6 tập tin đã thay đổi với 60 bổ sung42 xóa
  1. 1 1
      Makefile
  2. 1 10
      src/display/display.ml
  3. 7 15
      src/main.ml
  4. 27 0
      src/typing/common.ml
  5. 9 5
      src/typing/type.ml
  6. 15 11
      src/typing/typer.ml

+ 1 - 1
Makefile

@@ -133,7 +133,7 @@ uninstall:
 
 # display
 
-src/display/display.$(MODULE_EXT): src/syntax/ast.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/typing/type.$(MODULE_EXT) src/syntax/parser.$(MODULE_EXT)
+src/display/display.$(MODULE_EXT): src/syntax/ast.$(MODULE_EXT) src/typing/common.$(MODULE_EXT) src/typing/type.$(MODULE_EXT) src/typing/typecore.$(MODULE_EXT) src/syntax/parser.$(MODULE_EXT)
 
 # generators
 

+ 1 - 10
src/display/display.ml

@@ -9,15 +9,6 @@ type display_field_kind =
 	| FKType
 	| FKPackage
 
-type identifier_type =
-	| ITLocal of tvar
-	| ITMember of tclass * tclass_field
-	| ITStatic of tclass * tclass_field
-	| ITEnum of tenum * tenum_field
-	| ITGlobal of module_type * string * t
-	| ITType of module_type
-	| ITPackage of string
-
 exception Diagnostics of string
 exception ModuleSymbols of string
 exception DisplaySignatures of (t * documentation) list
@@ -25,7 +16,7 @@ exception DisplayType of t * pos
 exception DisplayPosition of Ast.pos list
 exception DisplaySubExpression of Ast.expr
 exception DisplayFields of (string * t * display_field_kind option * documentation) list
-exception DisplayToplevel of identifier_type list
+exception DisplayToplevel of IdentifierType.t list
 
 let is_display_file file =
 	file <> "?" && Common.unique_full_path file = (!Parser.resume_display).pfile

+ 7 - 15
src/main.ml

@@ -57,16 +57,9 @@ type context = {
 	mutable has_error : bool;
 }
 
-type cache = {
-	mutable c_haxelib : (string list, string list) Hashtbl.t;
-	mutable c_files : (string, float * Ast.package) Hashtbl.t;
-	mutable c_modules : (path * string, module_def) Hashtbl.t;
-}
-
 exception Abort
 exception Completion of string
 
-
 let version = 3300
 let version_major = version / 1000
 let version_minor = (version mod 1000) / 100
@@ -76,7 +69,6 @@ let version_is_stable = version_minor land 1 = 0
 let measure_times = ref false
 let prompt = ref false
 let start_time = ref (get_time())
-let global_cache = ref None
 
 let path_sep = if Sys.os_type = "Unix" then "/" else "\\"
 
@@ -1789,20 +1781,20 @@ with
 		let s_type t = htmlescape (s_type ctx t) in
 		let s_doc d = Option.map_default (fun s -> Printf.sprintf " d=\"%s\"" (htmlescape s)) "" d in
 		List.iter (fun id -> match id with
-			| Display.ITLocal v ->
+			| IdentifierType.ITLocal v ->
 				Buffer.add_string b (Printf.sprintf "<i k=\"local\" t=\"%s\">%s</i>\n" (s_type v.v_type) v.v_name);
-			| Display.ITMember(c,cf) ->
+			| IdentifierType.ITMember(c,cf) ->
 				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);
-			| Display.ITStatic(c,cf) ->
+			| IdentifierType.ITStatic(c,cf) ->
 				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);
-			| Display.ITEnum(en,ef) ->
+			| IdentifierType.ITEnum(en,ef) ->
 				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);
-			| Display.ITGlobal(mt,s,t) ->
+			| IdentifierType.ITGlobal(mt,s,t) ->
 				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);
-			| Display.ITType(mt) ->
+			| IdentifierType.ITType(mt) ->
 				let infos = t_infos mt in
 				Buffer.add_string b (Printf.sprintf "<i k=\"type\" p=\"%s\"%s>%s</i>\n" (s_type_path infos.mt_path) (s_doc infos.mt_doc) (snd infos.mt_path));
-			| Display.ITPackage s ->
+			| IdentifierType.ITPackage s ->
 				Buffer.add_string b (Printf.sprintf "<i k=\"package\">%s</i>\n" s)
 		) il;
 		Buffer.add_string b "</il>";

+ 27 - 0
src/typing/common.ml

@@ -107,6 +107,25 @@ type compiler_callback = {
 	mutable after_generation : (unit -> unit) list;
 }
 
+module IdentifierType = struct
+	type t =
+		| ITLocal of tvar
+		| ITMember of tclass * tclass_field
+		| ITStatic of tclass * tclass_field
+		| ITEnum of tenum * tenum_field
+		| ITGlobal of module_type * string * Type.t
+		| ITType of module_type
+		| ITPackage of string
+
+	let get_name = function
+		| ITLocal v -> v.v_name
+		| ITMember(_,cf) | ITStatic(_,cf) -> cf.cf_name
+		| ITEnum(_,ef) -> ef.ef_name
+		| ITGlobal(_,s,_) -> s
+		| ITType mt -> snd (t_infos mt).mt_path
+		| ITPackage s -> s
+end
+
 type display_information = {
 	mutable import_positions : (pos,bool ref) PMap.t;
 }
@@ -173,6 +192,14 @@ exception Abort of string * Ast.pos
 
 let display_default = ref DMNone
 
+type cache = {
+	mutable c_haxelib : (string list, string list) Hashtbl.t;
+	mutable c_files : (string, float * Ast.package) Hashtbl.t;
+	mutable c_modules : (path * string, module_def) Hashtbl.t;
+}
+
+let global_cache : cache option ref = ref None
+
 module Define = struct
 
 	type strict_defined =

+ 9 - 5
src/typing/type.ml

@@ -2612,15 +2612,19 @@ module StringError = struct
 				done;
 				matrix.(m).(n)
 
+	let filter_similar f cl =
+		let rec loop sl = match sl with
+			| (x,i) :: sl when f x i -> x :: loop sl
+			| _ -> []
+		in
+		loop cl
+
 	let string_error_raise s sl msg =
 		if sl = [] then msg else
 		let cl = List.map (fun s2 -> s2,levenshtein s s2) sl in
 		let cl = List.sort (fun (_,c1) (_,c2) -> compare c1 c2) cl in
-		let rec loop sl = match sl with
-			| (s2,i) :: sl when i <= (min (String.length s) (String.length s2)) / 3 -> s2 :: loop sl
-			| _ -> []
-		in
-		match loop cl with
+		let cl = filter_similar (fun s2 i -> i <= (min (String.length s) (String.length s2)) / 3) cl in
+		match cl with
 			| [] -> raise Not_found
 			| [s] -> Printf.sprintf "%s (Suggestion: %s)" msg s
 			| sl -> Printf.sprintf "%s (Suggestions: %s)" msg (String.concat ", " sl)

+ 15 - 11
src/typing/typer.ml

@@ -366,20 +366,24 @@ let parse_expr_string ctx s p inl =
 	| _,[EClass { d_data = [{ cff_name = "main",null_pos; cff_kind = FFun { f_expr = Some e } }]},_] -> if inl then e else loop e
 	| _ -> raise Interp.Invalid_expr
 
-let collect_toplevel_identifiers ctx =
+
+module ToplevelCollecter = struct
+	open IdentifierType
+
+	let run ctx =
 	let acc = DynArray.create () in
 
 	(* locals *)
 	PMap.iter (fun _ v ->
 		if not (is_gen_local v) then
-			DynArray.add acc (Display.ITLocal v)
+				DynArray.add acc (ITLocal v)
 	) ctx.locals;
 
 	(* member vars *)
 	if ctx.curfun <> FunStatic then begin
 		let rec loop c =
 			List.iter (fun cf ->
-				DynArray.add acc (Display.ITMember(ctx.curclass,cf))
+					DynArray.add acc (ITMember(ctx.curclass,cf))
 			) c.cl_ordered_fields;
 			match c.cl_super with
 				| None ->
@@ -393,7 +397,7 @@ let collect_toplevel_identifiers ctx =
 
 	(* statics *)
 	List.iter (fun cf ->
-		DynArray.add acc (Display.ITStatic(ctx.curclass,cf))
+			DynArray.add acc (ITStatic(ctx.curclass,cf))
 	) ctx.curclass.cl_ordered_statics;
 
 	(* enum constructors *)
@@ -408,7 +412,7 @@ let collect_toplevel_identifiers ctx =
 			end
 		| TEnumDecl e ->
 			PMap.iter (fun _ ef ->
-				DynArray.add acc (Display.ITEnum(e,ef))
+					DynArray.add acc (ITEnum(e,ef))
 			) e.e_constrs;
 	in
 	List.iter enum_ctors ctx.m.curmod.m_types;
@@ -423,7 +427,7 @@ let collect_toplevel_identifiers ctx =
 				| TAbstractDecl {a_impl = Some c} -> (PMap.find s c.cl_statics).cf_type
 				| _ -> raise Not_found
 			in
-			DynArray.add acc (Display.ITGlobal(mt,s,t))
+				DynArray.add acc (ITGlobal(mt,s,t))
 		with Not_found ->
 			()
 	) ctx.m.module_globals;
@@ -495,14 +499,14 @@ let collect_toplevel_identifiers ctx =
 	) class_paths;
 
 	List.iter (fun pack ->
-		DynArray.add acc (Display.ITPackage pack)
+			DynArray.add acc (ITPackage pack)
 	) !packages;
 
 	List.iter (fun mt ->
-		DynArray.add acc (Display.ITType mt)
+			DynArray.add acc (ITType mt)
 	) !module_types;
-
-	raise (Display.DisplayToplevel (DynArray.to_list acc))
+		DynArray.to_list acc
+end
 
 (* ---------------------------------------------------------------------- *)
 (* PASS 3 : type expression & check structure *)
@@ -3883,7 +3887,7 @@ and handle_display ctx e_ast iscall with_type =
 		let pl = loop e in
 		raise (Display.DisplayPosition pl);
 	| DMToplevel ->
-		collect_toplevel_identifiers ctx;
+		raise (Display.DisplayToplevel (ToplevelCollecter.run ctx))
 	| DMDefault | DMNone | DMModuleSymbols | DMDiagnostics ->
 		let opt_args args ret = TFun(List.map(fun (n,o,t) -> n,true,t) args,ret) in
 		let e,tl_overloads,doc = match e.eexpr with