Module Location
Source code locations (ranges of positions), used in parsetree
Warning: this module is unstable and part of compiler-libs.
type t= Warnings.loc={loc_start : Stdlib.Lexing.position;loc_end : Stdlib.Lexing.position;loc_ghost : bool;}
val none : tAn arbitrary value of type
t; describes an empty ghost range.
val in_file : string -> tReturn an empty ghost range located in a given file.
val init : Stdlib.Lexing.lexbuf -> string -> unitSet the file name and line number of the
lexbufto be the start of the named file.
val curr : Stdlib.Lexing.lexbuf -> tGet the location of the current token from the
lexbuf.
val symbol_rloc : unit -> tval symbol_gloc : unit -> tval rhs_loc : int -> trhs_loc nreturns the location of the symbol at positionn, starting at 1, in the current parser rule.
val rhs_interval : int -> int -> tval get_pos_info : Stdlib.Lexing.position -> string * int * intfile, line, char
type 'a loc={txt : 'a;loc : t;}
Input info
val input_name : string Stdlib.refval input_lexbuf : Stdlib.Lexing.lexbuf option Stdlib.ref
Toplevel-specific functions
Printing locations
val rewrite_absolute_path : string -> stringrewrite absolute path to honor the BUILD_PATH_PREFIX_MAP variable (https://reproducible-builds.org/specs/build-path-prefix-map/) if it is set.
val absolute_path : string -> stringval show_filename : string -> stringIn -absname mode, return the absolute path for this filename. Otherwise, returns the filename unchanged.
val print_filename : Stdlib.Format.formatter -> string -> unitval print_loc : Stdlib.Format.formatter -> t -> unitval print_locs : Stdlib.Format.formatter -> t list -> unit
Toplevel-specific location highlighting
val highlight_terminfo : Stdlib.Lexing.lexbuf -> Stdlib.Format.formatter -> t list -> unit
Reporting errors and warnings
The type of reports and report printers
type msg= (Stdlib.Format.formatter -> unit) loc
val msg : ?loc:t -> ('a, Stdlib.Format.formatter, unit, msg) Stdlib.format4 -> 'a
type report_kind=|Report_error|Report_warning of string|Report_warning_as_error of string|Report_alert of string|Report_alert_as_error of stringtype report={kind : report_kind;main : msg;sub : msg list;}type report_printer={pp : report_printer -> Stdlib.Format.formatter -> report -> unit;pp_report_kind : report_printer -> report -> Stdlib.Format.formatter -> report_kind -> unit;pp_main_loc : report_printer -> report -> Stdlib.Format.formatter -> t -> unit;pp_main_txt : report_printer -> report -> Stdlib.Format.formatter -> (Stdlib.Format.formatter -> unit) -> unit;pp_submsgs : report_printer -> report -> Stdlib.Format.formatter -> msg list -> unit;pp_submsg : report_printer -> report -> Stdlib.Format.formatter -> msg -> unit;pp_submsg_loc : report_printer -> report -> Stdlib.Format.formatter -> t -> unit;pp_submsg_txt : report_printer -> report -> Stdlib.Format.formatter -> (Stdlib.Format.formatter -> unit) -> unit;}A printer for
reports, defined using open-recursion. The goal is to make it easy to define new printers by re-using code from existing ones.
Report printers used in the compiler
val batch_mode_printer : report_printerval terminfo_toplevel_printer : Stdlib.Lexing.lexbuf -> report_printerval best_toplevel_printer : unit -> report_printerDetects the terminal capabilities and selects an adequate printer
Printing a report
val print_report : Stdlib.Format.formatter -> report -> unitDisplay an error or warning report.
val report_printer : (unit -> report_printer) Stdlib.refHook for redefining the printer of reports.
The hook is a
unit -> report_printerand not simply areport_printer: this is useful so that it can detect the type of the output (a file, a terminal, ...) and select a printer accordingly.
val default_report_printer : unit -> report_printerOriginal report printer for use in hooks.
Reporting warnings
Converting a Warnings.t into a report
val report_warning : t -> Warnings.t -> report optionreport_warning loc wproduces a report for the given warningw, orNoneif the warning is not to be printed.
val warning_reporter : (t -> Warnings.t -> report option) Stdlib.refHook for intercepting warnings.
val default_warning_reporter : t -> Warnings.t -> report optionOriginal warning reporter for use in hooks.
Printing warnings
val formatter_for_warnings : Stdlib.Format.formatter Stdlib.refval print_warning : t -> Stdlib.Format.formatter -> Warnings.t -> unitPrints a warning. This is simply the composition of
report_warningandprint_report.
val prerr_warning : t -> Warnings.t -> unitSame as
print_warning, but uses!formatter_for_warningsas output formatter.
Reporting alerts
Converting an Alert.t into a report
val report_alert : t -> Warnings.alert -> report optionreport_alert loc wproduces a report for the given alertw, orNoneif the alert is not to be printed.
val alert_reporter : (t -> Warnings.alert -> report option) Stdlib.refHook for intercepting alerts.
val default_alert_reporter : t -> Warnings.alert -> report optionOriginal alert reporter for use in hooks.
Printing alerts
val print_alert : t -> Stdlib.Format.formatter -> Warnings.alert -> unitPrints an alert. This is simply the composition of
report_alertandprint_report.
val prerr_alert : t -> Warnings.alert -> unitSame as
print_alert, but uses!formatter_for_warningsas output formatter.
Reporting errors
type error= reportAn
erroris areportwhichreport_kindmust beReport_error.
val error : ?loc:t -> ?sub:msg list -> string -> errorval errorf : ?loc:t -> ?sub:msg list -> ('a, Stdlib.Format.formatter, unit, error) Stdlib.format4 -> 'aval error_of_printer : ?loc:t -> ?sub:msg list -> (Stdlib.Format.formatter -> 'a -> unit) -> 'a -> errorval error_of_printer_file : (Stdlib.Format.formatter -> 'a -> unit) -> 'a -> error
Automatically reporting errors for raised exceptions
val register_error_of_exn : (exn -> error option) -> unitEach compiler module which defines a custom type of exception which can surface as a user-visible error should register a "printer" for this exception using
register_error_of_exn. The result of the printer is anerrorvalue containing a location, a message, and optionally sub-messages (each of them being located as well).
val error_of_exn : exn -> [ `Ok of error | `Already_displayed ] option
exceptionError of errorRaising
Error esignals an errore; the exception will be caught and the error will be printed.
exceptionAlready_displayed_errorRaising
Already_displayed_errorsignals an error which has already been printed. The exception will be caught, but nothing will be printed
val raise_errorf : ?loc:t -> ?sub:msg list -> ('a, Stdlib.Format.formatter, unit, 'b) Stdlib.format4 -> 'aval report_exception : Stdlib.Format.formatter -> exn -> unitReraise the exception if it is unknown.