Tying the knot between two modules

Imagine I have the two following modules:

module Base = struct
  type abst

  type base = Ident of string | Abst of abst list

  let pr pra = function
    | Ident s -> s
    | Abst al -> String.concat ", " (List.map pra al)
end

module Abst = struct
  type base
  type abst = Foo of base

  let pra pr = function
    | Foo b -> Printf.sprintf "Foo (%s)" (pr b)
end

Is there a way that I can tie the knot between the two? I know how to do it for the types using recursive modules, but not for the code part.

This is how I do it for the types:

module type BASESIG = sig
  type base
end

module type BASE = sig
  type abst
  type base = Ident of string | Abst of abst list
end

module MkAbst (B: BASESIG) = struct
  include B
  type abst = Foo of base
end

module rec MyAbst : sig
  include BASE with type abst = MkAbst(Base).abst
end = MyAbst

It’s only slightly more tricky:

module type BaseT = sig
  type base
  val pr : base -> string
end

module type AbstT = sig
  type abst
  val pra : abst -> string
end

module BaseF (Abst : AbstT) = struct
  type base = Ident of string | Abst of Abst.abst list

  let pr = function
    | Ident s -> s
    | Abst al -> String.concat ", " (List.map Abst.pra al)
end

module AbstF (Base : BaseT) = struct
  type abst = Foo of Base.base

  let pra = function
    | Foo b -> Printf.sprintf "Foo (%s)" (Base.pr b)
end

module rec Base : BaseT = BaseF(Abst)
and Abst : AbstT = AbstF(Base)

It’s also possible to simply make Base and Abst mutually recursive (without any functor), if you’re ok with having both implementations in the same file. And the middle-ground option, with one file defining a functor and the other one containing the recursive binding works too.
The main thing you should be careful about with recursive modules is the “safe module” constraint: every recursive cycle in a recursive module binding must contain at least one definition which only exports types (including module types if you want) and functions. (Or submodules with the same constraints. Classes are allowed too.)
Example:

module rec M : sig
  type t
  val compare : t -> t -> int
  val default : t
end = struct
  type t = T | S of S.t
  let compare x y = 0
  let default = S (S.singleton T)
end and S : Set.S with type elt = M.t = Set.Make(M)

The compiler will complain about the cycle M -> S -> M, in which neither M nor S is safe (M.default is not a function, and S.empty isn’t either). In this particular case you can fix it by making default a function (val default : unit -> t and let default () = ...), but sometimes it will not work.

Another option that’s lighter than using functors is to use an abstract type to break the recursive cycle.

module Base = struct

  type base = Ident of string | Abst of (base abst) list

  let pr pra = function
    | Ident s -> s
    | Abst al -> String.concat ", " (List.map pra al)
end

module Abst = struct
  type 'a abst = Foo of 'a

  let pra pr = function
    | Foo b -> Printf.sprintf "Foo (%s)" (pr b)
end
1 Like

This is very elegant, thanks a lot! There is one issue, though: as the module types are restricted to BaseT and AbstT, one cannot have access to the constructors. If I write something like

let test = Base.Abst []

I get an error telling me there is no Abst constructor.

Ah, indeed. It’s a bit ugly (and you need to duplicate some type definitions), but you can write the recursive binding that way:

module rec Base : sig
  type base = Ident of string | Abst of Abst.abst list
  include BaseT with type base := base
end = BaseF(Abst)
and Abst : sig
  type abst = Foo of Base.base
  include AbstT with type abst := abst
end = AbstF(Base)

Thanks again, but this won’t work as the Abst part and the Base part are in different files. Abst is generated (and can have any kind of repetition), and Base is written by the user. I’ve tried to break the symmetry with this:

module type BASESIG = sig
  type base
end

module type PRBASE = sig
  type abst
  type base = Ident of string | Abst of abst list

  val pr : (abst -> string) -> base -> string
end

module MkAbst (B: BASESIG) = struct
  include B
  type abst = Foo of base
end

