Module Type.Gist

Type gists.

Type gists reflect the essence of your types as OCaml values of a given representation type.

Type gists are useful to type the interface of your values at the boundaries of your program or to devise generic type indexed functions.

See the quick start. The cookbook has simple description examples. Generic functions can be found in Fun.Generic and this is a generic function template to write your own.

Interfaces

Interfaces allow to directly inject types that satisfy a given interface in the representation.

Arrays

module type ARRAY = sig ... end

Array interface.

type ('elt, 'arr) array_module = (module ARRAY with type elt = 'elt and type t = 'arr)

The type for representing array types of type 'a with elements of type 'elt.

Maps

module type MAP = sig ... end

Map interface.

type ('k, 'v, 'm) map_module = (module MAP with type key = 'k and type t = 'm and type value = 'v)

The type for representing map types of type 'm mapping keys of type 'k to values of type 'v.

Type representation

module Meta : sig ... end

Gist metadata.

type type_name = string

The type for type names as accessed from the top level scope. E.g Buffer.t.

type case_name = string

The type for case constructor names as accessed from the top level scope. E.g. Either.Left.

type 'a scalar =
  1. | Unit : unit Meta.t -> unit scalar
  2. | Bool : bool Meta.t -> bool scalar
  3. | Char : char Meta.t -> char scalar
  4. | Uchar : Stdlib.Uchar.t Meta.t -> Stdlib.Uchar.t scalar
  5. | Int : int Meta.t -> int scalar
  6. | Int32 : int32 Meta.t -> int32 scalar
  7. | Int64 : int64 Meta.t -> int64 scalar
  8. | Nativeint : nativeint Meta.t -> nativeint scalar
  9. | Float : float Meta.t -> float scalar

The type for representing scalar types of type 'a. See scalars.

type bytes_encoding = [
  1. | `Bytes
  2. | `Utf_8
]

The type for specifying the two standard interpretations of OCaml bytes and string values.

