blob: c0d7859456e8ba9e1a03e070ecb1f9fc13d3ffe8 (
plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
|
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* 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. *)
(* *)
(***********************************************************************)
(* The lexical analyzer for lexer definitions. *)
{
open Syntax
open Grammar
open Scan_aux
}
rule main = parse
[' ' '\010' '\013' '\009' ] +
{ main lexbuf }
| "(*"
{ comment_depth := 1;
comment lexbuf;
main lexbuf }
| (['A'-'Z' 'a'-'z'] | '_' ['A'-'Z' 'a'-'z' '\'' '0'-'9'])
( '_' ? ['A'-'Z' 'a'-'z' ''' '0'-'9'] ) *
{ match Lexing.lexeme lexbuf with
"rule" -> Trule
| "parse" -> Tparse
| "and" -> Tand
| "eof" -> Teof
| s -> Tident s }
| '"'
{ reset_string_buffer();
string lexbuf;
Tstring(get_stored_string()) }
| "'"
{ Tchar(char lexbuf) }
| '{'
{ let n1 = Lexing.lexeme_end lexbuf in
brace_depth := 1;
let n2 = action lexbuf in
Taction(Location(n1, n2)) }
| '=' { Tequal }
| ";;" { Tend }
| '|' { Tor }
| '_' { Tunderscore }
| "eof" { Teof }
| '[' { Tlbracket }
| ']' { Trbracket }
| '*' { Tstar }
| '?' { Tmaybe }
| '+' { Tplus }
| '(' { Tlparen }
| ')' { Trparen }
| '^' { Tcaret }
| '-' { Tdash }
| eof
{ raise(Lexical_error "unterminated lexer definition") }
| _
{ raise(Lexical_error("illegal character " ^ Lexing.lexeme lexbuf)) }
and action = parse
'{'
{ incr brace_depth;
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 }
| '\''
{ let _ = char lexbuf in action lexbuf }
| "(*"
{ comment_depth := 1;
comment lexbuf;
action lexbuf }
| eof
{ raise (Lexical_error "unterminated action") }
| _
{ action lexbuf }
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));
string lexbuf }
| '\\' ['0'-'9'] ['0'-'9'] ['0'-'9']
{ store_string_char(char_for_decimal_code lexbuf 1);
string lexbuf }
| eof
{ raise(Lexical_error "unterminated string") }
| _
{ store_string_char(Lexing.lexeme_char lexbuf 0);
string lexbuf }
and char = parse
[^ '\\'] "'"
{ Lexing.lexeme_char lexbuf 0 }
| '\\' ['\\' '\'' 'n' 't' 'b' 'r'] "'"
{ char_for_backslash (Lexing.lexeme_char lexbuf 1) }
| '\\' ['0'-'9'] ['0'-'9'] ['0'-'9'] "'"
{ char_for_decimal_code lexbuf 1 }
| _
{ raise(Lexical_error "bad character constant") }
and comment = parse
"(*"
{ incr comment_depth; comment lexbuf }
| "*)"
{ decr comment_depth;
if !comment_depth = 0 then () else comment lexbuf }
| '"'
{ reset_string_buffer();
string lexbuf;
reset_string_buffer();
comment lexbuf }
| eof
{ raise(Lexical_error "unterminated comment") }
| _
{ comment lexbuf }
;;
|