Skip to content
Closed
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
2 changes: 1 addition & 1 deletion parsing/lexer.mll
Original file line number Diff line number Diff line change
Expand Up @@ -479,7 +479,7 @@ rule token = parse
| ['+' '-'] symbolchar *
{ INFIXOP2(Lexing.lexeme lexbuf) }
| "**" symbolchar *
{ INFIXOP4(Lexing.lexeme lexbuf) }
{ EXPONENTIATION(Lexing.lexeme lexbuf) }
| '%' { PERCENT }
| ['*' '/' '%'] symbolchar *
{ INFIXOP3(Lexing.lexeme lexbuf) }
Expand Down
26 changes: 14 additions & 12 deletions parsing/parser.mly
Original file line number Diff line number Diff line change
Expand Up @@ -340,6 +340,7 @@ let mkctf_attrs d attrs =
%token <string> INFIXOP2
%token <string> INFIXOP3
%token <string> INFIXOP4
%token <string> EXPONENTIATION
%token INHERIT
%token INITIALIZER
%token <int> INT
Expand Down Expand Up @@ -465,6 +466,8 @@ The precedences must be listed from low to high.
%left INFIXOP2 PLUS PLUSDOT MINUS MINUSDOT PLUSEQ /* expr (e OP e OP e) */
%left PERCENT INFIXOP3 STAR /* expr (e OP e OP e) */
%right INFIXOP4 /* expr (e OP e OP e) */
%nonassoc prec_unary_minusdot prec_unary_plusdot /* unary -. */
%right EXPONENTIATION
%nonassoc prec_unary_minus prec_unary_plus /* unary - */
%nonassoc prec_constant_constructor /* cf. simple_expr (C versus C x) */
%nonassoc prec_constr_appl /* above AS BAR COLONCOLON COMMA */
Expand Down Expand Up @@ -1130,6 +1133,8 @@ expr:
{ mkinfix $1 $2 $3 }
| expr INFIXOP4 expr
{ mkinfix $1 $2 $3 }
| expr EXPONENTIATION expr
{ mkinfix $1 $2 $3 }
| expr PLUS expr
{ mkinfix $1 "+" $3 }
| expr PLUSDOT expr
Expand Down Expand Up @@ -1160,10 +1165,14 @@ expr:
{ mkinfix $1 "&&" $3 }
| expr COLONEQUAL expr
{ mkinfix $1 ":=" $3 }
| subtractive expr %prec prec_unary_minus
{ mkuminus $1 $2 }
| additive expr %prec prec_unary_plus
{ mkuplus $1 $2 }
| MINUS expr %prec prec_unary_minus
{ mkuminus "-" $2 }
| MINUSDOT expr %prec prec_unary_minusdot
{ mkuminus "-." $2 }
| PLUS expr %prec prec_unary_plus
{ mkuplus "+" $2 }
| PLUSDOT expr %prec prec_unary_plusdot
{ mkuplus "+." $2 }
| simple_expr DOT label_longident LESSMINUS expr
{ mkexp(Pexp_setfield($1, mkrhs $3 3, $5)) }
| simple_expr DOT LPAREN seq_expr RPAREN LESSMINUS expr
Expand Down Expand Up @@ -1950,6 +1959,7 @@ operator:
| INFIXOP2 { $1 }
| INFIXOP3 { $1 }
| INFIXOP4 { $1 }
| EXPONENTIATION { $1 }
| BANG { "!" }
| PLUS { "+" }
| PLUSDOT { "+." }
Expand Down Expand Up @@ -2074,14 +2084,6 @@ opt_semi:
| /* empty */ { () }
| SEMI { () }
;
subtractive:
| MINUS { "-" }
| MINUSDOT { "-." }
;
additive:
| PLUS { "+" }
| PLUSDOT { "+." }
;

/* Attributes and extensions */

Expand Down