package dolmen_type

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

Typechecker interface

type ty

types

type ty_var
type ty_cst
type term
type term_var
type term_cst
type term_cstr
type term_field
type 'a ast_tag

Type definitions

type order =
  1. | First_order
    (*

    First-oreder typechecking

    *)
  2. | Higher_order
    (*

    Higher-order typechecking

    *)

Control whether the typechecker should type

type poly =
  1. | Explicit
    (*

    Type arguments must be explicitly given in funciton applications

    *)
  2. | Implicit
    (*

    Type arguments are not given in funciton applications, and instead type annotations/coercions are used to disambiguate applications of polymorphic symbols.

    *)
  3. | Flexible
    (*

    Mix between explicit and implicit: depending on the arity of a symbol and the number of arguments provided, either the provided type arguments are used, or wildcards are generated for all of them, and later instantiated when needed.

    *)

The various polymorphism mode for the typechecker

type sym_inference_source = {
  1. symbol : Dolmen.Std.Id.t;
  2. symbol_loc : Dolmen.Std.Loc.t;
  3. mutable inferred_ty : ty;
}
type var_inference_source = {
  1. variable : Dolmen.Std.Id.t;
  2. variable_loc : Dolmen.Std.Loc.t;
  3. mutable inferred_ty : ty;
}
type wildcard_source =
  1. | Arg_of of wildcard_source
  2. | Ret_of of wildcard_source
  3. | From_source of Dolmen.Std.Term.t
  4. | Added_type_argument of Dolmen.Std.Term.t
  5. | Symbol_inference of sym_inference_source
  6. | Variable_inference of var_inference_source
type wildcard_shape =
  1. | Forbidden
  2. | Any_in_scope
  3. | Any_base of {
    1. allowed : ty list;
    2. preferred : ty;
    }
  4. | Arrow of {
    1. arg_shape : wildcard_shape;
    2. ret_shape : wildcard_shape;
    }
type infer_unbound_var_scheme =
  1. | No_inference
  2. | Unification_type_variable
type infer_term_scheme =
  1. | No_inference
  2. | Wildcard of wildcard_shape
type var_infer = {
  1. infer_unbound_vars : infer_unbound_var_scheme;
  2. infer_type_vars_in_binding_pos : bool;
  3. infer_term_vars_in_binding_pos : infer_term_scheme;
}

Specification of how to infer variables.

type sym_infer = {
  1. infer_type_csts : bool;
  2. infer_term_csts : infer_term_scheme;
}

Specification of how to infer symbols.

type free_wildcards =
  1. | Forbidden
  2. | Implicitly_universally_quantified
type expect =
  1. | Type
  2. | Term
  3. | Anything
type tag =
  1. | Set : 'a ast_tag * 'a -> tag
  2. | Add : 'a list ast_tag * 'a -> tag
    (*

    Existencial wrapper around tags

    *)
type res =
  1. | Ttype
  2. | Ty of ty
  3. | Term of term
  4. | Tags of tag list

The results of parsing an untyped term.

type builtin_res = [
  1. | `Ttype of Dolmen.Std.Term.t -> Dolmen.Std.Term.t list -> unit
  2. | `Ty of Dolmen.Std.Term.t -> Dolmen.Std.Term.t list -> ty
  3. | `Term of Dolmen.Std.Term.t -> Dolmen.Std.Term.t list -> term
  4. | `Tags of Dolmen.Std.Term.t -> Dolmen.Std.Term.t list -> tag list
]

The result of parsing a symbol by the theory

type not_found = [
  1. | `Not_found
]

Not bound bindings

type inferred =
  1. | Ty_fun of ty_cst
  2. | Term_fun of term_cst

The type for inferred symbols.

type reason =
  1. | Builtin
  2. | Bound of Dolmen.Std.Loc.file * Dolmen.Std.Term.t
  3. | Inferred of Dolmen.Std.Loc.file * Dolmen.Std.Term.t
  4. | Defined of Dolmen.Std.Loc.file * Dolmen.Std.Statement.def
  5. | Declared of Dolmen.Std.Loc.file * Dolmen.Std.Statement.decl
    (*

    The type of reasons for constant typing

    *)
type binding = [
  1. | `Not_found
  2. | `Builtin of [ `Ttype | `Ty | `Term | `Tag ]
  3. | `Variable of [ `Ty of ty_var * reason option | `Term of term_var * reason option ]
  4. | `Constant of [ `Ty of ty_cst * reason option | `Cstr of term_cstr * reason option | `Dstr of term_cst * reason option | `Term of term_cst * reason option | `Field of term_field * reason option ]
]

