Design suggestions for a functor with existential wrappers

I’m designing an interface for a data structure that uses GADTs and I’ve run into a small blocker.

My functor accepts module types of the following

module type S = sig 
 
  type t
  type 'a op (** operations on the data structure, returning a result of ['a] *)
  
  type wrap = Mk : 'a op * ('a -> unit) -> wrap
  (* existential type, with callback to return the result *)

  val run: t -> wrap list -> unit
  (* run the operations on the data structure *)
end

(simplified for presentation)

My functor collects requests to the data structure and uses run to execute them – as such, it needs access to the Wrap constructor:

module Make (S: S) = struct
     type t = { t: S.t; mutable queued: S.wrap list } 
     let create t = { t; queued=[] }
     let enqueue (t: t) (op: 'a S.op) (f: 'a -> unit) = 
          t.queued <- S.Mk (op, f) :: t.queued
     let execute_queued t =
         S.run t.t t.queued;
         t.queued <- []
end

(again, simplified for presentation)

This works, but I’m finding the interface slightly unergonomic, as each time the user must instantiate S, they must define a fresh wrapper type wrap = Mk ....

Anyone know if there’s a nicer way of encoding this?

Don’t know if it’s possible in your more complete case, but you may try to simpifly your S signature with something like this:

module type S = sig
  type t
  type 'a op

  val run : 'a op -> t -> 'a
end

It should be enough to implement your functor. Your existential wrapper can be defined in your functor, and even be only internal and not exposed in your interface with suitable smart constructors.

module Make (S : S ) = struct
  type wrap = W : 'a S.op * ('a -> unit) -> wrap
  type t = {t : S.t; mutable queued : wrap list}

  let create t = ...
  let enqueue t op f = ...

  let execute_queued t = 
    List.iter (fun (W (op, f)) -> f @@ S.run op t.t) t.queued;
    t.queued <- []
end

Alas, changing the signature like you suggest isn’t possible - one of the key things that I need to preserve in my signature is the run : t -> wrap list unit function that takes in several operations – indeed, if such a change were possible, it would be fairly straightforward to refactor the wrap operation into the functor.

Maybe the simplified functor I provided gave was more confusing that necessary - my interface must allow implementations to rely on the fact that they may see more than one operation at a time.

One can imagine an instantiation of the signature where the run function only runs the first n operations, or sorts the operations by priority, and only does high priority ones, for example.

You could use a second functor for wrapping


module Wrap(M : sig type 'a op end) = struct
  type t = Mk : 'a M.op * ('a -> unit) -> t
end

module type S = sig

  type t

  module Op : sig
    type 'a op (** operations on the data structure, returning a result of ['a] *)
  end

  (* existential type, with callback to return the result *)

  val run: t -> Wrap(Op).t list -> unit
  (* run the operations on the data structure *)
end


module Make (S: S) = struct
  module W = Wrap(S.Op)
  type t = { t: S.t; mutable queued: W.t list }
  let create t = { t; queued=[] }
  let enqueue (t: t) (op: 'a S.Op.op) (f: 'a -> unit) =
    t.queued <- W.Mk (op, f) :: t.queued
  let execute_queued t =
    S.run t.t t.queued;
    t.queued <- []
end

module DummyImpl : S = struct
  type t
  module Op = struct
    type 'a op
  end
  module W = Wrap(Op)
  let run _ (l: W.t list) = List.iter (fun (W.Mk (op, f)) -> assert false) l
end

not sure if that’s nicer in practice.

1 Like

Hmm, nice! Yes, that does avoid the repeated type definitions, although I guess, as you mention, it may be that the cure is worse than the disease in this case.

I wonder if there’s another way of expressing this relation without so much boilerplate.

If each implementation must have control over their batching strategy, then the wrapper type should be define by them. But, to define your functor, it is not necessary to know how a wrapped value is constructed. So, you could simplify your signature with this:

module type S = sig
  type t
  type wrap
  val run : t -> wrap list -> unit
end

module Make (S : S) : sig
  type t
  val create : S.t -> t
  val enqueue : t -> S.wrap -> unit
  val execute_queued : t -> unit
end

Here, each implementation is free to expose the way to construct wrapped op as they want.

1 Like

In-passing remark: if your op GADTs contain

| Map : 'a op * ('a -> 'b) -> 'b op

then exists 'a. ('a op * ('a -> unit)) is isomorphic to unit op, which does not require any existential wrapping to be defined.

(Encouraging your users to add Map is not necessarily much more convenient than forcing them to introduce Wrap, but maybe it is already there most of the time, or would be a nice expressivity addition with other benefits.)

1 Like

Yes, I suppose this is likely the most general construction. In my case, there is some further interactions between the functor and the signature, so exposing how the wrapper is constructed makes it easier to keep the type of the signature as simple as possible. I guess I’ll just have to bite the bullet and require users to expose the wrapper each time.