Browse Source

remove TPatMatch (will revisit in the undefined future)

Simon Krajewski 11 năm trước cách đây
mục cha
commit
6568450332
20 tập tin đã thay đổi với 21 bổ sung347 xóa
  1. 1 1
      codegen.ml
  2. 0 95
      filters.ml
  3. 1 3
      genas3.ml
  4. 2 4
      gencommon.ml
  5. 1 7
      gencpp.ml
  6. 1 2
      gencs.ml
  7. 1 2
      genjava.ml
  8. 1 3
      genjs.ml
  9. 0 68
      genneko.ml
  10. 0 4
      genphp.ml
  11. 1 2
      genpy.ml
  12. 0 1
      genswf8.ml
  13. 1 54
      genswf9.ml
  14. 8 11
      interp.ml
  15. 2 25
      optimizer.ml
  16. 0 1
      std/haxe/macro/Type.hx
  17. 0 4
      std/haxe/macro/TypedExprTools.hx
  18. 0 43
      type.ml
  19. 0 13
      typeload.ml
  20. 1 4
      typer.ml

+ 1 - 1
codegen.ml

@@ -1239,7 +1239,7 @@ let rec constructor_side_effects e =
 		true
 	| TField (_,FEnum _) ->
 		false
-	| TUnop _ | TArray _ | TField _ | TEnumParameter _ | TCall _ | TNew _ | TFor _ | TWhile _ | TSwitch _ | TPatMatch _ | TReturn _ | TThrow _ ->
+	| TUnop _ | TArray _ | TField _ | TEnumParameter _ | TCall _ | TNew _ | TFor _ | TWhile _ | TSwitch _ | TReturn _ | TThrow _ ->
 		true
 	| TBinop _ | TTry _ | TIf _ | TBlock _ | TVar _
 	| TFunction _ | TArrayDecl _ | TObjectDecl _

+ 0 - 95
filters.ml

@@ -376,26 +376,6 @@ let check_local_vars_init e =
 			| Some e ->
 				loop vars e;
 				join vars cvars)
-		| TPatMatch dt ->
-			let cvars = ref [] in
-			let rec fdt dt = match dt with
-				| DTExpr e ->
-					let old = !vars in
-					loop vars e;
-					restore vars old [];
-					cvars := !vars :: !cvars
-				| DTSwitch(e,cl,dto) ->
-					loop vars e;
-					List.iter (fun (_,dt) -> fdt dt) cl;
-					(match dto with None -> () | Some dt -> fdt dt)
-				| DTGuard(e,dt1,dt2) ->
-					fdt dt1;
-					(match dt2 with None -> () | Some dt -> fdt dt)
-				| DTBind(_,dt) -> fdt dt
-				| DTGoto _ -> ()
-			in
-			Array.iter fdt dt.dt_dt_lookup;
-			join vars !cvars
 		(* mark all reachable vars as initialized, since we don't exit the block  *)
 		| TBreak | TContinue | TReturn None ->
 			vars := PMap.map (fun _ -> true) !vars
@@ -469,33 +449,6 @@ let rec local_usage f e =
 				local_usage f e;
 			))
 		) catchs;
-	| TPatMatch dt ->
-		List.iter (fun (v,eo) ->
-			f (Declare v);
-			match eo with None -> () | Some e -> local_usage f e
-		) dt.dt_var_init;
-		let rec fdt dt = match dt with
-			| DTBind(bl,dt) ->
-				List.iter (fun ((v,_),e) ->
-					f (Declare v);
-					local_usage f e
-				) bl;
-				fdt dt
-			| DTExpr e -> local_usage f e
-			| DTGuard(e,dt1,dt2) ->
-				local_usage f e;
-				fdt dt1;
-				(match dt2 with None -> () | Some dt -> fdt dt)
-			| DTSwitch(e,cl,dto) ->
-				local_usage f e;
-				List.iter (fun (e,dt) ->
-					local_usage f e;
-					fdt dt
-				) cl;
-				(match dto with None -> () | Some dt -> fdt dt)
-			| DTGoto _ -> ()
-		in
-		Array.iter fdt dt.dt_dt_lookup
 	| _ ->
 		iter (local_usage f) e
 
@@ -538,27 +491,6 @@ let captured_vars com e =
 					v, e
 			) catchs in
 			mk (TTry (wrap used expr,catchs)) e.etype e.epos
-		(* TODO: find out this does *)
-(* 		| TMatch (expr,enum,cases,def) ->
-			let cases = List.map (fun (il,vars,e) ->
-				let pos = e.epos in
-				let e = ref (wrap used e) in
-				let vars = match vars with
-					| None -> None
-					| Some l ->
-						Some (List.map (fun v ->
-							match v with
-							| Some v when PMap.mem v.v_id used ->
-								let vtmp = mk_var v used in
-								e := concat (mk_init v vtmp pos) !e;
-								Some vtmp
-							| _ -> v
-						) l)
-				in
-				il, vars, !e
-			) cases in
-			let def = match def with None -> None | Some e -> Some (wrap used e) in
-			mk (TMatch (wrap used expr,enum,cases,def)) e.etype e.epos *)
 		| TFunction f ->
 			(*
 				list variables that are marked as used, but also used in that
@@ -789,33 +721,6 @@ let rename_local_vars com e =
 				loop e;
 				old()
 			) catchs;
