package links

  1. Overview
  2. Docs
val fst3 : ('a * 'b * 'c) -> 'd
val snd3 : ('a * 'b * 'c) -> 'd
val thd3 : ('a * 'b * 'c) -> 'd
module Functional : sig ... end
include module type of struct include Functional end

Functional combinators

val (-<-) : ('a -> 'b) -> ('c -> 'd) -> 'e -> 'f

"compose" operators (arrow indicates direction of composition)

val (->-) : ('a -> 'b) -> ('c -> 'd) -> 'e -> 'f
val curry : (('a * 'b) -> 'c) -> 'd -> 'e -> 'f
val uncurry : ('a -> 'b -> 'c) -> ('d * 'e) -> 'f
val identity : 'a -> 'b
val flip : ('a -> 'b -> 'c) -> 'd -> 'e -> 'f
val const : 'a -> 'b -> 'c
val cross : ('a -> 'b) -> ('c -> 'd) -> ('e * 'f) -> 'g * 'h

Simulating infix function words (a la Haskell backticks)

val (<|) : ('a -> 'b) -> 'c -> 'd

left-associative

val (|>) : 'a -> ('b -> 'c) -> 'd
module type OrderedShow = sig ... end
module type Map = sig ... end
module String : sig ... end
module Int : sig ... end
module IntPair : sig ... end
module Char : sig ... end
module Map : sig ... end
module type Set = sig ... end
module Set : sig ... end
module type INTSET = Set with type elt = int
module IntSet : sig ... end
module IntMap : sig ... end
module IntPairMap : sig ... end
module type STRINGMAP = Map with type key = string
module type INTMAP = Map with type key = int
module StringSet : sig ... end
module type CHARSET = Set with type elt = char
module CharSet : CHARSET
module CharMap : sig ... end
type stringset = StringSet.t
val show_stringset : stringset -> Ppx_deriving_runtime.string

module Typeable_stringset : Deriving_Typeable.Typeable with type a = stringset = Deriving_Typeable.Primitive_typeable(struct type t = stringset let magic = "stringset" end)*

type 'a stringmap = 'a StringMap.t
type intset = IntSet.t
val show_intset : intset -> Ppx_deriving_runtime.string
type 'a intmap = 'a IntMap.t
val list_to_set : IntSet.elt list -> IntSet.t
module ListUtils : sig ... end
include module type of struct include ListUtils end

Lists

val empty : 'a list -> bool

Test whether the argument is the empty list.

val fromTo : int -> int -> int list

fromTo a b is the list of consecutive integers starting with a and ending with b-1. Throws Invalid_argument "fromTo" if b < a.

val mapIndex : ('a -> int -> 'b) -> 'a0 list -> 'b0 list

map with index

val all_equiv : ('a -> 'a -> bool) -> 'a0 list -> bool

all_equiv rel list: given an equiv. rel'n rel, determine whether all elements of list are equivalent.

val span : ('a -> bool) -> 'a0 list -> 'a0 list * 'a0 list

span pred list: partition list into an initial sublist satisfying pred and the remainder.

val groupBy : ('a -> 'a0 -> bool) -> 'a1 list -> 'a1 list list

groupBy rel list: given a binary rel'n rel, partition list into chunks s.t. successive elements x, y in a chunk give the same value under rel.

val groupByPred : ('a -> 'b) -> 'c list -> 'd list list

groupByPred pred partitions list into chunks where all elements in the chunk give the same value under pred.

val groupByPred' : ('a -> 'b) -> 'a0 list -> 'a0 list list

groupByPred': Alternate implementation of groupByPred.

val unsnoc : 'a list -> 'b list * 'c

unsnoc list: Partition list into its last element and all the others.

  • returns

    (others, lastElem)

val unsnoc_opt : 'a list -> ('a list * 'a) option

unsnoc_opt list: Partition list into its last element and all the others.

  • returns

    Some (others, lastElem) or None if the list is empty.

val last : 'a list -> 'b

last list: Return the last element of a list

val last_opt : 'a list -> 'b option

last_opt list: Return the last element of a list, or None if the list is empty.

val curtail : 'a list -> 'a list

curtail list: Return a copy of the list with the last element removed.

val difference : 'a list -> 'b list -> 'a list
val remove_all : 'a list -> 'a list -> 'a list
val subset : 'a list -> 'b list -> bool
val less_to_cmp : ('a -> 'b -> bool) -> 'c -> 'd -> int

Convert a (bivalent) less-than function into a (three-valued) comparison function.

val has_duplicates : 'a list -> bool

Checks whether list contains duplicates

val unduplicate : ('a -> 'b -> bool) -> 'c list -> 'd list

Remove duplicates from a list, using the given relation to determine `duplicates'

val collect_duplicates : ('a -> 'b -> bool) -> 'c list -> 'd list

Collects only elements which are duplicate in the original list.

val ordered_consecutive : int list -> bool
val drop : int -> 'a list -> 'a list
val take : int -> 'a list -> 'b list
val remove : 'a -> 'b list -> 'b list
val concat_map : ('a -> 'b list) -> 'a list -> 'b list
val concat_map_uniq : ('a -> 'b list) -> 'a list -> 'c list
val concat_map_undup : ('a -> 'a -> bool) -> ('b -> 'c list) -> 'b list -> 'a list
val for_each : 'a list -> ('a -> unit) -> unit
val push_back : 'a -> 'b list ref -> unit
val push_front : 'a -> 'b list ref -> unit
val split3 : ('a * 'b * 'c) list -> 'd list * 'e list * 'f list
val split4 : ('a * 'b * 'c * 'd) list -> 'e list * 'f list * 'g list * 'h list
val drop_nth : 'a list -> int -> 'a list
val filter_map : ('a -> bool) -> ('b -> 'c) -> 'd list -> 'e list
exception Lists_length_mismatch
val filter_map2 : (('a * 'b) -> bool) -> (('c * 'd) -> 'e) -> 'f list -> 'g list -> 'h list

Filter on two lists and map them together. Equivalent to map -<- filter -<- zip precondition: the two lists must be the same length

val map_filter : ('a -> 'b) -> ('c -> bool) -> 'd list -> 'e list
val print_list : string list -> string
val zip : 'a list -> 'b list -> ('c * 'd) list
val zip_with : ('a -> 'b -> 'c) -> 'd list -> 'e list -> 'f list
val split_with : ('a -> 'b * 'c) -> 'a list -> 'b list * 'c list
val zip' : 'a list -> 'b list -> ('c * 'd) list
val zip_with' : ('a -> 'b -> 'c) -> 'd list -> 'e list -> 'f list
val transpose : 'a list list -> 'a0 list list
module AList : sig ... end
include module type of struct include AList end

Association-list utilities

val rassoc_eq : ('b -> 'b0 -> bool) -> 'b1 -> ('a * 'b1) list -> 'a
val rassoc : 'a -> ('b * 'c) list -> 'd
val rassq : 'a -> ('b * 'c) list -> 'd
val rremove_assoc_eq : ('b -> 'b0 -> bool) -> 'b1 -> ('a * 'b1) list -> ('a * 'b1) list
val rremove_assoc : 'a -> ('b * 'c) list -> ('b * 'c) list
val rremove_assq : 'a -> ('b * 'c) list -> ('b * 'c) list
val remove_keys : ('a * 'b) list -> 'c list -> ('a * 'b) list
val alistmap : ('a -> 'b) -> ('c * 'a) list -> ('d * 'b) list

alistmap maps f on the contents-parts of the entries, producing a new alist

val show_fgraph : ?glue:string -> (string -> string) -> string list -> string
val alistmap' : (('a * 'b) -> 'c) -> ('d * 'e) list -> ('f * 'g) list

alistmap' produces an alist by applying f to each element of the alist--f should produce a new contents-part for the entry.

val map2alist : ('a -> 'b) -> 'c list -> ('d * 'e) list

[map2alist f list] makes an alist that maps [x] to [f x] for each item in [list]. This is called the `graph' of f on the domain list.

val graph_func : ('a -> 'b) -> 'a list -> ('a * 'b) list
val range : ('a * 'b) list -> 'c list
val dom : ('a * 'b) list -> 'c list
val lookup_in : ('a * 'b) list -> 'c -> 'd

lookup_in alist is a function that looks up its argument in alist

val lookup : 'a -> ('b * 'c) list -> 'd option

lookup is like assoc but uses option types instead of exceptions to signal absence

module StringUtils : sig ... end
include module type of struct include StringUtils end

Strings

val string_of_char : char -> string
val string_of_alist : (string * string) list -> string
val split_string : string -> char -> string list
val split : char -> string -> string list
val explode : string -> char list
val is_numeric : string -> bool
val implode : char list -> string
val contains : (char -> bool) -> string -> bool
val find_char : bytes -> char -> int list
val mapstrcat : string -> ('a -> string) -> 'a list -> string
val string_starts_with : string -> string -> bool
val start_of : is:string -> string -> bool
val end_of : is:string -> string -> bool
val count : char -> string -> int
val replace : string -> string -> string -> string
val groupingsToString : ('a -> string) -> 'a list list -> string

Given a list-of-lists, groupingsToString concatenates them using ", " as the delimiter between elements and "; " as the delimiter between lists.

val numberp : string -> bool

File I/O utilities

val lines : in_channel -> string list
val call_with_open_infile : string -> ?binary:bool -> (in_channel -> 'a) -> 'a
val call_with_open_outfile : string -> ?binary:bool -> (out_channel -> 'a) -> 'a
val process_output : string -> string
val filter_through : command:string -> string -> string
val newer : string -> string -> bool

Is f1 strictly newer than f2, in terms of modification time?

val absolute_path : string -> string

Given a path name, possibly relative to CWD, return an absolute path to the same file.

val getuid_owns : string -> bool

Is the UID of the process is the same as that of the file's owner?

3-way assoc-list

val mem_assoc3 : 'a -> ('a0 * 'b * 'c) list -> bool
type ('a, 'b) either =
  1. | Left of 'a
  2. | Right of 'b

either type

*

val inLeft : 'a -> ('b, 'c) either
val inRight : 'a -> ('b, 'c) either
val fromLeft : ('a, 'b) either -> 'c
val fromRight : ('a, 'b) either -> 'c
val either_partition : ('a -> ('b, 'c) either) -> 'a0 list -> 'b0 list * 'c0 list

This module isn't used but creates a dependency on deriving, which we would like to avoid module EitherMonad = Deriving_monad.MonadPlusUtils( struct type 'a m = (string, 'a) either let return v = Right v let (>>=) m k = match m with | Left _ as l -> l | Right r -> k r let fail msg = Left msg let (>>) x y = x >>= fun _ -> y let mzero = Left "no error" let mplus l r = match l with | Left _ -> r | m -> m end)*

module Queue : sig ... end
module OptionUtils : sig ... end
include module type of struct include OptionUtils end
exception EmptyOption
val val_of : 'a option -> 'b
val is_some : 'a option -> bool
val opt_app : ('a -> 'b) -> 'c -> 'd option -> 'e
val opt_map : ('a -> 'b) -> 'c option -> 'd option
val opt_bind : ('a -> 'b option) -> 'c option -> 'b option
val opt_split : ('a * 'b) option -> 'c option * 'd option
val opt_iter : ('a -> 'b) -> 'a option -> unit
val from_option : 'a -> 'b option -> 'c
val perhaps_apply : ('a -> 'b option) -> 'c -> 'd
val opt_as_list : 'a option -> 'b list
val opt_sequence : 'a option list -> 'a list option
val some : 'a -> 'a option
val (>>=?) : 'a option -> ('a -> 'b option) -> 'b option
val (||=?) : 'a option -> 'a option -> 'a option
val (>>==?) : 'a list -> ('a0 -> 'a0 option) -> 'a1 list option
val map_tryPick : (StringMap.key -> 'a -> 'b option) -> 'c StringMap.t -> 'b option
val list_tryPick : ('a -> 'b option) -> 'c list -> 'b option

Character Encoding

*

Read a three-digit octal escape sequence and return the corresponding char

val read_octal : string -> char
val read_hex : string -> char
val escape_regexp : Notfound.Str.regexp

Handle escape sequences in string literals.

val decode_escapes : string -> string
val xml_escape : string -> string

xml_escape, xml_unescape Escape/unescape for XML escape sequences (e.g. &amp;)

val xml_unescape : string -> string
val base64decode : string -> string

(0 base64 Routines)

val base64encode : string -> string
val gensym_counter : int ref
val gensym : ?prefix:string -> unit -> string

Any two calls to gensym return distinct strings. The optional prefix argument can be used to supply a prefix for the string.

val pair_fresh_names : ?prefix:string -> 'a list -> ('a * string) list

gensym a new symbol for each item in the list and return the pairs of each item with its new name, always using the optional prefix argument as the prefix if given. The "graph" of the gensym function, if you will.

val refresh_names : string list -> (string * string) list

Given a list of names, generate a fresh name for each and pair the old name with the new one.

val any_true : bool list -> bool

Return true if any element of the given list is true

System interaction

val getenv : string -> string option

Get an environment variable, return Some x if it is defined as x, or None if it is not in the environment.

val safe_getenv : string -> string

Get an environment variable, return its value if it is defined, or raise an exception if it is not in the environment.

module Buffer = Notfound.Buffer
module Hashtbl = Notfound.Hashtbl
module List = Notfound.List
module ListLabels = Notfound.ListLabels
module MoreLabels = Notfound.MoreLabels
module Str = Notfound.Str
module StringLabels = Notfound.StringLabels
module Sys = Notfound.Sys
module Unix = Notfound.Unix
module UnixLabels = Notfound.UnixLabels
module Printexc = Notfound.Printexc
exception NotFound of string
val pow : int -> int -> int

the integer power function

val string_of_float' : float -> string

string of float with a trailing 0

val time_seconds : unit -> int
val time_milliseconds : unit -> int
val time_microseconds : unit -> int
val strip_leading_slash : string -> string
val strip_trailing_slash : string -> string
val strip_slashes : string -> string
val format_omission : Format.formatter -> unit
module Disk : sig ... end
module type GLOB_POLICY = sig ... end
module Glob : sig ... end
val locate_file : string -> string
module LwtHelpers : sig ... end
module PolyBuffer : sig ... end
module CalendarShow : sig ... end
module UnixTimestamp : sig ... end
module IO : sig ... end