]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/parsing/linenum.mll
update
[l4.git] / l4 / pkg / ocaml / contrib / parsing / linenum.mll
1 (***********************************************************************)
2 (*                                                                     *)
3 (*                           Objective Caml                            *)
4 (*                                                                     *)
5 (*            Xavier Leroy, projet Cristal, INRIA Rocquencourt         *)
6 (*                                                                     *)
7 (*  Copyright 1997 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: linenum.mll 2553 1999-11-17 18:59:06Z xleroy $ *)
14
15 (* An auxiliary lexer for determining the line number corresponding to
16    a file position, honoring the directives # linenum "filename" *)
17
18 {
19 let filename = ref ""
20 let linenum = ref 0
21 let linebeg = ref 0
22
23 let parse_sharp_line s =
24   try
25     (* Update the line number and file name *)
26     let l1 = ref 0 in
27     while let c = s.[!l1] in c < '0' || c > '9' do incr l1 done;
28     let l2 = ref (!l1 + 1) in
29     while let c = s.[!l2] in c >= '0' && c <= '9' do incr l2 done;
30     linenum := int_of_string(String.sub s !l1 (!l2 - !l1));
31     let f1 = ref (!l2 + 1) in
32     while !f1 < String.length s && s.[!f1] <> '"' do incr f1 done;
33     let f2 = ref (!f1 + 1) in 
34     while !f2 < String.length s && s.[!f2] <> '"' do incr f2 done;
35     if !f1 < String.length s then
36       filename := String.sub s (!f1 + 1) (!f2 - !f1 - 1)
37   with Failure _ | Invalid_argument _ ->
38     Misc.fatal_error "Linenum.parse_sharp_line"
39 }
40
41 rule skip_line = parse
42     "#" [' ' '\t']* ['0'-'9']+ [' ' '\t']*
43     ("\"" [^ '\n' '\r' '"' (* '"' *) ] * "\"")?
44     [^ '\n' '\r'] *
45     ('\n' | '\r' | "\r\n")
46       { parse_sharp_line(Lexing.lexeme lexbuf);
47         linebeg := Lexing.lexeme_start lexbuf;
48         Lexing.lexeme_end lexbuf }
49   | [^ '\n' '\r'] *
50     ('\n' | '\r' | "\r\n")
51       { incr linenum;
52         linebeg := Lexing.lexeme_start lexbuf;
53         Lexing.lexeme_end lexbuf }
54   | [^ '\n' '\r'] * eof
55       { incr linenum;
56         linebeg := Lexing.lexeme_start lexbuf;
57         raise End_of_file }
58
59 {
60
61 let for_position file loc =
62   let ic = open_in_bin file in
63   let lb = Lexing.from_channel ic in
64   filename := file;
65   linenum := 1;
66   linebeg := 0;
67   begin try
68     while skip_line lb <= loc do () done
69   with End_of_file -> ()
70   end;
71   close_in ic;
72   (!filename, !linenum - 1, !linebeg)
73
74 }