Ver Fonte

deal with all warning cases

Simon Krajewski há 3 anos atrás
pai
commit
4cbdd09e8a

+ 3 - 0
src/codegen/codegen.ml

@@ -109,6 +109,9 @@ let update_cache_dependencies t =
 				()
 			else
 				check_t m t
+		| TIntersection(t1,t2) ->
+			check_t m t1;
+			check_t m t2;
 	and check_field m cf =
 		check_t m cf.cf_type
 	in

+ 1 - 1
src/codegen/gencommon/gencommon.ml

@@ -1116,7 +1116,7 @@ let rec replace_mono t =
 		List.iter (fun (_,_,t) -> replace_mono t) args;
 		replace_mono ret
 	| TAnon _
-	| TDynamic _ -> ()
+	| TDynamic _ | TIntersection _ -> ()
 	| TLazy f ->
 		replace_mono (lazy_type f)
 

+ 1 - 1
src/codegen/gencommon/normalize.ml

@@ -60,7 +60,7 @@ let rec filter_param (stack:t list) t =
 		mk_anon ~fields a.a_status
 	| TFun(args,ret) ->
 		TFun(List.map (fun (n,o,t) -> (n,o,filter_param stack t)) args, filter_param stack ret)
-	| TDynamic _ ->
+	| TDynamic _ | TIntersection _ ->
 		t
 	| TLazy f ->
 		filter_param stack (lazy_type f)

+ 1 - 0
src/codegen/genxml.ml

@@ -124,6 +124,7 @@ let rec gen_type ?(values=None) t =
 	| TAnon a -> node "a" [] (pmap (fun f -> gen_field [] { f with cf_flags = unset_flag f.cf_flags (int_of_class_field_flag CfPublic) }) a.a_fields)
 	| TDynamic t2 -> node "d" [] (if t == t2 then [] else [gen_type t2])
 	| TLazy f -> gen_type (lazy_type f)
+	| TIntersection(t1,t2) -> node "d" [] [] (* TINTERSECTODO *)
 
 and gen_type_decl n t pl =
 	let i = t_infos t in

+ 1 - 0
src/codegen/overloads.ml

@@ -114,6 +114,7 @@ struct
 		| TDynamic _ -> t
 		| TLazy f -> simplify_t (lazy_type f)
 		| TFun _ -> t
+		| TIntersection(t1,t2) -> TIntersection(simplify_t t1,simplify_t t2)
 
 	(* rate type parameters *)
 	let rate_tp tlfun tlarg =

+ 1 - 1
src/compiler/displayOutput.ml

@@ -396,7 +396,7 @@ let promote_type_hints tctx =
 		| TAbstract(({a_name_pos = pn;a_path = (_,name)}),_) ->
 			md.m_type_hints <- (p,pn) :: md.m_type_hints;
 		| TDynamic _ -> ()
-		| TFun _ | TAnon _ -> ()
+		| TFun _ | TAnon _ | TIntersection _ -> ()
 	in
 	List.iter explore_type_hint tctx.g.type_hints
 

+ 2 - 0
src/core/display/completionItem.ml

@@ -507,6 +507,8 @@ module CompletionType = struct
 				}
 			| TDynamic t ->
 				CTDynamic (if t == t_dynamic then None else Some (from_type PMap.empty t))
+			| TIntersection(t1,t2) ->
+				CTDynamic None (* TINTERSECTODO *)
 		in
 		from_type values t
 end

+ 2 - 0
src/core/error.ml

@@ -192,6 +192,8 @@ module BetterErrors = struct
 			"Dynamic" ^ s_type_params ctx (if t == t2 then [] else [t2])
 		| TLazy f ->
 			s_type ctx (lazy_type f)
+		| TIntersection(t1,t2) ->
+			Printf.sprintf "(%s & %s)" (s_type ctx t1) (s_type ctx t2)
 
 	and s_type_params ctx = function
 		| [] -> ""

+ 1 - 0
src/core/json/genjson.ml

@@ -225,6 +225,7 @@ let rec generate_type ctx t =
 		| TAbstract(a,tl) -> "TAbstract",Some (generate_type_path_with_params ctx a.a_module.m_path a.a_path tl a.a_meta)
 		| TAnon an -> "TAnonymous", Some(generate_anon ctx an)
 		| TFun(tl,tr) -> "TFun", Some (jobject (generate_function_signature ctx tl tr))
+		| TIntersection(t1,t2) -> "TIntersection", None (* TINTERSECTODO *)
 	in
 	let name,args = loop t in
 	generate_adt ctx None name args