-		| TPatMatch dt ->
-			let rec fdt dt = match dt with
-				| DTSwitch(e,cl,dto) ->
-					loop e;
-					List.iter (fun (_,dt) ->
-						let old = save() in
-						fdt dt;
-						old();
-					) cl;
-					(match dto with None -> () | Some dt ->
-						let old = save() in
-						fdt dt;
-						old())
-				| DTBind(bl,dt) ->
-					List.iter (fun ((v,p),e) ->
-						declare v e.epos
-					) bl;
-					fdt dt
-				| DTExpr e -> loop e;
-				| DTGuard(e,dt1,dt2) ->
-					loop e;
-					fdt dt1;
-					(match dt2 with None -> () | Some dt -> fdt dt)
-				| DTGoto _ ->
-					()
-			in
-			Array.iter fdt dt.dt_dt_lookup
 		| TTypeExpr t ->
 			check t
 		| TNew (c,_,_) ->

+ 1 - 3
genas3.ml

@@ -298,7 +298,7 @@ let rec type_str ctx t p =
 let rec iter_switch_break in_switch e =
 	match e.eexpr with
 	| TFunction _ | TWhile _ | TFor _ -> ()
-	| TSwitch _ | TPatMatch _ when not in_switch -> iter_switch_break true e
+	| TSwitch _ when not in_switch -> iter_switch_break true e
 	| TBreak when in_switch -> raise Exit
 	| _ -> iter (iter_switch_break in_switch) e
 
@@ -746,7 +746,6 @@ and gen_expr ctx e =
 			print ctx "catch( %s : %s )" (s_ident v.v_name) (type_str ctx v.v_type e.epos);
 			gen_expr ctx e;
 		) catchs;
-	| TPatMatch dt -> assert false
 	| TSwitch (e,cases,def) ->
 		spr ctx "switch";
 		gen_value ctx (parent e);
@@ -920,7 +919,6 @@ and gen_value ctx e =
 			match def with None -> None | Some e -> Some (assign e)
 		)) e.etype e.epos);
 		v()
-	| TPatMatch dt -> assert false
 	| TTry (b,catchs) ->
 		let v = value true in
 		gen_expr ctx (mk (TTry (block (assign b),

+ 2 - 4
gencommon.ml

@@ -111,7 +111,7 @@ struct
 	let mk_heexpr = function
 		| TConst _ -> 0 | TLocal _ -> 1 | TArray _ -> 3 | TBinop _ -> 4 | TField _ -> 5 | TTypeExpr _ -> 7 | TParenthesis _ -> 8 | TObjectDecl _ -> 9
 		| TArrayDecl _ -> 10 | TCall _ -> 11 | TNew _ -> 12 | TUnop _ -> 13 | TFunction _ -> 14 | TVar _ -> 15 | TBlock _ -> 16 | TFor _ -> 17 | TIf _ -> 18 | TWhile _ -> 19
-		| TSwitch _ -> 20 | TPatMatch _ -> 21 | TTry _ -> 22 | TReturn _ -> 23 | TBreak -> 24 | TContinue -> 25 | TThrow _ -> 26 | TCast _ -> 27 | TMeta _ -> 28 | TEnumParameter _ -> 29
+		| TSwitch _ -> 20 (* | TPatMatch _ -> 21 *) | TTry _ -> 22 | TReturn _ -> 23 | TBreak -> 24 | TContinue -> 25 | TThrow _ -> 26 | TCast _ -> 27 | TMeta _ -> 28 | TEnumParameter _ -> 29
 
 	let mk_heetype = function
 		| TMono _ -> 0 | TEnum _ -> 1 | TInst _ -> 2 | TType _ -> 3 | TFun _ -> 4
@@ -4973,7 +4973,6 @@ struct
 			| TFor _
 			| TWhile _
 			| TSwitch _
-			| TPatMatch _
 			| TTry _
 			| TReturn _
 			| TBreak
@@ -9786,8 +9785,7 @@ struct
 					cur_num := last_num;
 
 					new_e
-				| TSwitch _
-				| TPatMatch _ ->
+				| TSwitch _ ->
 					let last_switch = !in_switch in
 					in_switch := true;
 

+ 1 - 7
gencpp.ml

@@ -1029,7 +1029,6 @@ let rec iter_retval f retval e =
       f true e;
       List.iter (fun (_,_,e) -> f false e) cases;
       (match def with None -> () | Some e -> f false e) *)
-   | TPatMatch dt -> assert false
    | TTry (e,catches) ->
       f retval e;
       List.iter (fun (_,e) -> f false e) catches
@@ -1516,7 +1515,6 @@ and find_local_functions_and_return_blocks_ctx ctx retval expression =
          if (retval) then begin
             define_local_return_block_ctx ctx expression (next_anon_function_name ctx) true;
          end  (* else we are done *)
-      | TPatMatch (_)
       | TTry (_, _)
       | TSwitch (_, _, _) when retval ->
             define_local_return_block_ctx ctx expression (next_anon_function_name ctx) true;
@@ -1540,7 +1538,6 @@ and find_local_functions_and_return_blocks_ctx ctx retval expression =
       | TArray (obj,_) when (is_null obj) -> ( )
       | TIf ( _ , _ , _ ) when retval -> (* ? operator style *)
          iter_retval find_local_functions_and_return_blocks retval expression
-      | TPatMatch (_)
       | TSwitch (_, _, _) when retval -> ( )
       (* | TMatch ( cond , _, _, _) *)
       | TWhile ( cond , _, _ )
@@ -2257,10 +2254,8 @@ and gen_expression ctx retval expression =
 
    (* These have already been defined in find_local_return_blocks ... *)
    | TTry (_,_)
-   | TSwitch (_,_,_)
-   | TPatMatch (_) when (retval && (not return_from_internal_node) )->
+   | TSwitch (_,_,_) when (retval && (not return_from_internal_node) ) ->
       gen_local_block_call()
-   | TPatMatch dt -> assert false
    | TSwitch (condition,cases,optional_default)  ->
       let switch_on_int_constants = (only_int_cases cases) && (not (contains_break expression)) in
       if (switch_on_int_constants) then begin
@@ -4828,7 +4823,6 @@ class script_writer common_ctx ctx filename =
    | TCast (cast,Some _) -> this#checkCast expression.etype cast true true;
    | TParenthesis _ -> error "Unexpected parens" expression.epos
    | TMeta(_,_) -> error "Unexpected meta" expression.epos
-   | TPatMatch _ ->  error "Unexpected pattern match" expression.epos
    );
    this#end_expr;
 end;;

+ 1 - 2
gencs.ml

@@ -966,7 +966,7 @@ let configure gen =
 
 	let has_semicolon e =
 		match e.eexpr with
-			| TBlock _ | TFor _ | TSwitch _ | TPatMatch _ | TTry _ | TIf _ -> false
+			| TBlock _ | TFor _ | TSwitch _ | TTry _ | TIf _ -> false
 			| TWhile (_,_,flag) when flag = Ast.NormalWhile -> false
 			| _ -> true
 	in
@@ -1478,7 +1478,6 @@ let configure gen =
 					if !strict_mode then assert false
 				| TObjectDecl _ -> write w "[ obj decl not supported ]"; if !strict_mode then assert false
 				| TFunction _ -> write w "[ func decl not supported ]"; if !strict_mode then assert false
-				| TPatMatch _ -> write w "[ match not supported ]"; if !strict_mode then assert false
 				| TEnumParameter _ -> write w "[ enum parameter not supported ]"; if !strict_mode then assert false
 		)
 		and do_call w e el =

