From 91048957f0681dba853f5720d3618aa1c5d0255e Mon Sep 17 00:00:00 2001 From: Hans Bolinder Date: Tue, 29 Nov 2016 09:37:21 +0100 Subject: stdilb: Check for bad type constraints in function types The parser recognizes the 'is_subtype(V, T)' syntax for constraints, and of course the new 'V :: T' syntax, but other variants result in an error message. Up to now, the parser and linter have let badly formed constraints through, and relied upon Dialyzer to emit warnings. is_subtype/2 cannot easily be taken out from the parser. Not only would we need find a way to emit a (linter) warning, but there also needs to be an option for suppressing the linter warning as compilation with +warnings_as_errors has to work. (Notice that the abstract format representation for 'V :: T' is the same as for 'is_subtype(V, T)'.) This correction was triggered by an email from Robert, and Kostis created pull request 1214 to provide a fix. However, Kostis' fix disallowed is_subtype() altogether, which breaks backward compatibility. As of Erlang/OTP 19.0 (ticket OTP-11879), the 'is_subtype(V, T)' is no longer documented. --- lib/stdlib/src/erl_parse.yrl | 36 +++++++++++++++++++++--------------- 1 file changed, 21 insertions(+), 15 deletions(-) (limited to 'lib/stdlib/src/erl_parse.yrl') diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl index 9cd95705af..a0bc21fbc5 100644 --- a/lib/stdlib/src/erl_parse.yrl +++ b/lib/stdlib/src/erl_parse.yrl @@ -33,7 +33,6 @@ list tail list_comprehension lc_expr lc_exprs binary_comprehension tuple -%struct record_expr record_tuple record_field record_fields map_expr map_tuple map_field map_field_assoc map_field_exact map_fields map_key if_expr if_clause if_clauses case_expr cr_clause cr_clauses receive_expr @@ -108,9 +107,8 @@ type_sig -> fun_type 'when' type_guards : {type, ?anno('$1'), bounded_fun, type_guards -> type_guard : ['$1']. type_guards -> type_guard ',' type_guards : ['$1'|'$3']. -type_guard -> atom '(' top_types ')' : {type, ?anno('$1'), constraint, - ['$1', '$3']}. -type_guard -> var '::' top_type : build_def('$1', '$3'). +type_guard -> atom '(' top_types ')' : build_compat_constraint('$1', '$3'). +type_guard -> var '::' top_type : build_constraint('$1', '$3'). top_types -> top_type : ['$1']. top_types -> top_type ',' top_types : ['$1'|'$3']. @@ -268,7 +266,6 @@ expr_max -> binary : '$1'. expr_max -> list_comprehension : '$1'. expr_max -> binary_comprehension : '$1'. expr_max -> tuple : '$1'. -%%expr_max -> struct : '$1'. expr_max -> '(' expr ')' : '$2'. expr_max -> 'begin' exprs 'end' : {block,?anno('$1'),'$2'}. expr_max -> if_expr : '$1'. @@ -327,10 +324,6 @@ lc_expr -> binary '<=' expr : {b_generate,?anno('$2'),'$1','$3'}. tuple -> '{' '}' : {tuple,?anno('$1'),[]}. tuple -> '{' exprs '}' : {tuple,?anno('$1'),'$2'}. - -%%struct -> atom tuple : -%% {struct,?anno('$1'),element(3, '$1'),element(3, '$2')}. - map_expr -> '#' map_tuple : {map, ?anno('$1'),'$2'}. map_expr -> expr_max '#' map_tuple : @@ -1056,13 +1049,13 @@ build_typed_attribute({atom,Aa,Attr},_) -> end. build_type_spec({Kind,Aa}, {SpecFun, TypeSpecs}) - when (Kind =:= spec) or (Kind =:= callback) -> + when Kind =:= spec ; Kind =:= callback -> NewSpecFun = case SpecFun of {atom, _, Fun} -> {Fun, find_arity_from_specs(TypeSpecs)}; - {{atom,_, Mod}, {atom,_, Fun}} -> - {Mod,Fun,find_arity_from_specs(TypeSpecs)} + {{atom, _, Mod}, {atom, _, Fun}} -> + {Mod, Fun, find_arity_from_specs(TypeSpecs)} end, {attribute,Aa,Kind,{NewSpecFun, TypeSpecs}}. @@ -1076,11 +1069,24 @@ find_arity_from_specs([Spec|_]) -> {type, _, 'fun', [{type, _, product, Args},_]} = Fun, length(Args). -build_def({var, A, '_'}, _Types) -> +%% The 'is_subtype(V, T)' syntax is not supported as of Erlang/OTP +%% 19.0, but is kept for backward compatibility. +build_compat_constraint({atom, _, is_subtype}, [{var, _, _}=LHS, Type]) -> + build_constraint(LHS, Type); +build_compat_constraint({atom, _, is_subtype}, [LHS, _Type]) -> + ret_err(?anno(LHS), "bad type variable"); +build_compat_constraint({atom, A, Atom}, _Types) -> + ret_err(A, io_lib:format("unsupported constraint ~w", [Atom])). + +build_constraint({atom, _, is_subtype}, [{var, _, _}=LHS, Type]) -> + build_constraint(LHS, Type); +build_constraint({atom, A, Atom}, _Foo) -> + ret_err(A, io_lib:format("unsupported constraint ~w", [Atom])); +build_constraint({var, A, '_'}, _Types) -> ret_err(A, "bad type variable"); -build_def(LHS, Types) -> +build_constraint(LHS, Type) -> IsSubType = {atom, ?anno(LHS), is_subtype}, - {type, ?anno(LHS), constraint, [IsSubType, [LHS, Types]]}. + {type, ?anno(LHS), constraint, [IsSubType, [LHS, Type]]}. lift_unions(T1, {type, _Aa, union, List}) -> {type, ?anno(T1), union, [T1|List]}; -- cgit v1.2.3