package base

  1. Overview
  2. Docs
Legend:
Library
Module
Module type
Parameter
Class
Class type

This module is the toplevel of the Base library; it's what you get when you write open Base.

The goal of Base is both to be a more complete standard library, with richer APIs, and to be more consistent in its design. For instance, in the standard library some things have modules and others don't; in Base, everything is a module.

Base extends some modules and data structures from the standard library, like Array, Buffer, Bytes, Char, Hashtbl, Int32, Int64, Lazy, List, Map, Nativeint, Printf, Random, Set, String, Sys, and Uchar. One key difference is that Base doesn't use exceptions as much as the standard library and instead makes heavy use of the Result type, as in:

type ('a,'b) result = Ok of 'a | Error of 'b 

Base also adds entirely new modules, most notably:

  • Comparable, Comparator, and Comparisons in lieu of polymorphic compare.
  • Container, which provides a consistent interface across container-like data structures (arrays, lists, strings).
  • Result, Error, and Or_error, supporting the or-error pattern.
module Applicative : sig ... end
module Array : sig ... end

Fixed-length, mutable vector of elements with O(1) get and set operations.

module Avltree : sig ... end

A low-level, mutable AVL tree.

module Backtrace : sig ... end

Module for managing stack backtraces.

Functions for performing binary searches over ordered sequences given length and get functions.

module Binary_searchable : sig ... end
module Blit : sig ... end
module Bool : sig ... end

Boolean type extended to be enumerable, hashable, sexpable, comparable, and stringable.

module Buffer : sig ... end

Extensible character buffers.

module Bytes : sig ... end

OCaml's byte sequence type, semantically similar to a char array, but taking less space in memory.

module Char : sig ... end

A type for 8-bit characters.

module Comparable : sig ... end

Defines functors for making modules comparable.

module Comparator : sig ... end

Comparison and serialization for a type, using a witness type to distinguish between comparison functions with different behavior.

module Comparisons : sig ... end

Interfaces for infix comparison operators and comparison functions.

module Container : sig ... end
module Either : sig ... end
module Equal : sig ... end

This module defines signatures that are to be included in other signatures to ensure a consistent interface to equal functions. There is a signature (S, S1, S2, S3) for each arity of type. Usage looks like:

module Error : sig ... end

A lazy string, implemented with Info, but intended specifically for error messages.

module Exn : sig ... end

Exceptions.

module Field : sig ... end

OCaml record field.

module Float : sig ... end

Floating-point representation and utilities.

module Floatable : sig ... end

Module type with float conversion functions.

module Fn : sig ... end

Various combinators for functions.

module Formatter : sig ... end

The Format.formatter type from OCaml's standard library, exported here for convenience and compatibility with other libraries.

module Hash : sig ... end
module Hash_set : sig ... end
module Hashable : sig ... end
module Hasher : sig ... end

Signatures required of types which can be used in [@@deriving hash].

module Hashtbl : sig ... end

A hash table is a mutable data structure implementing a map between keys and values. It supports constant-time lookup and in-place modification.

module Identifiable : sig ... end
module Indexed_container : sig ... end

Provides generic signatures for containers that support indexed iteration (iteri, foldi, ...). In principle, any container that has iter can also implement iteri, but the idea is that Indexed_container_intf should be included only for containers that have a meaningful underlying ordering.

module Info : sig ... end
module Int : sig ... end
module Int_conversions : sig ... end

Conversions between various integer types

module Int32 : sig ... end

An int of exactly 32 bits, regardless of the machine.

module Int63 : sig ... end

63-bit integers.

module Int64 : sig ... end

64-bit integers.

module Intable : sig ... end

Functor that adds integer conversion functions to a module.

module Int_math : sig ... end

This module implements derived integer operations (e.g., modulo, rounding to multiples) based on other basic operations.

module Invariant : sig ... end

This module defines signatures that are to be included in other signatures to ensure a consistent interface to invariant-style functions. There is a signature (S, S1, S2, S3) for each arity of type. Usage looks like:

module Lazy : sig ... end

A value of type 'a Lazy.t is a deferred computation, called a suspension, that has a result of type 'a.

