Merge pull request #29 from superbobry/ocamldoc-errors

PR#4518: change location format for reporting errors in ocamldoc
master
Gabriel Scherer 2015-11-23 23:20:10 +01:00
commit 6d5b2403bd
3 changed files with 19 additions and 20 deletions

View File

@ -102,7 +102,7 @@ Compilers:
- GPR#270: Make [transl_exception_constructor] generate [Immutable] blocks - GPR#270: Make [transl_exception_constructor] generate [Immutable] blocks
(Mark Shinwell) (Mark Shinwell)
- GPR#275: native-code generator for IBM z System running Linux. - GPR#275: native-code generator for IBM z System running Linux.
In memoriam Gene Amdahl, 1922-2015. In memoriam Gene Amdahl, 1922-2015.
(Bill O'Farrell, Tristan Amini, Xavier Leroy) (Bill O'Farrell, Tristan Amini, Xavier Leroy)
- GPR#282: relax short-paths safety check in presence of module aliases, take - GPR#282: relax short-paths safety check in presence of module aliases, take
penalty into account while building the printing map. penalty into account while building the printing map.
@ -319,6 +319,8 @@ Bug fixes:
(Marc Lasson, review by Alain Frisch) (Marc Lasson, review by Alain Frisch)
Features wishes: Features wishes:
- PR#4518, GPR#29: change location format for reporting errors in ocamldoc
(Sergei Lebedev)
- PR#4714: List.cons - PR#4714: List.cons
- PR#5418 (comments) : generate dependencies with $(CC) instead of gcc - PR#5418 (comments) : generate dependencies with $(CC) instead of gcc
- PR#6167: OCAMLPARAM support for disabling PIC generation ("pic=0") - PR#6167: OCAMLPARAM support for disabling PIC generation ("pic=0")

View File

@ -28,7 +28,7 @@ module type Texter =
module Info_retriever = module Info_retriever =
functor (MyTexter : Texter) -> functor (MyTexter : Texter) ->
struct struct
let create_see s = let create_see file s =
try try
let lexbuf = Lexing.from_string s in let lexbuf = Lexing.from_string s in
let (see_ref, s) = Odoc_parser.see_info Odoc_see_lexer.main lexbuf in let (see_ref, s) = Odoc_parser.see_info Odoc_see_lexer.main lexbuf in
@ -64,7 +64,7 @@ module Info_retriever =
i_desc = (match desc with "" -> None | _ -> Some (MyTexter.text_of_string desc)); i_desc = (match desc with "" -> None | _ -> Some (MyTexter.text_of_string desc));
i_authors = !Odoc_comments_global.authors; i_authors = !Odoc_comments_global.authors;
i_version = !Odoc_comments_global.version; i_version = !Odoc_comments_global.version;
i_sees = (List.map create_see !Odoc_comments_global.sees) ; i_sees = (List.map (create_see file) !Odoc_comments_global.sees) ;
i_since = !Odoc_comments_global.since; i_since = !Odoc_comments_global.since;
i_before = Odoc_merge.merge_before_tags i_before = Odoc_merge.merge_before_tags
(List.map (fun (n, s) -> (List.map (fun (n, s) ->
@ -87,19 +87,16 @@ module Info_retriever =
!Odoc_comments_global.customs) !Odoc_comments_global.customs)
} }
) )
with with e ->
Failure s -> let (l, c, message) = match e with
incr Odoc_global.errors ; | Failure s -> (!Odoc_lexer.line_number + 1, 0, s)
Printf.eprintf "File %S, line %d:\n%s\n%!" file (!Odoc_lexer.line_number + 1) s; | Odoc_text.Text_syntax (l, c, s) -> (l, c, Odoc_messages.text_parse_error l c s)
(0, None) | _other -> (0, 0, Odoc_messages.parse_error)
| Odoc_text.Text_syntax (l, c, s) -> in begin
incr Odoc_global.errors ; incr Odoc_global.errors;
prerr_endline (file^" : "^(Odoc_messages.text_parse_error l c s)); prerr_endline (Odoc_messages.error_location file l c ^ message);
(0, None) (0, None)
| _ -> end
incr Odoc_global.errors ;
prerr_endline (file^" : "^Odoc_messages.parse_error^"\n");
(0, None)
(** This function takes a string where a simple comment may has been found. It returns (** This function takes a string where a simple comment may has been found. It returns
false if there is a blank line or the first comment is a special one, or if there is false if there is a blank line or the first comment is a special one, or if there is

View File

@ -233,6 +233,9 @@ let help = " Display this list of options"
let warning = "Warning" let warning = "Warning"
let error_location file l c =
Printf.sprintf "File \"%s\", line %d, character %d:\n" file l c
let bad_magic_number = let bad_magic_number =
"Bad magic number for this ocamldoc dump!\n"^ "Bad magic number for this ocamldoc dump!\n"^
"This dump was not created by this version of OCamldoc." "This dump was not created by this version of OCamldoc."
@ -244,10 +247,7 @@ let errors_occured n = (string_of_int n)^" error(s) encountered"
let parse_error = "Parse error" let parse_error = "Parse error"
let text_parse_error l c s = let text_parse_error l c s =
let lines = Str.split (Str.regexp_string "\n") s in let lines = Str.split (Str.regexp_string "\n") s in
"Syntax error in text:\n"^s^"\n"^ (List.nth lines l) ^ "\n" ^ (String.make c ' ') ^ "^"
"line "^(string_of_int l)^", character "^(string_of_int c)^":\n"^
(List.nth lines l)^"\n"^
(String.make c ' ')^"^"
let file_not_found_in_paths paths name = let file_not_found_in_paths paths name =
Printf.sprintf "No file %s found in the load paths: \n%s" Printf.sprintf "No file %s found in the load paths: \n%s"