Parcourir la source

Disallow macro-in-macro (#7496)

* curious

* throw instead

* cleanup

* fence Compiler.getDefine

* nope...
Simon Krajewski il y a 6 ans
Parent
commit
00a3cb2b14

+ 1 - 1
src/compiler/serverMessage.ml

@@ -81,7 +81,7 @@ let module_path_changed com tabs (m,time,file) =
 		(sign_string com) (s_type_path m.m_path) m.m_extra.m_time m.m_extra.m_file time file)
 
 let not_cached com tabs m =
-	if config.print_not_cached then print_endline (Printf.sprintf "%s%s not cached (%s)" (sign_string com) (s_type_path m.m_path) (if m.m_extra.m_time = -1. then "macro-in-macro" else "modified"))
+	if config.print_not_cached then print_endline (Printf.sprintf "%s%s not cached (%s)" (sign_string com) (s_type_path m.m_path) "modified")
 
 let parsed com tabs (ffile,info) =
 	if config.print_parsed then print_endline (Printf.sprintf "%sparsed %s (%s)" (sign_string com) ffile info)

+ 0 - 1
src/context/typecore.ml

@@ -75,7 +75,6 @@ type typer_globals = {
 	mutable global_metadata : (string list * metadata_entry * (bool * bool * bool)) list;
 	mutable module_check_policies : (string list * module_check_policy list * bool) list;
 	mutable get_build_infos : unit -> (module_type * t list * class_field list) option;
-	delayed_macros : (unit -> unit) DynArray.t;
 	mutable global_using : (tclass * pos) list;
 	(* api *)
 	do_inherit : typer -> Type.tclass -> pos -> (bool * placed_type_path) -> bool;

+ 0 - 2
src/core/define.ml

@@ -62,7 +62,6 @@ type strict_defined =
 	| LuaVer
 	| LuaJit
 	| Macro
-	| MacroDebug
 	| MacroTimes
 	| NekoSource
 	| NekoV1
@@ -175,7 +174,6 @@ let infos = function
 	| LuaJit -> "lua_jit",("Enable the jit compiler for lua (version 5.2 only)",[Platform Lua])
 	| LuaVer -> "lua_ver",("The lua version to target",[Platform Lua])
 	| Macro -> "macro",("Defined when code is compiled in the macro context",[])
-	| MacroDebug -> "macro_debug",("Show warnings for potential macro problems (e.g. macro-in-macro calls)",[])
 	| MacroTimes -> "macro_times",("Display per-macro timing when used with --times",[])
 	| NetVer -> "net_ver",("<version:20-45> Sets the .NET version to be targeted",[Platform Cs])
 	| NetTarget -> "net_target",("<name> Sets the .NET target. Defaults to \"net\". xbox, micro (Micro Framework), compact (Compact Framework) are some valid values",[Platform Cs])

+ 0 - 2
src/macro/eval/evalContext.ml

@@ -41,7 +41,6 @@ type scope = {
 type env_kind =
 	| EKLocalFunction of int
 	| EKMethod of int * int
-	| EKDelayed
 
 (* Compile-time information for environments. This information is static for all
    environments of the same kind, e.g. all environments of a specific method. *)
@@ -217,7 +216,6 @@ let rec kind_name ctx kind =
 			let env = DynArray.get ctx.environments parent_id in
 			Printf.sprintf "%s.localFunction%i" (loop env.env_info.kind parent_id) i
 		| EKMethod(i1,i2),_ -> Printf.sprintf "%s.%s" (rev_hash i1) (rev_hash i2)
-		| EKDelayed,_ -> "delayed"
 	in
 	loop kind ctx.environment_offset
 

+ 0 - 6
src/macro/eval/evalJit.ml

@@ -442,12 +442,6 @@ and jit_expr jit return e =
 				let exec2 = jit_expr jit false min in
 				let exec3 = jit_expr jit false max in
 				emit_mk_pos exec1 exec2 exec3
-			| TIdent "$__delayed_call__",[{eexpr = TConst(TInt i)}] ->
-				let f = ctx.curapi.MacroApi.delayed_macro (Int32.to_int i) in
-				(fun env ->
-					let f = f() in
-					f()
-				)
 			| _ ->
 				let exec = jit_expr jit false e1 in
 				let execs = List.map (jit_expr jit false) el in

+ 0 - 9
src/macro/eval/evalMain.ml

@@ -139,15 +139,6 @@ let create com api is_macro =
 
 (* API for macroContext.ml *)
 
-let eval_delayed ctx e =
-	let jit,f = jit_expr ctx e in
-	let info = create_env_info true (file_hash e.epos.pfile) EKDelayed jit.capture_infos in
-	fun () ->
-		let env = push_environment ctx info jit.max_num_locals (Hashtbl.length jit.captures) in
-		match catch_exceptions ctx (fun () -> Std.finally (fun _ -> pop_environment ctx env) f env) e.epos with
-			| Some v -> v
-			| None -> vnull
-
 let call_path ctx path f vl api =
 	if ctx.had_error then
 		None

+ 0 - 2
src/macro/eval/evalStdLib.ml

@@ -543,8 +543,6 @@ module StdCallStack = struct
 			| EKMethod(st,sf) ->
 				let local_function = encode_enum_value key_haxe_StackItem 3 [|create_unknown (rev_hash st); create_unknown (rev_hash sf)|] None in
 				DynArray.add l (file_pos local_function);
-			| EKDelayed ->
-				()
 		) envs;
 		encode_array (DynArray.to_list l)
 

+ 0 - 1
src/macro/macroApi.ml

@@ -43,7 +43,6 @@ type 'value compiler_api = {
 	current_module : unit -> module_def;
 	on_reuse : (unit -> bool) -> unit;
 	mutable current_macro_module : unit -> module_def;
-	delayed_macro : int -> (unit -> (unit -> 'value));
 	use_cache : unit -> bool;
 	format_string : string -> Globals.pos -> Ast.expr;
 	cast_or_unify : Type.t -> texpr -> Globals.pos -> bool;

+ 11 - 19
src/optimization/inline.ml

@@ -531,7 +531,6 @@ let rec type_inline ctx cf f ethis params tret config p ?(self_calling_closure=f
 		| Some e -> Some (f e)
 	in
 	let in_loop = ref false in
-	let cancel_inlining = ref false in
 	let return_type t el =
 		(* If the function return is Dynamic or Void, stick to it. *)
 		if follow f.tf_type == t_dynamic || ExtType.is_void (follow f.tf_type) then f.tf_type
@@ -551,9 +550,6 @@ let rec type_inline ctx cf f ethis params tret config p ?(self_calling_closure=f
 				l.i_called <- l.i_called + i
 			else
 				l.i_read <- l.i_read + i;
-			(* never inline a function which contain a delayed macro because its bound
-				to its variables and not the calling method *)
-			if v.v_name = "$__delayed_call__" then cancel_inlining := true;
 			let e = { e with eexpr = TLocal l.i_subst } in
 			if l.i_abstract_this then mk (TCast(e,None)) v.v_type e.epos else e
 		| TConst TThis ->
@@ -705,22 +701,18 @@ let rec type_inline ctx cf f ethis params tret config p ?(self_calling_closure=f
 			Type.map_expr (map false false) e
 	in
 	let e = map true false f.tf_expr in
-	if !cancel_inlining then
-		None
-	else begin
 	let tl = List.map (fun e -> "",false,e.etype) params in
-		let e = state#finalize config e tl tret p 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"
-				cf.cf_name
-				(String.concat "" (List.map (fun (i,e) -> Printf.sprintf "\n\t\t%s<%i> = %s" (i.i_subst.v_name) (i.i_subst.v_id) (se "\t\t" e)) state#inlined_vars))
-				(se "\t" f.tf_expr)
-				(se "\t" e)
-			);
-		end;
-		Some e
-	end
+	let e = state#finalize config e tl tret p 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"
+			cf.cf_name
+			(String.concat "" (List.map (fun (i,e) -> Printf.sprintf "\n\t\t%s<%i> = %s" (i.i_subst.v_name) (i.i_subst.v_id) (se "\t\t" e)) state#inlined_vars))
+			(se "\t" f.tf_expr)
+			(se "\t" e)
+		);
+	end;
+	Some e
 
 (* Same as type_inline, but modifies the function body to add field inits *)
 and type_inline_ctor ctx c cf tf ethis el po =

+ 4 - 39
src/typing/macroContext.ml

@@ -46,8 +46,6 @@ let macro_interp_cache = ref None
 let macro_interp_on_reuse = ref []
 let macro_interp_reused = ref false
 
-let delayed_macro_result = ref ((fun() -> assert false) : unit -> unit -> Interp.value)
-
 let safe_decode v t p f =
 	try
 		f ()
@@ -348,14 +346,6 @@ let make_macro_api ctx p =
 			ctx.m.curmod
 		);
 		MacroApi.current_macro_module = (fun () -> assert false);
-		MacroApi.delayed_macro = (fun i ->
-			let mctx = (match ctx.g.macros with None -> assert false | Some (_,mctx) -> mctx) in
-			let f = (try DynArray.get mctx.g.delayed_macros i with _ -> failwith "Delayed macro retrieve failure") in
-			f();
-			let ret = !delayed_macro_result in
-			delayed_macro_result := (fun() -> assert false);
-			ret
-		);
 		MacroApi.use_cache = (fun() ->
 			!macro_enable_cache
 		);
@@ -742,37 +732,12 @@ let type_macro ctx mode cpath f (el:Ast.expr list) p =
 				)
 			in
 			safe_decode v mret p process
-
 	in
-	let e = (if ctx.in_macro then begin
-		(*
-			this is super-tricky : we can't evaluate a macro inside a macro because we might trigger some cycles.
-			So instead, we generate a haxe.macro.Context.delayedCalled(i) expression that will only evaluate the
-			macro if/when it is called.
-
-			The tricky part is that the whole delayed-evaluation process has to use the same contextual information
-			as if it was evaluated now.
-		*)
-		let ctx = {
-			ctx with locals = ctx.locals;
-		} in
-		let pos = DynArray.length mctx.g.delayed_macros in
-		DynArray.add mctx.g.delayed_macros (fun() ->
-			delayed_macro_result := (fun() ->
-				let mint = Interp.get_ctx() in
-				match call() with
-				| None -> (fun() -> raise MacroApi.Abort)
-				| Some e -> Interp.eval_delayed mint (type_expr ctx e WithType.value)
-			);
-		);
-		ctx.m.curmod.m_extra.m_time <- -1.; (* disable caching for modules having macro-in-macro *)
-		if Common.defined ctx.com Define.MacroDebug then
-			ctx.com.warning "Macro-in-macro call detected" p;
-		let e = (EConst (Ident "$__delayed_call__"),p) in
-		Some (EUntyped (ECall (e,[EConst (Int (string_of_int pos)),p]),p),p)
-	end else
+	let e = if ctx.in_macro then
+		Some (EThrow((EConst(String "macro-in-macro")),p),p)
+	else
 		call()
-	) in
+	in
 	e
 
 let call_macro ctx path meth args p =

+ 0 - 1
src/typing/typer.ml

@@ -2479,7 +2479,6 @@ let rec create com =
 			module_check_policies = [];
 			delayed = [];
 			debug_delayed = [];
-			delayed_macros = DynArray.create();
 			doinline = com.display.dms_inline && not (Common.defined com Define.NoInline);
 			hook_generate = [];
 			get_build_infos = (fun() -> None);

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

@@ -53,7 +53,7 @@ class Macro {
 
 	macro static public function getCases(pack:String) {
 		var cases = [];
-		var singleCase = haxe.macro.Compiler.getDefine("test");
+		var singleCase = haxe.macro.Context.definedValue("test");
 		function loop(pack:Array<String>) {
 			var path = Context.resolvePath(Path.join(pack));
 			for (file in sys.FileSystem.readDirectory(path)) {