The bindings that can occur.

type nonrec symbol = symbol =
  1. | Id of Dolmen.Std.Id.t
  2. | Builtin of Dolmen.Std.Term.builtin

Wrapper around potential function symbols from the Dolmen AST.

Errors and warnings

type _ warn = ..

The type of warnings, parameterized by the type of fragment they can trigger on

type warn +=
  1. | Unused_type_variable : [ `Quantified | `Letbound ] * ty_var -> Dolmen.Std.Term.t warn
    (*

    Unused quantified type variable

    *)
  2. | Unused_term_variable : [ `Quantified | `Letbound ] * term_var -> Dolmen.Std.Term.t warn
    (*

    Unused quantified term variable

    *)
  3. | Error_in_attribute : exn -> Dolmen.Std.Term.t warn
    (*

    An error occurred wile parsing an attribute

    *)
  4. | Superfluous_destructor : Dolmen.Std.Id.t * Dolmen.Std.Id.t * term_cst -> Dolmen.Std.Term.t warn
    (*

    The user implementation of typed terms returned a destructor where was asked for. This warning can very safely be ignored.

    *)
  5. | Redundant_pattern : term -> Dolmen.Std.Term.t warn
    (*

    Redundant cases in pattern matching

    *)

Warnings that cna trigger on regular parsed terms.

type warn +=
  1. | Shadowing : Dolmen.Std.Id.t * binding * binding -> _ warn
    (*

    Shadowing of the given identifier, together with the old and current binding.

    *)

Special case of warnings for shadowing, as it can happen both from a term but also a declaration, hence why the type variable of warn is left wild.

type _ err = ..

The type of errors, parameterized by the type of fragment they can trigger on

type err +=
  1. | Not_well_founded_datatypes : Dolmen.Std.Statement.decl list -> Dolmen.Std.Statement.decls err
    (*

    Not well-dounded datatypes definitions.

    *)

Errors that occur on declaration(s)

