瀏覽代碼

Turn TSwitch into a record (#11160)

* [everywhere] add tswitch record

* fix two gencommon problems, but there are more

there are always more
always

* fix converter mishap

* one more gencommon
Simon Krajewski 2 年之前
父節點
當前提交
85ed07d2ca
共有 38 個文件被更改,包括 471 次插入396 次删除
  1. 0 1
      src/codegen/codegen.ml
  2. 10 2
      src/codegen/gencommon/castDetect.ml
  3. 10 5
      src/codegen/gencommon/closuresToClass.ml
  4. 18 6
      src/codegen/gencommon/expressionUnwrap.ml
  5. 1 1
      src/codegen/gencommon/gencommon.ml
  6. 12 4
      src/codegen/gencommon/realTypeParams.ml
  7. 39 24
      src/codegen/gencommon/reflectionCFs.ml
  8. 19 9
      src/codegen/gencommon/switchToIf.ml
  9. 6 2
      src/codegen/gencommon/unnecessaryCastsRemoval.ml
  10. 16 8
      src/codegen/gencommon/unreachableCodeEliminationSynf.ml
  11. 0 6
      src/codegen/overloads.ml
  12. 2 2
      src/core/tOther.ml
  13. 11 83
      src/core/tPrinting.ml
  14. 12 1
      src/core/tType.ml
  15. 51 43
      src/core/texpr.ml
  16. 2 2
      src/filters/filters.ml
  17. 7 7
      src/filters/renameVars.ml
  18. 7 7
      src/generators/gencpp.ml
  19. 11 11
      src/generators/gencs.ml
  20. 5 5
      src/generators/genhl.ml
  21. 29 24
      src/generators/genjava.ml
  22. 10 7
      src/generators/genjs.ml
  23. 18 17
      src/generators/genjvm.ml
  24. 13 9
      src/generators/genlua.ml
  25. 3 3
      src/generators/genneko.ml
  26. 3 3
      src/generators/genphp7.ml
  27. 11 6
      src/generators/genpy.ml
  28. 7 7
      src/generators/genswf9.ml
  29. 14 14
      src/macro/eval/evalJit.ml
  30. 14 5
      src/macro/macroApi.ml
  31. 8 4
      src/optimization/analyzer.ml
  32. 15 10
      src/optimization/analyzerTexpr.ml
  33. 18 10
      src/optimization/analyzerTexprTransformer.ml
  34. 19 11
      src/optimization/inline.ml
  35. 26 21
      src/optimization/optimizer.ml
  36. 13 8
      src/typing/matcher/texprConverter.ml
  37. 7 4
      src/typing/nullSafety.ml
  38. 4 4
      src/typing/typeloadCheck.ml

+ 0 - 1
src/codegen/codegen.ml

@@ -373,7 +373,6 @@ module Dump = struct
 	let dump_types com =
 		match Common.defined_value_safe com Define.Dump with
 			| "pretty" -> dump_types com (Type.s_expr_pretty false "\t" true)
-			| "legacy" -> dump_types com Type.s_expr
 			| "record" -> dump_record com
 			| "position" -> dump_position com
 			| _ -> dump_types com (Type.s_expr_ast (not (Common.defined com Define.DumpIgnoreVarIds)) "\t")

+ 10 - 2
src/codegen/gencommon/castDetect.ml

@@ -1271,8 +1271,16 @@ let configure gen ?(overloads_cast_to_base = false) maybe_empty_t calls_paramete
 				{ e with eexpr = TIf (handle (run econd) gen.gcon.basic.tbool econd.etype, (in_value := false; run (mk_block ethen)), Option.map (fun e -> in_value := false; run (mk_block e)) eelse) }
 			| TWhile (econd, e1, flag) ->
 				{ e with eexpr = TWhile (handle (run econd) gen.gcon.basic.tbool econd.etype, (in_value := false; run (mk_block e1)), flag) }
-			| TSwitch (cond, el_e_l, edef) ->
-				{ e with eexpr = TSwitch(run cond, List.map (fun (el,e) -> (List.map run el, (in_value := false; run (mk_block e)))) el_e_l, Option.map (fun e -> in_value := false; run (mk_block e)) edef) }
+			| TSwitch switch ->
+				let switch = { switch with
+					switch_subject = run switch.switch_subject;
+					switch_cases = List.map (fun case -> {
+						case_patterns = List.map run case.case_patterns;
+						case_expr = (in_value := false; run (mk_block case.case_expr))
+					}) switch.switch_cases;
+					switch_default = Option.map (fun e -> in_value := false; run (mk_block e)) switch.switch_default;
+				} in
+				{ e with eexpr = TSwitch switch }
 			| TFor (v,cond,e1) ->
 				{ e with eexpr = TFor(v, run cond, (in_value := false; run (mk_block e1))) }
 			| TTry (e, ve_l) ->

+ 10 - 5
src/codegen/gencommon/closuresToClass.ml

@@ -1099,7 +1099,10 @@ struct
 			let mk_invoke_switch i api =
 				let t = TFun (func_sig_i i, t_dynamic) in
 				(* case i: return this.invokeX_o(0, 0, 0, 0, 0, ... arg[0], args[1]....); *)
-				[make_int gen.gcon.basic i pos], mk_return (mk (TCall(mk_this (iname i false) t, mk_dyn_call i api)) t_dynamic pos)
+				{
+					case_patterns = [make_int gen.gcon.basic i pos];
+					case_expr = mk_return (mk (TCall(mk_this (iname i false) t, mk_dyn_call i api)) t_dynamic pos)
+				}
 			in
 			let rec loop_cases api arity acc =
 				if arity < 0 then
@@ -1148,11 +1151,13 @@ struct
 						epos = pos;
 					} in
 
+					let switch = {
+						switch_subject = switch_cond;
+						switch_cases = loop_cases api !max_arity [];
+						switch_default = Some(make_throw (mk_arg_exception "Too many arguments" pos) pos);
+					} in
 					{
-						eexpr = TSwitch(
-							switch_cond,
-							loop_cases api !max_arity [],
-							Some(make_throw (mk_arg_exception "Too many arguments" pos) pos));
+						eexpr = TSwitch switch;
 						etype = basic.tvoid;
 						epos = pos;
 					}

+ 18 - 6
src/codegen/gencommon/expressionUnwrap.ml

@@ -170,8 +170,12 @@ let rec expr_stat_map fn (expr:texpr) =
 			{ expr with eexpr = TIf(fn cond, eif, eelse) }
 		| TWhile(cond, block, flag) ->
 			{ expr with eexpr = TWhile(fn cond, block, flag) }
-		| TSwitch(cond, el_block_l, default) ->
-			{ expr with eexpr = TSwitch( fn cond, List.map (fun (el,block) -> (List.map fn el, block)) el_block_l, default ) }
+		| TSwitch switch ->
+			let switch = { switch with
+				switch_subject = fn switch.switch_subject;
+				switch_cases = List.map (fun case -> {case with case_patterns = List.map fn case.case_patterns}) switch.switch_cases;
+			} in
+			{ expr with eexpr = TSwitch switch }
 		| TReturn(eopt) ->
 			{ expr with eexpr = TReturn(Option.map fn eopt) }
 		| TThrow (texpr) ->
@@ -361,8 +365,12 @@ let rec apply_assign assign_fun right =
 	match right.eexpr with
 		| TBlock el ->
 			{ right with eexpr = TBlock(apply_assign_block assign_fun el) }
-		| TSwitch (cond, elblock_l, default) ->
-			{ right with eexpr = TSwitch(cond, List.map (fun (el,block) -> (el, mk_get_block assign_fun block)) elblock_l, Option.map (mk_get_block assign_fun) default) }
+		| TSwitch switch ->
+			let switch = { switch with
+				switch_cases = List.map (fun case -> {case with case_expr = mk_get_block assign_fun case.case_expr}) switch.switch_cases;
+				switch_default = Option.map (mk_get_block assign_fun) switch.switch_default;
+			} in
+			{ right with eexpr = TSwitch switch }
 		| TTry (block, catches) ->
 			{ right with eexpr = TTry(mk_get_block assign_fun block, List.map (fun (v,block) -> (v,mk_get_block assign_fun block) ) catches) }
 		| TIf (cond,eif,eelse) ->
@@ -621,8 +629,12 @@ let configure gen =
 			{ e with eexpr = TBlock block }
 		| TTry (block, catches) ->
 			{ e with eexpr = TTry(traverse (mk_block block), List.map (fun (v,block) -> (v, traverse (mk_block block))) catches) }
-		| TSwitch (cond,el_e_l, default) ->
-			{ e with eexpr = TSwitch(cond, List.map (fun (el,e) -> (el, traverse (mk_block e))) el_e_l, Option.map (fun e -> traverse (mk_block e)) default) }
+		| TSwitch switch ->
+			let switch = { switch with
+				switch_cases = List.map (fun case -> {case with case_expr = traverse (mk_block case.case_expr)}) switch.switch_cases;
+				switch_default = Option.map (fun e -> traverse (mk_block e)) switch.switch_default;
+			} in
+			{ e with eexpr = TSwitch switch }
 		| TWhile (cond,block,flag) ->
 			{e with eexpr = TWhile(cond,traverse (mk_block block), flag) }
 		| TIf (cond, eif, eelse) ->

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

@@ -132,7 +132,7 @@ let path_of_md_def md_def =
 		| _ -> md_def.m_path
 
 let debug_type t = (s_type (print_context())) t
-let debug_expr = s_expr debug_type
+let debug_expr = s_expr_ast true "" debug_type
 
 let debug_mode = ref false
 let trace s = if !debug_mode then print_endline s else ()

+ 12 - 4
src/codegen/gencommon/realTypeParams.ml

@@ -522,7 +522,10 @@ struct
 						t_cf
 						pos
 				in
-				[make_string gen.gcon.basic cf.cf_name pos], expr
+				{
+					case_patterns = [make_string gen.gcon.basic cf.cf_name pos];
+					case_expr = expr;
+				}
 			) fields
 		in
 
@@ -567,10 +570,15 @@ struct
 						(
 							(* default: Reflect.setField(new_me, field, Reflect.field(this, field)) *)
 							let edef = gen.gtools.r_set_field basic.tvoid local_new_me local_field (gen.gtools.r_field false basic.tvoid this local_field) in
-							if fields <> [] then
+							if fields <> [] then begin
 								(* switch(field) { ... } *)
-								mk (TSwitch (local_field, fields_to_cases fields, Some edef)) basic.tvoid pos
-							else
+								let switch = {
+									switch_subject = local_field;
+									switch_cases = fields_to_cases fields;
+									switch_default = Some edef
+								} in
+								mk (TSwitch switch) basic.tvoid pos
+							end else
 								edef;
 						)
 					]) basic.tvoid pos,

+ 39 - 24
src/codegen/gencommon/reflectionCFs.ml

@@ -1000,11 +1000,18 @@ let implement_get_set ctx cl =
 			(if fields <> [] then has_fields := true);
 			let cases = List.map (fun (names, cf) ->
 				(if names = [] then Globals.die "" __LOC__);
-				(List.map (switch_case ctx pos) names, do_field cf cf.cf_type)
+				{
+					case_patterns = List.map (switch_case ctx pos) names;
+					case_expr = do_field cf cf.cf_type;
+				}
 			) fields in
 			let default = Some(do_default()) in
-
-			mk_block { eexpr = TSwitch(local_switch_var, cases, default); etype = basic.tvoid; epos = pos }
+			let switch = {
+				switch_subject = local_switch_var;
+				switch_cases = cases;
+				switch_default = default;
+			} in
+			mk_block { eexpr = TSwitch switch; etype = basic.tvoid; epos = pos }
 		in
 
 		let is_override = match cl.cl_super with
@@ -1177,26 +1184,27 @@ let implement_invokeField ctx slow_invoke cl =
 				let t = apply_params cf.cf_params (List.map (fun _ -> t_dynamic) cf.cf_params) cf.cf_type in
 				mk_this_call_raw cf.cf_name t params
 			in
