Selaa lähdekoodia

[gencommon] use info from Filters.mark_switch_break_loops and remove SwitchBreakSynf

Dan Korostelev 8 vuotta sitten
vanhempi
sitoutus
f0cc6abf6b

+ 0 - 117
src/generators/gencommon/switchBreakSynf.ml

@@ -1,117 +0,0 @@
-(*
-	The Haxe Compiler
-	Copyright (C) 2005-2017  Haxe Foundation
-
-	This program is free software; you can redistribute it and/or
-	modify it under the terms of the GNU General Public License
-	as published by the Free Software Foundation; either version 2
-	of the License, or (at your option) any later version.
-
-	This program is distributed in the hope that it will be useful,
-	but WITHOUT ANY WARRANTY; without even the implied warranty of
-	MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-	GNU General Public License for more details.
-
-	You should have received a copy of the GNU General Public License
-	along with this program; if not, write to the Free Software
-	Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301, USA.
-*)
-open Type
-open Gencommon
-
-(* TODO: remove this in favor of Filters.mark_switch_break_loops when we figure out who removes its TMetas *)
-
-(*
-	In most languages, 'break' is used as a statement also to break from switch statements.
-	This generates an incompatibility with haxe code, as we can use break to break from loops from inside a switch
-
-	This script will detect 'breaks' inside switch statements, and will offer the opportunity to change both
-	when this pattern is found.
-
-	Some options are possible:
-		On languages that support goto, 'break' may mean goto " after the loop ". There also can be special labels for
-			loops, so you can write "break label" (javascript, java, d)
-		On languages that do not support goto, a custom solution must be enforced
-
-	dependencies:
-		Since UnreachableCodeElimination must run before it, and Unreachable should be one of the
-		very last filters to run, we will make a fixed value which runs after UnreachableCodeElimination
-		(meaning: it's the very last filter)
-*)
-type add_to_block_api = texpr->bool->unit
-
-let init (change_loop:texpr->int->add_to_block_api->texpr) (change_break:texpr->int->add_to_block_api->texpr) =
-	let in_switch = ref false in
-	let cur_block = ref [] in
-	let to_add = ref [] in
-	let did_found = ref (-1) in
-
-	let api expr before =
-		if before then cur_block := expr :: !cur_block else to_add := expr :: !to_add
-	in
-	let num = ref 0 in
-	let cur_num = ref 0 in
-
-	let rec run e =
-		match e.eexpr with
-		| TFunction _ ->
-			let old_num = !num in
-			num := 0;
-				let ret = Type.map_expr run e in
-			num := old_num;
-			ret
-		| TFor _
-		| TWhile _ ->
-			let last_switch = !in_switch in
-			let last_found = !did_found in
-			let last_num = !cur_num in
-			in_switch := false;
-			incr num;
-			cur_num := !num;
-			did_found := -1;
-				let new_e = Type.map_expr run e in (* assuming that no loop will be found in the condition *)
-				let new_e = if !did_found <> -1 then change_loop new_e !did_found api else new_e in
-			did_found := last_found;
-			in_switch := last_switch;
-			cur_num := last_num;
-
-			new_e
-		| TSwitch _ ->
-			let last_switch = !in_switch in
-			in_switch := true;
-
-				let new_e = Type.map_expr run e in
-
-			in_switch := last_switch;
-			new_e
-		| TBlock bl ->
-			let last_block = !cur_block in
-			let last_toadd = !to_add in
-			to_add := [];
-			cur_block := [];
-
-				List.iter (fun e ->
-					let new_e = run e in
-					cur_block := new_e :: !cur_block;
-					match !to_add with
-						| [] -> ()
-						| _ -> cur_block := !to_add @ !cur_block; to_add := []
-				) bl;
-
-			let ret = List.rev !cur_block in
-			cur_block := last_block;
-			to_add := last_toadd;
-
-			{ e with eexpr = TBlock(ret) }
-		| TBreak ->
-			if !in_switch then (did_found := !cur_num; change_break e !cur_num api) else e
-		| _ -> Type.map_expr run e
-	in
-	run
-
-let priority = min_dep -. 150.0
-
-let configure gen change_loop change_break =
-	let run = init change_loop change_break in
-	let map e = Some(run e) in
-	gen.gsyntax_filters#add "switch_break_synf" (PCustom priority) map

+ 3 - 0
src/generators/gencommon/unreachableCodeEliminationSynf.ml

@@ -99,6 +99,9 @@ let init com java_mode =
 
 	let rec process_expr expr =
 		match expr.eexpr with
+			| TMeta (m,expr) ->
+				let expr,kind = process_expr expr in
+				{ expr with eexpr = TMeta (m, expr) }, kind
 			| TReturn _ | TThrow _ -> expr, BreaksFunction
 			| TContinue -> expr, BreaksLoop
 			| TBreak -> has_break := true; expr, BreaksLoop

+ 12 - 20
src/generators/gencs.ml

@@ -1163,7 +1163,6 @@ let generate con =
 				| TObjectDecl _
 				| TArrayDecl _
 				| TCast _
-				| TMeta _
 				| TParenthesis _
 				| TUnop _ ->
 					Type.iter loop expr
@@ -1343,8 +1342,15 @@ let generate con =
 						)
 					| TParenthesis e ->
 						write w "("; expr_s w e; write w ")"