module Inst (Base: PRBASE) = struct

  module rec MyAbst : sig
    include PRBASE with type abst = MkAbst(Base).abst
  end = MyAbst

  include MkAbst(MyAbst)

  let rec pra v = match v with
    | Foo b -> Printf.sprintf "Foo (%s)" (Base.pr pra v)
end

but I don’t know how to say that Base.abst = MkAbst(Base).abst, so OCaml complains about pra having the wrong type.

Maybe I need objects and late binding to solve this… In any case, thanks again for the help.

Each time I think I’m getting there, I’m reaching the same problem: how to make two abstract types equal to a third one. Here is my latest attempt:

module type BASE = sig
  type abst
  type base
  val prb : (abst -> string) -> base -> string
end

module Base = struct
  type abst
  type base = Ident of string | Abst of abst list

  let prb pra = function
    | Ident s -> s
    | Abst al -> String.concat ", " (List.map pra al)
end

module Abst = struct
  type 'b abst = Foo of 'b

  let pra prb v = match v with
    | Foo b -> Printf.sprintf "Foo (%s)" (prb b)
end

module Inst (B: BASE with type base = Base.base with type abst = Base.base Abst.abst) = struct
  let rec prb b = B.prb pra b
      and pra a = Abst.pra prb a
end

include Inst(Base : BASE with type base = Base.base with type abst = Base.base Abst.abst)

It all goes well until the last line, where the type-checker complains that Base.abst (which is abstract) is not compatible with Base.base Abst.abst.

Is there a way to tell the type-checker that BASE.abst = Base.abst = some type?

Please correct me if I am wrong, I think there is no way for an abstract type t declared in a module implementation to be made equal to another type t', if t' is not itself an alias to t. This is opposed to an abstract type in a module signature, that can be refined with the with type operator. If you want Base to be parameterized by the type Abst.abst, I think the way to go is to use functors, as @vlaviron suggested. Here is a somehow minimal correction of your code with functors:

module type BASE = sig
  type abst
  type base
  val prb : (abst -> string) -> base -> string
end

module type ABST = sig
  type 'a abst
end

module BaseF (Abst : ABST) = struct
  type base = Ident of string | Abst of abst list
  and abst = base Abst.abst

  let prb pra = function
    | Ident s -> s
    | Abst al -> String.concat ", " (List.map pra al)
end

module Abst = struct
  type 'b abst = Foo of 'b

  let pra prb v = match v with
    | Foo b -> Printf.sprintf "Foo (%s)" (prb b)
end

module Base = BaseF (Abst)

module Inst (B: BASE with type base = Base.base with type abst = Base.base Abst.abst) = struct
  let rec prb b = B.prb pra b
      and pra a = Abst.pra prb a
end

include Inst(Base : BASE with type base = Base.base with type abst = Base.base Abst.abst)

Anyway, if we come back to the module rec suggestion of @vlaviron that is more straightforward (I think), it is worth noticing that you can still have BaseF and AbstF defined in two different files, and just define the module rec in a third file (or even in one of the files that define BaseF and AbstF), to “tight the knot”.

I was not aware of this. Could you explain how this works assuming a third file?

I think that if base.ml (or actually base.mli) exposes Base.abst as abstract, you will never be able to equate it to anything later (as @thierry-martinez said above).
One possible solution would be to make the type Base.base parametric in the abst type:

module Base = struct
  type 'abst base = Ident of string | Abst of 'abst list

  let prb pra = function
    | Ident s -> s
    | Abst al -> String.concat ", " (List.map pra al)
end

Then you can bind the types in Abst:

module Abst = struct
  type base = abst Base.base
  and abst = Foo of base

  let rec pra v = match v with
    | Foo b -> Printf.sprintf "Foo (%s)" (prb b)
  and prb v = Base.prb pra v
end

This has the inconvenient that the initial Base module doesn’t have exactly the signature you’d like (the same is true of the functor approach).
You could have abst.ml re-export a Base sub-module with the final signature, but if you’re not careful you risk confusion between the Base and Abst.Base modules in the rest of the code.

