Procházet zdrojové kódy

Remove some API from haxe.macro.Compiler (#11540)

* remove some API from haxe.macro.Compiler

* js fixes

* never mind
Simon Krajewski před 1 rokem
rodič
revize
4260da3c6f

+ 0 - 1
src/context/typecore.ml

@@ -114,7 +114,6 @@ type typer_globals = {
 	mutable core_api : typer option;
 	mutable macros : ((unit -> unit) * typer) option;
 	mutable std_types : module_def;
-	type_patches : (path, (string * bool, type_patch) Hashtbl.t * type_patch) Hashtbl.t;
 	mutable module_check_policies : (string list * module_check_policy list * bool) list;
 	mutable global_using : (tclass * pos) list;
 	(* Indicates that Typer.create() finished building this instance *)

+ 0 - 10
src/macro/macroApi.ml

@@ -38,8 +38,6 @@ type 'value compiler_api = {
 	resolve_complex_type : Ast.type_hint -> Ast.type_hint;
 	store_typed_expr : Type.texpr -> Ast.expr;
 	allow_package : string -> unit;
-	type_patch : string -> string -> bool -> string option -> unit;
-	meta_patch : string -> string -> string option -> bool -> pos -> unit;
 	set_js_generator : (Genjs.ctx -> unit) -> unit;
 	get_local_type : unit -> t option;
 	get_expected_type : unit -> t option;
@@ -1953,14 +1951,6 @@ let macro_api ccom get_api =
 			(get_api()).allow_package (decode_string s);
 			vnull
 		);
-		"type_patch", vfun4 (fun t f s v ->
-			(get_api()).type_patch (decode_string t) (decode_string f) (decode_bool s) (opt decode_string v);
-			vnull
-		);
-		"meta_patch", vfun4 (fun m t f s ->
-			(get_api()).meta_patch (decode_string m) (decode_string t) (opt decode_string f) (decode_bool s) (get_api_call_pos ());
-			vnull
-		);
 		"add_global_metadata_impl", vfun5 (fun s1 s2 b1 b2 b3 ->
 			(get_api()).add_global_metadata (decode_string s1) (decode_string s2) (decode_bool b1,decode_bool b2,decode_bool b3) (get_api_call_pos());
 			vnull

+ 0 - 46
src/typing/macroContext.ml

@@ -51,28 +51,6 @@ let safe_decode com v expected t p f =
 		close_out ch;
 		raise_typing_error (Printf.sprintf "Expected %s but got %s (see %s.txt for details)" expected (Interp.value_string v) (String.concat "/" path)) p
 
-let get_type_patch ctx t sub =
-	let new_patch() =
-		{ tp_type = None; tp_remove = false; tp_meta = [] }
-	in
-	let path = Ast.parse_path t in
-	let h, tp = (try
-		Hashtbl.find ctx.g.type_patches path
-	with Not_found ->
-		let h = Hashtbl.create 0 in
-		let tp = new_patch() in
-		Hashtbl.add ctx.g.type_patches path (h,tp);
-		h, tp
-	) in
-	match sub with
-	| None -> tp
-	| Some k ->
-		try
-			Hashtbl.find h k
-		with Not_found ->
-			let tp = new_patch() in
-			Hashtbl.add h k tp;
-			tp
 
 let macro_timer com l =
 	Timer.timer (if Common.defined com Define.MacroTimes then ("macro" :: l) else ["macro"])
@@ -222,12 +200,6 @@ let make_macro_com_api com mcom p =
 			snd (Typecore.store_typed_expr com te p)
 		);
 		allow_package = (fun v -> Common.allow_package com v);
-		type_patch = (fun t f s v ->
-			Interp.exc_string "unsupported"
-		);
-		meta_patch = (fun m t f s p ->
-			Interp.exc_string "unsupported"
-		);
 		set_js_generator = (fun gen ->
 			com.js_gen <- Some (fun() ->
 				Path.mkdir_from_path com.file;
@@ -434,24 +406,6 @@ let make_macro_api ctx mctx p =
 		MacroApi.flush_context = (fun f ->
 			typing_timer ctx true f
 		);
-		MacroApi.type_patch = (fun t f s v ->
-			typing_timer ctx false (fun() ->
-				let v = (match v with None -> None | Some s ->
-					match ParserEntry.parse_string Grammar.parse_complex_type ctx.com.defines s null_pos raise_typing_error false with
-					| ParseSuccess((ct,_),_,_) -> Some ct
-					| ParseError(_,(msg,p),_) -> Parser.error msg p (* p is null_pos, but we don't have anything else here... *)
-				) in
-				let tp = get_type_patch ctx t (Some (f,s)) in
-				match v with
-				| None -> tp.tp_remove <- true
-				| Some t -> tp.tp_type <- Some t
-			);
-		);
-		MacroApi.meta_patch = (fun m t f s p ->
-			let ml = parse_metadata m p in
-			let tp = get_type_patch ctx t (match f with None -> None | Some f -> Some (f,s)) in
-			tp.tp_meta <- tp.tp_meta @ (List.map (fun (m,el,_) -> (m,el,p)) ml);
-		);
 		MacroApi.get_local_type = (fun() ->
 			match ctx.c.get_build_infos() with
 			| Some (mt,tl,_) ->

+ 0 - 70
src/typing/typeloadFields.ml

@@ -282,75 +282,6 @@ let transform_abstract_field com this_t a_t a f =
 	| _ ->
 		f
 
-let patch_class ctx c fields =
-	let path = match c.cl_kind with
-		| KAbstractImpl a -> a.a_path
-		| _ -> c.cl_path
-	in
-	let h = (try Some (Hashtbl.find ctx.g.type_patches path) with Not_found -> None) in
-	match h with
-	| None -> fields
-	| Some (h,hcl) ->
-		c.cl_meta <- c.cl_meta @ hcl.tp_meta;
-		let patch_getter t fn =
-			{ fn with f_type = t }
-		in
-		let patch_setter t fn =
-			match fn.f_args with
-			| [(name,opt,meta,_,expr)] ->
-				{ fn with f_args = [(name,opt,meta,t,expr)]; f_type = t }
-			| _ -> fn
-		in
-		let rec loop acc accessor_acc = function
-			| [] -> acc, accessor_acc
-			| f :: l ->
-				(* patch arguments types *)
-				(match f.cff_kind with
-				| FFun ff ->
-					let param (((n,pn),opt,m,_,e) as p) =
-						try
-							let t2 = (try Hashtbl.find h (("$" ^ (fst f.cff_name) ^ "__" ^ n),false) with Not_found -> Hashtbl.find h (("$" ^ n),false)) in
-							(n,pn), opt, m, (match t2.tp_type with None -> None | Some t -> Some (t,null_pos)), e
-						with Not_found ->
-							p
-					in
-					f.cff_kind <- FFun { ff with f_args = List.map param ff.f_args }
-				| _ -> ());
-				(* other patches *)
-				match (try Some (Hashtbl.find h (fst f.cff_name,List.mem_assoc AStatic f.cff_access)) with Not_found -> None) with
-				| None -> loop (f :: acc) accessor_acc l
-				| Some { tp_remove = true } -> loop acc accessor_acc l
-				| Some p ->
-					f.cff_meta <- f.cff_meta @ p.tp_meta;
-					let accessor_acc =
-						match p.tp_type with
-						| None -> accessor_acc
-						| Some t ->
-							match f.cff_kind with
-							| FVar (_,e) ->
-								f.cff_kind <- FVar (Some (t,null_pos),e); accessor_acc
-							| FProp (get,set,_,eo) ->
-								let typehint = Some (t,null_pos) in
-								let accessor_acc = if fst get = "get" then ("get_" ^ fst f.cff_name, patch_getter typehint) :: accessor_acc else accessor_acc in
-								let accessor_acc = if fst set = "set" then ("set_" ^ fst f.cff_name, patch_setter typehint) :: accessor_acc else accessor_acc in
-								f.cff_kind <- FProp (get,set,typehint,eo); accessor_acc
-							| FFun fn ->
-								f.cff_kind <- FFun { fn with f_type = Some (t,null_pos) }; accessor_acc
-					in
-					loop (f :: acc) accessor_acc l
-		in
-		let fields, accessor_patches = loop [] [] fields in
-		List.iter (fun (accessor_name, patch) ->
-			try
-				let f_accessor = List.find (fun f -> fst f.cff_name = accessor_name) fields in
-				match f_accessor.cff_kind with
-				| FFun fn -> f_accessor.cff_kind <- FFun (patch fn)
-				| _ -> ()
-			with Not_found ->
-				()
-		) accessor_patches;
-		List.rev fields
-
 let lazy_display_type ctx f =
 	f ()
 
@@ -1710,7 +1641,6 @@ let check_functional_interface ctx c =
 let init_class ctx_c cctx c p herits fields =
 	let com = ctx_c.com in
 	if cctx.is_class_debug then print_endline ("Created class context: " ^ dump_class_context cctx);
-	let fields = patch_class ctx_c c fields in
 	let fields = build_fields (ctx_c,cctx) c fields in
 	if cctx.is_core_api && com.display.dms_check_core_api then delay ctx_c PForce (fun() -> init_core_api ctx_c c);
 	if not cctx.is_lib then begin

+ 0 - 6
src/typing/typeloadModule.ml

@@ -450,13 +450,7 @@ module TypeLevel = struct
 		if ctx_m.m.is_display_file && DisplayPosition.display_position#enclosed_in (pos d.d_name) then
 			DisplayEmitter.display_module_type ctx_m (TEnumDecl e) (pos d.d_name);
 		let ctx_en = TyperManager.clone_for_enum ctx_m e in
-		let h = (try Some (Hashtbl.find ctx_en.g.type_patches e.e_path) with Not_found -> None) in
 		TypeloadCheck.check_global_metadata ctx_en e.e_meta (fun m -> e.e_meta <- m :: e.e_meta) e.e_module.m_path e.e_path None;
-		(match h with
-		| None -> ()
-		| Some (h,hcl) ->
-			Hashtbl.iter (fun _ _ -> raise_typing_error "Field type patch not supported for enums" e.e_pos) h;
-			e.e_meta <- e.e_meta @ hcl.tp_meta);
 		let constructs = ref d.d_data in
 		let get_constructs() =
 			List.map (fun c ->

+ 0 - 1
src/typing/typerEntry.ml

@@ -13,7 +13,6 @@ let create com macros =
 		g = {
 			core_api = None;
 			macros = macros;
-			type_patches = Hashtbl.create 0;
 			module_check_policies = [];
 			delayed = Array.init all_typer_passes_length (fun _ -> { tasks = []});
 			delayed_min_index = 0;

+ 5 - 110
std/haxe/macro/Compiler.hx

@@ -77,64 +77,9 @@ class Compiler {
 	}
 
 	#if (!neko && !eval)
-	private static function typePatch(cl:String, f:String, stat:Bool, t:String) {}
-
-	private static function metaPatch(meta:String, cl:String, f:String, stat:Bool) {}
-
 	private static function addGlobalMetadataImpl(pathFilter:String, meta:String, recursive:Bool, toTypes:Bool, toFields:Bool) {}
 	#end
 
-	/**
-		Removes a (static) field from a given class by name.
-		An error is thrown when `className` or `field` is invalid.
-	**/
-	@:deprecated
-	public static function removeField(className:String, field:String, ?isStatic:Bool) {
-		if (!path.match(className))
-			throw "Invalid " + className;
-		if (!ident.match(field))
-			throw "Invalid " + field;
-		#if (neko || eval)
-		Context.onAfterInitMacros(() -> load("type_patch", 4)(className, field, isStatic == true, null));
-		#else
-		typePatch(className, field, isStatic == true, null);
-		#end
-	}
-
-	/**
-		Set the type of a (static) field at a given class by name.
-		An error is thrown when `className` or `field` is invalid.
-	**/
-	@:deprecated
-	public static function setFieldType(className:String, field:String, type:String, ?isStatic:Bool) {
-		if (!path.match(className))
-			throw "Invalid " + className;
-		if (!ident.match((field.charAt(0) == "$") ? field.substr(1) : field))
-			throw "Invalid " + field;
-		#if (neko || eval)
-		Context.onAfterInitMacros(() -> load("type_patch", 4)(className, field, isStatic == true, type));
-		#else
-		typePatch(className, field, isStatic == true, type);
-		#end
-	}
-
-	/**
-		Add metadata to a (static) field or class by name.
-		An error is thrown when `className` or `field` is invalid.
-	**/
-	@:deprecated
-	public static function addMetadata(meta:String, className:String, ?field:String, ?isStatic:Bool) {
-		if (!path.match(className))
-			throw "Invalid " + className;
-		if (field != null && !ident.match(field))
-			throw "Invalid " + field;
-		#if (neko || eval)
-		Context.onAfterInitMacros(() -> load("meta_patch", 4)(meta, className, field, isStatic == true));
-		#else
-		metaPatch(meta, className, field, isStatic == true);
-		#end
-	}
-
 	/**
 		Add a class path where ".hx" source files or packages (sub-directories) can be found.
 
@@ -374,61 +319,6 @@ class Compiler {
 		});
 	}
 
-	/**
-		Load a type patch file that can modify the field types within declared classes and enums.
-	**/
-	public static function patchTypes(file:String):Void {
-		var file = Context.resolvePath(file);
-		var f = sys.io.File.read(file, true);
-		try {
-			while (true) {
-				var r = StringTools.trim(f.readLine());
-				if (r == "" || r.substr(0, 2) == "//")
-					continue;
-				if (StringTools.endsWith(r, ";"))
-					r = r.substr(0, -1);
-				if (r.charAt(0) == "-") {
-					r = r.substr(1);
-					var isStatic = StringTools.startsWith(r, "static ");
-					if (isStatic)
-						r = r.substr(7);
-					var p = r.split(".");
-					var field = p.pop();
-					removeField(p.join("."), field, isStatic);
-					continue;
-				}
-				if (r.charAt(0) == "@") {
-					var rp = r.split(" ");
-					var type = rp.pop();
-					var isStatic = rp[rp.length - 1] == "static";
-					if (isStatic)
-						rp.pop();
-					var meta = rp.join(" ");
-					var p = type.split(".");
-					var field = if (p.length > 1 && p[p.length - 2].charAt(0) >= "a") null else p.pop();
-					addMetadata(meta, p.join("."), field, isStatic);
-					continue;
-				}
-				if (StringTools.startsWith(r, "enum ")) {
-					define("enumAbstract:" + r.substr(5));
-					continue;
-				}
-				var rp = r.split(" : ");
-				if (rp.length > 1) {
-					r = rp.shift();
-					var isStatic = StringTools.startsWith(r, "static ");
-					if (isStatic)
-						r = r.substr(7);
-					var p = r.split(".");
-					var field = p.pop();
-					setFieldType(p.join("."), field, rp.join(" : "), isStatic);
-					continue;
-				}
-				throw "Invalid type patch " + r;
-			}
-		} catch (e:haxe.io.Eof) {}
-	}
-
 	/**
 		Marks types or packages to be kept by DCE.
 
@@ -487,6 +377,11 @@ class Compiler {
 		#end
 	}
 
+	public static function addMetadata(meta:String, className:String, ?field:String, ?isStatic:Bool) {
+		var pathFilter = field == null ? className : '$className.$field';
+		addGlobalMetadata(pathFilter, meta, true, field == null, field != null);
+	}
+
 	/**
 		Reference a json file describing user-defined metadata
 		See https://github.com/HaxeFoundation/haxe/blob/development/src-json/meta.json

+ 1 - 1
tests/misc/es6/Test.hx

@@ -32,7 +32,7 @@ class F extends E {
 }
 
 extern class ExtNoCtor {
-	static function __init__():Void haxe.macro.Compiler.includeFile("./extern.js", "top");
+	static function __init__():Void haxe.macro.Compiler.includeFile("./extern.js");
 }
 
 class Base extends ExtNoCtor {

+ 1 - 1
tests/misc/projects/Issue10844/user-defined-define-json-fail.hxml.stderr

@@ -1,3 +1,3 @@
 (unknown) : Uncaught exception Could not read file define.jsno
-$$normPath(::std::)/haxe/macro/Compiler.hx:506: characters 11-39 : Called from here
+$$normPath(::std::)/haxe/macro/Compiler.hx:401: characters 11-39 : Called from here
 (unknown) : Called from here

+ 1 - 1
tests/misc/projects/Issue10844/user-defined-meta-json-fail.hxml.stderr

@@ -1,3 +1,3 @@
 (unknown) : Uncaught exception Could not read file meta.jsno
-$$normPath(::std::)/haxe/macro/Compiler.hx:495: characters 11-39 : Called from here
+$$normPath(::std::)/haxe/macro/Compiler.hx:390: characters 11-39 : Called from here
 (unknown) : Called from here

+ 1 - 1
tests/misc/projects/Issue10844/user-defined-meta-json-indent-fail.hxml.stderr

@@ -1,3 +1,3 @@
 (unknown) : Uncaught exception Could not read file meta.jsno
-  $$normPath(::std::)/haxe/macro/Compiler.hx:495: characters 11-39 : Called from here
+  $$normPath(::std::)/haxe/macro/Compiler.hx:390: characters 11-39 : Called from here
   (unknown) : Called from here

+ 2 - 2
tests/misc/projects/Issue10844/user-defined-meta-json-pretty-fail.hxml.stderr

@@ -2,9 +2,9 @@
 
    | Uncaught exception Could not read file meta.jsno
 
-    ->  $$normPath(::std::)/haxe/macro/Compiler.hx:495: characters 11-39
+    ->  $$normPath(::std::)/haxe/macro/Compiler.hx:390: characters 11-39
 
-    495 |   var f = sys.io.File.getContent(path);
+    390 |   var f = sys.io.File.getContent(path);
         |           ^^^^^^^^^^^^^^^^^^^^^^^^^^^^
         | Called from here
 

+ 1 - 1
tests/misc/projects/Issue4660/Include.hx

@@ -1,5 +1,5 @@
 class Include {
     static function use() {
-        haxe.macro.Compiler.includeFile("include.js", Top);
+        haxe.macro.Compiler.includeFile("include.js");
     }
 }

+ 0 - 3
tests/misc/projects/Issue8567/compile.hxml

@@ -1,3 +0,0 @@
--cp src
--main Main
---macro patchTypes("src/test.txt")

+ 0 - 4
tests/misc/projects/Issue8567/src/Main.hx

@@ -1,4 +0,0 @@
-class Main {
-	static function main() {
-	}
-}

+ 0 - 0
tests/misc/projects/Issue8567/src/test.txt