summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--test/Lex/.cvsignore5
-rw-r--r--test/Lex/testmain.ml48
-rw-r--r--testsuite/tests/tool-lexyacc/Makefile9
-rw-r--r--testsuite/tests/tool-lexyacc/gram_aux.ml (renamed from test/Lex/gram_aux.ml)2
-rw-r--r--testsuite/tests/tool-lexyacc/grammar.mly (renamed from test/Lex/grammar.mly)2
-rw-r--r--testsuite/tests/tool-lexyacc/input (renamed from test/Lex/testscanner.mll)40
-rw-r--r--testsuite/tests/tool-lexyacc/input.ml312
-rw-r--r--testsuite/tests/tool-lexyacc/lexgen.ml (renamed from test/Lex/lexgen.ml)6
-rw-r--r--testsuite/tests/tool-lexyacc/main.ml (renamed from test/Lex/main.ml)5
-rw-r--r--testsuite/tests/tool-lexyacc/main.reference313
-rw-r--r--testsuite/tests/tool-lexyacc/output.ml (renamed from test/Lex/output.ml)8
-rw-r--r--testsuite/tests/tool-lexyacc/scan_aux.ml (renamed from test/Lex/scan_aux.ml)2
-rw-r--r--testsuite/tests/tool-lexyacc/scanner.mll (renamed from test/Lex/scanner.mll)2
-rw-r--r--testsuite/tests/tool-lexyacc/syntax.ml (renamed from test/Lex/syntax.ml)2
14 files changed, 668 insertions, 88 deletions
diff --git a/test/Lex/.cvsignore b/test/Lex/.cvsignore
deleted file mode 100644
index ed941f64f..000000000
--- a/test/Lex/.cvsignore
+++ /dev/null
@@ -1,5 +0,0 @@
-grammar.ml
-grammar.mli
-scanner.ml
-testscanner.ml
-grammar.output
diff --git a/test/Lex/testmain.ml b/test/Lex/testmain.ml
deleted file mode 100644
index 96d10a453..000000000
--- a/test/Lex/testmain.ml
+++ /dev/null
@@ -1,48 +0,0 @@
-(***********************************************************************)
-(* *)
-(* Objective Caml *)
-(* *)
-(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
-(* *)
-(* Copyright 1996 Institut National de Recherche en Informatique et *)
-(* en Automatique. All rights reserved. This file is distributed *)
-(* under the terms of the Q Public License version 1.0. *)
-(* *)
-(***********************************************************************)
-
-(* $Id$ *)
-
-(* The lexer generator. Command-line parsing. *)
-
-#open "syntax";;
-#open "testscanner";;
-#open "grammar";;
-#open "lexgen";;
-#open "output";;
-
-let main () =
- ic := stdin;
- oc := stdout;
- let lexbuf = lexing.from_channel ic in
- let (Lexdef(header,_) as def) =
- try
- grammar.lexer_definition testscanner.main lexbuf
- with
- parsing.Parse_error x ->
- prerr_string "Syntax error around char ";
- prerr_int (lexing.lexeme_start lexbuf);
- prerr_endline ".";
- sys.exit 2
- | scan_aux.Lexical_error s ->
- prerr_string "Lexical error around char ";
- prerr_int (lexing.lexeme_start lexbuf);
- prerr_string ": ";
- prerr_string s;
- prerr_endline ".";
- sys.exit 2 in
- let ((init, states, acts) as dfa) = make_dfa def in
- output_lexdef header dfa
-;;
-
-main(); sys.exit 0
-;;
diff --git a/testsuite/tests/tool-lexyacc/Makefile b/testsuite/tests/tool-lexyacc/Makefile
new file mode 100644
index 000000000..b9260a545
--- /dev/null
+++ b/testsuite/tests/tool-lexyacc/Makefile
@@ -0,0 +1,9 @@
+MODULES=syntax gram_aux grammar scan_aux scanner lexgen output
+MAIN_MODULE=main
+LEX_MODULES=scanner
+YACC_MODULES=grammar
+ADD_COMPFLAGS=-w a
+EXEC_ARGS=input
+
+include ../../makefiles/Makefile.one
+include ../../makefiles/Makefile.common
diff --git a/test/Lex/gram_aux.ml b/testsuite/tests/tool-lexyacc/gram_aux.ml
index b84d8588a..6b23b5ece 100644
--- a/test/Lex/gram_aux.ml
+++ b/testsuite/tests/tool-lexyacc/gram_aux.ml
@@ -10,7 +10,7 @@
(* *)
(***********************************************************************)
-(* $Id$ *)
+(* $Id: gram_aux.ml,v 1.4 1999/11/17 18:58:38 xleroy Exp $ *)
(* Auxiliaries for the parser. *)
diff --git a/test/Lex/grammar.mly b/testsuite/tests/tool-lexyacc/grammar.mly
index 8c1e4db94..ee5a8d240 100644
--- a/test/Lex/grammar.mly
+++ b/testsuite/tests/tool-lexyacc/grammar.mly
@@ -10,7 +10,7 @@
/* */
/***********************************************************************/
-/* $Id$ */
+/* $Id: grammar.mly,v 1.4 1999/11/17 18:58:38 xleroy Exp $ */
/* The grammar for lexer definitions */
diff --git a/test/Lex/testscanner.mll b/testsuite/tests/tool-lexyacc/input
index 3f1f0f34f..86114203f 100644
--- a/test/Lex/testscanner.mll
+++ b/testsuite/tests/tool-lexyacc/input
@@ -10,20 +10,18 @@
(* *)
(***********************************************************************)
-(* $Id$ *)
+(* $Id: scanner.mll,v 1.5 1999/11/17 18:58:39 xleroy Exp $ *)
(* The lexical analyzer for lexer definitions. *)
{
-#open "syntax";;
-#open "grammar";;
-#open "scan_aux";;
+open Syntax
+open Grammar
+open Scan_aux
}
rule main = parse
- _ * "qwertyuiopasdfghjklzxcvbnm0123456789!@#$%^&*()"
- { main lexbuf }
- | [' ' '\010' '\013' '\009' ] +
+ [' ' '\010' '\013' '\009' ] +
{ main lexbuf }
| "(*"
{ comment_depth := 1;
@@ -31,7 +29,7 @@ rule main = parse
main lexbuf }
| (['A'-'Z' 'a'-'z'] | '_' ['A'-'Z' 'a'-'z' '\'' '0'-'9'])
( '_' ? ['A'-'Z' 'a'-'z' ''' '0'-'9'] ) *
- { match lexing.lexeme lexbuf with
+ { match Lexing.lexeme lexbuf with
"rule" -> Trule
| "parse" -> Tparse
| "and" -> Tand
@@ -44,7 +42,7 @@ rule main = parse
| "'"
{ Tchar(char lexbuf) }
| '{'
- { let n1 = lexing.lexeme_end lexbuf in
+ { let n1 = Lexing.lexeme_end lexbuf in
brace_depth := 1;
let n2 = action lexbuf in
Taction(Location(n1, n2)) }
@@ -65,22 +63,22 @@ rule main = parse
| eof
{ raise(Lexical_error "unterminated lexer definition") }
| _
- { raise(Lexical_error("illegal character " ^ lexing.lexeme lexbuf)) }
+ { raise(Lexical_error("illegal character " ^ Lexing.lexeme lexbuf)) }
and action = parse
'{'
- { brace_depth := brace_depth + 1;
+ { incr brace_depth;
action lexbuf }
| '}'
- { brace_depth := brace_depth - 1;
- if brace_depth = 0 then lexing.lexeme_start lexbuf else action lexbuf }
+ { decr brace_depth;
+ if !brace_depth = 0 then Lexing.lexeme_start lexbuf else action lexbuf }
| '"'
{ reset_string_buffer();
string lexbuf;
reset_string_buffer();
action lexbuf }
| '\''
- { char lexbuf; action lexbuf }
+ { let _ = char lexbuf in action lexbuf }
| "(*"
{ comment_depth := 1;
comment lexbuf;
@@ -96,7 +94,7 @@ and string = parse
| '\\' [' ' '\010' '\013' '\009' '\026' '\012'] +
{ string lexbuf }
| '\\' ['\\' '"' 'n' 't' 'b' 'r']
- { store_string_char(char_for_backslash(lexing.lexeme_char lexbuf 1));
+ { store_string_char(char_for_backslash(Lexing.lexeme_char lexbuf 1));
string lexbuf }
| '\\' ['0'-'9'] ['0'-'9'] ['0'-'9']
{ store_string_char(char_for_decimal_code lexbuf 1);
@@ -104,14 +102,14 @@ and string = parse
| eof
{ raise(Lexical_error "unterminated string") }
| _
- { store_string_char(lexing.lexeme_char lexbuf 0);
+ { store_string_char(Lexing.lexeme_char lexbuf 0);
string lexbuf }
and char = parse
[^ '\\'] "'"
- { lexing.lexeme_char lexbuf 0 }
+ { Lexing.lexeme_char lexbuf 0 }
| '\\' ['\\' '\'' 'n' 't' 'b' 'r'] "'"
- { char_for_backslash (lexing.lexeme_char lexbuf 1) }
+ { char_for_backslash (Lexing.lexeme_char lexbuf 1) }
| '\\' ['0'-'9'] ['0'-'9'] ['0'-'9'] "'"
{ char_for_decimal_code lexbuf 1 }
| _
@@ -119,10 +117,10 @@ and char = parse
and comment = parse
"(*"
- { comment_depth := comment_depth + 1; comment lexbuf }
+ { incr comment_depth; comment lexbuf }
| "*)"
- { comment_depth := comment_depth - 1;
- if comment_depth = 0 then () else comment lexbuf }
+ { decr comment_depth;
+ if !comment_depth = 0 then () else comment lexbuf }
| '"'
{ reset_string_buffer();
string lexbuf;
diff --git a/testsuite/tests/tool-lexyacc/input.ml b/testsuite/tests/tool-lexyacc/input.ml
new file mode 100644
index 000000000..57d17c08d
--- /dev/null
+++ b/testsuite/tests/tool-lexyacc/input.ml
@@ -0,0 +1,312 @@
+
+open Syntax
+open Grammar
+open Scan_aux
+
+let rec action_43 lexbuf = (
+ comment lexbuf )
+and action_42 lexbuf = (
+ raise(Lexical_error "unterminated comment") )
+and action_41 lexbuf = (
+ reset_string_buffer();
+ string lexbuf;
+ reset_string_buffer();
+ comment lexbuf )
+and action_40 lexbuf = (
+ decr comment_depth;
+ if !comment_depth = 0 then () else comment lexbuf )
+and action_39 lexbuf = (
+ incr comment_depth; comment lexbuf )
+and action_38 lexbuf = (
+ raise(Lexical_error "bad character constant") )
+and action_37 lexbuf = (
+ char_for_decimal_code lexbuf 1 )
+and action_36 lexbuf = (
+ char_for_backslash (Lexing.lexeme_char lexbuf 1) )
+and action_35 lexbuf = (
+ Lexing.lexeme_char lexbuf 0 )
+and action_34 lexbuf = (
+ store_string_char(Lexing.lexeme_char lexbuf 0);
+ string lexbuf )
+and action_33 lexbuf = (
+ raise(Lexical_error "unterminated string") )
+and action_32 lexbuf = (
+ store_string_char(char_for_decimal_code lexbuf 1);
+ string lexbuf )
+and action_31 lexbuf = (
+ store_string_char(char_for_backslash(Lexing.lexeme_char lexbuf 1));
+ string lexbuf )
+and action_30 lexbuf = (
+ string lexbuf )
+and action_29 lexbuf = (
+ () )
+and action_28 lexbuf = (
+ action lexbuf )
+and action_27 lexbuf = (
+ raise (Lexical_error "unterminated action") )
+and action_26 lexbuf = (
+ comment_depth := 1;
+ comment lexbuf;
+ action lexbuf )
+and action_25 lexbuf = (
+ let _ = char lexbuf in action lexbuf )
+and action_24 lexbuf = (
+ reset_string_buffer();
+ string lexbuf;
+ reset_string_buffer();
+ action lexbuf )
+and action_23 lexbuf = (
+ decr brace_depth;
+ if !brace_depth = 0 then Lexing.lexeme_start lexbuf else action lexbuf )
+and action_22 lexbuf = (
+ incr brace_depth;
+ action lexbuf )
+and action_21 lexbuf = (
+ raise(Lexical_error("illegal character " ^ Lexing.lexeme lexbuf)) )
+and action_20 lexbuf = (
+ raise(Lexical_error "unterminated lexer definition") )
+and action_19 lexbuf = (
+ Tdash )
+and action_18 lexbuf = (
+ Tcaret )
+and action_17 lexbuf = (
+ Trparen )
+and action_16 lexbuf = (
+ Tlparen )
+and action_15 lexbuf = (
+ Tplus )
+and action_14 lexbuf = (
+ Tmaybe )
+and action_13 lexbuf = (
+ Tstar )
+and action_12 lexbuf = (
+ Trbracket )
+and action_11 lexbuf = (
+ Tlbracket )
+and action_10 lexbuf = (
+ Teof )
+and action_9 lexbuf = (
+ Tunderscore )
+and action_8 lexbuf = (
+ Tor )
+and action_7 lexbuf = (
+ Tend )
+and action_6 lexbuf = (
+ Tequal )
+and action_5 lexbuf = (
+ let n1 = Lexing.lexeme_end lexbuf in
+ brace_depth := 1;
+ let n2 = action lexbuf in
+ Taction(Location(n1, n2)) )
+and action_4 lexbuf = (
+ Tchar(char lexbuf) )
+and action_3 lexbuf = (
+ reset_string_buffer();
+ string lexbuf;
+ Tstring(get_stored_string()) )
+and action_2 lexbuf = (
+ match Lexing.lexeme lexbuf with
+ "rule" -> Trule
+ | "parse" -> Tparse
+ | "and" -> Tand
+ | "eof" -> Teof
+ | s -> Tident s )
+and action_1 lexbuf = (
+ comment_depth := 1;
+ comment lexbuf;
+ main lexbuf )
+and action_0 lexbuf = (
+ main lexbuf )
+and state_0 lexbuf =
+ match lexing.next_char lexbuf with
+ 'z'|'y'|'x'|'w'|'v'|'u'|'t'|'s'|'r'|'q'|'p'|'o'|'n'|'m'|'l'|'k'|'j'|'i'|'h'|'g'|'f'|'d'|'c'|'b'|'a'|'Z'|'Y'|'X'|'W'|'V'|'U'|'T'|'S'|'R'|'Q'|'P'|'O'|'N'|'M'|'L'|'K'|'J'|'I'|'H'|'G'|'F'|'E'|'D'|'C'|'B'|'A' -> state_51 lexbuf
+ | ' '|'\013'|'\n'|'\t' -> state_40 lexbuf
+ | '|' -> action_8 lexbuf
+ | '{' -> action_5 lexbuf
+ | 'e' -> state_56 lexbuf
+ | '_' -> state_55 lexbuf
+ | '^' -> action_18 lexbuf
+ | ']' -> action_12 lexbuf
+ | '[' -> action_11 lexbuf
+ | '?' -> action_14 lexbuf
+ | '=' -> action_6 lexbuf
+ | ';' -> state_48 lexbuf
+ | '-' -> action_19 lexbuf
+ | '+' -> action_15 lexbuf
+ | '*' -> action_13 lexbuf
+ | ')' -> action_17 lexbuf
+ | '(' -> state_43 lexbuf
+ | '\'' -> action_4 lexbuf
+ | '"' -> action_3 lexbuf
+ | '\000' -> action_20 lexbuf
+ | _ -> action_21 lexbuf
+and state_1 lexbuf =
+ match lexing.next_char lexbuf with
+ '}' -> action_23 lexbuf
+ | '{' -> action_22 lexbuf
+ | '(' -> state_34 lexbuf
+ | '\'' -> action_25 lexbuf
+ | '"' -> action_24 lexbuf
+ | '\000' -> action_27 lexbuf
+ | _ -> action_28 lexbuf
+and state_2 lexbuf =
+ match lexing.next_char lexbuf with
+ '\\' -> state_24 lexbuf
+ | '"' -> action_29 lexbuf
+ | '\000' -> action_33 lexbuf
+ | _ -> action_34 lexbuf
+and state_3 lexbuf =
+ match lexing.next_char lexbuf with
+ '\\' -> state_13 lexbuf
+ | '\000' -> lexing.backtrack lexbuf
+ | _ -> state_12 lexbuf
+and state_4 lexbuf =
+ match lexing.next_char lexbuf with
+ '*' -> state_9 lexbuf
+ | '(' -> state_8 lexbuf
+ | '"' -> action_41 lexbuf
+ | '\000' -> action_42 lexbuf
+ | _ -> action_43 lexbuf
+and state_8 lexbuf =
+ Lexing.set_backtrack lexbuf action_43;
+ match lexing.next_char lexbuf with
+ '*' -> action_39 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_9 lexbuf =
+ Lexing.set_backtrack lexbuf action_43;
+ match lexing.next_char lexbuf with
+ ')' -> action_40 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_12 lexbuf =
+ Lexing.set_backtrack lexbuf action_38;
+ match lexing.next_char lexbuf with
+ '\'' -> action_35 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_13 lexbuf =
+ Lexing.set_backtrack lexbuf action_38;
+ match lexing.next_char lexbuf with
+ '9'|'8'|'7'|'6'|'5'|'4'|'3'|'2'|'1'|'0' -> state_15 lexbuf
+ | 't'|'r'|'n'|'b'|'\\'|'\'' -> state_14 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_14 lexbuf =
+ match lexing.next_char lexbuf with
+ '\'' -> action_36 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_15 lexbuf =
+ match lexing.next_char lexbuf with
+ '9'|'8'|'7'|'6'|'5'|'4'|'3'|'2'|'1'|'0' -> state_16 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_16 lexbuf =
+ match lexing.next_char lexbuf with
+ '9'|'8'|'7'|'6'|'5'|'4'|'3'|'2'|'1'|'0' -> state_17 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_17 lexbuf =
+ match lexing.next_char lexbuf with
+ '\'' -> action_37 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_24 lexbuf =
+ Lexing.set_backtrack lexbuf action_34;
+ match lexing.next_char lexbuf with
+ '9'|'8'|'7'|'6'|'5'|'4'|'3'|'2'|'1'|'0' -> state_27 lexbuf
+ | 't'|'r'|'n'|'b'|'\\'|'"' -> action_31 lexbuf
+ | ' '|'\026'|'\013'|'\012'|'\n'|'\t' -> state_25 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_25 lexbuf =
+ Lexing.set_backtrack lexbuf action_30;
+ match lexing.next_char lexbuf with
+ ' '|'\026'|'\013'|'\012'|'\n'|'\t' -> state_25 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_27 lexbuf =
+ match lexing.next_char lexbuf with
+ '9'|'8'|'7'|'6'|'5'|'4'|'3'|'2'|'1'|'0' -> state_28 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_28 lexbuf =
+ match lexing.next_char lexbuf with
+ '9'|'8'|'7'|'6'|'5'|'4'|'3'|'2'|'1'|'0' -> action_32 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_34 lexbuf =
+ Lexing.set_backtrack lexbuf action_28;
+ match lexing.next_char lexbuf with
+ '*' -> action_26 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_40 lexbuf =
+ Lexing.set_backtrack lexbuf action_0;
+ match lexing.next_char lexbuf with
+ ' '|'\013'|'\n'|'\t' -> state_65 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_43 lexbuf =
+ Lexing.set_backtrack lexbuf action_16;
+ match lexing.next_char lexbuf with
+ '*' -> action_1 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_48 lexbuf =
+ Lexing.set_backtrack lexbuf action_21;
+ match lexing.next_char lexbuf with
+ ';' -> action_7 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_51 lexbuf =
+ Lexing.set_backtrack lexbuf action_2;
+ match lexing.next_char lexbuf with
+ 'z'|'y'|'x'|'w'|'v'|'u'|'t'|'s'|'r'|'q'|'p'|'o'|'n'|'m'|'l'|'k'|'j'|'i'|'h'|'g'|'f'|'e'|'d'|'c'|'b'|'a'|'Z'|'Y'|'X'|'W'|'V'|'U'|'T'|'S'|'R'|'Q'|'P'|'O'|'N'|'M'|'L'|'K'|'J'|'I'|'H'|'G'|'F'|'E'|'D'|'C'|'B'|'A'|'9'|'8'|'7'|'6'|'5'|'4'|'3'|'2'|'1'|'0'|'\'' -> state_59 lexbuf
+ | '_' -> state_60 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_55 lexbuf =
+ Lexing.set_backtrack lexbuf action_9;
+ match lexing.next_char lexbuf with
+ 'z'|'y'|'x'|'w'|'v'|'u'|'t'|'s'|'r'|'q'|'p'|'o'|'n'|'m'|'l'|'k'|'j'|'i'|'h'|'g'|'f'|'e'|'d'|'c'|'b'|'a'|'Z'|'Y'|'X'|'W'|'V'|'U'|'T'|'S'|'R'|'Q'|'P'|'O'|'N'|'M'|'L'|'K'|'J'|'I'|'H'|'G'|'F'|'E'|'D'|'C'|'B'|'A'|'9'|'8'|'7'|'6'|'5'|'4'|'3'|'2'|'1'|'0'|'\'' -> state_59 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_56 lexbuf =
+ Lexing.set_backtrack lexbuf action_2;
+ match lexing.next_char lexbuf with
+ 'z'|'y'|'x'|'w'|'v'|'u'|'t'|'s'|'r'|'q'|'p'|'n'|'m'|'l'|'k'|'j'|'i'|'h'|'g'|'f'|'e'|'d'|'c'|'b'|'a'|'Z'|'Y'|'X'|'W'|'V'|'U'|'T'|'S'|'R'|'Q'|'P'|'O'|'N'|'M'|'L'|'K'|'J'|'I'|'H'|'G'|'F'|'E'|'D'|'C'|'B'|'A'|'9'|'8'|'7'|'6'|'5'|'4'|'3'|'2'|'1'|'0'|'\'' -> state_59 lexbuf
+ | 'o' -> state_61 lexbuf
+ | '_' -> state_60 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_59 lexbuf =
+ Lexing.set_backtrack lexbuf action_2;
+ match lexing.next_char lexbuf with
+ 'z'|'y'|'x'|'w'|'v'|'u'|'t'|'s'|'r'|'q'|'p'|'o'|'n'|'m'|'l'|'k'|'j'|'i'|'h'|'g'|'f'|'e'|'d'|'c'|'b'|'a'|'Z'|'Y'|'X'|'W'|'V'|'U'|'T'|'S'|'R'|'Q'|'P'|'O'|'N'|'M'|'L'|'K'|'J'|'I'|'H'|'G'|'F'|'E'|'D'|'C'|'B'|'A'|'9'|'8'|'7'|'6'|'5'|'4'|'3'|'2'|'1'|'0'|'\'' -> state_59 lexbuf
+ | '_' -> state_60 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_60 lexbuf =
+ match lexing.next_char lexbuf with
+ 'z'|'y'|'x'|'w'|'v'|'u'|'t'|'s'|'r'|'q'|'p'|'o'|'n'|'m'|'l'|'k'|'j'|'i'|'h'|'g'|'f'|'e'|'d'|'c'|'b'|'a'|'Z'|'Y'|'X'|'W'|'V'|'U'|'T'|'S'|'R'|'Q'|'P'|'O'|'N'|'M'|'L'|'K'|'J'|'I'|'H'|'G'|'F'|'E'|'D'|'C'|'B'|'A'|'9'|'8'|'7'|'6'|'5'|'4'|'3'|'2'|'1'|'0'|'\'' -> state_59 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_61 lexbuf =
+ Lexing.set_backtrack lexbuf action_2;
+ match lexing.next_char lexbuf with
+ 'z'|'y'|'x'|'w'|'v'|'u'|'t'|'s'|'r'|'q'|'p'|'o'|'n'|'m'|'l'|'k'|'j'|'i'|'h'|'g'|'e'|'d'|'c'|'b'|'a'|'Z'|'Y'|'X'|'W'|'V'|'U'|'T'|'S'|'R'|'Q'|'P'|'O'|'N'|'M'|'L'|'K'|'J'|'I'|'H'|'G'|'F'|'E'|'D'|'C'|'B'|'A'|'9'|'8'|'7'|'6'|'5'|'4'|'3'|'2'|'1'|'0'|'\'' -> state_59 lexbuf
+ | 'f' -> state_62 lexbuf
+ | '_' -> state_60 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_62 lexbuf =
+ Lexing.set_backtrack lexbuf action_2;
+ match lexing.next_char lexbuf with
+ 'z'|'y'|'x'|'w'|'v'|'u'|'t'|'s'|'r'|'q'|'p'|'o'|'n'|'m'|'l'|'k'|'j'|'i'|'h'|'g'|'f'|'e'|'d'|'c'|'b'|'a'|'Z'|'Y'|'X'|'W'|'V'|'U'|'T'|'S'|'R'|'Q'|'P'|'O'|'N'|'M'|'L'|'K'|'J'|'I'|'H'|'G'|'F'|'E'|'D'|'C'|'B'|'A'|'9'|'8'|'7'|'6'|'5'|'4'|'3'|'2'|'1'|'0'|'\'' -> state_59 lexbuf
+ | '_' -> state_60 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_65 lexbuf =
+ Lexing.set_backtrack lexbuf action_0;
+ match lexing.next_char lexbuf with
+ ' '|'\013'|'\n'|'\t' -> state_65 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and main lexbuf =
+ Lexing.init lexbuf;
+ state_0 lexbuf
+
+and action lexbuf =
+ Lexing.init lexbuf;
+ state_1 lexbuf
+
+and string lexbuf =
+ Lexing.init lexbuf;
+ state_2 lexbuf
+
+and char lexbuf =
+ Lexing.init lexbuf;
+ state_3 lexbuf
+
+and comment lexbuf =
+ Lexing.init lexbuf;
+ state_4 lexbuf
+
diff --git a/test/Lex/lexgen.ml b/testsuite/tests/tool-lexyacc/lexgen.ml
index 42ff47c57..05cb3c033 100644
--- a/test/Lex/lexgen.ml
+++ b/testsuite/tests/tool-lexyacc/lexgen.ml
@@ -10,7 +10,7 @@
(* *)
(***********************************************************************)
-(* $Id$ *)
+(* $Id: lexgen.ml,v 1.5 2000/12/28 13:06:39 weis Exp $ *)
(* Compiling a lexer definition *)
@@ -128,9 +128,9 @@ let rec merge_trans l1 l2 =
if n1 = n2 then t1 :: merge_trans r1 r2 else
if n1 < n2 then t1 :: merge_trans r1 s2 else
t2 :: merge_trans s1 r2
- | ((OnChars n1 as t1) :: r1 as s1), ((ToAction n2 as t2) :: r2 as s2) ->
+ | ((OnChars n1 as t1) :: r1), ((ToAction n2) :: r2 as s2) ->
t1 :: merge_trans r1 s2
- | ((ToAction n1 as t1) :: r1 as s1), ((OnChars n2 as t2) :: r2 as s2) ->
+ | ((ToAction n1) :: r1 as s1), ((OnChars n2 as t2) :: r2) ->
t2 :: merge_trans s1 r2
diff --git a/test/Lex/main.ml b/testsuite/tests/tool-lexyacc/main.ml
index 6382401e2..1dd130b93 100644
--- a/test/Lex/main.ml
+++ b/testsuite/tests/tool-lexyacc/main.ml
@@ -10,7 +10,7 @@
(* *)
(***********************************************************************)
-(* $Id$ *)
+(* $Id: main.ml,v 1.4 1999/11/17 18:58:39 xleroy Exp $ *)
(* The lexer generator. Command-line parsing. *)
@@ -32,7 +32,8 @@ let main () =
else
source_name ^ ".ml" in
ic := open_in source_name;
- oc := open_out dest_name;
+(* oc := open_out dest_name; *) ignore dest_name;
+ oc := stdout;
let lexbuf = Lexing.from_channel !ic in
let (Lexdef(header,_) as def) =
try
diff --git a/testsuite/tests/tool-lexyacc/main.reference b/testsuite/tests/tool-lexyacc/main.reference
new file mode 100644
index 000000000..7711833a4
--- /dev/null
+++ b/testsuite/tests/tool-lexyacc/main.reference
@@ -0,0 +1,313 @@
+66 states, 44 actions.
+
+open Syntax
+open Grammar
+open Scan_aux
+
+let rec action_43 lexbuf = (
+ comment lexbuf )
+and action_42 lexbuf = (
+ raise(Lexical_error "unterminated comment") )
+and action_41 lexbuf = (
+ reset_string_buffer();
+ string lexbuf;
+ reset_string_buffer();
+ comment lexbuf )
+and action_40 lexbuf = (
+ decr comment_depth;
+ if !comment_depth = 0 then () else comment lexbuf )
+and action_39 lexbuf = (
+ incr comment_depth; comment lexbuf )
+and action_38 lexbuf = (
+ raise(Lexical_error "bad character constant") )
+and action_37 lexbuf = (
+ char_for_decimal_code lexbuf 1 )
+and action_36 lexbuf = (
+ char_for_backslash (Lexing.lexeme_char lexbuf 1) )
+and action_35 lexbuf = (
+ Lexing.lexeme_char lexbuf 0 )
+and action_34 lexbuf = (
+ store_string_char(Lexing.lexeme_char lexbuf 0);
+ string lexbuf )
+and action_33 lexbuf = (
+ raise(Lexical_error "unterminated string") )
+and action_32 lexbuf = (
+ store_string_char(char_for_decimal_code lexbuf 1);
+ string lexbuf )
+and action_31 lexbuf = (
+ store_string_char(char_for_backslash(Lexing.lexeme_char lexbuf 1));
+ string lexbuf )
+and action_30 lexbuf = (
+ string lexbuf )
+and action_29 lexbuf = (
+ () )
+and action_28 lexbuf = (
+ action lexbuf )
+and action_27 lexbuf = (
+ raise (Lexical_error "unterminated action") )
+and action_26 lexbuf = (
+ comment_depth := 1;
+ comment lexbuf;
+ action lexbuf )
+and action_25 lexbuf = (
+ let _ = char lexbuf in action lexbuf )
+and action_24 lexbuf = (
+ reset_string_buffer();
+ string lexbuf;
+ reset_string_buffer();
+ action lexbuf )
+and action_23 lexbuf = (
+ decr brace_depth;
+ if !brace_depth = 0 then Lexing.lexeme_start lexbuf else action lexbuf )
+and action_22 lexbuf = (
+ incr brace_depth;
+ action lexbuf )
+and action_21 lexbuf = (
+ raise(Lexical_error("illegal character " ^ Lexing.lexeme lexbuf)) )
+and action_20 lexbuf = (
+ raise(Lexical_error "unterminated lexer definition") )
+and action_19 lexbuf = (
+ Tdash )
+and action_18 lexbuf = (
+ Tcaret )
+and action_17 lexbuf = (
+ Trparen )
+and action_16 lexbuf = (
+ Tlparen )
+and action_15 lexbuf = (
+ Tplus )
+and action_14 lexbuf = (
+ Tmaybe )
+and action_13 lexbuf = (
+ Tstar )
+and action_12 lexbuf = (
+ Trbracket )
+and action_11 lexbuf = (
+ Tlbracket )
+and action_10 lexbuf = (
+ Teof )
+and action_9 lexbuf = (
+ Tunderscore )
+and action_8 lexbuf = (
+ Tor )
+and action_7 lexbuf = (
+ Tend )
+and action_6 lexbuf = (
+ Tequal )
+and action_5 lexbuf = (
+ let n1 = Lexing.lexeme_end lexbuf in
+ brace_depth := 1;
+ let n2 = action lexbuf in
+ Taction(Location(n1, n2)) )
+and action_4 lexbuf = (
+ Tchar(char lexbuf) )
+and action_3 lexbuf = (
+ reset_string_buffer();
+ string lexbuf;
+ Tstring(get_stored_string()) )
+and action_2 lexbuf = (
+ match Lexing.lexeme lexbuf with
+ "rule" -> Trule
+ | "parse" -> Tparse
+ | "and" -> Tand
+ | "eof" -> Teof
+ | s -> Tident s )
+and action_1 lexbuf = (
+ comment_depth := 1;
+ comment lexbuf;
+ main lexbuf )
+and action_0 lexbuf = (
+ main lexbuf )
+and state_0 lexbuf =
+ match lexing.next_char lexbuf with
+ 'z'|'y'|'x'|'w'|'v'|'u'|'t'|'s'|'r'|'q'|'p'|'o'|'n'|'m'|'l'|'k'|'j'|'i'|'h'|'g'|'f'|'d'|'c'|'b'|'a'|'Z'|'Y'|'X'|'W'|'V'|'U'|'T'|'S'|'R'|'Q'|'P'|'O'|'N'|'M'|'L'|'K'|'J'|'I'|'H'|'G'|'F'|'E'|'D'|'C'|'B'|'A' -> state_51 lexbuf
+ | ' '|'\013'|'\n'|'\t' -> state_40 lexbuf
+ | '|' -> action_8 lexbuf
+ | '{' -> action_5 lexbuf
+ | 'e' -> state_56 lexbuf
+ | '_' -> state_55 lexbuf
+ | '^' -> action_18 lexbuf
+ | ']' -> action_12 lexbuf
+ | '[' -> action_11 lexbuf
+ | '?' -> action_14 lexbuf
+ | '=' -> action_6 lexbuf
+ | ';' -> state_48 lexbuf
+ | '-' -> action_19 lexbuf
+ | '+' -> action_15 lexbuf
+ | '*' -> action_13 lexbuf
+ | ')' -> action_17 lexbuf
+ | '(' -> state_43 lexbuf
+ | '\'' -> action_4 lexbuf
+ | '"' -> action_3 lexbuf
+ | '\000' -> action_20 lexbuf
+ | _ -> action_21 lexbuf
+and state_1 lexbuf =
+ match lexing.next_char lexbuf with
+ '}' -> action_23 lexbuf
+ | '{' -> action_22 lexbuf
+ | '(' -> state_34 lexbuf
+ | '\'' -> action_25 lexbuf
+ | '"' -> action_24 lexbuf
+ | '\000' -> action_27 lexbuf
+ | _ -> action_28 lexbuf
+and state_2 lexbuf =
+ match lexing.next_char lexbuf with
+ '\\' -> state_24 lexbuf
+ | '"' -> action_29 lexbuf
+ | '\000' -> action_33 lexbuf
+ | _ -> action_34 lexbuf
+and state_3 lexbuf =
+ match lexing.next_char lexbuf with
+ '\\' -> state_13 lexbuf
+ | '\000' -> lexing.backtrack lexbuf
+ | _ -> state_12 lexbuf
+and state_4 lexbuf =
+ match lexing.next_char lexbuf with
+ '*' -> state_9 lexbuf
+ | '(' -> state_8 lexbuf
+ | '"' -> action_41 lexbuf
+ | '\000' -> action_42 lexbuf
+ | _ -> action_43 lexbuf
+and state_8 lexbuf =
+ Lexing.set_backtrack lexbuf action_43;
+ match lexing.next_char lexbuf with
+ '*' -> action_39 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_9 lexbuf =
+ Lexing.set_backtrack lexbuf action_43;
+ match lexing.next_char lexbuf with
+ ')' -> action_40 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_12 lexbuf =
+ Lexing.set_backtrack lexbuf action_38;
+ match lexing.next_char lexbuf with
+ '\'' -> action_35 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_13 lexbuf =
+ Lexing.set_backtrack lexbuf action_38;
+ match lexing.next_char lexbuf with
+ '9'|'8'|'7'|'6'|'5'|'4'|'3'|'2'|'1'|'0' -> state_15 lexbuf
+ | 't'|'r'|'n'|'b'|'\\'|'\'' -> state_14 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_14 lexbuf =
+ match lexing.next_char lexbuf with
+ '\'' -> action_36 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_15 lexbuf =
+ match lexing.next_char lexbuf with
+ '9'|'8'|'7'|'6'|'5'|'4'|'3'|'2'|'1'|'0' -> state_16 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_16 lexbuf =
+ match lexing.next_char lexbuf with
+ '9'|'8'|'7'|'6'|'5'|'4'|'3'|'2'|'1'|'0' -> state_17 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_17 lexbuf =
+ match lexing.next_char lexbuf with
+ '\'' -> action_37 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_24 lexbuf =
+ Lexing.set_backtrack lexbuf action_34;
+ match lexing.next_char lexbuf with
+ '9'|'8'|'7'|'6'|'5'|'4'|'3'|'2'|'1'|'0' -> state_27 lexbuf
+ | 't'|'r'|'n'|'b'|'\\'|'"' -> action_31 lexbuf
+ | ' '|'\026'|'\013'|'\012'|'\n'|'\t' -> state_25 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_25 lexbuf =
+ Lexing.set_backtrack lexbuf action_30;
+ match lexing.next_char lexbuf with
+ ' '|'\026'|'\013'|'\012'|'\n'|'\t' -> state_25 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_27 lexbuf =
+ match lexing.next_char lexbuf with
+ '9'|'8'|'7'|'6'|'5'|'4'|'3'|'2'|'1'|'0' -> state_28 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_28 lexbuf =
+ match lexing.next_char lexbuf with
+ '9'|'8'|'7'|'6'|'5'|'4'|'3'|'2'|'1'|'0' -> action_32 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_34 lexbuf =
+ Lexing.set_backtrack lexbuf action_28;
+ match lexing.next_char lexbuf with
+ '*' -> action_26 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_40 lexbuf =
+ Lexing.set_backtrack lexbuf action_0;
+ match lexing.next_char lexbuf with
+ ' '|'\013'|'\n'|'\t' -> state_65 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_43 lexbuf =
+ Lexing.set_backtrack lexbuf action_16;
+ match lexing.next_char lexbuf with
+ '*' -> action_1 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_48 lexbuf =
+ Lexing.set_backtrack lexbuf action_21;
+ match lexing.next_char lexbuf with
+ ';' -> action_7 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_51 lexbuf =
+ Lexing.set_backtrack lexbuf action_2;
+ match lexing.next_char lexbuf with
+ 'z'|'y'|'x'|'w'|'v'|'u'|'t'|'s'|'r'|'q'|'p'|'o'|'n'|'m'|'l'|'k'|'j'|'i'|'h'|'g'|'f'|'e'|'d'|'c'|'b'|'a'|'Z'|'Y'|'X'|'W'|'V'|'U'|'T'|'S'|'R'|'Q'|'P'|'O'|'N'|'M'|'L'|'K'|'J'|'I'|'H'|'G'|'F'|'E'|'D'|'C'|'B'|'A'|'9'|'8'|'7'|'6'|'5'|'4'|'3'|'2'|'1'|'0'|'\'' -> state_59 lexbuf
+ | '_' -> state_60 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_55 lexbuf =
+ Lexing.set_backtrack lexbuf action_9;
+ match lexing.next_char lexbuf with
+ 'z'|'y'|'x'|'w'|'v'|'u'|'t'|'s'|'r'|'q'|'p'|'o'|'n'|'m'|'l'|'k'|'j'|'i'|'h'|'g'|'f'|'e'|'d'|'c'|'b'|'a'|'Z'|'Y'|'X'|'W'|'V'|'U'|'T'|'S'|'R'|'Q'|'P'|'O'|'N'|'M'|'L'|'K'|'J'|'I'|'H'|'G'|'F'|'E'|'D'|'C'|'B'|'A'|'9'|'8'|'7'|'6'|'5'|'4'|'3'|'2'|'1'|'0'|'\'' -> state_59 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_56 lexbuf =
+ Lexing.set_backtrack lexbuf action_2;
+ match lexing.next_char lexbuf with
+ 'z'|'y'|'x'|'w'|'v'|'u'|'t'|'s'|'r'|'q'|'p'|'n'|'m'|'l'|'k'|'j'|'i'|'h'|'g'|'f'|'e'|'d'|'c'|'b'|'a'|'Z'|'Y'|'X'|'W'|'V'|'U'|'T'|'S'|'R'|'Q'|'P'|'O'|'N'|'M'|'L'|'K'|'J'|'I'|'H'|'G'|'F'|'E'|'D'|'C'|'B'|'A'|'9'|'8'|'7'|'6'|'5'|'4'|'3'|'2'|'1'|'0'|'\'' -> state_59 lexbuf
+ | 'o' -> state_61 lexbuf
+ | '_' -> state_60 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_59 lexbuf =
+ Lexing.set_backtrack lexbuf action_2;
+ match lexing.next_char lexbuf with
+ 'z'|'y'|'x'|'w'|'v'|'u'|'t'|'s'|'r'|'q'|'p'|'o'|'n'|'m'|'l'|'k'|'j'|'i'|'h'|'g'|'f'|'e'|'d'|'c'|'b'|'a'|'Z'|'Y'|'X'|'W'|'V'|'U'|'T'|'S'|'R'|'Q'|'P'|'O'|'N'|'M'|'L'|'K'|'J'|'I'|'H'|'G'|'F'|'E'|'D'|'C'|'B'|'A'|'9'|'8'|'7'|'6'|'5'|'4'|'3'|'2'|'1'|'0'|'\'' -> state_59 lexbuf
+ | '_' -> state_60 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_60 lexbuf =
+ match lexing.next_char lexbuf with
+ 'z'|'y'|'x'|'w'|'v'|'u'|'t'|'s'|'r'|'q'|'p'|'o'|'n'|'m'|'l'|'k'|'j'|'i'|'h'|'g'|'f'|'e'|'d'|'c'|'b'|'a'|'Z'|'Y'|'X'|'W'|'V'|'U'|'T'|'S'|'R'|'Q'|'P'|'O'|'N'|'M'|'L'|'K'|'J'|'I'|'H'|'G'|'F'|'E'|'D'|'C'|'B'|'A'|'9'|'8'|'7'|'6'|'5'|'4'|'3'|'2'|'1'|'0'|'\'' -> state_59 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_61 lexbuf =
+ Lexing.set_backtrack lexbuf action_2;
+ match lexing.next_char lexbuf with
+ 'z'|'y'|'x'|'w'|'v'|'u'|'t'|'s'|'r'|'q'|'p'|'o'|'n'|'m'|'l'|'k'|'j'|'i'|'h'|'g'|'e'|'d'|'c'|'b'|'a'|'Z'|'Y'|'X'|'W'|'V'|'U'|'T'|'S'|'R'|'Q'|'P'|'O'|'N'|'M'|'L'|'K'|'J'|'I'|'H'|'G'|'F'|'E'|'D'|'C'|'B'|'A'|'9'|'8'|'7'|'6'|'5'|'4'|'3'|'2'|'1'|'0'|'\'' -> state_59 lexbuf
+ | 'f' -> state_62 lexbuf
+ | '_' -> state_60 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_62 lexbuf =
+ Lexing.set_backtrack lexbuf action_2;
+ match lexing.next_char lexbuf with
+ 'z'|'y'|'x'|'w'|'v'|'u'|'t'|'s'|'r'|'q'|'p'|'o'|'n'|'m'|'l'|'k'|'j'|'i'|'h'|'g'|'f'|'e'|'d'|'c'|'b'|'a'|'Z'|'Y'|'X'|'W'|'V'|'U'|'T'|'S'|'R'|'Q'|'P'|'O'|'N'|'M'|'L'|'K'|'J'|'I'|'H'|'G'|'F'|'E'|'D'|'C'|'B'|'A'|'9'|'8'|'7'|'6'|'5'|'4'|'3'|'2'|'1'|'0'|'\'' -> state_59 lexbuf
+ | '_' -> state_60 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and state_65 lexbuf =
+ Lexing.set_backtrack lexbuf action_0;
+ match lexing.next_char lexbuf with
+ ' '|'\013'|'\n'|'\t' -> state_65 lexbuf
+ | _ -> lexing.backtrack lexbuf
+and main lexbuf =
+ Lexing.init lexbuf;
+ state_0 lexbuf
+
+and action lexbuf =
+ Lexing.init lexbuf;
+ state_1 lexbuf
+
+and string lexbuf =
+ Lexing.init lexbuf;
+ state_2 lexbuf
+
+and char lexbuf =
+ Lexing.init lexbuf;
+ state_3 lexbuf
+
+and comment lexbuf =
+ Lexing.init lexbuf;
+ state_4 lexbuf
+
diff --git a/test/Lex/output.ml b/testsuite/tests/tool-lexyacc/output.ml
index 97d757771..6c5614089 100644
--- a/test/Lex/output.ml
+++ b/testsuite/tests/tool-lexyacc/output.ml
@@ -10,7 +10,7 @@
(* *)
(***********************************************************************)
-(* $Id$ *)
+(* $Id: output.ml,v 1.5 2000/12/28 13:06:41 weis Exp $ *)
(* Generating a DFA as a set of mutually recursive functions *)
@@ -153,9 +153,9 @@ let rec output_entries = function
(* All together *)
let output_lexdef header (initial_st, st, actions) =
- prerr_int (Array.length st); prerr_string " states, ";
- prerr_int (List.length actions); prerr_string " actions.";
- prerr_newline();
+ print_int (Array.length st); print_string " states, ";
+ print_int (List.length actions); print_string " actions.";
+ print_newline();
copy_chunk header;
output_string !oc "\nlet rec ";
states := st;
diff --git a/test/Lex/scan_aux.ml b/testsuite/tests/tool-lexyacc/scan_aux.ml
index c449b13a5..172d6f41e 100644
--- a/test/Lex/scan_aux.ml
+++ b/testsuite/tests/tool-lexyacc/scan_aux.ml
@@ -10,7 +10,7 @@
(* *)
(***********************************************************************)
-(* $Id$ *)
+(* $Id: scan_aux.ml,v 1.4 1999/11/17 18:58:39 xleroy Exp $ *)
(* Auxiliaries for the lexical analyzer *)
diff --git a/test/Lex/scanner.mll b/testsuite/tests/tool-lexyacc/scanner.mll
index 131272fdd..c7d74b018 100644
--- a/test/Lex/scanner.mll
+++ b/testsuite/tests/tool-lexyacc/scanner.mll
@@ -10,7 +10,7 @@
(* *)
(***********************************************************************)
-(* $Id$ *)
+(* $Id: scanner.mll,v 1.5 1999/11/17 18:58:39 xleroy Exp $ *)
(* The lexical analyzer for lexer definitions. *)
diff --git a/test/Lex/syntax.ml b/testsuite/tests/tool-lexyacc/syntax.ml
index ff704cd2f..14d2987a1 100644
--- a/test/Lex/syntax.ml
+++ b/testsuite/tests/tool-lexyacc/syntax.ml
@@ -10,7 +10,7 @@
(* *)
(***********************************************************************)
-(* $Id$ *)
+(* $Id: syntax.ml,v 1.4 1999/11/17 18:58:39 xleroy Exp $ *)
(* The shallow abstract syntax *)