aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src/erl_parse.yrl
diff options
context:
space:
mode:
authorHans Bolinder <[email protected]>2015-05-20 12:45:37 +0200
committerHans Bolinder <[email protected]>2015-06-12 10:42:19 +0200
commitca1c1f8d1a4fe4f7b19b9959c48bd64915215f24 (patch)
tree2efd88009d5a10087f87be0616c7e0ed60f59447 /lib/stdlib/src/erl_parse.yrl
parent6347ee34c81a136055182367905647588a3947bf (diff)
downloadotp-ca1c1f8d1a4fe4f7b19b9959c48bd64915215f24.tar.gz
otp-ca1c1f8d1a4fe4f7b19b9959c48bd64915215f24.tar.bz2
otp-ca1c1f8d1a4fe4f7b19b9959c48bd64915215f24.zip
stdlib: Introduce precedence for operators in types
Add new functions erl_parse:type_inop_prec() and erl_parse:type_preop_prec(). Get rid of paren_type used for parentheses in types.
Diffstat (limited to 'lib/stdlib/src/erl_parse.yrl')
-rw-r--r--lib/stdlib/src/erl_parse.yrl64
1 files changed, 41 insertions, 23 deletions
diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl
index e328e065e3..274bb2a782 100644
--- a/lib/stdlib/src/erl_parse.yrl
+++ b/lib/stdlib/src/erl_parse.yrl
@@ -125,22 +125,19 @@ top_type_100 -> type_200 : '$1'.
top_type_100 -> type_200 '|' top_type_100 : lift_unions('$1','$3').
type_200 -> type_300 '..' type_300 : {type, ?anno('$1'), range,
- [skip_paren('$1'),
- skip_paren('$3')]}.
+ ['$1', '$3']}.
type_200 -> type_300 : '$1'.
-type_300 -> type_300 add_op type_400 : ?mkop2(skip_paren('$1'),
- '$2', skip_paren('$3')).
+type_300 -> type_300 add_op type_400 : ?mkop2('$1', '$2', '$3').
type_300 -> type_400 : '$1'.
-type_400 -> type_400 mult_op type_500 : ?mkop2(skip_paren('$1'),
- '$2', skip_paren('$3')).
+type_400 -> type_400 mult_op type_500 : ?mkop2('$1', '$2', '$3').
type_400 -> type_500 : '$1'.
-type_500 -> prefix_op type : ?mkop1('$1', skip_paren('$2')).
+type_500 -> prefix_op type : ?mkop1('$1', '$2').
type_500 -> type : '$1'.
-type -> '(' top_type ')' : {paren_type, ?anno('$2'), ['$2']}.
+type -> '(' top_type ')' : '$2'.
type -> var : '$1'.
type -> atom : '$1'.
type -> atom '(' ')' : build_gen_type('$1').
@@ -524,6 +521,7 @@ Erlang code.
-export([normalise/1,abstract/1,tokens/1,tokens/2]).
-export([abstract/2]).
-export([inop_prec/1,preop_prec/1,func_prec/0,max_prec/0]).
+-export([type_inop_prec/1,type_preop_prec/1]).
-export([map_anno/2, fold_anno/3, mapfold_anno/3,
new_anno/1, anno_to_term/1, anno_from_term/1]).
-export([set_line/2,get_attribute/2,get_attributes/1]).
@@ -671,11 +669,6 @@ lift_unions(T1, {type, _Aa, union, List}) ->
lift_unions(T1, T2) ->
{type, ?anno(T1), union, [T1, T2]}.
-skip_paren({paren_type,_A,[Type]}) ->
- skip_paren(Type);
-skip_paren(Type) ->
- Type.
-
build_gen_type({atom, Aa, tuple}) ->
{type, Aa, tuple, any};
build_gen_type({atom, Aa, map}) ->
@@ -687,7 +680,7 @@ build_gen_type({atom, Aa, Name}) ->
build_bin_type([{var, _, '_'}|Left], Int) ->
build_bin_type(Left, Int);
build_bin_type([], Int) ->
- skip_paren(Int);
+ Int;
build_bin_type([{var, Aa, _}|_], _) ->
ret_err(Aa, "Bad binary type").
@@ -807,8 +800,7 @@ record_fields([{typed,Expr,TypeInfo}|Fields]) ->
{atom, Aa, _} ->
case has_undefined(TypeInfo) of
false ->
- TypeInfo2 = maybe_add_paren(TypeInfo),
- lift_unions(abstract2(undefined, Aa), TypeInfo2);
+ lift_unions(abstract2(undefined, Aa), TypeInfo);
true ->
TypeInfo
end
@@ -822,18 +814,11 @@ has_undefined({atom,_,undefined}) ->
true;
has_undefined({ann_type,_,[_,T]}) ->
has_undefined(T);
-has_undefined({paren_type,_,[T]}) ->
- has_undefined(T);
has_undefined({type,_,union,Ts}) ->
lists:any(fun has_undefined/1, Ts);
has_undefined(_) ->
false.
-maybe_add_paren({ann_type,A,T}) ->
- {paren_type,A,[{ann_type,A,T}]};
-maybe_add_paren(T) ->
- T.
-
term(Expr) ->
try normalise(Expr)
catch _:_R -> ret_err(?anno(Expr), "bad attribute")
@@ -1099,6 +1084,39 @@ func_prec() -> {800,700}.
max_prec() -> 900.
+-type prec() :: non_neg_integer().
+
+-type type_inop() :: '::' | '|' | '..' | '+' | '-' | 'bor' | 'bxor'
+ | 'bsl' | 'bsr' | '*' | '/' | 'div' | 'rem' | 'band'.
+
+-type type_preop() :: '+' | '-' | 'bnot' | '#'.
+
+-spec type_inop_prec(type_inop()) -> {prec(), prec(), prec()}.
+
+type_inop_prec('=') -> {150,100,100};
+type_inop_prec('::') -> {160,150,150};
+type_inop_prec('|') -> {180,170,170};
+type_inop_prec('..') -> {300,200,300};
+type_inop_prec('+') -> {400,400,500};
+type_inop_prec('-') -> {400,400,500};
+type_inop_prec('bor') -> {400,400,500};
+type_inop_prec('bxor') -> {400,400,500};
+type_inop_prec('bsl') -> {400,400,500};
+type_inop_prec('bsr') -> {400,400,500};
+type_inop_prec('*') -> {500,500,600};
+type_inop_prec('/') -> {500,500,600};
+type_inop_prec('div') -> {500,500,600};
+type_inop_prec('rem') -> {500,500,600};
+type_inop_prec('band') -> {500,500,600};
+type_inop_prec('#') -> {800,700,800}.
+
+-spec type_preop_prec(type_preop()) -> {prec(), prec()}.
+
+type_preop_prec('+') -> {600,700};
+type_preop_prec('-') -> {600,700};
+type_preop_prec('bnot') -> {600,700};
+type_preop_prec('#') -> {700,800}.
+
%%% [Experimental]. The parser just copies the attributes of the
%%% scanner tokens to the abstract format. This design decision has
%%% been hidden to some extent: use set_line() and get_attribute() to