Browse Source

[typer] move lookups from g to com

Simon Krajewski 3 years ago
parent
commit
3d84f2071c

+ 5 - 5
src/compiler/compiler.ml

@@ -158,13 +158,13 @@ let load_display_module_in_macro tctx display_file_dot_path clear = match displa
 				display mode. This covers some cases like --macro typing it in non-display mode (issue #7017). *)
 			if clear then begin
 				begin try
-					let m = Hashtbl.find mctx.g.modules cpath in
-					Hashtbl.remove mctx.g.modules cpath;
-					Hashtbl.remove mctx.g.types_module cpath;
+					let m = Hashtbl.find mctx.com.module_lut cpath in
+					Hashtbl.remove mctx.com.module_lut cpath;
+					Hashtbl.remove mctx.com.type_to_module cpath;
 					List.iter (fun mt ->
 						let ti = t_infos mt in
-						Hashtbl.remove mctx.g.modules ti.mt_path;
-						Hashtbl.remove mctx.g.types_module ti.mt_path;
+						Hashtbl.remove mctx.com.module_lut ti.mt_path;
+						Hashtbl.remove mctx.com.type_to_module ti.mt_path;
 					) m.m_types
 				with Not_found ->
 					()

+ 6 - 0
src/context/common.ml

@@ -339,6 +339,8 @@ type context = {
 	mutable flash_version : float;
 	mutable features : (string,bool) Hashtbl.t;
 	mutable modules : Type.module_def list;
+	module_lut : (path , module_def) Hashtbl.t;
+	type_to_module : (path, path) Hashtbl.t;
 	mutable main : Type.texpr option;
 	mutable types : Type.module_type list;
 	mutable resources : (string,string) Hashtbl.t;
@@ -745,6 +747,8 @@ let create compilation_step cs version args =
 		types = [];
 		callbacks = new compiler_callbacks;
 		modules = [];
+		module_lut = Hashtbl.create 0;
+		type_to_module = Hashtbl.create 0;
 		main = None;
 		flash_version = 10.;
 		resources = Hashtbl.create 0;
@@ -828,6 +832,8 @@ let clone com is_macro_context =
 		native_libs = create_native_libs();
 		overload_cache = Hashtbl.create 0;
 		is_macro_context = is_macro_context;
+		module_lut = Hashtbl.create 0;
+		type_to_module = Hashtbl.create 0;
 	}
 
 let file_time file = Extc.filetime file

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

@@ -28,7 +28,7 @@ open DisplayTypes
 open Display
 
 let get_submodule_fields ctx path =
-	let m = Hashtbl.find ctx.g.modules path in
+	let m = Hashtbl.find ctx.com.module_lut 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 ->
 		make_ci_type (CompletionItem.CompletionModuleType.of_module_type mt) ImportStatus.Imported None

+ 1 - 3
src/context/typecore.ml

@@ -68,8 +68,6 @@ type typer_module = {
 }
 
 type typer_globals = {
-	types_module : (path, path) Hashtbl.t;
-	modules : (path , module_def) Hashtbl.t;
 	mutable delayed : (typer_pass * (unit -> unit) list) list;
 	mutable debug_delayed : (typer_pass * ((unit -> unit) * string * typer) list) list;
 	doinline : bool;
@@ -441,7 +439,7 @@ let create_fake_module ctx file =
 		Hashtbl.add fake_modules key mdep;
 		mdep
 	) in
-	Hashtbl.replace ctx.g.modules mdep.m_path mdep;
+	Hashtbl.replace ctx.com.module_lut mdep.m_path mdep;
 	mdep
 
 let push_this ctx e = match e.eexpr with

+ 1 - 1
src/filters/filters.ml

@@ -380,7 +380,7 @@ let remove_extern_fields com t = match t with
 let check_private_path ctx t = match t with
 	| TClassDecl c when c.cl_private ->
 		let rpath = (fst c.cl_module.m_path,"_" ^ snd c.cl_module.m_path) in
-		if Hashtbl.mem ctx.g.types_module rpath then typing_error ("This private class name will clash with " ^ s_type_path rpath) c.cl_pos;
+		if Hashtbl.mem ctx.com.type_to_module rpath then typing_error ("This private class name will clash with " ^ s_type_path rpath) c.cl_pos;
 	| _ ->
 		()
 

+ 1 - 1
src/optimization/inline.ml

@@ -112,7 +112,7 @@ let api_inline2 com c field params p =
 
 let api_inline ctx c field params p =
 	let mk_typeexpr path =
-		let m = (try Hashtbl.find ctx.g.modules path with Not_found -> die "" __LOC__) in
+		let m = (try Hashtbl.find ctx.com.module_lut path with Not_found -> die "" __LOC__) in
 		add_dependency ctx.m.curmod m;
 		Option.get (ExtList.List.find_map (function
 			| TClassDecl cl when cl.cl_path = path -> Some (make_static_this cl p)

+ 2 - 2
src/typing/finalization.ml

@@ -86,7 +86,7 @@ let finalize ctx =
 			()
 		| fl ->
 			let rec loop handled_types =
-				let all_types = Hashtbl.fold (fun _ m acc -> m.m_types @ acc) ctx.g.modules [] in
+				let all_types = Hashtbl.fold (fun _ m acc -> m.m_types @ acc) ctx.com.module_lut [] in
 				match (List.filter (fun mt -> not (List.memq mt handled_types)) all_types) with
 				| [] ->
 					()
@@ -198,5 +198,5 @@ let sort_types com modules =
 	List.rev !types, sorted_modules
 
 let generate ctx =
-	let types,modules = sort_types ctx.com ctx.g.modules in
+	let types,modules = sort_types ctx.com ctx.com.module_lut in
 	get_main ctx types,types,modules

+ 4 - 4
src/typing/generic.ml

@@ -157,7 +157,7 @@ let static_method_container gctx c cf p =
 		| TInst(cg,_) -> cg
 		| _ -> typing_error ("Cannot specialize @:generic static method because the generated type name is already used: " ^ name) p
 	with Error(Module_not_found path,_) when path = (pack,name) ->
-		let m = (try Hashtbl.find ctx.g.modules (Hashtbl.find ctx.g.types_module c.cl_path) with Not_found -> die "" __LOC__) in
+		let m = (try Hashtbl.find ctx.com.module_lut (Hashtbl.find ctx.com.type_to_module c.cl_path) with Not_found -> die "" __LOC__) in
 		let mg = {
 			m_id = alloc_mid();
 			m_path = (pack,name);
@@ -168,7 +168,7 @@ let static_method_container gctx c cf p =
 		gctx.mg <- Some mg;
 		let cg = mk_class mg (pack,name) c.cl_pos c.cl_name_pos in
 		mg.m_types <- [TClassDecl cg];
-		Hashtbl.add ctx.g.modules mg.m_path mg;
+		Hashtbl.add ctx.com.module_lut mg.m_path mg;
 		add_dependency mg m;
 		add_dependency ctx.m.curmod mg;
 		cg
@@ -232,7 +232,7 @@ let rec build_generic_class ctx c p tl =
 		| TInst({ cl_kind = KGenericInstance (csup,_) },_) when c == csup -> t
 		| _ -> typing_error ("Cannot specialize @:generic because the generated type name is already used: " ^ name) p
 	with Error(Module_not_found path,_) when path = (pack,name) ->
-		let m = (try Hashtbl.find ctx.g.modules (Hashtbl.find ctx.g.types_module c.cl_path) with Not_found -> die "" __LOC__) in
+		let m = (try Hashtbl.find ctx.com.module_lut (Hashtbl.find ctx.com.type_to_module c.cl_path) with Not_found -> die "" __LOC__) in
 		ignore(c.cl_build()); (* make sure the super class is already setup *)
 		let mg = {
 			m_id = alloc_mid();
@@ -259,7 +259,7 @@ let rec build_generic_class ctx c p tl =
 		) c.cl_meta;
 		cg.cl_meta <- (Meta.NoDoc,[],null_pos) :: cg.cl_meta;
 		mg.m_types <- [TClassDecl cg];
-		Hashtbl.add ctx.g.modules mg.m_path mg;
+		Hashtbl.add ctx.com.module_lut mg.m_path mg;
 		add_dependency mg m;
 		add_dependency ctx.m.curmod mg;
 		set_type_parameter_dependencies mg tl;

+ 3 - 3
src/typing/macroContext.ml

@@ -318,7 +318,7 @@ let make_macro_api ctx p =
 			let types = imports @ usings @ types in
 			let mpath = Ast.parse_path m in
 			begin try
-				let m = Hashtbl.find ctx.g.modules mpath in
+				let m = Hashtbl.find ctx.com.module_lut mpath in
 				ignore(TypeloadModule.type_types_into_module ctx m types pos)
 			with Not_found ->
 				let mnew = TypeloadModule.type_module ctx mpath (Path.UniqueKey.lazy_path ctx.m.curmod.m_extra.m_file) types pos in
@@ -364,7 +364,7 @@ let make_macro_api ctx p =
 		MacroApi.add_module_check_policy = (fun sl il b i ->
 			let add ctx =
 				ctx.g.module_check_policies <- (List.fold_left (fun acc s -> (ExtString.String.nsplit s ".",List.map Obj.magic il,b) :: acc) ctx.g.module_check_policies sl);
-				Hashtbl.iter (fun _ m -> m.m_extra.m_check_policy <- TypeloadModule.get_policy ctx.g m.m_path) ctx.g.modules;
+				Hashtbl.iter (fun _ m -> m.m_extra.m_check_policy <- TypeloadModule.get_policy ctx.g m.m_path) ctx.com.module_lut;
 			in
 			let add_macro ctx = match ctx.g.macros with
 				| None -> ()
@@ -526,7 +526,7 @@ let get_macro_context ctx p =
 
 let load_macro_module ctx cpath display p =
 	let api, mctx = get_macro_context ctx p in
-	let m = (try Hashtbl.find ctx.g.types_module cpath with Not_found -> cpath) in
+	let m = (try Hashtbl.find ctx.com.type_to_module cpath with Not_found -> cpath) in
 	(* Temporarily enter display mode while typing the macro. *)
 	let old = mctx.com.display in
 	if display then mctx.com.display <- ctx.com.display;

+ 2 - 2
src/typing/typeloadCheck.ml

@@ -323,12 +323,12 @@ let check_global_metadata ctx meta f_add mpath tpath so =
 let check_module_types ctx m p t =
 	let t = t_infos t in
 	try
-		let m2 = Hashtbl.find ctx.g.types_module t.mt_path in
+		let m2 = Hashtbl.find ctx.com.type_to_module t.mt_path in
 		if m.m_path <> m2 && String.lowercase (s_type_path m2) = String.lowercase (s_type_path m.m_path) then typing_error ("Module " ^ s_type_path m2 ^ " is loaded with a different case than " ^ s_type_path m.m_path) p;
 		typing_error ("Type name " ^ s_type_path t.mt_path ^ " is redefined from module " ^ s_type_path m2) p
 	with
 		Not_found ->
-			Hashtbl.add ctx.g.types_module t.mt_path m.m_path
+			Hashtbl.add ctx.com.type_to_module t.mt_path m.m_path
 
 module Inheritance = struct
 	let is_basic_class_path path = match path with

+ 1 - 1
src/typing/typeloadFields.ml

@@ -681,7 +681,7 @@ let transform_field (ctx,cctx) c f fields p =
 	in
 	if List.mem_assoc AMacro f.cff_access then
 		(match ctx.g.macros with
-		| Some (_,mctx) when Hashtbl.mem mctx.g.types_module c.cl_path ->
+		| Some (_,mctx) when Hashtbl.mem mctx.com.type_to_module c.cl_path ->
 			(* assume that if we had already a macro with the same name, it has not been changed during the @:build operation *)
 			if not (List.exists (fun f2 -> f2.cff_name = f.cff_name && List.mem_assoc AMacro f2.cff_access) (!fields)) then
 				typing_error "Class build macro cannot return a macro function when the class has already been compiled into the macro context" p

+ 4 - 4
src/typing/typeloadModule.ml

@@ -57,7 +57,7 @@ module ModuleLevel = struct
 
 	let add_module ctx m p =
 		List.iter (TypeloadCheck.check_module_types ctx m p) m.m_types;
-		Hashtbl.add ctx.g.modules m.m_path m
+		Hashtbl.add ctx.com.module_lut m.m_path m
 
 	(*
 		Build module structure : should be atomic - no type loading is possible
@@ -293,7 +293,7 @@ module ModuleLevel = struct
 		List.fold_left (fun acc path ->
 			let decls = try
 				let r = Hashtbl.find com.parser_cache path in
-				let mimport = Hashtbl.find ctx.g.modules ([],path) in
+				let mimport = Hashtbl.find com.module_lut ([],path) in
 				if mimport.m_extra.m_kind <> MFake then add_dependency m mimport;
 				r
 			with Not_found ->
@@ -757,7 +757,7 @@ let type_types_into_module ?(check=true) ctx m tdecls p =
 *)
 let type_module ctx mpath file ?(dont_check_path=false) ?(is_extern=false) tdecls p =
 	let m = ModuleLevel.make_module ctx mpath file p in
-	Hashtbl.add ctx.g.modules m.m_path m;
+	Hashtbl.add ctx.com.module_lut m.m_path m;
 	let tdecls = ModuleLevel.handle_import_hx ctx m tdecls p in
 	let ctx = type_types_into_module ctx m tdecls p in
 	if is_extern then m.m_extra.m_kind <- MExtern else if not dont_check_path then Typecore.check_module_path ctx m.m_path p;
@@ -771,7 +771,7 @@ let type_module_hook = ref (fun _ _ _ -> None)
 
 let load_module' ctx g m p =
 	try
-		Hashtbl.find ctx.g.modules m
+		Hashtbl.find ctx.com.module_lut m
 	with
 		Not_found ->
 			match !type_module_hook ctx m p with

+ 1 - 3
src/typing/typer.ml

@@ -516,7 +516,7 @@ and handle_efield ctx e p0 mode with_type =
 							in
 							let pack,name,sub,p = loop [] None path in
 							let mpath = (pack,name) in
-							if Hashtbl.mem ctx.g.modules mpath then
+							if Hashtbl.mem ctx.com.module_lut mpath then
 								let tname = Option.default name sub in
 								raise (Error (Type_not_found (mpath,tname,Not_defined),p))
 							else
@@ -1949,8 +1949,6 @@ let rec create com =
 		g = {
 			core_api = None;
 			macros = None;
-			modules = Hashtbl.create 0;
-			types_module = Hashtbl.create 0;
 			type_patches = Hashtbl.create 0;
 			global_metadata = [];
 			module_check_policies = [];