
I'm wondering if someone can cast some light on a pattern I've come across, which I'm calling the "mother of all X" pattern after Dan Piponi's blog post (http://blog.sigfpe.com/2008/12/mother-of-all-monads.html). Edward Kmett has also explored these ideas here: http://www.mail-archive.com/haskell-cafe@haskell.org/msg57738.html Preliminaries === Q: What is the "mother of all X", where X is some type class? A: It is a data type D such that: 1. There exist total functions:
lift :: X d => d a -> D a lower :: X d => D a -> d a
2. And you can write a valid instance:
instance X D
With *no superclass constraints*. 3. (We may also add the constraint that D is somehow the "smallest such" data type, but I don't know in exactly what sense I mean this). So the "mother of all X" is a data type that somehow encodes all of the functions that the X type class gives you. An example is in order! Example 1: Yoneda is the mother of all Functors === The code in this example and the next one is shamelessly stolen from the category-extras package (thanks Edward!). Here is the data type:
-- flip fmap :: forall a. f a -> (forall b. (a -> b) -> f b) newtype Yoneda f a = Yoneda { runYoneda :: forall b. (a -> b) -> f b }
And the injections. As it turns out, we don't need the Functor constraint on the lowerYoneda call:
liftYoneda :: Functor f => f a -> Yoneda f a liftYoneda f = Yoneda (flip fmap f)
lowerYoneda :: Yoneda f a -> f a lowerYoneda f = runYoneda f id
Finally, we can write the Functor instance. Notice that we don't need to make use of the Functor instance for f: all of the methods of Functor f have been somehow encoded into the Yoneda data type!
instance Functor (Yoneda f) where fmap f m = Yoneda (\k -> runYoneda m (k . f))
Note that we can also write an instance (Y f => Y (Yoneda f)) for any Functor subclass Y. But (Yoneda f) is not the mother of all Y, because we will need the Y f constraint to do so. Here is an example:
instance Applicative f => Applicative (Yoneda f) where pure = liftYoneda . pure mf <*> mx = liftYoneda (lowerYoneda mf <*> lowerYoneda mx)
Why is (Yoneda f) interesting? Because if I take some expression whose type is quantified over any superclass of Functor, and we want to run it with Functor instantiated to some F, if we instead run it with Functor instantiated to (Yoneda f) and then use lowerYoneda, we will automatically get guaranteed fmap fusion. Example 2: Codensity is the mother of all Monads === Data type:
-- (>>=) :: forall a. m a -> (forall b. (a -> m b) -> m b) newtype Codensity m a = Codensity { runCodensity :: forall b. (a -> m b) -> m b }
Isomorphism. We need Monad constraints on both ends now:
liftCodensity :: Monad m => m a -> Codensity m a liftCodensity m = Codensity ((>>=) m)
lowerCodensity :: Monad m => Codensity m a -> m a lowerCodensity m = runCodensity m return
Instances:
instance Functor (Codensity f) where fmap f m = Codensity (\k -> runCodensity m (k . f))
instance Applicative (Codensity f) where pure x = Codensity (\k -> k x) mf <*> mx = Codensity (\k -> runCodensity mf (\f -> runCodensity mx (\x -> k (f x))))
instance Monad (Codensity f) where return = pure m >>= k = Codensity (\c -> runCodensity m (\a -> runCodensity (k a) c))
Again, using (Codensity m) where you used m before can yield a performance improvement, notably in the case of free monads. See http://haskell.org/haskellwiki/Performance/Monads or http://wwwtcs.inf.tu-dresden.de/~voigt/mpc08.pdf. Example 3: Wotsit is the mother of all Categories === I don't actually know what the right name for this data type is, I just invented it and it seems to work:
-- (>>>) :: forall a b. t a b -> (forall c. t b c -> t a c) newtype Wotsit t a b = Wotsit { runWotsit :: forall c. t b c -> t a c }
Isomorphism:
liftWotsit :: Category t => t a b -> Wotsit t a b liftWotsit t = Wotsit ((>>>) t)
lowerWotsit :: Category t => Wotsit t a b -> t a b lowerWotsit t = runWotsit t id
And finally the instance:
instance Category (Wotsit t) where id = Wotsit id t1 . t2 = Wotsit (runWotsit t2 . runWotsit t1)
This is *strongly* reminiscent of normalisation-by-evaluation for monoids (reassociation realised by assocativity of function application), which is not surprising because Category is just a monoid. There is probably some connection between NBE and Yoneda (e.g. "Normalization and the Yoneda embedding", but I can't get access to this paper electronically). Conclusion === So I have a lot of questions about this stuff: 1. Is there a way to mechanically derive the "mother of all X" from the signature of X? Are these all instances of a single categorical framework? 2. Is there a mother of all idioms? By analogy with the previous three examples, I tried this:
-- (<**>) :: forall a. i a -> (forall b. i (a -> b) -> i b) newtype Thingy i a = Thingy { runThingy :: forall b. i (a -> b) -> i b }
But I can't see how to write either pure or <*> with that data type. This version seems to work slightly better:
newtype Thingy i a = Thingy { runThingy :: forall b. Yoneda i (a -> b) -> i b }
Because you can write pure (pure x = Thingy (\k -> lowerYoneda (fmap ($ x) k))). But <*> still eludes me! 3. Since (Codensity m) enforces >>= associativity, perhaps it can be used to define correct-by-construction monads in the style of operational or MonadPrompt? Any insight offered would be much appreciated :-) Cheers, Max