Module Base
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
, andComparisons
in lieu of polymorphic compare.Container
, which provides a consistent interface across container-like data structures (arrays, lists, strings).Result
,Error
, andOr_error
, supporting the or-error pattern.
The recommended way to use Base is to build with -open Base
. Files compiled this way will have the environment described in this file as their initial environment.
module Applicative : sig ... end
module Array : sig ... end
Mutable vector of elements with O(1)
get
andset
operations.
module Avltree : sig ... end
A low-level, mutable AVL tree.
module Backtrace : sig ... end
Module for managing stack backtraces.
module Binary_search : sig ... end
Functions for performing binary searches over ordered sequences given
length
andget
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
module Comparator : sig ... end
A type-indexed value that allows one to compare (and for generating error messages, serialize) values of the type in question.
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
module Hashtbl : sig ... end
module Identifiable : sig ... end
A signature combining functionality that is commonly used for types that are intended to act as names or identifiers.
module Indexed_container : sig ... end
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
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
module Maybe_bound : sig ... end
Used for specifying a bound (either upper or lower) as inclusive, exclusive, or unbounded.
module Monad : sig ... end
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
Option type.
module Option_array : sig ... end
'a Option_array.t
is a compact representation of'a option array
: it avoids allocating heap objects representingSome x
, usually representing them withx
instead. It uses a special representation forNone
that's guaranteed to never collide with any representation ofSome x
.
module Or_error : sig ... end
Type for tracking errors in an
Error.t
. This is a specialization of theResult
type, where theError
constructor carries anError.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
module Polymorphic_compare = Poly
module Popcount : sig ... end
This module exposes popcount functions (which count the number of ones in a bitstring) for the various integer types.
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
module Random : sig ... end
Pseudo-random number generation.
module Ref : sig ... end
Module for the type
ref
, mutable indirection cellsr
containing a value of type'a
, accessed with!r
and set byr := 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
module Sexpable : sig ... end
Provides functors for making modules sexpable. New code should use the
[@@deriving sexp]
syntax directly. These module types (S
,S1
,S2
, andS3
) are exported for backwards compatibility only.
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 aNan
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 theppx_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 youopen Base
, you'll get these extensions in theString
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 withDouble_array_tag
, the tag for float arrays.
module Unit : sig ... end
Module for the type
unit
.
module Uchar : sig ... end
Unicode character operations.
module Validate : sig ... end
A module for organizing validations of data structures.
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 withinf
.
module Word_size : sig ... end
For determining the word size that the program is using.
module Sexp : sig ... end
module Export : sig ... end
include Export
include Sexp.Private.Raw_grammar.Builtin
val unit_sexp_grammar : Sexplib0.Sexp.Private.Raw_grammar.t
val bool_sexp_grammar : Sexplib0.Sexp.Private.Raw_grammar.t
val string_sexp_grammar : Sexplib0.Sexp.Private.Raw_grammar.t
val bytes_sexp_grammar : Sexplib0.Sexp.Private.Raw_grammar.t
val char_sexp_grammar : Sexplib0.Sexp.Private.Raw_grammar.t
val int_sexp_grammar : Sexplib0.Sexp.Private.Raw_grammar.t
val float_sexp_grammar : Sexplib0.Sexp.Private.Raw_grammar.t
val int32_sexp_grammar : Sexplib0.Sexp.Private.Raw_grammar.t
val int64_sexp_grammar : Sexplib0.Sexp.Private.Raw_grammar.t
val nativeint_sexp_grammar : Sexplib0.Sexp.Private.Raw_grammar.t
val ref_sexp_grammar : Sexplib0.Sexp.Private.Raw_grammar.t
val lazy_t_sexp_grammar : Sexplib0.Sexp.Private.Raw_grammar.t
val option_sexp_grammar : Sexplib0.Sexp.Private.Raw_grammar.t
val list_sexp_grammar : Sexplib0.Sexp.Private.Raw_grammar.t
val array_sexp_grammar : Sexplib0.Sexp.Private.Raw_grammar.t
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 array_of_sexp : a. (Sexp.t -> 'a) -> Sexp.t -> 'a array
val sexp_of_array : a. ('a -> Sexp.t) -> 'a array -> Sexp.t
val array_sexp_grammar : Sexp.Private.Raw_grammar.t
type bool
= Bool.t
val compare_bool : bool -> bool -> int
val equal_bool : bool -> bool -> bool
val hash_fold_bool : Hash.state -> bool -> Hash.state
val hash_bool : bool -> Hash.hash_value
val bool_of_sexp : Sexp.t -> bool
val sexp_of_bool : bool -> Sexp.t
val bool_sexp_grammar : Sexp.Private.Raw_grammar.t
type char
= Char.t
val compare_char : char -> char -> int
val equal_char : char -> char -> bool
val hash_fold_char : Hash.state -> char -> Hash.state
val hash_char : char -> Hash.hash_value
val char_of_sexp : Sexp.t -> char
val sexp_of_char : char -> Sexp.t
val char_sexp_grammar : Sexp.Private.Raw_grammar.t
type exn
= Exn.t
type float
= Float.t
val compare_float : float -> float -> int
val equal_float : float -> float -> bool
val hash_fold_float : Hash.state -> float -> Hash.state
val hash_float : float -> Hash.hash_value
val float_of_sexp : Sexp.t -> float
val sexp_of_float : float -> Sexp.t
val float_sexp_grammar : Sexp.Private.Raw_grammar.t
type int
= Int.t
val compare_int : int -> int -> int
val equal_int : int -> int -> bool
val hash_fold_int : Hash.state -> int -> Hash.state
val hash_int : int -> Hash.hash_value
val int_of_sexp : Sexp.t -> int
val sexp_of_int : int -> Sexp.t
val int_sexp_grammar : Sexp.Private.Raw_grammar.t
type int32
= Int32.t
val compare_int32 : int32 -> int32 -> int
val equal_int32 : int32 -> int32 -> bool
val hash_fold_int32 : Hash.state -> int32 -> Hash.state
val hash_int32 : int32 -> Hash.hash_value
val int32_of_sexp : Sexp.t -> int32
val sexp_of_int32 : int32 -> Sexp.t
val int32_sexp_grammar : Sexp.Private.Raw_grammar.t
type int64
= Int64.t
val compare_int64 : int64 -> int64 -> int
val equal_int64 : int64 -> int64 -> bool
val hash_fold_int64 : Hash.state -> int64 -> Hash.state
val hash_int64 : int64 -> Hash.hash_value
val int64_of_sexp : Sexp.t -> int64
val sexp_of_int64 : int64 -> Sexp.t
val int64_sexp_grammar : Sexp.Private.Raw_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 hash_fold_list : a. (Hash.state -> 'a -> Hash.state) -> Hash.state -> 'a list -> Hash.state
val list_of_sexp : a. (Sexp.t -> 'a) -> Sexp.t -> 'a list
val sexp_of_list : a. ('a -> Sexp.t) -> 'a list -> Sexp.t
val list_sexp_grammar : Sexp.Private.Raw_grammar.t
type nativeint
= Nativeint.t
val compare_nativeint : nativeint -> nativeint -> int
val equal_nativeint : nativeint -> nativeint -> bool
val hash_fold_nativeint : Hash.state -> nativeint -> Hash.state
val hash_nativeint : nativeint -> Hash.hash_value
val nativeint_of_sexp : Sexp.t -> nativeint
val sexp_of_nativeint : nativeint -> Sexp.t
val nativeint_sexp_grammar : Sexp.Private.Raw_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 hash_fold_option : a. (Hash.state -> 'a -> Hash.state) -> Hash.state -> 'a option -> Hash.state
val option_of_sexp : a. (Sexp.t -> 'a) -> Sexp.t -> 'a option
val sexp_of_option : a. ('a -> Sexp.t) -> 'a option -> Sexp.t
val option_sexp_grammar : Sexp.Private.Raw_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 ref_of_sexp : a. (Sexp.t -> 'a) -> Sexp.t -> 'a ref
val sexp_of_ref : a. ('a -> Sexp.t) -> 'a ref -> Sexp.t
val ref_sexp_grammar : Sexp.Private.Raw_grammar.t
type string
= String.t
val compare_string : string -> string -> int
val equal_string : string -> string -> bool
val hash_fold_string : Hash.state -> string -> Hash.state
val hash_string : string -> Hash.hash_value
val string_of_sexp : Sexp.t -> string
val sexp_of_string : string -> Sexp.t
val string_sexp_grammar : Sexp.Private.Raw_grammar.t
type bytes
= Bytes.t
val compare_bytes : bytes -> bytes -> int
val equal_bytes : bytes -> bytes -> bool
val bytes_of_sexp : Sexp.t -> bytes
val sexp_of_bytes : bytes -> Sexp.t
val bytes_sexp_grammar : Sexp.Private.Raw_grammar.t
type unit
= Unit.t
val compare_unit : unit -> unit -> int
val equal_unit : unit -> unit -> bool
val hash_fold_unit : Hash.state -> unit -> Hash.state
val hash_unit : unit -> Hash.hash_value
val unit_of_sexp : Sexp.t -> unit
val sexp_of_unit : unit -> Sexp.t
val unit_sexp_grammar : Sexp.Private.Raw_grammar.t
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
Sexp
Exporting the ad-hoc types that are recognized by ppx_sexp_*
converters. sexp_array
, sexp_list
, and sexp_option
allow a record field to be absent when converting from a sexp, and if absent, the field will take a default value of the appropriate type:
sexp_array [||] sexp_bool false sexp_list [] sexp_option None
sexp_opaque
causes the conversion to sexp to produce the atom <opaque>
.
For more documentation, see sexplib/README.md.
type 'a sexp_array
= 'a array
type 'a sexp_list
= 'a list
type 'a sexp_opaque
= 'a
type 'a sexp_option
= 'a option
include List.Infix
val (@) : 'a Base__List.t -> 'a Base__List.t -> 'a Base__List.t
include Int.O
val (+) : Base__Int.t -> Base__Int.t -> Base__Int.t
val (-) : Base__Int.t -> Base__Int.t -> Base__Int.t
val (*) : Base__Int.t -> Base__Int.t -> Base__Int.t
val (/) : Base__Int.t -> Base__Int.t -> Base__Int.t
val (~-) : Base__Int.t -> Base__Int.t
val (**) : Base__Int.t -> Base__Int.t -> Base__Int.t
val (>=) : Base__Int.t -> Base__Int.t -> bool
val (<=) : Base__Int.t -> Base__Int.t -> bool
val (=) : Base__Int.t -> Base__Int.t -> bool
val (>) : Base__Int.t -> Base__Int.t -> bool
val (<) : Base__Int.t -> Base__Int.t -> bool
val (<>) : Base__Int.t -> Base__Int.t -> bool
val abs : Base__Int.t -> Base__Int.t
val neg : Base__Int.t -> Base__Int.t
val zero : Base__Int.t
val (%) : Base__Int.t -> Base__Int.t -> Base__Int.t
val (/%) : Base__Int.t -> Base__Int.t -> Base__Int.t
val (//) : Base__Int.t -> Base__Int.t -> float
val (land) : Base__Int.t -> Base__Int.t -> Base__Int.t
val (lor) : Base__Int.t -> Base__Int.t -> Base__Int.t
val (lxor) : Base__Int.t -> Base__Int.t -> Base__Int.t
val (lnot) : Base__Int.t -> Base__Int.t
val (lsl) : Base__Int.t -> int -> Base__Int.t
val (asr) : Base__Int.t -> int -> Base__Int.t
val (lsr) : Base__Int.t -> int -> Base__Int.t
include Base__.Import.Int_replace_polymorphic_compare
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 ascending : int -> int -> int
val descending : int -> int -> int
val equal : int -> int -> bool
val max : int -> int -> int
val min : int -> int -> int
include Float.O_dot
val (+.) : Base__Float.t -> Base__Float.t -> Base__Float.t
val (-.) : Base__Float.t -> Base__Float.t -> Base__Float.t
val (*.) : Base__Float.t -> Base__Float.t -> Base__Float.t
val (/.) : Base__Float.t -> Base__Float.t -> Base__Float.t
val (**.) : Base__Float.t -> Base__Float.t -> Base__Float.t
val (~-.) : Base__Float.t -> Base__Float.t
val (|>) : 'a -> ('a -> 'b) -> 'b
Reverse application operator.
x |> g |> f
is equivalent tof (g (x))
.
val (&&) : bool -> bool -> bool
val (||) : bool -> bool -> bool
val not : bool -> bool
val ignore : _ -> unit
val raise : exn -> _
val failwith : string -> 'a
val invalid_arg : string -> 'a
val raise_s : Sexp.t -> 'a
val force : 'a Lazy.t -> 'a
module Continue_or_stop = Base__.Container_intf.Export.Continue_or_stop
Continue_or_stop.t
is used by thef
argument tofold_until
in order to indicate whether folding should continue, or stop early.
exception
Not_found_s of Sexplib0.Sexp.t