Browse Source

[matcher] error on capture vars in .match patterns

closes #7921
Simon Krajewski 6 years ago
parent
commit
0a9c2cab33

+ 0 - 1
src/context/typecore.ml

@@ -132,7 +132,6 @@ let make_call_ref : (typer -> texpr -> texpr list -> t -> ?force_inline:bool ->
 let type_expr_ref : (typer -> expr -> WithType.t -> texpr) ref = ref (fun _ _ _ -> assert false)
 let type_expr_ref : (typer -> expr -> WithType.t -> texpr) ref = ref (fun _ _ _ -> assert false)
 let type_block_ref : (typer -> expr list -> WithType.t -> pos -> texpr) ref = ref (fun _ _ _ _ -> assert false)
 let type_block_ref : (typer -> expr list -> WithType.t -> pos -> texpr) ref = ref (fun _ _ _ _ -> assert false)
 let unify_min_ref : (typer -> texpr list -> t) ref = ref (fun _ _ -> assert false)
 let unify_min_ref : (typer -> texpr list -> t) ref = ref (fun _ _ -> assert false)
-let get_pattern_locals_ref : (typer -> expr -> Type.t -> (string, tvar * pos) PMap.t) ref = ref (fun _ _ _ -> assert false)
 let analyzer_run_on_expr_ref : (Common.context -> texpr -> texpr) ref = ref (fun _ _ -> assert false)
 let analyzer_run_on_expr_ref : (Common.context -> texpr -> texpr) ref = ref (fun _ _ -> assert false)
 
 
 let pass_name = function
 let pass_name = function

+ 0 - 5
src/macro/macroApi.ml

@@ -35,7 +35,6 @@ type 'value compiler_api = {
 	get_local_using : unit -> tclass list;
 	get_local_using : unit -> tclass list;
 	get_local_vars : unit -> (string, Type.tvar) PMap.t;
 	get_local_vars : unit -> (string, Type.tvar) PMap.t;
 	get_build_fields : unit -> 'value;
 	get_build_fields : unit -> 'value;
-	get_pattern_locals : Ast.expr -> Type.t -> (string,Type.tvar * Globals.pos) PMap.t;
 	define_type : 'value -> string option -> unit;
 	define_type : 'value -> string option -> unit;
 	define_module : string -> 'value list -> ((string * Globals.pos) list * Ast.import_mode) list -> Ast.type_path list -> unit;
 	define_module : string -> 'value list -> ((string * Globals.pos) list * Ast.import_mode) list -> Ast.type_path list -> unit;
 	module_dependency : string -> string -> unit;
 	module_dependency : string -> string -> unit;
@@ -1825,10 +1824,6 @@ let macro_api ccom get_api =
 			else
 			else
 				encode_obj ["file",encode_string p.Globals.pfile;"pos",vint p.Globals.pmin]
 				encode_obj ["file",encode_string p.Globals.pfile;"pos",vint p.Globals.pmin]
 		);
 		);
-		"pattern_locals", vfun2 (fun e t ->
-			let loc = (get_api()).get_pattern_locals (decode_expr e) (decode_type t) in
-			encode_string_map (fun (v,_) -> encode_type v.v_type) loc
-		);
 		"apply_params", vfun3 (fun tpl tl t ->
 		"apply_params", vfun3 (fun tpl tl t ->
 			let tl = List.map decode_type (decode_array tl) in
 			let tl = List.map decode_type (decode_array tl) in
 			let tpl = List.map (fun v -> decode_string (field v "name"), decode_type (field v "t")) (decode_array tpl) in
 			let tpl = List.map (fun v -> decode_string (field v "name"), decode_type (field v "t")) (decode_array tpl) in

+ 0 - 3
src/typing/macroContext.ml

@@ -301,9 +301,6 @@ let make_macro_api ctx p =
 			| None -> Interp.vnull
 			| None -> Interp.vnull
 			| Some (_,_,fields) -> Interp.encode_array (List.map Interp.encode_field fields)
 			| Some (_,_,fields) -> Interp.encode_array (List.map Interp.encode_field fields)
 		);
 		);
