sig
  type location = ParseLocation.t
  type t
  type term = TypedSTerm.t
  type view = private
      Var of TypedSTerm.t Var.t
    | Const of ID.t
    | App of TypedSTerm.t * TypedSTerm.t list
    | Bind of Binder.t * TypedSTerm.t Var.t * TypedSTerm.t
    | AppBuiltin of Builtin.t * TypedSTerm.t list
    | Multiset of TypedSTerm.t list
    | Record of (string * TypedSTerm.t) list * TypedSTerm.t option
    | Meta of TypedSTerm.meta_var
  and meta_var =
      TypedSTerm.t Var.t * TypedSTerm.t option Pervasives.ref *
      [ `BindDefault | `Generalize | `NoBind ]
  val view : TypedSTerm.t -> TypedSTerm.view
  val loc : TypedSTerm.t -> TypedSTerm.location option
  val ty : TypedSTerm.t -> TypedSTerm.t option
  val ty_exn : TypedSTerm.t -> TypedSTerm.t
  val head_exn : TypedSTerm.t -> ID.t
  val deref : TypedSTerm.t -> TypedSTerm.t
  val equal : t -> t -> bool
  val hash_fun : t -> CCHash.state -> CCHash.state
  val hash : t -> int
  val compare : t -> t -> int
  exception IllFormedTerm of string
  val tType : TypedSTerm.t
  val prop : TypedSTerm.t
  val var : ?loc:TypedSTerm.location -> TypedSTerm.t Var.t -> TypedSTerm.t
  val var_of_string :
    ?loc:TypedSTerm.location -> ty:TypedSTerm.t -> string -> TypedSTerm.t
  val app :
    ?loc:TypedSTerm.location ->
    ty:TypedSTerm.t -> TypedSTerm.t -> TypedSTerm.t list -> TypedSTerm.t
  val const :
    ?loc:TypedSTerm.location -> ty:TypedSTerm.t -> ID.t -> TypedSTerm.t
  val app_builtin :
    ?loc:TypedSTerm.location ->
    ty:TypedSTerm.t -> Builtin.t -> TypedSTerm.t list -> TypedSTerm.t
  val builtin :
    ?loc:TypedSTerm.location -> ty:TypedSTerm.t -> Builtin.t -> TypedSTerm.t
  val bind :
    ?loc:TypedSTerm.location ->
    ty:TypedSTerm.t ->
    Binder.t -> TypedSTerm.t Var.t -> TypedSTerm.t -> TypedSTerm.t
  val bind_list :
    ?loc:TypedSTerm.location ->
    ty:TypedSTerm.t ->
    Binder.t -> TypedSTerm.t Var.t list -> TypedSTerm.t -> TypedSTerm.t
  val multiset :
    ?loc:TypedSTerm.location ->
    ty:TypedSTerm.t -> TypedSTerm.t list -> TypedSTerm.t
  val meta : ?loc:TypedSTerm.location -> TypedSTerm.meta_var -> TypedSTerm.t
  val record :
    ?loc:TypedSTerm.location ->
    ty:TypedSTerm.t ->
    (string * TypedSTerm.t) list ->
    rest:TypedSTerm.t Var.t option -> TypedSTerm.t
  val record_flatten :
    ?loc:TypedSTerm.location ->
    ty:TypedSTerm.t ->
    (string * TypedSTerm.t) list -> rest:TypedSTerm.t option -> TypedSTerm.t
  val of_string :
    ?loc:TypedSTerm.location -> ty:TypedSTerm.t -> string -> TypedSTerm.t
  val at_loc : ?loc:TypedSTerm.location -> TypedSTerm.t -> TypedSTerm.t
  val with_ty : ty:TypedSTerm.t -> TypedSTerm.t -> TypedSTerm.t
  val map_ty :
    TypedSTerm.t -> f:(TypedSTerm.t -> TypedSTerm.t) -> TypedSTerm.t
  val fresh_var :
    ?loc:TypedSTerm.location -> ty:TypedSTerm.t -> unit -> TypedSTerm.t
  module Ty :
    sig
      type t = TypedSTerm.term
      type builtin = Prop | TType | Term | Int | Rat
      type view =
          Builtin of TypedSTerm.Ty.builtin
        | Var of TypedSTerm.Ty.t Var.t
        | App of ID.t * TypedSTerm.Ty.t list
        | Fun of TypedSTerm.Ty.t list * TypedSTerm.Ty.t
        | Forall of TypedSTerm.Ty.t Var.t * TypedSTerm.Ty.t
        | Multiset of TypedSTerm.Ty.t
        | Record of (string * TypedSTerm.Ty.t) list *
            TypedSTerm.Ty.t Var.t option
        | Meta of TypedSTerm.meta_var
      val view : TypedSTerm.Ty.t -> TypedSTerm.Ty.view
      val tType : TypedSTerm.Ty.t
      val var :
        ?loc:TypedSTerm.location -> TypedSTerm.Ty.t Var.t -> TypedSTerm.Ty.t
      val var_of_string :
        ?loc:TypedSTerm.location -> string -> TypedSTerm.Ty.t
      val meta :
        ?loc:TypedSTerm.location -> TypedSTerm.meta_var -> TypedSTerm.Ty.t
      val fun_ :
        ?loc:TypedSTerm.location ->
        TypedSTerm.Ty.t list -> TypedSTerm.Ty.t -> TypedSTerm.Ty.t
      val app :
        ?loc:TypedSTerm.location ->
        ID.t -> TypedSTerm.Ty.t list -> TypedSTerm.Ty.t
      val const : ?loc:TypedSTerm.location -> ID.t -> TypedSTerm.Ty.t
      val forall :
        ?loc:TypedSTerm.location ->
        TypedSTerm.Ty.t Var.t -> TypedSTerm.Ty.t -> TypedSTerm.Ty.t
      val forall_l :
        ?loc:TypedSTerm.location ->
        TypedSTerm.Ty.t Var.t list -> TypedSTerm.Ty.t -> TypedSTerm.Ty.t
      val multiset :
        ?loc:TypedSTerm.location -> TypedSTerm.Ty.t -> TypedSTerm.Ty.t
      val record :
        ?loc:TypedSTerm.location ->
        (string * TypedSTerm.Ty.t) list ->
        rest:TypedSTerm.Ty.t Var.t option -> TypedSTerm.Ty.t
      val record_flatten :
        ?loc:TypedSTerm.location ->
        (string * TypedSTerm.Ty.t) list ->
        rest:TypedSTerm.Ty.t option -> TypedSTerm.Ty.t
      val prop : TypedSTerm.Ty.t
      val int : TypedSTerm.Ty.t
      val rat : TypedSTerm.Ty.t
      val term : TypedSTerm.Ty.t
      val ( ==> ) :
        TypedSTerm.Ty.t list -> TypedSTerm.Ty.t -> TypedSTerm.Ty.t
      val close_forall : TypedSTerm.Ty.t -> TypedSTerm.Ty.t
      val arity : TypedSTerm.Ty.t -> int * int
      val is_tType : TypedSTerm.Ty.t -> bool
      val is_prop : TypedSTerm.Ty.t -> bool
      val returns : TypedSTerm.Ty.t -> TypedSTerm.Ty.t
      val returns_tType : TypedSTerm.Ty.t -> bool
      val returns_prop : TypedSTerm.Ty.t -> bool
    end
  module Form :
    sig
      type t = TypedSTerm.term
      type view =
          True
        | False
        | Atom of TypedSTerm.Form.t
        | Eq of TypedSTerm.Form.t * TypedSTerm.Form.t
        | Neq of TypedSTerm.Form.t * TypedSTerm.Form.t
        | Equiv of TypedSTerm.Form.t * TypedSTerm.Form.t
        | Xor of TypedSTerm.Form.t * TypedSTerm.Form.t
        | Imply of TypedSTerm.Form.t * TypedSTerm.Form.t
        | And of TypedSTerm.Form.t list
        | Or of TypedSTerm.Form.t list
        | Not of TypedSTerm.Form.t
        | Forall of TypedSTerm.Form.t Var.t * TypedSTerm.Form.t
        | Exists of TypedSTerm.Form.t Var.t * TypedSTerm.Form.t
      val view : TypedSTerm.Form.t -> TypedSTerm.Form.view
      val true_ : TypedSTerm.Form.t
      val false_ : TypedSTerm.Form.t
      val atom : TypedSTerm.Form.t -> TypedSTerm.Form.t
      val eq :
        ?loc:TypedSTerm.location ->
        TypedSTerm.Form.t -> TypedSTerm.Form.t -> TypedSTerm.Form.t
      val neq :
        ?loc:TypedSTerm.location ->
        TypedSTerm.Form.t -> TypedSTerm.Form.t -> TypedSTerm.Form.t
      val equiv :
        ?loc:TypedSTerm.location ->
        TypedSTerm.Form.t -> TypedSTerm.Form.t -> TypedSTerm.Form.t
      val xor :
        ?loc:TypedSTerm.location ->
        TypedSTerm.Form.t -> TypedSTerm.Form.t -> TypedSTerm.Form.t
      val imply :
        ?loc:TypedSTerm.location ->
        TypedSTerm.Form.t -> TypedSTerm.Form.t -> TypedSTerm.Form.t
      val and_ :
        ?loc:TypedSTerm.location ->
        TypedSTerm.Form.t list -> TypedSTerm.Form.t
      val or_ :
        ?loc:TypedSTerm.location ->
        TypedSTerm.Form.t list -> TypedSTerm.Form.t
      val not_ :
        ?loc:TypedSTerm.location -> TypedSTerm.Form.t -> TypedSTerm.Form.t
      val forall :
        ?loc:TypedSTerm.location ->
        TypedSTerm.Form.t Var.t -> TypedSTerm.Form.t -> TypedSTerm.Form.t
      val exists :
        ?loc:TypedSTerm.location ->
        TypedSTerm.Form.t Var.t -> TypedSTerm.Form.t -> TypedSTerm.Form.t
      val forall_l :
        ?loc:TypedSTerm.location ->
        TypedSTerm.Form.t Var.t list ->
        TypedSTerm.Form.t -> TypedSTerm.Form.t
      val exists_l :
        ?loc:TypedSTerm.location ->
        TypedSTerm.Form.t Var.t list ->
        TypedSTerm.Form.t -> TypedSTerm.Form.t
      val close_forall :
        ?loc:TypedSTerm.location -> TypedSTerm.Form.t -> TypedSTerm.Form.t
    end
  val is_var : TypedSTerm.t -> bool
  val is_meta : TypedSTerm.t -> bool
  val is_const : TypedSTerm.t -> bool
  val is_ground : TypedSTerm.t -> bool
  val is_monomorphic : TypedSTerm.t -> bool
  val is_subterm : strict:bool -> TypedSTerm.t -> of_:TypedSTerm.t -> bool
  val closed : TypedSTerm.t -> bool
  val open_binder :
    Binder.t -> TypedSTerm.t -> TypedSTerm.t Var.t list * TypedSTerm.t
  val var_occurs : var:TypedSTerm.t Var.t -> TypedSTerm.t -> bool
  val vars : TypedSTerm.t -> TypedSTerm.t Var.t list
  val free_vars : TypedSTerm.t -> TypedSTerm.t Var.t list
  val close_all : ty:TypedSTerm.t -> Binder.t -> TypedSTerm.t -> TypedSTerm.t
  val pp : t CCFormat.printer
  val to_string : t -> string
  module Set :
    sig
      type elt = term
      type t
      val empty : t
      val is_empty : t -> bool
      val mem : elt -> t -> bool
      val add : elt -> t -> t
      val singleton : elt -> t
      val remove : elt -> t -> t
      val union : t -> t -> t
      val inter : t -> t -> t
      val diff : t -> t -> t
      val compare : t -> t -> int
      val equal : t -> t -> bool
      val subset : t -> t -> bool
      val iter : (elt -> unit) -> t -> unit
      val fold : (elt -> '-> 'a) -> t -> '-> 'a
      val for_all : (elt -> bool) -> t -> bool
      val exists : (elt -> bool) -> t -> bool
      val filter : (elt -> bool) -> t -> t
      val partition : (elt -> bool) -> t -> t * t
      val cardinal : t -> int
      val elements : t -> elt list
      val min_elt : t -> elt
      val max_elt : t -> elt
      val choose : t -> elt
      val split : elt -> t -> t * bool * t
      val find : elt -> t -> elt
      val of_seq : elt Sequence.sequence -> t
      val to_seq : t -> elt Sequence.sequence
      val to_list : t -> elt list
      val of_list : elt list -> t
    end
  module Map :
    sig
      type key = term
      type +'a t
      val empty : 'a t
      val is_empty : 'a t -> bool
      val mem : key -> 'a t -> bool
      val add : key -> '-> 'a t -> 'a t
      val singleton : key -> '-> 'a t
      val remove : key -> 'a t -> 'a t
      val merge :
        (key -> 'a option -> 'b option -> 'c option) -> 'a t -> 'b t -> 'c t
      val compare : ('-> '-> int) -> 'a t -> 'a t -> int
      val equal : ('-> '-> bool) -> 'a t -> 'a t -> bool
      val iter : (key -> '-> unit) -> 'a t -> unit
      val fold : (key -> '-> '-> 'b) -> 'a t -> '-> 'b
      val for_all : (key -> '-> bool) -> 'a t -> bool
      val exists : (key -> '-> bool) -> 'a t -> bool
      val filter : (key -> '-> bool) -> 'a t -> 'a t
      val partition : (key -> '-> bool) -> 'a t -> 'a t * 'a t
      val cardinal : 'a t -> int
      val bindings : 'a t -> (key * 'a) list
      val min_binding : 'a t -> key * 'a
      val max_binding : 'a t -> key * 'a
      val choose : 'a t -> key * 'a
      val split : key -> 'a t -> 'a t * 'a option * 'a t
      val find : key -> 'a t -> 'a
      val map : ('-> 'b) -> 'a t -> 'b t
      val mapi : (key -> '-> 'b) -> 'a t -> 'b t
      val to_seq : 'a t -> (key * 'a) Sequence.sequence
      val of_seq : (key * 'a) Sequence.sequence -> 'a t
      val keys : 'a t -> key Sequence.sequence
      val values : 'a t -> 'Sequence.sequence
      val to_list : 'a t -> (key * 'a) list
      val of_list : (key * 'a) list -> 'a t
    end
  module Tbl :
    sig
      type key = term
      type 'a t
      val create : int -> 'a t
      val clear : 'a t -> unit
      val reset : 'a t -> unit
      val copy : 'a t -> 'a t
      val add : 'a t -> key -> '-> unit
      val remove : 'a t -> key -> unit
      val find : 'a t -> key -> 'a
      val find_all : 'a t -> key -> 'a list
      val replace : 'a t -> key -> '-> unit
      val mem : 'a t -> key -> bool
      val iter : (key -> '-> unit) -> 'a t -> unit
      val fold : (key -> '-> '-> 'b) -> 'a t -> '-> 'b
      val length : 'a t -> int
      val stats : 'a t -> Hashtbl.statistics
    end
  module Seq :
    sig
      val subterms : TypedSTerm.t -> TypedSTerm.t Sequence.t
      val subterms_with_bound :
        TypedSTerm.t -> (TypedSTerm.t * TypedSTerm.t Var.Set.t) Sequence.t
      val vars : TypedSTerm.t -> TypedSTerm.t Var.t Sequence.t
      val free_vars : TypedSTerm.t -> TypedSTerm.t Var.t Sequence.t
      val metas : TypedSTerm.t -> TypedSTerm.meta_var Sequence.t
    end
  module Subst :
    sig
      type t = (TypedSTerm.term, TypedSTerm.term) Var.Subst.t
      val empty : TypedSTerm.Subst.t
      val mem : TypedSTerm.Subst.t -> TypedSTerm.term Var.t -> bool
      val add :
        TypedSTerm.Subst.t ->
        TypedSTerm.term Var.t -> TypedSTerm.term -> TypedSTerm.Subst.t
      val find :
        TypedSTerm.Subst.t -> TypedSTerm.term Var.t -> TypedSTerm.term option
      val find_exn :
        TypedSTerm.Subst.t -> TypedSTerm.term Var.t -> TypedSTerm.term
      val eval : TypedSTerm.Subst.t -> TypedSTerm.term -> TypedSTerm.term
      val eval_head :
        TypedSTerm.Subst.t -> TypedSTerm.term -> TypedSTerm.term
      val pp : t CCFormat.printer
      val to_string : t -> string
    end
  exception UnifyFailure of string *
              (TypedSTerm.term * TypedSTerm.term) list *
              TypedSTerm.location option
  val pp_stack : (TypedSTerm.term * TypedSTerm.term) list CCFormat.printer
  module UStack :
    sig
      type t
      val create : unit -> TypedSTerm.UStack.t
      type snapshot
      val snapshot : st:TypedSTerm.UStack.t -> TypedSTerm.UStack.snapshot
      val restore :
        st:TypedSTerm.UStack.t -> TypedSTerm.UStack.snapshot -> unit
    end
  val unify :
    ?allow_open:bool ->
    ?loc:TypedSTerm.location ->
    ?st:TypedSTerm.UStack.t ->
    ?subst:TypedSTerm.Subst.t -> TypedSTerm.term -> TypedSTerm.term -> unit
  val apply_unify :
    ?allow_open:bool ->
    ?loc:TypedSTerm.location ->
    ?st:TypedSTerm.UStack.t ->
    ?subst:TypedSTerm.Subst.t ->
    TypedSTerm.t -> TypedSTerm.t list -> TypedSTerm.t
  val deref_rec : TypedSTerm.t -> TypedSTerm.t
  val app_infer :
    ?st:TypedSTerm.UStack.t ->
    ?subst:TypedSTerm.Subst.t ->
    TypedSTerm.t -> TypedSTerm.t list -> TypedSTerm.t
  val erase : TypedSTerm.t -> STerm.t
  module TPTP :
    sig val pp : t CCFormat.printer val to_string : t -> string end
  module ZF : sig val pp : t CCFormat.printer val to_string : t -> string end
end