+					| TMeta ((Meta.LoopLabel,[(EConst(Int n),_)],_), e) ->
+						(match e.eexpr with
+						| TFor _ | TWhile _ ->
+							expr_s w e;
+							print w "label%s: {}" n
+						| TBreak -> print w "goto label%s" n
+						| _ -> assert false)
 					| TMeta (_,e) ->
-							expr_s w e
+								expr_s w e
 					| TArrayDecl el
 					| TCall ({ eexpr = TLocal { v_name = "__array__" } }, el)
 					| TCall ({ eexpr = TField(_, FStatic({ cl_path = (["cs"],"NativeArray") }, { cf_name = "make" })) }, el) ->
@@ -1445,10 +1451,6 @@ let generate con =
 						write w "*(";
 						expr_s w e;
 						write w ")"
-					| TCall ({ eexpr = TLocal( { v_name = "__goto__" } ) }, [ { eexpr = TConst(TInt v) } ] ) ->
-						print w "goto label%ld" v
-					| TCall ({ eexpr = TLocal( { v_name = "__label__" } ) }, [ { eexpr = TConst(TInt v) } ] ) ->
-						print w "label%ld: {}" v
 					| TCall ({ eexpr = TLocal( { v_name = "__rethrow__" } ) }, _) ->
 						write w "throw"
 					(* operator overloading handling *)
@@ -2603,8 +2605,6 @@ let generate con =
 
 		Hashtbl.add gen.gspecial_vars "__rethrow__" true;
 		Hashtbl.add gen.gspecial_vars "__typeof__" true;
-		Hashtbl.add gen.gspecial_vars "__label__" true;
-		Hashtbl.add gen.gspecial_vars "__goto__" true;
 		Hashtbl.add gen.gspecial_vars "__is__" true;
 		Hashtbl.add gen.gspecial_vars "__as__" true;
 		Hashtbl.add gen.gspecial_vars "__cs__" true;
@@ -2717,7 +2717,10 @@ let generate con =
 		in
 
 		FixOverrides.configure ~explicit_fn_name:explicit_fn_name ~get_vmtype:real_type gen;
-		Normalize.configure gen ~allowed_metas:(Hashtbl.create 0);
+
+		let allowed_meta = Hashtbl.create 1 in
+		Hashtbl.add allowed_meta Meta.LoopLabel true;
+		Normalize.configure gen ~allowed_metas:allowed_meta;
 
 		AbstractImplementationFix.configure gen;
 
@@ -3105,17 +3108,6 @@ let generate con =
 
 		ArrayDeclSynf.configure gen native_arr_cl;
 
-		let goto_special = alloc_var "__goto__" t_dynamic in
-		let label_special = alloc_var "__label__" t_dynamic in
-		SwitchBreakSynf.configure gen
-			(fun e_loop n api ->
-				api ({ eexpr = TCall( mk_local label_special e_loop.epos, [ ExprBuilder.make_int gen.gcon n e_loop.epos ] ); etype = t_dynamic; epos = e_loop.epos }) false;
-				e_loop
-			)
-			(fun e_break n api ->
-				{ eexpr = TCall( mk_local goto_special e_break.epos, [ ExprBuilder.make_int gen.gcon n e_break.epos ] ); etype = t_dynamic; epos = e_break.epos }
-			);
-
 		DefaultArguments.configure gen;
 		InterfaceMetas.configure gen;
 

+ 14 - 20
src/generators/genjava.ml

@@ -315,7 +315,7 @@ struct
 			| TThrow _ -> true
 			(* this is hack to not use 'break' on switch cases *)
 			| TLocal { v_name = "__fallback__" } when is_switch -> true
-			| TCall( { eexpr = TLocal { v_name = "__goto__" } }, _ ) -> true
+			| TMeta ((Meta.LoopLabel,_,_), { eexpr = TBreak }) -> true
 			| TParenthesis p | TMeta (_,p) -> is_final_return_expr p
 			| TBlock bl -> is_final_return_block is_switch bl
 			| TSwitch (_, el_e_l, edef) ->