1 Like

Another approach to having access to the constructors in “the other” module is to hoist the type definitions out of the recursive module definition, making them polymorphic, and then only instantiating them in the recursive modules:

type 'abst base = Ident of string | Abst of 'abst list
type 'base abst = Foo of 'base

module BaseF (Abst : AbstT) = struct
  type nonrec base = Abst.abst base
  ...
end

module AbstF (Base : BaseT) = struct
  type nonrec abst = Base.base abst
  ...
end

I don’t know how that interacts with your desired divisions into files though.

Thanks for all the replies! As noted above, I was confused about the fact that types in modules are new (unlike types in signatures), so what I was trying was hopeless. Thanks to @esope, I now have a solution I’m happy with:

module type BASE = sig
  type 'abst base
  val prb: ('abst -> string) -> 'abst base -> string
end

module Abst (Base: BASE) = struct
  type base = abst Base.base
  and abst = Foo of base

  let rec pra = function
    | Foo b -> Printf.sprintf "Foo(%s)" (prb b)
  and prb b = Base.prb pra b
end

module Base = struct
  type 'abst base = Ident of string | Abst of 'abst list

  let rec prb pra = function
    | Ident s -> s
    | Abst al -> Printf.sprintf "[%s]" (String.concat "; " (List.map pra al))
end

module Inst = Abst(Base)

include Inst

let test = Foo (Abst [Foo (Ident "Bar"); Foo (Ident "Baz")])

let _ = print_endline (pra test)

The module type BASE and the functor Abst can be generated, and the user has the type to guide them (with names of the polymorphic variables being consistent with their final type).

Thanks again, it was a nice learning journey!

Ok, I think I missed a forth file for defining signatures! (Even if, again, this forth file can be one of the files that define BaseF or AbstF.)

I think that there is no difficulty except that I don’t know how to explain this clearly. More concretely (sorry, I just copy-paste @vlaviron code!), you can have in types.ml:

module type BaseT = sig
  type base
  val pr : base -> string
end

module type AbstT = sig
  type abst
  val pra : abst -> string
end

and if basef.ml:

module BaseF (Abst : Types.AbstT) = struct
  type base = Ident of string | Abst of Abst.abst list

  let pr = function
    | Ident s -> s
    | Abst al -> String.concat ", " (List.map Abst.pra al)
end

and in abstf.ml:

module AbstF (Base : Types.BaseT) = struct
  type abst = Foo of Base.base

  let pra = function
    | Foo b -> Printf.sprintf "Foo (%s)" (Base.pr b)
end

and in knot.ml:

module rec Base : sig
  type base = Ident of string | Abst of Abst.abst list
  include Types.BaseT with type base := base
end = Basef.BaseF(Abst)
and Abst : sig
  type abst = Foo of Base.base
  include Types.AbstT with type abst := abst
end = Abstf.AbstF(Base)

Ah ok. So just to clarify, this is using functors, which isn’t quite recursive modules. If you allow functor usage, I believe one can come up with a cleaner solution. True recursive modules do not require functors as they can fully reference one another, but they cannot be placed in separate files.

This is the case: we generate some modules/functors in a file, and others are written by the user in another file. Until now we were using recursive modules to tie the knot, but having to add mutually recursive functions broke the approach.

Just to clarify again though - the functions aren’t the problem. The functions in mutually recursive modules can see one another just fine AFAIK. The problem is that you’re using multiple files, and mutually recursive modules don’t support multiple files.

For example:

module rec A : sig type t = C val foo: B.t -> bool end = struct
   type t = C
   let foo = function | B.D -> true | _ -> false
end
and B : sig type t = D val foo: A.t -> bool end = struct
   type t = D
   let foo = function | A.C -> true | _ -> false
end;;

Now, recursive modules are a pain for other reasons. For example, you have to write their signature down, which is annoying, and of course there’s the single file limitation. But the issue is not that you have to write functions, as you can see from the example.