Proposal: Add Compositor class as superclass of Arrow

Cale Gibbard cgibbard at gmail.com
Fri Oct 19 18:03:15 EDT 2007


On 19/10/2007, apfelmus <apfelmus at quantentunnel.de> wrote:
> Cale Gibbard wrote:
> > fmap (f . g) x = fmap f (fmap g x)
> >   becomes:
> > (f . g) . x = f . (g . x)
> > fmap id x = x
> >   becomes
> > id . x = x
>
> Nice! Can this be done in Category Theory, too? I mean, it would be nice
> to internalize morphism, functors, natural transformations, ... in one
> and the same category (like Hask), so there's less fuss. I.e. given a
> category  C , construct an category  C\infty  that is basically the same
> as  C  but also contains the functors, natural transformations etc. of
> C and has this handy infix (.) operation.

Well, sort of, though they typically don't use quite that notation for
it. There is work on generalising to higher-dimensional categories,
where, for example, treating Cat as a 2-category, you have 0-cells
which are categories, 1-cells, which are functors, and 2-cells, which
are natural transformations between parallel functors. Natural
transformations support two kinds of composition, called vertical
(which is the usual one) and horizontal composition, so typically some
separate notation, like an asterisk, is chosen for horizontal
composition.

>
> > I've tried this out for a while, and it is actually rather nice to use
> > in many cases. Functor application is common enough that having a
> > one-character representation for it is great.
>
> I can't remember using fmap/liftM very often, but if I use `liftM`, then
> often in infix notation, so and infix symbol for  fmap  is indeed a very
> good idea.
>
> However, (.) in that role confuses me because I always think that the
> right argument should be function. In other words, I'm fine with
>
>    print . sum . map read . lines . readFile
>
> ( with a hypothetical instance Category (a -> IO b) ) while your
> proposal gives rise to
>
>    show . sum . map read . lines . readFile "foo.txt"
>
> which makes me feel ill.

Hmm, it doesn't really bother me so much. There are a number of ways
to read that. At the two extremes, you can read it as the composition
(show . sum . map read . lines) being functorially applied to
(readFile "foo.txt), or as a chain of functor applications with IO as
the functor at the other extreme. Of course, these are equal.

> In my opinion, function composition and
> function application should have separate notations. The new (.) blurs
> these lines too much for my taste (i.e. (.) :: (a -> b) -> Id a -> Id b)
> and I prefer <$> (or even plain $) for  fmap .
>
>
> In addition, I always longed for categories without an embedding (a ->
> b) -> c a b , they keep popping up while I program in Haskell and more
> often than I need infix  fmap . Also, I dislike (>>>) or (<<<) and very
> much prefer (.) for them.
>
>
> But in the end, we can have both worlds of (.) without name clash!
> Simply annotate functors with the category they operate on :)
>
>    class Category c => Functor c f where
>       (.) :: c a b -> f a -> f b
>
>    instance Functor (->) [] where
>       (.) = map
>
>    instance Category c => Functor c (c d) where
>       (.) = `o`
>
>
> Regards,
> apfelmus

Of course! That's quite a nice idea. Then we can have monads over an
arbitrary category on the objects of Hask as well, though I'm not sure
of too many examples yet, apart from the obvious one for Arrows.

class Functor c m => Monad c m where
   return :: a -> m a
   join :: m (m a) -> m a
   (>>=) :: m a -> (a -> m b) -> m b
   x >>= f = join (f . x)
   join x = x >>= id

 - Cale


More information about the Libraries mailing list