summaryrefslogtreecommitdiff
path: root/lib/stdlib/src/erl_parse.yrl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/src/erl_parse.yrl')
-rw-r--r--lib/stdlib/src/erl_parse.yrl42
1 files changed, 32 insertions, 10 deletions
diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl
index 33569d4a8d..6228c5857a 100644
--- a/lib/stdlib/src/erl_parse.yrl
+++ b/lib/stdlib/src/erl_parse.yrl
@@ -2,7 +2,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2021. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2022. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -48,13 +48,15 @@ top_type top_types type typed_expr typed_attr_val
type_sig type_sigs type_guard type_guards fun_type binary_type
type_spec spec_fun typed_exprs typed_record_fields field_types field_type
map_pair_types map_pair_type
-bin_base_type bin_unit_type.
+bin_base_type bin_unit_type
+maybe_expr maybe_match_exprs maybe_match.
Terminals
char integer float atom string var
'(' ')' ',' '->' '{' '}' '[' ']' '|' '||' '<-' ';' ':' '#' '.'
'after' 'begin' 'case' 'try' 'catch' 'end' 'fun' 'if' 'of' 'receive' 'when'
+'maybe' 'else'
'andalso' 'orelse'
'bnot' 'not'
'*' '/' 'div' 'rem' 'band' 'and'
@@ -63,6 +65,7 @@ char integer float atom string var
'==' '/=' '=<' '<' '>=' '>' '=:=' '=/=' '<=' '=>' ':='
'<<' '>>'
'!' '=' '::' '..' '...'
+'?='
'spec' 'callback' % helper
dot.
@@ -257,6 +260,7 @@ expr_max -> case_expr : '$1'.
expr_max -> receive_expr : '$1'.
expr_max -> fun_expr : '$1'.
expr_max -> try_expr : '$1'.
+expr_max -> maybe_expr : '$1'.
pat_expr -> pat_expr '=' pat_expr : {match,first_anno('$1'),'$1','$3'}.
pat_expr -> pat_expr comp_op pat_expr : ?mkop2('$1', '$2', '$3').
@@ -277,10 +281,6 @@ pat_expr_max -> '(' pat_expr ')' : '$2'.
map_pat_expr -> '#' map_tuple :
{map, ?anno('$1'),'$2'}.
-map_pat_expr -> pat_expr_max '#' map_tuple :
- {map, ?anno('$2'),'$1','$3'}.
-map_pat_expr -> map_pat_expr '#' map_tuple :
- {map, ?anno('$2'),'$1','$3'}.
record_pat_expr -> '#' atom '.' atom :
{record_index,?anno('$1'),element(3, '$2'),'$4'}.
@@ -401,7 +401,6 @@ if_clauses -> if_clause ';' if_clauses : ['$1' | '$3'].
if_clause -> guard clause_body :
{clause,first_anno(hd(hd('$1'))),[],'$1','$2'}.
-
case_expr -> 'case' expr 'of' cr_clauses 'end' :
{'case',?anno('$1'),'$2','$4'}.
@@ -477,6 +476,21 @@ try_clause -> var ':' pat_expr try_opt_stacktrace clause_guard clause_body :
try_opt_stacktrace -> ':' var : '$2'.
try_opt_stacktrace -> '$empty' : '_'.
+
+maybe_expr -> 'maybe' maybe_match_exprs 'end' :
+ {'maybe',?anno('$1'),'$2'}.
+maybe_expr -> 'maybe' maybe_match_exprs 'else' cr_clauses 'end' :
+ %% `erl_lint` can produce a better warning when the position
+ %% of the `else` keyword is known.
+ {'maybe',?anno('$1'),'$2',{'else',?anno('$3'),'$4'}}.
+
+maybe_match_exprs -> maybe_match : ['$1'].
+maybe_match_exprs -> maybe_match ',' maybe_match_exprs : ['$1' | '$3'].
+maybe_match_exprs -> expr : ['$1'].
+maybe_match_exprs -> expr ',' maybe_match_exprs : ['$1' | '$3'].
+
+maybe_match -> expr '?=' expr : {maybe_match,?anno('$2'),'$1','$3'}.
+
argument_list -> '(' ')' : {[],?anno('$1')}.
argument_list -> '(' exprs ')' : {'$2',?anno('$1')}.
@@ -647,6 +661,7 @@ Erlang code.
-type abstract_expr() :: af_literal()
| af_match(abstract_expr())
+ | af_maybe_match()
| af_variable()
| af_tuple(abstract_expr())
| af_nil()
@@ -673,7 +688,9 @@ Erlang code.
| af_local_fun()
| af_remote_fun()
| af_fun()
- | af_named_fun().
+ | af_named_fun()
+ | af_maybe()
+ | af_maybe_else().
-type af_record_update(T) :: {'record',
anno(),
@@ -816,6 +833,9 @@ Erlang code.
-type af_map_pattern() ::
{'map', anno(), [af_assoc_exact(af_pattern())]}.
+-type af_maybe() :: {'maybe', anno(), af_body()}.
+-type af_maybe_else() :: {'maybe', anno(), af_body(), {'else', anno(), af_clause_seq()}}.
+
-type abstract_type() :: af_annotated_type()
| af_atom()
| af_bitstring_type()
@@ -926,6 +946,8 @@ Erlang code.
-type af_match(T) :: {'match', anno(), af_pattern(), T}.
+-type af_maybe_match() :: {'maybe_match', anno(), af_pattern(), abstract_expr()}.
+
-type af_variable() :: {'var', anno(), atom()}. % | af_anon_variable()
%-type af_anon_variable() :: {'var', anno(), '_'}.
@@ -951,7 +973,7 @@ Erlang code.
-type binary_op() :: '/' | '*' | 'div' | 'rem' | 'band' | 'and' | '+' | '-'
| 'bor' | 'bxor' | 'bsl' | 'bsr' | 'or' | 'xor' | '++'
| '--' | '==' | '/=' | '=<' | '<' | '>=' | '>' | '=:='
- | '=/='.
+ | '=/=' | '!'.
-type af_unary_op(T) :: {'op', anno(), unary_op(), T}.
@@ -1397,7 +1419,7 @@ normalise({bin,_,Fs}) ->
eval_bits:expr_grp(Fs, [],
fun(E, _) ->
{value, normalise(E), []}
- end, [], true),
+ end),
B;
normalise({cons,_,Head,Tail}) ->
[normalise(Head)|normalise(Tail)];