Browse Source

Added Ast.mk_type_path to check every type_path creation (#9297)

* Added Ast.mk_type_path to check every type_path creation

* cleanup

* update the test

* fix magic types
Aleksandr Kuzmenko 5 years ago
parent
commit
29152de597

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

@@ -315,7 +315,7 @@ let sort_fields l with_type tk =
 
 let get_import_status ctx path =
 	try
-		let mt' = ctx.g.do_load_type_def ctx null_pos {tpackage = []; tname = snd path; tparams = []; tsub = None} in
+		let mt' = ctx.g.do_load_type_def ctx null_pos (mk_type_path ([],snd path)) in
 		if path <> (t_infos mt').mt_path then Shadowed else Imported
 	with _ ->
 		Unimported

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

@@ -214,7 +214,7 @@ let handle_path_display ctx path p =
 		| (IDKModule(sl,s),p),_ ->
 			raise (Parser.TypePath(sl,None,true,p))
 		| (IDKSubType(sl,sm,st),p),(DMDefinition | DMTypeDefinition) ->
-			resolve_position_by_path ctx { tpackage = sl; tname = sm; tparams = []; tsub = Some st} p
+			resolve_position_by_path ctx (Ast.mk_type_path ~sub:st (sl,sm)) p
 		| (IDKSubType(sl,sm,st),p),_ ->
 			raise (Parser.TypePath(sl,Some(sm,false),true,p))
 		| ((IDKSubTypeField(sl,sm,st,sf) | IDKModuleField(sl,(sm as st),sf)),p),DMDefault ->

+ 5 - 0
src/core/ast.ml

@@ -328,6 +328,11 @@ type type_decl = type_def * pos
 
 type package = string list * type_decl list
 
+let mk_type_path ?(params=[]) ?sub (pack,name) =
+	if name = "" then
+		raise (Invalid_argument "Empty module name is not allowed");
+	{ tpackage = pack; tname = name; tsub = sub; tparams = params; }
+
 let is_lower_ident i =
 	if String.length i = 0 then
 		raise (Invalid_argument "Identifier name must not be empty")

+ 4 - 18
src/core/tOther.ml

@@ -7,18 +7,9 @@ open TPrinting
 module TExprToExpr = struct
 	let tpath p mp pl =
 		if snd mp = snd p then
-			CTPath {
-				tpackage = fst p;
-				tname = snd p;
-				tparams = pl;
-				tsub = None;
-			}
-		else CTPath {
-				tpackage = fst mp;
-				tname = snd mp;
-				tparams = pl;
-				tsub = Some (snd p);
-			}
+			CTPath (mk_type_path ~params:pl p)
+		else
+			CTPath (mk_type_path ~params:pl ~sub:(snd p) mp)
 
 	let rec convert_type = function
 		| TMono r ->
@@ -29,12 +20,7 @@ module TExprToExpr = struct
 		| TEnum ({e_private = true; e_path=_,name},tl)
 		| TType ({t_private = true; t_path=_,name},tl)
 		| TAbstract ({a_private = true; a_path=_,name},tl) ->
-			CTPath {
-				tpackage = [];
-				tname = name;
-				tparams = List.map tparam tl;
-				tsub = None;
-			}
+			CTPath (mk_type_path ~params:(List.map tparam tl) ([],name))
 		| TEnum (e,pl) ->
 			tpath e.e_path e.e_module.m_path (List.map tparam pl)
 		| TInst({cl_kind = KExpr e} as c,pl) ->

+ 4 - 4
src/filters/exceptions.ml

@@ -365,9 +365,9 @@ let filter tctx =
 		let tp (pack,name) =
 			match List.rev pack with
 			| module_name :: pack_rev when not (Ast.is_lower_ident module_name) ->
-				({ tpackage = List.rev pack_rev; tname = module_name; tparams = []; tsub = Some name },null_pos)
+				(mk_type_path ~sub:name (List.rev pack_rev,module_name), null_pos)
 			| _ ->
-				({ tpackage = pack; tname = name; tparams = []; tsub = None },null_pos)
+				(mk_type_path (pack,name), null_pos)
 		in
 		let wildcard_catch_type =
 			let t = Typeload.load_instance tctx (tp config.ec_wildcard_catch) true in
@@ -424,7 +424,7 @@ let insert_save_stacks tctx =
 		(fun e -> e)
 	else
 		let native_stack_trace_cls =
-			let tp = { tpackage = ["haxe"]; tname = "NativeStackTrace"; tparams = []; tsub = None } in
+			let tp = mk_type_path (["haxe"],"NativeStackTrace") in
 			match Typeload.load_type_def tctx null_pos tp with
 			| TClassDecl cls -> cls
 			| TAbstractDecl { a_impl = Some cls } -> cls
@@ -488,7 +488,7 @@ let insert_save_stacks tctx =
 	Adds `this.__shiftStack()` calls to constructors of classes which extend `haxe.Exception`
 *)
 let patch_constructors tctx =
-	let tp = ({ tpackage = fst haxe_exception_type_path; tname = snd haxe_exception_type_path; tparams = []; tsub = None },null_pos) in
+	let tp = (mk_type_path haxe_exception_type_path, null_pos) in
 	match Typeload.load_instance tctx tp true with
 	(* Add only if `__shiftStack` method exists *)
 	| TInst(cls,_) when PMap.mem "__shiftStack" cls.cl_fields ->

+ 5 - 6
src/macro/macroApi.ml

@@ -609,12 +609,11 @@ let decode_opt_array f v =
 
 let rec decode_path t =
 	let p = field t "pos" in
-	{
-		tpackage = List.map decode_string (decode_array (field t "pack"));
-		tname = decode_string (field t "name");
-		tparams = decode_opt_array decode_tparam (field t "params");
-		tsub = opt decode_string (field t "sub");
-	},if p = vnull then Globals.null_pos else decode_pos p
+	let pack = List.map decode_string (decode_array (field t "pack"))
+	and name = decode_string (field t "name")
+	and params = decode_opt_array decode_tparam (field t "params")
+	and sub = opt decode_string (field t "sub") in
+	mk_type_path ~params ?sub (pack,name), if p = vnull then Globals.null_pos else decode_pos p
 
 and decode_tparam v =
 	match decode_enum v with

+ 6 - 14
src/syntax/grammar.mly

@@ -612,12 +612,7 @@ and parse_type_path2 p0 pack name p1 s =
 			| Some p -> punion p p1
 		in
 		if !in_display_file && display_position#enclosed_in p then begin
-			{
-				tpackage = List.rev pack;
-				tname = name;
-				tsub = None;
-				tparams = [];
-			},p
+			mk_type_path (List.rev pack,name), p
 		end else
 			f()
 	in
@@ -650,12 +645,9 @@ and parse_type_path2 p0 pack name p1 s =
 				end
 			| [< >] -> [],p2
 		) in