module List : sig ... end

Immutable, singly-linked lists, giving fast access to the front of the list, and slow (i.e., O(n)) access to the back of the list. The comparison functions on lists are lexicographic.

module Map : sig ... end

Map is a functional data structure (balanced binary tree) implementing finite maps over a totally-ordered domain, called a "key".

module Maybe_bound : sig ... end

Used for specifying a bound (either upper or lower) as inclusive, exclusive, or unbounded.

module Monad : sig ... end

A monad is an abstraction of the concept of sequencing of computations. A value of type 'a monad represents a computation that returns a value of type 'a.

module Nativeint : sig ... end

Processor-native integers.

module Nothing : sig ... end

An uninhabited type. This is useful when interfaces require that a type be specified, but the implementer knows this type will not be used in their implementation of the interface.

module Option : sig ... end

The option type indicates whether a meaningful value is present. It is frequently used to represent success or failure, using None for failure. To be more descriptive about why a function failed, see the Or_error module.

module Option_array : sig ... end

'a Option_array.t is a compact representation of 'a option array: it avoids allocating heap objects representing Some x, usually representing them with x instead. It uses a special representation for None that's guaranteed to never collide with any representation of Some x.

module Or_error : sig ... end

Type for tracking errors in an Error.t. This is a specialization of the Result type, where the Error constructor carries an Error.t.

module Ordered_collection_common : sig ... end

Functions for ordered collections.

module Ordering : sig ... end

Ordering is intended to make code that matches on the result of a comparison more concise and easier to read.

module Poly : sig ... end

A module containing the ad-hoc polymorphic comparison functions. Useful when you want to use polymorphic compare in some small scope of a file within which polymorphic compare has been hidden

module Popcount : sig ... end
module Pretty_printer : sig ... end

A list of pretty printers for various types, for use in toplevels.

module Printf : sig ... end

Functions for formatted output.

module Linked_queue : sig ... end

This module is a Base-style wrapper around OCaml's standard Queue module.

module Queue : sig ... end

A queue implemented with an array.

module Random : sig ... end

Pseudo-random number generation.

module Ref : sig ... end

Module for the type ref, mutable indirection cells r containing a value of type 'a, accessed with !r and set by r := a.

module Result : sig ... end

Result is often used to handle error messages.

module Sequence : sig ... end

A sequence of elements that can be produced one at a time, on demand, normally with no sharing.

module Set : sig ... end

Sets based on Comparator.S.

module Sexpable : sig ... end

Provides functors for making modules sexpable when you want the sexp representation of one type to be the same as that for some other isomorphic type.

module Sign : sig ... end

A type for representing the sign of a numeric value.

module Sign_or_nan : sig ... end

An extension to Sign with a Nan constructor, for representing the sign of float-like numeric values.

module Source_code_position : sig ... end

One typically obtains a Source_code_position.t using a [%here] expression, which is implemented by the ppx_here preprocessor.

module Stack : sig ... end
module Staged : sig ... end

A type for making staging explicit in the type of a function.

module String : sig ... end

An extension of the standard StringLabels. If you open Base, you'll get these extensions in the String module.

module Stringable : sig ... end

Provides type-specific conversion functions to and from string.

module Sys : sig ... end

Cross-platform system configuration values.

module T : sig ... end

This module defines various abstract interfaces that are convenient when one needs a module that matches a bare signature with just a type. This sometimes occurs in functor arguments and in interfaces.

module Type_equal : sig ... end

The purpose of Type_equal is to represent type equalities that the type checker otherwise would not know, perhaps because the type equality depends on dynamic data, or perhaps because the type system isn't powerful enough.

module Uniform_array : sig ... end

Same semantics as 'a Array.t, except it's guaranteed that the representation array is not tagged with Double_array_tag, the tag for float arrays.

module Unit : sig ... end

Module for the type unit.

module Uchar : sig ... end

Unicode character operations.

module Variant : sig ... end

First-class representative of an individual variant in a variant type, used in [@@deriving variants].

module With_return : sig ... end

with_return f allows for something like the return statement in C within f.