-			(cases,
-				mk_return (
-					mk_this_call cf (List.map (fun (name,optional,t) ->
-						let idx = make_int ctx.rcf_gen.gcon.basic !i pos in
-						let ret = { eexpr = TArray(dyn_arg_local, idx); etype = t_dynamic; epos = pos } in
-						let ret =
-							if ExtType.is_rest t then
-								{ ret with eexpr = TUnop(Spread,Prefix,{ ret with etype = t }) }
+			{
+				case_patterns = cases;
+				case_expr =	mk_return (
+						mk_this_call cf (List.map (fun (name,optional,t) ->
+							let idx = make_int ctx.rcf_gen.gcon.basic !i pos in
+							let ret = { eexpr = TArray(dyn_arg_local, idx); etype = t_dynamic; epos = pos } in
+							let ret =
+								if ExtType.is_rest t then
+									{ ret with eexpr = TUnop(Spread,Prefix,{ ret with etype = t }) }
+								else
+									ret
+							in
+							incr i;
+							if optional then
+								let condition = binop OpGt dyn_arg_length idx ctx.rcf_gen.gcon.basic.tbool pos in
+								mk (TIf (condition, ret, Some (make_null ret.etype pos))) ret.etype pos
 							else
 								ret
-						in
-						incr i;
-						if optional then
-							let condition = binop OpGt dyn_arg_length idx ctx.rcf_gen.gcon.basic.tbool pos in
-							mk (TIf (condition, ret, Some (make_null ret.etype pos))) ret.etype pos
-						else
-							ret
-					) (fst (get_fun (cf.cf_type))))
-				)
-			)
+						) (fst (get_fun (cf.cf_type))))
+					)
+			}
 		in
 
 		let cfs = List.filter (fun (_,cf) -> match cf.cf_kind with
@@ -1209,7 +1217,10 @@ let implement_invokeField ctx slow_invoke cl =
 			| [] -> cases
 			| _ ->
 				let ncases = List.map (fun cf -> switch_case ctx pos cf.cf_name) old in
-				( ncases, mk_return (slow_invoke this (mk_local (fst (List.hd field_args)) pos) (mk_local dynamic_arg pos)) ) :: cases
+				{
+					case_patterns = ncases;
+					case_expr = mk_return (slow_invoke this (mk_local (fst (List.hd field_args)) pos) (mk_local dynamic_arg pos))
+				} :: cases
 		in
 
 		let default = if !is_override then
@@ -1235,9 +1246,13 @@ let implement_invokeField ctx slow_invoke cl =
 				epos = pos
 			} )
 		in
-
+		let switch = {
+			switch_subject = mk_local switch_var pos;
+			switch_cases = cases;
+			switch_default = Some default;
+		} in
 		{
-			eexpr = TSwitch(mk_local switch_var pos, cases, Some default);
+			eexpr = TSwitch switch;
 			etype = basic.tvoid;
 			epos = pos;
 		}

+ 19 - 9
src/codegen/gencommon/switchToIf.ml

@@ -42,7 +42,7 @@ let configure gen (should_convert:texpr->bool) =
 	let basic = gen.gcon.basic in
 	let rec run e =
 		match e.eexpr with
-		| TSwitch (cond, cases, default) when should_convert e ->
+		| TSwitch ({switch_subject = cond;switch_cases = cases;switch_default = default} as switch) when should_convert e ->
 			let cond_etype, should_cache =
 				match gen.gfollow#run_f cond.etype with
 				| TAbstract ({ a_path = [], "Null" }, [t]) ->
@@ -56,8 +56,13 @@ let configure gen (should_convert:texpr->bool) =
 					cond.etype, false
 			in
 
-			if should_cache && not (should_convert { e with eexpr = TSwitch ({ cond with etype = cond_etype }, cases, default) }) then begin
-				{ e with eexpr = TSwitch (mk_cast cond_etype (run cond), List.map (fun (cs,e) -> (List.map run cs, run e)) cases, Option.map run default) }
+			if should_cache && not (should_convert { e with eexpr = TSwitch {switch with switch_subject = { cond with etype = cond_etype }}}) then begin
+				let switch = { switch with
+					switch_subject = mk_cast cond_etype (run cond);
+					switch_cases = List.map (fun case -> {case_patterns = List.map run case.case_patterns;case_expr = run case.case_expr}) cases;
+					switch_default = Option.map run default;
+				} in
+				{ e with eexpr = TSwitch switch }
 			end else begin
 				let local, fst_block =
 					match cond.eexpr, should_cache with
@@ -96,9 +101,9 @@ let configure gen (should_convert:texpr->bool) =
 
 				let rec loop cases =
 					match cases with
-					| (conds, e) :: [] ->
+					| {case_patterns = conds;case_expr = e} :: [] ->
 						mk (TIf (mk_many_cond conds, run e, Option.map run default)) e.etype e.epos
-					| (conds, e) :: tl ->
+					| {case_patterns = conds;case_expr = e} :: tl ->
 						mk (TIf (mk_many_cond conds, run e, Some (loop tl))) e.etype e.epos
 					| [] ->
 						match default with
@@ -120,7 +125,7 @@ let configure gen (should_convert:texpr->bool) =
 			`switch e { case MyEnum.A: ...; case MyEnum.B: ...; }`, which is supported natively
 			by some target languages like Java and C#.
 		*)
-		| TSwitch (cond, cases, default) ->
+		| TSwitch {switch_subject = cond;switch_cases = cases;switch_default = default}  ->
 			begin
 				try
 					match (simplify_expr cond).eexpr with
@@ -138,7 +143,7 @@ let configure gen (should_convert:texpr->bool) =
 						PMap.iter (fun _ ef -> Hashtbl.add fields ef.ef_index ef) real_enum.e_constrs;
 
 						let enum_expr = Texpr.Builder.make_typeexpr (TEnumDecl real_enum) e.epos in
