Skip to content

Commit 969bc96

Browse files
author
José Valim
committed
Move ++, --, ** and // to new table
1 parent e941d78 commit 969bc96

File tree

3 files changed

+69
-57
lines changed

3 files changed

+69
-57
lines changed

lib/elixir/src/elixir_parser.yrl

Lines changed: 37 additions & 39 deletions
Original file line numberDiff line numberDiff line change
@@ -2,11 +2,10 @@ Nonterminals
22
grammar expr_list
33
expr paren_expr block_expr fn_expr bracket_expr call_expr bracket_at_expr max_expr
44
base_expr matched_expr matched_op_expr unmatched_expr op_expr
5-
two_op bin_concat_op
6-
match_op default_op tail_op
7-
colon_colon_op
8-
comp_op_eol at_op_eol unary_op_eol dual_op_eol and_op_eol or_op_eol
9-
arrow_op_eol pin_op_eol mult_op_eol range_op_eol
5+
match_op tail_op colon_colon_op
6+
comp_op_eol at_op_eol unary_op_eol and_op_eol or_op_eol
7+
add_op_eol mult_op_eol exp_op_eol two_op_eol
8+
arrow_op_eol range_op_eol than_op_eol default_op_eol
109
when_op_eol in_op_eol inc_op_eol
1110
open_paren close_paren empty_paren
1211
open_bracket close_bracket
@@ -30,9 +29,10 @@ Terminals
3029
fn 'end' aliases
3130
number signed_number atom bin_string list_string sigil
3231
dot_call_op op_identifier
33-
comp_op at_op unary_op dual_op and_op or_op arrow_op pin_op
34-
mult_op range_op in_op inc_op when_op
35-
'=' '++' '--' '**' '//' '::' '|' '<>' '->'
32+
comp_op at_op unary_op and_op or_op arrow_op
33+
range_op in_op inc_op when_op than_op default_op
34+
dual_op add_op mult_op exp_op two_op
35+
'=' '::' '|' '->'
3636
'true' 'false' 'nil' 'do' eol ',' '.' '&'
3737
'(' ')' '[' ']' '{' '}' '<<' '>>'
3838
'...'
@@ -45,7 +45,7 @@ Right 10 stab_op.
4545
Left 20 ','.
4646
Right 30 colon_colon_op.
4747
Right 40 when_op_eol. %% when
48-
Right 50 default_op.
48+
Right 50 default_op_eol. %% //
4949
Left 60 tail_op.
5050
Left 70 inc_op_eol. %% inlist, inbits
5151
Right 80 match_op.
@@ -55,14 +55,14 @@ Left 150 comp_op_eol. %% <, >, <=, >=, ==, !=, =~, ===, !==
5555
Right 160 arrow_op_eol. %% < (op), (op) > (e.g <-, |>, <<<, >>>)
5656
Left 170 in_op_eol. %% in
5757
Left 200 range_op_eol. %% ..
58-
Left 210 dual_op_eol. %% +, -
59-
Left 220 mult_op_eol. %% *, /
60-
Left 230 pin_op_eol. %% ^ (op) (e.g ^^^)
61-
Right 240 bin_concat_op.
62-
Right 250 two_op.
58+
Left 210 add_op_eol. %% + (op), - (op)
59+
Left 220 mult_op_eol. %% * (op), / (op)
60+
Right 230 than_op_eol. %% < (op) > (e.g <>)
61+
Right 240 two_op_eol. %% ++, --, **
62+
Left 250 exp_op_eol. %% ^ (op) (e.g ^^^)
6363
Nonassoc 300 unary_op_eol. %% +, -, !, ^, not, ~~~
6464
Left 310 dot_call_op.
65-
Left 310 dot_op.
65+
Left 310 dot_op. %% .
6666
Nonassoc 320 at_op_eol. %% @ (op)
6767
Nonassoc 330 var.
6868

@@ -99,37 +99,37 @@ unmatched_expr -> at_op_eol expr : build_unary_op('$1', '$2').
9999
unmatched_expr -> block_expr : '$1'.
100100