+ 12 - 3
src/core/tFunctions.ml

@@ -276,6 +276,8 @@ let map loop t =
 		if ft == ft2 then t else ft2
 	| TDynamic t2 ->
 		if t == t2 then	t else TDynamic (loop t2)
+	| TIntersection(t1,t2) ->
+		TIntersection(loop t1,loop t2)
 
 let iter loop t =
 	match t with
@@ -303,6 +305,9 @@ let iter loop t =
 		loop ft
 	| TDynamic t2 ->
 		if t != t2 then	loop t2
+	| TIntersection(t1,t2) ->
+		loop t1;
+		loop t2
 
 let duplicate t =
 	let monos = ref [] in
@@ -433,6 +438,8 @@ let apply_params ?stack cparams params t =
 				t
 			else
 				TDynamic (loop t2)
+		| TIntersection(t1,t2) ->
+			TIntersection(loop t1,loop t2)
 	in
 	loop t
 
@@ -474,7 +481,7 @@ let follow_once t =
 		(match r.tm_type with
 		| None -> t
 		| Some t -> t)
-	| TAbstract _ | TEnum _ | TInst _ | TFun _ | TAnon _ | TDynamic _ ->
+	| TAbstract _ | TEnum _ | TInst _ | TFun _ | TAnon _ | TDynamic _ | TIntersection _ ->
 		t
 	| TType (t,tl) ->
 		apply_params t.t_params tl t.t_type
@@ -583,6 +590,8 @@ let rec has_mono t = match t with
 		PMap.fold (fun cf b -> has_mono cf.cf_type || b) a.a_fields false
 	| TLazy f ->
 		has_mono (lazy_type f)
+	| TIntersection(t1,t2) ->
+		has_mono t1 || has_mono t2
 
 let concat e1 e2 =
 	let e = (match e1.eexpr, e2.eexpr with
@@ -741,7 +750,7 @@ let quick_field t n =
 			FAnon (PMap.find n a.a_fields))
 	| TDynamic _ ->
 		FDynamic n
-	| TEnum _  | TMono _ | TAbstract _ | TFun _ ->
+	| TEnum _  | TMono _ | TAbstract _ | TFun _ | TIntersection _ (* TINTERSECTODO *) ->
 		raise Not_found
 	| TLazy _ | TType _ ->
 		die "" __LOC__
@@ -790,7 +799,7 @@ let resolve_typedef t =
 *)
 let type_has_meta t m =
 	match t with
-		| TMono _ | TFun _ | TAnon _ | TDynamic _ | TLazy _ -> false
+		| TMono _ | TFun _ | TAnon _ | TDynamic _ | TLazy _ | TIntersection _ -> false
 		| TEnum ({ e_meta = metadata }, _)
 		| TInst ({ cl_meta = metadata }, _)
 		| TType ({ t_meta = metadata }, _)

+ 2 - 0
src/core/tOther.ml

@@ -56,6 +56,8 @@ module TExprToExpr = struct
 			tpath ([],"Dynamic") ([],"Dynamic") (if t == t_dynamic then [] else [tparam t2])
 		| TLazy f ->
 			convert_type (lazy_type f)
+		| TIntersection(t1,t2) ->
+			CTIntersection[convert_type' t1;convert_type' t2]
 
 	and convert_type' t =
 		convert_type t,null_pos

+ 3 - 0
src/core/tPrinting.ml

@@ -21,6 +21,7 @@ let rec s_type_kind t =
 	| TAnon an -> "TAnon"
 	| TDynamic t2 -> "TDynamic"
 	| TLazy _ -> "TLazy"
+	| TIntersection(t1,t2) -> Printf.sprintf "TIntersection(%s, %s)" (s_type_kind t1) (s_type_kind t2)
 
 let s_module_type_kind = function
 	| TClassDecl c -> "TClassDecl(" ^ (s_type_path c.cl_path) ^ ")"
@@ -91,6 +92,8 @@ let rec s_type ctx t =
 		"Dynamic" ^ s_type_params ctx (if t == t2 then [] else [t2])
 	| TLazy f ->
 		s_type ctx (lazy_type f)
+	| TIntersection(t1,t2) ->
+		Printf.sprintf "(%s & %s)" (s_type ctx t1) (s_type ctx t2)
 
 and s_fun ctx t void =
 	match t with

+ 1 - 0
src/core/tType.ml

@@ -41,6 +41,7 @@ type t =
 	| TDynamic of t
 	| TLazy of tlazy ref
 	| TAbstract of tabstract * tparams
