Skip to content

Commit

Permalink
Added syntactic sugar for record expressions and record patterns:
Browse files Browse the repository at this point in the history
{ lbl } stands for { lbl = lbl }.


git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@9324 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
  • Loading branch information
xavierleroy committed Aug 27, 2009
1 parent 71b94fa commit b01621e
Show file tree
Hide file tree
Showing 8 changed files with 23 additions and 1 deletion.
4 changes: 4 additions & 0 deletions Changes
Expand Up @@ -3,6 +3,10 @@ Objective Caml 3.12.0:

(Changes that can break existing programs are marked with a "*" )

Language features:
- Shorthand notation for records: in expressions and patterns,
{ lbl } stands for { lbl = lbl } and { M.lbl } for { M.lbl = lbl }

Compilers and toplevel:
- Added option '-no-app-funct' to turn applicative functors off.
This option can help working around mysterious type incompatibilities
Expand Down
Binary file modified boot/ocamlc
Binary file not shown.
Binary file modified boot/ocamldep
Binary file not shown.
Binary file modified boot/ocamllex
Binary file not shown.
5 changes: 5 additions & 0 deletions parsing/longident.ml
Expand Up @@ -24,6 +24,11 @@ let rec flat accu = function

let flatten lid = flat [] lid

let last = function
Lident s -> s
| Ldot(lid, s) -> s
| Lapply(l1, l2) -> Misc.fatal_error "Longident.last"

let rec split_at_dots s pos =
try
let dot = String.index_from s pos '.' in
Expand Down
1 change: 1 addition & 0 deletions parsing/longident.mli
Expand Up @@ -20,4 +20,5 @@ type t =
| Lapply of t * t

val flatten: t -> string list
val last: t -> string
val parse: string -> t
12 changes: 12 additions & 0 deletions parsing/parser.mly
Expand Up @@ -191,6 +191,12 @@ let lapply p1 p2 =
then Lapply(p1, p2)
else raise (Syntaxerr.Error(Syntaxerr.Applicative_path (symbol_rloc())))

let exp_of_label lbl =
mkexp (Pexp_ident(Lident(Longident.last lbl)))

let pat_of_label lbl =
mkpat (Ppat_var(Longident.last lbl))

%}

/* Tokens */
Expand Down Expand Up @@ -1043,8 +1049,12 @@ record_expr:
lbl_expr_list:
label_longident EQUAL expr
{ [$1,$3] }
| label_longident
{ [$1, exp_of_label $1] }
| lbl_expr_list SEMI label_longident EQUAL expr
{ ($3, $5) :: $1 }
| lbl_expr_list SEMI label_longident
{ ($3, exp_of_label $3) :: $1 }
;
field_expr_list:
label EQUAL expr
Expand Down Expand Up @@ -1137,7 +1147,9 @@ pattern_semi_list:
;
lbl_pattern_list:
label_longident EQUAL pattern { [($1, $3)] }
| label_longident { [($1, pat_of_label $1)] }
| lbl_pattern_list SEMI label_longident EQUAL pattern { ($3, $5) :: $1 }
| lbl_pattern_list SEMI label_longident { ($3, pat_of_label $3) :: $1 }
;
/* Primitive declarations */
Expand Down
2 changes: 1 addition & 1 deletion parsing/parsetree.mli
Expand Up @@ -46,7 +46,7 @@ and row_field =
Rtag of label * bool * core_type list
| Rinherit of core_type

(* XXX Type expressions for the class language *)
(* Type expressions for the class language *)

type 'a class_infos =
{ pci_virt: virtual_flag;
Expand Down

0 comments on commit b01621e

Please sign in to comment.