ソースを参照

Change Null<T> to an abstract (#6380)

* use abstract instead of typedef for Null<T>

* make Null<T> a @:coreType (broken on C#/Java)

* fix infinite recursion

* fix flash

* fix overloads
Simon Krajewski 8 年 前
コミット
bdfb602c8a

+ 1 - 1
src/filters/defaultArguments.ml

@@ -29,7 +29,7 @@ open Codegen.ExprBuilder
 
 let gen_check basic t nullable_var const pos =
 	let needs_cast t1 t2 =
-		let is_null t = match t with TType ({t_path = ([],"Null")}, _) -> true | _ -> false in
+		let is_null t = match t with TAbstract ({a_path = ([],"Null")}, _) -> true | _ -> false in
 		(is_null t1) <> (is_null t2)
 	in
 

+ 7 - 10
src/generators/genas3.ml

@@ -247,6 +247,13 @@ let rec type_str ctx t p =
 	match t with
 	| TEnum _ | TInst _ when List.memq t ctx.local_types ->
 		"*"
+	| TAbstract ({a_path = [],"Null"},[t]) ->
+		(match follow t with
+		| TAbstract ({ a_path = [],"UInt" },_)
+		| TAbstract ({ a_path = [],"Int" },_)
+		| TAbstract ({ a_path = [],"Float" },_)
+		| TAbstract ({ a_path = [],"Bool" },_) -> "*"
+		| _ -> type_str ctx t p)
 	| TAbstract (a,pl) when not (Meta.has Meta.CoreType a.a_meta) ->
 		type_str ctx (Abstract.get_underlying_type a pl) p
 	| TAbstract (a,_) ->
@@ -291,16 +298,6 @@ let rec type_str ctx t p =
 	| TType (t,args) ->
 		(match t.t_path with
 		| [], "UInt" -> "uint"
-		| [] , "Null" ->
-			(match args with
-			| [t] ->
-				(match follow t with
-				| TAbstract ({ a_path = [],"UInt" },_)
-				| TAbstract ({ a_path = [],"Int" },_)
-				| TAbstract ({ a_path = [],"Float" },_)
-				| TAbstract ({ a_path = [],"Bool" },_) -> "*"
-				| _ -> type_str ctx t p)
-			| _ -> assert false);
 		| _ -> type_str ctx (apply_params t.t_params args t.t_type) p)
 	| TLazy f ->
 		type_str ctx ((!f)()) p

+ 4 - 0
src/generators/gencommon.ml

@@ -111,6 +111,8 @@ let follow_once t =
 		!f()
 	| TType (t,tl) ->
 		apply_params t.t_params tl t.t_type
+	| TAbstract({a_path = [],"Null"},[t]) ->
+		t
 	| _ ->
 		t
 
@@ -657,6 +659,8 @@ let init_ctx gen =
 			follow_f (!f())
 		| TType (t,tl) ->
 			follow_f (apply_params t.t_params tl t.t_type)
+		| TAbstract({a_path = [],"Null"},[t]) ->
+			follow_f t
 		| _ -> Some t
 	in
 	gen.gfollow#add "final" PLast follow

+ 1 - 1
src/generators/gencommon/closuresToClass.ml

@@ -653,7 +653,7 @@ struct
 		in
 
 		let rettype_real_to_func t = match run_follow gen t with
-			| TType({ t_path = [],"Null" }, _) ->
+			| TAbstract({ a_path = [],"Null" }, _) ->
 				0,t_dynamic
 			| _ when like_float t && not (like_i64 t) ->
 				(1, basic.tfloat)

+ 4 - 4
src/generators/gencommon/hardNullableSynf.ml

@@ -45,7 +45,7 @@ let name = "hard_nullable"
 let priority = solve_deps name [DAfter CastDetect.ReturnCast.priority]
 
 let rec is_null_t gen t = match gen.greal_type t with
-	| TType( { t_path = ([], "Null") }, [of_t])
+	| TAbstract( { a_path = ([], "Null") }, [of_t])
 	| TInst( { cl_path = (["haxe";"lang"], "Null") }, [of_t]) ->
 		let rec take_off_null t =
 			match is_null_t gen t with | None -> t | Some s -> take_off_null s
@@ -63,13 +63,13 @@ let follow_addon gen t =
 		let t = gen.gfollow#run_f t in
 		match t with
 			(* haxe.lang.Null<haxe.lang.Null<>> wouldn't be a valid construct, so only follow Null<> *)
-			| TType ( { t_path = ([], "Null") }, [of_t] ) -> strip_off_nullable of_t
+			| TAbstract ( { a_path = ([], "Null") }, [of_t] ) -> strip_off_nullable of_t
 			| _ -> t
 	in
 
 	match t with
-		| TType( ({ t_path = ([], "Null") } as tdef), [of_t]) ->
-			Some( TType(tdef, [ strip_off_nullable of_t ]) )
+		| TAbstract( ({ a_path = ([], "Null") } as tab), [of_t]) ->
+			Some( TAbstract(tab, [ strip_off_nullable of_t ]) )
 		| _ -> None
 
 let configure gen unwrap_null wrap_val null_to_dynamic has_value opeq_handler =

+ 2 - 0
src/generators/gencommon/normalize.ml

@@ -47,6 +47,8 @@ let rec filter_param t =
 		TEnum(e,List.map filter_param tl)
 	| TAbstract({ a_path = (["haxe";"extern"],"Rest") } as a,tl) ->
 		TAbstract(a, List.map filter_param tl)
+	| TAbstract({a_path = [],"Null"} as a,[t]) ->
+		TAbstract(a,[filter_param t])
 	| TAbstract(a,tl) when not (Meta.has Meta.CoreType a.a_meta) ->
 		filter_param (Abstract.get_underlying_type a tl)
 	| TAbstract(a,tl) ->

+ 2 - 2
src/generators/gencommon/switchToIf.ml

@@ -45,10 +45,10 @@ let configure gen (should_convert:texpr->bool) =
 		| TSwitch (cond, cases, default) when should_convert e ->
 			let cond_etype, should_cache =
 				match gen.gfollow#run_f cond.etype with
-				| TType ({ t_path = [], "Null" }, [t]) ->
+				| TAbstract ({ a_path = [], "Null" }, [t]) ->
 					let rec take_off_nullable t =
 						match gen.gfollow#run_f t with
-						| TType ({ t_path = [], "Null" }, [t]) -> take_off_nullable t
+						| TAbstract ({ a_path = [], "Null" }, [t]) -> take_off_nullable t
 						| _ -> t
 					in
 					take_off_nullable t, true

+ 8 - 11
src/generators/gencpp.ml

@@ -760,20 +760,17 @@ and type_string_suff suffix haxe_type remap =
    | TAbstract ({ a_path = ([],"Int") },[]) -> "int"
    | TAbstract ({ a_path = (["cpp"],"UInt8") },[]) -> "unsigned char"
    | TAbstract( { a_path = ([], "EnumValue") }, _  ) -> "Dynamic"
+   | TAbstract ({ a_path = ([],"Null") }, [t]) ->
+		(match follow t with
+		| TAbstract ({ a_path = [],"Int" },_)
+		| TAbstract ({ a_path = [],"Float" },_)
+		| TAbstract ({ a_path = [],"Bool" },_) -> "Dynamic" ^ suffix
+		| t when type_has_meta_key t Meta.NotNull -> "Dynamic" ^ suffix
+		| _ -> type_string_suff suffix t remap)
    | TEnum (enum,params) ->  "::" ^ (join_class_path_remap enum.e_path "::") ^ suffix
    | TInst (klass,params) ->  (class_string klass suffix params remap)
    | TType (type_def,params) ->
       (match type_def.t_path with
-      | [] , "Null" ->
-         (match params with
-         | [t] ->
-            (match follow t with
-            | TAbstract ({ a_path = [],"Int" },_)
-            | TAbstract ({ a_path = [],"Float" },_)
-            | TAbstract ({ a_path = [],"Bool" },_) -> "Dynamic" ^ suffix
-            | t when type_has_meta_key t Meta.NotNull -> "Dynamic" ^ suffix
-            | _ -> type_string_suff suffix t remap)
-         | _ -> assert false);
       | [] , "Array" ->
          (match params with
          | [t] when (type_string (follow t) ) = "Dynamic" -> "Dynamic"
@@ -6770,7 +6767,7 @@ let is_assign_op op =
 
 let rec script_type_string haxe_type =
    match haxe_type with
-   | TType ({ t_path = ([],"Null") },[t]) ->
+   | TAbstract ({ a_path = ([],"Null") },[t]) ->
       (match follow t with
       | TAbstract ({ a_path = [],"Int" },_)
       | TAbstract ({ a_path = [],"Float" },_)

+ 21 - 21
src/generators/gencs.ml

@@ -94,7 +94,7 @@ let is_pointer gen t =
 let rec is_null t =
 	match t with
 		| TInst( { cl_path = (["haxe"; "lang"], "Null") }, _ )
-		| TType( { t_path = ([], "Null") }, _ ) -> true
+		| TAbstract( { a_path = ([], "Null") }, _ ) -> true
 		| TType( t, tl ) -> is_null (apply_params t.t_params tl t.t_type)
 		| TMono r ->
 			(match !r with
@@ -786,8 +786,8 @@ let generate con =
 				| TAbstract ({ a_path = ["cs"],"Out" },_)
 				| TType ({ t_path = [],"Single" },[])
 				| TAbstract ({ a_path = [],"Single" },[]) -> Some t
-				| TType (({ t_path = [],"Null" } as tdef),[t2]) ->
-						Some (TType(tdef,[follow (gen.gfollow#run_f t2)]))
+				| TAbstract (({ a_path = [],"Null" } as tab),[t2]) ->
+						Some (TAbstract(tab,[follow (gen.gfollow#run_f t2)]))
 				| TAbstract({ a_path = ["cs"],"PointerAccess" },[t]) ->
 						Some (TAbstract(ptr,[t]))
 				| TAbstract (a, pl) when not (Meta.has Meta.CoreType a.a_meta) ->
@@ -827,6 +827,23 @@ let generate con =
 		let rec real_type t =
 			let t = gen.gfollow#run_f t in
 			let ret = match t with
+				| TAbstract({ a_path = ([], "Null") }, [t]) ->
+					(*
+						Null<> handling is a little tricky.
+						It will only change to haxe.lang.Null<> when the actual type is non-nullable or a type parameter
+						It works on cases such as Hash<T> returning Null<T> since cast_detect will invoke real_type at the original type,
+						Null<T>, which will then return the type haxe.lang.Null<>
+					*)
+					if erase_generics then
+						if is_cs_basic_type t then
+							t_dynamic
+						else
+							real_type t
+					else
+						(match real_type t with
+							| TInst( { cl_kind = KTypeParameter _ }, _ ) -> TInst(null_t, [t])
+							| t when is_cs_basic_type t -> TInst(null_t, [t])
+							| _ -> real_type t)
 				| TAbstract (a, pl) when not (Meta.has Meta.CoreType a.a_meta) ->
 					real_type (Abstract.get_underlying_type a pl)
 				| TAbstract ({ a_path = (["cs";"_Flags"], "EnumUnderlying") }, [t]) ->
@@ -854,23 +871,6 @@ let generate con =
 				| TInst(cl, params) when Meta.has Meta.Enum cl.cl_meta ->
 					TInst(cl, List.map (fun _ -> t_dynamic) params)
 				| TInst(cl, params) -> TInst(cl, change_param_type (TClassDecl cl) params)
-				| TType({ t_path = ([], "Null") }, [t]) ->
-					(*
-						Null<> handling is a little tricky.
-						It will only change to haxe.lang.Null<> when the actual type is non-nullable or a type parameter
-						It works on cases such as Hash<T> returning Null<T> since cast_detect will invoke real_type at the original type,
-						Null<T>, which will then return the type haxe.lang.Null<>
-					*)
-					if erase_generics then
-						if is_cs_basic_type t then
-							t_dynamic
-						else
-							real_type t
-					else
-						(match real_type t with
-							| TInst( { cl_kind = KTypeParameter _ }, _ ) -> TInst(null_t, [t])
-							| t when is_cs_basic_type t -> TInst(null_t, [t])
-							| _ -> real_type t)
 				| TAbstract _
 				| TType _ -> t
 				| TAnon (anon) when (match !(anon.a_status) with | Statics _ | EnumStatics _ | AbstractStatics _ -> true | _ -> false) -> t
@@ -2944,7 +2944,7 @@ let generate con =
 		in
 
 		let may_nullable t = match gen.gfollow#run_f t with
-			| TType({ t_path = ([], "Null") }, [t]) ->
+			| TAbstract({ a_path = ([], "Null") }, [t]) ->
 				(match follow t with
 					| TInst({ cl_path = ([], "String") }, [])
 					| TAbstract ({ a_path = ([], "Float") },[])

+ 10 - 3
src/generators/genhl.ml

@@ -334,6 +334,12 @@ let make_debug ctx arr =
 	done;
 	out
 
+let fake_tnull =
+	{null_abstract with
+		a_path = [],"Null";
+		a_params = ["T",t_dynamic];
+	}
+
 let rec to_type ?tref ctx t =
 	match t with
 	| TMono r ->
@@ -353,7 +359,6 @@ let rec to_type ?tref ctx t =
 			t
 		) in
 		(match td.t_path with
-		| [], "Null" when not (is_nullable t) -> HNull t
 		| ["haxe";"macro"], name -> Hashtbl.replace ctx.macro_typedefs name t; t
 		| _ -> t)
 	| TLazy f ->
@@ -425,6 +430,9 @@ let rec to_type ?tref ctx t =
 			in
 			loop tl
 		| _ -> class_type ~tref ctx c pl false)
+	| TAbstract ({a_path = [],"Null"},[t1]) ->
+		let t = to_type ?tref ctx t1 in
+		if not (is_nullable t) then HNull t else t
 	| TAbstract (a,pl) ->
 		if Meta.has Meta.CoreType a.a_meta then
 			(match a.a_path with
@@ -501,8 +509,7 @@ and real_type ctx e =
 						If we have a number, it is more accurate to cast it to the type parameter before wrapping it as dynamic
 					*)
 					| TInst ({cl_kind=KTypeParameter _},_), t when is_number (to_type ctx t) ->
-						let tnull = { t_path = [],"Null"; t_module = null_module; t_pos = null_pos; t_name_pos = null_pos; t_private = false; t_doc = None; t_meta = []; t_params = ["T",t_dynamic]; t_type = t_dynamic } in
-						(name, opt, TType (tnull,[t]))
+						(name, opt, TAbstract (fake_tnull,[t]))
 					| _ ->
 						a
 				) args args2, ret)

+ 21 - 20
src/generators/genjava.ml

@@ -994,7 +994,7 @@ let generate con =
 	let fn_cl = get_cl (get_type gen (["haxe";"lang"],"Function")) in
 
 	let runtime_cl = get_cl (get_type gen (["haxe";"lang"],"Runtime")) in
-	let nulltdef = match (get_type gen ([],"Null")) with TTypeDecl t -> t | _ -> assert false in
+	let nulltabstract = get_abstract (get_type gen ([],"Null")) in
 
 	(*let string_ref = get_cl ( get_type gen (["haxe";"lang"], "StringRefl")) in*)
 
@@ -1035,8 +1035,8 @@ let generate con =
 									| TAbstract ({ a_path = ["java"],"Char16" },[])
 									| TType ({ t_path = [],"Single" },[])
 									| TAbstract ({ a_path = [],"Single" },[]) ->
-										TType(nulltdef, [f_t])
-									(*| TType ({ t_path = [], "Null"*)
+										TAbstract(nulltabstract, [f_t])
+									(*| TAbstract ({ a_path = [], "Null"*)
 									| TInst (cl, ((_ :: _) as p)) when cl.cl_path <> (["java"],"NativeArray") ->
 										(* TInst(cl, List.map (fun _ -> t_dynamic) p) *)
 										TInst(cl,p)
@@ -1078,8 +1078,8 @@ let generate con =
 			| TType ({ t_path = [],"Single" },[])
 			| TAbstract ({ a_path = [],"Single" },[]) ->
 					Some t
-			| TType (({ t_path = [],"Null" } as tdef),[t2]) ->
-					Some (TType(tdef,[gen.gfollow#run_f t2]))
+			| TAbstract (({ a_path = [],"Null" } as tab),[t2]) ->
+					Some (TAbstract(tab,[gen.gfollow#run_f t2]))
 			| TAbstract (a, pl) when not (Meta.has Meta.CoreType a.a_meta) ->
 					Some (gen.gfollow#run_f ( Abstract.get_underlying_type a pl) )
 			| TAbstract( { a_path = ([], "EnumValue") }, _ )
@@ -1114,20 +1114,8 @@ let generate con =
 	let rec real_type t =
 		let t = gen.gfollow#run_f t in
 		match t with
-			| TAbstract (a, pl) when not (Meta.has Meta.CoreType a.a_meta) ->
-				real_type (Abstract.get_underlying_type a pl)
-			| TInst( { cl_path = (["haxe"], "Int32") }, [] ) -> gen.gcon.basic.tint
-			| TInst( { cl_path = (["haxe"], "Int64") }, [] ) -> ti64
-			| TAbstract( { a_path = ([], "Class") }, p	)
-			| TAbstract( { a_path = ([], "Enum") }, p  )
-			| TInst( { cl_path = ([], "Class") }, p  )
-			| TInst( { cl_path = ([], "Enum") }, p	) -> TInst(cl_cl,[t_dynamic])
-			| TEnum(e,params) -> TEnum(e, List.map (fun _ -> t_dynamic) params)
-			| TInst(c,params) when Meta.has Meta.Enum c.cl_meta ->
-				TInst(c, List.map (fun _ -> t_dynamic) params)
-			| TInst({ cl_kind = KExpr _ }, _) -> t_dynamic
-			| TInst _ -> t
-			| TType({ t_path = ([], "Null") }, [t]) -> (
+			| TAbstract({ a_path = ([], "Null") }, [t]) when is_java_basic_type (gen.gfollow#run_f t) -> t_dynamic
+			| TAbstract({ a_path = ([], "Null") }, [t]) -> (
 				match gen.gfollow#run_f t with
 				| TAbstract( { a_path = ([], "Bool") }, [] ) ->
 					TInst(cl_boolean, [])
@@ -1152,6 +1140,19 @@ let generate con =
 					| _ -> real_type t
 				)
 			)
+			| TAbstract (a, pl) when not (Meta.has Meta.CoreType a.a_meta) ->
+				real_type (Abstract.get_underlying_type a pl)
+			| TInst( { cl_path = (["haxe"], "Int32") }, [] ) -> gen.gcon.basic.tint
+			| TInst( { cl_path = (["haxe"], "Int64") }, [] ) -> ti64
+			| TAbstract( { a_path = ([], "Class") }, p	)
+			| TAbstract( { a_path = ([], "Enum") }, p  )
+			| TInst( { cl_path = ([], "Class") }, p  )
+			| TInst( { cl_path = ([], "Enum") }, p	) -> TInst(cl_cl,[t_dynamic])
+			| TEnum(e,params) -> TEnum(e, List.map (fun _ -> t_dynamic) params)
+			| TInst(c,params) when Meta.has Meta.Enum c.cl_meta ->
+				TInst(c, List.map (fun _ -> t_dynamic) params)
+			| TInst({ cl_kind = KExpr _ }, _) -> t_dynamic
+			| TInst _ -> t
 			| TType _ | TAbstract _ -> t
 			| TAnon (anon) -> (match !(anon.a_status) with
 				| Statics _ | EnumStatics _ | AbstractStatics _ -> t
@@ -2459,7 +2460,7 @@ let generate con =
 	in
 
 	let may_nullable t = match gen.gfollow#run_f t with
-		| TType({ t_path = ([], "Null") }, [t]) ->
+		| TAbstract({ a_path = ([], "Null") }, [t]) ->
 			(match follow t with
 				| TInst({ cl_path = ([], "String") }, [])
 				| TAbstract ({ a_path = ([], "Float") },[])

+ 6 - 9
src/generators/genphp.ml

@@ -126,20 +126,17 @@ and type_string_suff suffix haxe_type =
 	| TAbstract ({ a_path = [],"Float" },[]) -> "double"
 	| TAbstract ({ a_path = [],"Bool" },[]) -> "bool"
 	| TAbstract ({ a_path = [],"Void" },[]) -> "Void"
+	| TAbstract ({ a_path = [],"Null"},[t]) ->
+		(match follow t with
+		| TInst ({ cl_path = [],"Int" },_)
+		| TInst ({ cl_path = [],"Float" },_)
+		| TEnum ({ e_path = [],"Bool" },_) -> "Dynamic"
+		| _ -> type_string_suff suffix t)
 	| TEnum (enum,params) ->  (join_class_path enum.e_path "::") ^ suffix
 	| TInst (klass,params) ->  (class_string klass suffix params)
 	| TAbstract (abs,params) ->  (join_class_path abs.a_path "::") ^ suffix
 	| TType (type_def,params) ->
 		(match type_def.t_path with
-		| [] , "Null" ->
-			(match params with
-			| [t] ->
-				(match follow t with
-				| TInst ({ cl_path = [],"Int" },_)
-				| TInst ({ cl_path = [],"Float" },_)
-				| TEnum ({ e_path = [],"Bool" },_) -> "Dynamic"
-				| _ -> type_string_suff suffix t)
-			| _ -> assert false);
 		| [] , "Array" ->
 			(match params with
 			| [t] -> "Array<" ^ (type_string (follow t) ) ^ " >"

+ 4 - 2
src/generators/genswf9.ml

@@ -189,7 +189,7 @@ let rec follow_basic t =
 		| _ -> t)
 	| TLazy f ->
 		follow_basic (!f())
-	| TType ({ t_path = [],"Null" },[tp]) ->
+	| TAbstract ({ a_path = [],"Null" },[tp]) ->
 		(match follow_basic tp with
 		| TMono _
 		| TFun _
@@ -228,7 +228,9 @@ let rec type_id ctx t =
 			| _ -> type_path ctx ([],"Object"))
 		| _ ->
 			type_path ctx c.cl_path)
-	| TAbstract (a,_) ->
+	| TAbstract ({ a_path = [],"Null"},_) ->
+		HMPath ([],"Object")
+	| TAbstract (a,_) when Meta.has Meta.CoreType a.a_meta ->
 		type_path ctx a.a_path
 	| TFun _ | TType ({ t_path = ["flash";"utils"],"Function" },[]) ->
 		type_path ctx ([],"Function")

+ 3 - 3
src/generators/genxml.ml

@@ -75,8 +75,8 @@ let rec follow_param t =
 		(match !r with
 		| Some t -> follow_param t
 		| _ -> t)
-	| TType ({ t_path = [],"Null" } as t,tl) ->
-		follow_param (apply_params t.t_params tl t.t_type)
+	| TAbstract ({ a_path = [],"Null" },[t]) ->
+		follow_param t
 	| _ ->
 		t
 
@@ -356,7 +356,7 @@ let generate_type com t =
 			| Some t -> notnull t)
 		| TLazy f ->
 			notnull ((!f)())
-		| TType ({ t_path = [],"Null" },[t]) ->
+		| TAbstract ({ a_path = [],"Null" },[t]) ->
 			t
 		| _ ->
 			t

+ 1 - 1
src/optimization/analyzerTexpr.ml

@@ -188,7 +188,7 @@ let type_change_ok com t1 t2 =
 		let rec is_nullable_or_whatever = function
 			| TMono r ->
 				(match !r with None -> false | Some t -> is_nullable_or_whatever t)
-			| TType ({ t_path = ([],"Null") },[_]) ->
+			| TAbstract ({ a_path = ([],"Null") },[_]) ->
 				true
 			| TLazy f ->
 				is_nullable_or_whatever (!f())

+ 2 - 2
src/typing/abstract.ml

@@ -30,8 +30,8 @@ let rec get_underlying_type a pl =
 				| _ -> t)
 			| TLazy f ->
 				loop (!f())
-			| TType({t_path=([],"Null")} as tn,[t1]) ->
-				TType(tn,[loop t1])
+			| TAbstract({a_path=([],"Null")} as a,[t1]) ->
+				TAbstract(a,[loop t1])
 			| TType (t,tl) ->
 				loop (apply_params t.t_params tl t.t_type)
 			| TAbstract(a,tl) when not (Meta.has Meta.CoreType a.a_meta) ->

+ 15 - 15
src/typing/overloads.ml

@@ -15,8 +15,8 @@ let same_overload_args ?(get_vmtype) t1 t2 f1 f2 =
 			| _ -> t)
 		| TLazy f ->
 			follow_skip_null (!f())
-		| TType ({ t_path = [],"Null" } as t, [p]) ->
-			TType(t,[follow p])
+		| TAbstract ({ a_path = [],"Null" } as a, [p]) ->
+			TAbstract(a,[follow p])
 		| TType (t,tl) ->
 			follow_skip_null (apply_params t.t_params tl t.t_type)
 		| _ -> t
@@ -69,17 +69,17 @@ let rec get_overloads c i =
 module Resolution =
 struct
 	let rec simplify_t t = match t with
-		| TAbstract(a,_) when Meta.has Meta.CoreType a.a_meta ->
-			t
 		| TInst _ | TEnum _ ->
 			t
-		| TAbstract(a,tl) -> simplify_t (Abstract.get_underlying_type a tl)
-		| TType(({ t_path = [],"Null" } as t), [t2]) -> (match simplify_t t2 with
+		| TAbstract(({ a_path = [],"Null" } as t), [t2]) -> (match simplify_t t2 with
 			| (TAbstract(a,_) as t2) when Meta.has Meta.CoreType a.a_meta ->
-				TType(t, [simplify_t t2])
+				TAbstract(t, [simplify_t t2])
 			| (TEnum _ as t2) ->
-				TType(t, [simplify_t t2])
+				TAbstract(t, [simplify_t t2])
 			| t2 -> t2)
+		| TAbstract(a,_) when Meta.has Meta.CoreType a.a_meta ->
+			t
+		| TAbstract(a,tl) -> simplify_t (Abstract.get_underlying_type a tl)
 		| TType(t, tl) ->
 			simplify_t (apply_params t.t_params tl t.t_type)
 		| TMono r -> (match !r with
@@ -143,10 +143,16 @@ struct
 			(cacc, 0)
 		| TDynamic _, _ ->
 			(max_int, 0) (* a function with dynamic will always be worst of all *)
-		| TAbstract(a, _), TDynamic _ when Meta.has Meta.CoreType a.a_meta ->
+		| TAbstract(a, _), TDynamic _ when Meta.has Meta.CoreType a.a_meta && a.a_path <> ([],"Null") ->
 			(cacc + 2, 0) (* a dynamic to a basic type will have an "unboxing" penalty *)
 		| _, TDynamic _ ->
 			(cacc + 1, 0)
+		| TAbstract({ a_path = [], "Null" }, [tf]), TAbstract({ a_path = [], "Null" }, [ta]) ->
+			rate_conv (cacc+0) tf ta
+		| TAbstract({ a_path = [], "Null" }, [tf]), ta ->
+			rate_conv (cacc+1) tf ta
+		| tf, TAbstract({ a_path = [], "Null" }, [ta]) ->
+			rate_conv (cacc+1) tf ta
 		| TAbstract(af,tlf), TAbstract(aa,tla) ->
 			(if af == aa then
 				(cacc, rate_tp tlf tla)
@@ -169,12 +175,6 @@ struct
 					Option.get !ret
 			else
 				raise Not_found)
-		| TType({ t_path = [], "Null" }, [tf]), TType({ t_path = [], "Null" }, [ta]) ->
-			rate_conv (cacc+0) tf ta
-		| TType({ t_path = [], "Null" }, [tf]), ta ->
-			rate_conv (cacc+1) tf ta
-		| tf, TType({ t_path = [], "Null" }, [ta]) ->
-			rate_conv (cacc+1) tf ta
 		| TFun _, TFun _ -> (* unify will make sure they are compatible *)
 			cacc,0
 		| tfun,targ ->

+ 17 - 3
src/typing/type.ml

@@ -642,12 +642,14 @@ let rec follow t =
 		follow (!f())
 	| TType (t,tl) ->
 		follow (apply_params t.t_params tl t.t_type)
+	| TAbstract({a_path = [],"Null"},[t]) ->
+		follow t
 	| _ -> t
 
 let rec is_nullable = function
 	| TMono r ->
 		(match !r with None -> false | Some t -> is_nullable t)
-	| TType ({ t_path = ([],"Null") },[_]) ->
+	| TAbstract ({ a_path = ([],"Null") },[_]) ->
 		true
 	| TLazy f ->
 		is_nullable (!f())
@@ -674,7 +676,7 @@ let rec is_nullable = function
 let rec is_null ?(no_lazy=false) = function
 	| TMono r ->
 		(match !r with None -> false | Some t -> is_null t)
-	| TType ({ t_path = ([],"Null") },[t]) ->
+	| TAbstract ({ a_path = ([],"Null") },[t]) ->
 		not (is_nullable (follow t))
 	| TLazy f ->
 		if no_lazy then raise Exit else is_null (!f())
@@ -687,7 +689,7 @@ let rec is_null ?(no_lazy=false) = function
 let rec is_explicit_null = function
 	| TMono r ->
 		(match !r with None -> false | Some t -> is_null t)
-	| TType ({ t_path = ([],"Null") },[t]) ->
+	| TAbstract ({ a_path = ([],"Null") },[t]) ->
 		true
 	| TLazy f ->
 		is_null (!f())
@@ -1723,6 +1725,12 @@ let rec type_eq param a b =
 			Unify_error l -> error (cannot_unify a b :: l))
 	| TDynamic a , TDynamic b ->
 		type_eq param a b
+	| TAbstract ({a_path=[],"Null"},[t1]),TAbstract ({a_path=[],"Null"},[t2]) ->
+		type_eq param t1 t2
+	| TAbstract ({a_path=[],"Null"},[t]),_ when param <> EqDoNotFollowNull ->
+		type_eq param t b
+	| _,TAbstract ({a_path=[],"Null"},[t]) when param <> EqDoNotFollowNull ->
+		type_eq param a t
 	| TAbstract (a1,tl1) , TAbstract (a2,tl2) ->
 		if a1 != a2 && not (param = EqCoreType && a1.a_path = a2.a_path) then error [cannot_unify a b];
 		List.iter2 (type_eq param) tl1 tl2
@@ -1815,6 +1823,12 @@ let rec unify a b =
 	| TEnum (ea,tl1) , TEnum (eb,tl2) ->
 		if ea != eb then error [cannot_unify a b];
 		unify_type_params a b tl1 tl2
+	| TAbstract ({a_path=[],"Null"},[t]),_ ->
+		begin try unify t b
+		with Unify_error l -> error (cannot_unify a b :: l) end
+	| _,TAbstract ({a_path=[],"Null"},[t]) ->
+		begin try unify a t
+		with Unify_error l -> error (cannot_unify a b :: l) end
 	| TAbstract (a1,tl1) , TAbstract (a2,tl2) when a1 == a2 ->
 		begin try
 			unify_type_params a b tl1 tl2

+ 7 - 10
src/typing/typer.ml

@@ -175,6 +175,8 @@ let rec is_pos_infos = function
 		true
 	| TType (t,tl) ->
 		is_pos_infos (apply_params t.t_params tl t.t_type)
+	| TAbstract({a_path=[],"Null"},[t]) ->
+		is_pos_infos t
 	| _ ->
 		false
 
@@ -4489,29 +4491,24 @@ let rec create com =
 			| "Int" -> ctx.t.tint <- TAbstract (a,[])
 			| "Bool" -> ctx.t.tbool <- TAbstract (a,[])
 			| "Dynamic" -> t_dynamic_def := TAbstract(a,List.map snd a.a_params);
-			| _ -> ());
-		| TEnumDecl e ->
-			()
-		| TClassDecl c ->
-			()
-		| TTypeDecl td ->
-			(match snd td.t_path with
 			| "Null" ->
 				let mk_null t =
 					try
-						if not (is_null ~no_lazy:true t) then TType (td,[t]) else t
+						if not (is_null ~no_lazy:true t) then TAbstract (a,[t]) else t
 					with Exit ->
 						(* don't force lazy evaluation *)
 						let r = ref (fun() -> assert false) in
 						r := (fun() ->
-							let t = (if not (is_null t) then TType (td,[t]) else t) in
+							let t = (if not (is_null t) then TAbstract (a,[t]) else t) in
 							r := (fun() -> t);
 							t
 						);
 						TLazy r
 				in
 				ctx.t.tnull <- mk_null;
-			| _ -> ());
+			| _ -> ())
+		| TEnumDecl _ | TClassDecl _ | TTypeDecl _ ->
+			()
 	) ctx.g.std.m_types;
 	let m = Typeload.load_module ctx ([],"String") null_pos in
 	(match m.m_types with

+ 3 - 1
std/StdTypes.hx

@@ -72,7 +72,9 @@
 
 	@see https://haxe.org/manual/types-nullability.html
 **/
-typedef Null<T> = T
+@:forward
+@:coreType
+abstract Null<T> from T to T { }
 
 /**
 	The standard Boolean type, which can either be `true` or `false`.