summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorAlain Frisch <alain@frisch.fr>2011-12-21 08:58:56 +0000
committerAlain Frisch <alain@frisch.fr>2011-12-21 08:58:56 +0000
commitd79455bc76b260455bd6a443a6d8149df6602241 (patch)
treec7d56544e11a13d6ba4dcc6c85987fdc21d6c95c
parent8c16e88983a7788bc78a2bcf702b2b615852289a (diff)
New syntax for 'custom let bindings': let.simple_expr pat = expr in expr
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@11906 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--Changes10
-rw-r--r--parsing/lexer.mll2
-rw-r--r--parsing/parser.mly25
-rw-r--r--typing/oprint.ml6
4 files changed, 8 insertions, 35 deletions
diff --git a/Changes b/Changes
index 1af5a459a..06aaf54e0 100644
--- a/Changes
+++ b/Changes
@@ -12,14 +12,8 @@ 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.
-
+- New syntax "let.e0 p = e1 in e2" where e0 is a simple expression,
+ expanded to "e0 e1 (fun p -> e2).
Compilers:
- Revised simplification of let-alias (PR#5205, PR#5288)
diff --git a/parsing/lexer.mll b/parsing/lexer.mll
index c0ddf023b..87e2a8cbc 100644
--- a/parsing/lexer.mll
+++ b/parsing/lexer.mll
@@ -402,8 +402,6 @@ 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 87d43bdab..43a485151 100644
--- a/parsing/parser.mly
+++ b/parsing/parser.mly
@@ -319,17 +319,6 @@ 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 */
@@ -397,7 +386,6 @@ let let_operator op bindings cont =
%token LESS
%token LESSMINUS
%token LET
-%token <string> LETOP
%token <string> LIDENT
%token LPAREN
%token MATCH
@@ -474,7 +462,6 @@ 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 ...) */
@@ -995,8 +982,9 @@ 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 DOT simple_expr let_binding IN seq_expr
+ { let (pat, expr) = $4 in
+ mkexp(Pexp_apply($3, ["", expr; "", ghexp(Pexp_function("", None, [pat, $6]))])) }
| LET MODULE UIDENT module_binding IN seq_expr
{ mkexp(Pexp_letmodule($3, $4, $6)) }
| LET OPEN mod_longident IN seq_expr
@@ -1719,7 +1707,6 @@ operator:
| INFIXOP2 { $1 }
| INFIXOP3 { $1 }
| INFIXOP4 { $1 }
- | LETOP { $1 }
| BANG { "!" }
| PLUS { "+" }
| PLUSDOT { "+." }
@@ -1735,12 +1722,6 @@ 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 { "[]" } */
diff --git a/typing/oprint.ml b/typing/oprint.ml
index fa5f45870..21ef16080 100644
--- a/typing/oprint.ml
+++ b/typing/oprint.ml
@@ -32,9 +32,9 @@ let parenthesized_ident name =
(List.mem name ["or"; "mod"; "land"; "lor"; "lxor"; "lsl"; "lsr"; "asr"])
||
(match name.[0] with
- | 'l' when String.length name > 3 && String.sub name 0 3 = "let" -> true
- | 'a'..'z' | 'A'..'Z' | '\223'..'\246' | '\248'..'\255' | '_' -> false
- | _ -> true)
+ 'a'..'z' | 'A'..'Z' | '\223'..'\246' | '\248'..'\255' | '_' ->
+ false
+ | _ -> true)
let value_ident ppf name =
if parenthesized_ident name then