+ 1 - 2
genjava.ml

@@ -1128,7 +1128,7 @@ let configure gen =
 		match e.eexpr with
 			| TLocal { v_name = "__fallback__" }
 			| TCall ({ eexpr = TLocal( { v_name = "__label__" } ) }, [ { eexpr = TConst(TInt _) } ] ) -> false
-			| TBlock _ | TFor _ | TSwitch _ | TPatMatch _ | TTry _ | TIf _ -> false
+			| TBlock _ | TFor _ | TSwitch _ | TTry _ | TIf _ -> false
 			| TWhile (_,_,flag) when flag = Ast.NormalWhile -> false
 			| _ -> true
 	in
@@ -1518,7 +1518,6 @@ let configure gen =
 					if !strict_mode then assert false
 				| TObjectDecl _ -> write w "[ obj decl not supported ]"; if !strict_mode then assert false
 				| TFunction _ -> write w "[ func decl not supported ]"; if !strict_mode then assert false
-				| TPatMatch _ -> write w "[ match not supported ]"; if !strict_mode then assert false
 				| TEnumParameter _ -> write w "[ enum parameter not supported ]"; if !strict_mode then assert false
 		in
 		expr_s w e

+ 1 - 3
genjs.ml

@@ -306,7 +306,7 @@ let rec has_return e =
 let rec iter_switch_break in_switch e =
 	match e.eexpr with
 	| TFunction _ | TWhile _ | TFor _ -> ()
-	| TSwitch _ | TPatMatch _ when not in_switch -> iter_switch_break true e
+	| TSwitch _ when not in_switch -> iter_switch_break true e
 	| TBreak when in_switch -> raise Exit
 	| _ -> iter (iter_switch_break in_switch) e
 
@@ -704,7 +704,6 @@ and gen_expr ctx e =
 		bend();
 		newline ctx;
 		spr ctx "}";
-	| TPatMatch dt -> assert false
 	| TSwitch (e,cases,def) ->
 		spr ctx "switch";
 		gen_value ctx e;
@@ -873,7 +872,6 @@ and gen_value ctx e =
 			match def with None -> None | Some e -> Some (assign e)
 		)) e.etype e.epos);
 		v()
-	| TPatMatch dt -> assert false
 	| TTry (b,catchs) ->
 		let v = value() in
 		let block e = mk (TBlock [e]) e.etype e.epos in

+ 0 - 68
genneko.ml