101101
op_expr -> match_op expr : { '$1', '$2' }.
102-
op_expr -> dual_op_eol expr : { '$1', '$2' }.
102+
op_expr -> add_op_eol expr : { '$1', '$2' }.
103103
op_expr -> mult_op_eol expr : { '$1', '$2' }.
104-
op_expr -> two_op expr : { '$1', '$2' }.
104+
op_expr -> exp_op_eol expr : { '$1', '$2' }.
105+
op_expr -> two_op_eol expr : { '$1', '$2' }.
105106
op_expr -> and_op_eol expr : { '$1', '$2' }.
106107
op_expr -> or_op_eol expr : { '$1', '$2' }.
107-
op_expr -> pin_op_eol expr : { '$1', '$2' }.
108108
op_expr -> tail_op expr : { '$1', '$2' }.
109-
op_expr -> bin_concat_op expr : { '$1', '$2' }.
109+
op_expr -> than_op_eol expr : { '$1', '$2' }.
110110
op_expr -> in_op_eol expr : { '$1', '$2' }.
111111
op_expr -> inc_op_eol expr : { '$1', '$2' }.
112112
op_expr -> when_op_eol expr : { '$1', '$2' }.
113113
op_expr -> range_op_eol expr : { '$1', '$2' }.
114-
op_expr -> default_op expr : { '$1', '$2' }.
114+
op_expr -> default_op_eol expr : { '$1', '$2' }.
115115
op_expr -> colon_colon_op expr : { '$1', '$2' }.
116116
op_expr -> comp_op_eol expr : { '$1', '$2' }.
117117
op_expr -> arrow_op_eol expr : { '$1', '$2' }.
118118

119119
matched_op_expr -> match_op matched_expr : { '$1', '$2' }.
120-
matched_op_expr -> dual_op_eol matched_expr : { '$1', '$2' }.
120+
matched_op_expr -> add_op_eol matched_expr : { '$1', '$2' }.
121121
matched_op_expr -> mult_op_eol matched_expr : { '$1', '$2' }.
122-
matched_op_expr -> two_op matched_expr : { '$1', '$2' }.
122+
matched_op_expr -> exp_op_eol matched_expr : { '$1', '$2' }.
123+
matched_op_expr -> two_op_eol matched_expr : { '$1', '$2' }.
123124
matched_op_expr -> and_op_eol matched_expr : { '$1', '$2' }.
124125
matched_op_expr -> or_op_eol matched_expr : { '$1', '$2' }.
125-
matched_op_expr -> pin_op_eol matched_expr : { '$1', '$2' }.
126126
matched_op_expr -> tail_op matched_expr : { '$1', '$2' }.
127-
matched_op_expr -> bin_concat_op matched_expr : { '$1', '$2' }.
127+
matched_op_expr -> than_op_eol matched_expr : { '$1', '$2' }.
128128
matched_op_expr -> in_op_eol matched_expr : { '$1', '$2' }.
129129
matched_op_expr -> inc_op_eol matched_expr : { '$1', '$2' }.
130130
matched_op_expr -> when_op_eol matched_expr : { '$1', '$2' }.
131131
matched_op_expr -> range_op_eol matched_expr : { '$1', '$2' }.
132-
matched_op_expr -> default_op matched_expr : { '$1', '$2' }.
132+
matched_op_expr -> default_op_eol matched_expr : { '$1', '$2' }.
133133
matched_op_expr -> colon_colon_op matched_expr : { '$1', '$2' }.
134134
matched_op_expr -> comp_op_eol matched_expr : { '$1', '$2' }.
135135
matched_op_expr -> arrow_op_eol matched_expr : { '$1', '$2' }.
@@ -255,24 +255,22 @@ close_curly -> eol '}' : '$2'.
255255

256256
% Operators
257257

258-
dual_op_eol -> dual_op : '$1'.
259-
dual_op_eol -> dual_op eol : '$1'.
258+
add_op_eol -> add_op : '$1'.
259+
add_op_eol -> add_op eol : '$1'.
260+
add_op_eol -> dual_op : '$1'.
261+
add_op_eol -> dual_op eol : '$1'.
260262

261263
mult_op_eol -> mult_op : '$1'.
262264
mult_op_eol -> mult_op eol : '$1'.
263265

264-
two_op -> '++' : '$1'.
265-
two_op -> '--' : '$1'.
266-
two_op -> '++' eol : '$1'.
267-
two_op -> '--' eol : '$1'.
268-
two_op -> '**' : '$1'.
269-
two_op -> '**' eol : '$1'.
266+
exp_op_eol -> exp_op : '$1'.
267+
exp_op_eol -> exp_op eol : '$1'.
270268

271-
pin_op_eol -> pin_op : '$1'.
272-
pin_op_eol -> pin_op eol : '$1'.
269+
two_op_eol -> two_op : '$1'.
270+
two_op_eol -> two_op eol : '$1'.
273271

274-
default_op -> '//' : '$1'.
275-
default_op -> '//' eol : '$1'.
272+
default_op_eol -> default_op : '$1'.
273+
default_op_eol -> default_op eol : '$1'.
276274

277275
colon_colon_op -> '::' : '$1'.
278276
colon_colon_op -> '::' eol : '$1'.
@@ -294,8 +292,8 @@ or_op_eol -> or_op eol : '$1'.
294292
tail_op -> '|' : '$1'.
295293
tail_op -> '|' eol : '$1'.
296294