type err +=
  1. | Expected : string * res option -> Dolmen.Std.Term.t err
    (*

    The parsed term didn't match the expected shape

    *)
  2. | Bad_index_arity : string * int * int -> Dolmen.Std.Term.t err
    (*

    Bad_index_arity (name, expected, actual) denotes an error where an indexed family of operators (based on name) expect to be indexed by expected arguments but got actual instead.

    *)
  3. | Bad_ty_arity : ty_cst * int -> Dolmen.Std.Term.t err
    (*

    Bad_ty_arity (cst, actual) denotes a type constant that was applied to actual arguments, but which has a different arity (which should be accessible by getting its type/sort/arity).

    *)
  4. | Bad_op_arity : symbol * int list * int -> Dolmen.Std.Term.t err
    (*

    Bad_op_arity (symbol, expected, actual) denotes a named operator (which may be a builtin operator, a top-level defined constant which is being substituted, etc...) expecting a number of arguments among the expected list, but instead got actual number of arguments.

    *)
  5. | Bad_cstr_arity : term_cstr * int list * int -> Dolmen.Std.Term.t err
    (*

    Bad_cstr_arity (cstr, expected, actual) denotes an ADT constructor, which was expecting one of expected arguments, but which was applied to actual arguments.

    *)
  6. | Bad_term_arity : term_cst * int list * int -> Dolmen.Std.Term.t err
    (*

    Bad_term_arity (func, expected, actual) denotes a function symbol, which was expecting one of expected arguments, but which was applied to actual arguments.

    *)
  7. | Bad_poly_arity : ty_var list * ty list -> Dolmen.Std.Term.t err
    (*

    Bad_poly_arity (ty_vars, ty_args) denotes a polymorphic term application, where the function term being applied was provided with the type arguments [ty_args], but the function type expected a number of arguments that is the length of [ty_vars], and the two lengths differ. Under application is allowed, so in the cases where there are less provided arguments than expected type arguments, the presence of term arguments after the type arguments forced the raising of this exception.

    *)
  8. | Over_application : term list -> Dolmen.Std.Term.t err
    (*

    Over_application over_args denotes an application where after applying the provided arguments, the application resulted in a term with a non-function type, but that term was still provided with over_args.

    *)
  9. | Repeated_record_field : term_field -> Dolmen.Std.Term.t err
    (*

    Repeated_record_field f denotes an error within an expression that builds a record by giving values to all fields, but where the field f appears more than once.

    *)
  10. | Missing_record_field : term_field -> Dolmen.Std.Term.t err
    (*

    Missing_record_field f denotes an error within an expression that builds a record by giving values to all fields, but where the field f does not appear.

    *)
  11. | Mismatch_record_type : term_field * ty_cst -> Dolmen.Std.Term.t err
    (*

    Mismatch_record_type (f, r) denotes an error where while building a record expression for a record of type c, a field f belonging to another record type was used.

    *)
  12. | Mismatch_sum_type : term_cstr * ty -> Dolmen.Std.Term.t err
  13. | Partial_pattern_match : term list -> Dolmen.Std.Term.t err
    (*

    Partial_pattern_match missing denotes an error within a pattern matching in which the list of patterns do not cover all of the values of the type being matched. A list of non-matched terms is given to help users complete the pattern matching.

    *)
  14. | Var_application : term_var -> Dolmen.Std.Term.t err
    (*

    Var_application v denotes a variable which was applied to other terms, which is forbidden in first-order formulas.

    *)
  15. | Ty_var_application : ty_var -> Dolmen.Std.Term.t err
    (*

    Ty_var_application v denotes a type variable which was applied to other terms, which is forbidden in first-order formulas.

    *)
  16. | Type_mismatch : term * ty -> Dolmen.Std.Term.t err
    (*

    Type_mismatch (term, expected) denotes a context where term was expected to have type expected, but it is not the case.

    *)
  17. | Var_in_binding_pos_underspecified : Dolmen.Std.Term.t err
    (*

    Variable in a binding pos (e.g. quantifier) without a type, and no configured way to infer its type.

    *)
  18. | Unhandled_builtin : Dolmen.Std.Term.builtin -> Dolmen.Std.Term.t err
  19. | Cannot_tag_tag : Dolmen.Std.Term.t err
  20. | Cannot_tag_ttype : Dolmen.Std.Term.t err
  21. | Cannot_find : Dolmen.Std.Id.t * string -> Dolmen.Std.Term.t err
  22. | Forbidden_quantifier : Dolmen.Std.Term.t err
  23. | Missing_destructor : Dolmen.Std.Id.t -> Dolmen.Std.Term.t err
  24. | Type_def_rec : Dolmen.Std.Statement.def -> Dolmen.Std.Statement.defs err
  25. | Higher_order_application : Dolmen.Std.Term.t err
  26. | Higher_order_type : Dolmen.Std.Term.t err
  27. | Higher_order_env_in_tff_typechecker : Dolmen.Std.Loc.t err
    (*

    Programmer error

    *)
  28. | Polymorphic_function_argument : Dolmen.Std.Term.t err
  29. | Non_prenex_polymorphism : ty -> Dolmen.Std.Term.t err
  30. | Inference_forbidden : ty_var * wildcard_source * ty -> Dolmen.Std.Term.t err
  31. | Inference_conflict : ty_var * wildcard_source * ty * ty list -> Dolmen.Std.Term.t err
  32. | Inference_scope_escape : ty_var * wildcard_source * ty_var * reason option -> Dolmen.Std.Term.t err
    (*

    Inference_scope_escape (w, w_src, v, reason) denotes a situation where the wildcard variable w (which comes from w_src), was instantiated with a type that would lead to the variable v from escaping its scope; reason is the reason of the binding for v.

    *)
  33. | Unbound_type_wildcards : (ty_var * wildcard_source list) list -> Dolmen.Std.Term.t err
  34. | Uncaught_exn : exn * Printexc.raw_backtrace -> Dolmen.Std.Term.t err
  35. | Unhandled_ast : Dolmen.Std.Term.t err

Errors that occur on regular parsed terms.

Global State

type state

The type of mutable state for typechecking.

val new_state : unit -> state

Create a new state.

val copy_state : state -> state

Make a copy of the global state included in the env

Typing Environment

type env

The type of environments for typechecking.

type 'a typer = env -> Dolmen.Std.Term.t -> 'a

A general type for typers. Takes a local environment and the current untyped term, and return a value. The typer may need additional information for parsing, in which case the return value will be a function.

  • raises Typing_error
type builtin_symbols = env -> symbol -> [ builtin_res | not_found ]

The type of a typer for builtin symbols. Given the environment and a symbol, the theory should return a typing function if the symbol belongs to the theory. This typing function takes first the ast term of the whole application that is beign typechecked, and the list of arguments to the symbol.

type warning =
  1. | Warning : env * 'a fragment * 'a warn -> warning

