Proposal: refactor Arrow class

Edward Kmett ekmett at gmail.com
Tue Jan 8 16:12:21 CET 2013


As it stands this proposal would mean a real performance hit for multiple
performance sensitive packages of mine or two reasons:

1.)

Due to the fact that GHC can't optimize strict function composition

http://hackage.haskell.org/trac/ghc/ticket/7542

and that (Foo . f) expands to (\x -> f x) we use unsafeCoerce in many
places to generate ideal core.

In 3.7, this happened entirely on function arrows and so we could contain
the noise entirely in the lens package.

In order to generate the correct core when faced with the same issue in
profunctors, we were forced to add an {-# LANGUAGE Unsafe #-} module
Data.Profunctor.Unsafe to the profunctors package that let the user invoke
an operator like the `lmap` and `rmap` of a profunctor, but which had
strict semantics and which could be unsafeCoerce. Used correctly this
allows us to maintain SafeHaskell guarantees and still generate the ideal
core.

This eta expansion isn't a trivial issue. From a constant perspective it
means a practical speed difference of 50% in many lens combinators vs. just
dealing with the eta expansion and bad semantics that result from just
using (.) or in the profunctor case, rmap or lmap.

But worse, accumulation of eta expansion wrappers can result in asymptotic
slowdowns. This is witnessed by another ghc bug that we found during work
on lens, where the derived Functor, Foldable and Traversable instances
provided by GHC run in O(n^2) time:

http://hackage.haskell.org/trac/ghc/ticket/7436

And the slowdown can be a factor of 10 even before these asymptotic factors
kick in since to get the correct semantics you need the strict composition
from the first ticket and GHC is terrible at optimizing it.

I'm pretty strongly against losing that much performance.

2.)

Profunctor as it exists provides an efficient dimap that lets you map over
both sides.

This doesn't matter for some 'single arrow' like Profunctors, but it does
matter for the profunctors for Mealy and Moore machines, where now any
dimap requires two passes. That said, I have not measured the slowdown on
my machines package.

Putting in a separate Profunctor class for the union of functionality
between Prearrow and Postarrow (PostFunctor? as it has little to do with
Arrow) is problematic for a couple of reasons.

If we simply make it an alias for Prearrow + Postarrow:

class (Prearrow p, Postarrow p) => Profunctor p

then either

a.) users have to specify an instance for a class with no laws (or which
just contains dimap with a default definition in terms of lmap and rmap),
which is troubling and inconvenient for users.

b.) we have to use appropriately Flexible and Undecidable instance, which
means it probably can't find its way into base and a part of the community
will rebel against it on moral grounds, and we can't get an efficient dimap
in that case regardless.


One compromise would be to drop the Postarrow notion despite 'Profunctor'
being 'too big', and just have:

class Prefunctor p => Profunctor p

with Profunctor p and Category p as superclasses to Arrow.

This loses some of the minimalism of your proposal but can be implemented
in a way that provides for the above concerns.



But if moving Profunctor into the standard library means losing
Data.Profunctor.Unsafe, then I still have an objection.

Losing that module forces me to choose between the a number of bad
scenarios:

a 50% constant factor hit w/ bad semantics around _|_'s and asymptotic
slowdowns
a 10-fold speed hit and good semantics
exposing a user visible unsafeCoerce
requiring some otherwise completely unnecessary class to recover the
existing semantics and dealing with user confusion

I'm not a fan of any of these scenarios.

-Edward Kmett

On Mon, Jan 7, 2013 at 7:05 AM, Ross Paterson <ross at soi.city.ac.uk> wrote:

> On Sun, Jul 15, 2012 at 06:22:01PM +0100, Ross Paterson wrote:
> > I propose to refactor the Arrow class, so that GHC's arrow notation can
> > be a bit more general.  (The module Control.Arrow itself would remain
> > standard Haskell.)
>
> There was resistance to this on two grounds:
> - a Profunctor class would be more principled
> - if we're going to change Arrow, we should make other changes too
>
> I think the second set of changes is orthogonal, and should be
> considered separately.
>
> Regarding the first, it's certainly true that the original proposal was
> unsatisfyingly asymmetrical, but the PreArrow class is what I want to
> generalize most of arrow notation to, and Profunctor would be too much.
> So here's a revised proposal, which amounts to splitting the Profunctor
> class into two independent classes:
>
>   -- | A binary type constructor that is contravariant in its first
> argument
>   class PreArrow a where
>     premap :: (b -> b') -> a b' c -> a b c
>
>   -- | A binary type constructor that is covariant in its second argument
>   class PostArrow a where
>     postmap :: (c -> c') -> a b c -> a b c'
>
> and changing the Arrow class from
>
>   class Category a => Arrow a where
>     arr :: (b -> c) -> a b c
>     first :: a b c -> a (b,d) (c,d)
>     -- various functions made methods to allow efficient specializations
>
> to
>
>   class (Category a, PreArrow a, PostArrow a) => Arrow a where
>     arr :: (b -> c) -> a b c
>     arr f = premap f id
>
>     first :: a b c -> a (b,d) (c,d)
>     -- rest unchanged
>
> with instances
>
>   instance PreArrow (->)
>   instance PostArrow (->)
>   instance Arrow (->)
>   instance PreArrow (Kleisli m)
>   instance Monad m => PostArrow (Kleisli m)
>   instance Monad m => Arrow (Kleisli m)
>
> The default implementation of arr could alternatively be postmap f id,
> but one has to choose one; perfect symmetry is unattainable.
>
> There's also the question of whether it's worth interposing a method-less
> class
>
>    class (PreArrow a, PostArrow a) => Profunctor a
>
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://www.haskell.org/mailman/listinfo/libraries
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/libraries/attachments/20130108/fa73d50f/attachment.htm>


More information about the Libraries mailing list