module Word_size : sig ... end

For determining the word size that the program is using.

include module type of struct include T end
module type T = T.T
module type T1 = T.T1
module type T2 = T.T2
module type T3 = T.T3
module Sexp : sig ... end
module Export : sig ... end
include module type of struct include Export end
type 'a array = 'a Array.t
val compare_array : 'a. ('a -> 'a -> int) -> 'a array -> 'a array -> int
val equal_array : 'a. ('a -> 'a -> bool) -> 'a array -> 'a array -> bool
val globalize_array : 'a. ('a -> 'a) -> 'a array -> 'a array
val array_of_sexp : 'a. (Sexplib0.Sexp.t -> 'a) -> Sexplib0.Sexp.t -> 'a array
val sexp_of_array : 'a. ('a -> Sexplib0.Sexp.t) -> 'a array -> Sexplib0.Sexp.t
val array_sexp_grammar : 'a. 'a Sexplib0.Sexp_grammar.t -> 'a array Sexplib0.Sexp_grammar.t
type bool = Bool.t
val compare_bool : bool -> bool -> int
val equal_bool : bool -> bool -> bool
val globalize_bool : bool -> bool
val hash_fold_bool : Hash.state -> bool -> Hash.state
val hash_bool : bool -> Hash.hash_value
val bool_of_sexp : Sexplib0.Sexp.t -> bool
val sexp_of_bool : bool -> Sexplib0.Sexp.t
val bool_sexp_grammar : bool Sexplib0.Sexp_grammar.t
type char = Char.t
val compare_char : char -> char -> int
val equal_char : char -> char -> bool
val globalize_char : char -> char
val hash_fold_char : Hash.state -> char -> Hash.state
val hash_char : char -> Hash.hash_value
val char_of_sexp : Sexplib0.Sexp.t -> char
val sexp_of_char : char -> Sexplib0.Sexp.t
val char_sexp_grammar : char Sexplib0.Sexp_grammar.t
type exn = Exn.t
val sexp_of_exn : exn -> Sexplib0.Sexp.t
type float = Float.t
val compare_float : float -> float -> int
val equal_float : float -> float -> bool
val globalize_float : float -> float
val hash_fold_float : Hash.state -> float -> Hash.state
val hash_float : float -> Hash.hash_value
val float_of_sexp : Sexplib0.Sexp.t -> float
val sexp_of_float : float -> Sexplib0.Sexp.t
val float_sexp_grammar : float Sexplib0.Sexp_grammar.t
type int = Int.t
val compare_int : int -> int -> int
val equal_int : int -> int -> bool
val globalize_int : int -> int
val hash_fold_int : Hash.state -> int -> Hash.state
val hash_int : int -> Hash.hash_value
val int_of_sexp : Sexplib0.Sexp.t -> int
val sexp_of_int : int -> Sexplib0.Sexp.t
val int_sexp_grammar : int Sexplib0.Sexp_grammar.t
type int32 = Int32.t
val compare_int32 : int32 -> int32 -> int
val equal_int32 : int32 -> int32 -> bool
val globalize_int32 : int32 -> int32
val hash_fold_int32 : Hash.state -> int32 -> Hash.state
val hash_int32 : int32 -> Hash.hash_value
val int32_of_sexp : Sexplib0.Sexp.t -> int32
val sexp_of_int32 : int32 -> Sexplib0.Sexp.t
val int32_sexp_grammar : int32 Sexplib0.Sexp_grammar.t
type int64 = Int64.t
val compare_int64 : int64 -> int64 -> int
val equal_int64 : int64 -> int64 -> bool
val globalize_int64 : int64 -> int64
val hash_fold_int64 : Hash.state -> int64 -> Hash.state
val hash_int64 : int64 -> Hash.hash_value
val int64_of_sexp : Sexplib0.Sexp.t -> int64
val sexp_of_int64 : int64 -> Sexplib0.Sexp.t
val int64_sexp_grammar : int64 Sexplib0.Sexp_grammar.t
type 'a list = 'a List.t
val compare_list : 'a. ('a -> 'a -> int) -> 'a list -> 'a list -> int
val equal_list : 'a. ('a -> 'a -> bool) -> 'a list -> 'a list -> bool
val globalize_list : 'a. ('a -> 'a) -> 'a list -> 'a list
val hash_fold_list : 'a. (Hash.state -> 'a -> Hash.state) -> Hash.state -> 'a list -> Hash.state
val list_of_sexp : 'a. (Sexplib0.Sexp.t -> 'a) -> Sexplib0.Sexp.t -> 'a list
val sexp_of_list : 'a. ('a -> Sexplib0.Sexp.t) -> 'a list -> Sexplib0.Sexp.t
val list_sexp_grammar : 'a. 'a Sexplib0.Sexp_grammar.t -> 'a list Sexplib0.Sexp_grammar.t
type nativeint = Nativeint.t
val compare_nativeint : nativeint -> nativeint -> int
val equal_nativeint : nativeint -> nativeint -> bool
val globalize_nativeint : nativeint -> nativeint
val hash_fold_nativeint : Hash.state -> nativeint -> Hash.state
val hash_nativeint : nativeint -> Hash.hash_value
val nativeint_of_sexp : Sexplib0.Sexp.t -> nativeint
val sexp_of_nativeint : nativeint -> Sexplib0.Sexp.t
val nativeint_sexp_grammar : nativeint Sexplib0.Sexp_grammar.t
type 'a option = 'a Option.t
val compare_option : 'a. ('a -> 'a -> int) -> 'a option -> 'a option -> int
val equal_option : 'a. ('a -> 'a -> bool) -> 'a option -> 'a option -> bool
val globalize_option : 'a. ('a -> 'a) -> 'a option -> 'a option
val hash_fold_option : 'a. (Hash.state -> 'a -> Hash.state) -> Hash.state -> 'a option -> Hash.state
val option_of_sexp : 'a. (Sexplib0.Sexp.t -> 'a) -> Sexplib0.Sexp.t -> 'a option
val sexp_of_option : 'a. ('a -> Sexplib0.Sexp.t) -> 'a option -> Sexplib0.Sexp.t
val option_sexp_grammar : 'a. 'a Sexplib0.Sexp_grammar.t -> 'a option Sexplib0.Sexp_grammar.t
type 'a ref = 'a Ref.t
val compare_ref : 'a. ('a -> 'a -> int) -> 'a ref -> 'a ref -> int
val equal_ref : 'a. ('a -> 'a -> bool) -> 'a ref -> 'a ref -> bool
val globalize_ref : 'a. ('a -> 'a) -> 'a ref -> 'a ref
val ref_of_sexp : 'a. (Sexplib0.Sexp.t -> 'a) -> Sexplib0.Sexp.t -> 'a ref
val sexp_of_ref : 'a. ('a -> Sexplib0.Sexp.t) -> 'a ref -> Sexplib0.Sexp.t
val ref_sexp_grammar : 'a. 'a Sexplib0.Sexp_grammar.t -> 'a ref Sexplib0.Sexp_grammar.t
type string = String.t
val compare_string : string -> string -> int
val equal_string : string -> string -> bool
val globalize_string : string -> string
val hash_fold_string : Hash.state -> string -> Hash.state
val hash_string : string -> Hash.hash_value
val string_of_sexp : Sexplib0.Sexp.t -> string
val sexp_of_string : string -> Sexplib0.Sexp.t
val string_sexp_grammar : string Sexplib0.Sexp_grammar.t
type bytes = Bytes.t
val compare_bytes : bytes -> bytes -> int
val equal_bytes : bytes -> bytes -> bool
val globalize_bytes : bytes -> bytes
val bytes_of_sexp : Sexplib0.Sexp.t -> bytes
val sexp_of_bytes : bytes -> Sexplib0.Sexp.t
val bytes_sexp_grammar : bytes Sexplib0.Sexp_grammar.t
type unit = Unit.t
val compare_unit : unit -> unit -> int
val equal_unit : unit -> unit -> bool
val globalize_unit : unit -> unit
val hash_fold_unit : Hash.state -> unit -> Hash.state
val hash_unit : unit -> Hash.hash_value
val unit_of_sexp : Sexplib0.Sexp.t -> unit
val sexp_of_unit : unit -> Sexplib0.Sexp.t
val unit_sexp_grammar : unit Sexplib0.Sexp_grammar.t

