summaryrefslogtreecommitdiffstats
path: root/camlp4/ocaml_src/meta
diff options
context:
space:
mode:
authorMichel Mauny <Michel.Mauny@ensta.fr>2005-05-31 17:05:15 +0000
committerMichel Mauny <Michel.Mauny@ensta.fr>2005-05-31 17:05:15 +0000
commitda63a5ca3add6f776aebc32b61cc5595585b01c7 (patch)
tree0fd4811f4b2fc6ce2274c828c4eeb57a62f6d0fa /camlp4/ocaml_src/meta
parent4803624ae5e5e03960ebb36127995e300932c67a (diff)
Fixed bug #3642 (trace M.N.P.q)
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@6898 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'camlp4/ocaml_src/meta')
-rw-r--r--camlp4/ocaml_src/meta/pa_r.ml27
1 files changed, 15 insertions, 12 deletions
diff --git a/camlp4/ocaml_src/meta/pa_r.ml b/camlp4/ocaml_src/meta/pa_r.ml
index 2fa43b727..46bd68581 100644
--- a/camlp4/ocaml_src/meta/pa_r.ml
+++ b/camlp4/ocaml_src/meta/pa_r.ml
@@ -136,13 +136,16 @@ let mklistpat _loc last =
loop true
;;
-let mkexprident _loc i j =
- let rec loop m =
- function
- MLast.ExAcc (_, x, y) -> loop (MLast.ExAcc (_loc, m, x)) y
- | e -> MLast.ExAcc (_loc, m, e)
- in
- loop (MLast.ExUid (_loc, i)) j
+let mkexprident _loc ids =
+ match ids with
+ [] -> Stdpp.raise_with_loc _loc (Stream.Error "illegal long identifier")
+ | id :: ids ->
+ let rec loop m =
+ function
+ id :: ids -> loop (MLast.ExAcc (_loc, m, id)) ids
+ | [] -> m
+ in
+ loop id ids
;;
let mkassert _loc e =
@@ -1207,8 +1210,8 @@ Grammar.extend
[Gramext.Snterm
(Grammar.Entry.obj (expr_ident : 'expr_ident Grammar.Entry.e))],
Gramext.action
- (fun (i : 'expr_ident) (_loc : Lexing.position * Lexing.position) ->
- (i : 'expr));
+ (fun (ids : 'expr_ident) (_loc : Lexing.position * Lexing.position) ->
+ (mkexprident _loc ids : 'expr));
[Gramext.Stoken ("CHAR", "")],
Gramext.action
(fun (s : string) (_loc : Lexing.position * Lexing.position) ->
@@ -1373,15 +1376,15 @@ Grammar.extend
Gramext.action
(fun (j : 'expr_ident) _ (i : string)
(_loc : Lexing.position * Lexing.position) ->
- (mkexprident _loc i j : 'expr_ident));
+ (MLast.ExUid (_loc, i) :: j : 'expr_ident));
[Gramext.Stoken ("UIDENT", "")],
Gramext.action
(fun (i : string) (_loc : Lexing.position * Lexing.position) ->
- (MLast.ExUid (_loc, i) : 'expr_ident));
+ ([MLast.ExUid (_loc, i)] : 'expr_ident));
[Gramext.Stoken ("LIDENT", "")],
Gramext.action
(fun (i : string) (_loc : Lexing.position * Lexing.position) ->
- (MLast.ExLid (_loc, i) : 'expr_ident))]];
+ ([MLast.ExLid (_loc, i)] : 'expr_ident))]];
Grammar.Entry.obj (fun_def : 'fun_def Grammar.Entry.e), None,
[None, Some Gramext.RightA,
[[Gramext.Stoken ("", "->");