summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorPierre Weis <Pierre.Weis@inria.fr>2004-06-14 21:29:05 +0000
committerPierre Weis <Pierre.Weis@inria.fr>2004-06-14 21:29:05 +0000
commite0122726af55d8c81286b66a32adaee99e0573ae (patch)
tree3892c786c8966719e081417839b0f20a98d19c5b
parentfcb86d407d1edeace3a80b0a361ffd062ebd2450 (diff)
Implementation of an extension of record typing: the first path
annotated label in a record implies the implicit path annotations of the other labels. This way, a single annotation allows the simultaneous annotation of the whole set of labels. This is a conservative extension, since all the labels of a record must already belong to the same module. Hence, any program that was typable before, had this property and is thus still typable in the new scheme. This new treatment provides a simple way to desambiguate labels in mass, just adding a module path annotation on one of the field labels; this slight improvement of record typing thus avoids the burden of repeating Module.label for each label of the record. git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@6409 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--Changes4
-rw-r--r--stdlib/sys.ml2
-rw-r--r--typing/typecore.ml20
3 files changed, 23 insertions, 3 deletions
diff --git a/Changes b/Changes
index 296a38c41..2b0ef4eca 100644
--- a/Changes
+++ b/Changes
@@ -7,6 +7,10 @@ Language features:
- Support for immediate objects, i.e. objects defined without going
through a class. (Syntax is "object <field and methods> end".)
+Type-checking:
+- When typing records, the module path annotation of the first path
+ annotated label now stands for all of the labels of the record.
+
Both compilers:
- More compact compilation of classes.
- Much more efficient handling of class definitions inside functors
diff --git a/stdlib/sys.ml b/stdlib/sys.ml
index 2d68ad633..f9c256cb7 100644
--- a/stdlib/sys.ml
+++ b/stdlib/sys.ml
@@ -78,4 +78,4 @@ let catch_break on =
(* OCaml version string, must be in the format described in sys.mli. *)
-let ocaml_version = "3.07+20 (2004-06-14)";;
+let ocaml_version = "3.07+21 (2004-06-14)";;
diff --git a/typing/typecore.ml b/typing/typecore.ml
index 70a0ccf32..0c3ccc87b 100644
--- a/typing/typecore.ml
+++ b/typing/typecore.ml
@@ -335,6 +335,22 @@ let build_or_pat env loc lid =
pat pats in
rp { r with pat_loc = loc }
+let rec find_record_qual = function
+ | [] -> None
+ | (Longident.Ldot (modname, _), _) :: _ -> Some modname
+ | _ :: rest -> find_record_qual rest
+
+let type_label_a_list type_lid_a lid_a_list =
+ match find_record_qual lid_a_list with
+ | None -> List.map type_lid_a lid_a_list
+ | Some modname ->
+ List.map
+ (function
+ | (Longident.Lident id), sarg ->
+ type_lid_a (Longident.Ldot (modname, id), sarg)
+ | lid_a -> type_lid_a lid_a)
+ lid_a_list
+
let rec type_pat env sp =
match sp.ppat_desc with
Ppat_any ->
@@ -442,7 +458,7 @@ let rec type_pat env sp =
(label, arg)
in
rp {
- pat_desc = Tpat_record(List.map type_label_pat lid_sp_list);
+ pat_desc = Tpat_record(type_label_a_list type_label_pat lid_sp_list);
pat_loc = sp.ppat_loc;
pat_type = ty;
pat_env = env }
@@ -934,7 +950,7 @@ let rec type_exp env sexp =
if label.lbl_private = Private then
raise(Error(sexp.pexp_loc, Private_type ty));
(label, {arg with exp_type = instance arg.exp_type}) in
- let lbl_exp_list = List.map type_label_exp lid_sexp_list in
+ let lbl_exp_list = type_label_a_list type_label_exp lid_sexp_list in
let rec check_duplicates seen_pos lid_sexp lbl_exp =
match (lid_sexp, lbl_exp) with
((lid, _) :: rem1, (lbl, _) :: rem2) ->