Format stuff

type nonrec ('a, 'b, 'c) format = ('a, 'b, 'c) Stdlib.format
type nonrec ('a, 'b, 'c, 'd) format4 = ('a, 'b, 'c, 'd) Stdlib.format4
type nonrec ('a, 'b, 'c, 'd, 'e, 'f) format6 = ('a, 'b, 'c, 'd, 'e, 'f) Stdlib.format6

List operators

include module type of struct include List.Infix end
val (@) : 'a List.t -> 'a List.t -> 'a List.t

Int operators and comparisons

include module type of struct include Int.O end
val (+) : Int.t -> Int.t -> Int.t
val (-) : Int.t -> Int.t -> Int.t
val (*) : Int.t -> Int.t -> Int.t
val (/) : Int.t -> Int.t -> Int.t
val (~-) : Int.t -> Int.t
val (**) : Int.t -> Int.t -> Int.t
val (land) : Int.t -> Int.t -> Int.t
val (lor) : Int.t -> Int.t -> Int.t
val (lxor) : Int.t -> Int.t -> Int.t
val lnot : Int.t -> Int.t
val abs : Int.t -> Int.t
val neg : Int.t -> Int.t
val zero : Int.t
val (%) : Int.t -> Int.t -> Int.t
val (/%) : Int.t -> Int.t -> Int.t
val (//) : Int.t -> Int.t -> float
val (lsl) : Int.t -> int -> Int.t
val (asr) : Int.t -> int -> Int.t
val (lsr) : Int.t -> int -> Int.t
val (=) : int -> int -> bool
val (<>) : int -> int -> bool
val (<) : int -> int -> bool
val (>) : int -> int -> bool
val (<=) : int -> int -> bool
val (>=) : int -> int -> bool
val compare : int -> int -> int
val equal : int -> int -> bool
val ascending : int -> int -> int
val descending : int -> int -> int
val max : int -> int -> int
val min : int -> int -> int

Float operators

include module type of struct include Float.O_dot end

Similar to O, except that operators are suffixed with a dot, allowing one to have both int and float operators in scope simultaneously.

Similar to O, except that operators are suffixed with a dot, allowing one to have both int and float operators in scope simultaneously.

val (+.) : Float.t -> Float.t -> Float.t
val (-.) : Float.t -> Float.t -> Float.t
val (*.) : Float.t -> Float.t -> Float.t
val (/.) : Float.t -> Float.t -> Float.t
val (%.) : Float.t -> Float.t -> Float.t
val (**.) : Float.t -> Float.t -> Float.t
val (~-.) : Float.t -> Float.t
val (|>) : 'a -> ('a -> 'b) -> 'b

Reverse application operator. x |> g |> f is equivalent to f (g (x)).

val (@@) : ('a -> 'b) -> 'a -> 'b

Application operator. g @@ f @@ x is equivalent to g (f (x)).

Boolean operations

val (&&) : bool -> bool -> bool
val (||) : bool -> bool -> bool
val not : bool -> bool
val ignore : _ -> unit
val (^) : String.t -> String.t -> String.t

Common string operations

Reference operations

val (!) : 'a ref -> 'a
val ref : 'a -> 'a ref
val (:=) : 'a ref -> 'a -> unit

Pair operations

val fst : ('a * 'b) -> 'a
val snd : ('a * 'b) -> 'b

Exceptions stuff

val raise : exn -> _
val failwith : string -> 'a
val invalid_arg : string -> 'a
val raise_s : Sexp.t -> 'a

Misc

val phys_equal : 'a -> 'a -> bool
val force : 'a Lazy.t -> 'a
module Continue_or_stop = Container.Continue_or_stop

Continue_or_stop.t is used by the f argument to fold_until in order to indicate whether folding should continue, or stop early.

exception Not_found_s of Sexplib0.Sexp.t