Browse Source

Jvm annotation rework (#11398)

* [jvm] rework annotation handling

* don't break the gencommon bros

yet

* try to unhang haxelib

* try something else

* allow array declarations in strict annotations

* move misc tests from Java to Jvm runner

just in case somebody deletes the Java target

* flush PBuildClass after loading annotation type

this prevents field not found errors

* try to get classes and arrays under control

* add pseudo Mixin test
Simon Krajewski 1 năm trước cách đây
mục cha
commit
b75ecf7e5d

+ 2 - 1
src-json/meta.json

@@ -41,7 +41,8 @@
 	{
 		"name": "Annotation",
 		"metadata": ":annotation",
-		"doc": "Annotation (`@interface`) definitions on `--java-lib` imports will be annotated with this metadata. Has no effect on types compiled by Haxe.",
+		"doc": "Marks a class as a Java annotation",
+		"params": ["Retention policy"],
 		"platforms": ["java"],
 		"targets": ["TClass"]
 	},

+ 35 - 1
src/codegen/javaModern.ml

@@ -18,6 +18,7 @@ module AccessFlags = struct
 		| MAbstract
 		| MStrict
 		| MSynthetic
+		| MAnnotation
 		| MEnum
 
 	let to_int = function
@@ -34,6 +35,7 @@ module AccessFlags = struct
 		| MAbstract -> 0x400
 		| MStrict -> 0x800
 		| MSynthetic -> 0x1000
+		| MAnnotation -> 0x2000
 		| MEnum -> 0x4000
 
 	let has_flag b flag =
@@ -706,6 +708,27 @@ module Converter = struct
 	open PathConverter
 	open SignatureConverter
 
+	let extract_retention_policy l =
+		let rec loop2 l = match l with
+			| [] ->
+				None
+			| ann :: l ->
+				match ann.ann_type,ann.ann_elements with
+				| TObject((["java";"lang";"annotation"],"Retention"),_),[("value",ValEnum(_,name))] ->
+					Some name
+				| _ ->
+					loop2 l
+		in
+		let rec loop l = match l with
+			| [] ->
+				None
+			| AttrVisibleAnnotations l :: _ ->
+				loop2 l
+			| _ :: l ->
+				loop l
+		in
+		loop l
+
 	let convert_type_parameter ctx (name,extends,implements) p =
 		let jsigs = match extends with
 			| Some jsig -> jsig :: implements
@@ -908,10 +931,12 @@ module Converter = struct
 		let is_interface = AccessFlags.has_flag jc.jc_flags MInterface in
 		if is_interface then add_flag HInterface
 		else if AccessFlags.has_flag jc.jc_flags MAbstract then add_flag HAbstract;
+		let is_annotation = AccessFlags.has_flag jc.jc_flags MAnnotation in
 		begin match jc.jc_super with
 			| TObject(([],""),_)
 			| TObject((["java";"lang"],"Object"),_) ->
-				()
+				if is_annotation then
+					add_flag (HExtends ({tpackage = ["java";"lang";"annotation"]; tname = "Annotation"; tsub = None; tparams = []},null_pos));
 			| jsig ->
 				add_flag (HExtends (get_type_path (convert_signature ctx p jsig),p))
 		end;
@@ -957,6 +982,15 @@ module Converter = struct
 		end;
 		let _,class_name = jname_to_hx (snd jc.jc_path) in
 		add_meta (Meta.Native, [EConst (String (s_type_path jc.jc_path,SDoubleQuotes) ),p],p);
+		if is_annotation then begin
+			let args = match extract_retention_policy jc.jc_attributes with
+				| None ->
+					[]
+				| Some v ->
+					[EConst (String(v,SDoubleQuotes)),p]
+			in
+			add_meta (Meta.Annotation,args,p)
+		end;
 		let d = {
 			d_name = (class_name,p);
 			d_doc = None;

+ 75 - 52
src/generators/genjvm.ml

@@ -141,48 +141,54 @@ end
 
 open NativeSignatures
 
+let jsignature_of_path path = match path with
+	| [],"Bool" -> TBool
+	| ["java"],"Int8" -> TByte
+	| ["java"],"Int16" -> TShort
+	| [],"Int" -> TInt
+	| ["haxe"],"Int32" -> TInt
+	| ["haxe"],"Int64" -> TLong
+	| ["java"],"Int64" -> TLong
+	| ["java"],"Char16" -> TChar
+	| [],"Single" -> TFloat
+	| [],"Float" -> TDouble
+	| [],"Dynamic" -> object_sig
+	| _ -> raise Exit
+
 let rec jsignature_of_type gctx stack t =
 	if List.exists (fast_eq t) stack then object_sig else
 	let jsignature_of_type = jsignature_of_type gctx (t :: stack) in
 	let jtype_argument_of_type t = jtype_argument_of_type gctx stack t in
 	match t with
 	| TAbstract(a,tl) ->
-		begin match a.a_path with
-			| [],"Bool" -> TBool
-			| ["java"],"Int8" -> TByte
-			| ["java"],"Int16" -> TShort
-			| [],"Int" -> TInt
-			| ["haxe"],"Int32" -> TInt
-			| ["haxe"],"Int64" -> TLong
-			| ["java"],"Int64" -> TLong
-			| ["java"],"Char16" -> TChar
-			| [],"Single" -> TFloat
-			| [],"Float" -> TDouble
-			| [],"Void" -> void_sig
-			| [],"Null" ->
-				begin match tl with
-				| [t] -> get_boxed_type (jsignature_of_type t)
-				| _ -> die "" __LOC__
-				end
-			| ["haxe";"ds"],"Vector" ->
-				begin match tl with
-				| [t] -> TArray(jsignature_of_type t,None)
-				| _ -> die "" __LOC__
-				end
-			| [],"Dynamic" ->
-				object_sig
-			| [],("Class" | "Enum") ->
-				begin match tl with
-				| [t] -> TObject(java_class_path,[TType(WNone,jsignature_of_type t)])
-				| _ -> java_class_sig
-				end
-			| [],"EnumValue" ->
-				java_enum_sig object_sig
-			| _ ->
-				if Meta.has Meta.CoreType a.a_meta then
-					TObject(a.a_path,List.map jtype_argument_of_type tl)
-				else
-					jsignature_of_type (Abstract.get_underlying_type a tl)
+		begin try
+			jsignature_of_path a.a_path
+		with Exit ->
+			begin match a.a_path with
+				| [],"Void" -> void_sig
+				| [],"Null" ->
+					begin match tl with
+					| [t] -> get_boxed_type (jsignature_of_type t)
+					| _ -> die "" __LOC__
+					end
+				| ["haxe";"ds"],"Vector" ->
+					begin match tl with
+					| [t] -> TArray(jsignature_of_type t,None)
+					| _ -> die "" __LOC__
+					end
+				| [],("Class" | "Enum") ->
+					begin match tl with
+					| [t] -> TObject(java_class_path,[TType(WNone,jsignature_of_type t)])
+					| _ -> java_class_sig
+					end
+				| [],"EnumValue" ->
+					java_enum_sig object_sig
+				| _ ->
+					if Meta.has Meta.CoreType a.a_meta then
+						TObject(a.a_path,List.map jtype_argument_of_type tl)
+					else
+						jsignature_of_type (Abstract.get_underlying_type a tl)
+			end
 		end
 	| TDynamic _ -> object_sig
 	| TMono r ->
@@ -259,6 +265,19 @@ module AnnotationHandler = struct
 			| EConst (Ident "true") -> ABool true
 			| EConst (Ident "false") -> ABool false
 			| EArrayDecl el -> AArray (List.map parse_value el)
+			| EField(e1,"class",_) ->
+				let path = parse_path e1 in
+				let jsig =  try
+					Some (jsignature_of_path path)
+				with Exit -> match path with
+					| ([],"Void") ->
+						None
+					| ([],name) ->
+						Some (TObject((["haxe";"root"],name),[]))
+					| _ ->
+						Some (TObject(path,[]))
+				in
+				AClass jsig
 			| EField(e1,s,_) ->
 				let path = parse_path e1 in
 				AEnum(object_path_sig path,s)
@@ -287,20 +306,25 @@ module AnnotationHandler = struct
 				Error.raise_typing_error "Call expression expected" (pos e)
 		in
 		ExtList.List.filter_map (fun (m,el,_) -> match m,el with
-			| Meta.Meta,[e] ->
-				let path,annotation = parse_expr e in
+			| Meta.Meta,(e1 :: el) ->
+				let path,annotation = parse_expr e1 in
 				let path = match path with
 					| [],name -> ["haxe";"root"],name
 					| _ -> path
 				in
-				Some(path,annotation)
+				(* If there's no value this was an untyped @:meta. Let's assume RUNTIME retention. *)
+				let is_runtime_visible = match el with
+					| [(EConst (String("CLASS",_)),_)] -> false
+					| _ -> true
+				in
+				Some(path,annotation,is_runtime_visible)
 			| _ ->
 				None
 		) meta
 
 	let generate_annotations builder meta =
-		List.iter (fun (path,annotation) ->
-			builder#add_annotation path annotation
+		List.iter (fun (path,annotation,is_runtime_visible) ->
+			builder#add_annotation path annotation is_runtime_visible
 		) (convert_annotations meta)
 end
 
@@ -2286,8 +2310,11 @@ class tclass_to_jvm gctx c = object(self)
 		if is_annotation then begin
 			jc#add_access_flag 0x2000;
 			jc#add_interface (["java";"lang";"annotation"],"Annotation") [];
-			(* TODO: this should be done via Haxe metadata instead of hardcoding it here *)
-			jc#add_annotation retention_path ["value",(AEnum(retention_policy_sig,"RUNTIME"))];
+			let value = match get_meta_string c.cl_meta Meta.Annotation with
+				| None -> "CLASS"
+				| Some value -> value
+			in
+			jc#add_annotation retention_path ["value",(AEnum(retention_policy_sig,value))] true;
 		end;
 		if (has_class_flag c CAbstract) then jc#add_access_flag 0x0400; (* abstract *)
 		if Meta.has Meta.JvmSynthetic c.cl_meta then jc#add_access_flag 0x1000 (* synthetic *)
@@ -2436,12 +2463,8 @@ class tclass_to_jvm gctx c = object(self)
 		let handler = new texpr_to_jvm gctx field_info jc jm tr in
 		List.iter (fun (v,_) ->
 			let slot,_,_ = handler#add_local v VarArgument in
-			let annot = AnnotationHandler.convert_annotations v.v_meta in
-			match annot with
-			| [] ->
-				()
-			| _ ->
-				jm#add_argument_annotation slot annot;
+			let l = AnnotationHandler.convert_annotations v.v_meta in
+			List.iter (fun (path,annotation,is_runtime_visible) -> jm#add_argument_annotation slot path annotation is_runtime_visible) l;
 		) args;
 		jm#finalize_arguments;
 		begin match mtype with
@@ -2634,7 +2657,7 @@ class tclass_to_jvm gctx c = object(self)
 
 	method generate_annotations =
 		AnnotationHandler.generate_annotations (jc :> JvmBuilder.base_builder) c.cl_meta;
-		jc#add_annotation (["haxe";"jvm";"annotation"],"ClassReflectionInformation") (["hasSuperClass",(ABool (c.cl_super <> None))])
+		jc#add_annotation (["haxe";"jvm";"annotation"],"ClassReflectionInformation") (["hasSuperClass",(ABool (c.cl_super <> None))]) true
 
 	method private do_generate =
 		self#set_access_flags;
@@ -2758,7 +2781,7 @@ let generate_enum gctx en =
 				jm_ctor#add_argument_and_field n jsig [FdPublic;FdFinal]
 			) args;
 			jm_ctor#return;
-			jc_ctor#add_annotation (["haxe";"jvm";"annotation"],"EnumValueReflectionInformation") (["argumentNames",AArray (List.map (fun (name,_) -> AString name) args)]);
+			jc_ctor#add_annotation (["haxe";"jvm";"annotation"],"EnumValueReflectionInformation") (["argumentNames",AArray (List.map (fun (name,_) -> AString name) args)]) true;
 			if args <> [] then begin
 				let jm_params = jc_ctor#spawn_method "_hx_getParameters" (method_sig [] (Some (array_sig object_sig))) [MPublic;MSynthetic] in
 				let jm_equals,compare_field = generate_enum_equals gctx jc_ctor in
@@ -2825,7 +2848,7 @@ let generate_enum gctx en =
 		jm_clinit#return;
 	end;
 	AnnotationHandler.generate_annotations (jc_enum :> JvmBuilder.base_builder) en.e_meta;
-	jc_enum#add_annotation (["haxe";"jvm";"annotation"],"EnumReflectionInformation") (["constructorNames",AArray names]);
+	jc_enum#add_annotation (["haxe";"jvm";"annotation"],"EnumReflectionInformation") (["constructorNames",AArray names]) true;
 	write_class gctx en.e_path (jc_enum#export_class gctx.default_export_config)
 
 let generate_module_type ctx mt =

+ 9 - 0
src/generators/jvm/jvmAttribute.ml

@@ -85,7 +85,9 @@ type j_attribute =
 	| AttributeInnerClasses of jvm_inner_class array
 	| AttributeEnclosingMethod of jvm_constant_pool_index * jvm_constant_pool_index
 	| AttributeRuntimeVisibleAnnotations of j_annotation array
+	| AttributeRuntimeInvisibleAnnotations of j_annotation array
 	| AttributeRuntimeVisibleParameterAnnotations of j_annotation array array
+	| AttributeRuntimeInvisibleParameterAnnotations of j_annotation array array
 	| AttributeBootstrapMethods of j_bootstrap_method array
 
 let write_verification_type ch = function
@@ -236,10 +238,17 @@ let write_attribute pool jvma =
 	| AttributeRuntimeVisibleAnnotations al ->
 		write_array16 ch write_annotation al;
 		"RuntimeVisibleAnnotations"
+	| AttributeRuntimeInvisibleAnnotations al ->
+		write_array16 ch write_annotation al;
+		"RuntimeInvisibleAnnotations"
 	| AttributeRuntimeVisibleParameterAnnotations al ->
 		write_byte ch (Array.length al);
 		Array.iter (write_array16 ch write_annotation) al;
 		"RuntimeVisibleParameterAnnotations"
+	| AttributeRuntimeInvisibleParameterAnnotations al ->
+		write_byte ch (Array.length al);
+		Array.iter (write_array16 ch write_annotation) al;
+		"RuntimeInvisibleParameterAnnotations"
 	| AttributeBootstrapMethods a ->
 		write_array16 ch (fun _ bm ->
 			write_ui16 ch bm.bm_method_ref;

+ 15 - 8
src/generators/jvm/jvmBuilder.ml

@@ -29,6 +29,7 @@ type annotation_kind =
 	| AEnum of jsignature * string
 	| AArray of annotation_kind list
 	| AAnnotation of jsignature * annotation
+	| AClass of jsignature option
 
 and annotation = (string * annotation_kind) list
 
@@ -58,7 +59,8 @@ let convert_annotations pool annotations =
 				| AAnnotation (jsig, a) ->
 					let ann = process_annotation (jsig, a) in
 					'@',ValAnnotation(ann)
-
+				| AClass jsig ->
+					'c',ValClass(pool#add_string (Option.map_default (generate_signature false) "V" jsig))
 			in
 			offset,loop ak
 		) l in
@@ -67,13 +69,13 @@ let convert_annotations pool annotations =
 			ann_elements = Array.of_list l;
 		}
 	in
-	let a = Array.map process_annotation annotations in
-	a
+	Array.map process_annotation annotations
 
 class base_builder = object(self)
 	val mutable access_flags = 0
 	val attributes = DynArray.create ()
-	val annotations = DynArray.create ()
+	val runtime_visible_annotations = DynArray.create ()
+	val runtime_invisible_annotations = DynArray.create ()
 	val mutable was_exported = false
 
 	method add_access_flag i =
@@ -82,14 +84,19 @@ class base_builder = object(self)
 	method add_attribute (a : j_attribute) =
 		DynArray.add attributes a
 
-	method add_annotation (path : jpath) (a : annotation) =
-		DynArray.add annotations ((TObject(path,[])),a)
+	method add_annotation (path : jpath) (a : annotation) (is_runtime_visible : bool) =
+		DynArray.add (if is_runtime_visible then runtime_visible_annotations else runtime_invisible_annotations) ((TObject(path,[])),a)
 
 	method private commit_annotations pool =
-		if DynArray.length annotations > 0 then begin
+		if DynArray.length runtime_visible_annotations > 0 then begin
 			let open JvmAttribute in
-			let a = convert_annotations pool (DynArray.to_array annotations) in
+			let a = convert_annotations pool (DynArray.to_array runtime_visible_annotations) in
 			self#add_attribute (AttributeRuntimeVisibleAnnotations a)
+		end;
+		if DynArray.length runtime_invisible_annotations > 0 then begin
+			let open JvmAttribute in
+			let a = convert_annotations pool (DynArray.to_array runtime_invisible_annotations) in
+			self#add_attribute (AttributeRuntimeInvisibleAnnotations a)
 		end
 
 	method export_attributes (pool : JvmConstantPool.constant_pool) =

+ 27 - 16
src/generators/jvm/jvmMethod.ml

@@ -155,7 +155,8 @@ class builder jc name jsig = object(self)
 	val mutable stack_frames = []
 	val mutable exceptions = []
 	val mutable argument_locals = []
-	val mutable argument_annotations = Hashtbl.create 0
+	val mutable runtime_visible_argument_annotations = Hashtbl.create 0
+	val mutable runtime_invisible_argument_annotations = Hashtbl.create 0
 	val mutable thrown_exceptions = Hashtbl.create 0
 	val mutable regex_count = 0
 
@@ -1011,9 +1012,15 @@ class builder jc name jsig = object(self)
 	method replace_top jsig =
 		code#get_stack#replace jsig
 
-	method add_argument_annotation (slot : int) (a : (path * annotation) list) =
-		let a = Array.of_list (List.map (fun (path,annot) -> TObject(path,[]),annot) a) in
-		Hashtbl.add argument_annotations slot a
+	method add_argument_annotation (slot : int) (path : jpath) (a : annotation) (is_runtime_visible : bool) =
+		let h = if is_runtime_visible then runtime_visible_argument_annotations else runtime_invisible_argument_annotations in
+		try
+			let d = Hashtbl.find h slot in
+			DynArray.add d (TObject(path,[]),a)
+		with Not_found ->
+			let d = DynArray.create () in
+			DynArray.add d (TObject(path,[]),a);
+			Hashtbl.add h slot d
 
 	(** This function has to be called once all arguments are declared. *)
 	method finalize_arguments =
@@ -1137,18 +1144,22 @@ class builder jc name jsig = object(self)
 		end;
 		if Hashtbl.length thrown_exceptions > 0 then
 			self#add_attribute (AttributeExceptions (Array.of_list (Hashtbl.fold (fun k _ c -> k :: c) thrown_exceptions [])));
-		if Hashtbl.length argument_annotations > 0 then begin
-			let l = List.length argument_locals in
-			let offset = if self#has_method_flag MStatic then 0 else 1 in
-			let a = Array.init (l - offset) (fun i ->
-				try
-					let annot = Hashtbl.find argument_annotations (i + offset) in
-					convert_annotations jc#get_pool annot
-				with Not_found ->
-					[||]
-			) in
-			DynArray.add attributes (AttributeRuntimeVisibleParameterAnnotations a)
-		end;
+		let collect_annotations h f =
+			if Hashtbl.length h > 0 then begin
+				let l = List.length argument_locals in
+				let offset = if self#has_method_flag MStatic then 0 else 1 in
+				let a = Array.init (l - offset) (fun i ->
+					try
+						let d = Hashtbl.find h (i + offset) in
+						convert_annotations jc#get_pool (DynArray.to_array d)
+					with Not_found ->
+						[||]
+				) in
+				f a
+			end;
+		in
+		collect_annotations runtime_visible_argument_annotations (fun a -> DynArray.add attributes (AttributeRuntimeVisibleParameterAnnotations a));
+		collect_annotations runtime_invisible_argument_annotations (fun a -> DynArray.add attributes (AttributeRuntimeInvisibleParameterAnnotations a));
 		let attributes = self#export_attributes jc#get_pool in
 		let offset_name = jc#get_pool#add_string name in
 		let offset_desc = jc#get_pool#add_string descriptor in

+ 2 - 1
src/typing/functionArguments.ml

@@ -89,7 +89,8 @@ object(self)
 		| None ->
 			let make_local name kind t meta pn =
 				let v = alloc_var kind name t pn in
-				v.v_meta <- v.v_meta @ meta;
+				let meta = (StrictMeta.check_strict_meta ctx meta) @ meta in
+				v.v_meta <- meta;
 				v
 			in
 			let rec loop acc is_abstract_this syntax typed = match syntax,typed with

+ 60 - 3
src/typing/strictMeta.ml

@@ -3,6 +3,7 @@ open Ast
 open Type
 open Common
 open Typecore
+open Error
 
 let get_native_repr md pos =
 	let path, meta = match md with
@@ -57,10 +58,48 @@ let rec process_meta_argument ?(toplevel=true) ctx expr = match expr.eexpr with
 			(efield(get_native_repr md expr.epos, "class"), p)
 	| TTypeExpr md ->
 		get_native_repr md expr.epos
+	| TArrayDecl el ->
+		let el = List.map (process_meta_argument ctx) el in
+		(EArrayDecl el,expr.epos)
 	| _ ->
 		display_error ctx.com "This expression is too complex to be a strict metadata argument" expr.epos;
 		(EConst(Ident "null"), expr.epos)
 
+let rec kind_of_type_against ctx t_want e_have =
+	match follow t_want with
+	| TInst({cl_path = (["java";"lang"],"Class")},[t1]) ->
+		let e = type_expr ctx e_have (WithType.with_type t_want) in
+		begin match follow e.etype with
+			| TAbstract({a_path = ([],"Class")},[t2]) ->
+				unify ctx t2 t1 e.epos
+			| TAnon an ->
+				begin match !(an.a_status) with
+					| ClassStatics c ->
+						unify ctx (TInst(c,extract_param_types c.cl_params)) t1 e.epos
+					| AbstractStatics a ->
+						unify ctx (TAbstract(a,extract_param_types a.a_params)) t1 e.epos
+					| _ ->
+						unify ctx e.etype t_want e.epos
+				end
+			| _ ->
+				unify ctx e.etype t_want e.epos
+		end;
+		e
+	| TInst({cl_path = (["java"],"NativeArray")},[t1]) ->
+		begin match fst e_have with
+			| EArrayDecl el ->
+				let el = List.map (kind_of_type_against ctx t1) el in
+				mk (TArrayDecl el) t1 (snd e_have)
+			| _ ->
+				let e = type_expr ctx e_have (WithType.with_type t_want) in
+				unify ctx e.etype t_want e.epos;
+				e
+		end
+	| t1 ->
+		let e = type_expr ctx e_have (WithType.with_type t1) in
+		unify ctx e.etype t1 e.epos;
+		e
+
 let handle_fields ctx fields_to_check with_type_expr =
 	List.map (fun ((name,_,_),expr) ->
 		let pos = snd expr in
@@ -73,8 +112,7 @@ let handle_fields ctx fields_to_check with_type_expr =
 		in
 
 		let left = type_expr ctx left_side NoValue in
-		let right = type_expr ctx expr (WithType.with_type left.etype) in
-		unify ctx left.etype right.etype (snd expr);
+		let right = kind_of_type_against ctx left.etype expr in
 		(EBinop(Ast.OpAssign,fieldexpr,process_meta_argument ctx right), pos)
 	) fields_to_check
 
@@ -131,10 +169,29 @@ let get_strict_meta ctx meta params pos =
 			display_error ctx.com "A @:strict metadata must contain exactly one parameter. Please check the documentation for more information" pos;
 			raise Exit
 	in
+	let t = Typeload.load_complex_type ctx false (ctype,pos) in
+	flush_pass ctx PBuildClass "get_strict_meta";
 	let texpr = type_expr ctx changed_expr NoValue in
 	let with_type_expr = (ECheckType( (EConst (Ident "null"), pos), (ctype,null_pos) ), pos) in
 	let extra = handle_fields ctx fields_to_check with_type_expr in
-	meta, [make_meta ctx texpr extra], pos
+	let args = [make_meta ctx texpr extra] in
+	let args = if Common.defined ctx.com Define.Jvm then match t with
+		| TInst(c,_) ->
+			let v = get_meta_string c.cl_meta Meta.Annotation in
+			begin match v with
+			| None ->
+				(* We explicitly set this to the default retention policy CLASS. This allows us to treat
+				   @:strict as default CLASS and @:meta as default RUNTIME. *)
+				args @ [EConst (String("CLASS",SDoubleQuotes)),pos]
+			| Some v ->
+				args @ [EConst (String(v,SDoubleQuotes)),pos]
+			end;
+		| _ ->
+			args
+	else
+		args
+	in
+	meta, args, pos
 
 let check_strict_meta ctx metas =
 	let pf = ctx.com.platform in

+ 1 - 1
std/jvm/annotation/ClassReflectionInformation.hx

@@ -22,7 +22,7 @@
 
 package jvm.annotation;
 
-@:annotation
+@:annotation("RUNTIME")
 @:native("haxe.jvm.annotation.ClassReflectionInformation")
 @:keep
 interface ClassReflectionInformation extends java.lang.annotation.Annotation {

+ 1 - 1
std/jvm/annotation/EnumReflectionInformation.hx

@@ -22,7 +22,7 @@
 
 package jvm.annotation;
 
-@:annotation
+@:annotation("RUNTIME")
 @:native("haxe.jvm.annotation.EnumReflectionInformation")
 @:keep
 interface EnumReflectionInformation extends java.lang.annotation.Annotation {

+ 1 - 1
std/jvm/annotation/EnumValueReflectionInformation.hx

@@ -22,7 +22,7 @@
 
 package jvm.annotation;
 
-@:annotation
+@:annotation("RUNTIME")
 @:native("haxe.jvm.annotation.EnumValueReflectionInformation")
 @:keep
 interface EnumValueReflectionInformation extends java.lang.annotation.Annotation {

+ 25 - 0
tests/misc/java/projects/Annotations/AnnotationLib.hx

@@ -0,0 +1,25 @@
+@:annotation("RUNTIME")
+interface MyVisibleAnnotation {}
+
+@:annotation("CLASS")
+interface MyInvisibleAnnotation {}
+
+@:annotation("RUNTIME")
+interface MyVisibleArrayAnnotation {
+	function value():java.NativeArray<String>;
+}
+
+@:annotation("RUNTIME")
+interface MyVisibleArrayArrayAnnotation {
+	function value():java.NativeArray<java.NativeArray<String>>;
+}
+
+@:strict(MyVisibleAnnotation())
+@:strict(MyInvisibleAnnotation())
+@:strict(MyVisibleArrayAnnotation({value: ["foo", "bar"]}))
+@:strict(MyVisibleArrayArrayAnnotation({value: [["foo1", "bar1"], ["foo2", "bar2"]]}))
+class AnnotationLib {
+	@:strict(MyVisibleAnnotation())
+	@:strict(MyInvisibleAnnotation())
+	static function test(@:strict(MyVisibleAnnotation()) arg1:String, @:strict(MyInvisibleAnnotation()) arg2:String) {}
+}

+ 82 - 0
tests/misc/java/projects/Annotations/Main.hx

@@ -0,0 +1,82 @@
+import haxe.io.BytesInput;
+import sys.io.File;
+import sys.io.FileInput;
+import format.jvm.Data;
+
+using StringTools;
+using Lambda;
+
+typedef Annotations = {
+	var ?runtimeVisible:Array<Annotation>;
+	var ?runtimeInvisible:Array<Annotation>;
+	var ?runtimeVisibleParameter:Array<Array<Annotation>>;
+	var ?runtimeInvisibleParameter:Array<Array<Annotation>>;
+}
+
+function getAnnotations(attributes:Array<Attribute>) {
+	var annotations:Annotations = {};
+
+	for (attribute in attributes) {
+		switch (attribute) {
+			case RuntimeVisibleAnnotations(a):
+				annotations.runtimeVisible = a;
+			case RuntimeInvisibleAnnotations(a):
+				annotations.runtimeInvisible = a;
+			case RuntimeVisibleParameterAnnotations(a):
+				annotations.runtimeVisibleParameter = a;
+			case RuntimeInvisibleParameterAnnotations(a):
+				annotations.runtimeInvisibleParameter = a;
+			case _:
+		}
+	}
+	return annotations;
+}
+
+function hasAnnotation(annotations:Array<Annotation>, name:String) {
+	return annotations.exists(ann -> ann.type == name);
+}
+
+function reportPresence(source:String, annotations:Array<Array<Annotation>>, name:String) {
+	Sys.println('Presence of $name on $source');
+	for (key => annotations in annotations) {
+		Sys.println('  $key: ${hasAnnotation(annotations, name)}');
+	}
+}
+
+function main() {
+	var input = File.read("annotationLib.jar");
+	var zip = new format.zip.Reader(input);
+	var data = zip.read();
+	for (entry in data) {
+		if (!entry.fileName.endsWith("AnnotationLib.class")) {
+			continue;
+		}
+		var input = new BytesInput(entry.data);
+		var reader = new format.jvm.Reader(input);
+		var jc = reader.read();
+		var annotations = getAnnotations(jc.attributes);
+		reportPresence(jc.thisClass, [annotations.runtimeVisible, annotations.runtimeInvisible], "Lhaxe/root/MyVisibleAnnotation;");
+		reportPresence(jc.thisClass, [annotations.runtimeVisible, annotations.runtimeInvisible], "Lhaxe/root/MyInvisibleAnnotation;");
+
+		for (method in jc.methods) {
+			if (method.name != "test") {
+				continue;
+			}
+			var annotations = getAnnotations(method.attributes);
+			reportPresence(method.name, [annotations.runtimeVisible, annotations.runtimeInvisible], "Lhaxe/root/MyVisibleAnnotation;");
+			reportPresence(method.name, [annotations.runtimeVisible, annotations.runtimeInvisible], "Lhaxe/root/MyInvisibleAnnotation;");
+
+			for (i in 0...2) {
+				var name = '${method.name} (arg $i)';
+				reportPresence(name, [annotations.runtimeVisibleParameter[i], annotations.runtimeInvisibleParameter[i]], "Lhaxe/root/MyVisibleAnnotation;");
+				reportPresence(name, [annotations.runtimeVisibleParameter[i], annotations.runtimeInvisibleParameter[i]], "Lhaxe/root/MyInvisibleAnnotation;");
+			}
+		}
+
+		var ann = annotations.runtimeVisible.find(ann -> ann.type == "Lhaxe/root/MyVisibleArrayAnnotation;");
+		Sys.println(ann.elementValuePairs[0].elementValue.value);
+
+		var ann = annotations.runtimeVisible.find(ann -> ann.type == "Lhaxe/root/MyVisibleArrayArrayAnnotation;");
+		Sys.println(ann.elementValuePairs[0].elementValue.value);
+	}
+}

+ 33 - 0
tests/misc/java/projects/Annotations/MainMixin.hx

@@ -0,0 +1,33 @@
+using jvm.NativeTools.NativeClassTools;
+
+@:annotation("RUNTIME")
+interface Mixin extends java.lang.annotation.Annotation {
+	function value():java.NativeArray<Class<Dynamic>>;
+	function targets():java.NativeArray<String>;
+	function priority():Int;
+	function remap():Bool;
+}
+
+class B {}
+
+@:strict(Mixin({
+	value: [String, B],
+	targets: ["here"],
+	priority: 9001,
+	remap: true
+}))
+class C {}
+
+class MainMixin {
+	static function main() {
+		var annot = C.native().getAnnotation(Mixin.native());
+		for (v in annot.value()) {
+			trace(v);
+		}
+		for (v in annot.targets()) {
+			trace(v);
+		}
+		trace(annot.priority());
+		trace(annot.remap());
+	}
+}

+ 3 - 0
tests/misc/java/projects/Annotations/compile-mixin.hxml

@@ -0,0 +1,3 @@
+--main MainMixin
+--jvm mixin.jar
+--cmd java -jar mixin.jar

+ 5 - 0
tests/misc/java/projects/Annotations/compile-mixin.hxml.stdout

@@ -0,0 +1,5 @@
+MainMixin.hx:25: class java.lang.String
+MainMixin.hx:25: class haxe.root.B
+MainMixin.hx:28: here
+MainMixin.hx:30: 9001
+MainMixin.hx:31: true

+ 12 - 0
tests/misc/java/projects/Annotations/compile.hxml

@@ -0,0 +1,12 @@
+AnnotationLib
+--jvm annotationLib.jar
+
+--next
+
+--main Main
+-lib format
+--jvm jvm.jar
+
+--next
+
+--cmd java -jar jvm.jar

+ 26 - 0
tests/misc/java/projects/Annotations/compile.hxml.stdout

@@ -0,0 +1,26 @@
+Presence of Lhaxe/root/MyVisibleAnnotation; on haxe/root/AnnotationLib
+  0: true
+  1: false
+Presence of Lhaxe/root/MyInvisibleAnnotation; on haxe/root/AnnotationLib
+  0: false
+  1: true
+Presence of Lhaxe/root/MyVisibleAnnotation; on test
+  0: true
+  1: false
+Presence of Lhaxe/root/MyInvisibleAnnotation; on test
+  0: false
+  1: true
+Presence of Lhaxe/root/MyVisibleAnnotation; on test (arg 0)
+  0: true
+  1: false
+Presence of Lhaxe/root/MyInvisibleAnnotation; on test (arg 0)
+  0: false
+  1: false
+Presence of Lhaxe/root/MyVisibleAnnotation; on test (arg 1)
+  0: false
+  1: false
+Presence of Lhaxe/root/MyInvisibleAnnotation; on test (arg 1)
+  0: false
+  1: true
+ArrayValue([{tag: 115, value: ConstValue(CONSTANT_Utf8(foo))},{tag: 115, value: ConstValue(CONSTANT_Utf8(bar))}])
+ArrayValue([{tag: 91, value: ArrayValue([{tag: 115, value: ConstValue(CONSTANT_Utf8(foo1))},{tag: 115, value: ConstValue(CONSTANT_Utf8(bar1))}])},{tag: 91, value: ArrayValue([{tag: 115, value: ConstValue(CONSTANT_Utf8(foo2))},{tag: 115, value: ConstValue(CONSTANT_Utf8(bar2))}])}])

+ 1 - 5
tests/runci/targets/Java.hx

@@ -7,10 +7,9 @@ import runci.Config.*;
 using StringTools;
 
 class Java {
-	static final miscJavaDir = getMiscSubDir('java');
-
 	static public function getJavaDependencies() {
 		haxelibInstallGit("HaxeFoundation", "hxjava", true);
+		haxelibInstallGit("HaxeFoundation", "format", "jvm", "--always");
 		runCommand("javac", ["-version"]);
 	}
 
@@ -24,9 +23,6 @@ class Java {
 		runCommand("haxe", ["compile-java.hxml","-dce","no"].concat(args));
 		runCommand("java", ["-jar", "bin/java/TestMain-Debug.jar"]);
 
-		changeDirectory(miscJavaDir);
-		runCommand("haxe", ["run.hxml"]);
-
 		changeDirectory(sysDir);
 		runCommand("haxe", ["compile-java.hxml"].concat(args));
 		runSysTest("java", ["-jar", "bin/java/Main-Debug.jar"]);

+ 5 - 0
tests/runci/targets/Jvm.hx

@@ -4,6 +4,8 @@ import runci.System.*;
 import runci.Config.*;
 
 class Jvm {
+	static final miscJavaDir = getMiscSubDir('java');
+
 	static public function run(args:Array<String>) {
 		deleteDirectoryRecursively("bin/jvm");
 		Java.getJavaDependencies();
@@ -17,6 +19,9 @@ class Jvm {
 			runCommand("java", ["-jar", "bin/unit.jar"]);
 		}
 
+		changeDirectory(miscJavaDir);
+		runCommand("haxe", ["run.hxml"]);
+
 		changeDirectory(sysDir);
 		runCommand("haxe", ["compile-jvm.hxml"].concat(args));
 		runSysTest("java", ["-jar", "bin/jvm/sys.jar"]);