Existential wrapper around warnings

type error =
  1. | Error : env * 'a fragment * 'a err -> error

Existential wrapper around errors

exception Typing_error of error

Exception for typing errors

val empty_env : ?st:state -> ?expect:expect -> ?var_infer:var_infer -> ?sym_infer:sym_infer -> ?order:order -> ?poly:poly -> ?quants:bool -> ?free_wildcards:free_wildcards -> warnings:(warning -> unit) -> file:Dolmen.Std.Loc.file -> builtin_symbols -> env

Create a new environment.

Location helpers

Completes the location with the file name form the env.

val fragment_loc : env -> _ fragment -> Dolmen.Std.Loc.full

Convenient function to get the location of a fragment.

val binding_reason : binding -> reason option

Extract the reason from a binding

  • raises Invalid_argument

    if the binding is `Not_found

Name/Path helpers

val var_name : env -> Dolmen.Std.Name.t -> string

Extract a variable name from a standard name.

Build a path from a standard name.

Bindings helpers

type var = [
  1. | `Ty_var of ty_var
  2. | `Term_var of term_var
  3. | `Letin of env * Dolmen.Std.Term.t * term_var * term
]

Variable bindings

type cst = [
  1. | `Cstr of term_cstr
  2. | `Dstr of term_cst
  3. | `Field of term_field
  4. | `Ty_cst of ty_cst
  5. | `Term_cst of term_cst
]

Constant bindings

type builtin = [
  1. | `Builtin of builtin_res
]

Builtin binding

type bound = [
  1. | var
  2. | cst
  3. | builtin
]
val find_var : env -> Dolmen.Std.Id.t -> [ var | not_found ]

Try and find the given id in the set of locally bound variables.

val find_global : env -> Dolmen.Std.Id.t -> [ cst | not_found ]

Try and find the given id in the set of globally bound constants.

val find_builtin : env -> Dolmen.Std.Id.t -> [ builtin | not_found ]

Try and find the given id in the set of bound builtin symbols.

val find_bound : env -> Dolmen.Std.Id.t -> [ bound | not_found ]

Try and find a bound identifier in the env, whetehr it be locally bound (such as bound variables), constants bound at top-level, or builtin symbols bound by the builtin theory.

val get_global_custom : env -> 'a Dolmen.Std.Tag.t -> 'a option

Get a custom value from the global environment.

val set_global_custom : env -> 'a Dolmen.Std.Tag.t -> 'a -> unit

Set a custom value in the global environment.

Errors & Warnings

val _warn : env -> 'a fragment -> 'a warn -> unit

Emit a warning

val _error : env -> 'a fragment -> 'a err -> _

Raise an error

val suggest : limit:int -> env -> Dolmen.Std.Id.t -> Dolmen.Std.Id.t list

From a dolmen identifier, return a list of existing bound identifiers in the env that are up to ~limit in terms of distance of edition.

Parsing functions

val monomorphize : env -> Dolmen.Std.Term.t -> term -> term

Monomorphize a term.

val parse_expr : res typer

Main parsing function.

val parse_ty : ty typer
val parse_term : term typer
val parse_prop : term typer

Wrappers around parse_expr to set the expect field of the env, and unwrap an expected return value.

val parse_app_ty_cst : (ty_cst -> Dolmen.Std.Term.t list -> res) typer
val parse_app_term_cst : (term_cst -> Dolmen.Std.Term.t list -> res) typer

Function used for parsing applications. The first dolmen term given is the application term being parsed (used for reporting errors).

val parse_app_ho_term : (term -> Dolmen.Std.Term.t list -> res) typer

Function used for parsing an higher-order application.

val unwrap_ty : env -> Dolmen.Std.Term.t -> res -> ty
val unwrap_term : env -> Dolmen.Std.Term.t -> res -> term

Unwrap a result, raising the adequate typing error if the result if not as expected.

High-level functions

val decls : env -> ?attrs:Dolmen.Std.Term.t list -> Dolmen.Std.Statement.decls -> [ `Type_decl of ty_cst | `Term_decl of term_cst ] list

Parse a list of potentially mutually recursive declarations.

val defs : env -> ?attrs:Dolmen.Std.Term.t list -> Dolmen.Std.Statement.defs -> [ `Type_def of Dolmen.Std.Id.t * ty_cst * ty_var list * ty | `Term_def of Dolmen.Std.Id.t * term_cst * ty_var list * term_var list * term ] list

Parse a definition

val parse : term typer

Parse a formula