@@ -1173,7 +1173,6 @@ let generate con =
 	let has_semicolon e =
 		match e.eexpr with
 			| TLocal { v_name = "__fallback__" }
-			| TCall ({ eexpr = TLocal( { v_name = "__label__" } ) }, [ { eexpr = TConst(TInt _) } ] ) -> false
 			| TCall ({ eexpr = TLocal( { v_name = "__lock__" } ) }, _ ) -> false
 			| TBlock _ | TFor _ | TSwitch _ | TTry _ | TIf _ -> false
 			| TWhile (_,_,flag) when flag = Ast.NormalWhile -> false
@@ -1250,7 +1249,6 @@ let generate con =
 			| TObjectDecl _
 			| TArrayDecl _
 			| TCast _
-			| TMeta _
 			| TParenthesis _
 			| TUnop _ ->
 				Type.iter loop expr
@@ -1330,6 +1328,14 @@ let generate con =
 				| TTypeExpr mt -> write w (md_s e.epos mt)
 				| TParenthesis e ->
 					write w "("; expr_s w e; write w ")"
+				| TMeta ((Meta.LoopLabel,[(EConst(Int n),_)],_), e) ->
+					(match e.eexpr with
+					| TFor _ | TWhile _ ->
+						print w "label%s:" n;
+						newline w;
+						expr_s w e;
+					| TBreak -> print w "break label%s" n
+					| _ -> assert false)
 				| TMeta (_,e) ->
 					expr_s w e
 				| TCall ({ eexpr = TLocal { v_name = "__array__" } }, el)
@@ -1400,10 +1406,6 @@ let generate con =
 						if has_semicolon eblock then write w ";";
 						end_block w;
 					)
-				| TCall ({ eexpr = TLocal( { v_name = "__goto__" } ) }, [ { eexpr = TConst(TInt v) } ] ) ->
-					print w "break label%ld" v
-				| TCall ({ eexpr = TLocal( { v_name = "__label__" } ) }, [ { eexpr = TConst(TInt v) } ] ) ->
-					print w "label%ld:" v
 				| TCall ({ eexpr = TLocal( { v_name = "__typeof__" } ) }, [ { eexpr = TTypeExpr md } as expr ] ) ->
 					expr_s w expr;
 					write w ".class"
@@ -2050,8 +2052,6 @@ let generate con =
 	(* generate source code *)
 	init_ctx gen;
 
-	Hashtbl.add gen.gspecial_vars "__label__" true;
-	Hashtbl.add gen.gspecial_vars "__goto__" true;
 	Hashtbl.add gen.gspecial_vars "__is__" true;
 	Hashtbl.add gen.gspecial_vars "__typeof__" true;
 	Hashtbl.add gen.gspecial_vars "__java__" true;
@@ -2094,7 +2094,11 @@ let generate con =
 	in
 
 	FixOverrides.configure ~get_vmtype gen;
-	Normalize.configure gen ~allowed_metas:(Hashtbl.create 0);
+
+	let allowed_meta = Hashtbl.create 1 in
+	Hashtbl.add allowed_meta Meta.LoopLabel true;
+	Normalize.configure gen ~allowed_metas:allowed_meta;
+
 	AbstractImplementationFix.configure gen;
 
 	let closure_t = ClosuresToClass.DoubleAndDynamicClosureImpl.get_ctx gen (get_cl (get_type gen (["haxe";"lang"],"Function"))) 6 in
@@ -2411,16 +2415,6 @@ let generate con =
 
 	ArrayDeclSynf.configure gen native_arr_cl;
 
-	let goto_special = alloc_var "__goto__" t_dynamic in
-	let label_special = alloc_var "__label__" t_dynamic in
-	SwitchBreakSynf.configure gen
-		(fun e_loop n api ->
-			{ e_loop with eexpr = TBlock( { eexpr = TCall( mk_local label_special e_loop.epos, [ Codegen.ExprBuilder.make_int gen.gcon n e_loop.epos ] ); etype = t_dynamic; epos = e_loop.epos } :: [e_loop] ) };
-		)
-		(fun e_break n api ->
-			{ eexpr = TCall( mk_local goto_special e_break.epos, [  Codegen.ExprBuilder.make_int gen.gcon n e_break.epos ] ); etype = t_dynamic; epos = e_break.epos }
-		);
-
 	DefaultArguments.configure gen;
 	InterfaceMetas.configure gen;