functor (K : Field.T) (X : Alphabet.T->
  sig
    module M :
      sig
        type t = X.t array
        type word = t
        val mul : t -> t -> t
        val one : t
        val inj : X.t -> t
        val length : t -> int
        val sub : t -> int -> int -> t
        val eq : t -> t -> bool
        val compare : t -> t -> int
        val peq : t -> int -> t -> int -> int -> bool
        val to_string : t -> string
        val included : t -> t -> bool
        val unifier : ?i:int -> t -> t -> int
        val ordered_unifiers : t -> t -> int list
        val ordered_unifiers_bicontext : t -> t -> ((t * t) * (t * t)) list
        val unifiers_bicontext : t -> t -> ((t * t) * (t * t)) list
        module Order :
          sig
            val lexicographic : (X.t -> X.t -> bool) -> t -> t -> bool
            val deglex : (X.t -> X.t -> bool) -> t -> t -> bool
          end
        module Anick :
          sig
            type t = word list
            val empty : t
            val singleton : X.t -> t
            val singletons : X.t list -> t list
            val hd : t -> word
            val tl : t -> t
            val weq : t -> t -> bool
            val eq : t list -> t list -> bool
            val compare : t list -> t list -> int
            val extend : word list -> t list -> t list
            val eval : t -> t
            val length : t -> int
            val to_string : t -> string
          end
      end
    module A :
      sig
        module Ring :
          sig
            type t = K.t
            val eq : t -> t -> bool
            val add : t -> t -> t
            val zero : t
            val neg : t -> t
            val mul : t -> t -> t
            val one : t
            val to_string : t -> string
          end
        module E :
          sig
            type key = M.t
            type 'a t = 'Map.Make(M).t
            val empty : 'a t
            val is_empty : 'a t -> bool
            val mem : key -> 'a t -> bool
            val update : key -> ('a option -> 'a option) -> '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 union :
              (key -> '-> '-> 'a option) -> 'a t -> 'a t -> 'a 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 min_binding_opt : 'a t -> (key * 'a) option
            val max_binding : 'a t -> key * 'a
            val max_binding_opt : 'a t -> (key * 'a) option
            val choose : 'a t -> key * 'a
            val choose_opt : 'a t -> (key * 'a) option
            val split : key -> 'a t -> 'a t * 'a option * 'a t
            val find : key -> 'a t -> 'a
            val find_opt : key -> 'a t -> 'a option
            val find_first : (key -> bool) -> 'a t -> key * 'a
            val find_first_opt : (key -> bool) -> 'a t -> (key * 'a) option
            val find_last : (key -> bool) -> 'a t -> key * 'a
            val find_last_opt : (key -> bool) -> 'a t -> (key * 'a) option
            val map : ('-> 'b) -> 'a t -> 'b t
            val mapi : (key -> '-> 'b) -> 'a t -> 'b t
            val to_seq : 'a t -> (key * 'a) Seq.t
            val to_seq_from : key -> 'a t -> (key * 'a) Seq.t
            val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
            val of_seq : (key * 'a) Seq.t -> 'a t
            val add : key -> K.t -> K.t t -> K.t t
          end
        type r = K.t
        type t = r E.t
        val zero : t
        val cinj : K.t -> M.t -> t
        val inj : M.t -> t
        val coeff : t -> M.t -> r
        val included : t -> t -> bool
        val eq : t -> t -> bool
        val add_monomial : t -> r -> M.t -> t
        val add : t -> t -> t
        val cmul : K.t -> t -> t
        val neg : t -> t
        val sub : t -> t -> t
        val to_string : t -> string
        val map : (M.t -> t) -> t -> t
        val iter : (K.t -> M.t -> unit) -> K.t E.t -> unit
        module Map :
          sig
            module E :
              sig
                type key = M.t
                type 'a t = 'Map.Make(M).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 update : key -> ('a option -> 'a option) -> '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 union :
                  (key -> '-> '-> 'a option) -> 'a t -> 'a t -> 'a 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 min_binding_opt : 'a t -> (key * 'a) option
                val max_binding : 'a t -> key * 'a
                val max_binding_opt : 'a t -> (key * 'a) option
                val choose : 'a t -> key * 'a
                val choose_opt : 'a t -> (key * 'a) option
                val split : key -> 'a t -> 'a t * 'a option * 'a t
                val find : key -> 'a t -> 'a
                val find_opt : key -> 'a t -> 'a option
                val find_first : (key -> bool) -> 'a t -> key * 'a
                val find_first_opt :
                  (key -> bool) -> 'a t -> (key * 'a) option
                val find_last : (key -> bool) -> 'a t -> key * 'a
                val find_last_opt :
                  (key -> bool) -> 'a t -> (key * 'a) option
                val map : ('-> 'b) -> 'a t -> 'b t
                val mapi : (key -> '-> 'b) -> 'a t -> 'b t
                val to_seq : 'a t -> (key * 'a) Seq.t
                val to_seq_from : key -> 'a t -> (key * 'a) Seq.t
                val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
                val of_seq : (key * 'a) Seq.t -> 'a t
              end
            type map = t E.t
            val set : map -> M.t -> t -> map
            val app : map -> M.t -> t
            val bind : map -> t -> t
            val zero : map
            val to_string : map -> string
            type t = map
          end
        module Presentation :
          sig
            type pres = M.t array
            type t = pres
            val make : t -> t
            val dim : t -> int
            val presentation_to_string : M.t array -> string
            module Map :
              sig
                module M :
                  sig
                    type t = K.t array array
                    type matrix = t
                    val zero : int -> int -> t
                    val init : int -> int -> (int -> int -> K.t) -> t
                    val rows : t -> int
                    val cols : t -> int
                    val get : t -> int -> int -> K.t
                    val to_string : t -> string
                    module Row :
                      sig
                        val is_zero : K.t array array -> int -> bool
                        val replace : t -> int -> K.t array -> t
                        val exchange : t -> int -> int -> t
                        val mult : t -> K.t -> int -> t
                        val madd : t -> int -> K.t -> int -> t
                      end
                    val row_echelon : t -> t
                    val rank : t -> int
                    val nullity : t -> int
                    module Labeled :
                      functor (X : Alphabet.T->
                        sig
                          module L :
                            sig
                              type key = X.t
                              type 'a t = 'Map.Make(X).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 update :
                                key ->
                                ('a option -> 'a option) -> '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 union :
                                (key -> '-> '-> 'a option) ->
                                'a t -> 'a t -> 'a t
                              val compare :
                                ('-> '-> int) -> 'a t -> 'a t -> int
                              val equal :
                                ('-> '-> bool) -> 'a t -> 'a t -> bool
                              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 min_binding_opt : 'a t -> (key * 'a) option
                              val max_binding : 'a t -> key * 'a
                              val max_binding_opt : 'a t -> (key * 'a) option
                              val choose : 'a t -> key * 'a
                              val choose_opt : 'a t -> (key * 'a) option
                              val split :
                                key -> 'a t -> 'a t * 'a option * 'a t
                              val find_opt : key -> 'a t -> 'a option
                              val find_first :
                                (key -> bool) -> 'a t -> key * 'a
                              val find_first_opt :
                                (key -> bool) -> 'a t -> (key * 'a) option
                              val find_last :
                                (key -> bool) -> 'a t -> key * 'a
                              val find_last_opt :
                                (key -> bool) -> 'a t -> (key * 'a) option
                              val map : ('-> 'b) -> 'a t -> 'b t
                              val mapi : (key -> '-> 'b) -> 'a t -> 'b t
                              val to_seq : 'a t -> (key * 'a) Seq.t
                              val to_seq_from :
                                key -> 'a t -> (key * 'a) Seq.t
                              val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
                              val of_seq : (key * 'a) Seq.t -> 'a t
                              val find : X.t -> 'a t -> 'a
                              val iter : (X.t -> '-> unit) -> 'a t -> unit
                              val of_array : X.t array -> int t
                            end
                          type map = int L.t
                          type t = map * map * matrix
                          val matrix : t -> matrix
                          val zero : X.t array -> X.t array -> t
                          val set : t -> X.t -> X.t -> K.t -> unit
                          val get : t -> X.t -> X.t -> K.t
                          val rank : t -> int
                          val nullity : t -> int
                          val iter_src : (X.t -> unit) -> t -> unit
                          val iter_tgt : (X.t -> unit) -> t -> unit
                          val iter : (X.t -> X.t -> unit) -> t -> unit
                        end
                  end
                module L :
                  sig
                    module L :
                      sig
                        type key = M.t
                        type 'a t = 'Map.Make(M).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 update :
                          key -> ('a option -> 'a option) -> '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 union :
                          (key -> '-> '-> 'a option) ->
                          'a t -> 'a t -> 'a t
                        val compare :
                          ('-> '-> int) -> 'a t -> 'a t -> int
                        val equal :
                          ('-> '-> bool) -> 'a t -> 'a t -> bool
                        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 min_binding_opt : 'a t -> (key * 'a) option
                        val max_binding : 'a t -> key * 'a
                        val max_binding_opt : 'a t -> (key * 'a) option
                        val choose : 'a t -> key * 'a
                        val choose_opt : 'a t -> (key * 'a) option
                        val split : key -> 'a t -> 'a t * 'a option * 'a t
                        val find_opt : key -> 'a t -> 'a option
                        val find_first : (key -> bool) -> 'a t -> key * 'a
                        val find_first_opt :
                          (key -> bool) -> 'a t -> (key * 'a) option
                        val find_last : (key -> bool) -> 'a t -> key * 'a
                        val find_last_opt :
                          (key -> bool) -> 'a t -> (key * 'a) option
                        val map : ('-> 'b) -> 'a t -> 'b t
                        val mapi : (key -> '-> 'b) -> 'a t -> 'b t
                        val to_seq : 'a t -> (key * 'a) Seq.t
                        val to_seq_from : key -> 'a t -> (key * 'a) Seq.t
                        val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
                        val of_seq : (key * 'a) Seq.t -> 'a t
                        val find : M.t -> 'a t -> 'a
                        val iter : (M.t -> '-> unit) -> 'a t -> unit
                        val of_array : M.t array -> int t
                      end
                    type map = int L.t
                    type t = map * map * M.matrix
                    val matrix : t -> M.matrix
                    val zero : M.t array -> M.t array -> t
                    val set : t -> M.t -> M.t -> K.t -> unit
                    val get : t -> M.t -> M.t -> K.t
                    val rank : t -> int
                    val nullity : t -> int
                    val iter_src : (M.t -> unit) -> t -> unit
                    val iter_tgt : (M.t -> unit) -> t -> unit
                    val iter : (M.t -> M.t -> unit) -> t -> unit
                  end
                type map = L.t
                type t = map
                val app : t -> t -> t
                val zero : M.t array -> M.t array -> t
                val of_map : Map.map -> M.t array -> M.t array -> t
                val to_map : t -> Map.map
                val rank : t -> int
                val nullity : t -> int
                val to_string : t -> string
              end
            val iter : (M.t -> unit) -> t -> unit
            module Complex :
              sig
                type t =
                  Module.FreeLeft(K)(M).Presentation.Complex.t = {
                  modules : pres array;
                  d : Map.t array;
                }
                val modules : t -> pres array
                val maps : t -> Map.t array
                val length : t -> int
                val make : pres array -> Map.t array -> t
                val valid : t -> bool
                val to_string : t -> string
                val homology : t -> int array
              end
            val to_string : M.t array -> string
          end
        module Field :
          sig
            type t = K.t
            val eq : t -> t -> bool
            val add : t -> t -> t
            val zero : t
            val neg : t -> t
            val mul : t -> t -> t
            val one : t
            val to_string : t -> string
            val inv : t -> t
          end
        val one : t
        val mul_monomial : t -> M.t -> t
        val mul : t -> t -> t
        val leading : (M.t -> M.t -> bool) -> t -> K.t * M.t
      end
    type t = {
      leq : Algebra.Presentation.M.t -> Algebra.Presentation.M.t -> bool;
      generators : X.t list;
      rules : (Algebra.Presentation.M.t * Algebra.Presentation.A.t) list;
    }
    val free :
      (Algebra.Presentation.M.t -> Algebra.Presentation.M.t -> bool) ->
      X.t list -> Algebra.Presentation.t
    val orient :
      Algebra.Presentation.t ->
      Algebra.Presentation.A.t ->
      Algebra.Presentation.M.t * Algebra.Presentation.A.t
    val add_rule :
      Algebra.Presentation.t ->
      Algebra.Presentation.M.t * Algebra.Presentation.A.t ->
      Algebra.Presentation.t
    val add_relation :
      Algebra.Presentation.t ->
      Algebra.Presentation.A.t -> Algebra.Presentation.t
    val make :
      (Algebra.Presentation.M.t -> Algebra.Presentation.M.t -> bool) ->
      X.t list -> Algebra.Presentation.A.t list -> Algebra.Presentation.t
    val heads : Algebra.Presentation.t -> Algebra.Presentation.M.t list
    val to_string : Algebra.Presentation.t -> string
    val normalize :
      Algebra.Presentation.t ->
      Algebra.Presentation.A.t -> Algebra.Presentation.A.t
    val buchberger : Algebra.Presentation.t -> Algebra.Presentation.t
    val reduce : Algebra.Presentation.t -> Algebra.Presentation.t
    module Algebra :
      functor (P : sig val presentation : Algebra.Presentation.t end->
        sig
          type t = A.t
          type r
          val eq : t -> t -> bool
          val add : t -> t -> t
          val zero : t
          val neg : t -> t
          val mul : t -> t -> t
          val one : t
          val to_string : t -> string
          module Field :
            sig
              val eq : r -> r -> bool
              val add : r -> r -> r
              val zero : r
              val neg : r -> r
              val mul : r -> r -> r
              val one : r
              val to_string : r -> string
              val inv : r -> r
            end
          val cmul : r -> t -> t
        end
    module Augmentation :
      sig
        type t = Algebra.Presentation.A.t -> K.t
        exception Invalid
        val make :
          Algebra.Presentation.Augmentation.t ->
          (Algebra.Presentation.M.t -> K.t) ->
          Algebra.Presentation.Augmentation.t
        val graded :
          Algebra.Presentation.Augmentation.t ->
          Algebra.Presentation.Augmentation.t
        val monoid :
          Algebra.Presentation.Augmentation.t ->
          Algebra.Presentation.Augmentation.t
      end
    module Anick :
      sig
        type chain = Algebra.Presentation.M.Anick.t
        module AMod :
          sig
            module Mod :
              sig
                module Ring :
                  sig
                    type t = Ring.Op(A).t
                    val eq : t -> t -> bool
                    val add : t -> t -> t
                    val zero : t
                    val neg : t -> t
                    val mul : t -> t -> t
                    val one : t
                    val to_string : t -> string
                  end
                module E :
                  sig
                    type key = M.Anick.t
                    type 'a t = 'Map.Make(M.Anick).t
                    val empty : 'a t
                    val is_empty : 'a t -> bool
                    val mem : key -> 'a t -> bool
                    val update :
                      key -> ('a option -> 'a option) -> '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 union :
                      (key -> '-> '-> 'a option) -> 'a t -> 'a t -> 'a 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 min_binding_opt : 'a t -> (key * 'a) option
                    val max_binding : 'a t -> key * 'a
                    val max_binding_opt : 'a t -> (key * 'a) option
                    val choose : 'a t -> key * 'a
                    val choose_opt : 'a t -> (key * 'a) option
                    val split : key -> 'a t -> 'a t * 'a option * 'a t
                    val find : key -> 'a t -> 'a
                    val find_opt : key -> 'a t -> 'a option
                    val find_first : (key -> bool) -> 'a t -> key * 'a
                    val find_first_opt :
                      (key -> bool) -> 'a t -> (key * 'a) option
                    val find_last : (key -> bool) -> 'a t -> key * 'a
                    val find_last_opt :
                      (key -> bool) -> 'a t -> (key * 'a) option
                    val map : ('-> 'b) -> 'a t -> 'b t
                    val mapi : (key -> '-> 'b) -> 'a t -> 'b t
                    val to_seq : 'a t -> (key * 'a) Seq.t
                    val to_seq_from : key -> 'a t -> (key * 'a) Seq.t
                    val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
                    val of_seq : (key * 'a) Seq.t -> 'a t
                    val add :
                      key -> Ring.Op(A).t -> Ring.Op(A).t t -> Ring.Op(A).t t
                  end
                type r = Ring.Op(A).t
                type t = r E.t
                val zero : t
                val inj : M.Anick.t -> t
                val coeff : t -> M.Anick.t -> r
                val included : t -> t -> bool
                val eq : t -> t -> bool
                val add_monomial : t -> r -> M.Anick.t -> t
                val add : t -> t -> t
                val neg : t -> t
                val sub : t -> t -> t
                val map : (M.Anick.t -> t) -> t -> t
                val iter :
                  (Ring.Op(A).t -> M.Anick.t -> unit) ->
                  Ring.Op(A).t E.t -> unit
                module Map :
                  sig
                    module E :
                      sig
                        type key = M.Anick.t
                        type 'a t = 'Map.Make(M.Anick).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 update :
                          key -> ('a option -> 'a option) -> '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 union :
                          (key -> '-> '-> 'a option) ->
                          'a t -> 'a t -> 'a 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 min_binding_opt : 'a t -> (key * 'a) option
                        val max_binding : 'a t -> key * 'a
                        val max_binding_opt : 'a t -> (key * 'a) option
                        val choose : 'a t -> key * 'a
                        val choose_opt : 'a t -> (key * 'a) option
                        val split : key -> 'a t -> 'a t * 'a option * 'a t
                        val find : key -> 'a t -> 'a
                        val find_opt : key -> 'a t -> 'a option
                        val find_first : (key -> bool) -> 'a t -> key * 'a
                        val find_first_opt :
                          (key -> bool) -> 'a t -> (key * 'a) option
                        val find_last : (key -> bool) -> 'a t -> key * 'a
                        val find_last_opt :
                          (key -> bool) -> 'a t -> (key * 'a) option
                        val map : ('-> 'b) -> 'a t -> 'b t
                        val mapi : (key -> '-> 'b) -> 'a t -> 'b t
                        val to_seq : 'a t -> (key * 'a) Seq.t
                        val to_seq_from : key -> 'a t -> (key * 'a) Seq.t
                        val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
                        val of_seq : (key * 'a) Seq.t -> 'a t
                      end
                    type map = t E.t
                    val set : map -> M.Anick.t -> t -> map
                    val app : map -> M.Anick.t -> t
                    val bind : map -> t -> t
                    val zero : map
                    val to_string : map -> string
                    type t = map
                  end
                module Presentation :
                  sig
                    type pres = M.Anick.t array
                    type t = pres
                    val make : t -> t
                    val dim : t -> int
                    val presentation_to_string : M.Anick.t array -> string
                    module Map :
                      sig
                        module M :
                          sig
                            type t = Ring.Op(A).t array array
                            type matrix = t
                            val zero : int -> int -> t
                            val init :
                              int -> int -> (int -> int -> Ring.Op(A).t) -> t
                            val rows : t -> int
                            val cols : t -> int
                            val get : t -> int -> int -> Ring.Op(A).t
                            val to_string : t -> string
                            module Row :
                              sig
                                val is_zero :
                                  Ring.Op(A).t array array -> int -> bool
                                val replace :
                                  t -> int -> Ring.Op(A).t array -> t
                                val exchange : t -> int -> int -> t
                                val mult : t -> Ring.Op(A).t -> int -> t
                                val madd :
                                  t -> int -> Ring.Op(A).t -> int -> t
                              end
                            val row_echelon : t -> t
                            val rank : t -> int
                            val nullity : t -> int
                            module Labeled :
                              functor (X : Alphabet.T->
                                sig
                                  module L :
                                    sig
                                      type key = X.t
                                      type 'a t = 'Map.Make(X).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 update :
                                        key ->
                                        ('a option -> 'a option) ->
                                        '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 union :
                                        (key -> '-> '-> 'a option) ->
                                        'a t -> 'a t -> 'a t
                                      val compare :
                                        ('-> '-> int) ->
                                        'a t -> 'a t -> int
                                      val equal :
                                        ('-> '-> bool) ->
                                        'a t -> 'a t -> bool
                                      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 min_binding_opt :
                                        'a t -> (key * 'a) option
                                      val max_binding : 'a t -> key * 'a
                                      val max_binding_opt :
                                        'a t -> (key * 'a) option
                                      val choose : 'a t -> key * 'a
                                      val choose_opt :
                                        'a t -> (key * 'a) option
                                      val split :
                                        key ->
                                        'a t -> 'a t * 'a option * 'a t
                                      val find_opt : key -> 'a t -> 'a option
                                      val find_first :
                                        (key -> bool) -> 'a t -> key * 'a
                                      val find_first_opt :
                                        (key -> bool) ->
                                        'a t -> (key * 'a) option
                                      val find_last :
                                        (key -> bool) -> 'a t -> key * 'a
                                      val find_last_opt :
                                        (key -> bool) ->
                                        'a t -> (key * 'a) option
                                      val map : ('-> 'b) -> 'a t -> 'b t
                                      val mapi :
                                        (key -> '-> 'b) -> 'a t -> 'b t
                                      val to_seq : 'a t -> (key * 'a) Seq.t
                                      val to_seq_from :
                                        key -> 'a t -> (key * 'a) Seq.t
                                      val add_seq :
                                        (key * 'a) Seq.t -> 'a t -> 'a t
                                      val of_seq : (key * 'a) Seq.t -> 'a t
                                      val find : X.t -> 'a t -> 'a
                                      val iter :
                                        (X.t -> '-> unit) -> 'a t -> unit
                                      val of_array : X.t array -> int t
                                    end
                                  type map = int L.t
                                  type t = map * map * matrix
                                  val matrix : t -> matrix
                                  val zero : X.t array -> X.t array -> t
                                  val set :
                                    t -> X.t -> X.t -> Ring.Op(A).t -> unit
                                  val get : t -> X.t -> X.t -> Ring.Op(A).t
                                  val rank : t -> int
                                  val nullity : t -> int
                                  val iter_src : (X.t -> unit) -> t -> unit
                                  val iter_tgt : (X.t -> unit) -> t -> unit
                                  val iter :
                                    (X.t -> X.t -> unit) -> t -> unit
                                end
                          end
                        module L :
                          sig
                            module L :
                              sig
                                type key = M.Anick.t
                                type 'a t = 'Map.Make(M.Anick).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 update :
                                  key ->
                                  ('a option -> 'a option) -> '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 union :
                                  (key -> '-> '-> 'a option) ->
                                  'a t -> 'a t -> 'a t
                                val compare :
                                  ('-> '-> int) -> 'a t -> 'a t -> int
                                val equal :
                                  ('-> '-> bool) -> 'a t -> 'a t -> bool
                                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 min_binding_opt :
                                  'a t -> (key * 'a) option
                                val max_binding : 'a t -> key * 'a
                                val max_binding_opt :
                                  'a t -> (key * 'a) option
                                val choose : 'a t -> key * 'a
                                val choose_opt : 'a t -> (key * 'a) option
                                val split :
                                  key -> 'a t -> 'a t * 'a option * 'a t
                                val find_opt : key -> 'a t -> 'a option
                                val find_first :
                                  (key -> bool) -> 'a t -> key * 'a
                                val find_first_opt :
                                  (key -> bool) -> 'a t -> (key * 'a) option
                                val find_last :
                                  (key -> bool) -> 'a t -> key * 'a
                                val find_last_opt :
                                  (key -> bool) -> 'a t -> (key * 'a) option
                                val map : ('-> 'b) -> 'a t -> 'b t
                                val mapi : (key -> '-> 'b) -> 'a t -> 'b t
                                val to_seq : 'a t -> (key * 'a) Seq.t
                                val to_seq_from :
                                  key -> 'a t -> (key * 'a) Seq.t
                                val add_seq :
                                  (key * 'a) Seq.t -> 'a t -> 'a t
                                val of_seq : (key * 'a) Seq.t -> 'a t
                                val find : M.Anick.t -> 'a t -> 'a
                                val iter :
                                  (M.Anick.t -> '-> unit) -> 'a t -> unit
                                val of_array : M.Anick.t array -> int t
                              end
                            type map = int L.t
                            type t = map * map * M.matrix
                            val matrix : t -> M.matrix
                            val zero :
                              M.Anick.t array -> M.Anick.t array -> t
                            val set :
                              t ->
                              M.Anick.t -> M.Anick.t -> Ring.Op(A).t -> unit
                            val get :
                              t -> M.Anick.t -> M.Anick.t -> Ring.Op(A).t
                            val rank : t -> int
                            val nullity : t -> int
                            val iter_src : (M.Anick.t -> unit) -> t -> unit
                            val iter_tgt : (M.Anick.t -> unit) -> t -> unit
                            val iter :
                              (M.Anick.t -> M.Anick.t -> unit) -> t -> unit
                          end
                        type map = L.t
                        type t = map
                        val app : t -> t -> t
                        val zero : M.Anick.t array -> M.Anick.t array -> t
                        val of_map :
                          Map.map -> M.Anick.t array -> M.Anick.t array -> t
                        val to_map : t -> Map.map
                        val rank : t -> int
                        val nullity : t -> int
                        val to_string : t -> string
                      end
                    val iter : (M.Anick.t -> unit) -> t -> unit
                    module Complex :
                      sig
                        type t =
                          Module.FreeLeft(Ring.Op(A))(M.Anick).Presentation.Complex.t = {
                          modules : pres array;
                          d : Map.t array;
                        }
                        val modules : t -> pres array
                        val maps : t -> Map.t array
                        val length : t -> int
                        val make : pres array -> Map.t array -> t
                        val valid : t -> bool
                        val to_string : t -> string
                        val homology : t -> int array
                      end
                    val to_string : M.Anick.t array -> string
                  end
                val cinj : M.Anick.t -> Ring.Op(A).t -> t
                val cmul : t -> Ring.Op(A).t -> t
                val to_string : t -> string
              end
            module Ring :
              sig
                type t = Ring.Op(A).t
                val eq : t -> t -> bool
                val add : t -> t -> t
                val zero : t
                val neg : t -> t
                val mul : t -> t -> t
                val one : t
                val to_string : t -> string
              end
            module E :
              sig
                type key = M.Anick.t
                type 'a t = 'Map.Make(M.Anick).t
                val empty : 'a t
                val is_empty : 'a t -> bool
                val mem : key -> 'a t -> bool
                val update : key -> ('a option -> 'a option) -> '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 union :
                  (key -> '-> '-> 'a option) -> 'a t -> 'a t -> 'a 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 min_binding_opt : 'a t -> (key * 'a) option
                val max_binding : 'a t -> key * 'a
                val max_binding_opt : 'a t -> (key * 'a) option
                val choose : 'a t -> key * 'a
                val choose_opt : 'a t -> (key * 'a) option
                val split : key -> 'a t -> 'a t * 'a option * 'a t
                val find : key -> 'a t -> 'a
                val find_opt : key -> 'a t -> 'a option
                val find_first : (key -> bool) -> 'a t -> key * 'a
                val find_first_opt :
                  (key -> bool) -> 'a t -> (key * 'a) option
                val find_last : (key -> bool) -> 'a t -> key * 'a
                val find_last_opt :
                  (key -> bool) -> 'a t -> (key * 'a) option
                val map : ('-> 'b) -> 'a t -> 'b t
                val mapi : (key -> '-> 'b) -> 'a t -> 'b t
                val to_seq : 'a t -> (key * 'a) Seq.t
                val to_seq_from : key -> 'a t -> (key * 'a) Seq.t
                val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
                val of_seq : (key * 'a) Seq.t -> 'a t
                val add :
                  key -> Ring.Op(A).t -> Ring.Op(A).t t -> Ring.Op(A).t t
              end
            type r = Ring.Op(A).t
            type t = r E.t
            val zero : t
            val inj : M.Anick.t -> t
            val coeff : t -> M.Anick.t -> r
            val included : t -> t -> bool
            val eq : t -> t -> bool
            val add_monomial : t -> r -> M.Anick.t -> t
            val add : t -> t -> t
            val neg : t -> t
            val sub : t -> t -> t
            val map : (M.Anick.t -> t) -> t -> t
            val iter :
              (Ring.Op(A).t -> M.Anick.t -> unit) -> Ring.Op(A).t E.t -> unit
            module Presentation :
              sig
                type pres = M.Anick.t array
                type t = pres
                val make : t -> t
                val dim : t -> int
                val presentation_to_string : M.Anick.t array -> string
                module Map :
                  sig
                    module M :
                      sig
                        type t = Ring.Op(A).t array array
                        type matrix = t
                        val zero : int -> int -> t
                        val init :
                          int -> int -> (int -> int -> Ring.Op(A).t) -> t
                        val rows : t -> int
                        val cols : t -> int
                        val get : t -> int -> int -> Ring.Op(A).t
                        val to_string : t -> string
                        module Row :
                          sig
                            val is_zero :
                              Ring.Op(A).t array array -> int -> bool
                            val replace : t -> int -> Ring.Op(A).t array -> t
                            val exchange : t -> int -> int -> t
                            val mult : t -> Ring.Op(A).t -> int -> t
                            val madd : t -> int -> Ring.Op(A).t -> int -> t
                          end
                        val row_echelon : t -> t
                        val rank : t -> int
                        val nullity : t -> int
                        module Labeled :
                          functor (X : Alphabet.T->
                            sig
                              module L :
                                sig
                                  type key = X.t
                                  type 'a t = 'Map.Make(X).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 update :
                                    key ->
                                    ('a option -> 'a option) -> '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 union :
                                    (key -> '-> '-> 'a option) ->
                                    'a t -> 'a t -> 'a t
                                  val compare :
                                    ('-> '-> int) -> 'a t -> 'a t -> int
                                  val equal :
                                    ('-> '-> bool) ->
                                    'a t -> 'a t -> bool
                                  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 min_binding_opt :
                                    'a t -> (key * 'a) option
                                  val max_binding : 'a t -> key * 'a
                                  val max_binding_opt :
                                    'a t -> (key * 'a) option
                                  val choose : 'a t -> key * 'a
                                  val choose_opt : 'a t -> (key * 'a) option
                                  val split :
                                    key -> 'a t -> 'a t * 'a option * 'a t
                                  val find_opt : key -> 'a t -> 'a option
                                  val find_first :
                                    (key -> bool) -> 'a t -> key * 'a
                                  val find_first_opt :
                                    (key -> bool) ->
                                    'a t -> (key * 'a) option
                                  val find_last :
                                    (key -> bool) -> 'a t -> key * 'a
                                  val find_last_opt :
                                    (key -> bool) ->
                                    'a t -> (key * 'a) option
                                  val map : ('-> 'b) -> 'a t -> 'b t
                                  val mapi :
                                    (key -> '-> 'b) -> 'a t -> 'b t
                                  val to_seq : 'a t -> (key * 'a) Seq.t
                                  val to_seq_from :
                                    key -> 'a t -> (key * 'a) Seq.t
                                  val add_seq :
                                    (key * 'a) Seq.t -> 'a t -> 'a t
                                  val of_seq : (key * 'a) Seq.t -> 'a t
                                  val find : X.t -> 'a t -> 'a
                                  val iter :
                                    (X.t -> '-> unit) -> 'a t -> unit
                                  val of_array : X.t array -> int t
                                end
                              type map = int L.t
                              type t = map * map * matrix
                              val matrix : t -> matrix
                              val zero : X.t array -> X.t array -> t
                              val set :
                                t -> X.t -> X.t -> Ring.Op(A).t -> unit
                              val get : t -> X.t -> X.t -> Ring.Op(A).t
                              val rank : t -> int
                              val nullity : t -> int
                              val iter_src : (X.t -> unit) -> t -> unit
                              val iter_tgt : (X.t -> unit) -> t -> unit
                              val iter : (X.t -> X.t -> unit) -> t -> unit
                            end
                      end
                    module L :
                      sig
                        module L :
                          sig
                            type key = M.Anick.t
                            type 'a t = 'Map.Make(M.Anick).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 update :
                              key -> ('a option -> 'a option) -> '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 union :
                              (key -> '-> '-> 'a option) ->
                              'a t -> 'a t -> 'a t
                            val compare :
                              ('-> '-> int) -> 'a t -> 'a t -> int
                            val equal :
                              ('-> '-> bool) -> 'a t -> 'a t -> bool
                            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 min_binding_opt : 'a t -> (key * 'a) option
                            val max_binding : 'a t -> key * 'a
                            val max_binding_opt : 'a t -> (key * 'a) option
                            val choose : 'a t -> key * 'a
                            val choose_opt : 'a t -> (key * 'a) option
                            val split :
                              key -> 'a t -> 'a t * 'a option * 'a t
                            val find_opt : key -> 'a t -> 'a option
                            val find_first :
                              (key -> bool) -> 'a t -> key * 'a
                            val find_first_opt :
                              (key -> bool) -> 'a t -> (key * 'a) option
                            val find_last : (key -> bool) -> 'a t -> key * 'a
                            val find_last_opt :
                              (key -> bool) -> 'a t -> (key * 'a) option
                            val map : ('-> 'b) -> 'a t -> 'b t
                            val mapi : (key -> '-> 'b) -> 'a t -> 'b t
                            val to_seq : 'a t -> (key * 'a) Seq.t
                            val to_seq_from : key -> 'a t -> (key * 'a) Seq.t
                            val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
                            val of_seq : (key * 'a) Seq.t -> 'a t
                            val find : M.Anick.t -> 'a t -> 'a
                            val iter :
                              (M.Anick.t -> '-> unit) -> 'a t -> unit
                            val of_array : M.Anick.t array -> int t
                          end
                        type map = int L.t
                        type t = map * map * M.matrix
                        val matrix : t -> M.matrix
                        val zero : M.Anick.t array -> M.Anick.t array -> t
                        val set :
                          t -> M.Anick.t -> M.Anick.t -> Ring.Op(A).t -> unit
                        val get : t -> M.Anick.t -> M.Anick.t -> Ring.Op(A).t
                        val rank : t -> int
                        val nullity : t -> int
                        val iter_src : (M.Anick.t -> unit) -> t -> unit
                        val iter_tgt : (M.Anick.t -> unit) -> t -> unit
                        val iter :
                          (M.Anick.t -> M.Anick.t -> unit) -> t -> unit
                      end
                    type map = L.t
                    type t = map
                    val app : t -> t -> t
                    val zero : M.Anick.t array -> M.Anick.t array -> t
                    val of_map :
                      Mod.Map.map -> M.Anick.t array -> M.Anick.t array -> t
                    val to_map : t -> Mod.Map.map
                    val rank : t -> int
                    val nullity : t -> int
                    val to_string : t -> string
                  end
                val iter : (M.Anick.t -> unit) -> t -> unit
                module Complex :
                  sig
                    type t =
                      Module.FreeLeft(Ring.Op(A))(M.Anick).Presentation.Complex.t = {
                      modules : pres array;
                      d : Map.t array;
                    }
                    val modules : t -> pres array
                    val maps : t -> Map.t array
                    val length : t -> int
                    val make : pres array -> Map.t array -> t
                    val valid : t -> bool
                    val to_string : t -> string
                    val homology : t -> int array
                  end
                val to_string : M.Anick.t array -> string
              end
            val cinj : M.Anick.t -> Ring.Op(A).t -> t
            val cmul : t -> Ring.Op(A).t -> t
            val to_string : t -> string
            val normalize :
              Algebra.Presentation.t ->
              Ring.Op(A).t E.t -> Algebra.Presentation.t
            module Map :
              sig
                module E = Mod.Map.E
                type map = Mod.t E.t
                val set : map -> M.Anick.t -> Mod.t -> map
                val app : map -> M.Anick.t -> Mod.t
                val zero : map
                val to_string : map -> string
                type t = map
                val bind :
                  Algebra.Presentation.t ->
                  map ->
                  Algebra.Presentation.Anick.AMod.Mod.t ->
                  Algebra.Presentation.t
              end
          end
        module AKMod :
          sig
            type t = Algebra.Presentation.Anick.AMod.t
            type r = K.t
            val cinj :
              K.t ->
              Algebra.Presentation.M.Anick.t ->
              Algebra.Presentation.M.t -> Algebra.Presentation.Anick.AMod.t
            val inj :
              Algebra.Presentation.Anick.AMod.t ->
              Algebra.Presentation.M.t -> Algebra.Presentation.Anick.AMod.t
            val cmul :
              K.t ->
              Algebra.Presentation.Anick.AMod.t ->
              Algebra.Presentation.Anick.AMod.t
            val iter :
              (K.t ->
               Algebra.Presentation.M.Anick.t ->
               Algebra.Presentation.M.t -> unit) ->
              Algebra.Presentation.Anick.AKMod.t -> unit
            val map :
              (Algebra.Presentation.M.Anick.t ->
               Algebra.Presentation.M.t -> Algebra.Presentation.Anick.AMod.t) ->
              Algebra.Presentation.Anick.AKMod.t ->
              Algebra.Presentation.Anick.AMod.t
          end
        val chains :
          Algebra.Presentation.t ->
          int -> Algebra.Presentation.M.Anick.t list array
        val resolution :
          ?augmentation:Algebra.Presentation.Augmentation.t ->
          Algebra.Presentation.t ->
          int -> Algebra.Presentation.Anick.AMod.Presentation.Complex.t
        module KMod :
          sig
            module Ring :
              sig
                type t = K.t
                val eq : t -> t -> bool
                val add : t -> t -> t
                val zero : t
                val neg : t -> t
                val mul : t -> t -> t
                val one : t
                val to_string : t -> string
              end
            module E :
              sig
                type key = M.Anick.t
                type 'a t = 'Map.Make(M.Anick).t
                val empty : 'a t
                val is_empty : 'a t -> bool
                val mem : key -> 'a t -> bool
                val update : key -> ('a option -> 'a option) -> '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 union :
                  (key -> '-> '-> 'a option) -> 'a t -> 'a t -> 'a 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 min_binding_opt : 'a t -> (key * 'a) option
                val max_binding : 'a t -> key * 'a
                val max_binding_opt : 'a t -> (key * 'a) option
                val choose : 'a t -> key * 'a
                val choose_opt : 'a t -> (key * 'a) option
                val split : key -> 'a t -> 'a t * 'a option * 'a t
                val find : key -> 'a t -> 'a
                val find_opt : key -> 'a t -> 'a option
                val find_first : (key -> bool) -> 'a t -> key * 'a
                val find_first_opt :
                  (key -> bool) -> 'a t -> (key * 'a) option
                val find_last : (key -> bool) -> 'a t -> key * 'a
                val find_last_opt :
                  (key -> bool) -> 'a t -> (key * 'a) option
                val map : ('-> 'b) -> 'a t -> 'b t
                val mapi : (key -> '-> 'b) -> 'a t -> 'b t
                val to_seq : 'a t -> (key * 'a) Seq.t
                val to_seq_from : key -> 'a t -> (key * 'a) Seq.t
                val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
                val of_seq : (key * 'a) Seq.t -> 'a t
                val add : key -> K.t -> K.t t -> K.t t
              end
            type r = K.t
            type t = r E.t
            val zero : t
            val cinj : K.t -> M.Anick.t -> t
            val inj : M.Anick.t -> t
            val coeff : t -> M.Anick.t -> r
            val included : t -> t -> bool
            val eq : t -> t -> bool
            val add_monomial : t -> r -> M.Anick.t -> t
            val add : t -> t -> t
            val cmul : K.t -> t -> t
            val neg : t -> t
            val sub : t -> t -> t
            val to_string : t -> string
            val map : (M.Anick.t -> t) -> t -> t
            val iter : (K.t -> M.Anick.t -> unit) -> K.t E.t -> unit
            module Map :
              sig
                module E :
                  sig
                    type key = M.Anick.t
                    type 'a t = 'Map.Make(M.Anick).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 update :
                      key -> ('a option -> 'a option) -> '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 union :
                      (key -> '-> '-> 'a option) -> 'a t -> 'a t -> 'a 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 min_binding_opt : 'a t -> (key * 'a) option
                    val max_binding : 'a t -> key * 'a
                    val max_binding_opt : 'a t -> (key * 'a) option
                    val choose : 'a t -> key * 'a
                    val choose_opt : 'a t -> (key * 'a) option
                    val split : key -> 'a t -> 'a t * 'a option * 'a t
                    val find : key -> 'a t -> 'a
                    val find_opt : key -> 'a t -> 'a option
                    val find_first : (key -> bool) -> 'a t -> key * 'a
                    val find_first_opt :
                      (key -> bool) -> 'a t -> (key * 'a) option
                    val find_last : (key -> bool) -> 'a t -> key * 'a
                    val find_last_opt :
                      (key -> bool) -> 'a t -> (key * 'a) option
                    val map : ('-> 'b) -> 'a t -> 'b t
                    val mapi : (key -> '-> 'b) -> 'a t -> 'b t
                    val to_seq : 'a t -> (key * 'a) Seq.t
                    val to_seq_from : key -> 'a t -> (key * 'a) Seq.t
                    val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
                    val of_seq : (key * 'a) Seq.t -> 'a t
                  end
                type map = t E.t
                val set : map -> M.Anick.t -> t -> map
                val app : map -> M.Anick.t -> t
                val bind : map -> t -> t
                val zero : map
                val to_string : map -> string
                type t = map
              end
            module Presentation :
              sig
                type pres = M.Anick.t array
                type t = pres
                val make : t -> t
                val dim : t -> int
                val presentation_to_string : M.Anick.t array -> string
                module Map :
                  sig
                    module M :
                      sig
                        type t = K.t array array
                        type matrix = t
                        val zero : int -> int -> t
                        val init : int -> int -> (int -> int -> K.t) -> t
                        val rows : t -> int
                        val cols : t -> int
                        val get : t -> int -> int -> K.t
                        val to_string : t -> string
                        module Row :
                          sig
                            val is_zero : K.t array array -> int -> bool
                            val replace : t -> int -> K.t array -> t
                            val exchange : t -> int -> int -> t
                            val mult : t -> K.t -> int -> t
                            val madd : t -> int -> K.t -> int -> t
                          end
                        val row_echelon : t -> t
                        val rank : t -> int
                        val nullity : t -> int
                        module Labeled :
                          functor (X : Alphabet.T->
                            sig
                              module L :
                                sig
                                  type key = X.t
                                  type 'a t = 'Map.Make(X).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 update :
                                    key ->
                                    ('a option -> 'a option) -> '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 union :
                                    (key -> '-> '-> 'a option) ->
                                    'a t -> 'a t -> 'a t
                                  val compare :
                                    ('-> '-> int) -> 'a t -> 'a t -> int
                                  val equal :
                                    ('-> '-> bool) ->
                                    'a t -> 'a t -> bool
                                  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 min_binding_opt :
                                    'a t -> (key * 'a) option
                                  val max_binding : 'a t -> key * 'a
                                  val max_binding_opt :
                                    'a t -> (key * 'a) option
                                  val choose : 'a t -> key * 'a
                                  val choose_opt : 'a t -> (key * 'a) option
                                  val split :
                                    key -> 'a t -> 'a t * 'a option * 'a t
                                  val find_opt : key -> 'a t -> 'a option
                                  val find_first :
                                    (key -> bool) -> 'a t -> key * 'a
                                  val find_first_opt :
                                    (key -> bool) ->
                                    'a t -> (key * 'a) option
                                  val find_last :
                                    (key -> bool) -> 'a t -> key * 'a
                                  val find_last_opt :
                                    (key -> bool) ->
                                    'a t -> (key * 'a) option
                                  val map : ('-> 'b) -> 'a t -> 'b t
                                  val mapi :
                                    (key -> '-> 'b) -> 'a t -> 'b t
                                  val to_seq : 'a t -> (key * 'a) Seq.t
                                  val to_seq_from :
                                    key -> 'a t -> (key * 'a) Seq.t
                                  val add_seq :
                                    (key * 'a) Seq.t -> 'a t -> 'a t
                                  val of_seq : (key * 'a) Seq.t -> 'a t
                                  val find : X.t -> 'a t -> 'a
                                  val iter :
                                    (X.t -> '-> unit) -> 'a t -> unit
                                  val of_array : X.t array -> int t
                                end
                              type map = int L.t
                              type t = map * map * matrix
                              val matrix : t -> matrix
                              val zero : X.t array -> X.t array -> t
                              val set : t -> X.t -> X.t -> K.t -> unit
                              val get : t -> X.t -> X.t -> K.t
                              val rank : t -> int
                              val nullity : t -> int
                              val iter_src : (X.t -> unit) -> t -> unit
                              val iter_tgt : (X.t -> unit) -> t -> unit
                              val iter : (X.t -> X.t -> unit) -> t -> unit
                            end
                      end
                    module L :
                      sig
                        module L :
                          sig
                            type key = M.Anick.t
                            type 'a t = 'Map.Make(M.Anick).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 update :
                              key -> ('a option -> 'a option) -> '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 union :
                              (key -> '-> '-> 'a option) ->
                              'a t -> 'a t -> 'a t
                            val compare :
                              ('-> '-> int) -> 'a t -> 'a t -> int
                            val equal :
                              ('-> '-> bool) -> 'a t -> 'a t -> bool
                            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 min_binding_opt : 'a t -> (key * 'a) option
                            val max_binding : 'a t -> key * 'a
                            val max_binding_opt : 'a t -> (key * 'a) option
                            val choose : 'a t -> key * 'a
                            val choose_opt : 'a t -> (key * 'a) option
                            val split :
                              key -> 'a t -> 'a t * 'a option * 'a t
                            val find_opt : key -> 'a t -> 'a option
                            val find_first :
                              (key -> bool) -> 'a t -> key * 'a
                            val find_first_opt :
                              (key -> bool) -> 'a t -> (key * 'a) option
                            val find_last : (key -> bool) -> 'a t -> key * 'a
                            val find_last_opt :
                              (key -> bool) -> 'a t -> (key * 'a) option
                            val map : ('-> 'b) -> 'a t -> 'b t
                            val mapi : (key -> '-> 'b) -> 'a t -> 'b t
                            val to_seq : 'a t -> (key * 'a) Seq.t
                            val to_seq_from : key -> 'a t -> (key * 'a) Seq.t
                            val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
                            val of_seq : (key * 'a) Seq.t -> 'a t
                            val find : M.Anick.t -> 'a t -> 'a
                            val iter :
                              (M.Anick.t -> '-> unit) -> 'a t -> unit
                            val of_array : M.Anick.t array -> int t
                          end
                        type map = int L.t
                        type t = map * map * M.matrix
                        val matrix : t -> M.matrix
                        val zero : M.Anick.t array -> M.Anick.t array -> t
                        val set : t -> M.Anick.t -> M.Anick.t -> K.t -> unit
                        val get : t -> M.Anick.t -> M.Anick.t -> K.t
                        val rank : t -> int
                        val nullity : t -> int
                        val iter_src : (M.Anick.t -> unit) -> t -> unit
                        val iter_tgt : (M.Anick.t -> unit) -> t -> unit
                        val iter :
                          (M.Anick.t -> M.Anick.t -> unit) -> t -> unit
                      end
                    type map = L.t
                    type t = map
                    val app : t -> t -> t
                    val zero : M.Anick.t array -> M.Anick.t array -> t
                    val of_map :
                      Map.map -> M.Anick.t array -> M.Anick.t array -> t
                    val to_map : t -> Map.map
                    val rank : t -> int
                    val nullity : t -> int
                    val to_string : t -> string
                  end
                val iter : (M.Anick.t -> unit) -> t -> unit
                module Complex :
                  sig
                    type t =
                      Module.FreeLeft(K)(M.Anick).Presentation.Complex.t = {
                      modules : pres array;
                      d : Map.t array;
                    }
                    val modules : t -> pres array
                    val maps : t -> Map.t array
                    val length : t -> int
                    val make : pres array -> Map.t array -> t
                    val valid : t -> bool
                    val to_string : t -> string
                    val homology : t -> int array
                  end
                val to_string : M.Anick.t array -> string
              end
          end
        module MF :
          sig
            module M :
              sig
                type t = A.t array array
                type matrix = t
                val zero : int -> int -> t
                val init : int -> int -> (int -> int -> A.t) -> t
                val rows : t -> int
                val cols : t -> int
                val get : t -> int -> int -> A.t
                val to_string : t -> string
                module Row :
                  sig
                    val is_zero : A.t array array -> int -> bool
                    val replace : t -> int -> A.t array -> t
                    val exchange : t -> int -> int -> t
                    val mult : t -> A.t -> int -> t
                    val madd : t -> int -> A.t -> int -> t
                  end
                val row_echelon : t -> t
                val rank : t -> int
                val nullity : t -> int
                module Labeled :
                  functor (X : Alphabet.T->
                    sig
                      module L :
                        sig
                          type key = X.t
                          type 'a t = 'Map.Make(X).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 update :
                            key -> ('a option -> 'a option) -> '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 union :
                            (key -> '-> '-> 'a option) ->
                            'a t -> 'a t -> 'a t
                          val compare :
                            ('-> '-> int) -> 'a t -> 'a t -> int
                          val equal :
                            ('-> '-> bool) -> 'a t -> 'a t -> bool
                          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 min_binding_opt : 'a t -> (key * 'a) option
                          val max_binding : 'a t -> key * 'a
                          val max_binding_opt : 'a t -> (key * 'a) option
                          val choose : 'a t -> key * 'a
                          val choose_opt : 'a t -> (key * 'a) option
                          val split : key -> 'a t -> 'a t * 'a option * 'a t
                          val find_opt : key -> 'a t -> 'a option
                          val find_first : (key -> bool) -> 'a t -> key * 'a
                          val find_first_opt :
                            (key -> bool) -> 'a t -> (key * 'a) option
                          val find_last : (key -> bool) -> 'a t -> key * 'a
                          val find_last_opt :
                            (key -> bool) -> 'a t -> (key * 'a) option
                          val map : ('-> 'b) -> 'a t -> 'b t
                          val mapi : (key -> '-> 'b) -> 'a t -> 'b t
                          val to_seq : 'a t -> (key * 'a) Seq.t
                          val to_seq_from : key -> 'a t -> (key * 'a) Seq.t
                          val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
                          val of_seq : (key * 'a) Seq.t -> 'a t
                          val find : X.t -> 'a t -> 'a
                          val iter : (X.t -> '-> unit) -> 'a t -> unit
                          val of_array : X.t array -> int t
                        end
                      type map = int L.t
                      type t = map * map * matrix
                      val matrix : t -> matrix
                      val zero : X.t array -> X.t array -> t
                      val set : t -> X.t -> X.t -> A.t -> unit
                      val get : t -> X.t -> X.t -> A.t
                      val rank : t -> int
                      val nullity : t -> int
                      val iter_src : (X.t -> unit) -> t -> unit
                      val iter_tgt : (X.t -> unit) -> t -> unit
                      val iter : (X.t -> X.t -> unit) -> t -> unit
                    end
              end
            module M' :
              sig
                type t = K.t array array
                type matrix = t
                val zero : int -> int -> t
                val init : int -> int -> (int -> int -> K.t) -> t
                val rows : t -> int
                val cols : t -> int
                val get : t -> int -> int -> K.t
                val to_string : t -> string
                module Row :
                  sig
                    val is_zero : K.t array array -> int -> bool
                    val replace : t -> int -> K.t array -> t
                    val exchange : t -> int -> int -> t
                    val mult : t -> K.t -> int -> t
                    val madd : t -> int -> K.t -> int -> t
                  end
                val row_echelon : t -> t
                val rank : t -> int
                val nullity : t -> int
                module Labeled :
                  functor (X : Alphabet.T->
                    sig
                      module L :
                        sig
                          type key = X.t
                          type 'a t = 'Map.Make(X).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 update :
                            key -> ('a option -> 'a option) -> '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 union :
                            (key -> '-> '-> 'a option) ->
                            'a t -> 'a t -> 'a t
                          val compare :
                            ('-> '-> int) -> 'a t -> 'a t -> int
                          val equal :
                            ('-> '-> bool) -> 'a t -> 'a t -> bool
                          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 min_binding_opt : 'a t -> (key * 'a) option
                          val max_binding : 'a t -> key * 'a
                          val max_binding_opt : 'a t -> (key * 'a) option
                          val choose : 'a t -> key * 'a
                          val choose_opt : 'a t -> (key * 'a) option
                          val split : key -> 'a t -> 'a t * 'a option * 'a t
                          val find_opt : key -> 'a t -> 'a option
                          val find_first : (key -> bool) -> 'a t -> key * 'a
                          val find_first_opt :
                            (key -> bool) -> 'a t -> (key * 'a) option
                          val find_last : (key -> bool) -> 'a t -> key * 'a
                          val find_last_opt :
                            (key -> bool) -> 'a t -> (key * 'a) option
                          val map : ('-> 'b) -> 'a t -> 'b t
                          val mapi : (key -> '-> 'b) -> 'a t -> 'b t
                          val to_seq : 'a t -> (key * 'a) Seq.t
                          val to_seq_from : key -> 'a t -> (key * 'a) Seq.t
                          val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
                          val of_seq : (key * 'a) Seq.t -> 'a t
                          val find : X.t -> 'a t -> 'a
                          val iter : (X.t -> '-> unit) -> 'a t -> unit
                          val of_array : X.t array -> int t
                        end
                      type map = int L.t
                      type t = map * map * matrix
                      val matrix : t -> matrix
                      val zero : X.t array -> X.t array -> t
                      val set : t -> X.t -> X.t -> K.t -> unit
                      val get : t -> X.t -> X.t -> K.t
                      val rank : t -> int
                      val nullity : t -> int
                      val iter_src : (X.t -> unit) -> t -> unit
                      val iter_tgt : (X.t -> unit) -> t -> unit
                      val iter : (X.t -> X.t -> unit) -> t -> unit
                    end
              end
            val map : (A.t -> K.t) -> M.t -> M'.t
            module Labeled :
              functor (X : Alphabet.T) (X' : Alphabet.T->
                sig
                  module L :
                    sig
                      module L :
                        sig
                          type key = X.t
                          type 'a t = 'Map.Make(X).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 update :
                            key -> ('a option -> 'a option) -> '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 union :
                            (key -> '-> '-> 'a option) ->
                            'a t -> 'a t -> 'a t
                          val compare :
                            ('-> '-> int) -> 'a t -> 'a t -> int
                          val equal :
                            ('-> '-> bool) -> 'a t -> 'a t -> bool
                          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 min_binding_opt : 'a t -> (key * 'a) option
                          val max_binding : 'a t -> key * 'a
                          val max_binding_opt : 'a t -> (key * 'a) option
                          val choose : 'a t -> key * 'a
                          val choose_opt : 'a t -> (key * 'a) option
                          val split : key -> 'a t -> 'a t * 'a option * 'a t
                          val find_opt : key -> 'a t -> 'a option
                          val find_first : (key -> bool) -> 'a t -> key * 'a
                          val find_first_opt :
                            (key -> bool) -> 'a t -> (key * 'a) option
                          val find_last : (key -> bool) -> 'a t -> key * 'a
                          val find_last_opt :
                            (key -> bool) -> 'a t -> (key * 'a) option
                          val map : ('-> 'b) -> 'a t -> 'b t
                          val mapi : (key -> '-> 'b) -> 'a t -> 'b t
                          val to_seq : 'a t -> (key * 'a) Seq.t
                          val to_seq_from : key -> 'a t -> (key * 'a) Seq.t
                          val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
                          val of_seq : (key * 'a) Seq.t -> 'a t
                          val find : X.t -> 'a t -> 'a
                          val iter : (X.t -> '-> unit) -> 'a t -> unit
                          val of_array : X.t array -> int t
                        end
                      type map = int L.t
                      type t = map * map * M.matrix
                      val matrix : t -> M.matrix
                      val zero : X.t array -> X.t array -> t
                      val set : t -> X.t -> X.t -> A.t -> unit
                      val get : t -> X.t -> X.t -> A.t
                      val rank : t -> int
                      val nullity : t -> int
                      val iter_src : (X.t -> unit) -> t -> unit
                      val iter_tgt : (X.t -> unit) -> t -> unit
                      val iter : (X.t -> X.t -> unit) -> t -> unit
                    end
                  module L' :
                    sig
                      module L :
                        sig
                          type key = X'.t
                          type 'a t = 'Map.Make(X').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 update :
                            key -> ('a option -> 'a option) -> '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 union :
                            (key -> '-> '-> 'a option) ->
                            'a t -> 'a t -> 'a t
                          val compare :
                            ('-> '-> int) -> 'a t -> 'a t -> int
                          val equal :
                            ('-> '-> bool) -> 'a t -> 'a t -> bool
                          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 min_binding_opt : 'a t -> (key * 'a) option
                          val max_binding : 'a t -> key * 'a
                          val max_binding_opt : 'a t -> (key * 'a) option
                          val choose : 'a t -> key * 'a
                          val choose_opt : 'a t -> (key * 'a) option
                          val split : key -> 'a t -> 'a t * 'a option * 'a t
                          val find_opt : key -> 'a t -> 'a option
                          val find_first : (key -> bool) -> 'a t -> key * 'a
                          val find_first_opt :
                            (key -> bool) -> 'a t -> (key * 'a) option
                          val find_last : (key -> bool) -> 'a t -> key * 'a
                          val find_last_opt :
                            (key -> bool) -> 'a t -> (key * 'a) option
                          val map : ('-> 'b) -> 'a t -> 'b t
                          val mapi : (key -> '-> 'b) -> 'a t -> 'b t
                          val to_seq : 'a t -> (key * 'a) Seq.t
                          val to_seq_from : key -> 'a t -> (key * 'a) Seq.t
                          val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
                          val of_seq : (key * 'a) Seq.t -> 'a t
                          val find : X'.t -> 'a t -> 'a
                          val iter : (X'.t -> '-> unit) -> 'a t -> unit
                          val of_array : X'.t array -> int t
                        end
                      type map = int L.t
                      type t = map * map * M'.matrix
                      val matrix : t -> M'.matrix
                      val zero : X'.t array -> X'.t array -> t
                      val set : t -> X'.t -> X'.t -> K.t -> unit
                      val get : t -> X'.t -> X'.t -> K.t
                      val rank : t -> int
                      val nullity : t -> int
                      val iter_src : (X'.t -> unit) -> t -> unit
                      val iter_tgt : (X'.t -> unit) -> t -> unit
                      val iter : (X'.t -> X'.t -> unit) -> t -> unit
                    end
                  val map :
                    (X.t -> X'.t) ->
                    (X.t -> X'.t) -> (A.t -> K.t) -> L.t -> L'.t
                end
          end
        module MFL :
          sig
            module L :
              sig
                module L :
                  sig
                    type key = M.Anick.t
                    type 'a t = 'Map.Make(M.Anick).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 update :
                      key -> ('a option -> 'a option) -> '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 union :
                      (key -> '-> '-> 'a option) -> 'a t -> 'a t -> 'a t
                    val compare : ('-> '-> int) -> 'a t -> 'a t -> int
                    val equal : ('-> '-> bool) -> 'a t -> 'a t -> bool
                    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 min_binding_opt : 'a t -> (key * 'a) option
                    val max_binding : 'a t -> key * 'a
                    val max_binding_opt : 'a t -> (key * 'a) option
                    val choose : 'a t -> key * 'a
                    val choose_opt : 'a t -> (key * 'a) option
                    val split : key -> 'a t -> 'a t * 'a option * 'a t
                    val find_opt : key -> 'a t -> 'a option
                    val find_first : (key -> bool) -> 'a t -> key * 'a
                    val find_first_opt :
                      (key -> bool) -> 'a t -> (key * 'a) option
                    val find_last : (key -> bool) -> 'a t -> key * 'a
                    val find_last_opt :
                      (key -> bool) -> 'a t -> (key * 'a) option
                    val map : ('-> 'b) -> 'a t -> 'b t
                    val mapi : (key -> '-> 'b) -> 'a t -> 'b t
                    val to_seq : 'a t -> (key * 'a) Seq.t
                    val to_seq_from : key -> 'a t -> (key * 'a) Seq.t
                    val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
                    val of_seq : (key * 'a) Seq.t -> 'a t
                    val find : M.Anick.t -> 'a t -> 'a
                    val iter : (M.Anick.t -> '-> unit) -> 'a t -> unit
                    val of_array : M.Anick.t array -> int t
                  end
                type map = int L.t
                type t = map * map * MF.M.matrix
                val matrix : t -> MF.M.matrix
                val zero : M.Anick.t array -> M.Anick.t array -> t
                val set : t -> M.Anick.t -> M.Anick.t -> A.t -> unit
                val get : t -> M.Anick.t -> M.Anick.t -> A.t
                val rank : t -> int
                val nullity : t -> int
                val iter_src : (M.Anick.t -> unit) -> t -> unit
                val iter_tgt : (M.Anick.t -> unit) -> t -> unit
                val iter : (M.Anick.t -> M.Anick.t -> unit) -> t -> unit
              end
            module L' :
              sig
                module L :
                  sig
                    type key = M.Anick.t
                    type 'a t = 'Map.Make(M.Anick).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 update :
                      key -> ('a option -> 'a option) -> '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 union :
                      (key -> '-> '-> 'a option) -> 'a t -> 'a t -> 'a t
                    val compare : ('-> '-> int) -> 'a t -> 'a t -> int
                    val equal : ('-> '-> bool) -> 'a t -> 'a t -> bool
                    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 min_binding_opt : 'a t -> (key * 'a) option
                    val max_binding : 'a t -> key * 'a
                    val max_binding_opt : 'a t -> (key * 'a) option
                    val choose : 'a t -> key * 'a
                    val choose_opt : 'a t -> (key * 'a) option
                    val split : key -> 'a t -> 'a t * 'a option * 'a t
                    val find_opt : key -> 'a t -> 'a option
                    val find_first : (key -> bool) -> 'a t -> key * 'a
                    val find_first_opt :
                      (key -> bool) -> 'a t -> (key * 'a) option
                    val find_last : (key -> bool) -> 'a t -> key * 'a
                    val find_last_opt :
                      (key -> bool) -> 'a t -> (key * 'a) option
                    val map : ('-> 'b) -> 'a t -> 'b t
                    val mapi : (key -> '-> 'b) -> 'a t -> 'b t
                    val to_seq : 'a t -> (key * 'a) Seq.t
                    val to_seq_from : key -> 'a t -> (key * 'a) Seq.t
                    val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
                    val of_seq : (key * 'a) Seq.t -> 'a t
                    val find : M.Anick.t -> 'a t -> 'a
                    val iter : (M.Anick.t -> '-> unit) -> 'a t -> unit
                    val of_array : M.Anick.t array -> int t
                  end
                type map = int L.t
                type t = map * map * MF.M'.matrix
                val matrix : t -> MF.M'.matrix
                val zero : M.Anick.t array -> M.Anick.t array -> t
                val set : t -> M.Anick.t -> M.Anick.t -> K.t -> unit
                val get : t -> M.Anick.t -> M.Anick.t -> K.t
                val rank : t -> int
                val nullity : t -> int
                val iter_src : (M.Anick.t -> unit) -> t -> unit
                val iter_tgt : (M.Anick.t -> unit) -> t -> unit
                val iter : (M.Anick.t -> M.Anick.t -> unit) -> t -> unit
              end
            val map :
              (M.Anick.t -> M.Anick.t) ->
              (M.Anick.t -> M.Anick.t) -> (A.t -> K.t) -> L.t -> L'.t
          end
        val complex :
          ?augmentation:Algebra.Presentation.Augmentation.t ->
          Algebra.Presentation.t ->
          int -> Algebra.Presentation.Anick.KMod.Presentation.Complex.t
        val homology :
          ?augmentation:Algebra.Presentation.Augmentation.t ->
          Algebra.Presentation.t -> int -> int array
      end
  end