Browse Source

Early returns in NullCoal (#10791)

* Early returns in NullCoal

* Mental test

* Check call expr too

* More exprs

* get has_dead_end under control

* Ignore tfor

* tfor returns

Co-authored-by: Simon Krajewski <[email protected]>
RblSb 2 years ago
parent
commit
31779014a0

+ 1 - 1
src/core/tFunctions.ml

@@ -850,4 +850,4 @@ let type_has_meta t m =
 let var_extra params e = {
 	v_params = params;
 	v_expr = e;
-}
+}

+ 77 - 0
src/core/texpr.ml

@@ -842,3 +842,80 @@ let punion_el default_pos el =
 			default_pos
 		else
 			punion first last
+
+let is_exhaustive e1 def =
+	let rec loop e1 = match e1.eexpr with
+		| TMeta((Meta.Exhaustive,_,_),_) -> true
+		| TMeta(_, e1) | TParenthesis e1 -> loop e1
+		| _ -> false
+	in
+	def <> None || loop e1
+
+let rec is_true_expr e1 = match e1.eexpr with
+	| TConst(TBool true) -> true
+	| TParenthesis e1 -> is_true_expr e1
+	| _ -> false
+
+let rec is_false_expr e1 = match e1.eexpr with
+	| TConst(TBool false) -> true
+	| TParenthesis e1 -> is_false_expr e1
+	| _ -> false
+
+module DeadEnd = struct
+	exception BreakOrContinue
+
+	(*
+		Checks if execution of provided expression is guaranteed to be terminated with `return`, `throw`, `break` or `continue`.
+	*)
+	let has_dead_end e =
+		let rec loop e =
+			let in_loop e =
+				try
+					loop e
+				with BreakOrContinue ->
+					false
+			in
+			match e.eexpr with
+			| TContinue | TBreak ->
+				raise BreakOrContinue
+			| TThrow e1 ->
+				loop e1 || true
+			| TReturn (Some e1) ->
+				loop e1 || true (* recurse first, could be `return continue` *)
+			| TReturn None ->
+				true
+			| TFunction _ ->
+				false (* This isn't executed, so don't recurse *)
+			| TIf (cond, if_body, Some else_body) ->
+				loop cond || loop if_body && loop else_body
+			| TSwitch(e1, cases, def) ->
+				let check_exhaustive () =
+					(is_exhaustive e1 def) && List.for_all (fun (el,e) ->
+						List.exists loop el ||
+						loop e
+					) cases &&
+					Option.map_default (loop ) true def (* true because we know it's exhaustive *)
+				in
+				loop e1 || check_exhaustive ()
+			| TFor(_, e1, _) ->
+				loop e1
+			| TBinop(OpBoolAnd, e1, e2) ->
+				loop e1 || is_true_expr e1 && loop e2
+			| TBinop(OpBoolOr, e1, e2) ->
+				loop e1 || is_false_expr e1 && loop e2
+			| TWhile(cond, body, flag) ->
+				loop cond || ((flag = DoWhile || is_true_expr cond) && in_loop body)
+			| TTry(e1,[]) ->
+				loop e1
+			| TTry(_,catches) ->
+				(* The try expression is irrelevant because we have to conservatively assume that
+				   anything could throw control flow into the catch expressions. *)
+				List.for_all (fun (_,e) -> loop e) catches
+			| _ ->
+				check_expr loop e
+		in
+		try
+			loop e
+		with BreakOrContinue ->
+			true
+end

+ 0 - 5
src/optimization/analyzerTexpr.ml

@@ -25,11 +25,6 @@ open Globals
 
 let s_expr_pretty e = s_expr_pretty false "" false (s_type (print_context())) e
 
-let rec is_true_expr e1 = match e1.eexpr with
-	| TConst(TBool true) -> true
-	| TParenthesis e1 -> is_true_expr e1
-	| _ -> false
-
 let is_stack_allocated c = Meta.has Meta.StructAccess c.cl_meta
 
 let map_values ?(allow_control_flow=true) f e =

+ 1 - 1
src/optimization/analyzerTexprTransformer.ml

@@ -432,7 +432,7 @@ let rec func ctx bb tf t p =
 				end
 			end
 		| TSwitch(e1,cases,edef) ->
-			let is_exhaustive = edef <> None || is_exhaustive e1 in
+			let is_exhaustive = is_exhaustive e1 edef in
 			let bb,e1 = bind_to_temp bb false e1 in
 			bb.bb_terminator <- TermCondBranch e1;
 			let reachable = ref [] in

+ 1 - 1
src/optimization/inline.ml

@@ -723,7 +723,7 @@ let rec type_inline ctx cf f ethis params tret config p ?(self_calling_closure=f
 			in_loop := old;
 			{ e with eexpr = TWhile (cond,eloop,flag) }
 		| TSwitch (e1,cases,def) when term ->
-			let term = term && (def <> None || is_exhaustive e1) in
+			let term = term && (is_exhaustive e1 def) in
 			let cases = List.map (fun (el,e) ->
 				let el = List.map (map false false) el in
 				el, map term false e

+ 0 - 6
src/optimization/optimizerTexpr.ml

@@ -21,12 +21,6 @@ let has_side_effect e =
 	with Exit ->
 		true
 
-let rec is_exhaustive e1 = match e1.eexpr with
-	| TMeta((Meta.Exhaustive,_,_),_) -> true
-	| TMeta(_, e1) | TParenthesis e1 -> is_exhaustive e1
-	| _ -> false
-
-
 let is_read_only_field_access e fa = match fa with
 	| FEnum _ ->
 		true

+ 1 - 17
src/typing/nullSafety.ml

@@ -320,22 +320,6 @@ class unificator =
 			traverse a_args b_args
 	end
 
-(**
-	Checks if execution of provided expression is guaranteed to be terminated with `return`, `throw`, `break` or `continue`.
-*)
-let rec is_dead_end e =
-	match e.eexpr with
-		| TThrow _ -> true
-		| TReturn _ -> true
-		| TBreak -> true
-		| TContinue -> true
-		| TWhile (_, body, DoWhile) -> is_dead_end body
-		| TIf (_, if_body, Some else_body) -> is_dead_end if_body && is_dead_end else_body
-		| TBlock exprs -> List.exists is_dead_end exprs
-		| TMeta (_, e) -> is_dead_end e
-		| TCast (e, _) -> is_dead_end e
-		| _ -> false
-
 (**
 	Check if `expr` is a `trace` (not a call, but identifier itself)
 *)
@@ -923,7 +907,7 @@ class local_safety (mode:safety_mode) =
 					self#get_current_scope#reset_to initial_safe;
 					(** execute `else_body` with known not-null variables *)
 					let handle_dead_end body safe_vars =
-						if is_dead_end body then
+						if DeadEnd.has_dead_end body then
 							List.iter self#get_current_scope#add_to_safety safe_vars
 					in
 					(match else_body with

+ 11 - 1
src/typing/typer.ml

@@ -1847,7 +1847,17 @@ and type_expr ?(mode=MGet) ctx (e,p) (with_type:WithType.t) =
 		let e1 = vr#as_var "tmp" {e1 with etype = ctx.t.tnull e1.etype} in
 		let e_null = Builder.make_null e1.etype e1.epos in
 		let e_cond = mk (TBinop(OpNotEq,e1,e_null)) ctx.t.tbool e1.epos in
-		let iftype = WithType.WithType(e2.etype,None) in
+
+		let follow_null_once t =
+			match t with
+			| TAbstract({a_path = [],"Null"},[t]) -> t
+			| _ -> t
+		in
+		let iftype = if DeadEnd.has_dead_end e2 then
+			WithType.with_type (follow_null_once e1.etype)
+		else
+			WithType.WithType(e2.etype,None)
+		in
 		let e_if = make_if_then_else ctx e_cond e1 e2 iftype p in
 		vr#to_texpr e_if
 	| EBinop (OpAssignOp OpNullCoal,e1,e2) ->

+ 168 - 4
tests/unit/src/unit/issues/Issue10744.hx

@@ -5,11 +5,175 @@ import unit.HelperMacros.typeString;
 class Issue10744 extends Test {
 	function test() {
 		var v:Null<Int> = 10;
-		eq("Null<Int>", typeString(v ?? return));
-		eq("Null<Int>", typeString(v ?? throw true));
+		eq("Int", typeString(v ?? return));
+		eq("Int", typeString(v ?? throw true));
 		for (i in 0...1) {
-			eq("Null<Int>", typeString(v ?? break));
-			eq("Null<Int>", typeString(v ?? continue));
+			eq("Int", typeString(v ?? break));
+			eq("Int", typeString(v ?? continue));
 		}
+		eq("Int", typeString(v ?? {
+			(throw "nope");
+		}));
+		eq("Null<Int>", typeString(v ?? {
+			if (Std.random(0) == 0)
+				return;
+			else
+				v;
+		}));
+		eq("Null<Int>", typeString(v ?? {
+			function foo()
+				return;
+			v;
+		}));
+		eq("Int", typeString(v ?? {
+			if (Std.random(0) == 0)
+				return;
+			else
+				throw "nope";
+		}));
+		eq("Int", typeString(v ?? {
+			Std.parseInt(return);
+		}));
+		eq("Int", typeString(v ?? {
+			(return)();
+		}));
+		eq("Int", typeString(v ?? {
+			v + return;
+			v;
+		}));
+		eq("Null<Int>", typeString(v ?? {
+			false && return ;
+			v;
+		}));
+		eq("Int", typeString(v ?? {
+			true && return ;
+			v;
+		}));
+		eq("Int", typeString(v ?? {
+			false || return ;
+			v;
+		}));
+		eq("Int", typeString(v ?? {
+			final a = return;
+			v;
+		}));
+		eq("Int", typeString(v ?? {
+			[0, return, 2];
+			v;
+		}));
+		eq("Null<Int>", typeString(v ?? {
+			for (i in 0...Std.random(1)) {
+				return;
+			}
+			v;
+		}));
+		eq("Int", typeString(v ?? {
+			for (i in [0, return, 2]) {
+				break;
+			}
+			v;
+		}));
+		eq("Int", typeString(v ?? {
+			switch (null) {
+				case _: return;
+			}
+			v;
+		}));
+		eq("Int", typeString(v ?? {
+			switch (return) {
+				case _: null;
+			}
+			v;
+		}));
+		eq("Int", typeString(v ?? {
+			final arr = [];
+			arr[return];
+			v;
+		}));
+		eq("Int", typeString(v ?? {
+			new EReg("", return);
+			v;
+		}));
+		eq("Null<Int>", typeString(v ?? {
+			do {
+				break;
+				return;
+			} while (true);
+			v;
+		}));
+		eq("Int", typeString(v ?? {
+			do {
+				break; // die
+				return;
+			} while (true); // resurrect
+			return; // die again
+			v;
+		}));
+		eq("Null<Int>", typeString(v ?? {
+			try {
+				throw null;
+			} catch (e) {}
+			v;
+		}));
+		eq("Int", typeString(v ?? {
+			try {
+				throw null;
+			} catch (e) {
+				return;
+			}
+			v;
+		}));
+		eq("Null<Int>", typeString(v ?? {
+			try {
+				throw null;
+			} catch (e:String) {
+				// fall through
+			} catch (e) {
+				return;
+			}
+			v;
+		}));
+		eq("Null<Int>", typeString(v ?? {
+			try {
+				return;
+			} catch (e:String) {
+				// fall through
+			} catch (e) {
+				return;
+			}
+			v;
+		}));
+		eq("Int", typeString(v ?? {
+			try {
+				return;
+			} catch (e:String) {
+				return;
+			} catch (e) {
+				return;
+			}
+			v;
+		}));
+		eq("Null<Int>", typeString(v ?? {
+			try {
+				// something here COULD throw and end up in the fall through case
+			} catch (e:String) {
+				// fall through
+			} catch (e) {
+				return;
+			}
+			v;
+		}));
+		eq("Int", typeString(v ?? {
+			try {
+				return;
+			}
+			v;
+		}));
+		eq("Null<Int>", typeString(v ?? {
+			try {
+				// fall through
+			}
+			v;
+		}));
 	}
 }