297-
bin_concat_op -> '<>' : '$1'.
298-
bin_concat_op -> '<>' eol : '$1'.
295+
than_op_eol -> than_op : '$1'.
296+
than_op_eol -> than_op eol : '$1'.
299297

300298
in_op_eol -> in_op : '$1'.
301299
in_op_eol -> in_op eol : '$1'.

lib/elixir/src/elixir_tokenizer.erl

Lines changed: 29 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -16,19 +16,14 @@
1616
).
1717

1818
-define(op2(T1, T2),
19-
T1 == $<, T2 == $>;
2019
T1 == $+, T2 == $+;
2120
T1 == $-, T2 == $-;
2221
T1 == $*, T2 == $*;
23-
T1 == $/, T2 == $/;
2422
T1 == $:, T2 == $:;
25-
T1 == $-, T2 == $>;
26-
T1 == $., T2 == $.
23+
T1 == $-, T2 == $>
2724
).
2825

2926
-define(op1(T),
30-
T == $*;
31-
T == $/;
3227
T == $=;
3328
T == $|
3429
).
@@ -46,9 +41,16 @@
4641
-define(unary_op3(T1, T2, T3),
4742
T1 == $~, T2 == $~, T3 == $~).
4843

49-
-define(pin_op3(T1, T2, T3),
50-
T1 == $^, T2 == $^, T3 == $^
51-
).
44+
-define(exp_op3(T1, T2, T3),
45+
T1 == $^, T2 == $^, T3 == $^).
46+
47+
-define(two_op(T1, T2),
48+
T1 == $+, T2 == $+;
49+
T1 == $-, T2 == $-;
50+
T1 == $*, T2 == $*).
51+
52+
-define(than_op(T1, T2),
53+
T1 == $<, T2 == $>).
5254

5355
-define(mult_op(T),
5456
T == $* orelse T == $/).
@@ -94,6 +96,9 @@
9496
-define(range_op(T1, T2),
9597
T1 == $., T2 == $.).
9698

99+
-define(default_op(T1, T2),
100+
T1 == $/, T2 == $/).
101+
97102
tokenize(String, Line, Opts) ->
98103
File = case lists:keyfind(file, 1, Opts) of
99104
{ file, V1 } -> V1;
@@ -242,13 +247,13 @@ tokenize([$.,T1,T2|Rest], Line, Scope, Tokens) when ?container(T1, T2) ->
242247
% ## Three Token Operators
243248
tokenize([$.,T1,T2,T3|Rest], Line, Scope, Tokens) when
244249
?unary_op3(T1, T2, T3); ?comp_op3(T1, T2, T3); ?and_op3(T1, T2, T3); ?or_op3(T1, T2, T3);
245-
?arrow_op3(T1, T2, T3); ?pin_op3(T1, T2, T3) ->
250+
?arrow_op3(T1, T2, T3); ?exp_op3(T1, T2, T3) ->
246251
handle_call_identifier(Rest, Line, list_to_atom([T1, T2, T3]), Scope, Tokens);
247252

248253
% ## Two Token Operators
249254
tokenize([$.,T1,T2|Rest], Line, Scope, Tokens) when
250255
?comp_op2(T1, T2); ?and_op(T1, T2); ?or_op(T1, T2); ?arrow_op(T1, T2);
251-
?range_op(T1, T2) ->
256+
?range_op(T1, T2); ?than_op(T1, T2); ?default_op(T1, T2); ?two_op(T1, T2) ->
252257
handle_call_identifier(Rest, Line, list_to_atom([T1, T2]), Scope, Tokens);
253258

254259
tokenize([$.,T1,T2|Rest], Line, Scope, Tokens) when ?op2(T1, T2) ->
@@ -326,13 +331,13 @@ tokenize([$:,T1,T2|Rest], Line, Scope, Tokens) when ?container(T1, T2) ->
326331
% ## Three Token Operators
327332
tokenize([$:,T1,T2,T3|Rest], Line, Scope, Tokens) when
328333
?unary_op3(T1, T2, T3); ?comp_op3(T1, T2, T3); ?and_op3(T1, T2, T3); ?or_op3(T1, T2, T3);
329-
?arrow_op3(T1, T2, T3); ?pin_op3(T1, T2, T3) ->
334+
?arrow_op3(T1, T2, T3); ?exp_op3(T1, T2, T3) ->
330335
tokenize(Rest, Line, Scope, [{ atom, Line, list_to_atom([T1,T2,T3]) }|Tokens]);
331336