type ('elt, 'arr) arraylike =
  1. | String : string Meta.t * bytes_encoding -> (char, string) arraylike
  2. | Bytes : bytes Meta.t * bytes_encoding -> (char, bytes) arraylike
  3. | Array : 'elt array Meta.t * 'elt t -> ('elt, 'elt array) arraylike
  4. | Bigarray1 : ('elt, 'b, 'c) Stdlib.Bigarray.Array1.t Meta.t * ('elt, 'b) Stdlib.Bigarray.kind * 'c Stdlib.Bigarray.layout * 'elt t -> ('elt, ('elt, 'b, 'c) Stdlib.Bigarray.Array1.t) arraylike
  5. | Array_module : 'arr Meta.t * ('elt, 'arr) array_module * 'elt t -> ('elt, 'arr) arraylike

The type for representing array types of type 'a with elements of type 'elt. See arraylike.

and ('k, 'v, 'm) maplike =
  1. | Hashtbl : ('k, 'v) Stdlib.Hashtbl.t Meta.t * 'k t * 'v t -> ('k, 'v, ('k, 'v) Stdlib.Hashtbl.t) maplike
  2. | Map_module : 'm Meta.t * ('k, 'v, 'm) map_module * 'k t * 'v t -> ('k, 'v, 'm) maplike

The type for representing map types of type 'm mapping keys of type 'k to values of type 'v. See maplike.

and 'p product

The type for representing product types of type 'p. See products.

and 'r record = 'r product

The type for representing record types of type 'r. See records.

and 'v variant

The type for representing variants of type 'v. See variants.

and 's sum =
  1. | Option : 'a option Meta.t * 'a t -> 'a option sum
  2. | Either : ('a, 'b) Stdlib.Either.t Meta.t * 'a t * 'b t -> ('a, 'b) Stdlib.Either.t sum
  3. | Result : ('a, 'b) Stdlib.result Meta.t * 'a t * 'b t -> ('a, 'b) Stdlib.result sum
  4. | List : 'a list Meta.t * 'a t -> 'a list sum
  5. | Variant : 'v variant -> 'v sum

The type for representing sum types of type 's. See sums.

and ('a, 'b) func

The type for representing functions types 'a -> 'b. See functions.

and 'a abstract

The type for representing abstract types of type 'a. See abstract types.

and 'a t =
  1. | Scalar : 'a scalar -> 'a t
  2. | Arraylike : ('elt, 'arr) arraylike -> 'arr t
  3. | Maplike : ('k, 'v, 'm) maplike -> 'm t
  4. | Product : 'p product -> 'p t
  5. | Record : 'r record -> 'r t
  6. | Sum : 's sum -> 's t
  7. | Func : ('a, 'b) func -> ('a -> 'b) t
  8. | Abstract : 'a abstract -> 'a t
  9. | Lazy : 'a lazy_t Meta.t * 'a t -> 'a lazy_t t
  10. | Ref : 'a Stdlib.ref Meta.t * 'a t -> 'a Stdlib.ref t
  11. | Rec : 'a t lazy_t -> 'a t
    (*

    Recursion

    *)

The type for type gists.

Constructors and operations

val todo : ?type_name:type_name -> unit -> 'a t

todo ~type_name () is a stub gist. Generic functions will raise Invalid_argument when they hit the stub.

val ref : ?meta:'a Stdlib.ref Meta.t -> 'a t -> 'a Stdlib.ref t

ref g is Ref g.

val lazy' : ?meta:'a lazy_t Meta.t -> 'a t -> 'a lazy_t t

lazy' ~meta g is Lazy (meta, g).

val rec' : 'a t lazy_t -> 'a t

rec' lg is Rec lg.

Scalars

module Scalar : sig ... end

Operating on scalar types.

val unit : unit t

unit is Scalar (Unit Meta.empty).

val bool : bool t

bool is Scalar (Bool Meta.empty).

val char : char t

char is Scalar (Char Meta.empty).

val uchar : Stdlib.Uchar.t t

uchar is Scalar (Uchar Meta.empty).

val int : int t

int is Scalar (Int Meta.empty).

val int32 : int32 t

int32 is Scalar (Int32 Meta.empty).

val int64 : int64 t

int64 is Scalar (Int64 Meta.empty).

val nativeint : nativeint t

nativeint is Scalar (Nativeint Meta.empt)y.

val float : float t

float is Scalar (Float Meta.empty).

Arraylike

The arraylike type gathers generic linear arrays and a few special cases for linear array types of the standard library. The specialisation can be converted to generic linear arrays.

module Arraylike : sig ... end

Operating on arraylike types.

val string_as_bytes : string t

string_as_bytes is Arraylike (String (Meta.empty, `Bytes)).

val string_as_utf_8 : string t

string_as_utf_8 is Arraylike (String (Meta.empty, `Utf_8)).

val bytes_as_bytes : bytes t

bytes_as_bytes is Arraylike (Bytes (Meta.empty, `Bytes)).

val bytes_as_utf_8 : bytes t

bytes_as_utf_8 is Arraylike (Bytes (Meta.empty, `Utf_8)).

val array : ?meta:'elt array Meta.t -> 'elt t -> 'elt array t

array represents arrays with elements of given representation.

val bigarray1 : ?meta:('elt, 'b, 'c) Stdlib.Bigarray.Array1.t Meta.t -> ('elt, 'b) Stdlib.Bigarray.kind -> 'c Stdlib.Bigarray.layout -> 'elt t -> ('elt, 'b, 'c) Stdlib.Bigarray.Array1.t t

bigarray represents bigarrays with elements of given representation.

val array_module : ?meta:'arr Meta.t -> ('elt, 'arr) array_module -> 'elt t -> 'arr t

array_module represents array modules with elements of the given representation.

Maplike

The maplike type gathers generic functional key value maps and a special case for hash tables.

module Maplike : sig ... end

Operations on maplikes.

val hashtbl : ?meta:('k, 'v) Stdlib.Hashtbl.t Meta.t -> 'k t -> 'v t -> ('k, 'v) Stdlib.Hashtbl.t t

hashtbl represents hashtables with keys and values of given representations.

val map_module : ?meta:'m Meta.t -> ('k, 'v, 'm) map_module -> 'k t -> 'v t -> 'm t

map_module m k v represents map modules with keys and values of the given representations. See here create map modules from standard library maps.

Products

Products (tuples), records and variant cases are all products of types. The toplevel type representation distinguishes them in different cases but otherwise they share the same representation: a product of typed and possibly named fields.

The field type represents an individual field of a product. The fields type represent the ordered sequence of fields and the way to construct the product from its fields with a constructor function.

type ('p, 'f) field

The type for representing the field of type 'f of a product of type 'p. See the Field module.

type ('p, _) fields =
  1. | Ctor : 'ctor -> ('p, 'ctor) fields
  2. | App : ('p, 'f -> 'a) fields * ('p, 'f) field -> ('p, 'a) fields

The type for representing the fields of a product of type 'p and its construction via a constructor function. See the Fields module.

When a fields value types with ('p, 'p) fields we know how to project each field of product 'p and how to construct a value from its fields.

module Field : sig ... end

Operating on fields.

module Fields : sig ... end

Operating on sequences of fields.

module Product : sig ... end

Operating on products.

val field' : ('p, 'f) field -> ('p, 'f -> 'a) Product.cons -> ('p, 'a) Product.cons

field f p adds f to the construction of p.

val field : ?meta:('p, 'f) field Meta.t -> ?inject:('p -> 'f -> 'p) -> ?set:('p -> 'f -> unit) -> ?default:'f -> string -> 'f t -> ('p -> 'f) -> ('p, 'f -> 'a) Product.cons -> ('p, 'a) Product.cons

field name g project p defines a named field for a product 'v. This is combines Field.make and field'.

val dim : ?meta:('p, 'd) field Meta.t -> ?inject:('p -> 'd -> 'p) -> ?default:'d -> 'd t -> ('p -> 'd) -> ('p, 'd -> 'a) Product.cons -> ('p, 'a) Product.cons

dim is like field but is a nameless field.

val product : ?meta:'p Meta.t -> ?type_name:type_name -> 'ctor -> ('p, 'ctor) Product.cons

product ctor is a product constructed with ctor to be satured with Type.Gist.field or Type.Gist.dim.

val finish_product : ('p, 'p) Product.cons -> 'p t

finish_product p finishes the product to yield a Product gist value.

val p2 : ?meta:('a * 'b) Meta.t -> ?type_name:type_name -> 'a t -> 'b t -> ('a * 'b) t

p2 represents pairs with given dimensions types.

val p3 : ?meta:('a * 'b * 'c) Meta.t -> ?type_name:type_name -> 'a t -> 'b t -> 'c t -> ('a * 'b * 'c) t

p3 represents triplets with given dimensions types.

val p4 : ?meta:('a * 'b * 'c * 'd) Meta.t -> ?type_name:type_name -> 'a t -> 'b t -> 'c t -> 'd t -> ('a * 'b * 'c * 'd) t

p4 represents quadruplets with given dimensions types.

Records

A record is a product of named fields named after the record type name and tagged by Record. The following are convenience combinators to build them. See an example.

val record : ?meta:'r Meta.t -> type_name -> 'ctor -> ('r, 'ctor) Product.cons

record type_name ctor is a record constructed with ctor to be satured with Type.Gist.field. type_name is the record type name.

val finish_record : ('r, 'r) Product.cons -> 'r t

finish_record f finishes the record to yield a Record gist value.

Variants

Variants are described by a list of cases and function that indicate how to select the case for a value. A case is a product named after the case name.

module Variant : sig ... end

Operating on variants.

val case : ?meta:'v Meta.t -> case_name -> 'ctor -> ('v, 'ctor) Product.cons

case case_name ctor is a variant case named case_name constructed with ctor to be satured with Type.Gist.dim or Type.Gist.field (for inline records). name is the OCaml constructor name of the case as accessed from the top level scope. E.g. "Either.Left".

val finish_case : ('v, 'v) Product.cons -> 'v Variant.case

finish_case f finishes the case by giving the product to Variant.Case.make.

val case0 : ?meta:'v Meta.t -> string -> 'v -> 'v Variant.case

case0 name v is case name v |> finish_case.

val variant : ?meta:'v Meta.t -> case_name -> ('v -> 'v Variant.case) -> 'v Variant.case list -> 'v t

variant case_name project cases is a variant decontructed by project and whose cases are enumerated in cases. type_name is the OCaml type name as accesed from the top level scope. This is Variant.make wrapped in a Variant and Sum gist value.

Sums

The sum type gathers generic variants and a few special cases for variants of the standard library. The specialisation can be converted to a generic variant.

module Sum : sig ... end

Operating on sums.

val option : ?meta:'a option Meta.t -> 'a t -> 'a option t

option represents options of the given representation type as an Option wrapped in a Sum gist value.

val either : ?meta:('a, 'b) Stdlib.Either.t Meta.t -> 'a t -> 'b t -> ('a, 'b) Stdlib.Either.t t

either represents eithers of the given representation types as an Either wrapped in a Sum gist value.

val result : ?meta:('a, 'b) Stdlib.result Meta.t -> 'a t -> 'b t -> ('a, 'b) Stdlib.result t

result represents results of the given representation types as an Result wrapped in a Sum gist value.

val list : ?meta:'a list Meta.t -> 'a t -> 'a list t

list represents lists of the given representation type as List wrapped in a Sum gist value.

Functions

module Func : sig ... end

Operating on functions.

val func : ?meta:('a -> 'b) Meta.t -> 'a t -> 'b t -> ('a -> 'b) t

func ~meta d r represents a function from domain d to range r. This is Func.make wrapped in Func gist value.

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

d @-> r is func d r.

Abstract types

Abstract types are represented by lists of versioned public representations with which they can be converted.

module Abstract : sig ... end

Operating on abstract types.

val abstract : ?meta:'a Meta.t -> type_name -> 'a Abstract.repr list -> 'a t

abstract ~meta name reprs represents an abstract type named type_name with public representations reprs. This is Abstract.make wrapped in an Abstract gist value.

Gists

val meta : 'a t -> 'a Meta.t

meta g is g's top meta.

val with_meta : 'a Meta.t -> 'a t -> 'a t

with_meta m g is g with meta meta.

val type_name : 'a t -> type_name

type_name g is g's type name.

val pp_type : Stdlib.Format.formatter -> 'a t -> unit

pp_type g formats a pseudo OCaml type expression for g.