Module Base

include module type of sig ... end with module Array := Caml.Array with module Buffer := Caml.Buffer with module Char := Caml.Char with module Hashtbl := Caml.Hashtbl with module Int32 := Caml.Int32 with module Int64 := Caml.Int64 with module Lazy := Caml.Lazy with module List := Caml.List with module Map := Caml.Map with module Nativeint := Caml.Nativeint with module Printf := Caml.Printf with module Random := Caml.Random with module Set := Caml.Set with module String := Caml.String with module Sys := Caml.Sys with module Uchar := Caml.Uchar with module Lexing := Caml.Lexing with type (a, b, c) format := (a, b, c) Pervasives.format with type (a, b, c, d) format4 := (a, b, c, d) Pervasives.format4 with type (a, b, c, d, e, f) format6 := (a, b, c, d, e, f) Pervasives.format6 with type ref := a Pervasives.ref
module Arg = Arg
module Array = Array
module ArrayLabels = ArrayLabels
module Buffer = Buffer
module Bytes = Bytes
module BytesLabels = BytesLabels
module Callback = Callback
module Char = Char
module Complex = Complex
module Digest = Digest
module Ephemeron = Ephemeron
module Filename = Filename
module Format = Format
module Gc = Gc
module Genlex = Genlex
module Hashtbl = Hashtbl
module Int32 = Int32
module Int64 = Int64
module Lazy = Lazy
module Lexing = Lexing
module List = List
module ListLabels = ListLabels
module Map = Map
module Marshal = Marshal
module MoreLabels = MoreLabels
module Nativeint = Nativeint
module Obj = Obj
module Oo = Oo
module Parsing = Parsing
module Pervasives = Pervasives
module Printexc = Printexc
module Printf = Printf
module Queue = Queue
module Random = Random
module Scanf = Scanf
module Set = Set
module Sort = Sort
module Spacetime = Spacetime
module Stack = Stack
module StdLabels = StdLabels
module Stream = Stream
module String = String
module StringLabels = StringLabels
module Sys = Sys
module Uchar = Uchar
module Weak = Weak
external raise : exn ‑> 'a =
external raise_notrace : exn ‑> 'a =
val invalid_arg : string ‑> 'a
val failwith : string ‑> 'a
exception Exit
external (=) : 'a ‑> 'a ‑> bool =
external (<>) : 'a ‑> 'a ‑> bool =
external (<) : 'a ‑> 'a ‑> bool =
external (>) : 'a ‑> 'a ‑> bool =
external (<=) : 'a ‑> 'a ‑> bool =
external (>=) : 'a ‑> 'a ‑> bool =
external compare : 'a ‑> 'a ‑> int =
val min : 'a ‑> 'a ‑> 'a
val max : 'a ‑> 'a ‑> 'a
external (==) : 'a ‑> 'a ‑> bool =
external (!=) : 'a ‑> 'a ‑> bool =
external not : bool ‑> bool =
external (&&) : bool ‑> bool ‑> bool =
external (&) : bool ‑> bool ‑> bool =
external (||) : bool ‑> bool ‑> bool =
external or : bool ‑> bool ‑> bool =
external __LOC__ : string =
external __FILE__ : string =
external __LINE__ : int =
external __MODULE__ : string =
external __POS__ : string * int * int * int =
external __LOC_OF__ : 'a ‑> string * 'a =
external __LINE_OF__ : 'a ‑> int * 'a =
external __POS_OF__ : 'a ‑> (string * int * int * int) * 'a =
external (|>) : 'a ‑> ('a ‑> 'b) ‑> 'b =
external (@@) : ('a ‑> 'b) ‑> 'a ‑> 'b =
external (~-) : int ‑> int =
external (~+) : int ‑> int =
external succ : int ‑> int =
external pred : int ‑> int =
external (+) : int ‑> int ‑> int =
external (-) : int ‑> int ‑> int =
external (*) : int ‑> int ‑> int =
external (/) : int ‑> int ‑> int =
external (mod) : int ‑> int ‑> int =
val abs : int ‑> int
val max_int : int
val min_int : int
external (land) : int ‑> int ‑> int =
external (lor) : int ‑> int ‑> int =
external (lxor) : int ‑> int ‑> int =
val (lnot) : int ‑> int
external (lsl) : int ‑> int ‑> int =
external (lsr) : int ‑> int ‑> int =
external (asr) : int ‑> int ‑> int =
external (~-.) : float ‑> float =
external (~+.) : float ‑> float =
external (+.) : float ‑> float ‑> float =
external (-.) : float ‑> float ‑> float =
external (*.) : float ‑> float ‑> float =
external (/.) : float ‑> float ‑> float =
external (**) : float ‑> float ‑> float =
external sqrt : float ‑> float =
external exp : float ‑> float =
external log : float ‑> float =
external log10 : float ‑> float =
external expm1 : float ‑> float =
external log1p : float ‑> float =
external cos : float ‑> float =
external sin : float ‑> float =
external tan : float ‑> float =
external acos : float ‑> float =
external asin : float ‑> float =
external atan : float ‑> float =
external atan2 : float ‑> float ‑> float =
external hypot : float ‑> float ‑> float =
external cosh : float ‑> float =
external sinh : float ‑> float =
external tanh : float ‑> float =
external ceil : float ‑> float =
external floor : float ‑> float =
external abs_float : float ‑> float =
external copysign : float ‑> float ‑> float =
external mod_float : float ‑> float ‑> float =
external frexp : float ‑> float * int =
external ldexp : float ‑> int ‑> float =
external modf : float ‑> float * float =
external float : int ‑> float =
external float_of_int : int ‑> float =
external truncate : float ‑> int =
external int_of_float : float ‑> int =
val infinity : float
val neg_infinity : float
val nan : float
val max_float : float
val min_float : float
val epsilon_float : float
type fpclass = Pervasives.fpclass =
| FP_normal
| FP_subnormal
| FP_zero
| FP_infinite
| FP_nan
external classify_float : float ‑> fpclass =
val (^) : string ‑> string ‑> string
external int_of_char : char ‑> int =
val char_of_int : int ‑> char
external ignore : 'a ‑> unit =
val string_of_bool : bool ‑> string
val bool_of_string : string ‑> bool
val string_of_int : int ‑> string
external int_of_string : string ‑> int =
val string_of_float : float ‑> string
external float_of_string : string ‑> float =
external fst : ('a * 'b) ‑> 'a =
external snd : ('a * 'b) ‑> 'b =
val (@) : 'a list ‑> 'a list ‑> 'a list
type in_channel = Pervasives.in_channel
type out_channel = Pervasives.out_channel
val stdin : in_channel
val stdout : out_channel
val stderr : out_channel
val print_char : char ‑> unit
val print_string : string ‑> unit
val print_bytes : bytes ‑> unit
val print_int : int ‑> unit
val print_float : float ‑> unit
val print_endline : string ‑> unit
val print_newline : unit ‑> unit
val prerr_char : char ‑> unit
val prerr_string : string ‑> unit
val prerr_bytes : bytes ‑> unit
val prerr_int : int ‑> unit
val prerr_float : float ‑> unit
val prerr_endline : string ‑> unit
val prerr_newline : unit ‑> unit
val read_line : unit ‑> string
val read_int : unit ‑> int
val read_float : unit ‑> float
type open_flag = Pervasives.open_flag =
| Open_rdonly
| Open_wronly
| Open_append
| Open_creat
| Open_trunc
| Open_excl
| Open_binary
| Open_text
| Open_nonblock
val open_out : string ‑> out_channel
val open_out_bin : string ‑> out_channel
val open_out_gen : open_flag list ‑> int ‑> string ‑> out_channel
val flush : out_channel ‑> unit
val flush_all : unit ‑> unit
val output_char : out_channel ‑> char ‑> unit
val output_string : out_channel ‑> string ‑> unit
val output_bytes : out_channel ‑> bytes ‑> unit
val output : out_channel ‑> bytes ‑> int ‑> int ‑> unit
val output_substring : out_channel ‑> string ‑> int ‑> int ‑> unit
val output_byte : out_channel ‑> int ‑> unit
val output_binary_int : out_channel ‑> int ‑> unit
val output_value : out_channel ‑> 'a ‑> unit
val seek_out : out_channel ‑> int ‑> unit
val pos_out : out_channel ‑> int
val out_channel_length : out_channel ‑> int
val close_out : out_channel ‑> unit
val close_out_noerr : out_channel ‑> unit
val set_binary_mode_out : out_channel ‑> bool ‑> unit
val open_in : string ‑> in_channel
val open_in_bin : string ‑> in_channel
val open_in_gen : open_flag list ‑> int ‑> string ‑> in_channel
val input_char : in_channel ‑> char
val input_line : in_channel ‑> string
val input : in_channel ‑> bytes ‑> int ‑> int ‑> int
val really_input : in_channel ‑> bytes ‑> int ‑> int ‑> unit
val really_input_string : in_channel ‑> int ‑> string
val input_byte : in_channel ‑> int
val input_binary_int : in_channel ‑> int
val input_value : in_channel ‑> 'a
val seek_in : in_channel ‑> int ‑> unit
val pos_in : in_channel ‑> int
val in_channel_length : in_channel ‑> int
val close_in : in_channel ‑> unit
val close_in_noerr : in_channel ‑> unit
val set_binary_mode_in : in_channel ‑> bool ‑> unit
module LargeFile = Pervasives.LargeFile
type 'a ref = 'a Pervasives.ref = {
mutable contents : 'a;
}
external ref : 'a ‑> 'a ref =
external (!) : 'a ref ‑> 'a =
external (:=) : 'a ref ‑> 'a ‑> unit =
external incr : int ref ‑> unit =
external decr : int ref ‑> unit =
type ('a, 'b) result = ('a'b) Pervasives.result =
| Ok of 'a
| Error of 'b
type ('a, 'b, 'c, 'd, 'e, 'f) format6 = ('a'b'c'd'e'f) CamlinternalFormatBasics.format6
type ('a, 'b, 'c, 'd) format4 = ('a'b'c'c'c'dformat6
type ('a, 'b, 'c) format = ('a'b'c'cformat4
val string_of_format : ('a'b'c'd'e'fformat6 ‑> string
external format_of_string : ('a'b'c'd'e'fformat6 ‑> ('a'b'c'd'e'fformat6 =
val (^^) : ('a'b'c'd'e'fformat6 ‑> ('f'b'c'e'g'hformat6 ‑> ('a'b'c'd'g'hformat6
val exit : int ‑> 'a
val at_exit : (unit ‑> unit) ‑> unit
val valid_float_lexem : string ‑> string
val unsafe_really_input : in_channel ‑> bytes ‑> int ‑> int ‑> unit
val do_at_exit : unit ‑> unit
module Applicative : sig ... end
module Applicative_intf : sig ... end

Applicatives model computations in which values computed by subcomputations cannot affect what subsequent computations will take place. Relative to monads, this restriction takes power away from the user of the interface and gives it to the implementation. In particular, because the structure of the entire computation is known, one can augment its definition with some description of that structure.

module Array : sig ... end
module Avltree : sig ... end

A low-level, mutable AVL tree.

module Backtrace : sig ... end

Dealing with stack backtraces.

module Binary_searchable : sig ... end

See Binary_searchable_intf.

module Binary_searchable_intf : sig ... end

Module types for a binary_search function for a sequence, and functors for building binary_search functions.

module Blit : sig ... end

See Blit_intf for documentation.

module Blit_intf : sig ... end

Standard type for blit functions, and reusable code for validating blit arguments.

module Bool : sig ... end
module Buffer : sig ... end
module Char : sig ... end

Character operations.

module Commutative_group : sig ... end

A signature for a commutative group (in the group-theory sense).

module Comparable : sig ... end
module Comparable_intf : 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 Container : sig ... end
module Container_intf : sig ... end

This file has generic signatures for container data structures, with standard functions (iter, fold, exists, for_all, ...) that one would expect to find in any container. The idea is to include Container.S0 or Container.S1 in the signature for every container-like data structure (Array, List, String, ...) to ensure a consistent interface.

module Either : sig ... end
module Either_intf : sig ... end

Many functions in Either focus on just one constructor. The Focused signature abstracts over which constructor is the focus. To use these functions, use the First or Second modules in S.

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

sexp_of_t uses a global table of sexp converters. To register a converter for a new exception, add [@@deriving_inline sexp][@@@end] to its definition. If no suitable converter is found, the standard converter in Printexc will be used to generate an atomic S-expression.

module Field : sig ... end

OCaml record field.

module Float : sig ... end

Floating-point representation and utilities.

module Floatable : sig ... end
module Fn : sig ... end

various combinators for functions

module Hash : sig ... end
module Hash_intf : sig ... end

Hash_intf.S is the interface which a hash-function must support

module Hash_set : sig ... end
module Hash_set_intf : sig ... end
module Hasher : sig ... end

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

module Hashtbl : sig ... end
module Hashtbl_intf : sig ... end
module Heap_block : sig ... end

A heap block is a value that is guaranteed to live on the OCaml heap, and is hence guaranteed to be usable with finalization or in a weak pointer. It is an abstract type so we can use the type system to guarantee that the values we put in weak pointers and use with finalizers are heap blocks.

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 Info_intf : sig ... end

Info is a library for lazily constructing human-readable information as a string or sexp, with a primary use being error messages. Using Info is often preferable to sprintf or manually constructing strings because you don't have to eagerly construct the string --- you only need to pay when you actually want to display the info. which for many applications is rare. Using Info is also better than creating custom exceptions because you have more control over the format.

module Int : sig ... end

OCaml's native integer type.

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
module Int_intf : sig ... end
module Intable : sig ... end
module Invariant : sig ... end
module Lazy : sig ... end

This file is a modified version of lazy.mli from the OCaml distribution.

module List : sig ... end

List operations.

module Map : sig ... end
module Map_intf : sig ... end

See map.mli for comments.

module Maybe_bound : sig ... end
module Monad : sig ... end
module Nativeint : sig ... end
module Option : sig ... end
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
module Ordering : sig ... end

Ordering is intended to make code that matches on the result of a comparison more concise and easier to read. For example, one would write:

module Poly : sig ... end
module Polymorphic_compare : sig ... end
module Polymorphic_compare_intf : sig ... end

Interfaces used for hiding and replacing polymorphic compare. Including a module with interface S should hide the majority of functions that use polymorphic compare.

module Popcount : sig ... end

This module exposes popcount functions for the various integer types. Functions are exposed in their respective modules.

module Pretty_printer : sig ... end

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

module Printf : sig ... end
module Linked_queue : sig ... end

This module is a wrapper around OCaml's standard Queue module that follows Base idioms and adds some functions. See Queue_intf for documentation of standard queue functions.

module Queue_intf : sig ... end

An interface for queues that follows Base's conventions, as opposed to OCaml's standard Queue module.

module Random : sig ... end

This is a slightly modified version of the OCaml standard library's random.mli. We want Base's Random module to be different from OCaml's standard one:

module Ref : sig ... end

Module for the type ref

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 Set_intf : sig ... end

See set.mli for comments.

module Sexpable : sig ... end

New code should use the @@deriving_inline sexp@@@end syntax directly. These module types (S, S1, S2, and S3) are exported for backwards compatibility only. *

module Sign : sig ... end

A simple type for representing the sign of a numeric value.

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 Staged : sig ... end

A type for making staging explicit in the type of a function. For example, you might want to have a function that creates a function for allocating unique identifiers. Rather than using the type:

module String : sig ... end

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

module Stringable : sig ... end
module String_dict : sig ... end

Efficient static string dictionaries. By static, we mean that new key-value pairs cannot be added after the dictionary is created.

module Sys : sig ... end

Cross-platform system configuration values.

module T : sig ... end
module Type_equal : sig ... end

For representing type equalities otherwise not known by the type-checker.

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. Allows standardized ways of checking for conditions, and keeps track of the location of errors by keeping a path to each error found. Thus, if you were validating the following datastructure:

module Variant : sig ... end

OCaml variant type.

module With_return : sig ... end

with_return f allows for something like the return statement in C within f. There are three ways f can terminate:

module Word_size : sig ... end

For determining the word size that the program is using.

module Sexp : sig ... end
module Exported_for_specific_uses : sig ... end
module Export : sig ... end
include Export
type 'a array = 'a Array.t
val array_of_sexp : a. (Base__.Sexplib.Sexp.t ‑> 'a) ‑> Base__.Sexplib.Sexp.t ‑> 'a array
val sexp_of_array : a. ('a ‑> Base__.Sexplib.Sexp.t) ‑> 'a array ‑> Base__.Sexplib.Sexp.t
val compare_array : a. ('a ‑> 'a ‑> int) ‑> 'a array ‑> 'a array ‑> int
type bool = Bool.t
val bool_of_sexp : Base__.Sexplib.Sexp.t ‑> bool
val sexp_of_bool : bool ‑> Base__.Sexplib.Sexp.t
val compare_bool : bool ‑> bool ‑> int
type char = Char.t
val char_of_sexp : Base__.Sexplib.Sexp.t ‑> char
val sexp_of_char : char ‑> Base__.Sexplib.Sexp.t
val compare_char : char ‑> char ‑> int
type exn = Exn.t
val sexp_of_exn : exn ‑> Base__.Sexplib.Sexp.t
type float = Float.t
val float_of_sexp : Base__.Sexplib.Sexp.t ‑> float
val sexp_of_float : float ‑> Base__.Sexplib.Sexp.t
val compare_float : float ‑> float ‑> int
type int = Int.t
val int_of_sexp : Base__.Sexplib.Sexp.t ‑> int
val sexp_of_int : int ‑> Base__.Sexplib.Sexp.t
val compare_int : int ‑> int ‑> int
type int32 = Int32.t
val int32_of_sexp : Base__.Sexplib.Sexp.t ‑> int32
val sexp_of_int32 : int32 ‑> Base__.Sexplib.Sexp.t
val compare_int32 : int32 ‑> int32 ‑> int
type int64 = Int64.t
val int64_of_sexp : Base__.Sexplib.Sexp.t ‑> int64
val sexp_of_int64 : int64 ‑> Base__.Sexplib.Sexp.t
val compare_int64 : int64 ‑> int64 ‑> int
type 'a list = 'a List.t
val list_of_sexp : a. (Base__.Sexplib.Sexp.t ‑> 'a) ‑> Base__.Sexplib.Sexp.t ‑> 'a list
val sexp_of_list : a. ('a ‑> Base__.Sexplib.Sexp.t) ‑> 'a list ‑> Base__.Sexplib.Sexp.t
val compare_list : a. ('a ‑> 'a ‑> int) ‑> 'a list ‑> 'a list ‑> int
type nativeint = Nativeint.t
val nativeint_of_sexp : Base__.Sexplib.Sexp.t ‑> nativeint
val sexp_of_nativeint : nativeint ‑> Base__.Sexplib.Sexp.t
val compare_nativeint : nativeint ‑> nativeint ‑> int
type 'a option = 'a Option.t
val option_of_sexp : a. (Base__.Sexplib.Sexp.t ‑> 'a) ‑> Base__.Sexplib.Sexp.t ‑> 'a option
val sexp_of_option : a. ('a ‑> Base__.Sexplib.Sexp.t) ‑> 'a option ‑> Base__.Sexplib.Sexp.t
val compare_option : a. ('a ‑> 'a ‑> int) ‑> 'a option ‑> 'a option ‑> int
type 'a ref = 'a Ref.t
val ref_of_sexp : a. (Base__.Sexplib.Sexp.t ‑> 'a) ‑> Base__.Sexplib.Sexp.t ‑> 'a ref
val sexp_of_ref : a. ('a ‑> Base__.Sexplib.Sexp.t) ‑> 'a ref ‑> Base__.Sexplib.Sexp.t
val compare_ref : a. ('a ‑> 'a ‑> int) ‑> 'a ref ‑> 'a ref ‑> int
type string = String.t
val string_of_sexp : Base__.Sexplib.Sexp.t ‑> string
val sexp_of_string : string ‑> Base__.Sexplib.Sexp.t
val compare_string : string ‑> string ‑> int
type unit = Unit.t
val unit_of_sexp : Base__.Sexplib.Sexp.t ‑> unit
val sexp_of_unit : unit ‑> Base__.Sexplib.Sexp.t
val compare_unit : unit ‑> unit ‑> int
type ('a, 'b, 'c) format = ('a'b'c) Pervasives.format

Format stuff

type ('a, 'b, 'c, 'd) format4 = ('a'b'c'd) Pervasives.format4
type ('a, 'b, 'c, 'd, 'e, 'f) format6 = ('a'b'c'd'e'f) Pervasives.format6

List operators

include List.Infix
val (@) : 'a Base__List.t ‑> 'a Base__List.t ‑> 'a Base__List.t

Int operators and comparisons

include Int.O

A sub-module designed to be opened to make working with ints more convenient.

include Int_intf.Operators_unbounded
type t
val (+) : t ‑> t ‑> t
val (-) : t ‑> t ‑> t
val (*) : t ‑> t ‑> t
val (/) : t ‑> t ‑> t
val (~-) : t ‑> t
include Polymorphic_compare_intf.Infix with type t := t
type t
val (>=) : t ‑> t ‑> bool
val (<=) : t ‑> t ‑> bool
val (=) : t ‑> t ‑> bool
val (>) : t ‑> t ‑> bool
val (<) : t ‑> t ‑> bool
val (<>) : t ‑> t ‑> bool
val abs : t ‑> t
val neg : t ‑> t
val zero : t
val of_int_exn : int ‑> t
val (%) : t ‑> t ‑> t
val (/%) : t ‑> t ‑> t
val (//) : t ‑> t ‑> float
val (land) : t ‑> t ‑> t
val (lor) : t ‑> t ‑> t
val (lxor) : t ‑> t ‑> t
val (lnot) : t ‑> t
val (lsl) : t ‑> int ‑> t
val (asr) : t ‑> int ‑> t
val (lsr) : t ‑> 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 ascending : int ‑> int ‑> int
val descending : int ‑> int ‑> int
val compare : int ‑> int ‑> int
val equal : int ‑> int ‑> bool
val max : int ‑> int ‑> int
val min : int ‑> int ‑> int
external (|>) : 'a ‑> ('a ‑> 'b) ‑> 'b = "%revapply"

Composition operator

external (&&) : bool ‑> bool ‑> bool = "%sequand"

Boolean operations

external (||) : bool ‑> bool ‑> bool = "%sequor"
external not : bool ‑> bool = "%boolnot"
external ignore : _ ‑> unit = "%ignore"
val (^) : String.t ‑> String.t ‑> String.t

Common string operations

external (!) : 'a ref ‑> 'a = "%field0"

Reference operations

external ref : 'a ‑> 'a ref = "%makemutable"
external (:=) : 'a ref ‑> 'a ‑> unit = "%setfield0"
val fst : ('a * 'b) ‑> 'a

Pair operations

val snd : ('a * 'b) ‑> 'b
val failwith : string ‑> 'a

Exceptions stuff

val invalid_arg : string ‑> 'a
val raise : exn ‑> 'a
val raise_s : Sexp.t ‑> 'a
val phys_equal : 'a ‑> 'a ‑> bool

Misc

module Not_exposed_properly : sig ... end