[Haskell-beginners] Re: Monadic composition without throwing genericity under the bus?

Heinrich Apfelmus apfelmus at quantentunnel.de
Thu Feb 4 05:43:42 EST 2010


Dave Bayer wrote:
> Let me be as concise as I can, for a second try.
> 
> One can't make a function-valued monad into an instance of Category,
> because a Category takes two type arguments, while a Monad takes one?
> [...]
> I simply can't believe that I'm the first person to stumble over
> this. Either this is a famous rough edge, and others can list off a
> dozen similar circumstances where one gets stuck, or there's an easy
> work-around I'm just not seeing.
> 
> Can anyone confirm that it's simply not possible to plumb type
> classes the way I want to plumb them? If so, should I be proposing a
> language extension on a different mailing list?

You want a composition of functors

   Wrap m  ~  m ° (->)

but since higher-kinded polymorphism is a bit limited in Haskell
(decidability!), I don't think there's a way to make this an instance of
Category directly.


The usual solution is to make  Wrap  a newtype

   newtype Wrap m a b = Wrap (m (a -> b))

   instance Monad m => Category (Wrap m) where ...

and live with it.


If you want to be a bit more generic, you can use a newtype to denote
functor composition

   {-# LANGUAGE TypeSynonymInstances #-}

   newtype f `O` g a b = O (f (g a b))

   instance Monad m => Category (m `O` (->)) where
      id    = return id
      f . g = liftM2 (.) f g


But in both cases, there is no way around the fact that the Category
class needs a new type as argument.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com



More information about the Beginners mailing list