package frama-c

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

A datatype provides useful values for types. It is a high-level API on top of module Type.

  • since Carbon-20101201

Type declarations

type 'a t = private {
  1. equal : 'a -> 'a -> bool;
  2. compare : 'a -> 'a -> int;
  3. hash : 'a -> int;
  4. copy : 'a -> 'a;
  5. pretty : Format.formatter -> 'a -> unit;
  6. mem_project : (Project_skeleton.t -> bool) -> 'a -> bool;
}

Values associated to each datatype. Some others are provided directly in module Type.

  • before 26.0-Iron

    there was additional fields only used for Journalization that has been removed.

module type Ty = sig ... end

A type with its type value.

module type S_no_copy = sig ... end

All values associated to a datatype, excepted copy.

module type S = sig ... end

All values associated to a datatype.

Getters from a type value

val info : 'a Type.t -> 'a t
val equal : 'a Type.t -> 'a -> 'a -> bool
val compare : 'a Type.t -> 'a -> 'a -> int
val hash : 'a Type.t -> 'a -> int
val copy : 'a Type.t -> 'a -> 'a
val pretty : 'a Type.t -> Format.formatter -> 'a -> unit
val mem_project : 'a Type.t -> (Project_skeleton.t -> bool) -> 'a -> bool

Easy builders

val undefined : 'a -> 'b

Must be used if you don't want to implement a required function.

val identity : 'a -> 'a

Must be used if you want to implement a required function by fun x -> x. Only useful for implementing rehash and copy.

val from_compare : 'a -> 'a -> bool

Must be used for equal in order to implement it by compare x y = 0 (with your own compare function).

val never_any_project : (Project_skeleton.t -> bool) -> 'a -> bool

Must be used for mem_project if values of your type does never contain any project.

module type Undefined = sig ... end

Sub-signature of S.

Each values in these modules are undefined. The usual way to use it is: module X: Datatype.S = struct include Undefined type t = ... let reprs = ... let name = ... let mem_project = ... (* Usually, Datatype.never_any_project *) (* define only useful functions for this datatype *) end

Same as Undefined, but the type is supposed to be marshallable by the standard OCaml way (in particular, no hash-consing or projects inside the type).

Generic builders

module type Make_input = sig ... end

Input signature of Make and Make_with_collections. Values to implement in order to get a datatype. Feel free to use easy builders (see above) for easy implementation.

module Make (X : Make_input) : S with type t = X.t

Generic datatype builder.

module type Functor_info = sig ... end

Additional info for building Set, Map and Hashtbl.

module type Set = sig ... end

A standard OCaml set signature extended with datatype operations.

module type Map = sig ... end

A standard OCaml map signature extended with datatype operations.

module type Hashtbl_with_descr = sig ... end

Marshallable collectors with hashtbl-like interface.

module type Hashtbl = sig ... end

A standard OCaml hashtbl signature extended with datatype operations.

module type S_with_collections = sig ... end

A datatype for a type t extended with predefined set, map and hashtbl over t.

Generic comparable datatype builder: functions equal, compare and hash must not be undefined.

Add sets, maps and hashtables modules to an existing datatype, provided the equal, compare and hash functions are not undefined.

Predefined datatype

module Unit : S_with_collections with type t = unit
module Bool : S_with_collections with type t = bool
module Int : S_with_collections with type t = int
module Int32 : S_with_collections with type t = int32
val int32 : int32 Type.t
module Int64 : S_with_collections with type t = int64
val int64 : int64 Type.t
module Nativeint : S_with_collections with type t = nativeint
val nativeint : nativeint Type.t
module Float : S_with_collections with type t = float
val float : float Type.t
module Char : S_with_collections with type t = char
module String : S_with_collections with type t = string
val string : string Type.t
module Formatter : S with type t = Format.formatter
val formatter : Format.formatter Type.t
module Integer : S_with_collections with type t = Integer.t
val integer : Integer.t Type.t
module Filepath : sig ... end

Type-safe strings representing normalized filepaths. See module Filepath.Normalized.

Generic functors for polymorphic types

module type Polymorphic = sig ... end

Output signature of Polymorphic.

module Polymorphic (P : sig ... end) : Polymorphic with type 'a poly = 'a P.t

Functor for polymorphic types with only 1 type variable.

module type Polymorphic2 = sig ... end

Output signature of Polymorphic2.

module Polymorphic2 (P : sig ... end) : Polymorphic2 with type ('a, 'b) poly = ('a, 'b) P.t

Functor for polymorphic types with 2 type variables.

module type Polymorphic3 = sig ... end

Output signature of Polymorphic3.

module Polymorphic3 (P : sig ... end) : Polymorphic3 with type ('a, 'b, 'c) poly = ('a, 'b, 'c) P.t

Functor for polymorphic types with 3 type variables.

module type Polymorphic4 = sig ... end

Output signature of Polymorphic4.

