summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorNicolas Pouillard <np@nicolaspouillard.fr>2007-12-18 08:59:11 +0000
committerNicolas Pouillard <np@nicolaspouillard.fr>2007-12-18 08:59:11 +0000
commitf8841fe8c18bc08c6ff6e3e94e0b9ae913e7e300 (patch)
treecbd5fffe90fbde56f72d2265f354eeb37626b220
parent653f2273b8cd03d5d7d05519e64a1ef9f3922d97 (diff)
camlp4,cleanup: Remove some dead code in Camlp4GrammarParser.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@8718 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--camlp4/Camlp4Parsers/Camlp4GrammarParser.ml8
1 files changed, 5 insertions, 3 deletions
diff --git a/camlp4/Camlp4Parsers/Camlp4GrammarParser.ml b/camlp4/Camlp4Parsers/Camlp4GrammarParser.ml
index e00b72da2..4098e8274 100644
--- a/camlp4/Camlp4Parsers/Camlp4GrammarParser.ml
+++ b/camlp4/Camlp4Parsers/Camlp4GrammarParser.ml
@@ -52,7 +52,6 @@ module Make (Syntax : Sig.Camlp4Syntax) = struct
| STself of loc and string
| STtok of loc
| STstring_tok of loc
- | STany of loc
| STtyp of Ast.ctyp ]
;
@@ -167,7 +166,7 @@ module Make (Syntax : Sig.Camlp4Syntax) = struct
try
List.map
(fun
- (* ...; [ "foo" ]; ... ==> ...; (x = [ "foo" ] -> Token.extract_string x); ... *)
+ (* ...; [ "foo" ]; ... ==> ...; (x = [ "foo" ] -> Gram.Token.extract_string x); ... *)
[ {prod = [({pattern = None; styp = STtok _} as s)]; action = None} ->
{prod = [{ (s) with pattern = Some <:patt< x >> }];
action = Some <:expr< Token.extract_string x >>}
@@ -223,7 +222,6 @@ module Make (Syntax : Sig.Camlp4Syntax) = struct
Loc.raise _loc
(Stream.Error ("'" ^ x ^ "' illegal in anonymous entry level"))
else <:ctyp< '$tvar$ >>
- | STany _loc -> <:ctyp< _ >>
| STtok _loc -> <:ctyp< $uid:gm$.Token.t >>
| STstring_tok _loc -> <:ctyp< string >>
| STtyp t -> t ]
@@ -395,6 +393,7 @@ module Make (Syntax : Sig.Camlp4Syntax) = struct
TXlist loc min symb sep
;
+ (*
value sstoken _loc s =
let n = mk_name _loc <:ident< $lid:"a_" ^ s$ >> in
TXnterm _loc n None
@@ -471,6 +470,7 @@ module Make (Syntax : Sig.Camlp4Syntax) = struct
let styp = STquo _loc "a_opt" in
{used = used; text = text; styp = styp; pattern = None}
;
+ *)
value text_of_entry _loc e =
let ent =
@@ -829,6 +829,7 @@ module Make (Syntax : Sig.Camlp4Syntax) = struct
END;
+ (*
EXTEND Gram
symbol: LEVEL "top"
[ NONA
@@ -839,6 +840,7 @@ module Make (Syntax : Sig.Camlp4Syntax) = struct
ssopt _loc s ] ]
;
END;
+ *)
value sfold _loc n foldfun f e s =
let styp = STquo _loc (new_type_var ()) in