Просмотр исходного кода

[gencommon] move mk_return to Codegen and use it instead of manually constructing TReturn Some

Dan Korostelev 8 лет назад
Родитель
Сommit
888012a94b

+ 3 - 0
src/generators/codegen.ml

@@ -73,6 +73,9 @@ let fcall e name el ret p =
 let mk_parent e =
 	mk (TParenthesis e) e.etype e.epos
 
+let mk_return e =
+	mk (TReturn (Some e)) t_dynamic e.epos
+
 let binop op a b t p =
 	mk (TBinop (op,a,b)) t p
 

+ 0 - 2
src/generators/gencommon.ml

@@ -1007,8 +1007,6 @@ let get_real_fun gen t =
 	| TFun(args,t) -> TFun(List.map (fun (n,o,t) -> n,o,gen.greal_type t) args, gen.greal_type t)
 	| _ -> t
 
-let mk_return e = { eexpr = TReturn (Some e); etype = t_dynamic; epos = e.epos }
-
 let v_nativearray = alloc_var "__array__" t_dynamic
 let mk_nativearray_decl gen t el pos =
 	{

+ 3 - 2
src/generators/gencommon/castDetect.ml

@@ -21,6 +21,7 @@ open Common
 open Ast
 open Globals
 open Type
+open Codegen
 open Gencommon
 
 (* ******************************************* *)
@@ -91,10 +92,10 @@ struct
 				let ret_type = match !current_ret_type with | Some(s) -> s | None -> gen.gcon.error "Invalid return outside function declaration." e.epos; assert false in
 				(match eopt with
 				| None when not (ExtType.is_void ret_type) ->
-					{ e with eexpr = TReturn( Some(null ret_type e.epos)) }
+					mk_return (null ret_type e.epos)
 				| None -> e
 				| Some eret ->
-					{ e with eexpr = TReturn( Some(handle (run eret) ret_type eret.etype ) ) })
+					mk_return (handle (run eret) ret_type eret.etype))
 			| TFunction(tfunc) ->
 				let last_ret = !current_ret_type in
 				current_ret_type := Some(tfunc.tf_type);

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

@@ -126,7 +126,7 @@ let mk_conversion_fun gen e =
 		epos = e.epos;
 	} in
 	let body = if not (ExtType.is_void ret) then
-		{ body with eexpr = TReturn( Some body ) }
+		mk_return body
 	else
 		body
 	in
@@ -446,7 +446,7 @@ let configure gen ft =
 					epos = pos
 				} in
 				let ibody = if not (ExtType.is_void tfunc.tf_type) then
-					{ ibody with eexpr = TReturn( Some ibody ) }
+					mk_return ibody
 				else
 					ibody
 				in
@@ -747,13 +747,13 @@ struct
 			let tf_expr = if is_void then begin
 				let rec map e =
 					match e.eexpr with
-						| TReturn None -> { e with eexpr = TReturn (Some (null t_dynamic e.epos)) }
+						| TReturn None ->
+							mk_return (null t_dynamic e.epos)
 						| _ -> Type.map_expr map e
 				in
 				let e = mk_block (map tfunc.tf_expr) in
 				match e.eexpr with
-					| TBlock(bl) ->
-						{ e with eexpr = TBlock(bl @ [{ eexpr = TReturn (Some (null t_dynamic e.epos)); etype = t_dynamic; epos = e.epos }]) }
+					| TBlock bl -> { e with eexpr = TBlock (bl @ [mk_return (null t_dynamic e.epos)]) }
 					| _ -> assert false
 			end else tfunc.tf_expr in
 

+ 10 - 14
src/generators/gencommon/enumToClass.ml

@@ -186,20 +186,16 @@ struct
 			eexpr = TFunction {
 				tf_args = [];
 				tf_type = basic.tstring;
-				tf_expr = {
-					eexpr = TReturn (Some (
-						let e_constructs = mk_static_field_access_infer cl "__hx_constructs" pos [] in
-						let e_this = mk (TConst TThis) (TInst (cl,[])) pos in
-						let e_index = mk_field_access gen e_this "index" pos in
-						{
-							eexpr = TArray(e_constructs,e_index);
-							etype = basic.tstring;
-							epos = pos;
-						}
-					));
-					epos = pos;
-					etype = basic.tvoid;
-				}
+				tf_expr = mk_return (
+					let e_constructs = mk_static_field_access_infer cl "__hx_constructs" pos [] in
+					let e_this = mk (TConst TThis) (TInst (cl,[])) pos in
+					let e_index = mk_field_access gen e_this "index" pos in
+					{
+						eexpr = TArray(e_constructs,e_index);
+						etype = basic.tstring;
+						epos = pos;
+					}
+				)
 			};
 			etype = getTag_cf_type;
 			epos = pos;

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

@@ -534,9 +534,9 @@ let try_call_unwrap_statement gen problematic_expression_unwrap (add_statement:t
 			match e.eexpr with
 				| TThrow _ -> e
 				| _ when ExtType.is_void e.etype ->
-						{ e with eexpr = TBlock([e; { e with eexpr = TReturn None }]) }
+					{ e with eexpr = TBlock([e; { e with eexpr = TReturn None }]) }
 				| _ ->
-						{ e with eexpr = TReturn( Some e ) }
+					Codegen.mk_return e
 		) e )
 	in
 

+ 2 - 5
src/generators/gencommon/fixOverrides.ml

@@ -19,6 +19,7 @@
 open Option
 open Common
 open Type