@@ -369,74 +369,6 @@ and gen_expr ctx e =
 		gen_expr ctx e
 	| TCast (e1,Some t) ->
 		gen_expr ctx (Codegen.default_cast ~vtmp:"@tmp" ctx.com e1 t e.etype e.epos)
- 	| TPatMatch dt ->
-		let num_labels = Array.length dt.dt_dt_lookup in
-		let lc = ctx.label_count in
-		ctx.label_count <- ctx.label_count + num_labels + 1;
-		let get_label i ="label_" ^ (string_of_int (lc + i)) in
-		let goto i = call p (builtin p "goto") [ident p (get_label i)] in
-		let state = Hashtbl.create 0 in
-		let v_name v = "v" ^ (string_of_int v.v_id) in
-		let get_locals e =
-			let locals = Hashtbl.create 0 in
-			let rec loop e = match e.eexpr with
-				| TLocal v -> Hashtbl.replace locals v true
-				| _ -> Type.iter loop e
-			in
-			loop e;
-			Hashtbl.fold (fun v _ l -> if Hashtbl.mem locals v then (v.v_name, Some (field p (ident p "@state") (v_name v))) :: l else l) state []
-		in
-		let rec loop d = match d with
-			| DTGoto i ->
-				goto i
-			| DTBind (bl,dt) ->
-				let block = List.map (fun ((v,_),est) ->
-					let est = gen_expr ctx est in
-					let field = field p (ident p "@state") (v_name v) in
-					Hashtbl.replace state v field;
-					(EBinop ("=",field,est),p)
-				) bl in
-				EBlock (block @ [loop dt]),p
-			| DTExpr e ->
-				let block = [
-					(EBinop ("=",ident p "@ret",gen_expr ctx e),p);
-					goto num_labels;
-				] in
-				(match get_locals e with [] -> EBlock block,p | el -> EBlock ((EVars(el),p) :: block),p)
-			| DTGuard (e,dt1,dt2) ->
-				let eg = match dt2 with
- 					| None -> (EIf (gen_expr ctx e,loop dt1,None),p)
-					| Some dt -> (EIf (gen_expr ctx e,loop dt1,Some (loop dt)),p)
-				in
-				(match get_locals e with [] -> eg | el -> EBlock [(EVars(el),p);eg],p)
-			| DTSwitch (e,cl,dto) ->
-				let e = gen_expr ctx e in
-				let def = match dto with None -> None | Some dt -> Some (loop dt) in
-				let cases = List.map (fun (e,dt) -> gen_expr ctx e,loop dt) cl in
-				EBlock [
-					(ESwitch (e,cases,def),p);
-					goto num_labels;
-				],p
-		in
-		let acc = DynArray.create () in
-		for i = num_labels -1 downto 0 do
-			let e = loop dt.dt_dt_lookup.(i) in
-			DynArray.add acc (ELabel (get_label i),p);
-			DynArray.add acc e;
-		done;
-		DynArray.add acc (ELabel (get_label num_labels),p);
-		DynArray.add acc (ident p "@ret");
-		let el = DynArray.to_list acc in
-		let var_init = List.fold_left (fun acc (v,eo) -> (v.v_name,(match eo with None -> None | Some e -> Some (gen_expr ctx e))) :: acc) [] dt.dt_var_init in
-		let state_init = Hashtbl.fold (fun v _ l -> (v_name v,null p) :: l) state [] in
-		let init = match var_init,state_init with
-			| [], [] -> []
-			| el, [] -> el
-			| [], vl -> ["@state",Some (EObject vl,p)]
-			| el, vl -> ("@state",Some (EObject vl,p)) :: el
-		in
-		let el = match init with [] -> (goto dt.dt_first) :: el | _ -> (EVars init,p) :: (goto dt.dt_first) :: el in
-		EBlock el,p
 	| TSwitch (e,cases,eo) ->
 		let e = gen_expr ctx e in
 		let eo = (match eo with None -> None | Some e -> Some (gen_expr ctx e)) in

+ 0 - 4
genphp.ml

@@ -1311,7 +1311,6 @@ and gen_expr ctx e =
 				| TThrow _
 				| TWhile _
 				| TFor _
-				| TPatMatch _
 				| TTry _
 				| TBreak
 				| TBlock _ ->
@@ -1325,7 +1324,6 @@ and gen_expr ctx e =
 					| TThrow _
 					| TWhile _
 					| TFor _
-					| TPatMatch _
 					| TTry _
 					| TBlock _ -> ()
 					| _ ->
@@ -1592,7 +1590,6 @@ and gen_expr ctx e =
 		bend();
 		newline ctx;
 		spr ctx "}"
-	| TPatMatch dt -> assert false
 	| TSwitch (e,cases,def) ->
 		let old_loop = ctx.in_loop in
 		ctx.in_loop <- false;
@@ -1783,7 +1780,6 @@ and gen_value ctx e =
 	| TThrow _
 	| TSwitch _
 	| TFor _
-	| TPatMatch _
 	| TIf _
 	| TTry _ ->
 		inline_block ctx e

+ 1 - 2
genpy.ml

