Ver Fonte

added metadata position

Nicolas Cannasse há 14 anos atrás
pai
commit
62ed7ee558
10 ficheiros alterados com 34 adições e 37 exclusões
  1. 1 1
      ast.ml
  2. 4 4
      codegen.ml
  3. 2 2
      genswf.ml
  4. 6 6
      genswf9.ml
  5. 3 3
      genxml.ml
  6. 5 4
      interp.ml
  7. 7 7
      parser.ml
  8. 2 2
      std/haxe/macro/Type.hx
  9. 2 2
      type.ml
  10. 2 6
      typeload.ml

+ 1 - 1
ast.ml

@@ -199,7 +199,7 @@ type type_param = string * type_path list
 
 type documentation = string option
 
-type metadata = (string * expr list) list
+type metadata = (string * expr list * pos) list
 
 type access =
 	| APublic

+ 4 - 4
codegen.ml

@@ -292,7 +292,7 @@ let build_metadata com t =
 			(t.t_pos, ["",t.t_meta],(match follow t.t_type with TAnon a -> PMap.fold (fun f acc -> (f.cf_name,f.cf_meta) :: acc) a.a_fields [] | _ -> []),[])
 	) in
 	let filter l =
-		let l = List.map (fun (n,ml) -> n, List.filter (fun (m,_) -> m.[0] <> ':') ml) l in
+		let l = List.map (fun (n,ml) -> n, List.filter (fun (m,_,_) -> m.[0] <> ':') ml) l in
 		List.filter (fun (_,ml) -> ml <> []) l
 	in
 	let meta, fields, statics = filter meta, filter fields, filter statics in
@@ -316,7 +316,7 @@ let build_metadata com t =
 			error "Metadata should be constant" p
 	in
 	let make_meta_field ml =