-		MacroApi.get_pattern_locals = (fun e t ->
-			!get_pattern_locals_ref ctx e t
-		);
 		MacroApi.define_type = (fun v mdep ->
 		MacroApi.define_type = (fun v mdep ->
 			let cttype = { tpackage = ["haxe";"macro"]; tname = "Expr"; tparams = []; tsub = Some ("TypeDefinition") } in
 			let cttype = { tpackage = ["haxe";"macro"]; tname = "Expr"; tparams = []; tsub = Some ("TypeDefinition") } in
 			let mctx = (match ctx.g.macros with None -> assert false | Some (_,mctx) -> mctx) in
 			let mctx = (match ctx.g.macros with None -> assert false | Some (_,mctx) -> mctx) in

+ 8 - 5
src/typing/matcher.ml

@@ -147,6 +147,7 @@ module Pattern = struct
 		ctx_locals : (string, tvar) PMap.t;
 		ctx_locals : (string, tvar) PMap.t;
 		mutable current_locals : (string, tvar * pos) PMap.t;
 		mutable current_locals : (string, tvar * pos) PMap.t;
 		mutable in_reification : bool;
 		mutable in_reification : bool;
+		is_postfix_match : bool;
 	}
 	}
 
 
 	exception Bad_pattern of string
 	exception Bad_pattern of string
@@ -180,6 +181,7 @@ module Pattern = struct
 		in
 		in
 		let add_local final name p =
 		let add_local final name p =
 			let is_wildcard_local = name = "_" in
 			let is_wildcard_local = name = "_" in
+			if not is_wildcard_local && pctx.is_postfix_match then error "Capture variables are not allowed in .match patterns" p;
 			if not is_wildcard_local && PMap.mem name pctx.current_locals then error (Printf.sprintf "Variable %s is bound multiple times" name) p;
 			if not is_wildcard_local && PMap.mem name pctx.current_locals then error (Printf.sprintf "Variable %s is bound multiple times" name) p;
 			match pctx.or_locals with
 			match pctx.or_locals with
 			| Some map when not is_wildcard_local ->
 			| Some map when not is_wildcard_local ->
@@ -505,13 +507,14 @@ module Pattern = struct
 		let pat = loop e in
 		let pat = loop e in
 		pat,p
 		pat,p
 
 
-	let make ctx t e =
+	let make ctx t e postfix_match =
 		let pctx = {
 		let pctx = {
 			ctx = ctx;
 			ctx = ctx;
 			current_locals = PMap.empty;
 			current_locals = PMap.empty;
 			ctx_locals = ctx.locals;
 			ctx_locals = ctx.locals;
 			or_locals = None;
 			or_locals = None;
 			in_reification = false;
 			in_reification = false;
+			is_postfix_match = postfix_match;
 		} in
 		} in
 		make pctx true t e
 		make pctx true t e
 end
 end
@@ -525,7 +528,7 @@ module Case = struct
 		case_pos : pos;
 		case_pos : pos;
 	}
 	}
 
 
-	let make ctx t el eg eo_ast with_type p =
+	let make ctx t el eg eo_ast with_type postfix_match p =
 		let rec collapse_case el = match el with
 		let rec collapse_case el = match el with
 			| e :: [] ->
 			| e :: [] ->
 				e
 				e
@@ -546,7 +549,7 @@ module Case = struct
 		) ctx.locals [] in
 		) ctx.locals [] in
 		let old_ret = ctx.ret in
 		let old_ret = ctx.ret in
 		ctx.ret <- map ctx.ret;
 		ctx.ret <- map ctx.ret;
-		let pat = Pattern.make ctx (map t) e in
+		let pat = Pattern.make ctx (map t) e postfix_match in
 		unapply_type_parameters ctx.type_params monos;
 		unapply_type_parameters ctx.type_params monos;
 		let eg = match eg with
 		let eg = match eg with
 			| None -> None
 			| None -> None
@@ -1489,7 +1492,7 @@ end
 module Match = struct
 module Match = struct
 	open Typecore
 	open Typecore
 
 
