summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--Changes8
-rw-r--r--parsing/lexer.mll2
-rw-r--r--parsing/parser.mly22
3 files changed, 32 insertions, 0 deletions
diff --git a/Changes b/Changes
index f9780490a..1af5a459a 100644
--- a/Changes
+++ b/Changes
@@ -12,6 +12,14 @@ Language features:
Using the -principal option guarantees forward compatibility.
- New (module M) and (module M : S) syntax in patterns, for immediate
unpacking of a first-class module.
+- Let-like operators can now be defined. Syntax for definining
+ such an operator: let (let!) x f = ...; for using it: let! p = e1 in e2,
+ sugar for (let!) e1 (fun p -> e2); or with an explicit module qualifier
+ M.let! p = e1 in e2. Multiple-bindings are allowed (let! p1 = e1 and p2 = e2
+ in in e3 is equivalent to let! (p1, p2) = (e1, e2) in e3. The lexical
+ definition for a let-like operator is the string "let", immediatly followed
+ by an non-empty sequence of operator characters.
+
Compilers:
- Revised simplification of let-alias (PR#5205, PR#5288)
diff --git a/parsing/lexer.mll b/parsing/lexer.mll
index 87e2a8cbc..c0ddf023b 100644
--- a/parsing/lexer.mll
+++ b/parsing/lexer.mll
@@ -402,6 +402,8 @@ rule token = parse
{ INFIXOP4(Lexing.lexeme lexbuf) }
| ['*' '/' '%'] symbolchar *
{ INFIXOP3(Lexing.lexeme lexbuf) }
+ | "let" symbolchar+
+ { LETOP(Lexing.lexeme lexbuf) }
| eof { EOF }
| _
{ raise (Error(Illegal_character (Lexing.lexeme_char lexbuf 0),
diff --git a/parsing/parser.mly b/parsing/parser.mly
index 885a581d4..87d43bdab 100644
--- a/parsing/parser.mly
+++ b/parsing/parser.mly
@@ -319,6 +319,17 @@ let wrap_type_annotation newtypes core_type body =
let polyvars, core_type = varify_constructors newtypes core_type in
(exp, ghtyp(Ptyp_poly(polyvars,core_type)))
+let let_operator op bindings cont =
+ let pat, expr =
+ match List.rev bindings with
+ | [] -> assert false
+ | [x] -> x
+ | l ->
+ let pats, exprs = List.split l in
+ ghpat (Ppat_tuple pats), ghexp (Pexp_tuple exprs)
+ in
+ mkexp(Pexp_apply(op, ["", expr; "", ghexp(Pexp_function("", None, [pat, cont]))]))
+
%}
/* Tokens */
@@ -386,6 +397,7 @@ let wrap_type_annotation newtypes core_type body =
%token LESS
%token LESSMINUS
%token LET
+%token <string> LETOP
%token <string> LIDENT
%token LPAREN
%token MATCH
@@ -462,6 +474,7 @@ The precedences must be listed from low to high.
%nonassoc below_SEMI
%nonassoc SEMI /* below EQUAL ({lbl=...; lbl=...}) */
%nonassoc LET /* above SEMI ( ...; let ... in ...) */
+%nonassoc LETOP
%nonassoc below_WITH
%nonassoc FUNCTION WITH /* below BAR (match ... with ...) */
%nonassoc AND /* above WITH (module rec A: SIG with ... and ...) */
@@ -982,6 +995,8 @@ expr:
{ mkexp(Pexp_apply($1, List.rev $2)) }
| LET rec_flag let_bindings IN seq_expr
{ mkexp(Pexp_let($2, List.rev $3, $5)) }
+ | let_operator let_bindings IN seq_expr
+ { let_operator $1 $2 $4 }
| LET MODULE UIDENT module_binding IN seq_expr
{ mkexp(Pexp_letmodule($3, $4, $6)) }
| LET OPEN mod_longident IN seq_expr
@@ -1704,6 +1719,7 @@ operator:
| INFIXOP2 { $1 }
| INFIXOP3 { $1 }
| INFIXOP4 { $1 }
+ | LETOP { $1 }
| BANG { "!" }
| PLUS { "+" }
| PLUSDOT { "+." }
@@ -1719,6 +1735,12 @@ operator:
| AMPERAMPER { "&&" }
| COLONEQUAL { ":=" }
;
+let_operator:
+ LETOP
+ { mkexp (Pexp_ident(Lident $1)) }
+ | mod_longident DOT LETOP
+ { mkexp (Pexp_ident(Ldot ($1, $3))) }
+;
constr_ident:
UIDENT { $1 }
/* | LBRACKET RBRACKET { "[]" } */