+open Codegen
 open Gencommon
 
 (* ******************************************* *)
@@ -137,11 +138,7 @@ let run ~explicit_fn_name ~get_vmtype gen =
 									eexpr = TFunction({
 										tf_args = List.map (fun v -> v,None) vars;
 										tf_type = r2;
-										tf_expr = (if is_void then call else {
-											eexpr = TReturn (Some (mk_cast r2 call));
-											etype = r2;
-											epos = p
-										})
+										tf_expr = if is_void then call else (mk_return (mk_cast r2 call));
 									});
 									etype = real_ftype;
 									epos = p;

+ 7 - 8
src/generators/gencommon/reflectionCFs.ml

@@ -544,8 +544,8 @@ let get_delete_field ctx cl is_dynamic =
 			let conflict_ctx = Option.get ctx.rcf_hash_conflict_ctx in
 			let ehead = mk_this (mk_internal_name "hx" "conflicts") conflict_ctx.t in
 			(mk (TIf (
-				mk (TBinop (OpLt, local_switch_var, ExprBuilder.make_int gen.gcon 0 pos)) basic.tbool pos,
-				mk (TReturn (Some (conflict_ctx.delete ehead local_switch_var local_name))) basic.tvoid pos,
+				binop OpLt local_switch_var (ExprBuilder.make_int gen.gcon 0 pos) basic.tbool pos,
+				mk_return (conflict_ctx.delete ehead local_switch_var local_name),
 				None
 			)) basic.tvoid pos) :: common
 		else
@@ -1353,14 +1353,13 @@ let implement_invokeField ctx ~slow_invoke cl =
 			let dyn_arg_local = mk_local dynamic_arg pos in
 			let cases = List.map (switch_case ctx pos) names in
 			(cases,
-				{ eexpr = TReturn(Some (mk_this_call cf (List.map (fun (name,_,t) ->
+				mk_return (
+					mk_this_call cf (List.map (fun (name,_,t) ->
 						let ret = { eexpr = TArray(dyn_arg_local, ExprBuilder.make_int ctx.rcf_gen.gcon !i pos); etype = t_dynamic; epos = pos } in
 						incr i;
 						ret
-					) (fst (get_args (cf.cf_type))) ) ));
-					etype = basic.tvoid;
-					epos = pos
-				}
+					) (fst (get_args (cf.cf_type))))
+				)
 			)
 		in
 
@@ -1378,7 +1377,7 @@ let implement_invokeField ctx ~slow_invoke cl =
 		in
 
 		let default = if !is_override then
-			{ eexpr = TReturn(Some (call_super ctx all_args t_dynamic dyn_fun cl this_t pos) ); etype = basic.tvoid; epos = pos }
+			mk_return (call_super ctx all_args t_dynamic dyn_fun cl this_t pos)
 		else (
 			let field = begin
 				let fun_name = mk_internal_name "hx" "getField" in

+ 9 - 22
src/generators/gencommon/typeParams.ml

@@ -415,12 +415,7 @@ struct
 								{
 									tf_args = [];
 									tf_type = t_dynamic;
-									tf_expr =
-									{
-										eexpr = TReturn( Some call );
-										etype = t_dynamic;
-										epos = p;
-									}
+									tf_expr = mk_return call
 								});
 								etype = cfield.cf_type;
 								epos = p;
@@ -664,19 +659,13 @@ struct
 					{
 						tf_args = [me,None];
 						tf_type = t_dynamic;
-						tf_expr =
-						{
-							eexpr = TReturn( Some
-							{
-								eexpr = TIf(
-									{ eexpr = TBinop(Ast.OpNotEq, mk_local me p, null me.v_type p); etype = basic.tbool; epos = p },
-									call,
-									Some( null me.v_type p )
-								);
-								etype = t_dynamic;
-								epos = p;
-							});
-							etype = basic.tvoid;
+						tf_expr = mk_return {
+							eexpr = TIf(
+								{ eexpr = TBinop(Ast.OpNotEq, mk_local me p, null me.v_type p); etype = basic.tbool; epos = p },
+								call,
+								Some( null me.v_type p )
+							);
+							etype = t_dynamic;
 							epos = p;
 						}
 					});
@@ -703,9 +692,7 @@ struct
 						eexpr = TFunction {
 							tf_type = t_dynamic;
 							tf_args = [];
-							tf_expr = mk_block { this with
-								eexpr = TReturn (Some this)
-							}
+							tf_expr = mk_block (mk_return this)
 						}
 					};
 					cthis.cl_ordered_fields <- field :: cthis.cl_ordered_fields;

+ 1 - 2
src/generators/gencommon/unreachableCodeEliminationSynf.ml

@@ -71,7 +71,6 @@ let rec get_constant_expr e =
 		| _ -> None
 
 let traverse gen java_mode =
-	let basic = gen.gcon.basic in
 	let should_warn = false in
 
 	let do_warn =
@@ -135,7 +134,7 @@ let traverse gen java_mode =
 			| TFunction tf ->
 				let changed, kind = process_expr tf.tf_expr in
 				let changed = if not (ExtType.is_void tf.tf_type) && kind <> BreaksFunction then
-					Type.concat changed { eexpr = TReturn( Some (null tf.tf_type expr.epos) ); etype = basic.tvoid; epos = expr.epos }
+					Type.concat changed (Codegen.mk_return (null tf.tf_type expr.epos))
 				else
 					changed
 				in