@@ -911,7 +911,6 @@ module Transformer = struct
 			let e = trans is_value [] e in
 			let r = { a_expr with eexpr = TMeta(m, e.a_expr); etype = e.a_expr.etype } in
 			lift_expr ~blocks:e.a_blocks r
-		| ( _, TPatMatch _ ) -> assert false
 		| ( _, TLocal _ ) -> lift_expr a_expr
 
 		| ( _, TConst _ ) -> lift_expr a_expr
@@ -1308,7 +1307,7 @@ module Printer = struct
 				Printf.sprintf "(%s if %s else %s)" (print_expr pctx eif) (print_expr pctx econd) (print_expr pctx eelse)
 			| TMeta(_,e1) ->
 				print_expr pctx e1
-			| TPatMatch _ | TSwitch _ | TCast(_, Some _) | TFor _ | TUnop(_,Postfix,_) ->
+			| TSwitch _ | TCast(_, Some _) | TFor _ | TUnop(_,Postfix,_) ->
 				assert false
 
 	and print_if_else pctx econd eif eelse as_elif =

+ 0 - 1
genswf8.ml

@@ -1167,7 +1167,6 @@ and gen_expr_2 ctx retval e =
 		gen_expr ctx retval e
 	| TCast (e1,Some t) ->
 		gen_expr ctx retval (Codegen.default_cast ctx.com e1 t e.etype e.epos)
-	| TPatMatch dt -> assert false
 	| TFor (v,it,e) ->
 		gen_expr ctx true it;
 		let r = alloc_tmp ctx in

+ 1 - 54
genswf9.ml

@@ -1299,59 +1299,6 @@ let rec gen_expr_content ctx retval e =
 		);
 		List.iter (fun j -> j()) jend;
 		branch());
-(* 	| TMatch (e0,_,cases,def) ->
-		let t = classify ctx e.etype in
-		let rparams = alloc_reg ctx (KType (type_path ctx ([],"Array"))) in
-		let has_params = List.exists (fun (_,p,_) -> p <> None) cases in
-		gen_expr ctx true e0;
-		if has_params then begin
-			write ctx HDup;
-			write ctx (HGetProp (ident "params"));
-			set_reg ctx rparams;
-		end;
-		write ctx (HGetProp (ident "index"));
-		write ctx HToInt;
-		let switch,case = begin_switch ctx in
-		(match def with
-		| None ->
-			if retval then begin
-				write ctx HNull;
-				coerce ctx t;
-			end;
-		| Some e ->
-			gen_expr ctx retval e;
-			if retval && classify ctx e.etype <> t then coerce ctx t);
-		let jends = List.map (fun (cl,params,e) ->
-			let j = jump ctx J3Always in
-			List.iter case cl;
-			pop_value ctx retval;
-			let b = open_block ctx retval in
-			(match params with
-			| None -> ()
-			| Some l ->
-				let p = ref (-1) in
-				List.iter (fun v ->
-					incr p;
-					match v with
-					| None -> ()
-					| Some v ->
-						define_local ctx v e.epos;
-						let acc = gen_local_access ctx v e.epos Write in
-						write ctx (HReg rparams.rid);
-						write ctx (HSmallInt !p);
-						getvar ctx VArray;
-						setvar ctx acc None
-				) l
-			);
-			gen_expr ctx retval e;
-			b();
-			if retval && classify ctx e.etype <> t then coerce ctx t;
-			j
-		) cases in
-		switch();
-		List.iter (fun j -> j()) jends;
-		free_reg ctx rparams *)
-	| TPatMatch dt -> assert false
 	| TCast (e1,t) ->
 		gen_expr ctx retval e1;
 		if retval then begin
@@ -1743,7 +1690,7 @@ and generate_function ctx fdata stat =
 			| TReturn (Some e) ->
 				let rec inner_loop e =
 					match e.eexpr with
-					| TSwitch _ | TPatMatch _ | TFor _ | TWhile _ | TTry _ -> false
+					| TSwitch _ | TFor _ | TWhile _ | TTry _ -> false
 					| TIf _ -> loop e
 					| TParenthesis e | TMeta(_,e) -> inner_loop e
 					| _ -> true

+ 8 - 11
interp.ml

@@ -4565,9 +4565,7 @@ and encode_texpr e =
 				enc_array (List.map (fun (el,e) -> enc_obj ["values",encode_texpr_list el;"expr",loop e]) cases);
 				vopt encode_texpr edef
 				]
