Sys.Signals module for a Variant type of signals (and a set_signal function that...
[ocaml.git] / stdlib / lexing.mli
blob7bf47ea49dd95428f57e3308ba660f4f3c918822
1 (***********************************************************************)
2 (* *)
3 (* Objective Caml *)
4 (* *)
5 (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
6 (* *)
7 (* Copyright 1996 Institut National de Recherche en Informatique et *)
8 (* en Automatique. All rights reserved. This file is distributed *)
9 (* under the terms of the GNU Library General Public License, with *)
10 (* the special exception on linking described in file ../LICENSE. *)
11 (* *)
12 (***********************************************************************)
14 (* $Id$ *)
16 (** The run-time library for lexers generated by [ocamllex]. *)
18 (** {6 Positions} *)
20 type position = {
21 pos_fname : string;
22 pos_lnum : int;
23 pos_bol : int;
24 pos_cnum : int;
26 (** A value of type [position] describes a point in a source file.
27 [pos_fname] is the file name; [pos_lnum] is the line number;
28 [pos_bol] is the offset of the beginning of the line (number
29 of characters between the beginning of the file and the beginning
30 of the line); [pos_cnum] is the offset of the position (number of
31 characters between the beginning of the file and the position).
33 See the documentation of type [lexbuf] for information about
34 how the lexing engine will manage positions.
37 val dummy_pos : position;;
38 (** A value of type [position], guaranteed to be different from any
39 valid position.
43 (** {6 Lexer buffers} *)
46 type lexbuf =
47 { refill_buff : lexbuf -> unit;
48 mutable lex_buffer : string;
49 mutable lex_buffer_len : int;
50 mutable lex_abs_pos : int;
51 mutable lex_start_pos : int;
52 mutable lex_curr_pos : int;
53 mutable lex_last_pos : int;
54 mutable lex_last_action : int;
55 mutable lex_eof_reached : bool;
56 mutable lex_mem : int array;
57 mutable lex_start_p : position;
58 mutable lex_curr_p : position;
60 (** The type of lexer buffers. A lexer buffer is the argument passed
61 to the scanning functions defined by the generated scanners.
62 The lexer buffer holds the current state of the scanner, plus
63 a function to refill the buffer from the input.
65 Note that the lexing engine will only change the [pos_cnum] field
66 of [lex_curr_p] by updating it with the number of characters read
67 since the start of the [lexbuf]. The other fields are copied
68 without change by the lexing engine. In order to keep them
69 accurate, they must be initialised before the first use of the
70 lexbuf, and updated by the relevant lexer actions (i.e. at each
71 end of line).
74 val from_channel : in_channel -> lexbuf
75 (** Create a lexer buffer on the given input channel.
76 [Lexing.from_channel inchan] returns a lexer buffer which reads
77 from the input channel [inchan], at the current reading position. *)
79 val from_string : string -> lexbuf
80 (** Create a lexer buffer which reads from
81 the given string. Reading starts from the first character in
82 the string. An end-of-input condition is generated when the
83 end of the string is reached. *)
85 val from_function : (string -> int -> int) -> lexbuf
86 (** Create a lexer buffer with the given function as its reading method.
87 When the scanner needs more characters, it will call the given
88 function, giving it a character string [s] and a character
89 count [n]. The function should put [n] characters or less in [s],
90 starting at character number 0, and return the number of characters
91 provided. A return value of 0 means end of input. *)
94 (** {6 Functions for lexer semantic actions} *)
97 (** The following functions can be called from the semantic actions
98 of lexer definitions (the ML code enclosed in braces that
99 computes the value returned by lexing functions). They give
100 access to the character string matched by the regular expression
101 associated with the semantic action. These functions must be
102 applied to the argument [lexbuf], which, in the code generated by
103 [ocamllex], is bound to the lexer buffer passed to the parsing
104 function. *)
106 val lexeme : lexbuf -> string
107 (** [Lexing.lexeme lexbuf] returns the string matched by
108 the regular expression. *)
110 val lexeme_char : lexbuf -> int -> char
111 (** [Lexing.lexeme_char lexbuf i] returns character number [i] in
112 the matched string. *)
114 val lexeme_start : lexbuf -> int
115 (** [Lexing.lexeme_start lexbuf] returns the offset in the
116 input stream of the first character of the matched string.
117 The first character of the stream has offset 0. *)
119 val lexeme_end : lexbuf -> int
120 (** [Lexing.lexeme_end lexbuf] returns the offset in the input stream
121 of the character following the last character of the matched
122 string. The first character of the stream has offset 0. *)
124 val lexeme_start_p : lexbuf -> position
125 (** Like [lexeme_start], but return a complete [position] instead
126 of an offset. *)
128 val lexeme_end_p : lexbuf -> position
129 (** Like [lexeme_end], but return a complete [position] instead
130 of an offset. *)
132 (** {6 Miscellaneous functions} *)
134 val flush_input : lexbuf -> unit
135 (** Discard the contents of the buffer and reset the current
136 position to 0. The next use of the lexbuf will trigger a
137 refill. *)
139 (**/**)
141 (** {6 } *)
143 (** The following definitions are used by the generated scanners only.
144 They are not intended to be used by user programs. *)
146 val sub_lexeme : lexbuf -> int -> int -> string
147 val sub_lexeme_opt : lexbuf -> int -> int -> string option
148 val sub_lexeme_char : lexbuf -> int -> char
149 val sub_lexeme_char_opt : lexbuf -> int -> char option
151 type lex_tables =
152 { lex_base : string;
153 lex_backtrk : string;
154 lex_default : string;
155 lex_trans : string;
156 lex_check : string;
157 lex_base_code : string;
158 lex_backtrk_code : string;
159 lex_default_code : string;
160 lex_trans_code : string;
161 lex_check_code : string;
162 lex_code: string;}
164 val engine : lex_tables -> int -> lexbuf -> int
165 val new_engine : lex_tables -> int -> lexbuf -> int