ocamlbuild: a short location printing implementation
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14146 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
75beffa385
commit
d70b93a252
|
@ -0,0 +1,30 @@
|
|||
(* it's not worth adding a dependency on parsing/location.ml(i) or
|
||||
compilerlibs just to support location printing, so we re-implement
|
||||
that here *)
|
||||
|
||||
open Lexing
|
||||
|
||||
type location = position * position
|
||||
|
||||
let file loc = loc.pos_fname
|
||||
let line loc = loc.pos_lnum
|
||||
let char loc = loc.pos_cnum - loc.pos_bol
|
||||
|
||||
let print_loc ppf (start, end_) =
|
||||
let open Format in
|
||||
let print one_or_two ppf (start_num, end_num) =
|
||||
if one_or_two then fprintf ppf " %d" start_num
|
||||
else fprintf ppf "s %d-%d" start_num end_num in
|
||||
fprintf ppf "File %S, line%a, character%a:@."
|
||||
(file start)
|
||||
(print (line start = line end_))
|
||||
(line start, line end_)
|
||||
(print (line start = line end_ && char start = char end_))
|
||||
(char start, char end_)
|
||||
|
||||
let of_lexbuf lexbuf =
|
||||
(lexbuf.lex_start_p, lexbuf.lex_curr_p)
|
||||
|
||||
let print_loc_option ppf = function
|
||||
| None -> ()
|
||||
| Some loc -> print_loc ppf loc
|
|
@ -0,0 +1,6 @@
|
|||
type location = Lexing.position * Lexing.position
|
||||
|
||||
val print_loc : Format.formatter -> location -> unit
|
||||
val print_loc_option : Format.formatter -> location option -> unit
|
||||
|
||||
val of_lexbuf : Lexing.lexbuf -> location
|
|
@ -1,3 +1,4 @@
|
|||
Loc
|
||||
Log
|
||||
My_unix
|
||||
My_std
|
||||
|
|
Loading…
Reference in New Issue