-			| TPatMatch _ ->
-				assert false
-			| TTry(e1,catches) -> 20,[
+			| TTry(e1,catches) -> 19,[
 				loop e1;
 				enc_array (List.map (fun (v,e) ->
 					enc_obj [
@@ -4575,13 +4573,13 @@ and encode_texpr e =
 						"expr",loop e
 					]) catches
 				)]
-			| TReturn e1 -> 21,[vopt encode_texpr e1]
-			| TBreak -> 22,[]
-			| TContinue -> 23,[]
-			| TThrow e1 -> 24,[loop e1]
-			| TCast(e1,mt) -> 25,[loop e1;match mt with None -> VNull | Some mt -> encode_module_type mt]
-			| TMeta(m,e1) -> 26,[encode_meta_entry m;loop e1]
-			| TEnumParameter(e1,ef,i) -> 27,[loop e1;encode_efield ef;VInt i]
+			| TReturn e1 -> 20,[vopt encode_texpr e1]
+			| TBreak -> 21,[]
+			| TContinue -> 22,[]
+			| TThrow e1 -> 23,[loop e1]
+			| TCast(e1,mt) -> 24,[loop e1;match mt with None -> VNull | Some mt -> encode_module_type mt]
+			| TMeta(m,e1) -> 25,[encode_meta_entry m;loop e1]
+			| TEnumParameter(e1,ef,i) -> 26,[loop e1;encode_efield ef;VInt i]
 		in
 		enc_obj [
 			"pos", encode_pos e.epos;
@@ -4962,7 +4960,6 @@ let rec make_ast e =
 		) cases in
 		let def = match eopt def with None -> None | Some (EBlock [],_) -> Some None | e -> Some e in
 		ESwitch (make_ast e,cases,def)
-	| TPatMatch _
 	| TEnumParameter _ ->
 		(* these are considered complex, so the AST is handled in TMeta(Meta.Ast) *)
 		assert false

+ 2 - 25
optimizer.ml

@@ -34,7 +34,7 @@ let has_side_effect e =
 		match e.eexpr with
 		| TConst _ | TLocal _ | TField _ | TTypeExpr _ | TFunction _ -> ()
 		| TCall ({ eexpr = TField(_,FStatic({ cl_path = ([],"Std") },{ cf_name = "string" })) },args) -> Type.iter loop e
-		| TPatMatch _ | TNew _ | TCall _ | TBinop ((OpAssignOp _ | OpAssign),_,_) | TUnop ((Increment|Decrement),_,_) -> raise Exit
+		| TNew _ | TCall _ | TBinop ((OpAssignOp _ | OpAssign),_,_) | TUnop ((Increment|Decrement),_,_) -> raise Exit
 		| TReturn _ | TBreak | TContinue | TThrow _ | TCast (_,Some _) -> raise Exit
 		| TArray _ | TEnumParameter _ | TCast (_,None) | TBinop _ | TUnop _ | TParenthesis _ | TMeta _ | TWhile _ | TFor _ | TIf _ | TTry _ | TSwitch _ | TArrayDecl _ | TVar _ | TBlock _ | TObjectDecl _ -> Type.iter loop e
 	in
@@ -352,17 +352,6 @@ let rec type_inline ctx cf f ethis params tret config p ?(self_calling_closure=f
 			let eloop = map false eloop in
 			in_loop := old;
 			{ e with eexpr = TWhile (cond,eloop,flag) }
-(* 		| TMatch (v,en,cases,def) ->
-			let term = term && def <> None in
-			let cases = List.map (fun (i,vl,e) ->
-				let vl = opt (List.map (fun v -> opt (fun v -> (local v).i_subst) v)) vl in
-				i, vl, map term e
-			) cases in
-			let def = opt (map term) def in
-			{ e with eexpr = TMatch (map false v,en,cases,def); etype = if term && ret_val then unify_min ctx ((List.map (fun (_,_,e) -> e) cases) @ (match def with None -> [] | Some e -> [e])) else e.etype } *)
-		| TPatMatch _ ->
-			cancel_inlining := true; (* TODO *)
-			e
 		| TSwitch (e1,cases,def) when term ->
 			let term = term && def <> None in
 			let cases = List.map (fun (el,e) ->
@@ -766,7 +755,7 @@ let rec need_parent e =
 	match e.eexpr with
 	| TConst _ | TLocal _ | TArray _ | TField _ | TEnumParameter _ | TParenthesis _ | TMeta _ | TCall _ | TNew _ | TTypeExpr _ | TObjectDecl _ | TArrayDecl _ -> false
 	| TCast (e,None) -> need_parent e
-	| TCast _ | TThrow _ | TReturn _ | TTry _ | TPatMatch _ | TSwitch _ | TFor _ | TIf _ | TWhile _ | TBinop _ | TContinue | TBreak
+	| TCast _ | TThrow _ | TReturn _ | TTry _ | TSwitch _ | TFor _ | TIf _ | TWhile _ | TBinop _ | TContinue | TBreak
 	| TBlock _ | TVar _ | TFunction _ | TUnop _ -> true
 
 let sanitize_expr com e =
@@ -785,7 +774,6 @@ let sanitize_expr com e =
 		match e.eexpr with
 		| TVar _	(* needs to be put into blocks *)
 		| TFor _	(* a temp var is needed for holding iterator *)
-		| TPatMatch _	(* a temp var is needed for holding enum *)
 		| TCall ({ eexpr = TLocal { v_name = "__js__" } },_) (* we never know *)
 			-> block e
 		| _ -> e
@@ -870,17 +858,6 @@ let sanitize_expr com e =
 		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) }
-	| TPatMatch dt ->
-		let rec loop d = match d with
-			| DTGoto _ -> d
-			| DTExpr e -> DTExpr (complex e)
-			| DTBind(bl,dt) -> DTBind(bl, loop dt)
-			| DTGuard(e,dt1,dt2) -> DTGuard(complex e,loop dt1,match dt2 with None -> None | Some dt -> Some (loop dt))
-			| DTSwitch(e,cl,dto) ->
-				let cl = List.map (fun (e,dt) -> complex e,loop dt) cl in
-				DTSwitch(parent e,cl,match dto with None -> None | Some dt -> Some (loop dt))
-		in
-		{ e with eexpr = TPatMatch({dt with dt_dt_lookup = Array.map loop dt.dt_dt_lookup })}
 	| _ ->
 		e
 

+ 0 - 1
std/haxe/macro/Type.hx

@@ -268,7 +268,6 @@ enum TypedExprDef {
 	TIf(econd:TypedExpr, eif:TypedExpr, eelse:Null<TypedExpr>);
 	TWhile(econd:TypedExpr, e:TypedExpr, normalWhile:Bool);
 	TSwitch(e:TypedExpr, cases:Array<{values:Array<TypedExpr>, expr:TypedExpr}>, edef:Null<TypedExpr>);
-	TPatMatch;
 	TTry(e:TypedExpr, catches:Array<{v:TVar, expr:TypedExpr}>);
 	TReturn(e:Null<TypedExpr>);
 	TBreak;

+ 0 - 4
std/haxe/macro/TypedExprTools.hx

@@ -64,7 +64,6 @@ class TypedExprTools {
 			case TFunction(fu): with(e, TFunction({ t: fu.t, args: fu.args, expr: f(fu.expr)}));
 			case TIf(e1, e2, e3): with(e, TIf(f(e1), f(e2), e3 == null ? null : f(e3)));
 			case TSwitch(e1, cases, e2): with(e, TSwitch(f(e1), cases.map(function(c) return { values: c.values.map(f), expr: f(c.expr) }), e2 == null ? null : f(e2)));
-			case TPatMatch: throw false;
 			case TTry(e1, catches): with(e, TTry(f(e1), catches.map(function(c) return { v:c.v, expr: f(c.expr) })));
 			case TReturn(e1): with(e, TReturn(e1 == null ? null : f(e1)));
 			case TCast(e1, mt): with(e, TCast(f(e1), mt));
@@ -112,8 +111,6 @@ class TypedExprTools {
 			case TTry(e1, catches):
 				f(e1);
 				for (c in catches) f(c.expr);
-			case TPatMatch:
-				throw false;
 		}
 	}
 
@@ -148,7 +145,6 @@ class TypedExprTools {
 			case TFunction(fu): with(e, TFunction({ t: ft(fu.t), args: fu.args.map(function(arg) return { v: fv(arg.v), value: arg.value }), expr: f(fu.expr)}), ft(e.t));
 			case TIf(e1, e2, e3): with(e, TIf(f(e1), f(e2), e3 == null ? null : f(e3)), ft(e.t));
 			case TSwitch(e1, cases, e2): with(e, TSwitch(f(e1), cases.map(function(c) return { values: c.values.map(f), expr: f(c.expr) }), e2 == null ? null : f(e2)), ft(e.t));
-			case TPatMatch: throw false;
 			case TTry(e1, catches): with(e, TTry(f(e1), catches.map(function(c) return { v:fv(c.v), expr: f(c.expr) })), ft(e.t));
 			case TReturn(e1): with(e, TReturn(e1 == null ? null : f(e1)), ft(e.t));
 			case TCast(e1, mt): with(e, TCast(f(e1), mt), ft(e.t));

+ 0 - 43
type.ml

@@ -121,7 +121,6 @@ and texpr_expr =
 	| TIf of texpr * texpr * texpr option
 	| TWhile of texpr * texpr * Ast.while_flag
 	| TSwitch of texpr * (texpr list * texpr) list * texpr option
-	| TPatMatch of decision_tree
 	| TTry of texpr * (tvar * texpr) list
 	| TReturn of texpr option
 	| TBreak
@@ -829,7 +828,6 @@ let s_expr_kind e =
 	| TIf (_,_,_) -> "If"
 	| TWhile (_,_,_) -> "While"
 	| TSwitch (_,_,_) -> "Switch"
-	| TPatMatch _ -> "PatMatch"
 	| TTry (_,_) -> "Try"
 	| TReturn _ -> "Return"
 	| TBreak -> "Break"
@@ -906,7 +904,6 @@ let rec s_expr s_type 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)
-	| TPatMatch dt -> s_dt "" (dt.dt_dt_lookup.(dt.dt_first))
 	| 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 ->
@@ -985,7 +982,6 @@ let rec s_expr_pretty tabs s_type e =
 		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 (slist loop cl) (s_expr_pretty ntabs s_type e)) cases) (match def with None -> "" | Some e -> ntabs ^ "default: " ^ (s_expr_pretty ntabs s_type e) ^ "\n") in
 		s ^ tabs ^ "}"