+	| TIntersection of t * t
 
 and tmono = {
 	mutable tm_type : t option;

+ 4 - 1
src/core/tUnification.ml

@@ -304,11 +304,14 @@ let rec link e a b =
 		| TLazy f ->
 			loop (lazy_type f)
 		| TAnon a ->
-			try
+			begin try
 				PMap.iter (fun _ f -> if loop f.cf_type then raise Exit) a.a_fields;
 				false
 			with
 				Exit -> true
+			end
+		| TIntersection(t1,t2) ->
+			loop t1 || loop t2
 	in
 	(* tell is already a ~= b *)
 	if loop b then

+ 2 - 2
src/generators/gencpp.ml

@@ -814,7 +814,7 @@ and type_string_suff suffix haxe_type remap =
       | EnumStatics e -> type_string_suff suffix (TEnum (e,List.map snd e.e_params))
       | _ -> "Dynamic"  ^ suffix )
       *)
-   | TDynamic haxe_type -> "Dynamic" ^ suffix
+   | TDynamic _ | TIntersection _ -> "Dynamic" ^ suffix
    | TLazy func -> type_string_suff suffix (lazy_type func) remap
    | TAbstract (abs,pl) when abs.a_impl <> None ->
       type_string_suff suffix (Abstract.get_underlying_type abs pl) remap
@@ -1777,7 +1777,7 @@ let rec cpp_type_of stack ctx haxe_type =
 
       | TFun _ -> TCppObject
       | TAnon _ -> TCppObject
-      | TDynamic _ -> TCppDynamic
+      | TDynamic _ | TIntersection _ -> TCppDynamic
       | TLazy func -> cpp_type_of stack ctx (lazy_type func)
       )
    end

+ 1 - 1
src/generators/genhl.ml

@@ -421,7 +421,7 @@ let rec to_type ?tref ctx t =
 			Array.iteri (fun i (n,_,_) -> vp.vindex <- PMap.add n i vp.vindex) vp.vfields;
 			t
 		)
-	| TDynamic _ ->
+	| TDynamic _ | TIntersection _ ->
 		HDyn
 	| TEnum (e,_) ->
 		enum_type ~tref ctx e

+ 2 - 0
src/generators/genhxold.ml

@@ -110,6 +110,8 @@ let generate_type com t =
 			"() -> " ^ ftype ret
 		| TFun (args,ret) ->
 			String.concat " -> " (List.map (fun (_,_,t) -> ftype t) args) ^ " -> " ^ ftype ret
+		| TIntersection(t1,t2) ->
+			"(" ^ (ftype t1) ^ " & " ^ (ftype t2) ^ ")"
 	and ftype t =
 		match t with
 		| TMono r ->

+ 1 - 1
src/generators/genjvm.ml

@@ -150,7 +150,7 @@ let rec jsignature_of_type gctx stack t =
 				else
 					jsignature_of_type (Abstract.get_underlying_type a tl)
 		end
-	| TDynamic _ -> object_sig
+	| TDynamic _ | TIntersection _ -> object_sig
 	| TMono r ->
 		begin match r.tm_type with
 		| Some t -> jsignature_of_type t

+ 1 - 1
src/generators/genphp7.ml

@@ -1395,7 +1395,7 @@ class code_writer (ctx:php_generator_context) hx_type_path php_name =
 					)
 				| TFun _ -> self#use ~prefix:false ([], "Closure")
 				| TAnon _ -> "object"
