package colibri2
include module type of struct include Dolmen_std.Expr.Ty end
Usual definitions
type t = Dolmen_std.Expr.ty
The type of types.
type subst =
(Dolmen_std.Expr.ty_var, Dolmen_std.Expr.ty) Dolmen_std.Expr.Subst.t
The type of substitutions over types.
type 'a tag = 'a Dolmen_std.Tag.t
A type for tags to attach to arbitrary types.
exception Bad_arity of Dolmen_std.Expr.ty_cst * t list
Raised when applying a type constant to the wrong number of arguments.
exception Prenex_polymorphism of t
Raised when the type provided is polymorphic, but occurred in a place where polymorphic types are forbidden by prenex/rank-1 polymorphism.
val hash : t -> int
A hash function for types, should be suitable to create hashtables.
An equality function on types. Should be compatible with the hash function.
Comparison function over types. Should be compativle with the equality function.
val print : Stdlib.Format.formatter -> t -> unit
Printing function.
Alias management
val alias_to :
Dolmen_std.Expr.ty_cst ->
Dolmen_std.Expr.ty_var list ->
Dolmen_std.Expr.ty ->
unit
Alias the given type constant.
View
type view = [
| `Prop
(*Propositions/booleans
*)| `Int
(*Integers
*)| `Rat
(*Rationals
*)| `Real
(*Reals
*)| `Array of Dolmen_std.Expr.ty * Dolmen_std.Expr.ty
(*Function arrays, from source to destination type.
*)| `Bitv of int
(*Bitvectors of fixed length.
*)| `Float of int * int
(*Floating points.
*)| `String
(*Strings
*)| `String_reg_lang
(*Regular languages over strings
*)| `Var of Dolmen_std.Expr.ty_var
(*Variables (excluding wildcards)
*)| `Wildcard of Dolmen_std.Expr.ty_var
(*Wildcards
*)| `App of [ `Generic of Dolmen_std.Expr.ty_cst | `Builtin of Dolmen_std.Expr.builtin ] * Dolmen_std.Expr.ty list
(*Generic applications.
*)| `Arrow of Dolmen_std.Expr.ty list * Dolmen_std.Expr.ty
| `Pi of Dolmen_std.Expr.ty_var list * Dolmen_std.Expr.ty
]
View on types.
val pi_arity : t -> int
Returns the number of expected type arguments that the given type expects (i.e. the number of prenex polymorphic variables in the given type).
val poly_sig :
t ->
Dolmen_std.Expr.ty_var list * Dolmen_std.Expr.ty list * Dolmen_std.Expr.ty
Split a type into a polymorphic signature.
Type structure definition
type adt_case = Dolmen_std.Expr.Ty.adt_case = {
cstr : Dolmen_std.Expr.term_cst;
tester : Dolmen_std.Expr.term_cst;
dstrs : Dolmen_std.Expr.term_cst option array;
}
One case of an algebraic datatype definition.
type def = Dolmen_std.Expr.Ty.def =
| Abstract
| Adt of {
ty : Dolmen_std.Expr.ty_cst;
record : bool;
cases : adt_case array;
}
The various ways to define a type inside the solver.
val define : Dolmen_std.Expr.ty_cst -> def -> unit
Register a type definition.
val definition : Dolmen_std.Expr.ty_cst -> def option
Return the definition of a type (if it exists).
Variables and constants
val prop : t
The type of propositions
val bool : t
Alias for prop
.
val unit : t
The unit type.
val base : t
An arbitrary type.
val int : t
The type of integers
val rat : t
The type of rationals
val real : t
The type of reals.
val string : t
The type of strings
val string_reg_lang : t
The type of regular language over strings.
val of_var : Dolmen_std.Expr.Ty.Var.t -> t
Create a type from a variable.
val apply : Dolmen_std.Expr.Ty.Const.t -> t list -> t
Application for types.
val pi : Dolmen_std.Expr.Ty.Var.t list -> t -> t
Create a prenex/rank-1 polymorphic type.
val bitv : int -> t
Bitvectors of a given length.
val float : int -> int -> t
Floating point of given exponent and significand.
val roundingMode : t
Type for the various Floating point rounding modes.
val fv : t -> Dolmen_std.Expr.Ty.Var.t list
Returns the list of free variables in the type.
val set_wildcard : Dolmen_std.Expr.ty_var -> t -> unit
Instantiate the given wildcard.
val add_wildcard_hook :
hook:(Dolmen_std.Expr.ty_var -> Dolmen_std.Expr.ty -> unit) ->
Dolmen_std.Expr.ty_var ->
unit
Tag for hooks called upon the wildcard instantiation.
val get_tag : t -> 'a Dolmen_std.Tag.t -> 'a option
Get the value bound to a tag.
val get_tag_list : t -> 'a list Dolmen_std.Tag.t -> 'a list
Get the list of values bound to a list tag, returning the empty list if no value is bound.
val get_tag_last : t -> 'a list Dolmen_std.Tag.t -> 'a option
Get the last value bound to a list tag.
val set_tag : t -> 'a Dolmen_std.Tag.t -> 'a -> unit
Set the value bound to the tag.
val add_tag : t -> 'a list Dolmen_std.Tag.t -> 'a -> unit
Bind an additional value to a list tag.
val add_tag_opt : t -> 'a list Dolmen_std.Tag.t -> 'a option -> unit
Optionally bind an additional value to a list tag.
val add_tag_list : t -> 'a list Dolmen_std.Tag.t -> 'a list -> unit
Bind a list of additional values to a list tag.
val unset_tag : t -> _ Dolmen_std.Tag.t -> unit
Remove the binding to the given tag.
val pp : Stdlib.Format.formatter -> t -> unit
module Var : sig ... end
module Const : sig ... end