-	| TPatMatch dt -> s_dt tabs (dt.dt_dt_lookup.(dt.dt_first))
 	| TTry (e,cl) ->
 		sprintf "try %s%s" (loop e) (slist (fun (v,e) -> sprintf "catch( %s : %s ) %s" v.v_name (s_type v.v_type) (loop e)) cl)
 	| TReturn None ->
@@ -1700,25 +1696,6 @@ let iter f e =
 		f e;
 		List.iter (fun (el,e2) -> List.iter f el; f e2) cases;
 		(match def with None -> () | Some e -> f e)
-	| TPatMatch dt ->
-		let rec loop dt = match dt with
-			| DTBind(_,dt) -> loop dt
-			| DTGoto _ -> ()
-			| DTSwitch(e,cl,dto) ->
-				f e;
-				List.iter (fun (e,dt) ->
-					f e;
-					loop dt
-				) cl;
-				(match dto with None -> () | Some dt -> loop dt)
-			| DTExpr e -> f e
-			| DTGuard(eg,dt1,dt2) ->
-				f eg;
-				loop dt1;
-				(match dt2 with None -> () | Some dt -> loop dt)
-		in
-		List.iter (fun (_,eo) -> match eo with None -> () | Some e -> f e) dt.dt_var_init;
-		Array.iter loop dt.dt_dt_lookup
 	| TTry (e,catches) ->
 		f e;
 		List.iter (fun (_,e) -> f e) catches
