Mark P Jones wrote:
| | Neat.  And it solves a problem I was kludging around with explicit,
| | existentially quantified dictionaries.
| 
| Great!  Can I look forward to hearing more about that some time?

OK, it's to do with arrows:

> class Arrow a where
>       arr :: (b -> c) -> a b c
>       (>>>) :: a b c -> a c d -> a b d
>       first :: a b c -> a (b,d) (c,d)

Given an arrow a, I want to form a new arrow

> newtype Instance f a b c = Inst (a (f b) (f c))

Defining arr and >>> is easy (provided f is a functor and a an arrow),
but to define first, we need an isomorphism between f(b,c) and (f b,g b)
for some functor g.  Some examples:

        f       g
        --------------------------------------------
        (,) s   Id      state transformers
        Stream  Stream  synchronous circuits
        (->) s  (->) s  a version of Dick Kieburtz's co-state comonad

With functional dependencies, I can presumably write

  class (Functor f, Functor g) => Zippable f g | f -> g where
        unzipper :: f(b,c) -> (f b, g c)
        zipper :: (f b, g c) -> f(b,c)

  instance Zippable ((->) s) ((->) s) where
        unzipper f = (fst . f, snd . f)
        zipper (f,g) x = (f x, g x)

  instance (Zippable f g, Arrow a) => Arrow (Instance f a) where
        arr f = Inst (arr (fmap f))
        Inst f >>> Inst g = Inst (f >>> g)
        first (Inst f) = Inst (arr unzipper >>> first f >>> arr zipper)

The type constructor g only features inside the last composition;
none of the top-level things have types that mention g, so doing this
without dependencies isn't easy.

The kludge I used was an explicit dictionary

> data ZipD f =
>       forall g. ZipD
>               (forall b,c. f(b,c) -> (f b, g c))
>               (forall b,c. (f b, g c) -> f(b,c))

and a class

> class Functor f => Zippable f where
>       zipD :: ZipD f

Defining an instance looked like this:

> instance Zippable ((->) s) where
>       zipD = ZipD unzipper zipper
>               where   unzipper f = (fst . f, snd . f)
>                       zipper (f,g) x = (f x, g x)

Then I could define the arrow:

> instance (Zippable f, Arrow a) => Arrow (Instance f a) where
>       arr f = Inst (arr (fmap f))
>       Inst f >>> Inst g = Inst (f >>> g)
>       first (Inst f) = Inst (arr unzipper >>> first f >>> arr zipper)
>               where   ZipD unzipper zipper = zipD

This kludge only handles situations where a subset of the arguments are
dependent on the rest.


Reply via email to