]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/ocaml/contrib/parsing/location.mli
Update
[l4.git] / l4 / pkg / ocaml / ocaml / contrib / parsing / location.mli
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 Q Public License version 1.0.               *)
10 (*                                                                     *)
11 (***********************************************************************)
12
13 (* $Id: location.mli 8705 2007-12-04 13:38:58Z doligez $ *)
14
15 (* Source code locations (ranges of positions), used in parsetree. *)
16
17 open Format
18
19 type t = {
20   loc_start: Lexing.position;
21   loc_end: Lexing.position;
22   loc_ghost: bool;
23 }
24
25 (* Note on the use of Lexing.position in this module.
26    If [pos_fname = ""], then use [!input_name] instead.
27    If [pos_lnum = -1], then [pos_bol = 0]. Use [pos_cnum] and
28      re-parse the file to get the line and character numbers.
29    Else all fields are correct.
30 *)
31
32 val none : t
33 (** An arbitrary value of type [t]; describes an empty ghost range. *)
34 val in_file : string -> t;;
35 (** Return an empty ghost range located in a given file. *)
36 val init : Lexing.lexbuf -> string -> unit
37 (** Set the file name and line number of the [lexbuf] to be the start
38     of the named file. *)
39 val curr : Lexing.lexbuf -> t
40 (** Get the location of the current token from the [lexbuf]. *)
41
42 val symbol_rloc: unit -> t
43 val symbol_gloc: unit -> t
44 val rhs_loc: int -> t
45
46 val input_name: string ref
47 val input_lexbuf: Lexing.lexbuf option ref
48
49 val get_pos_info : Lexing.position -> string * int * int (* file, line, char *)
50 val print_error: formatter -> t -> unit
51 val print_error_cur_file: formatter -> unit
52 val print_warning: t -> formatter -> Warnings.t -> unit
53 val prerr_warning: t -> Warnings.t -> unit
54 val echo_eof: unit -> unit
55 val reset: unit -> unit
56
57 val highlight_locations: formatter -> t -> t -> bool