@@ -1777,16 +1754,6 @@ let map_expr f e =
 		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)) }
-	| TPatMatch dt ->
-		let rec loop dt = match dt with
-			| DTBind(vl,dt) -> DTBind(vl, loop dt)
-			| DTGoto _ -> dt
-			| DTSwitch(e,cl,dto) -> DTSwitch(f e, List.map (fun (e,dt) -> f e,loop dt) cl,match dto with None -> None | Some dt -> Some (loop dt))
-			| DTExpr e -> DTExpr(f e)
-			| DTGuard(e,dt1,dt2) -> DTGuard(f e,loop dt1,match dt2 with None -> None | Some dt -> Some (loop dt))
-		in
-		let vi = List.map (fun (v,eo) -> v, match eo with None -> None | Some e -> Some(f e)) dt.dt_var_init in
-		{ e with eexpr = TPatMatch({dt with dt_dt_lookup = Array.map loop dt.dt_dt_lookup; dt_var_init = vi})}
 	| TTry (e1,catches) ->
 		let e1 = f e1 in
 		{ e with eexpr = TTry (e1, List.map (fun (v,e) -> v, f e) catches) }
@@ -1878,16 +1845,6 @@ let map_expr_type f ft fv e =
 		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 }
-	| TPatMatch dt ->
-		let rec loop dt = match dt with
-			| DTBind(vl,dt) -> DTBind(vl, loop dt)
-			| DTGoto _ -> dt
-			| DTSwitch(e,cl,dto) -> DTSwitch(f e, List.map (fun (e,dt) -> f e,loop dt) cl,match dto with None -> None | Some dt -> Some (loop dt))
-			| DTExpr e -> DTExpr(f e)
-			| DTGuard (e,dt1,dt2) -> DTGuard(f e, loop dt, match dt2 with None -> None | Some dt -> Some (loop dt))
-		in
-		let vi = List.map (fun (v,eo) -> v, match eo with None -> None | Some e -> Some(f e)) dt.dt_var_init in
-		{ e with eexpr = TPatMatch({dt with dt_dt_lookup = Array.map loop dt.dt_dt_lookup; dt_var_init = vi}); 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 }

+ 0 - 13
typeload.ml

@@ -964,19 +964,6 @@ let rec return_flow ctx e =
 		return_flow e
 	| TSwitch ({eexpr = TMeta((Meta.Exhaustive,_,_),_)},cases,None) ->
 		List.iter (fun (_,e) -> return_flow e) cases;
-	| TPatMatch dt ->
-		let rec loop d = match d with
-			| DTExpr e -> return_flow e
-			| DTGuard(_,dt1,dt2) ->
-				loop dt1;
-				(match dt2 with None -> () | Some dt -> loop dt)
-			| DTBind (_,d) -> loop d
-			| DTSwitch (_,cl,dto) ->
-				List.iter (fun (_,dt) -> loop dt) cl;
-				(match dto with None -> () | Some dt -> loop dt)
-			| DTGoto i -> loop (dt.dt_dt_lookup.(i))
-		in
-		loop (dt.dt_dt_lookup.(dt.dt_first))
 	| TTry (e,cases) ->
 		return_flow e;
 		List.iter (fun (_,e) -> return_flow e) cases;

+ 1 - 4
typer.ml

@@ -3092,10 +3092,7 @@ and type_expr ctx (e,p) (with_type:with_type) =
 		begin try
 			let dt = match_expr ctx e1 cases def with_type p in
 			let wrap e1 = if not dt.dt_is_complex then e1 else mk (TMeta((Meta.Ast,[e,p],p),e1)) e1.etype e1.epos in
-			if not ctx.in_macro && not (Common.defined ctx.com Define.Interp) && ctx.com.config.pf_pattern_matching && dt.dt_is_complex then
-				wrap (mk (TPatMatch dt) dt.dt_type p)
-			else
-				wrap (Codegen.PatternMatchConversion.to_typed_ast ctx dt p)
+			wrap (Codegen.PatternMatchConversion.to_typed_ast ctx dt p)
 		with Exit ->
 			type_switch_old ctx e1 cases def with_type p
 		end