-		{
-			tpackage = List.rev pack;
-			tname = name;
-			tparams = params;
-			tsub = sub;
-		},punion (match p0 with None -> p1 | Some p -> p) p2
+		let tp = mk_type_path ~params ?sub (List.rev pack,name)
+		and pos = punion (match p0 with None -> p1 | Some p -> p) p2 in
+		tp,pos
 
 and type_name = parser
 	| [< '(Const (Ident name),p); s >] ->
@@ -1129,14 +1121,14 @@ and parse_macro_expr p = parser
 	| [< '(DblDot,_); t = parse_complex_type >] ->
 		let _, to_type, _  = reify !in_macro in
 		let t = to_type t p in
-		(ECheckType (t,(CTPath { tpackage = ["haxe";"macro"]; tname = "Expr"; tsub = Some "ComplexType"; tparams = [] },null_pos)),p)
+		(ECheckType (t,(CTPath (mk_type_path ~sub:"ComplexType" (["haxe";"macro"],"Expr")),null_pos)),p)
 	| [< '(Kwd Var,p1); vl = psep Comma (parse_var_decl false) >] ->
 		reify_expr (EVars vl,p1) !in_macro
 	| [< '(Kwd Final,p1); vl = psep Comma (parse_var_decl true) >] ->
 		reify_expr (EVars vl,p1) !in_macro
 	| [< d = parse_class None [] [] false >] ->
 		let _,_,to_type = reify !in_macro in
-		(ECheckType (to_type d,(CTPath { tpackage = ["haxe";"macro"]; tname = "Expr"; tsub = Some "TypeDefinition"; tparams = [] },null_pos)),p)
+		(ECheckType (to_type d,(CTPath (mk_type_path ~sub:"TypeDefinition" (["haxe";"macro"],"Expr")),null_pos)),p)
 	| [< e = secure_expr >] ->
 		reify_expr e !in_macro
 

+ 1 - 1
src/syntax/reification.ml

@@ -395,4 +395,4 @@ let reify in_macro =
 let reify_expr e in_macro =
 	let to_expr,_,_ = reify in_macro in
 	let e = to_expr e in
-	(ECheckType (e,(CTPath { tpackage = ["haxe";"macro"]; tname = "Expr"; tsub = None; tparams = [] },null_pos)),pos e)
+	(ECheckType (e,(CTPath (mk_type_path (["haxe";"macro"],"Expr")),null_pos)),pos e)

+ 1 - 1
src/typing/finalization.ml

@@ -13,7 +13,7 @@ let get_main ctx types =
 	match ctx.com.main_class with
 	| None -> None
 	| Some cl ->
-		let t = Typeload.load_type_def ctx null_pos { tpackage = fst cl; tname = snd cl; tparams = []; tsub = None } in
+		let t = Typeload.load_type_def ctx null_pos (mk_type_path cl) in
 		let fmode, ft, r = (match t with
 		| TEnumDecl _ | TTypeDecl _ | TAbstractDecl _ ->
 			error ("Invalid -main : " ^ s_type_path cl ^ " is not a class") null_pos

+ 2 - 2
src/typing/generic.ml

@@ -150,7 +150,7 @@ let static_method_container gctx c cf p =
 	let pack = fst c.cl_path in
 	let name = (snd c.cl_path) ^ "_" ^ cf.cf_name ^ "_" ^ gctx.name in
 	try
-		let t = Typeload.load_instance ctx ({ tpackage = pack; tname = name; tparams = []; tsub = None },p) true in
+		let t = Typeload.load_instance ctx (mk_type_path (pack,name),p) true in
 		match t with
 		| TInst(cg,_) -> cg
 		| _ -> error ("Cannot specialize @:generic static method because the generated type name is already used: " ^ name) p
@@ -193,7 +193,7 @@ let rec build_generic ctx c p tl =
 	let gctx = make_generic ctx c.cl_params tl p in
 	let name = (snd c.cl_path) ^ "_" ^ gctx.name in
 	try
-		let t = Typeload.load_instance ctx ({ tpackage = pack; tname = name; tparams = []; tsub = None },p) false in
+		let t = Typeload.load_instance ctx (mk_type_path (pack,name),p) false in
 		match t with
 		| TInst({ cl_kind = KGenericInstance (csup,_) },_) when c == csup -> t
 		| _ -> error ("Cannot specialize @:generic because the generated type name is already used: " ^ name) p

+ 9 - 8
src/typing/macroContext.ml

@@ -152,9 +152,9 @@ let make_macro_api ctx p =
 				let path = parse_path s in
 				let tp = match List.rev (fst path) with
 					| s :: sl when String.length s > 0 && (match s.[0] with 'A'..'Z' -> true | _ -> false) ->
-						{ tpackage = List.rev sl; tname = s; tparams = []; tsub = Some (snd path) }
+						mk_type_path ~sub:(snd path) (List.rev sl,s)
 					| _ ->
-						{ tpackage = fst path; tname = snd path; tparams = []; tsub = None }
+						mk_type_path path
 				in
 				try
 					let m = Some (Typeload.load_instance ctx (tp,p) true) in
@@ -299,7 +299,7 @@ let make_macro_api ctx p =
 			| Some (_,_,fields) -> Interp.encode_array (List.map Interp.encode_field fields)
 		);
 		MacroApi.define_type = (fun v mdep ->
-			let cttype = { tpackage = ["haxe";"macro"]; tname = "Expr"; tparams = []; tsub = Some ("TypeDefinition") } in
+			let cttype = mk_type_path ~sub:"TypeDefinition" (["haxe";"macro"],"Expr") in
 			let mctx = (match ctx.g.macros with None -> assert false | Some (_,mctx) -> mctx) in
 			let ttype = Typeload.load_instance mctx (cttype,p) false in
 			let f () = Interp.decode_type_def v in
@@ -526,7 +526,7 @@ let load_macro' ctx display cpath f p =
 	let (meth,mloaded) = try Hashtbl.find mctx.com.cached_macros (cpath,f) with Not_found ->
 		let t = macro_timer ctx ["typing";s_type_path cpath ^ "." ^ f] in
 		let mloaded,restore = load_macro_module ctx mpath display p in
-		let mt = Typeload.load_type_def mctx p { tpackage = fst mpath; tname = snd mpath; tparams = []; tsub = sub } in
+		let mt = Typeload.load_type_def mctx p (mk_type_path ?sub mpath) in
 		let cl, meth = (match mt with
 			| TClassDecl c ->
 				mctx.g.do_finalize mctx;
@@ -576,7 +576,7 @@ type macro_arg_type =
 let type_macro ctx mode cpath f (el:Ast.expr list) p =
 	let mctx, (margs,mret,mclass,mfield), call_macro = load_macro ctx (mode = MDisplay) cpath f p in
 	let mpos = mfield.cf_pos in
-	let ctexpr = { tpackage = ["haxe";"macro"]; tname = "Expr"; tparams = []; tsub = None } in
+	let ctexpr = mk_type_path (["haxe";"macro"],"Expr") in
 	let expr = Typeload.load_instance mctx (ctexpr,p) false in
 	(match mode with
 	| MDisplay ->
@@ -584,18 +584,19 @@ let type_macro ctx mode cpath f (el:Ast.expr list) p =
 	| MExpr ->
 		unify mctx mret expr mpos;
 	| MBuild ->
-		let ctfields = { tpackage = []; tname = "Array"; tparams = [TPType (CTPath { tpackage = ["haxe";"macro"]; tname = "Expr"; tparams = []; tsub = Some "Field" },null_pos)]; tsub = None } in
+		let params = [TPType (CTPath (mk_type_path ~sub:"Field" (["haxe";"macro"],"Expr")),null_pos)] in
+		let ctfields = mk_type_path ~params ([],"Array") in
 		let tfields = Typeload.load_instance mctx (ctfields,p) false in
 		unify mctx mret tfields mpos
 	| MMacroType ->
-		let cttype = { tpackage = ["haxe";"macro"]; tname = "Type"; tparams = []; tsub = None } in
+		let cttype = mk_type_path (["haxe";"macro"],"Type") in
 		let ttype = Typeload.load_instance mctx (cttype,p) false in
 		try
 			unify_raise mctx mret ttype mpos;
 			(* TODO: enable this again in the future *)
 			(* ctx.com.warning "Returning Type from @:genericBuild macros is deprecated, consider returning ComplexType instead" p; *)
 		with Error (Unify _,_) ->
-			let cttype = { tpackage = ["haxe";"macro"]; tname = "Expr"; tparams = []; tsub = Some ("ComplexType") } in
+			let cttype = mk_type_path ~sub:"ComplexType" (["haxe";"macro"],"Expr") in
 			let ttype = Typeload.load_instance mctx (cttype,p) false in
 			unify_raise mctx mret ttype mpos;
 	);

+ 3 - 3
src/typing/magicTypes.ml

@@ -20,7 +20,7 @@ let extend_remoting ctx c t p async prot =
 	let new_name = (if async then "Async_" else "Remoting_") ^ t.tname in
 	(* check if the proxy already exists *)
 	let t = (try
-		load_type_def ctx p { tpackage = fst path; tname = new_name; tparams = []; tsub = None }
+		load_type_def ctx p (mk_type_path (fst path,new_name))
 	with
 		Error (Module_not_found _,p2) when p == p2 ->
 	(* build it *)
@@ -32,10 +32,10 @@ let extend_remoting ctx c t p async prot =
 		| e -> ctx.com.package_rules <- rules; raise e) in
 	ctx.com.package_rules <- rules;
 	let base_fields = [
-		{ cff_name = "__cnx",null_pos; cff_pos = p; cff_doc = None; cff_meta = []; cff_access = []; cff_kind = FVar (Some (CTPath { tpackage = ["haxe";"remoting"]; tname = if async then "AsyncConnection" else "Connection"; tparams = []; tsub = None },null_pos),None) };
+		{ cff_name = "__cnx",null_pos; cff_pos = p; cff_doc = None; cff_meta = []; cff_access = []; cff_kind = FVar (Some (CTPath (mk_type_path (["haxe";"remoting"],if async then "AsyncConnection" else "Connection")),null_pos),None) };
 		{ cff_name = "new",null_pos; cff_pos = p; cff_doc = None; cff_meta = []; cff_access = [APublic,null_pos]; cff_kind = FFun { f_args = [("c",null_pos),false,[],None,None]; f_type = None; f_expr = Some (EBinop (OpAssign,(EConst (Ident "__cnx"),p),(EConst (Ident "c"),p)),p); f_params = [] } };
 	] in
-	let tvoid = CTPath { tpackage = []; tname = "Void"; tparams = []; tsub = None } in
+	let tvoid = CTPath (mk_type_path ([],"Void")) in
 	let build_field is_public acc f =
 		if fst f.cff_name = "new" then
 			acc

+ 1 - 1
src/typing/matcher.ml

@@ -1451,7 +1451,7 @@ module TexprConverter = struct
 		let v_lookup = ref IntMap.empty in
 		let com = ctx.com in
 		let p = dt.dt_pos in
-		let c_type = match follow (Typeload.load_instance ctx ({ tpackage = ["std"]; tname="Type"; tparams=[]; tsub = None},p) true) with TInst(c,_) -> c | t -> assert false in
+		let c_type = match follow (Typeload.load_instance ctx (mk_type_path (["std"],"Type"),p) true) with TInst(c,_) -> c | t -> assert false in
 		let mk_index_call e =
 			if not ctx.in_macro && not ctx.com.display.DisplayMode.dms_full_typing then
 				(* If we are in display mode there's a chance that these fields don't exist. Let's just use a

+ 9 - 9
src/typing/typeload.ml

@@ -215,8 +215,8 @@ let load_qualified_type_def ctx pack mname tname p =
 	load a type or a subtype definition
 *)
 let load_type_def ctx p t =
-	if t = Parser.magic_type_path then raise_fields (DisplayToplevel.collect ctx TKType NoValue true) CRTypeHint (DisplayTypes.make_subject None p);
-
+	if t = Parser.magic_type_path then
+		raise_fields (DisplayToplevel.collect ctx TKType NoValue true) CRTypeHint (DisplayTypes.make_subject None p);
 	(* The type name is the module name or the module sub-type name *)
 	let tname = (match t.tsub with None -> t.tname | Some n -> n) in
 
@@ -696,7 +696,7 @@ let hide_params ctx =
 *)
 let load_core_type ctx name =
 	let show = hide_params ctx in
-	let t = load_instance ctx ({ tpackage = []; tname = name; tparams = []; tsub = None; },null_pos) false in
+	let t = load_instance ctx (mk_type_path ([],name),null_pos) false in
 	show();
 	add_dependency ctx.m.curmod (match t with
 	| TInst (c,_) -> c.cl_module
@@ -708,7 +708,7 @@ let load_core_type ctx name =
 
 let t_iterator ctx =
 	let show = hide_params ctx in
-	match load_type_def ctx null_pos { tpackage = []; tname = "Iterator"; tparams = []; tsub = None } with
+	match load_type_def ctx null_pos (mk_type_path ([],"Iterator")) with
 	| TTypeDecl t ->
 		show();
 		add_dependency ctx.m.curmod t.t_module;
@@ -828,8 +828,8 @@ let load_core_class ctx c =
 			c
 	) in
 	let tpath = match c.cl_kind with
-		| KAbstractImpl a -> { tpackage = fst a.a_path; tname = snd a.a_path; tparams = []; tsub = None; }
-		| _ -> { tpackage = fst c.cl_path; tname = snd c.cl_path; tparams = []; tsub = None; }
+		| KAbstractImpl a -> mk_type_path a.a_path
+		| _ -> mk_type_path c.cl_path
 	in
 	let t = load_instance ctx2 (tpath,c.cl_pos) true in
 	flush_pass ctx2 PFinal "core_final";
@@ -916,10 +916,10 @@ let string_list_of_expr_path (e,p) =
 let handle_using ctx path p =
 	let t = match List.rev path with
 		| (s1,_) :: (s2,_) :: sl ->
-			if is_lower_ident s2 then { tpackage = (List.rev (s2 :: List.map fst sl)); tname = s1; tsub = None; tparams = [] }
-			else { tpackage = List.rev (List.map fst sl); tname = s2; tsub = Some s1; tparams = [] }
+			if is_lower_ident s2 then mk_type_path ((List.rev (s2 :: List.map fst sl)),s1)
+			else mk_type_path ~sub:s1 (List.rev (List.map fst sl),s2)
 		| (s1,_) :: sl ->
-			{ tpackage = List.rev (List.map fst sl); tname = s1; tsub = None; tparams = [] }
+			mk_type_path (List.rev (List.map fst sl),s1)
 		| [] ->
 			DisplayException.raise_fields (DisplayToplevel.collect ctx TKType NoValue true) CRUsing (DisplayTypes.make_subject None {p with pmin = p.pmax});
 	in

+ 2 - 2
src/typing/typeloadFields.ml

@@ -1057,7 +1057,7 @@ let create_method (ctx,cctx,fctx) c f fd p =
 		if ctx.in_macro then begin
 			(* a class with a macro cannot be extern in macro context (issue #2015) *)
 			c.cl_extern <- false;
-			let texpr = CTPath { tpackage = ["haxe";"macro"]; tname = "Expr"; tparams = []; tsub = None } in
+			let texpr = CTPath (mk_type_path (["haxe";"macro"],"Expr")) in
 			(* ExprOf type parameter might contain platform-specific type, let's replace it by Expr *)
 			let no_expr_of (t,p) = match t with
 				| CTPath { tpackage = ["haxe";"macro"]; tname = "Expr"; tsub = Some ("ExprOf"); tparams = [TPType _] }
@@ -1071,7 +1071,7 @@ let create_method (ctx,cctx,fctx) c f fd p =
 				f_expr = fd.f_expr;
 			}
 		end else
-			let tdyn = Some (CTPath { tpackage = []; tname = "Dynamic"; tparams = []; tsub = None },null_pos) in
+			let tdyn = Some (CTPath (mk_type_path ([],"Dynamic")),null_pos) in
 			let to_dyn p t = match t with
 				| { tpackage = ["haxe";"macro"]; tname = "Expr"; tsub = Some ("ExprOf"); tparams = [TPType t] } -> Some t
 				| { tpackage = []; tname = ("ExprOf"); tsub = None; tparams = [TPType t] } -> Some t

+ 3 - 3
src/typing/typeloadModule.ml

@@ -319,8 +319,8 @@ let module_pass_1 ctx m tdecls loadp =
 				acc
 			| fields ->
 				let a_t =
-					let params = List.map (fun t -> TPType (CTPath { tname = fst t.tp_name; tparams = []; tsub = None; tpackage = [] },null_pos)) d.d_params in
-					CTPath { tpackage = []; tname = fst d.d_name; tparams = params; tsub = None },null_pos
+					let params = List.map (fun t -> TPType (CTPath (mk_type_path ([],fst t.tp_name)),null_pos)) d.d_params in
+					CTPath (mk_type_path ~params ([],fst d.d_name)),null_pos
 				in
 				let rec loop = function
 					| [] -> a_t
@@ -949,7 +949,7 @@ let type_module ctx mpath file ?(dont_check_path=false) ?(is_extern=false) tdecl
 	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;
 	begin if ctx.is_display_file then match ctx.com.display.dms_kind with
 		| DMResolve s ->
-			DisplayPath.resolve_position_by_path ctx {tname = s; tpackage = []; tsub = None; tparams = []} p
+			DisplayPath.resolve_position_by_path ctx (mk_type_path ([],s)) p
 		| _ ->
 			()
 	end;

+ 14 - 9
src/typing/typeloadParse.ml

@@ -316,15 +316,20 @@ let parse_module ctx m p =
 					d_meta = [];
 					d_params = d.d_params;
 					d_flags = if priv then [EPrivate] else [];
-					d_data = CTPath (if priv then { tpackage = []; tname = "Dynamic"; tparams = []; tsub = None; } else
-						{
-							tpackage = !remap;
-							tname = fst d.d_name;
-							tparams = List.map (fun tp ->
-								TPType (CTPath { tpackage = []; tname = fst tp.tp_name; tparams = []; tsub = None; },null_pos)
-							) d.d_params;
-							tsub = None;
-						}),null_pos;
+					d_data = begin
+						let tp =
+							if priv then
+								mk_type_path ([],"Dynamic")
+							else
+								let params =
+									List.map (fun tp ->
+										TPType (CTPath (mk_type_path ([],fst tp.tp_name)),null_pos)
+									) d.d_params
+								in
+								mk_type_path ~params (!remap,fst d.d_name)
+						in
+						CTPath (tp),null_pos;
+					end
 				},p) :: acc
 			in
 			match t with

+ 2 - 2
src/typing/typerBase.ml

@@ -111,7 +111,7 @@ let rec type_module_type ctx t tparams p =
 		let mt = try
 			module_type_of_type t
 		with Exit ->
-			if follow t == t_dynamic then Typeload.load_type_def ctx p { tpackage = []; tname = "Dynamic"; tparams = []; tsub = None }
+			if follow t == t_dynamic then Typeload.load_type_def ctx p (mk_type_path ([],"Dynamic"))
 			else error "Invalid module type" p
 		in
 		type_module_type ctx mt None p
@@ -141,7 +141,7 @@ let rec type_module_type ctx t tparams p =
 		mk (TTypeExpr (TAbstractDecl a)) (TType (t_tmp,[])) p
 
 let type_type ctx tpath p =
-	type_module_type ctx (Typeload.load_type_def ctx p { tpackage = fst tpath; tname = snd tpath; tparams = []; tsub = None }) None p
+	type_module_type ctx (Typeload.load_type_def ctx p (mk_type_path tpath)) None p
 
 let mk_module_type_access ctx t p : access_mode -> access_kind =
 	let e = type_module_type ctx t None p in

+ 16 - 0
tests/misc/projects/Issue9294/Main.hx

@@ -0,0 +1,16 @@
+import haxe.macro.Context;
+
+class Main {
+	static function main() {
+		test();
+	}
+
+	macro static public function test() {
+		try {
+			Context.getType("");
+		} catch(e:Dynamic) {
+			Context.error(Std.string(e), Context.currentPos());
+		}
+		return macro {};
+	}
+}

+ 1 - 0
tests/misc/projects/Issue9294/compile-fail.hxml

@@ -0,0 +1 @@
+-main Main

+ 1 - 0
tests/misc/projects/Issue9294/compile-fail.hxml.stderr

@@ -0,0 +1 @@
+Main.hx:5: characters 3-9 : Empty module name is not allowed