summaryrefslogtreecommitdiffstats
path: root/parsing
diff options
context:
space:
mode:
authorAlain Frisch <alain@frisch.fr>2014-09-25 15:16:19 +0000
committerAlain Frisch <alain@frisch.fr>2014-09-25 15:16:19 +0000
commit5dac90505f84fa8ee66feedec91e3d6a6c4bb453 (patch)
tree4ae6d7bac8305427c3fad7e3fe0e04ad9aac222f /parsing
parent4aa48476d8ff931e2f83e6428071322c28a75aac (diff)
Allow qualified reference to constructors (at least in bang-types). A regular variant type supports qualified constructors of the form: M.t.X. An extensible variant type supports qualified constructors of the form: M.t.N.X.
git-svn-id: http://caml.inria.fr/svn/ocaml/branches/constructors_with_record3@15332 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'parsing')
-rw-r--r--parsing/longident.ml23
-rw-r--r--parsing/longident.mli2
-rw-r--r--parsing/parser.mly12
3 files changed, 36 insertions, 1 deletions
diff --git a/parsing/longident.ml b/parsing/longident.ml
index 706881af3..bb7778725 100644
--- a/parsing/longident.ml
+++ b/parsing/longident.ml
@@ -39,3 +39,26 @@ let parse s =
[] -> Lident "" (* should not happen, but don't put assert false
so as not to crash the toplevel (see Genprintval) *)
| hd :: tl -> List.fold_left (fun p s -> Ldot(p, s)) (Lident hd) tl
+
+
+
+let rec concat t = function
+ | Lident s -> Ldot (t, s)
+ | Ldot (a, s) -> Ldot (concat t a, s)
+ | _ -> assert false
+
+let is_lident s =
+ match s.[0] with
+ | 'a'..'z' | '_' -> true
+ | _ -> false
+
+let rec split_lident = function
+ | Ldot(t, s) when is_lident (last t) ->
+ Some (t, Lident s)
+ | Ldot(Ldot (t1, s1) as t, s) ->
+ begin match split_lident t with
+ | None -> None
+ | Some (x, y) -> Some (x, Ldot(y, s))
+ end
+ | _ ->
+ None
diff --git a/parsing/longident.mli b/parsing/longident.mli
index 9e7958550..132e46901 100644
--- a/parsing/longident.mli
+++ b/parsing/longident.mli
@@ -20,3 +20,5 @@ type t =
val flatten: t -> string list
val last: t -> string
val parse: string -> t
+val concat: t -> t -> t
+val split_lident: t -> (t * t) option
diff --git a/parsing/parser.mly b/parsing/parser.mly
index f723e5aeb..3da50bd15 100644
--- a/parsing/parser.mly
+++ b/parsing/parser.mly
@@ -1995,12 +1995,22 @@ val_longident:
| mod_longident DOT val_ident { Ldot($1, $3) }
;
constr_longident:
- mod_longident %prec below_DOT { $1 }
+ constr_longident2 %prec below_DOT { $1 }
| LBRACKET RBRACKET { Lident "[]" }
| LPAREN RPAREN { Lident "()" }
| FALSE { Lident "false" }
| TRUE { Lident "true" }
;
+constr_longident2:
+ mod_longident %prec below_DOT { $1 }
+ | mod_longident DOT LIDENT DOT mod_longident %prec below_DOT {
+ Longident.concat (Ldot($1, $3)) $5
+ }
+
+ | LIDENT DOT mod_longident %prec below_DOT {
+ Longident.concat (Lident $1) $3
+ }
+;
label_longident:
LIDENT { Lident $1 }
| mod_longident DOT LIDENT { Ldot($1, $3) }