-	let match_expr ctx e cases def with_type p =
+	let match_expr ctx e cases def with_type postfix_match p =
 		let match_debug = Meta.has (Meta.Custom ":matchDebug") ctx.curfield.cf_meta in
 		let match_debug = Meta.has (Meta.Custom ":matchDebug") ctx.curfield.cf_meta in
 		let rec loop e = match fst e with
 		let rec loop e = match fst e with
 			| EArrayDecl el when (match el with [(EFor _ | EWhile _),_] -> false | _ -> true) ->
 			| EArrayDecl el when (match el with [(EFor _ | EWhile _),_] -> false | _ -> true) ->
@@ -1514,7 +1517,7 @@ module Match = struct
 		in
 		in
 		let cases = List.map (fun (el,eg,eo,p) ->
 		let cases = List.map (fun (el,eg,eo,p) ->
 			let p = match eo with Some e when p = null_pos -> pos e | _ -> p in
 			let p = match eo with Some e when p = null_pos -> pos e | _ -> p in
-			let case,bindings,pat = Case.make ctx t el eg eo with_type p in
+			let case,bindings,pat = Case.make ctx t el eg eo with_type postfix_match p in
 			case,bindings,[pat]
 			case,bindings,[pat]
 		) cases in
 		) cases in
 		let infer_switch_type () =
 		let infer_switch_type () =

+ 2 - 6
src/typing/typer.ml

@@ -2313,11 +2313,7 @@ and type_call ctx e el (with_type:WithType.t) inline p =
 		let et = type_expr ctx e WithType.value in
 		let et = type_expr ctx e WithType.value in
 		(match follow et.etype with
 		(match follow et.etype with
 			| TEnum _ ->
 			| TEnum _ ->
-				let e = Matcher.Match.match_expr ctx e [[epat],None,Some (EConst(Ident "true"),p),p] (Some (Some (EConst(Ident "false"),p),p)) (WithType.with_type ctx.t.tbool) p in
-				(* TODO: add that back *)
-(* 				let locals = !get_pattern_locals_ref ctx epat t in
-				PMap.iter (fun _ (_,p) -> display_error ctx "Capture variables are not allowed" p) locals; *)
-				e
+				Matcher.Match.match_expr ctx e [[epat],None,Some (EConst(Ident "true"),p),p] (Some (Some (EConst(Ident "false"),p),p)) (WithType.with_type ctx.t.tbool) true p
 			| _ -> def ())
 			| _ -> def ())
 	| (EConst (Ident "__unprotect__"),_) , [(EConst (String _),_) as e] ->
 	| (EConst (Ident "__unprotect__"),_) , [(EConst (String _),_) as e] ->
 		let e = type_expr ctx e WithType.value in
 		let e = type_expr ctx e WithType.value in
@@ -2429,7 +2425,7 @@ and type_expr ctx (e,p) (with_type:WithType.t) =
 		mk (TWhile (cond,e,DoWhile)) ctx.t.tvoid p
 		mk (TWhile (cond,e,DoWhile)) ctx.t.tvoid p
 	| ESwitch (e1,cases,def) ->
 	| ESwitch (e1,cases,def) ->
 		let wrap e1 = mk (TMeta((Meta.Ast,[e,p],p),e1)) e1.etype e1.epos in
 		let wrap e1 = mk (TMeta((Meta.Ast,[e,p],p),e1)) e1.etype e1.epos in
-		let e = Matcher.Match.match_expr ctx e1 cases def with_type p in
+		let e = Matcher.Match.match_expr ctx e1 cases def with_type false p in
 		wrap e
 		wrap e
 	| EReturn e ->
 	| EReturn e ->
 		type_return ctx e with_type p
 		type_return ctx e with_type p

+ 16 - 0
tests/misc/projects/Issue7921/Main.hx

@@ -0,0 +1,16 @@
+enum E<T> {
+	None;
+	Some(v:T);
+}
+
+class Main {
+	static function foo(v:E<Int>) {
+		var a = None;
+		return v.match(a);
+	}
+
+	static function main() {
+		trace(foo(None));
+		trace(foo(Some(55)));
+	}
+}

+ 2 - 0
tests/misc/projects/Issue7921/compile-fail.hxml

@@ -0,0 +1,2 @@
+--main Main
+--interp

+ 1 - 0
tests/misc/projects/Issue7921/compile-fail.hxml.stderr

@@ -0,0 +1 @@
+Main.hx:9: characters 18-19 : Capture variables are not allowed in .match patterns