sig
  type date = int
  type dir = IO_In | IO_Out | IO_Inout
  module VarSet :
    sig
      type elt = string
      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 map : (elt -> elt) -> t -> t
      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 min_elt_opt : t -> elt option
      val max_elt : t -> elt
      val max_elt_opt : t -> elt option
      val choose : t -> elt
      val choose_opt : t -> elt option
      val split : elt -> t -> t * bool * t
      val find : elt -> t -> elt
      val find_opt : elt -> t -> elt option
      val find_first : (elt -> bool) -> t -> elt
      val find_first_opt : (elt -> bool) -> t -> elt option
      val find_last : (elt -> bool) -> t -> elt
      val find_last_opt : (elt -> bool) -> t -> elt option
      val of_list : elt list -> t
    end
  module Index :
    sig
      type t =
          TiConst of int
        | TiVar of string
        | TiBinop of string * Types.Index.t * Types.Index.t
      type env = (string * int) list
      exception Illegal_op of string
      exception Illegal_type_index of Types.Index.t
      exception Unbound_type_index of string
      val subst : Types.Index.env -> Types.Index.t -> Types.Index.t
      val vars_of : Types.Index.t -> Types.VarSet.t
      val to_string : Types.Index.t -> string
    end
  type typ =
      TyEvent
    | TyBool
    | TyEnum of Types.name * string list
    | TyInt of Types.siz
    | TyFloat
    | TyChar
    | TyArray of Types.Index.t * Types.typ
    | TyVar of Types.typ Types.var
    | TyArrow of Types.typ * Types.typ
    | TyProduct of Types.typ list
    | TyRecord of Types.name * (string * Types.typ) list
  and siz =
      SzExpr1 of Types.Index.t
    | SzExpr2 of Types.Index.t * Types.Index.t
    | SzVar of Types.siz Types.var
  and name = NmLit of string | NmVar of Types.name Types.var
  and 'a var = { stamp : string; mutable value : 'Types.value; }
  and 'a value = Unknown | Known of 'a
  type typ_scheme = {
    ts_tparams : Types.typ Types.var list;
    ts_sparams : Types.siz Types.var list;
    ts_body : Types.typ;
  }
  val make_var : unit -> 'Types.var
  val new_type_var : unit -> Types.typ
  val new_size_var : unit -> Types.siz
  val new_name_var : unit -> Types.name
  val real_type : Types.typ -> Types.typ
  val real_size : Types.siz -> Types.siz
  val real_name : Types.name -> Types.name
  val no_type : Types.typ
  val type_int : int list -> Types.typ
  exception TypeConflict of Types.typ * Types.typ
  exception TypeCircularity of Types.typ * Types.typ
  val is_event_type : Types.typ -> bool
  val ivars_of : Types.typ -> string list
  val enums_of : Types.typ -> (string * Types.typ) list
  val size_of : Types.typ -> int
  val subtype_of : Types.typ -> Types.typ
  val is_lit_name : Types.name -> bool
  val subst_indexes : Types.Index.env -> Types.typ -> Types.typ
  val type_equal : strict:bool -> Types.typ -> Types.typ -> bool
  val unify : Types.typ -> Types.typ -> unit
  val type_instance : Types.typ_scheme -> Types.typ
  val string_of_type_scheme : Types.typ_scheme -> string
  val string_of_type : ?szvars:bool -> Types.typ -> string
  val string_of_name : Types.name -> string
end