-				| TDynamic _ -> "mixed"
+				| TDynamic _ | TIntersection _ -> "mixed"
 				| TLazy _ -> fail ~msg:"TLazy not implemented" self#pos __LOC__
 				| TMono mono ->
 					(match mono.tm_type with

+ 3 - 0
src/generators/genswf.ml

@@ -94,6 +94,9 @@ let build_dependencies t =
 		| TType (tt,pl) ->
 			add_type_rec (t::l) tt.t_type;
 			List.iter (add_type_rec (t::l)) pl
+		| TIntersection(t1,t2) ->
+			add_type_rec l t1;
+			add_type_rec l t2
 	and add_type t =
 		add_type_rec [] t
 	and add_expr e =

+ 1 - 1
src/generators/genswf9.ml

@@ -301,7 +301,7 @@ let classify ctx t =
 		KType (type_id ctx t)
 	| TMono _
 	| TType _
-	| TDynamic _ ->
+	| TDynamic _ | TIntersection _ ->
 		KDynamic
 	| TLazy _ ->
 		die "" __LOC__

+ 1 - 1
src/macro/eval/evalJit.ml

@@ -31,7 +31,7 @@ open EvalMisc
 let rope_path t = match follow t with
 	| TInst({cl_path=path},_) | TEnum({e_path=path},_) | TAbstract({a_path=path},_) -> s_type_path path
 	| TDynamic _ -> "Dynamic"
-	| TFun _ | TAnon _ | TMono _ | TType _ | TLazy _ -> die "" __LOC__
+	| TFun _ | TAnon _ | TMono _ | TType _ | TLazy _ | TIntersection _  -> die "" __LOC__
 
 let eone = mk (TConst(TInt (Int32.one))) t_dynamic null_pos
 

+ 1 - 1
src/macro/eval/evalMain.ml

@@ -585,7 +585,7 @@ let handle_decoding_error f v t =
 					end
 				| _ -> error "expected enum value" v
 			end
-		| TInst _ | TAbstract _ | TFun _ ->
+		| TInst _ | TAbstract _ | TFun _ | TIntersection _ ->
 			(* TODO: might need some more of these, not sure *)
 			die "" __LOC__
 		| TMono r ->

+ 3 - 1
src/macro/macroApi.ml

@@ -1089,6 +1089,8 @@ and encode_type t =
 			loop (lazy_type f)
 		| TAbstract (a, pl) ->
 			8, [encode_abref a; encode_tparams pl]
+		| TIntersection(t1,t2) ->
+			9, [encode_type t1;encode_type t2]
 	in
 	let tag, pl = loop t in
 	encode_enum IType tag pl
@@ -1833,7 +1835,7 @@ let macro_api ccom get_api =
 					| Some t -> t)
 				| TAbstract (a,tl) when not (Meta.has Meta.CoreType a.a_meta) ->
 					Abstract.get_underlying_type a tl
-				| TAbstract _ | TEnum _ | TInst _ | TFun _ | TAnon _ | TDynamic _ ->
+				| TAbstract _ | TEnum _ | TInst _ | TFun _ | TAnon _ | TDynamic _ |  TIntersection _ ->
 					t
 				| TType (t,tl) ->
 					apply_params t.t_params tl t.t_type

+ 4 - 1
src/optimization/dce.ml

@@ -250,6 +250,9 @@ and mark_t dce p t =
 			if not (Meta.has Meta.CoreType a.a_meta) then
 				mark_t dce p (Abstract.get_underlying_type a pl)
 		| TLazy _ | TDynamic _ | TType _ | TAnon _ | TMono _ -> ()
+		| TIntersection(t1,t2) ->
+			mark_t dce p t1;
+			mark_t dce p t2;
 		end;
 		dce.t_stack <- List.tl dce.t_stack
 	end
@@ -317,7 +320,7 @@ let rec to_string dce t = match t with
 			()
 		else
 			to_string dce t
-	| TEnum _ | TFun _ | TAnon _ | TAbstract({a_impl = None},_) ->
+	| TEnum _ | TFun _ | TAnon _ | TAbstract({a_impl = None},_) | TIntersection _ ->
 		(* if we to_string these it does not imply that we need all its sub-types *)
 		()
 

+ 3 - 0
src/typing/generic.ml

@@ -240,6 +240,9 @@ let rec build_generic ctx c p tl =
 			| TFun (args,ret) ->
 				List.iter (fun (_,_,t) -> loop t) args;
 				loop ret
+			| TIntersection(t1,t2) ->
+				loop t1;
+				loop t2;
 			end
 		and add_dep m tl =
 			add_dependency mg m;

+ 1 - 1
src/typing/nullSafety.ml

@@ -370,7 +370,7 @@ let rec can_pass_type src dst =
 			| TType (t, tl) -> can_pass_type src (apply_params t.t_params tl t.t_type)
 			| TFun _ -> true
 			| TAnon _ -> true
-			| TDynamic _ -> true
+			| TDynamic _ | TIntersection _ -> true
 			| TLazy _ -> true
 			| TAbstract ({ a_path = ([],"Null") }, [t]) -> true
 			| TAbstract _ -> true

+ 1 - 0
src/typing/typeloadFields.ml

@@ -739,6 +739,7 @@ module TypeBinding = struct
 			| TFun (args,ret) -> is_full_type ret && List.for_all (fun (_,_,t) -> is_full_type t) args
 			| TMono r -> (match r.tm_type with None -> false | Some t -> is_full_type t)
 			| TAbstract _ | TInst _ | TEnum _ | TLazy _ | TDynamic _ | TAnon _ | TType _ -> true
+			| TIntersection(t1,t2) -> is_full_type t1 && is_full_type t2
 		in
 		let force_macro () =
 			(* force macro system loading of this class in order to get completion *)