Proposal: Add Compositor class as superclass of Arrow

Cale Gibbard cgibbard at gmail.com
Thu Oct 18 10:03:40 EDT 2007


Hello, just thought I'd finally weigh in on this thread, having given
it a little thought.

While there are a few nice examples of instances of Compositor, I
think I'd prefer to have (.) be what is currently fmap. Note that it
generalises ordinary function composition through the functor ((->)
e). Also you get a restricted form of the Arrow case through the
inclusion of an instance of Functor for ((~>) e) when (~>) is an
Arrow.

(Taking (<<<) and (>>>) for Compositor is fine as far as I'm concerned though.)

The one fear I initially had about this was the guarantee of
associativity for function composition, which at first you might think
could fail, but in fact this still holds for any functor, and
beautifully so:

The law for functors:
fmap (f . g) x = fmap f (fmap g x)
becomes:
(f . g) . x = f . (g . x)
where on the LHS, the first (.) is the one from ((->) e), function
composition proper, and on the RHS, both are for the general case.

So associativity still holds in general, and in fact is exactly one of
the two laws Functors are supposed to satisfy!

Incidentally,
fmap id x = x
becomes
id . x = x
Which is another very reasonable thing.

Of course, the examples you gave for Compositor are also Functors, but
that's not quite the same thing as their Compositor instance.

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.

Of course, if we did this, we'd still want to keep around a prefix
form for Functor application, since there are places where that seems
more readable, especially mapping over a datastructure as part of a
composition chain. I'd probably want the prefix form to be called map,
like it was in versions of Haskell prior to '98. List map can be
called lmap or something, if people really want the non-general
version so badly.

 - Cale

On 13/10/2007, Ashley Yakeley <ashley at semantic.org> wrote:
> http://hackage.haskell.org/trac/ghc/ticket/1773
> (darcs patch attached to ticket)
>
> The Compositor class has two members:
>
>   class Compositor comp where
>     identity :: comp a a
>     (>>>) :: comp a b -> comp b c -> comp a c
>
> with the obvious monoid. Since all Arrows are Compositors, make
> Compositor a superclass of Arrow.
>
> A number of useful types are Compositors but not Arrows:
>
> 1. Bijections
>
>    data Bijection a b = MkBijection (a -> b) (b -> a)
>
> 2. Codecs, i.e. encoder/decoder pairs such as charset converters
>
>    data Codec base derived = MkCodec
>    {
>      encode :: derived -> base,
>      decode :: base -> Maybe derived -- or other Monad
>    }
>
>    utf8 :: Codec [Word8] String
>    xml :: Codec String XML
>
> 3. Lenses
> These make updatable sections of data structures.
>
>    data Lens s t = MkLens
>    {
>      lensGet :: s -> t,
>      lensPutback :: t -> s -> s
>    }
>
> See http://www.cis.upenn.edu/~bcpierce/papers/lenses-etapsslides.pdf
>
> 4. Reified proofs of type identity
>    These are useful if you use GADTs and type-witnesses a lot.
>
>    newtype SameType a a' = MkSameType (forall f. f a -> f a')
>
> Proposal period: two weeks, until 10-27
>
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://www.haskell.org/mailman/listinfo/libraries
>


More information about the Libraries mailing list