module Polymorphic4 (P : sig ... end) : Polymorphic4 with type ('a, 'b, 'c, 'd) poly = ('a, 'b, 'c, 'd) P.t

Functor for polymorphic types with 4 type variables.

Predefined functors for polymorphic types

module Poly_pair : Polymorphic2 with type ('a, 'b) poly = 'a * 'b
module Pair (T1 : S) (T2 : S) : S with type t = T1.t * T2.t
val pair : 'a Type.t -> 'b Type.t -> ('a * 'b) Type.t
module Poly_ref : Polymorphic with type 'a poly = 'a ref
module Ref (T : S) : S with type t = T.t ref
val t_ref : 'a Type.t -> 'a ref Type.t
module Poly_option : Polymorphic with type 'a poly = 'a option
module Option (T : S) : S with type t = T.t option
module Option_with_collections (T : S) (Info : Functor_info) : S_with_collections with type t = T.t option
val option : 'a Type.t -> 'a option Type.t
module Poly_list : Polymorphic with type 'a poly = 'a list
module List (T : S) : S with type t = T.t list
module List_with_collections (T : S) (Info : Functor_info) : S_with_collections with type t = T.t list
val list : 'a Type.t -> 'a list Type.t
module Poly_array : Polymorphic with type 'a poly = 'a array
module Array (T : S) : S with type t = T.t array
module Array_with_collections (T : S) (Info : Functor_info) : S_with_collections with type t = T.t array
val array : 'a Type.t -> 'a array Type.t
  • since Neon-20140301
module Poly_queue : Polymorphic with type 'a poly = 'a Queue.t
val queue : 'a Type.t -> 'a Queue.t Type.t
module Queue (T : S) : S with type t = T.t Queue.t
module Triple (T1 : S) (T2 : S) (T3 : S) : S with type t = T1.t * T2.t * T3.t
val triple : 'a Type.t -> 'b Type.t -> 'c Type.t -> ('a * 'b * 'c) Type.t
  • since Fluorine-20130401
module Triple_with_collections (T1 : S) (T2 : S) (T3 : S) (Info : Functor_info) : S_with_collections with type t = T1.t * T2.t * T3.t
module Quadruple (T1 : S) (T2 : S) (T3 : S) (T4 : S) : S with type t = T1.t * T2.t * T3.t * T4.t
val quadruple : 'a Type.t -> 'b Type.t -> 'c Type.t -> 'd Type.t -> ('a * 'b * 'c * 'd) Type.t
  • since Fluorine-20130401
module Quadruple_with_collections (T1 : S) (T2 : S) (T3 : S) (T4 : S) (Info : Functor_info) : S_with_collections with type t = T1.t * T2.t * T3.t * T4.t
module Function (T1 : sig ... end) (T2 : S) : S with type t = T1.t -> T2.t
val func : ?label:(string * (unit -> 'a) option) -> 'a Type.t -> 'b Type.t -> ('a -> 'b) Type.t
val optlabel_func : string -> (unit -> 'a) -> 'a Type.t -> 'b Type.t -> ('a -> 'b) Type.t

optlabel_func lab dft ty1 ty2 is equivalent to func ~label:(lab, Some dft) ty1 ty2

val func2 : ?label1:(string * (unit -> 'a) option) -> 'a Type.t -> ?label2:(string * (unit -> 'b) option) -> 'b Type.t -> 'c Type.t -> ('a -> 'b -> 'c) Type.t
val func3 : ?label1:(string * (unit -> 'a) option) -> 'a Type.t -> ?label2:(string * (unit -> 'b) option) -> 'b Type.t -> ?label3:(string * (unit -> 'c) option) -> 'c Type.t -> 'd Type.t -> ('a -> 'b -> 'c -> 'd) Type.t
val func4 : ?label1:(string * (unit -> 'a) option) -> 'a Type.t -> ?label2:(string * (unit -> 'b) option) -> 'b Type.t -> ?label3:(string * (unit -> 'c) option) -> 'c Type.t -> ?label4:(string * (unit -> 'd) option) -> 'd Type.t -> 'e Type.t -> ('a -> 'b -> 'c -> 'd -> 'e) Type.t
module Set (S : Set.S) (E : S with type t = S.elt) (Info : Functor_info) : Set with type t = S.t and type elt = E.t
module Map (M : Map.S) (Key : S with type t = M.key) (Info : Functor_info) : Map with type 'a t = 'a M.t and type key = M.key and module Key = Key
module Hashtbl (H : Hashtbl_with_descr) (Key : S with type t = H.key) (Info : Functor_info) : Hashtbl with type 'a t = 'a H.t and type key = H.key and module Key = Key
module type Sub_caml_weak_hashtbl = sig ... end
module Caml_weak_hashtbl (D : S) : sig ... end
module Weak (W : Sub_caml_weak_hashtbl) (D : S with type t = W.data) : S with type t = W.t