332337
% ## Two Token Operators
333338
tokenize([$:,T1,T2|Rest], Line, Scope, Tokens) when
334339
?comp_op2(T1, T2); ?and_op(T1, T2); ?or_op(T1, T2); ?arrow_op(T1, T2);
335-
?range_op(T1, T2) ->
340+
?range_op(T1, T2); ?than_op(T1, T2); ?default_op(T1, T2); ?two_op(T1, T2) ->
336341
tokenize(Rest, Line, Scope, [{ atom, Line, list_to_atom([T1,T2]) }|Tokens]);
337342

338343
tokenize([$:,T1,T2|Rest], Line, Scope, Tokens) when ?op2(T1, T2) ->
@@ -388,8 +393,8 @@ tokenize([T1,T2,T3|Rest], Line, Scope, Tokens) when ?or_op3(T1, T2, T3) ->
388393
tokenize([T1,T2,T3|Rest], Line, Scope, Tokens) when ?arrow_op3(T1, T2, T3) ->
389394
handle_op(Rest, Line, arrow_op, list_to_atom([T1,T2,T3]), Scope, Tokens);
390395

391-
tokenize([T1,T2,T3|Rest], Line, Scope, Tokens) when ?pin_op3(T1, T2, T3) ->
392-
handle_op(Rest, Line, pin_op, list_to_atom([T1,T2,T3]), Scope, Tokens);
396+
tokenize([T1,T2,T3|Rest], Line, Scope, Tokens) when ?exp_op3(T1, T2, T3) ->
397+
handle_op(Rest, Line, exp_op, list_to_atom([T1,T2,T3]), Scope, Tokens);
393398

394399
% ## Containers + punctuation tokens
395400
tokenize([T,T|Rest], Line, Scope, Tokens) when T == $<; T == $> ->
@@ -402,6 +407,12 @@ tokenize([T|Rest], Line, Scope, Tokens) when T == $(;
402407
handle_terminator(Rest, Line, Scope, Token, Tokens);
403408

404409
% ## Two Token Operators
410+
tokenize([T1,T2|Rest], Line, Scope, Tokens) when ?two_op(T1, T2) ->
411+
handle_op(Rest, Line, two_op, list_to_atom([T1, T2]), Scope, Tokens);
412+
413+
tokenize([T1,T2|Rest], Line, Scope, Tokens) when ?than_op(T1, T2) ->
414+
handle_op(Rest, Line, than_op, list_to_atom([T1, T2]), Scope, Tokens);
415+
405416
tokenize([T1,T2|Rest], Line, Scope, Tokens) when ?range_op(T1, T2) ->
406417
handle_op(Rest, Line, range_op, list_to_atom([T1, T2]), Scope, Tokens);
407418

@@ -417,6 +428,9 @@ tokenize([T1,T2|Rest], Line, Scope, Tokens) when ?and_op(T1, T2) ->
417428
tokenize([T1,T2|Rest], Line, Scope, Tokens) when ?or_op(T1, T2) ->
418429
handle_op(Rest, Line, or_op, list_to_atom([T1, T2]), Scope, Tokens);
419430

431+
tokenize([T1,T2|Rest], Line, Scope, Tokens) when ?default_op(T1, T2) ->
432+
handle_op(Rest, Line, default_op, list_to_atom([T1, T2]), Scope, Tokens);
433+
420434
tokenize([T1,T2|Rest], Line, Scope, Tokens) when ?op2(T1, T2) ->
421435
handle_op(Rest, Line, list_to_atom([T1, T2]), Scope, Tokens);
422436

lib/elixir/test/erlang/tokenizer_test.erl

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -92,7 +92,7 @@ newline_test() ->
9292
{'.',2},
9393
{identifier,2,bar}] = tokenize("foo\n.bar"),
9494
[{number,1,1},
95-
{'++',2},
95+
{two_op,2,'++'},
9696
{number,2,2}] = tokenize("1\n++2").
9797

9898
aliases_test() ->
@@ -112,10 +112,10 @@ empty_string_test() ->
112112
[{list_string,1,[<<>>]}] = tokenize("''").
113113

114114
default_test() ->
115-
[{identifier,1,x},{'//',1},{number,1,1}] = tokenize("x // 1").
115+
[{identifier,1,x},{default_op,1,'//'},{number,1,1}] = tokenize("x // 1").
116116

117117
addadd_test() ->
118-
[{identifier,1,x},{'++',1},{identifier,1,y}] = tokenize("x ++ y").
118+
[{identifier,1,x},{two_op,1,'++'},{identifier,1,y}] = tokenize("x ++ y").
119119

120120
chars_test() ->
121121
[{number,1,97}] = tokenize("?a"),

0 commit comments

Comments
 (0)