[Haskell-cafe] arrow notation
Ross Paterson
ross at soi.city.ac.uk
Mon Feb 11 03:30:45 CET 2013
On Mon, Feb 11, 2013 at 12:27:15AM +0100, Ertugrul Söylemez wrote:
> I'm making heavy use of arrow notation, so I'd like to propose a set of
> small improvements, not only syntactical.
>
> ## Ignored input values
>
> Many computations ignore their input value. You can recognize them by
> their type: If the input type is fully polymorphic and the output type
> is unrelated, the computation cannot use its input value. In that case
> it would make sense to just pass whatever is the cheapest thing you
> could pass without requiring me to spell it out:
>
> comp1 :: Arr a Int
> comp2 :: Arr a Double
>
> Before:
>
> proc x1 -> do
> x2 <- comp1 -< x1
> x3 <- comp2 -< x2
> id -< (x2, x3)
>
> After:
>
> proc _ -> do
> x1 <- comp1
> x2 <- comp2
> id -< (x1, x2)
>
> Then the arrow notation compiler could just pass whatever is most
> convenient at that spot. In this case it would just compose with
> '&&&':
>
> comp1 &&& comp2
Inspection of types is not allowed with GHC's constraint-based
type checker, which rules out things like this.
> ## returnA
>
> We don't need it anymore, and it has quite a stupid definition. Get rid
> of it in favor of 'id'.
It would be reasonable to redefine returnA = id
> ## Operators
>
> I often need to mix regular arguments with computation arguments in
> banana notation:
>
> let f c = f' x y c z
> (| f (comp -< v) |)
This wouldn't be legal if f was defined inside the proc. If the arguments
come from outside the proc, you could write (permuting the arguments)
(| (f x y z) (comp -< v) |)
If they're defined inside the proc, you'd have something like
(| f (comp -< v) |) x y z
> ## PreArrow
>
> All sensible arrows form a family of functors:
>
> instance (Arrow a) => Functor (a b) where
> fmap f = (arr f .)
>
> But they do more: Every arrow is a profunctor as defined in the
> 'profunctors' package:
>
> instance (Arrow a) => Profunctor a where
> lmap f = (. arr f)
> rmap = fmap
>
> That's just what you called PreArrow,
Not so: every arrow has lmap and rmap, but not everything that has an
lmap also has an rmap.
> ## Applicative
>
> One of the main bottlenecks of arrows is the heavy tuple handling, but
> most (if not all) arrows form a family of applicative functors. I
> noticed a huge speedup by moving from arrow style to applicative style
> where possible:
>
> liftA2 (+) (lmap f c) (fmap g d)
>
> is often much faster than:
>
> arr (uncurry (+)) . (c . arr f &&& arr g . d)
>
> Besides being more readable it sometimes improved the performance of my
> code by an order of magnitude. So perhaps check to see if the category
> forms an applicative functor. If it does, you can get along without
> Arrow entirely.
>
> In fact I propose to generalize all the Arrow* classes to Category*
> classes.
That sounds reasonable. It's convenient to use simpler classes instead
of Arrow where possible, but it's not always possible.
More information about the Haskell-Cafe
mailing list