Forráskód Böngészése

added TAnon type parameters (for signatures type display only).

Nicolas Cannasse 19 éve
szülő
commit
bd92af8476
3 módosított fájl, 23 hozzáadás és 19 törlés
  1. 1 1
      genxml.ml
  2. 10 9
      type.ml
  3. 12 9
      typer.ml

+ 1 - 1
genxml.ml

@@ -47,7 +47,7 @@ let rec gen_type t =
 	| TEnum (e,params) -> node "e" [gen_path e.e_path] (List.map gen_type params)
 	| TInst (c,params) -> node "c" [gen_path c.cl_path] (List.map gen_type params)
 	| TFun (args,r) -> node "f" ["a",String.concat ":" (List.map fst args)] (List.map gen_type (List.map snd args @ [r]))
-	| TAnon (fields,_) -> node "a" [] (pmap (fun f -> node f.cf_name [] [gen_type f.cf_type]) fields)
+	| TAnon (fields,_,_) -> node "a" [] (pmap (fun f -> node f.cf_name [] [gen_type f.cf_type]) fields)
 	| TDynamic t2 -> node "d" [] (if t == t2 then [] else [gen_type t2])
 	| TLazy f -> gen_type (!f())
 

+ 10 - 9
type.ml

@@ -29,7 +29,7 @@ type t =
 	| TEnum of tenum * t list
 	| TInst of tclass * t list
 	| TFun of (string * t) list * t
-	| TAnon of (string, tclass_field) PMap.t * string option
+	| TAnon of (string, tclass_field) PMap.t * t list * string option
 	| TDynamic of t
 	| TLazy of (unit -> t) ref
 
@@ -201,9 +201,9 @@ let rec s_type ctx t =
 		String.concat " -> " (List.map (fun (s,t) -> 
 			(if s = "" then "" else s ^ " : ") ^ s_fun ctx t true
 		) l) ^ " -> " ^ s_fun ctx t false
-	| TAnon (fl,name) ->
+	| TAnon (fl,tl,name) ->
 		(match name with
-		| Some s -> s
+		| Some s -> s ^ s_type_params ctx tl
 		| None ->
 			let fl = PMap.fold (fun f acc -> (" " ^ f.cf_name ^ " : " ^ s_type ctx f.cf_type) :: acc) fl [] in
 			"{" ^ String.concat "," fl ^ " }");
@@ -255,7 +255,8 @@ let rec link e a b =
 				loop t2
 		| TLazy f ->
 			loop (!f())
-		| TAnon (fl,_) ->
+		| TAnon (fl,tl,_) ->
+			List.exists loop tl ||
 			try
 				PMap.iter (fun _ f -> if loop f.cf_type then raise Exit) fl;
 				false
@@ -311,8 +312,8 @@ let apply_params cparams params t =
 				TInst (c,List.map loop tl))
 		| TFun (tl,r) ->
 			TFun (List.map (fun (s,t) -> s, loop t) tl,loop r)
-		| TAnon (fl,name) ->
-			TAnon (PMap.map (fun f -> { f with cf_type = loop f.cf_type }) fl,name)
+		| TAnon (fl,tl,name) ->
+			TAnon (PMap.map (fun f -> { f with cf_type = loop f.cf_type }) fl,List.map loop tl,name)
 		| TLazy f ->
 			loop (!f())
 		| TDynamic t2 ->
@@ -341,7 +342,7 @@ let rec type_eq param a b =
 		type_eq param r1 r2 && List.for_all2 (fun (_,t1) (_,t2) -> type_eq param t1 t2) l1 l2
 	| TDynamic a , TDynamic b ->
 		type_eq param a b
-	| TAnon (fl1,_), TAnon (fl2,_) ->
+	| TAnon (fl1,_,_), TAnon (fl2,_,_) ->
 		let keys1 = PMap.fold (fun f acc -> f :: acc) fl1 [] in
 		let keys2 = PMap.fold (fun f acc -> f :: acc) fl2 [] in
 		(try
@@ -421,7 +422,7 @@ let rec unify a b =
 			List.iter2 (fun (_,t1) (_,t2) -> unify t1 t2) l2 l1 (* contravariance *)
 		with
 			Unify_error l -> error (cannot_unify a b :: l))
-	| TInst (c,tl) , TAnon (fl,_) ->
+	| TInst (c,tl) , TAnon (fl,_,_) ->
 		(try
 			PMap.iter (fun n f2 ->
 				let f1 = (try PMap.find n c.cl_fields with Not_found -> error [has_no_field a n]) in
@@ -435,7 +436,7 @@ let rec unify a b =
 			) fl
 		with
 			Unify_error l -> error (cannot_unify a b :: l))
