diff --git a/Changes b/Changes index ffba2321c6d3..2722264b0ba3 100644 --- a/Changes +++ b/Changes @@ -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 diff --git a/boot/ocamlc b/boot/ocamlc index 808d5b87f9a7..4e13e5e71443 100755 Binary files a/boot/ocamlc and b/boot/ocamlc differ diff --git a/boot/ocamldep b/boot/ocamldep index 106160ccc621..8c4e5de6e1d2 100755 Binary files a/boot/ocamldep and b/boot/ocamldep differ diff --git a/boot/ocamllex b/boot/ocamllex index 15437fdb04ec..0685966d21c1 100755 Binary files a/boot/ocamllex and b/boot/ocamllex differ diff --git a/parsing/longident.ml b/parsing/longident.ml index 57652ea1af64..1b459ca3f4d2 100644 --- a/parsing/longident.ml +++ b/parsing/longident.ml @@ -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 diff --git a/parsing/longident.mli b/parsing/longident.mli index 7b4e943bff33..4568bc953cdb 100644 --- a/parsing/longident.mli +++ b/parsing/longident.mli @@ -20,4 +20,5 @@ type t = | Lapply of t * t val flatten: t -> string list +val last: t -> string val parse: string -> t diff --git a/parsing/parser.mly b/parsing/parser.mly index 0170453c34d4..b229fa1a4cec 100644 --- a/parsing/parser.mly +++ b/parsing/parser.mly @@ -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 */ @@ -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 @@ -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 */ diff --git a/parsing/parsetree.mli b/parsing/parsetree.mli index 92996b391c61..8676fda5f791 100644 --- a/parsing/parsetree.mli +++ b/parsing/parsetree.mli @@ -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;