-						let cases = List.map (fun (patterns, body) ->
+						let cases = List.map (fun {case_patterns = patterns; case_expr = body} ->
 							let patterns = List.map (fun e ->
 								match e.eexpr with
 								| TConst (TInt i) ->
@@ -148,9 +153,14 @@ let configure gen (should_convert:texpr->bool) =
 									raise Not_found
 							) patterns in
 							let body = run body in
-							patterns, body
+							{ case_patterns = patterns;case_expr = body}
 						) cases in
-						{ e with eexpr = TSwitch (enum, cases, Option.map run default) }
+						let switch = {
+							switch_subject = enum;
+							switch_cases = cases;
+							switch_default = Option.map run default;
+						} in
+						{ e with eexpr = TSwitch switch }
 					| _ ->
 						raise Not_found
 				with Not_found ->

+ 6 - 2
src/codegen/gencommon/unnecessaryCastsRemoval.ml

@@ -40,8 +40,12 @@ let rec traverse e =
 		{ e with eexpr = TBlock bl }
 	| TTry (block, catches) ->
 		{ e with eexpr = TTry(traverse (mk_block block), List.map (fun (v,block) -> (v, traverse (mk_block block))) catches) }
-	| TSwitch (cond,el_e_l, default) ->
-		{ e with eexpr = TSwitch(cond, List.map (fun (el,e) -> (el, traverse (mk_block e))) el_e_l, Option.map (fun e -> traverse (mk_block e)) default) }
+	| TSwitch switch ->
+		let switch = { switch with
+			switch_cases = List.map (fun case -> { case with case_expr = traverse (mk_block e)}) switch.switch_cases;
+			switch_default = Option.map (fun e -> traverse (mk_block e)) switch.switch_default;
+		} in
+		{ e with eexpr = TSwitch switch }
 	| TWhile (cond,block,flag) ->
 		{e with eexpr = TWhile(cond,traverse (mk_block block), flag) }
 	| TIf (cond, eif, eelse) ->

+ 16 - 8
src/codegen/gencommon/unreachableCodeEliminationSynf.ml

@@ -178,17 +178,25 @@ let init gen java_mode =
 					has_break := last_has_break;
 					return_loop { expr with eexpr = TWhile(cond,block,flag) } Normal
 				end
-			| TSwitch(cond, el_e_l, None) ->
-				{ expr with eexpr = TSwitch(cond, List.map (fun (el, e) -> (el, handle_case (process_expr e))) el_e_l, None) }, Normal
-			| TSwitch(cond, el_e_l, Some def) ->
+			| TSwitch ({switch_default = None} as switch) ->
+				let switch = { switch with
+					switch_cases = List.map (fun case -> {case with case_expr = handle_case (process_expr case.case_expr)}) switch.switch_cases;
+					switch_default = None;
+				} in
+				{ expr with eexpr = TSwitch switch }, Normal
+			| TSwitch ({switch_default = Some def} as switch) ->
 				let def, k = process_expr def in
 				let def = handle_case (def, k) in
 				let k = ref k in
-				let ret = { expr with eexpr = TSwitch(cond, List.map (fun (el, e) ->
-					let e, ek = process_expr e in
-					k := aggregate_kind !k ek;
-					(el, handle_case (e, ek))
-				) el_e_l, Some def) } in
+				let switch = { switch with
+					switch_cases = List.map (fun case ->
+						let e, ek = process_expr case.case_expr in
+						k := aggregate_kind !k ek;
+						{case with case_expr = handle_case (e, ek)}
+					) switch.switch_cases;
+					switch_default = Some def;
+				} in
+				let ret = { expr with eexpr = TSwitch switch } in
 				ret, !k
 			| TTry (e, catches) ->
 				let e, k = process_expr e in

+ 0 - 6
src/codegen/overloads.ml

@@ -219,12 +219,6 @@ struct
 		| r :: ret ->
 			rm_duplicates (r :: acc) ret
 
-	let s_options rated =
-		String.concat ",\n" (List.map (fun ((elist,t,_),rate) ->
-			"( " ^ (String.concat "," (List.map (fun(e,_) -> s_expr (s_type (print_context())) e) elist)) ^ " ) => " ^
-			"( " ^ (String.concat "," (List.map (fun (i,i2) -> string_of_int i ^ ":" ^ string_of_int i2) rate)) ^ " ) => " ^ (s_type (print_context()) t)
-		) rated)
-
 	let count_optionals t =
 		match follow t with
 		| TFun(args,_) ->

+ 2 - 2
src/core/tOther.ml

@@ -149,8 +149,8 @@ module TExprToExpr = struct
 			EFor (ein,convert_expr e)
 		| TIf (e,e1,e2) -> EIf (convert_expr e,convert_expr e1,eopt e2)
 		| TWhile (e1,e2,flag) -> EWhile (convert_expr e1, convert_expr e2, flag)
-		| TSwitch (e,cases,def) ->
-			let cases = List.map (fun (vl,e) ->
+		| TSwitch {switch_subject = e;switch_cases = cases;switch_default = def} ->
+			let cases = List.map (fun {case_patterns = vl;case_expr = e} ->
 				List.map convert_expr vl,None,(match e.eexpr with TBlock [] -> None | _ -> Some (convert_expr e)),e.epos
 			) cases in
 			let def = match eopt def with None -> None | Some (EBlock [],_) -> Some (None,null_pos) | Some e -> Some (Some e,pos e) in

+ 11 - 83
src/core/tPrinting.ml

@@ -161,7 +161,7 @@ let s_expr_kind e =
 	| TFor (_,_,_) -> "For"
 	| TIf (_,_,_) -> "If"
 	| TWhile (_,_,_) -> "While"
-	| TSwitch (_,_,_) -> "Switch"
+	| TSwitch _ -> "Switch"
 	| TTry (_,_) -> "Try"
 	| TReturn _ -> "Return"
 	| TBreak -> "Break"
@@ -188,81 +188,6 @@ let s_field_access s_type fa = match fa with
 	| FEnum (en,f) -> "enum(" ^ s_type_path en.e_path ^ "." ^ f.ef_name ^ ")"
 	| FDynamic f -> "dynamic(" ^ f ^ ")"
 
-let rec s_expr s_type e =
-	let sprintf = Printf.sprintf in
-	let slist f l = String.concat "," (List.map f l) in
-	let loop = s_expr s_type in
-	let s_var v = v.v_name ^ ":" ^ string_of_int v.v_id ^ if has_var_flag v VCaptured then "[c]" else "" in
-	let str = (match e.eexpr with
-	| TConst c ->
-		"Const " ^ s_const c
-	| TLocal v ->
-		"Local " ^ s_var v
-	| TArray (e1,e2) ->
-		sprintf "%s[%s]" (loop e1) (loop e2)
-	| TBinop (op,e1,e2) ->
-		sprintf "(%s %s %s)" (loop e1) (s_binop op) (loop e2)
-	| TEnumIndex e1 ->
-		sprintf "EnumIndex %s" (loop e1)
-	| TEnumParameter (e1,_,i) ->
-		sprintf "%s[%i]" (loop e1) i
-	| TField (e,f) ->
-		let fstr = s_field_access s_type f in
-		sprintf "%s.%s" (loop e) fstr
-	| TTypeExpr m ->
-		sprintf "TypeExpr %s" (s_type_path (t_path m))
-	| TParenthesis e ->
-		sprintf "Parenthesis %s" (loop e)
-	| TObjectDecl fl ->
-		sprintf "ObjectDecl {%s}" (slist (fun ((f,_,qs),e) -> sprintf "%s : %s" (s_object_key_name f qs) (loop e)) fl)
-	| TArrayDecl el ->
-		sprintf "ArrayDecl [%s]" (slist loop el)
-	| TCall (e,el) ->
-		sprintf "Call %s(%s)" (loop e) (slist loop el)
-	| TNew (c,pl,el) ->
-		sprintf "New %s%s(%s)" (s_type_path c.cl_path) (match pl with [] -> "" | l -> sprintf "<%s>" (slist s_type l)) (slist loop el)
-	| TUnop (op,f,e) ->
-		(match f with
-		| Prefix -> sprintf "(%s %s)" (s_unop op) (loop e)
-		| Postfix -> sprintf "(%s %s)" (loop e) (s_unop op))
-	| TFunction f ->
-		let args = slist (fun (v,o) -> sprintf "%s : %s%s" (s_var v) (s_type v.v_type) (match o with None -> "" | Some c -> " = " ^ loop c)) f.tf_args in
-		sprintf "Function(%s) : %s = %s" args (s_type f.tf_type) (loop f.tf_expr)
-	| TVar (v,eo) ->
-		sprintf "Vars %s" (sprintf "%s : %s%s" (s_var v) (s_type v.v_type) (match eo with None -> "" | Some e -> " = " ^ loop e))
-	| TBlock el ->
-		sprintf "Block {\n%s}" (String.concat "" (List.map (fun e -> sprintf "%s;\n" (loop e)) el))
-	| TFor (v,econd,e) ->
-		sprintf "For (%s : %s in %s,%s)" (s_var v) (s_type v.v_type) (loop econd) (loop e)
-	| TIf (e,e1,e2) ->
-		sprintf "If (%s,%s%s)" (loop e) (loop e1) (match e2 with None -> "" | Some e -> "," ^ loop e)
-	| TWhile (econd,e,flag) ->
-		(match flag with
-		| NormalWhile -> sprintf "While (%s,%s)" (loop econd) (loop e)
-		| DoWhile -> sprintf "DoWhile (%s,%s)" (loop e) (loop econd))
-	| TSwitch (e,cases,def) ->
-		sprintf "Switch (%s,(%s)%s)" (loop e) (slist (fun (cl,e) -> sprintf "case %s: %s" (slist loop cl) (loop e)) cases) (match def with None -> "" | Some e -> "," ^ loop e)
-	| TTry (e,cl) ->
-		sprintf "Try %s(%s) " (loop e) (slist (fun (v,e) -> sprintf "catch( %s : %s ) %s" (s_var v) (s_type v.v_type) (loop e)) cl)
-	| TReturn None ->
-		"Return"
-	| TReturn (Some e) ->
-		sprintf "Return %s" (loop e)
-	| TBreak ->
-		"Break"
-	| TContinue ->
-		"Continue"
-	| TThrow e ->
-		"Throw " ^ (loop e)
-	| TCast (e,t) ->
-		sprintf "Cast %s%s" (match t with None -> "" | Some t -> s_type_path (t_path t) ^ ": ") (loop e)
-	| TMeta ((n,el,_),e) ->
-		sprintf "@%s%s %s" (Meta.to_string n) (match el with [] -> "" | _ -> "(" ^ (String.concat ", " (List.map Ast.Printer.s_expr el)) ^ ")") (loop e)
-	| TIdent s ->
-		"Ident " ^ s
-	) in
-	sprintf "(%s : %s)" str (s_type e.etype)
-
 let rec s_expr_pretty print_var_ids tabs top_level s_type e =
 	let sprintf = Printf.sprintf in
 	let loop = s_expr_pretty print_var_ids tabs false s_type in
@@ -307,9 +232,12 @@ let rec s_expr_pretty print_var_ids tabs top_level s_type e =
 		(match flag with
 		| NormalWhile -> sprintf "while (%s) %s" (loop econd) (loop e)
 		| DoWhile -> sprintf "do (%s) while(%s)" (loop e) (loop econd))
-	| TSwitch (e,cases,def) ->
+	| TSwitch switch ->
 		let ntabs = tabs ^ "\t" in
-		let s = sprintf "switch (%s) {\n%s%s" (loop e) (slist "" (fun (cl,e) -> sprintf "%scase %s: %s;\n" ntabs (clist loop cl) (s_expr_pretty print_var_ids ntabs top_level s_type e)) cases) (match def with None -> "" | Some e -> ntabs ^ "default: " ^ (s_expr_pretty print_var_ids ntabs top_level s_type e) ^ "\n") in
+		let s = sprintf "switch (%s) {\n%s%s"
+			(loop switch.switch_subject)
+			(slist "" (fun case -> sprintf "%scase %s: %s;\n" ntabs (clist loop case.case_patterns) (s_expr_pretty print_var_ids ntabs top_level s_type case.case_expr)) switch.switch_cases)
+			(match switch.switch_default with None -> "" | Some e -> ntabs ^ "default: " ^ (s_expr_pretty print_var_ids ntabs top_level s_type e) ^ "\n") in
 		s ^ tabs ^ "}"
 	| TTry (e,cl) ->
 		sprintf "try %s%s" (loop e) (clist (fun (v,e) -> sprintf " catch (%s:%s) %s" (local v) (s_type v.v_type) (loop e)) cl)
@@ -401,15 +329,15 @@ let rec s_expr_ast print_var_ids tabs s_type e =
 			sprintf "Catch %s%s" (local v None) (tag_args (tabs ^ "\t") [loop ~extra_tabs:"\t" e]);
 		) catches in
 		tag "Try" ((loop e1) :: sl)
-	| TSwitch (e1,cases,eo) ->
-		let sl = List.map (fun (el,e) ->
+	| TSwitch switch ->
+		let sl = List.map (fun {case_patterns = el;case_expr = e} ->
 			tag "Case" ~t:(Some e.etype) ~extra_tabs:"\t" ((List.map loop el) @ [loop ~extra_tabs:"\t" e])
-		) cases in
-		let sl = match eo with
+		) switch.switch_cases in
+		let sl = match switch.switch_default with
 			| None -> sl
 			| Some e -> sl @ [tag "Default" ~t:(Some e.etype) ~extra_tabs:"\t" [loop ~extra_tabs:"\t" e]]
 		in
-		tag "Switch" ((loop e1) :: sl)
+		tag "Switch" ((loop switch.switch_subject) :: sl)
 	| TMeta ((m,el,_),e1) ->
 		let s = Meta.to_string m in
 		let s = match el with

+ 12 - 1
src/core/tType.ml

@@ -177,7 +177,7 @@ and texpr_expr =
 	| TFor of tvar * texpr * texpr
 	| TIf of texpr * texpr * texpr option
 	| TWhile of texpr * texpr * Ast.while_flag
-	| TSwitch of texpr * (texpr list * texpr) list * texpr option
+	| TSwitch of tswitch
 	| TTry of texpr * (tvar * texpr) list
 	| TReturn of texpr option
 	| TBreak
@@ -189,6 +189,17 @@ and texpr_expr =
 	| TEnumIndex of texpr
 	| TIdent of string
 
+and tswitch = {
+	switch_subject : texpr;
+	switch_cases : switch_case list;
+	switch_default: texpr option;
+}
+
+and switch_case = {
+	case_patterns : texpr list;
+	case_expr : texpr;
+}
+
 and tfield_access =
 	| FInstance of tclass * tparams * tclass_field
 	| FStatic of tclass * tclass_field

+ 51 - 43
src/core/texpr.ml

@@ -47,10 +47,10 @@ let iter f e =
 		f e;
 		f e1;
 		(match e2 with None -> () | Some e -> f e)
-	| TSwitch (e,cases,def) ->
-		f e;
-		List.iter (fun (el,e2) -> List.iter f el; f e2) cases;
-		(match def with None -> () | Some e -> f e)
+	| TSwitch switch ->
+		f switch.switch_subject;
+		List.iter (fun case -> List.iter f case.case_patterns; f case.case_expr) switch.switch_cases;
+		(match switch.switch_default with None -> () | Some e -> f e)
 	| TTry (e,catches) ->
 		f e;
 		List.iter (fun (_,e) -> f e) catches
@@ -83,10 +83,10 @@ let check_expr predicate e =
 			predicate fu.tf_expr
 		| TIf (e,e1,e2) ->
 			predicate e || predicate e1 || (match e2 with None -> false | Some e -> predicate e)
-		| TSwitch (e,cases,def) ->
-			predicate e
-			|| List.exists (fun (el,e2) -> List.exists predicate el || predicate e2) cases
-			|| (match def with None -> false | Some e -> predicate e)
+		| TSwitch switch ->
+			predicate switch.switch_subject
+			|| List.exists (fun case -> List.exists predicate case.case_patterns || predicate case.case_expr) switch.switch_cases
+			|| (match switch.switch_default with None -> false | Some e -> predicate e)
 		| TTry (e,catches) ->
 			predicate e || List.exists (fun (_,e) -> predicate e) catches
 
@@ -142,10 +142,14 @@ let map_expr f e =
 		let ec = f ec in
 		let e1 = f e1 in
 		{ e with eexpr = TIf (ec,e1,match e2 with None -> None | Some e -> Some (f e)) }
-	| TSwitch (e1,cases,def) ->
-		let e1 = f e1 in
-		let cases = List.map (fun (el,e2) -> List.map f el, f e2) cases in
-		{ e with eexpr = TSwitch (e1, cases, match def with None -> None | Some e -> Some (f e)) }
+	| TSwitch switch ->
+		let e1 = f switch.switch_subject in
+		let cases = List.map (fun case -> {
+			case_patterns = List.map f case.case_patterns;
+			case_expr = f case.case_expr
+		}) switch.switch_cases in
+		let def = Option.map f switch.switch_default in
+		{ e with eexpr = TSwitch {switch with switch_subject = e1;switch_cases = cases;switch_default = def} }
 	| TTry (e1,catches) ->
 		let e1 = f e1 in
 		{ e with eexpr = TTry (e1, List.map (fun (v,e) -> v, f e) catches) }
@@ -236,10 +240,14 @@ let map_expr_type f ft fv e =
 		let ec = f ec in
 		let e1 = f e1 in
 		{ e with eexpr = TIf (ec,e1,match e2 with None -> None | Some e -> Some (f e)); etype = ft e.etype }
-	| TSwitch (e1,cases,def) ->
-		let e1 = f e1 in
-		let cases = List.map (fun (el,e2) -> List.map f el, f e2) cases in
-		{ e with eexpr = TSwitch (e1, cases, match def with None -> None | Some e -> Some (f e)); etype = ft e.etype }
+	| TSwitch switch ->
+		let e1 = f switch.switch_subject in
+		let cases = List.map (fun case -> {
+			case_patterns = List.map f case.case_patterns;
+			case_expr = f case.case_expr
+		}) switch.switch_cases in
+		let def = Option.map f switch.switch_default in
+		{ e with eexpr = TSwitch {switch with switch_subject = e1;switch_cases = cases;switch_default = def}; etype = ft e.etype }
 	| TTry (e1,catches) ->
 		let e1 = f e1 in
 		{ e with eexpr = TTry (e1, List.map (fun (v,e) -> fv v, f e) catches); etype = ft e.etype }
@@ -284,10 +292,10 @@ let rec equal e1 e2 = match e1.eexpr,e2.eexpr with
 	| TIf(e1,ethen1,None),TIf(e2,ethen2,None) -> equal e1 e2 && equal ethen1 ethen2
 	| TIf(e1,ethen1,Some eelse1),TIf(e2,ethen2,Some eelse2) -> equal e1 e2 && equal ethen1 ethen2 && equal eelse1 eelse2
 	| TWhile(e1,eb1,flag1),TWhile(e2,eb2,flag2) -> equal e1 e2 && equal eb2 eb2 && flag1 = flag2
-	| TSwitch(e1,cases1,eo1),TSwitch(e2,cases2,eo2) ->
-		equal e1 e2 &&
-		safe_for_all2 (fun (el1,e1) (el2,e2) -> safe_for_all2 equal el1 el2 && equal e1 e2) cases1 cases2 &&
-		(match eo1,eo2 with None,None -> true | Some e1,Some e2 -> equal e1 e2 | _ -> false)
+	| TSwitch switch1,TSwitch switch2 ->
+		equal switch1.switch_subject switch2.switch_subject &&
+		safe_for_all2 (fun case1 case2 -> safe_for_all2 equal case1.case_patterns case2.case_patterns && equal case1.case_expr case2.case_expr) switch1.switch_cases switch2.switch_cases &&
+		(match switch1.switch_default,switch2.switch_default with None,None -> true | Some e1,Some e2 -> equal e1 e2 | _ -> false)
 	| TTry(e1,catches1),TTry(e2,catches2) -> equal e1 e2 && safe_for_all2 (fun (v1,e1) (v2,e2) -> v1 == v2 && equal e1 e2) catches1 catches2
 	| TReturn None,TReturn None -> true
 	| TReturn(Some e1),TReturn(Some e2) -> equal e1 e2
@@ -434,15 +442,15 @@ let foldmap f acc e =
 		let acc,e1 = f acc e1 in
 		let acc,eo = foldmap_opt f acc eo in
 		acc,{ e with eexpr = TIf (ec,e1,eo)}
-	| TSwitch (e1,cases,def) ->
-		let acc,e1 = f acc e1 in
-		let acc,cases = List.fold_left (fun (acc,cases) (el,e2) ->
-			let acc,el = foldmap_list f acc el in
-			let acc,e2 = f acc e2 in
-			acc,((el,e2) :: cases)
-		) (acc,[]) cases in
-		let acc,def = foldmap_opt f acc def in
-		acc,{ e with eexpr = TSwitch (e1, cases, def) }
+	| TSwitch switch ->
+		let acc,e1 = f acc switch.switch_subject in
+		let acc,cases = List.fold_left (fun (acc,cases) case ->
+			let acc,el = foldmap_list f acc case.case_patterns in
+			let acc,e2 = f acc case.case_expr in
+			acc,({case_patterns = el;case_expr = e2} :: cases)
+		) (acc,[]) switch.switch_cases in
+		let acc,def = foldmap_opt f acc switch.switch_default in
+		acc,{ e with eexpr = TSwitch {switch with switch_subject = e1;switch_cases = cases;switch_default = def} }
 	| TTry (e1,catches) ->
 		let acc,e1 = f acc e1 in
 		let acc,catches = foldmap_pairs f acc catches in
@@ -732,14 +740,14 @@ let dump_with_pos tabs e =
 			add "TWhile";
 			loop e1;
 			loop e2;
-		| TSwitch(e1,cases,def) ->
+		| TSwitch switch ->
 			add "TSwitch";
-			loop e1;
-			List.iter (fun (el,e) ->
-				List.iter (loop' (tabs ^ "    ")) el;
-				loop' (tabs ^ "      ") e;
-			) cases;
-			Option.may (loop' (tabs ^ "      ")) def
+			loop switch.switch_subject;
+			List.iter (fun case ->
+				List.iter (loop' (tabs ^ "    ")) case.case_patterns;
+				loop' (tabs ^ "      ") case.case_expr;
+			) switch.switch_cases;
+			Option.may (loop' (tabs ^ "      ")) switch.switch_default
 		| TTry(e1,catches) ->
 			add "TTry";
 			loop e1;
@@ -890,15 +898,15 @@ module DeadEnd = struct
 				loop cond || loop if_body && loop else_body
 			| TIf (cond, _, None) ->
 				loop cond
-			| TSwitch(e1, cases, def) ->
+			| TSwitch switch ->
 				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 *)
+					(is_exhaustive switch.switch_subject switch.switch_default) && List.for_all (fun case ->
+						List.exists loop case.case_patterns ||
+						loop case.case_expr
+					) switch.switch_cases &&
+					Option.map_default (loop ) true switch.switch_default (* true because we know it's exhaustive *)
 				in
-				loop e1 || check_exhaustive ()
+				loop switch.switch_subject || check_exhaustive ()
 			| TFor(_, e1, _) ->
 				loop e1
 			| TBinop(OpBoolAnd, e1, e2) ->

+ 2 - 2
src/filters/filters.ml

@@ -221,9 +221,9 @@ let check_local_vars_init ctx e =
 			) catches in
 			loop vars e;
 			join vars cvars;
-		| TSwitch (e,cases,def) ->
+		| TSwitch {switch_subject = e;switch_cases = cases;switch_default = def} ->
 			loop vars e;
-			let cvars = List.map (fun (ec,e) ->
+			let cvars = List.map (fun {case_patterns = ec;case_expr = e} ->
 				let old = !vars in
 				List.iter (loop vars) ec;
 				vars := old;

+ 7 - 7
src/filters/renameVars.ml

@@ -235,13 +235,13 @@ let rec collect_vars ?(in_block=false) rc scope e =
 			collect_vars scope e;
 			if rc.rc_no_catch_var_shadowing then use_var rc scope v;
 		) catches
-	| TSwitch (target, cases, default_opt) when rc.rc_switch_cases_no_blocks ->
-		collect_vars scope target;
-		List.iter (fun (el,e) ->
-			List.iter (collect_vars scope) el;
-			collect_ignore_block ~in_block:true rc scope e
-		) cases;
-		Option.may (collect_ignore_block ~in_block:true rc scope) default_opt
+	| TSwitch switch when rc.rc_switch_cases_no_blocks ->
+		collect_vars scope switch.switch_subject;
+		List.iter (fun case ->
+			List.iter (collect_vars scope) case.case_patterns;
+			collect_ignore_block ~in_block:true rc scope case.case_expr
+		) switch.switch_cases;
+		Option.may (collect_ignore_block ~in_block:true rc scope) switch.switch_default
 	| TBlock exprs when rc.rc_scope = BlockScope && not in_block ->
 		let scope = create_scope (Some scope) in
 		List.iter (collect_vars scope) exprs

+ 7 - 7
src/generators/gencpp.ml

@@ -1698,7 +1698,7 @@ and tcpp_to_string tcpp =
 
 and cpp_class_path_of klass params =
    match (get_meta_string klass.cl_meta Meta.Native)<>"" with
-   | true -> 
+   | true ->
       let typeParams = match params with
       | [] -> ""
       | _ -> "< " ^ String.concat "," (List.map tcpp_to_string params) ^ " >" in
@@ -3134,7 +3134,7 @@ let retype_expression ctx request_type function_args function_type expression_tr
             CppIf(ec, e1, e2), if return_type=TCppVoid then TCppVoid else cpp_type_of expr.etype
 
           (* Switch internal return - wrap whole thing in block  *)
-         | TSwitch (condition,cases,def) ->
+         | TSwitch {switch_subject = condition;switch_cases = cases;switch_default = def} ->
             if return_type<>TCppVoid then
                abort "Value from a switch not handled" expr.epos;
 
@@ -3142,19 +3142,19 @@ let retype_expression ctx request_type function_args function_type expression_tr
             let condition = retype conditionType condition in
             let cppDef = match def with None -> None | Some e -> Some (retype TCppVoid (mk_block e)) in
             if forCppia then begin
-               let cases = List.map (fun (el,e2) ->
+               let cases = List.map (fun {case_patterns = el;case_expr = e2} ->
                   let cppBlock = retype TCppVoid (mk_block e2) in
                   (List.map (retype conditionType) el), cppBlock ) cases in
                CppSwitch(condition, conditionType, cases, cppDef, -1), TCppVoid
             end else (try
                (match conditionType with TCppScalar("int") | TCppScalar("bool") -> () | _ -> raise Not_found );
-               let cases = List.map (fun (el,e2) ->
+               let cases = List.map (fun {case_patterns = el;case_expr = e2} ->
                   (List.map const_int_of el), (retype TCppVoid (mk_block e2)) ) cases in
                CppIntSwitch(condition, cases, cppDef), TCppVoid
             with Not_found ->
                let label = alloc_file_id () in
                (* do something better maybe ... *)
-               let cases = List.map (fun (el,e2) ->
+               let cases = List.map (fun {case_patterns = el;case_expr = e2} ->
                   let cppBlock = retype TCppVoid (mk_block e2) in
                   let gotoExpr = { cppexpr = CppGoto(label); cpptype = TCppVoid; cpppos = e2.epos } in
                   let cppBlock = cpp_append_block cppBlock  gotoExpr in
@@ -7952,11 +7952,11 @@ class script_writer ctx filename asciiOut =
    | TEnumIndex expr ->
          this#write ( (this#op IaCallMember) ^ (this#typeTextString "::hx::EnumBase") ^ " " ^ (this#stringText "__Index") ^ "0" ^ (this#commentOf ("Enum index") ) ^ "\n");
          this#gen_expression expr;
-   | TSwitch (condition,cases,optional_default)  ->
+   | TSwitch {switch_subject = condition;switch_cases = cases;switch_default = optional_default} ->
          this#write ( (this#op IaSwitch) ^ (string_of_int (List.length cases)) ^ " " ^
                            (match optional_default with None -> "0" | Some _ -> "1") ^ "\n");
          this#gen_expression condition;
-         List.iter (fun (cases_list,expression) ->
+         List.iter (fun {case_patterns = cases_list;case_expr = expression} ->
             this#writeList ("\t\t\t"^indent) (List.length cases_list);
             List.iter (fun value -> this#gen_expression value ) cases_list;
             this#gen_expression expression;

+ 11 - 11
src/generators/gencs.ml

@@ -1722,12 +1722,12 @@ let generate con =
 								in_value := true;
 								expr_s w (mk_paren econd);
 						)
-					| TSwitch (econd, ele_l, default) ->
+					| TSwitch switch ->
 						write w "switch ";
-						expr_s w (mk_paren econd);
+						expr_s w (mk_paren switch.switch_subject);
 						write w " ";
 						begin_block w;
-						List.iter (fun (el, e) ->
+						List.iter (fun {case_patterns = el;case_expr = e}  ->
 							List.iter (fun e ->
 								write w "case ";
 								in_value := true;
@@ -1739,12 +1739,12 @@ let generate con =
 							expr_s w (mk_block e);
 							newline w;
 							newline w
-						) ele_l;
-						if is_some default then begin
+						) switch.switch_cases;
+						if is_some switch.switch_default then begin
 							write w "default:";
 							newline w;
 							in_value := false;
-							expr_s w (get default);
+							expr_s w (get switch.switch_default);
 							newline w;
 						end;
 						end_block w
@@ -3387,13 +3387,13 @@ let generate con =
 
 		SwitchToIf.configure gen (fun e ->
 			match e.eexpr with
-				| TSwitch(cond, cases, def) ->
-					(match gen.gfollow#run_f cond.etype with
+				| TSwitch switch ->
+					(match gen.gfollow#run_f switch.switch_subject.etype with
 						| TAbstract ({ a_path = ([], "Int") },[])
 						| TInst({ cl_path = ([], "String") },[]) ->
-							(List.exists (fun (c,_) ->
-								List.exists (fun expr -> match expr.eexpr with | TConst _ -> false | _ -> true ) c
-							) cases)
+							(List.exists (fun case ->
+								List.exists (fun expr -> match expr.eexpr with | TConst _ -> false | _ -> true ) case.case_patterns
+							) switch.switch_cases)
 						| _ -> true
 					)
 				| _ -> die "" __LOC__

+ 5 - 5
src/generators/genhl.ml

@@ -2733,7 +2733,7 @@ and eval_expr ctx e =
 		eval_expr ctx e
 	| TFor (v,it,loop) ->
 		eval_expr ctx (Texpr.for_remap ctx.com.basic v it loop e.epos)
-	| TSwitch (en,cases,def) ->
+	| TSwitch {switch_subject = en;switch_cases = cases;switch_default = def} ->
 		let rt = to_type ctx e.etype in
 		let r = alloc_tmp ctx rt in
 		(try
@@ -2747,12 +2747,12 @@ and eval_expr ctx e =
 				| _ ->
 					raise Exit
 			in
-			List.iter (fun (values,_) ->
+			List.iter (fun case ->
 				List.iter (fun v ->
 					let i = get_int v in
 					if i < 0 then raise Exit;
 					if i > !max then max := i;
-				) values;
+				) case.case_patterns;
 			) cases;
 			if !max > 255 || cases = [] then raise Exit;
 			let ridx = eval_to ctx en HI32 in
@@ -2766,7 +2766,7 @@ and eval_expr ctx e =
 				let re = eval_to ctx e rt in
 				if rt <> HVoid then op ctx (OMov (r,re)));
 			let jends = ref [jump ctx (fun i -> OJAlways i)] in
-			List.iter (fun (values,ecase) ->
+			List.iter (fun {case_patterns = values;case_expr = ecase} ->
 				List.iter (fun v ->
 					Array.set indexes (get_int v) (current_pos ctx - switch_pos)
 				) values;
@@ -2779,7 +2779,7 @@ and eval_expr ctx e =
 		with Exit ->
 			let jends = ref [] in
 			let rvalue = eval_expr ctx en in
-			let loop (cases,e) =
+			let loop {case_patterns = cases;case_expr = e} =
 				hold ctx rvalue;
 				let ok = List.map (fun c ->
 					let ct = common_type ctx en c true c.epos in

+ 29 - 24
src/generators/genjava.ml

@@ -366,8 +366,8 @@ struct
 			| 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) ->
-				List.for_all (fun (_,e) -> is_final_return_expr e) el_e_l && Option.map_default is_final_return_expr false edef
+			| TSwitch switch ->
+				List.for_all (fun case -> is_final_return_expr case.case_expr) switch.switch_cases && Option.map_default is_final_return_expr false switch.switch_default
 			| TIf (_,eif, Some eelse) ->
 				is_final_return_expr eif && is_final_return_expr eelse
 			| TFor (_,_,e) ->
@@ -486,7 +486,7 @@ struct
 		let rec reorder_cases unordered ordered =
 			match unordered with
 				| [] -> ordered
-				| (el, e) :: tl ->
+				| {case_patterns = el;case_expr = e} :: tl ->
 					let current = Hashtbl.create 1 in
 					List.iter (fun e ->
 						let str = get_str e in
@@ -497,21 +497,21 @@ struct
 					let rec extract_fields cases found_cases ret_cases =
 						match cases with
 							| [] -> found_cases, ret_cases
-							| (el, e) :: tl ->
+							| {case_patterns = el;case_expr = e}  :: tl ->
 								if List.exists (fun e -> Hashtbl.mem current (java_hash (get_str e)) ) el then begin
 									has_conflict := true;
 									List.iter (fun e -> Hashtbl.add current (java_hash (get_str e)) true) el;
-									extract_fields tl ( (el, e) :: found_cases ) ret_cases
+									extract_fields tl ( {case_patterns = el;case_expr = e}  :: found_cases ) ret_cases
 								end else
-									extract_fields tl found_cases ( (el, e) :: ret_cases )
+									extract_fields tl found_cases ( {case_patterns = el;case_expr = e}  :: ret_cases )
 					in
 					let found, remaining = extract_fields tl [] [] in
 					let ret = if found <> [] then
-						let ret = List.sort (fun (e1,_) (e2,_) -> compare (List.length e2) (List.length e1) ) ( (el, e) :: found ) in
+						let ret = List.sort (fun case1 case2 -> compare (List.length case2.case_patterns) (List.length case1.case_patterns) ) ( {case_patterns = el;case_expr = e} :: found ) in
 						let rec loop ret acc =
 							match ret with
-								| (el, e) :: ( (_,_) :: _ as tl ) -> loop tl ( (true, el, e) :: acc )
-								| (el, e) :: [] -> ( (false, el, e) :: acc )
+								| {case_patterns = el;case_expr = e}  :: ( _ :: _ as tl ) -> loop tl ( (true, el, e) :: acc )
+								| {case_patterns = el;case_expr = e}  :: [] -> ( (false, el, e) :: acc )
 								| _ -> die "" __LOC__
 						in
 						List.rev (loop ret [])
@@ -574,13 +574,18 @@ struct
 
 			let e = if has_fallback then { e with eexpr = TBlock([ e; mk (TIdent "__fallback__") t_dynamic e.epos]) } else e in
 
-			(el, e)
+			{case_patterns = el;case_expr = e}
 		in
 
 		let is_not_null_check = mk (TBinop (OpNotEq, local, { local with eexpr = TConst TNull })) basic.tbool local.epos in
 		let if_not_null e = { e with eexpr = TIf (is_not_null_check, e, None) } in
+		let switch = {
+			switch_subject = !local_hashcode;
+			switch_cases = List.map change_case (reorder_cases ecases []);
+			switch_default = None
+		} in
 		let switch = if_not_null { eswitch with
-			eexpr = TSwitch(!local_hashcode, List.map change_case (reorder_cases ecases []), None);
+			eexpr = TSwitch switch;
 		} in
 		(if !has_case then begin
 			(if has_default then block := { e1 with eexpr = TVar(execute_def_var, Some({ e1 with eexpr = TConst(TBool true); etype = basic.tbool })); etype = basic.tvoid } :: !block);
@@ -818,9 +823,9 @@ struct
 				| TCast(expr, _) when is_string e.etype ->
 					{ e with eexpr = TCall( mk_static_field_access_infer runtime_cl "toString" expr.epos [], [run expr] ) }
 
-				| TSwitch(cond, ecases, edefault) when is_string cond.etype ->
+				| TSwitch switch when is_string switch.switch_subject.etype ->
 					(*let change_string_switch gen eswitch e1 ecases edefault =*)
-					change_string_switch gen e (run cond) (List.map (fun (el,e) -> (el, run e)) ecases) (Option.map run edefault)
+					change_string_switch gen e (run switch.switch_subject) (List.map (fun case -> {case with case_expr = run case.case_expr}) switch.switch_cases) (Option.map run switch.switch_default)
 
 				| TBinop( (Ast.OpNotEq as op), e1, e2)
 				| TBinop( (Ast.OpEq as op), e1, e2) when not (is_null e2 || is_null e1) && (is_string e1.etype || is_string e2.etype || is_equatable gen e1.etype || is_equatable gen e2.etype) ->
@@ -1744,11 +1749,11 @@ let generate con =
 							in_value := true;
 							expr_s w (mk_paren econd);
 					)
-				| TSwitch (econd, ele_l, default) ->
+				| TSwitch switch ->
 					write w "switch ";
-					expr_s w (mk_paren econd);
+					expr_s w (mk_paren switch.switch_subject);
 					begin_block w;
-					List.iter (fun (el, e) ->
+					List.iter (fun {case_patterns = el;case_expr = e}  ->
 						List.iter (fun e ->
 							write w "case ";
 							in_value := true;
@@ -1765,12 +1770,12 @@ let generate con =
 						expr_s w (mk_block e);
 						newline w;
 						newline w
-					) ele_l;
-					if is_some default then begin
+					) switch.switch_cases;
+					if is_some switch.switch_default then begin
 						write w "default:";
 						newline w;
 						in_value := false;
-						expr_s w (get default);
+						expr_s w (get switch.switch_default);
 						newline w;
 					end;
 					end_block w
@@ -2623,14 +2628,14 @@ let generate con =
 
 	SwitchToIf.configure gen (fun e ->
 		match e.eexpr with
-			| TSwitch(cond, cases, def) ->
-				(match gen.gfollow#run_f cond.etype with
+			| TSwitch switch ->
+				(match gen.gfollow#run_f switch.switch_subject.etype with
 					| TInst( { cl_path = (["haxe"], "Int32") }, [] )
 					| TAbstract ({ a_path = ([], "Int") },[])
 					| TInst({ cl_path = ([], "String") },[]) ->
-						(List.exists (fun (c,_) ->
-							List.exists (fun expr -> match expr.eexpr with | TConst _ -> false | _ -> true ) c
-						) cases)
+						(List.exists (fun case ->
+							List.exists (fun expr -> match expr.eexpr with | TConst _ -> false | _ -> true ) case.case_patterns
+						) switch.switch_cases)
 					| _ -> true
 				)
 			| _ -> die "" __LOC__

+ 10 - 7
src/generators/genjs.ml

@@ -866,12 +866,12 @@ and gen_expr ctx e =
 		ctx.catch_vars <- List.tl ctx.catch_vars
 	| TTry _ ->
 		abort "Unhandled try/catch, please report" e.epos
-	| TSwitch (e,cases,def) ->
+	| TSwitch {switch_subject = e;switch_cases = cases;switch_default = def} ->
 		spr ctx "switch";
 		gen_value ctx e;
 		spr ctx " {";
 		newline ctx;
-		List.iter (fun (el,e2) ->
+		List.iter (fun {case_patterns = el;case_expr = e2} ->
 			List.iter (fun e ->
 				match e.eexpr with
 				| TConst(c) when c = TNull ->
@@ -1078,12 +1078,15 @@ and gen_value ctx e =
 		(match eo with
 		| None -> spr ctx "null"
 		| Some e -> gen_value ctx e);
-	| TSwitch (cond,cases,def) ->
+	| TSwitch switch ->
 		let v = value() in
-		gen_expr ctx (mk (TSwitch (cond,
-			List.map (fun (e1,e2) -> (e1,assign e2)) cases,
-			match def with None -> None | Some e -> Some (assign e)
-		)) e.etype e.epos);
+		let switch = { switch with
+			switch_cases = List.map (fun case -> { case with
+				case_expr = assign case.case_expr
+			}) switch.switch_cases;
+			switch_default = Option.map assign switch.switch_default
+		} in
+		gen_expr ctx (mk (TSwitch switch) e.etype e.epos);
 		v()
 	| TTry (b,catchs) ->
 		let v = value() in

+ 18 - 17
src/generators/genjvm.ml

@@ -347,17 +347,17 @@ let write_class gctx path jc =
 	gctx.out#add_entry (Bytes.unsafe_to_string (IO.close_out ch)) path;
 	t()
 
-let is_const_int_pattern (el,_) =
+let is_const_int_pattern case =
 	List.for_all (fun e -> match e.eexpr with
 		| TConst (TInt _) -> true
 		| _ -> false
-	) el
+	) case.case_patterns
 
-let is_const_string_pattern (el,_) =
+let is_const_string_pattern case =
 	List.for_all (fun e -> match e.eexpr with
 		| TConst (TString _) -> true
 		| _ -> false
-	) el
+	) case.case_patterns
 
 let is_interface_var_access c cf =
 	(has_class_flag c CInterface) && match cf.cf_kind with
@@ -909,21 +909,22 @@ class texpr_to_jvm
 			label_else#if_ (if flip then CmpNe else CmpEq)
 		end
 
-	method switch ret e1 cases def =
+	method switch ret {switch_subject = e1;switch_cases = cases;switch_default = def} =
 		let need_val = match ret with
 			| RValue _ -> true
 			| RReturn -> return_type <> None
 			| _ -> false
 		in
+		(* TODO: this seems to be missing the default, though in that case there probably wouldn't be a TSwitch in the AST *)
 		if cases = [] then
 			self#texpr ret e1
 		else if List.for_all is_const_int_pattern cases then begin
-			let cases = List.map (fun (el,e) ->
+			let cases = List.map (fun case ->
 				let il = List.map (fun e -> match e.eexpr with
 					| TConst (TInt i32) -> i32
 					| _ -> die "" __LOC__
-				) el in
-				(il,(fun () -> self#texpr ret e))
+				) case.case_patterns in
+				(il,(fun () -> self#texpr ret case.case_expr))
 			) cases in
 			let def = match def with
 				| None -> None
@@ -933,12 +934,12 @@ class texpr_to_jvm
 			jm#cast TInt;
 			jm#int_switch need_val cases def
 		end else if List.for_all is_const_string_pattern cases then begin
-			let cases = List.map (fun (el,e) ->
+			let cases = List.map (fun case ->
 				let sl = List.map (fun e -> match e.eexpr with
 					| TConst (TString s) -> s
 					| _ -> die "" __LOC__
-				) el in
-				(sl,(fun () -> self#texpr ret e))
+				) case.case_patterns in
+				(sl,(fun () -> self#texpr ret case.case_expr))
 			) cases in
 			let def = match def with
 				| None -> None
@@ -958,9 +959,9 @@ class texpr_to_jvm
 			self#cast v.v_type;
 			store();
 			let ev = mk (TLocal v) v.v_type null_pos in
-			let el = List.rev_map (fun (el,e) ->
+			let el = List.rev_map (fun case ->
 				let f e' = mk (TBinop(OpEq,ev,e')) com.basic.tbool e'.epos in
-				let e_cond = match el with
+				let e_cond = match case.case_patterns with
 					| [] -> die "" __LOC__
 					| [e] -> f e
 					| e :: el ->
@@ -968,10 +969,10 @@ class texpr_to_jvm
 							mk (TBinop(OpBoolOr,eacc,f e)) com.basic.tbool e.epos
 						) (f e) el
 				in
-				(e_cond,e)
+				(e_cond,case.case_expr)
 			) cases in
 			(* If we rewrite an exhaustive switch that has no default value, treat the last case as the default case to satisfy control flow. *)
-			let cases,def = if need_val && def = None then (match List.rev cases with (_,e) :: cases -> List.rev cases,Some e | _ -> die "" __LOC__) else cases,def in
+			let cases,def = if need_val && def = None then (match List.rev cases with case :: cases -> List.rev cases,Some case.case_expr | _ -> die "" __LOC__) else cases,def in
 			let e = List.fold_left (fun e_else (e_cond,e_then) -> Some (mk (TIf(e_cond,e_then,e_else)) e_then.etype e_then.epos)) def el in
 			self#texpr ret (Option.get e);
 			pop_scope()
@@ -1928,8 +1929,8 @@ class texpr_to_jvm
 					self#texpr ret (mk_block e3);
 					if need_val ret then self#cast e.etype;
 				)
-		| TSwitch(e1,cases,def) ->
-			self#switch ret e1 cases def
+		| TSwitch switch ->
+			self#switch ret switch
 		| TWhile(e1,e2,flag) ->
 			block_exits <- ExitLoop :: block_exits;
 			let is_true_loop = match (Texpr.skip e1).eexpr with TConst (TBool true) -> true | _ -> false in

+ 13 - 9
src/generators/genlua.ml

@@ -1006,8 +1006,8 @@ and gen_expr ?(local=true) ctx e = begin
         println ctx "elseif _hx_result ~= _hx_pcall_default then";
         println ctx "  return _hx_result";
         print ctx "end";
-    | TSwitch (e,cases,def) ->
-        List.iteri (fun cnt (el,e2) ->
+    | TSwitch {switch_subject = e;switch_cases = cases;switch_default = def} ->
+        List.iteri (fun cnt {case_patterns = el;case_expr = e2} ->
             if cnt == 0 then spr ctx "if "
             else (newline ctx; spr ctx "elseif ");
             List.iteri (fun ccnt e3 ->
@@ -1086,7 +1086,8 @@ and gen_block_element ctx e  =
              | Increment -> print ctx " + 1;"
              | _ -> print ctx " - 1;"
             )
-        | TSwitch (e,[],def) ->
+        | TSwitch {switch_subject = e; switch_cases = [];switch_default = def} ->
+			(* TODO: this omits the subject which is not correct in the general case *)
             (match def with
              | None -> ()
              | Some e -> gen_block_element ctx e)
@@ -1262,12 +1263,15 @@ and gen_value ctx e =
         gen_elseif ctx eo;
         spr ctx " end";
         v()
-    | TSwitch (cond,cases,def) ->
-        let v = value() in
-        gen_expr ctx (mk (TSwitch (cond,
-                                   List.map (fun (e1,e2) -> (e1,assign e2)) cases,
-                                   match def with None -> None | Some e -> Some (assign e)
-                                  )) e.etype e.epos);
+    | TSwitch switch ->
+		let v = value() in
+		let switch = { switch with
+			switch_cases = List.map (fun case -> { case with
+				case_expr = assign case.case_expr
+			}) switch.switch_cases;
+			switch_default = Option.map assign switch.switch_default
+		} in
+		gen_expr ctx (mk (TSwitch switch) e.etype e.epos);
         v()
     | TTry (b,catchs) ->
         let v = value() in

+ 3 - 3
src/generators/genneko.ml

@@ -373,13 +373,13 @@ and gen_expr ctx e =
 		gen_expr ctx (Codegen.default_cast ~vtmp:"@tmp" ctx.com e1 t e.etype e.epos)
 	| TIdent s ->
 		ident p s
-	| TSwitch (e,cases,eo) ->
+	| TSwitch {switch_subject = e;switch_cases = cases;switch_default = eo} ->
 		let e = gen_expr ctx e in
 		let eo = (match eo with None -> None | Some e -> Some (gen_expr ctx e)) in
 		try
 			(ESwitch (
 				e,
-				List.map (fun (el,e2) ->
+				List.map (fun {case_patterns = el;case_expr = e2} ->
 					match List.map (gen_expr ctx) el with
 					| [] -> die "" __LOC__
 					| [e] -> e, gen_expr ctx e2
@@ -391,7 +391,7 @@ and gen_expr ctx e =
 			Exit ->
 				(EBlock [
 					(EVars ["@tmp",Some e],p);
-					List.fold_left (fun acc (el,e) ->
+					List.fold_left (fun acc {case_patterns = el;case_expr = e} ->
 						let cond = (match el with
 							| [] -> die "" __LOC__
 							| e :: l ->

+ 3 - 3
src/generators/genphp7.ml

@@ -1682,7 +1682,7 @@ class code_writer (ctx:php_generator_context) hx_type_path php_name =
 						| _ ->
 							self#write_expr_while condition expr do_while
 					)
-				| TSwitch (switch, cases, default ) -> self#write_expr_switch switch cases default
+				| TSwitch switch -> self#write_expr_switch switch.switch_subject switch.switch_cases switch.switch_default
 				| TTry (try_expr, catches) -> self#write_expr_try_catch try_expr catches
 				| TReturn expr -> self#write_expr_return expr
 				| TBreak -> self#write "break"
@@ -1856,7 +1856,7 @@ class code_writer (ctx:php_generator_context) hx_type_path php_name =
 						| TFor (_, _, _) -> false
 						| TFunction _ -> false
 						| TBlock _ -> false
-						| TSwitch (_, _, _) -> false
+						| TSwitch _ -> false
 						| _ -> true
 			in
 			if needs_closure then
@@ -2836,7 +2836,7 @@ class code_writer (ctx:php_generator_context) hx_type_path php_name =
 			let rec write_cases cases =
 				match cases with
 					| [] -> ()
-					| (conditions, expr) :: rest ->
+					| {case_patterns = conditions;case_expr = expr} :: rest ->
 						self#write "if (";
 						write_conditions conditions;
 						self#write ") ";

+ 11 - 6
src/generators/genpy.ml

@@ -386,7 +386,7 @@ module Transformer = struct
 
 	and transform_switch ae is_value e1 cases edef =
 		let case_functions = ref [] in
-		let case_to_if (el,e) eelse =
+		let case_to_if {case_patterns = el;case_expr = e} eelse =
 			let val_reversed = List.rev el in
 			let mk_eq e = mk (TBinop(OpEq,e1,e)) !t_bool (punion e1.epos e.epos) in
 			let cond = match val_reversed with
@@ -435,7 +435,7 @@ module Transformer = struct
 
 	and transform_string_switch ae is_value e1 cases edef =
 		let length_map = Hashtbl.create 0 in
-		List.iter (fun (el,e) ->
+		List.iter (fun {case_patterns = el;case_expr = e} ->
 			List.iter (fun es ->
 				match es.eexpr with
 				| TConst (TString s) ->
@@ -464,7 +464,7 @@ module Transformer = struct
 			let cases = Hashtbl.fold (fun i el acc ->
 				let eint = mk (TConst (TInt (Int32.of_int i))) !t_int e1.epos in
 				let fs = match List.fold_left (fun eacc ec -> Some (mk_if ec eacc)) edef !el with Some e -> e | None -> die "" __LOC__ in
-				([eint],fs) :: acc
+				({case_patterns = [eint];case_expr = fs}) :: acc
 			) length_map [] in
 			let c_string = match !t_string with TInst(c,_) -> c | _ -> die "" __LOC__ in
 			let cf_length = PMap.find "length" c_string.cl_fields in
@@ -472,9 +472,14 @@ module Transformer = struct
 			let res_var = alloc_var (ae.a_next_id()) ef.etype ef.epos in
 			let res_local = {ef with eexpr = TLocal res_var} in
 			let var_expr = {ef with eexpr = TVar(res_var,Some ef)} in
+			let switch = {
+				switch_subject = res_local;
+				switch_cases = cases;
+				switch_default = edef
+			} in
 			let e = mk (TBlock [
 				var_expr;
-				mk (TSwitch(res_local,cases,edef)) ae.a_expr.etype e1.epos
+				mk (TSwitch switch) ae.a_expr.etype e1.epos
 			]) ae.a_expr.etype e1.epos in
 			forward_transform e ae
 
@@ -826,7 +831,7 @@ module Transformer = struct
 			let new_expr = { ae.a_expr with eexpr = TWhile( true_expr, new_e, NormalWhile) } in
 			forward_transform new_expr ae
 
-		| (is_value, TSwitch(e, cases, edef)) ->
+		| (is_value, TSwitch {switch_subject = e;switch_cases = cases;switch_default = edef}) ->
 			begin match follow e.etype with
 				| TInst({cl_path = [],"str"},_) ->
 					transform_string_switch ae is_value e cases edef
@@ -1894,7 +1899,7 @@ module Generator = struct
 						| TConst (TSuper | TThis) | TThrow _ | TReturn _ ->
 							raise Exit
 						(* TODO: We could do some branch intersection stunts to make this more accurate. *)
-						| TIf(e1,_,_) | TSwitch(e1,_,_) | TWhile(e1,_,_) ->
+						| TIf(e1,_,_) | TSwitch ({switch_subject = e1; _}) | TWhile(e1,_,_) ->
 							loop e1
 						| _ ->
 							Type.iter loop e

+ 7 - 7
src/generators/genswf9.ml

@@ -1298,7 +1298,7 @@ let rec gen_expr_content ctx retval e =
 		write ctx (HJump (J3Always,0));
 		ctx.continues <- (fun target -> DynArray.set ctx.code op (HJump (J3Always,target - p))) :: ctx.continues;
 		no_value ctx retval
-	| TSwitch (e0,el,eo) ->
+	| TSwitch {switch_subject = e0;switch_cases = cases;switch_default = eo} ->
 		let t = classify ctx e.etype in
 		(try
 			let t0 = classify ctx e0.etype in
@@ -1310,9 +1310,9 @@ let rec gen_expr_content ctx retval e =
 				| TParenthesis e | TBlock [e] | TMeta (_,e) -> get_int e
 				| _ -> raise Not_found
 			in
-			List.iter (fun (vl,_) -> List.iter (fun v ->
+			List.iter (fun case -> List.iter (fun v ->
 				try ignore (get_int v) with _ -> raise Exit
-			) vl) el;
+			) case.case_patterns ) cases;
 			gen_expr ctx true e0;
 			if t0 <> KInt then write ctx HToInt;
 			let switch, case = begin_switch ctx in
@@ -1325,14 +1325,14 @@ let rec gen_expr_content ctx retval e =
 			| Some e ->
 				gen_expr ctx retval e;
 				if retval && classify ctx e.etype <> t then coerce ctx t);
-			let jends = List.map (fun (vl,e) ->
+			let jends = List.map (fun {case_patterns = vl;case_expr = e} ->
 				let j = jump ctx J3Always in
 				List.iter (fun v -> case (get_int v)) vl;
 				pop_value ctx retval;
 				gen_expr ctx retval e;
 				if retval && classify ctx e.etype <> t then coerce ctx t;
 				j
-			) el in
+			) cases in
 			List.iter (fun j -> j()) jends;
 			switch();
 		with Exit ->
@@ -1341,7 +1341,7 @@ let rec gen_expr_content ctx retval e =
 		set_reg ctx r;
 		let branch = begin_branch ctx in
 		let prev = ref (fun () -> ()) in
-		let jend = List.map (fun (vl,e) ->
+		let jend = List.map (fun {case_patterns = vl;case_expr = e} ->
 			(!prev)();
 			let rec loop = function
 				| [] ->
@@ -1362,7 +1362,7 @@ let rec gen_expr_content ctx retval e =
 			pop_value ctx retval;
 			if retval && classify ctx e.etype <> t then coerce ctx t;
 			jump ctx J3Always
-		) el in
+		) cases in
 		(!prev)();
 		free_reg ctx r;
 		(match eo with

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

@@ -51,11 +51,11 @@ let is_string t = match follow t with
 	| TInst({cl_path=[],"String"},_) -> true
 	| _ -> false
 
-let is_const_int_pattern (el,_) =
+let is_const_int_pattern case =
 	List.for_all (fun e -> match e.eexpr with
 		| TConst (TInt _) -> true
 		| _ -> false
-	) el
+	) case.case_patterns
 
 open EvalJitContext
 
@@ -248,12 +248,12 @@ and jit_expr jit return e =
 			| Some e -> jit_expr jit return e
 		in
 		emit_if exec_cond exec_then exec_else
-	| TSwitch(e1,cases,def) when is_int e1.etype && List.for_all is_const_int_pattern cases ->
-		let exec = jit_expr jit false e1 in
+	| TSwitch switch when is_int switch.switch_subject.etype && List.for_all is_const_int_pattern switch.switch_cases ->
+		let exec = jit_expr jit false switch.switch_subject in
 		let h = ref IntMap.empty in
 		let max = ref 0 in
 		let min = ref max_int in
-		List.iter (fun (el,e) ->
+		List.iter (fun {case_patterns = el;case_expr = e} ->
 			push_scope jit e.epos;
 			let exec = jit_expr jit return e in
 			List.iter (fun e -> match e.eexpr with
@@ -265,14 +265,14 @@ and jit_expr jit return e =
 				| _ -> die "" __LOC__
 			) el;
 			pop_scope jit;
-		) cases;
-		let exec_def = jit_default jit return def in
+		) switch.switch_cases;
+		let exec_def = jit_default jit return switch.switch_default in
 		let l = !max - !min + 1 in
 		if l > 0 && l < 256 then begin
 			let cases = Array.init l (fun i -> try IntMap.find (i + !min) !h with Not_found -> exec_def) in
-			emit_int_switch_array (- !min) exec cases exec_def e1.epos
+			emit_int_switch_array (- !min) exec cases exec_def switch.switch_subject.epos
 		end else
-			emit_int_switch_map exec !h exec_def e1.epos
+			emit_int_switch_map exec !h exec_def switch.switch_subject.epos
 	(* | TSwitch(e1,cases,def) when is_string e1.etype ->
 		let exec = jit_expr jit false e1 in
 		let h = ref PMap.empty in
@@ -287,17 +287,17 @@ and jit_expr jit return e =
 		) cases;
 		let exec_def = jit_default jit return def in
 		emit_string_switch_map exec !h exec_def e1.epos *)
-	| TSwitch(e1,cases,def) ->
-		let exec = jit_expr jit false e1 in
+	| TSwitch switch ->
+		let exec = jit_expr jit false switch.switch_subject in
 		let execs = DynArray.create () in
-		let patterns = List.map (fun (el,e) ->
+		let patterns = List.map (fun {case_patterns = el;case_expr = e}  ->
 			push_scope jit e.epos;
 			let el = List.map (jit_expr jit false) el in
 			DynArray.add execs (jit_expr jit return e);
 			pop_scope jit;
 			el
-		) cases in
-		let exec_def = jit_default jit return def in
+		) switch.switch_cases in
+		let exec_def = jit_default jit return switch.switch_default in
 		emit_switch exec (DynArray.to_array execs) (Array.of_list patterns) exec_def
 	| TWhile({eexpr = TParenthesis e1},e2,flag) ->
 		loop {e with eexpr = TWhile(e1,e2,flag)}

+ 14 - 5
src/macro/macroApi.ml

@@ -1363,10 +1363,10 @@ and encode_texpr e =
 			| TFor(v,e1,e2) -> 15,[encode_tvar v;loop e1;loop e2]
 			| TIf(eif,ethen,eelse) -> 16,[loop eif;loop ethen;vopt encode_texpr eelse]
 			| TWhile(econd,e1,flag) -> 17,[loop econd;loop e1;vbool (flag = NormalWhile)]
-			| TSwitch(e1,cases,edef) -> 18,[
-				loop e1;
-				encode_array (List.map (fun (el,e) -> encode_obj ["values",encode_texpr_list el;"expr",loop e]) cases);
-				vopt encode_texpr edef
+			| TSwitch switch -> 18,[
+				loop switch.switch_subject;
+				encode_array (List.map (fun case -> encode_obj ["values",encode_texpr_list case.case_patterns;"expr",loop case.case_expr]) switch.switch_cases);
+				vopt encode_texpr switch.switch_default
 				]
 			| TTry(e1,catches) -> 19,[
 				loop e1;
@@ -1539,7 +1539,16 @@ and decode_texpr v =
 		| 15, [v;v1;v2] -> TFor(decode_tvar v,loop v1,loop v2)
 		| 16, [vif;vthen;velse] -> TIf(loop vif,loop vthen,opt loop velse)
 		| 17, [vcond;v1;b] -> TWhile(loop vcond,loop v1,if decode_bool b then NormalWhile else DoWhile)
-		| 18, [v1;cl;vdef] -> TSwitch(loop v1,List.map (fun v -> List.map loop (decode_array (field v "values")),loop (field v "expr")) (decode_array cl),opt loop vdef)
+		| 18, [v1;cl;vdef] ->
+			let switch = {
+				switch_subject = loop v1;
+				switch_cases = List.map (fun v -> {
+					case_patterns = List.map loop (decode_array (field v "values"));
+					case_expr = loop (field v "expr")
+				}) (decode_array cl);
+				switch_default = opt loop vdef;
+			} in
+			TSwitch switch
 		| 19, [v1;cl] -> TTry(loop v1,List.map (fun v -> decode_tvar (field v "v"),loop (field v "expr")) (decode_array cl))
 		| 20, [vo] -> TReturn(opt loop vo)
 		| 21, [] -> TBreak

+ 8 - 4
src/optimization/analyzer.ml

@@ -1034,10 +1034,14 @@ module Run = struct
 						let e2 = loop e2 in
 						let e3 = loop e3 in
 						{e with eexpr = TIf(e1,e2,Some e3); etype = get_t e.etype}
-					| TSwitch(e1,cases,edef) ->
-						let cases = List.map (fun (el,e) -> el,loop e) cases in
-						let edef = Option.map loop edef in
-						{e with eexpr = TSwitch(e1,cases,edef); etype = get_t e.etype}
+					| TSwitch switch ->
+						let cases = List.map (fun case -> {case with case_expr = loop case.case_expr}) switch.switch_cases in
+						let edef = Option.map loop switch.switch_default in
+						let switch = { switch with
+							switch_cases = cases;
+							switch_default = edef;
+						} in
+						{e with eexpr = TSwitch switch; etype = get_t e.etype}
 					| TTry(e1,catches) ->
 						let e1 = loop e1 in
 						let catches = List.map (fun (v,e) -> v,loop e) catches in

+ 15 - 10
src/optimization/analyzerTexpr.ml

@@ -44,11 +44,15 @@ let map_values ?(allow_control_flow=true) f e =
 			let e2 = loop true e2 in
 			let e3 = loop true e3 in
 			{e with eexpr = TIf(e1,e2,Some e3)}
-		| TSwitch(e1,cases,edef) ->
+		| TSwitch switch ->
 			branching := true;
-			let cases = List.map (fun (el,e) -> el,loop true e) cases in
-			let edef = Option.map (loop true) edef in
-			{e with eexpr = TSwitch(e1,cases,edef)}
+			let cases = List.map (fun case -> {case with case_expr = loop true case.case_expr}) switch.switch_cases in
+			let edef = Option.map (loop true) switch.switch_default in
+			let switch = { switch with
+				switch_cases = cases;
+				switch_default = edef;
+			} in
+			{e with eexpr = TSwitch switch}
 		| TBlock [e1] ->
 			loop complex e1
 		| TBlock el ->
@@ -553,8 +557,8 @@ module Fusion = struct
 					| Some e ->
 						block_element acc (e :: el)
 				end
-			| ({eexpr = TSwitch(e1,cases,def)} as e) :: el ->
-				begin match Optimizer.check_constant_switch e1 cases def with
+			| ({eexpr = TSwitch switch} as e) :: el ->
+				begin match Optimizer.check_constant_switch switch with
 				| Some e -> block_element acc (e :: el)
 				| None -> block_element (e :: acc) el
 				end
@@ -678,13 +682,14 @@ module Fusion = struct
 						let e2 = replace e2 in
 						let eo = Option.map replace eo in
 						{e with eexpr = TIf(e1,e2,eo)}
-					| TSwitch(e1,cases,edef) ->
+					| TSwitch switch ->
 						let e1 = match com.platform with
-							| Lua | Python -> explore e1
-							| _ -> replace e1
+							| Lua | Python -> explore switch.switch_subject
+							| _ -> replace switch.switch_subject
 						in
 						if not !found then raise Exit;
-						{e with eexpr = TSwitch(e1,cases,edef)}
+						let switch = { switch with switch_subject = e1 } in
+						{e with eexpr = TSwitch switch}
 					(* locals *)
 					| TLocal v2 when v1 == v2 && not !blocked ->
 						found := true;

+ 18 - 10
src/optimization/analyzerTexprTransformer.ml

@@ -431,9 +431,9 @@ let rec func ctx bb tf t p =
 					bb_next
 				end
 			end
-		| TSwitch(e1,cases,edef) ->
-			let is_exhaustive = is_exhaustive e1 edef in
-			let bb,e1 = bind_to_temp bb e1 in
+		| TSwitch switch ->
+			let is_exhaustive = is_exhaustive switch.switch_subject switch.switch_default in
+			let bb,e1 = bind_to_temp bb switch.switch_subject in
 			bb.bb_terminator <- TermCondBranch e1;
 			let reachable = ref [] in
 			let make_case e =
@@ -444,12 +444,12 @@ let rec func ctx bb tf t p =
 				close_node bb_case_next;
 				bb_case
 			in
-			let cases = List.map (fun (el,e) ->
-				let bb_case = make_case e in
-				List.iter (fun e -> add_cfg_edge bb bb_case (CFGCondBranch e)) el;
-				el,bb_case
-			) cases in
-			let def = match edef with
+			let cases = List.map (fun case ->
+				let bb_case = make_case case.case_expr in
+				List.iter (fun e -> add_cfg_edge bb bb_case (CFGCondBranch e)) case.case_patterns;
+				case.case_patterns,bb_case
+			) switch.switch_cases in
+			let def = match switch.switch_default with
 				| None ->
 					None
 				| Some e ->
@@ -708,7 +708,15 @@ let rec block_to_texpr_el ctx bb =
 				let e2 = block bb_body in
 				if_live bb_next,Some (mk (TWhile(get_terminator(),e2,NormalWhile)) ctx.com.basic.tvoid p)
 			| SESwitch(bbl,bo,bb_next,p) ->
-				Some bb_next,Some (mk (TSwitch(get_terminator(),List.map (fun (el,bb) -> el,block bb) bbl,Option.map block bo)) ctx.com.basic.tvoid p)
+				let switch = {
+					switch_subject = get_terminator();
+					switch_cases = List.map (fun (el,bb) -> {
+						case_patterns = el;
+						case_expr = block bb
+					}) bbl;
+					switch_default = Option.map block bo;
+				} in
+				Some bb_next,Some (mk (TSwitch switch) ctx.com.basic.tvoid p)
 		in
 		let bb_next,e_term = loop bb bb.bb_syntax_edge in
 		let el = DynArray.to_list bb.bb_el in

+ 19 - 11
src/optimization/inline.ml

@@ -734,15 +734,23 @@ let rec type_inline ctx cf f ethis params tret config p ?(self_calling_closure=f
 			let eloop = map false false eloop in
 			in_loop := old;
 			{ e with eexpr = TWhile (cond,eloop,flag) }
-		| TSwitch (e1,cases,def) when term ->
-			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
-			) cases in
-			let def = opt (map term false) def in
-			let t = return_type e.etype ((List.map snd cases) @ (match def with None -> [] | Some e -> [e])) in
-			{ e with eexpr = TSwitch (map false false e1,cases,def); etype = t }
+		| TSwitch switch when term ->
+			let term = term && (is_exhaustive switch.switch_subject switch.switch_default) in
+			let cases = List.map (fun case ->
+				let el = List.map (map false false) case.case_patterns in
+				{
+					case_patterns = el;
+					case_expr = map term false case.case_expr
+				}
+			) switch.switch_cases in
+			let def = opt (map term false) switch.switch_default in
+			let t = return_type e.etype ((List.map (fun case -> case.case_expr) cases) @ (match def with None -> [] | Some e -> [e])) in
+			let switch = {switch with
+				switch_subject = map false false switch.switch_subject;
+				switch_cases = cases;
+				switch_default = def;
+			} in
+			{ e with eexpr = TSwitch switch; etype = t }
 		| TTry (e1,catches) ->
 			let t = if not term then e.etype else return_type e.etype (e1::List.map snd catches) in
 			{ e with eexpr = TTry (map term false e1,List.map (fun (v,e) ->
@@ -758,10 +766,10 @@ let rec type_inline ctx cf f ethis params tret config p ?(self_calling_closure=f
 					let r = match e.eexpr with
 					| TReturn _ -> true
 					| TFunction _ -> false
-					| TIf (_,_,None) | TSwitch (_,_,None) | TFor _ | TWhile (_,_,NormalWhile) -> false (* we might not enter this code at all *)
+					| TIf (_,_,None) | TSwitch {switch_default = None} | TFor _ | TWhile (_,_,NormalWhile) -> false (* we might not enter this code at all *)
 					| TTry (a, catches) -> List.for_all has_term_return (a :: List.map snd catches)
 					| TIf (cond,a,Some b) -> has_term_return cond || (has_term_return a && has_term_return b)
-					| TSwitch (cond,cases,Some def) -> has_term_return cond || List.for_all has_term_return (def :: List.map snd cases)
+					| TSwitch ({switch_default = Some def} as switch) -> has_term_return switch.switch_subject || List.for_all has_term_return (def :: List.map (fun case -> case.case_expr) switch.switch_cases)
 					| TBinop (OpBoolAnd,a,b) -> has_term_return a && has_term_return b
 					| _ -> Type.iter loop e; false
 					in

+ 26 - 21
src/optimization/optimizer.ml

@@ -185,24 +185,29 @@ let sanitize_expr com e =
 		let e1 = block e1 in
 		let catches = List.map (fun (v,e) -> v, block e) catches in
 		{ e with eexpr = TTry (e1,catches) }
-	| TSwitch (e1,cases,def) ->
-		let e1 = parent e1 in
-		let cases = List.map (fun (el,e) -> el, complex e) cases in
-		let def = (match def with None -> None | Some e -> Some (complex e)) in
-		{ e with eexpr = TSwitch (e1,cases,def) }
+	| TSwitch switch ->
+		let e1 = parent switch.switch_subject in
+		let cases = List.map (fun case -> {case with case_expr = complex case.case_expr}) switch.switch_cases in
+		let def = Option.map complex switch.switch_default in
+		let switch = { switch with
+			switch_subject = e1;
+			switch_cases = cases;
+			switch_default = def;
+		} in
+		{ e with eexpr = TSwitch switch }
 	| _ ->
 		e
 
 let reduce_expr com e =
 	match e.eexpr with
-	| TSwitch (_,cases,_) ->
-		List.iter (fun (cl,_) ->
+	| TSwitch switch ->
+		List.iter (fun case ->
 			List.iter (fun e ->
 				match e.eexpr with
 				| TCall ({ eexpr = TField (_,FEnum _) },_) -> raise_typing_error "Not-constant enum in switch cannot be matched" e.epos
 				| _ -> ()
-			) cl
-		) cases;
+			) case.case_patterns
+		) switch.switch_cases;
 		e
 	| TBlock l ->
 		(match List.rev l with
@@ -258,22 +263,22 @@ let rec extract_constant_value e = match e.eexpr with
 	| _ ->
 		None
 
-let check_constant_switch e1 cases def =
+let check_constant_switch switch =
 	let rec loop e1 cases = match cases with
-		| (el,e) :: cases ->
+		| case :: cases ->
 			(* Map everything first so that we find unknown things eagerly. *)
 			let el = List.map (fun e2 -> match extract_constant_value e2 with
 				| Some e2 -> e2
 				| None -> raise Exit
-			) el in
+			) case.case_patterns in
 			if List.exists (fun e2 ->
 				Texpr.equal e1 e2
 			) el then
-				Some e
+				Some case.case_expr
 			else
 				loop e1 cases
 		| [] ->
-			begin match def with
+			begin match switch.switch_default with
 			| None -> None
 			| Some e -> Some e
 			end
@@ -282,20 +287,20 @@ let check_constant_switch e1 cases def =
 		| TBlock [] -> true
 		| _ -> false
 	in
-	let is_empty_def () = match def with
+	let is_empty_def () = match switch.switch_default with
 		| None -> true
 		| Some e -> is_empty e
 in
-	match Texpr.skip e1 with
+	match Texpr.skip switch.switch_subject with
 		| {eexpr = TConst ct} as e1 when (match ct with TSuper | TThis -> false | _ -> true) ->
 			begin try
-				loop e1 cases
+				loop e1 switch.switch_cases
 			with Exit ->
 				None
 			end
 		| _ ->
-			if List.for_all (fun (_,e) -> is_empty e) cases && is_empty_def() then
-				Some e1
+			if List.for_all (fun case -> is_empty case.case_expr) switch.switch_cases && is_empty_def() then
+				Some switch.switch_subject
 			else
 				None
 
@@ -306,8 +311,8 @@ let reduce_control_flow com e = match e.eexpr with
 		(match flag with
 		| NormalWhile -> { e with eexpr = TBlock [] } (* erase sub *)
 		| DoWhile -> e) (* we cant remove while since sub can contain continue/break *)
-	| TSwitch (e1,cases,def) ->
-		begin match check_constant_switch e1 cases def with
+	| TSwitch switch ->
+		begin match check_constant_switch switch with
 		| Some e -> e
 		| None -> e
 		end

+ 13 - 8
src/typing/matcher/texprConverter.ml

@@ -266,7 +266,7 @@ let to_texpr ctx t_switch with_type dt =
 						let eo = loop params dt in
 						begin match eo with
 							| None -> None
-							| Some e -> Some (List.map (constructor_to_texpr ctx) (List.sort Constructor.compare cons),e)
+							| Some e -> Some {case_patterns = List.map (constructor_to_texpr ctx) (List.sort Constructor.compare cons);case_expr = e}
 						end
 					) cases in
 					let is_nullable_subject = is_explicit_null e_subject.etype in
@@ -276,10 +276,10 @@ let to_texpr ctx t_switch with_type dt =
 						| SKLength -> ExprToPattern.type_field_access ctx e_subject "length"
 					in
 					let e = match cases,e_default,with_type with
-						| [_,e2],None,_ when (match finiteness with RunTimeFinite -> true | _ -> false) && not is_nullable_subject ->
-							{e2 with etype = t_switch}
-						| [[e1],e2],Some _,_
-						| [[e1],e2],None,NoValue ->
+						| [case],None,_ when (match finiteness with RunTimeFinite -> true | _ -> false) && not is_nullable_subject ->
+							{case.case_expr with etype = t_switch}
+						| [{case_patterns = [e1];case_expr = e2}],Some _,_
+						| [{case_patterns = [e1];case_expr = e2}],None,NoValue ->
 							let e_op = mk (TBinop(OpEq,e_subject,e1)) ctx.t.tbool e_subject.epos in
 							begin match e2.eexpr with
 								| TIf(e_op2,e3,e_default2) when (match e_default,e_default2 with Some(e1),Some(e2) when e1 == e2 -> true | _ -> false) ->
@@ -288,8 +288,8 @@ let to_texpr ctx t_switch with_type dt =
 								| _ ->
 									mk (TIf(e_op,e2,e_default)) t_switch dt.dt_pos
 							end
-						| [([{eexpr = TConst (TBool true)}],e1);([{eexpr = TConst (TBool false)}],e2)],None,_
-						| [([{eexpr = TConst (TBool false)}],e2);([{eexpr = TConst (TBool true)}],e1)],None,_ ->
+						| [{case_patterns = [{eexpr = TConst (TBool true)}];case_expr = e2};{case_patterns = [{eexpr = TConst (TBool false)}];case_expr = e1}],None,_
+						| [{case_patterns = [{eexpr = TConst (TBool false)}];case_expr = e2};{case_patterns = [{eexpr = TConst (TBool true)}];case_expr = e1}],None,_ ->
 							mk (TIf(e_subject,e1,Some e2)) t_switch dt.dt_pos
 						| _ ->
 							let e_subject = match finiteness with
@@ -299,7 +299,12 @@ let to_texpr ctx t_switch with_type dt =
 								| _ ->
 									e_subject
 							in
-							mk (TSwitch(e_subject,cases,e_default)) t_switch dt.dt_pos
+							let switch = {
+								switch_subject = e_subject;
+								switch_cases = cases;
+								switch_default = e_default;
+							} in
+							mk (TSwitch switch) t_switch dt.dt_pos
 					in
 					Some e
 				| Guard(e,dt1,dt2) ->

+ 7 - 4
src/typing/nullSafety.ml

@@ -1132,7 +1132,7 @@ class expr_checker mode immediate_execution report =
 				| TFor _ -> self#check_for e
 				| TIf _ -> self#check_if e
 				| TWhile _ -> self#check_while e
-				| TSwitch (target, cases, default) -> self#check_switch target cases default e.epos
+				| TSwitch switch -> self#check_switch switch e.epos
 				| TTry (try_block, catches) -> self#check_try try_block catches
 				| TReturn (Some expr) -> self#check_return expr e.epos
 				| TReturn None -> ()
@@ -1293,15 +1293,18 @@ class expr_checker mode immediate_execution report =
 		(**
 			Check safety in `switch` expressions.
 		*)
-		method private check_switch target cases default p =
+		method private check_switch switch p =
+			let target = switch.switch_subject in
+			let cases = switch.switch_cases in
+			let default = switch.switch_default in
 			if self#is_nullable_expr target then
 				self#error "Cannot switch on nullable value." [target.epos; p];
 			self#check_expr target;
 			let rec traverse_cases cases =
 				match cases with
 					| [] -> ()
-					| (_, body) :: rest ->
-						self#check_expr body;
+					| case :: rest ->
+						self#check_expr case.case_expr;
 						traverse_cases rest
 			in
 			traverse_cases cases;

+ 4 - 4
src/typing/typeloadCheck.ml

@@ -287,11 +287,11 @@ let rec return_flow ctx e =
 	| TIf (_,e1,Some e2) ->
 		return_flow e1;
 		return_flow e2;
-	| TSwitch (v,cases,Some e) ->
-		List.iter (fun (_,e) -> return_flow e) cases;
+	| TSwitch ({switch_default = Some e} as switch) ->
+		List.iter (fun case -> return_flow case.case_expr) switch.switch_cases;
 		return_flow e
-	| TSwitch ({eexpr = TMeta((Meta.Exhaustive,_,_),_)},cases,None) ->
-		List.iter (fun (_,e) -> return_flow e) cases;
+	| TSwitch ({switch_subject = {eexpr = TMeta((Meta.Exhaustive,_,_),_)}} as switch) ->
+		List.iter (fun case -> return_flow case.case_expr) switch.switch_cases;
 	| TTry (e,cases) ->
 		return_flow e;
 		List.iter (fun (_,e) -> return_flow e) cases;