-	| TAnon (fl1,_) , TAnon (fl2,_) ->
+	| TAnon (fl1,_,_) , TAnon (fl2,_,_) ->
 		(try
 			PMap.iter (fun n f2 ->
 				let f1 = (try PMap.find n fl1 with Not_found -> error [has_no_field a n]) in

+ 12 - 9
typer.ml

@@ -265,7 +265,7 @@ let rec load_normal_type ctx t p allow_no_params =
 				let fields = PMap.map (fun f -> 
 					{ f with cf_type = apply_params s.s_types t f.cf_type }
 				) s.s_fields in
-				TAnon (fields,Some (s_type_path s.s_path))
+				TAnon (fields,t,Some (s_type_path s.s_path))
 			)
 		in
 		if allow_no_params && t.tparams = [] then
@@ -314,7 +314,7 @@ and load_type ctx p t =
 				cf_doc = None;
 			} acc
 		in
-		TAnon (List.fold_left loop PMap.empty l,None)
+		TAnon (List.fold_left loop PMap.empty l,[],None)
 	| TPFunction (args,r) ->
 		match args with
 		| [TPNormal { tpackage = []; tparams = []; tname = "Void" }] ->
@@ -335,8 +335,11 @@ let rec reverse_type t =
 		TPNormal { tpackage = fst c.cl_path; tname = snd c.cl_path; tparams = List.map reverse_type params }
 	| TFun (params,ret) ->
 		TPFunction (List.map (fun (_,t) -> reverse_type t) params,reverse_type ret)
-	| TAnon (fields,_) ->
+	| TAnon (fields,[],None) ->
 		TPAnonymous (PMap.fold (fun f acc -> (f.cf_name , reverse_type f.cf_type) :: acc) fields [])
+	| TAnon (_,params,Some name) when name.[0] != '#' ->
+		let path = List.rev (ExtString.String.nsplit "." name) in
+		TPNormal { tpackage = List.rev (List.tl path); tname = List.hd path; tparams = List.map reverse_type params }
 	| TDynamic t2 ->
 		TPNormal { tpackage = []; tname = "Dynamic"; tparams = if t == t2 then [] else [reverse_type t2] }
 	| _ ->
@@ -517,7 +520,7 @@ let t_iterator ctx =
 		let fields = PMap.map (fun f -> 
 			{ f with cf_type = apply_params s.s_types [pt] f.cf_type }
 		) s.s_fields in
-		TAnon (fields,Some "Iterator") , pt
+		TAnon (fields,[pt],Some "Iterator") , pt
 	| _ ->
 		assert false
 
@@ -567,7 +570,7 @@ let unify_call_params ctx t el args p =
 			el
 		| [] , [(_,t)] ->
 			(match follow t with
-			| TAnon (_,Some "haxe.PosInfos") ->
+			| TAnon (_,[],Some "haxe.PosInfos") ->
 				let infos = mk_infos ctx p [] in
 				let e = (!type_expr_ref) ctx ~need_val:true infos in
 				el @ [e]
@@ -709,7 +712,7 @@ let type_type ctx tpath p =
 				cf_expr = None;
 			} acc
 		) c.cl_statics PMap.empty in
-		mk (TType (TClassDecl c)) (TAnon (fl,Some ("#" ^ s_type_path c.cl_path))) p
+		mk (TType (TClassDecl c)) (TAnon (fl,types,Some ("#" ^ s_type_path c.cl_path))) p
 	| TEnumDecl e ->
 		let types = List.map (fun _ -> mk_mono()) e.e_types in
 		let fl = PMap.fold (fun f acc ->
@@ -724,7 +727,7 @@ let type_type ctx tpath p =
 				cf_params = [];
 			} acc
 		) e.e_constrs PMap.empty in
-		mk (TType (TEnumDecl e)) (TAnon (fl,Some ("#" ^ s_type_path e.e_path))) p
+		mk (TType (TEnumDecl e)) (TAnon (fl,types,Some ("#" ^ s_type_path e.e_path))) p
 	| TSignatureDecl _ ->
 		error (s_type_path tpath ^ " is not a value") p
 
@@ -849,7 +852,7 @@ let type_field ctx e i p get =
 			no_field())
 	| TDynamic t ->
 		AccExpr (mk (TField (e,i)) t p)
-	| TAnon (fl,_) ->
+	| TAnon (fl,_,_) ->
 		(try
 			let f = PMap.find i fl in
 			if not f.cf_public && not ctx.untyped then error ("Cannot access to private field " ^ i) p;
@@ -1254,7 +1257,7 @@ and type_expr ctx ?(need_val=true) (e,p) =
 			((f,e) :: l, PMap.add f cf acc)
 		in
 		let fields , types = List.fold_left loop ([],PMap.empty) fl in
-		mk (TObjectDecl fields) (TAnon (types,None)) p
+		mk (TObjectDecl fields) (TAnon (types,[],None)) p
 	| EArrayDecl el ->
 		let t , pt = t_array ctx in
 		let dyn = ref ctx.untyped in