aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src/erl_parse.yrl
diff options
context:
space:
mode:
authorHans Bolinder <[email protected]>2010-06-02 13:57:00 +0000
committerErlang/OTP <[email protected]>2010-06-02 13:57:00 +0000
commit007340ead70a3867be6f65c60222a6a30afdf28c (patch)
treee5295a1d933c827ab1cda5b60850ab86295b5045 /lib/stdlib/src/erl_parse.yrl
parenta2b84aa66d96ac3f808ca60d2de072992fdb1410 (diff)
downloadotp-007340ead70a3867be6f65c60222a6a30afdf28c.tar.gz
otp-007340ead70a3867be6f65c60222a6a30afdf28c.tar.bz2
otp-007340ead70a3867be6f65c60222a6a30afdf28c.zip
OTP-8664 Erlang parser augmented with operators for integer types
Expressions evaluating to integers can now be used in types and function specifications where hitherto only integers were allowed ("Erlang_Integer").
Diffstat (limited to 'lib/stdlib/src/erl_parse.yrl')
-rw-r--r--lib/stdlib/src/erl_parse.yrl41
1 files changed, 28 insertions, 13 deletions
diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl
index 141ee18afd..bb4b18cf9b 100644
--- a/lib/stdlib/src/erl_parse.yrl
+++ b/lib/stdlib/src/erl_parse.yrl
@@ -47,7 +47,7 @@ opt_bit_size_expr bit_size_expr opt_bit_type_list bit_type_list bit_type
top_type top_type_100 top_types type typed_expr typed_attr_val
type_sig type_sigs type_guard type_guards fun_type fun_type_100 binary_type
type_spec spec_fun typed_exprs typed_record_fields field_types field_type
-bin_base_type bin_unit_type int_type.
+bin_base_type bin_unit_type type_200 type_300 type_400 type_500.
Terminals
char integer float atom string var
@@ -120,8 +120,24 @@ top_types -> top_type ',' top_types : ['$1'|'$3'].
top_type -> var '::' top_type_100 : {ann_type, ?line('$1'), ['$1','$3']}.
top_type -> top_type_100 : '$1'.
-top_type_100 -> type : '$1'.
-top_type_100 -> type '|' top_type_100 : lift_unions('$1','$3').
+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, ?line('$1'), range,
+ [skip_paren('$1'),
+ skip_paren('$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_400 : '$1'.
+
+type_400 -> type_400 mult_op type_500 : ?mkop2(skip_paren('$1'),
+ '$2', skip_paren('$3')).
+type_400 -> type_500 : '$1'.
+
+type_500 -> prefix_op type : ?mkop1('$1', skip_paren('$2')).
+type_500 -> type : '$1'.
type -> '(' top_type ')' : {paren_type, ?line('$2'), ['$2']}.
type -> var : '$1'.
@@ -143,16 +159,10 @@ type -> '#' atom '{' '}' : {type, ?line('$1'), record, ['$2']}.
type -> '#' atom '{' field_types '}' : {type, ?line('$1'),
record, ['$2'|'$4']}.
type -> binary_type : '$1'.
-type -> int_type : '$1'.
-type -> int_type '..' int_type : {type, ?line('$1'), range,
- ['$1', '$3']}.
+type -> integer : '$1'.
type -> 'fun' '(' ')' : {type, ?line('$1'), 'fun', []}.
type -> 'fun' '(' fun_type_100 ')' : '$3'.
-int_type -> integer : '$1'.
-int_type -> '-' integer : abstract(-normalise('$2'),
- ?line('$2')).
-
fun_type_100 -> '(' '...' ')' '->' top_type
: {type, ?line('$1'), 'fun',
[{type, ?line('$1'), any}, '$5']}.
@@ -180,9 +190,9 @@ binary_type -> '<<' bin_unit_type '>>' : {type, ?line('$1'),binary,
binary_type -> '<<' bin_base_type ',' bin_unit_type '>>'
: {type, ?line('$1'), binary, ['$2', '$4']}.
-bin_base_type -> var ':' integer : build_bin_type(['$1'], '$3').
+bin_base_type -> var ':' type : build_bin_type(['$1'], '$3').
-bin_unit_type -> var ':' var '*' integer : build_bin_type(['$1', '$3'], '$5').
+bin_unit_type -> var ':' var '*' type : build_bin_type(['$1', '$3'], '$5').
attr_val -> expr : ['$1'].
attr_val -> expr ',' exprs : ['$1' | '$3'].
@@ -607,6 +617,11 @@ lift_unions(T1, {type, _La, union, List}) ->
lift_unions(T1, T2) ->
{type, ?line(T1), union, [T1, T2]}.
+skip_paren({paren_type,_L,[Type]}) ->
+ skip_paren(Type);
+skip_paren(Type) ->
+ Type.
+
build_gen_type({atom, La, tuple}) ->
{type, La, tuple, any};
build_gen_type({atom, La, Name}) ->
@@ -615,7 +630,7 @@ build_gen_type({atom, La, Name}) ->
build_bin_type([{var, _, '_'}|Left], Int) ->
build_bin_type(Left, Int);
build_bin_type([], Int) ->
- Int;
+ skip_paren(Int);
build_bin_type([{var, La, _}|_], _) ->
ret_err(La, "Bad binary type").