-		mk (TObjectDecl (List.map (fun (f,el) ->
+		mk (TObjectDecl (List.map (fun (f,el,_) ->
 			f, mk (match el with [] -> TConst TNull | _ -> TArrayDecl (List.map loop el)) (api.tarray t_dynamic) p
 		) ml)) (api.tarray t_dynamic) p
 	in
@@ -390,8 +390,8 @@ let on_generate ctx t =
 	| TClassDecl c ->
 		List.iter (fun m ->
 			match m with
-			| ":native",[Ast.EConst (Ast.String name),p] ->
-				c.cl_meta <- (":real",[Ast.EConst (Ast.String (s_type_path c.cl_path)),p]) :: c.cl_meta;
+			| ":native",[Ast.EConst (Ast.String name),p],mp ->
+				c.cl_meta <- (":real",[Ast.EConst (Ast.String (s_type_path c.cl_path)),p],mp) :: c.cl_meta;
 				c.cl_path <- parse_path name;
 			| _ -> ()
 		) c.cl_meta;

+ 2 - 2
genswf.ml

@@ -254,7 +254,7 @@ let build_class com c file =
 		let flags = if stat then AStatic :: flags else flags in
 		let name = (make_tpath f.hlf_name).tname in
 		let mk_meta() =
-			List.map (fun (s,cl) -> s, List.map (fun c -> EConst c,pos) cl) (!meta)
+			List.map (fun (s,cl) -> s, List.map (fun c -> EConst c,pos) cl, pos) (!meta)
 		in
 		let cf = {
 			cff_name = name;
@@ -408,7 +408,7 @@ let build_class com c file =
 		d_name = path.tname;
 		d_doc = None;
 		d_params = [];
-		d_meta = if c.hlc_final && List.exists (fun f -> f.cff_name <> "new" && not (List.mem AStatic f.cff_access)) fields then [":final",[]] else [];
+		d_meta = if c.hlc_final && List.exists (fun f -> f.cff_name <> "new" && not (List.mem AStatic f.cff_access)) fields then [":final",[],pos] else [];
 		d_flags = flags;
 		d_data = fields;
 	} in

+ 6 - 6
genswf9.ml

@@ -1825,7 +1825,7 @@ let generate_enum_init ctx e hc meta =
 let extract_meta meta =
 	let rec loop = function
 		| [] -> []
-		| (":meta",[ECall ((EConst (Ident n | Type n),_),args),_]) :: l ->
+		| (":meta",[ECall ((EConst (Ident n | Type n),_),args),_],_) :: l ->
 			let mk_arg (a,p) =
 				match a with
 				| EConst (String s) -> (None, s)
@@ -1858,8 +1858,8 @@ let generate_field_kind ctx f c stat =
 		| _ ->
 			let rec lookup_kind = function
 				| [] -> f.cf_name, MK3Normal
-				| (":getter",[EConst (Ident f | Type f),_]) :: _ -> f, MK3Getter
-				| (":setter",[EConst (Ident f | Type f),_]) :: _ -> f, MK3Setter
+				| (":getter",[EConst (Ident f | Type f),_],_) :: _ -> f, MK3Getter
+				| (":setter",[EConst (Ident f | Type f),_],_) :: _ -> f, MK3Setter
 				| _ :: l -> lookup_kind l
 			in
 			let name, kind = lookup_kind f.cf_meta in
@@ -1937,9 +1937,9 @@ let generate_class ctx c =
 				| [] -> ident f.cf_name
 				| x :: l ->
 					match x with
-					| ((":getter" | ":setter"),[EConst (Ident f | Type f),_]) -> ident f
-					| (":ns",[EConst (String ns),_]) -> HMName (f.cf_name,HNNamespace ns)
-					| (":protected",[]) ->
+					| ((":getter" | ":setter"),[EConst (Ident f | Type f),_],_) -> ident f
+					| (":ns",[EConst (String ns),_],_) -> HMName (f.cf_name,HNNamespace ns)
+					| (":protected",[],_) ->
 						let p = (match c.cl_path with [], n -> n | p, n -> String.concat "." p ^ ":" ^ n) in
 						has_protected := Some p;
 						HMName (f.cf_name,HNProtected p)

+ 3 - 3
genxml.ml

@@ -52,7 +52,7 @@ let gen_arg_name (name,opt,_) =
 let cpath c =
 	let rec loop = function
 		| [] -> c.cl_path
-		| (":real",[(Ast.EConst (Ast.String s),_)]) :: _ -> parse_path s
+		| (":real",[(Ast.EConst (Ast.String s),_)],_) :: _ -> parse_path s
 		| _ :: l -> loop l
 	in
 	loop c.cl_meta
@@ -286,7 +286,7 @@ let generate_type com t =
 			n ^ " : " ^ stype t ^ " = " ^ (s_constant v)
 	in
 	let print_meta ml =
-		List.iter (fun (m,pl) ->
+		List.iter (fun (m,pl,_) ->
 			match m with
 			| ":defparam" -> ()
 			| _ ->
@@ -315,7 +315,7 @@ let generate_type com t =
 					List.map (fun (a,o,t) ->
 						let rec loop = function
 							| [] -> Ident "null"
-							| (":defparam",[(EConst (String p),_);(EConst v,_)]) :: _ when p = a ->
+							| (":defparam",[(EConst (String p),_);(EConst v,_)],_) :: _ when p = a ->
 								(match v with
 								| Float "1.#QNAN" -> Float "0./*NaN*/"
 								| Float "4294967295." -> Int "0xFFFFFFFF"

+ 5 - 4
interp.ml

@@ -2794,17 +2794,18 @@ let encode_meta m set =
 	let meta = ref m in
 	enc_obj [
 		"get", VFunction (Fun0 (fun() ->
-			enc_array (List.map (fun (m,ml) ->
+			enc_array (List.map (fun (m,ml,p) ->
 				enc_obj [
 					"name", enc_string m;
 					"params", enc_array (List.map encode_expr ml);
+					"pos", encode_pos p;
 				]
 			) (!meta))
 		));
-		"add", VFunction (Fun2 (fun k vl ->
+		"add", VFunction (Fun3 (fun k vl p ->
 			(try
 				let el = List.map decode_expr (dec_array vl) in
-				meta := (dec_string k, el) :: !meta;
+				meta := (dec_string k, el, decode_pos p) :: !meta;
 				set (!meta)
 			with Invalid_expr ->
 				failwith "Invalid expression");
@@ -2812,7 +2813,7 @@ let encode_meta m set =
 		));
 		"remove", VFunction (Fun1 (fun k ->
 			let k = (try dec_string k with Invalid_expr -> raise Builtin_error) in
-			meta := List.filter (fun (m,_) -> m <> k) (!meta);
+			meta := List.filter (fun (m,_,_) -> m <> k) (!meta);
 			set (!meta);
 			VNull
 		));

+ 7 - 7
parser.ml

@@ -248,17 +248,17 @@ and parse_common_flags = parser
 	| [< >] -> []
 
 and parse_meta = parser
-	| [< '(At,_); name = meta_name; s >] ->
+	| [< '(At,_); name,p = meta_name; s >] ->
 		(match s with parser
-		| [< '(POpen,_); params = psep Comma expr; '(PClose,_); s >] -> (name,params) :: parse_meta s
-		| [< >] -> (name,[]) :: parse_meta s)
+		| [< '(POpen,_); params = psep Comma expr; '(PClose,_); s >] -> (name,params,p) :: parse_meta s
+		| [< >] -> (name,[],p) :: parse_meta s)
 	| [< >] -> []
 
 and meta_name = parser
-	| [< '(Const (Ident i),_) >] -> i
-	| [< '(Const (Type t),_) >] -> t
-	| [< '(Kwd k,_) >] -> s_keyword k
-	| [< '(DblDot,_); s >] -> ":" ^ meta_name s
+	| [< '(Const (Ident i),p) >] -> i, p
+	| [< '(Const (Type t),p) >] -> t, p
+	| [< '(Kwd k,p) >] -> s_keyword k,p
+	| [< '(DblDot,_); s >] -> let n, p = meta_name s in ":" ^ n, p
 
 and parse_enum_flags = parser
 	| [< '(Kwd Enum,p) >] -> [] , p

+ 2 - 2
std/haxe/macro/Type.hx

@@ -94,7 +94,7 @@ typedef DefType = {> BaseType,
 }
 
 typedef Metadata = {
-	function get() : Array<{ name : String, params : Array<Expr> }>;
-	function add( name : String, params : Array<Expr> ) : Void;
+	function get() : Array<{ name : String, params : Array<Expr>, pos : Expr.Position }>;
+	function add( name : String, params : Array<Expr>, pos : Expr.Position ) : Void;
 	function remove( name : String ) : Void;
 }

+ 2 - 2
type.ml

@@ -138,7 +138,7 @@ and tclass_kind =
 	| KGeneric
 	| KGenericInstance of tclass * tparams
 
-and metadata = (string * Ast.expr list) list
+and metadata = Ast.metadata
 
 and tclass = {
 	mutable cl_path : path;
@@ -523,7 +523,7 @@ let invalid_visibility n = Invalid_visibility n
 let has_no_field t n = Has_no_field (t,n)
 let has_extra_field t n = Has_extra_field (t,n)
 let error l = raise (Unify_error l)
-let has_meta m ml = List.exists (fun (m2,_) -> m = m2) ml
+let has_meta m ml = List.exists (fun (m2,_,_) -> m = m2) ml
 let no_meta = []
 
 (*

+ 2 - 6
typeload.ml

@@ -21,10 +21,6 @@ open Type
 open Common
 open Typecore
 
-(* make sure we don't access metadata at load time *)
-let has_meta m (ml:Ast.metadata) =
-	List.exists (fun(m2,_) -> m = m2) ml
-
 let type_function_param ctx t e opt p =
 	match e with
 	| None ->
@@ -890,7 +886,7 @@ let init_class ctx c p herits fields =
 	in
 	let rec check_require = function
 		| [] -> None
-		| (":require",conds) :: l ->
+		| (":require",conds,_) :: l ->
 			let rec loop = function
 				| [] -> check_require l
 				| (EConst (Ident i | Type i),_) :: l ->
@@ -1158,7 +1154,7 @@ let type_module ctx m tdecls loadp =
 			let names = ref [] in
 			let index = ref 0 in
 			let rec loop = function
-				| (":build",[ECall (epath,el),p]) :: _ ->
+				| (":build",[ECall (epath,el),p],_) :: _ ->
 					let rec loop (e,p) =
 						match e with
 						| EConst (Ident i) | EConst (Type i) -> i