Module Misc
Miscellaneous useful types and functions
Warning: this module is unstable and part of compiler-libs.
val fatal_error : string -> 'aval fatal_errorf : ('a, Stdlib.Format.formatter, unit, 'b) Stdlib.format4 -> 'a
val try_finally : ?always:(unit -> unit) -> ?exceptionally:(unit -> unit) -> (unit -> 'a) -> 'atry_finally work ~always ~exceptionallyis designed to run code inworkthat may fail with an exception, and has two kind of cleanup routines:always, that must be run after any execution of the function (typically, freeing system resources), andexceptionally, that should be run only ifworkoralwaysfailed with an exception (typically, undoing user-visible state changes that would only make sense if the function completes correctly). For example:let objfile = outputprefix ^ ".cmo" in let oc = open_out_bin objfile in Misc.try_finally (fun () -> bytecode ++ Timings.(accumulate_time (Generate sourcefile)) (Emitcode.to_file oc modulename objfile); Warnings.check_fatal ()) ~always:(fun () -> close_out oc) ~exceptionally:(fun _exn -> remove_file objfile);If
exceptionallyfail with an exception, it is propagated as usual.If
alwaysorexceptionallyuse exceptions internally for control-flow but do not raise, thentry_finallyis careful to preserve any exception backtrace coming fromworkoralwaysfor easier debugging.
val map_end : ('a -> 'b) -> 'a list -> 'b list -> 'b listval map_left_right : ('a -> 'b) -> 'a list -> 'b listval for_all2 : ('a -> 'b -> bool) -> 'a list -> 'b list -> boolval replicate_list : 'a -> int -> 'a listval list_remove : 'a -> 'a list -> 'a listval split_last : 'a list -> 'a list * 'aval may : ('a -> unit) -> 'a option -> unitval may_map : ('a -> 'b) -> 'a option -> 'b option
type ref_and_value=|R : 'a Stdlib.ref * 'a -> ref_and_value
val protect_refs : ref_and_value list -> (unit -> 'a) -> 'aprotect_refs l ftemporarily setsrtovfor eachR (r, v)inlwhile executingf. The previous contents of the references is restored even iffraises an exception.
module Stdlib : sig ... endval find_in_path : string list -> string -> stringval find_in_path_rel : string list -> string -> stringval find_in_path_uncap : string list -> string -> stringval remove_file : string -> unitval expand_directory : string -> string -> stringval split_path_contents : ?sep:char -> string -> string listval create_hashtable : int -> ('a * 'b) list -> ('a, 'b) Stdlib.Hashtbl.tval copy_file : Stdlib.in_channel -> Stdlib.out_channel -> unitval copy_file_chunk : Stdlib.in_channel -> Stdlib.out_channel -> int -> unitval string_of_file : Stdlib.in_channel -> stringval output_to_file_via_temporary : ?mode:Stdlib.open_flag list -> string -> (string -> Stdlib.out_channel -> 'a) -> 'aval log2 : int -> intval align : int -> int -> intval no_overflow_add : int -> int -> boolval no_overflow_sub : int -> int -> boolval no_overflow_mul : int -> int -> boolval no_overflow_lsl : int -> int -> bool
module Int_literal_converter : sig ... endval chop_extensions : string -> stringval search_substring : string -> string -> int -> intval replace_substring : before:string -> after:string -> string -> stringval rev_split_words : string -> string listval get_ref : 'a list Stdlib.ref -> 'a listval set_or_ignore : ('a -> 'b option) -> 'b option Stdlib.ref -> 'a -> unitval fst3 : ('a * 'b * 'c) -> 'aval snd3 : ('a * 'b * 'c) -> 'bval thd3 : ('a * 'b * 'c) -> 'cval fst4 : ('a * 'b * 'c * 'd) -> 'aval snd4 : ('a * 'b * 'c * 'd) -> 'bval thd4 : ('a * 'b * 'c * 'd) -> 'cval for4 : ('a * 'b * 'c * 'd) -> 'd
module LongString : sig ... endval edit_distance : string -> string -> int -> int optionedit_distance a b cutoffcomputes the edit distance between stringsaandb. To help efficiency, it uses a cutoff: if the distancedis smaller thancutoff, it returnsSome d, elseNone.The distance algorithm currently used is Damerau-Levenshtein: it computes the number of insertion, deletion, substitution of letters, or swapping of adjacent letters to go from one word to the other. The particular algorithm may change in the future.
val spellcheck : string list -> string -> string listspellcheck env nametakes a list of namesenvthat exist in the current environment and an erroneousname, and returns a list of suggestions taken fromenv, that are close enough tonamethat it may be a typo for one of them.
val did_you_mean : Stdlib.Format.formatter -> (unit -> string list) -> unitdid_you_mean ppf get_choiceshints that the user may have meant one of the option returned by callingget_choices. It does nothing if the returned list is empty.The
unit -> ...thunking is meant to delay any potentially-slow computation (typically computing edit-distance with many things from the current environment) to when the hint message is to be printed. You should print an understandable error message before callingdid_you_mean, so that users get a clear notification of the failure even if producing the hint is slow.
val cut_at : string -> char -> string * stringString.cut_at s creturns a pair containing the sub-string before the first occurrence ofcins, and the sub-string after the first occurrence ofcins.let (before, after) = String.cut_at s c in before ^ String.make 1 c ^ afteris the identity ifscontainsc.Raise
Not_foundif the character does not appear in the string- since
- 4.01
module Color : sig ... endmodule Error_style : sig ... endval normalise_eol : string -> stringnormalise_eol sreturns a fresh copy ofswith any '\r' characters removed. Intended for pre-processing text which will subsequently be printed on a channel which performs EOL transformations (i.e. Windows)
val delete_eol_spaces : string -> stringdelete_eol_spaces sreturns a fresh copy ofswith any end of line spaces removed. Intended to normalize the output of the toplevel for tests.
val pp_two_columns : ?sep:string -> ?max_lines:int -> Stdlib.Format.formatter -> (string * string) list -> unitpp_two_columns ?sep ?max_lines ppf lprints the lines inlas two columns separated bysep("|" by default).max_linescan be used to indicate a maximum number of lines to print -- an ellipsis gets inserted at the middle if the input has too many lines.Example:
pp_two_columns ~max_lines:3 Format.std_formatter [ "abc", "hello"; "def", "zzz"; "a" , "bllbl"; "bb" , "dddddd"; ]prints
abc | hello ... bb | dddddd
Hook machinery
Hooks machinery: add_hook name f will register a function that will be called on the argument of a later call to apply_hooks. Hooks are applied in the lexicographical order of their names.
exceptionHookExnWrapper of{error : exn;hook_name : string;hook_info : hook_info;}An exception raised by a hook will be wrapped into a
HookExnWrapperconstructor by the hook machinery.
val raise_direct_hook_exn : exn -> 'aA hook can use
raise_unwrapped_hook_exnto raise an exception that will not be wrapped into aHookExnWrapper.
module type HookSig = sig ... endval show_config_variable_and_exit : string -> unitval get_build_path_prefix_map : unit -> Build_path_prefix_map.map optionReturns the map encoded in the
BUILD_PATH_PREFIX_MAPenvironment variable.
val debug_prefix_map_flags : unit -> string listReturns the list of
--debug-prefix-mapflags to be passed to the assembler, built from theBUILD_PATH_PREFIX_MAPenvironment variable.
val print_if : Stdlib.Format.formatter -> bool Stdlib.ref -> (Stdlib.Format.formatter -> 'a -> unit) -> 'a -> 'aprint_if ppf flag fmt xprintsxwithfmtonppfifbis true.