1995-08-09 08:06:35 -07:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Objective Caml *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
1999-11-17 10:59:06 -08:00
|
|
|
(* en Automatique. All rights reserved. This file is distributed *)
|
2001-12-07 05:41:02 -08:00
|
|
|
(* under the terms of the GNU Library General Public License, with *)
|
|
|
|
(* the special exception on linking described in file ../LICENSE. *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(* $Id$ *)
|
|
|
|
|
2001-10-26 15:38:48 -07:00
|
|
|
(** The run-time library for lexers generated by [ocamllex]. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2002-11-01 09:06:47 -08:00
|
|
|
(** {6 Positions} *)
|
|
|
|
|
|
|
|
type position = {
|
|
|
|
pos_fname : string;
|
|
|
|
pos_lnum : int;
|
|
|
|
pos_bol : int;
|
|
|
|
pos_cnum : int;
|
|
|
|
}
|
|
|
|
(** A value of type [position] describes a point in a source file.
|
2002-11-02 13:52:54 -08:00
|
|
|
[pos_fname] is the file name; [pos_lnum] is the line number;
|
|
|
|
[pos_bol] is the offset of the beginning of the line (number
|
|
|
|
of characters between the beginning of the file and the beginning
|
|
|
|
of the line); [pos_cnum] is the offset of the position (number of
|
|
|
|
characters between the beginning of the file and the position).
|
2002-11-01 09:06:47 -08:00
|
|
|
*)
|
|
|
|
|
|
|
|
val dummy_pos : position;;
|
2002-11-02 13:52:54 -08:00
|
|
|
(** A value of type [position], guaranteed to be different from any
|
|
|
|
valid position.
|
|
|
|
*)
|
2002-11-01 09:06:47 -08:00
|
|
|
|
|
|
|
|
2001-12-28 15:13:35 -08:00
|
|
|
(** {6 Lexer buffers} *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2001-10-26 15:38:48 -07:00
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
type lexbuf =
|
|
|
|
{ refill_buff : lexbuf -> unit;
|
1995-08-08 06:37:34 -07:00
|
|
|
mutable lex_buffer : string;
|
2002-03-18 08:16:31 -08:00
|
|
|
mutable lex_buffer_len : int;
|
1995-05-04 03:15:53 -07:00
|
|
|
mutable lex_abs_pos : int;
|
|
|
|
mutable lex_start_pos : int;
|
|
|
|
mutable lex_curr_pos : int;
|
1996-05-28 05:43:22 -07:00
|
|
|
mutable lex_last_pos : int;
|
1997-04-15 12:19:16 -07:00
|
|
|
mutable lex_last_action : int;
|
2002-11-01 09:06:47 -08:00
|
|
|
mutable lex_eof_reached : bool;
|
|
|
|
mutable lex_mem : int array;
|
|
|
|
mutable lex_start_p : position;
|
|
|
|
mutable lex_curr_p : position;
|
|
|
|
}
|
2001-12-03 14:16:03 -08:00
|
|
|
(** The type of lexer buffers. A lexer buffer is the argument passed
|
|
|
|
to the scanning functions defined by the generated scanners.
|
|
|
|
The lexer buffer holds the current state of the scanner, plus
|
2002-11-01 09:06:47 -08:00
|
|
|
a function to refill the buffer from the input.
|
|
|
|
|
|
|
|
Note that the lexing engine will only manage the [pos_cnum] field
|
|
|
|
of [lex_curr_p] by updating it with the number of characters read
|
|
|
|
since the start of the [lexbuf]. For the other fields to be
|
|
|
|
accurate, they must be updated by the lexer actions.
|
|
|
|
*)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val from_channel : in_channel -> lexbuf
|
2001-10-26 15:38:48 -07:00
|
|
|
(** Create a lexer buffer on the given input channel.
|
|
|
|
[Lexing.from_channel inchan] returns a lexer buffer which reads
|
|
|
|
from the input channel [inchan], at the current reading position. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val from_string : string -> lexbuf
|
2001-10-26 15:38:48 -07:00
|
|
|
(** Create a lexer buffer which reads from
|
|
|
|
the given string. Reading starts from the first character in
|
|
|
|
the string. An end-of-input condition is generated when the
|
|
|
|
end of the string is reached. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val from_function : (string -> int -> int) -> lexbuf
|
2001-10-26 15:38:48 -07:00
|
|
|
(** Create a lexer buffer with the given function as its reading method.
|
|
|
|
When the scanner needs more characters, it will call the given
|
|
|
|
function, giving it a character string [s] and a character
|
|
|
|
count [n]. The function should put [n] characters or less in [s],
|
|
|
|
starting at character number 0, and return the number of characters
|
|
|
|
provided. A return value of 0 means end of input. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2001-10-26 15:38:48 -07:00
|
|
|
|
2001-12-28 15:13:35 -08:00
|
|
|
(** {6 Functions for lexer semantic actions} *)
|
2001-10-26 15:38:48 -07:00
|
|
|
|
|
|
|
|
|
|
|
(** The following functions can be called from the semantic actions
|
|
|
|
of lexer definitions (the ML code enclosed in braces that
|
|
|
|
computes the value returned by lexing functions). They give
|
|
|
|
access to the character string matched by the regular expression
|
|
|
|
associated with the semantic action. These functions must be
|
|
|
|
applied to the argument [lexbuf], which, in the code generated by
|
|
|
|
[ocamllex], is bound to the lexer buffer passed to the parsing
|
|
|
|
function. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val lexeme : lexbuf -> string
|
2001-10-26 15:38:48 -07:00
|
|
|
(** [Lexing.lexeme lexbuf] returns the string matched by
|
1995-05-04 03:15:53 -07:00
|
|
|
the regular expression. *)
|
2001-10-26 15:38:48 -07:00
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val lexeme_char : lexbuf -> int -> char
|
2001-10-26 15:38:48 -07:00
|
|
|
(** [Lexing.lexeme_char lexbuf i] returns character number [i] in
|
|
|
|
the matched string. *)
|
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val lexeme_start : lexbuf -> int
|
2002-11-01 09:06:47 -08:00
|
|
|
(** [Lexing.lexeme_start lexbuf] returns the offset in the
|
2001-10-26 15:38:48 -07:00
|
|
|
input stream of the first character of the matched string.
|
2002-11-01 09:06:47 -08:00
|
|
|
The first character of the stream has offset 0. *)
|
2001-10-26 15:38:48 -07:00
|
|
|
|
2001-12-03 14:16:03 -08:00
|
|
|
val lexeme_end : lexbuf -> int
|
2002-11-01 09:06:47 -08:00
|
|
|
(** [Lexing.lexeme_end lexbuf] returns the offset in the input stream
|
2001-10-26 15:38:48 -07:00
|
|
|
of the character following the last character of the matched
|
2002-11-01 09:06:47 -08:00
|
|
|
string. The first character of the stream has offset 0. *)
|
|
|
|
|
|
|
|
val lexeme_start_p : lexbuf -> position
|
|
|
|
(** Like [lexeme_start], but return a complete [position] instead
|
|
|
|
of an offset. *)
|
|
|
|
|
|
|
|
val lexeme_end_p : lexbuf -> position
|
|
|
|
(** Like [lexeme_end], but return a complete [position] instead
|
|
|
|
of an offset. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2001-10-30 08:52:04 -08:00
|
|
|
(**/**)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2001-12-28 15:13:35 -08:00
|
|
|
(** {6 } *)
|
2001-10-26 15:38:48 -07:00
|
|
|
|
|
|
|
(** The following definitions are used by the generated scanners only.
|
1995-05-04 03:15:53 -07:00
|
|
|
They are not intended to be used by user programs. *)
|
|
|
|
|
2002-10-28 08:46:50 -08:00
|
|
|
val sub_lexeme : lexbuf -> int -> int -> string
|
|
|
|
val sub_lexeme_opt : lexbuf -> int -> int -> string option
|
|
|
|
val sub_lexeme_char : lexbuf -> int -> char
|
|
|
|
val sub_lexeme_char_opt : lexbuf -> int -> char option
|
|
|
|
|
1996-02-25 06:45:47 -08:00
|
|
|
type lex_tables =
|
2001-12-03 14:16:03 -08:00
|
|
|
{ lex_base : string;
|
|
|
|
lex_backtrk : string;
|
|
|
|
lex_default : string;
|
|
|
|
lex_trans : string;
|
2002-10-28 08:46:50 -08:00
|
|
|
lex_check : string;
|
|
|
|
lex_base_code : string;
|
|
|
|
lex_backtrk_code : string;
|
|
|
|
lex_default_code : string;
|
|
|
|
lex_trans_code : string;
|
|
|
|
lex_check_code : string;
|
|
|
|
lex_code: string;}
|
1996-02-25 06:45:47 -08:00
|
|
|
|
2002-11-01 09:06:47 -08:00
|
|
|
val engine : lex_tables -> int -> lexbuf -> int
|
|
|
|
val new_engine : lex_tables -> int -> lexbuf -> int
|