
I'd like to hear from anyone who's using arrow notation as supported by GHC, because I'm planning a couple of changes to parts of it.

Hi Ross,
I make some use of arrow notation, though sadly I often have to avoid it
because my (pseudo-)"arrows" don't have arr. I'd love to see a variant that
has restricted expressiveness in exchange for arr-freeness.
-- Conal
On Thu, Feb 7, 2013 at 6:08 AM, Ross Paterson
I'd like to hear from anyone who's using arrow notation as supported by GHC, because I'm planning a couple of changes to parts of it.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Thu, Feb 07, 2013 at 02:49:40PM -0800, Conal Elliott wrote:
Hi Ross,
I make some use of arrow notation, though sadly I often have to avoid it because my (pseudo-)"arrows" don't have arr. I'd love to see a variant that has restricted expressiveness in exchange for arr-freeness.
Are you familiar with Adam Megacz's "Generalized Arrows" work? http://www.cs.berkeley.edu/~megacz/garrows/ (I, too, would love to see Arrows-without-arr in Haskell)
-- Conal
--
-Julian Blake Kongslie

On Thu, Feb 07, 2013 at 02:49:40PM -0800, Conal Elliott wrote:
I make some use of arrow notation, though sadly I often have to avoid it because my (pseudo-)"arrows" don't have arr. I'd love to see a variant that has restricted expressiveness in exchange for arr-freeness.
It's hard to imagine arrow notation without arr (or at least contravariance in the first argument of the "arrow") because forming expressions using the local environment is so central to it. That is, I can't imagine what things you are trying to write in that situation.

On Thu, Feb 7, 2013 at 5:41 PM, Ross Paterson
On Thu, Feb 07, 2013 at 02:49:40PM -0800, Conal Elliott wrote:
I make some use of arrow notation, though sadly I often have to avoid it because my (pseudo-)"arrows" don't have arr. I'd love to see a variant that has restricted expressiveness in exchange for arr-freeness.
It's hard to imagine arrow notation without arr (or at least contravariance in the first argument of the "arrow") because forming expressions using the local environment is so central to it. That is, I can't imagine what things you are trying to write in that situation.
What I have in mind is a small collection of methods including fst & snd (and similarly for sums) that could be defined via arr but could instead form the basis of translating restricted arrow notation for (pseudo-)arrows that don't support arr. I keep running into these pseudo-arrows in practical work. The reliance of arrow notation on arr means that I can't use arrow notation, and my code is terribly difficult to read. -- Conal

2013/2/9 Conal Elliott
On Thu, Feb 7, 2013 at 5:41 PM, Ross Paterson
wrote: It's hard to imagine arrow notation without arr (or at least contravariance in the first argument of the "arrow") because forming expressions using the local environment is so central to it. That is, I can't imagine what things you are trying to write in that situation.
What I have in mind is a small collection of methods including fst & snd (and similarly for sums) that could be defined via arr but could instead form the basis of translating restricted arrow notation for (pseudo-)arrows that don't support arr.
I also support this idea, I'd appreciate such a generalization. As an example, where it would be useful: One of my students was working on a (very nice) project where he used Haskell as a DSL for generating a FRP-like javascript code. The arrow notation without "arr" would be ideal for this situation. He couldn't implement "arr" as it would require to translate an arbitrary Haskell function to JS. So having a more general variant of "Arrow" without "arr" and with a collection of methods sufficient for the arrow notation would be quite helpful. (I wonder what methods would have to be included in the collection.) Best regards, Petr Pudlak

On Sun, Feb 10, 2013 at 09:28:12PM +0100, Petr Pudlák wrote:
2013/2/9 Conal Elliott
wrote: What I have in mind is a small collection of methods including fst & snd (and similarly for sums) that could be defined via arr but could instead form the basis of translating restricted arrow notation for (pseudo-)arrows that don't support arr.
I also support this idea, I'd appreciate such a generalization.
As an example, where it would be useful: One of my students was working on a (very nice) project where he used Haskell as a DSL for generating a FRP-like javascript code. The arrow notation without "arr" would be ideal for this situation. He couldn't implement "arr" as it would require to translate an arbitrary Haskell function to JS. So having a more general variant of "Arrow" without "arr" and with a collection of methods sufficient for the arrow notation would be quite helpful. (I wonder what methods would have to be included in the collection.)
Let's try to break this down. Suppose we split arr :: forall b c. (b -> c) -> a b c into two primitives (^>>) :: forall b c d. (b -> c) -> a c d -> a b d id :: forall b. a b b The contravariant functor (^>>) is essential to arrow notation, but I suspect the issue is the universally quantified b in the type of id (or equivalently returnA). One might instead use a variant of id constrained to an ADT with just the operations you want.

The proposed changes are described here: http://hackage.haskell.org/trac/ghc/wiki/ArrowNotation

Ross Paterson
I'd like to hear from anyone who's using arrow notation as supported by GHC, because I'm planning a couple of changes to parts of it.
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 ## returnA We don't need it anymore, and it has quite a stupid definition. Get rid of it in favor of '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) |) Since parentheses are required for computation arguments you could relax the syntax to allow regular arguments in simple cases as well: (| f' x y (comp -< v) 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, so there is no need to reinvent the wheel. Get Profunctor into base. ## 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. The ultimate goal is to get rid of arrows. We don't really need them anymore. I'd rather like to see SHE's idiom brackets in Haskell and use a more lightweight syntax for stuff like ArrowChoice and ArrowLoop (or CategoryChoice and CategoryLoop), although I don't yet know what it would look like. Greets, Ertugrul -- Not to be or to be and (not to be or to be and (not to be or to be and (not to be or to be and ... that is the list monad.

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.

Ross Paterson
Many computations ignore their input value. You can recognize them by their type: [...]
Inspection of types is not allowed with GHC's constraint-based type checker, which rules out things like this.
Too bad. Would it be possible to get rid of "-< ()"?
## 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
Yes, that would be a good start. For many applications using 'id' instead of 'arr id' gives a huge performance boost. In my particular case (I'm doing wire-based FRP (WFRP)) I often start with a complex "sum" network of categorical computations: c1 . c2 <|> c3 . c4 . (c5 <|> c6) <|> c7 The distinguishing feature of WFRP, what makes it so fast, is that you can get rid of complexity by recognizing 'id' and 'empty' when they pop up. The component computations can "morph" into them over time, for example for 3 is identity-like for three seconds and then switches to 'empty'. You can recognize and discard entire subnetworks quickly.
## 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
Of course, and that's the inconvenient part. You have to write wrapper functions. It would be nice, if the bananas would consider unparenthesized expressions as regular arguments.
## 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.
I see. You want to get rid of 'arr' altogether. On one hand that is desirable. On the other hand for arrows lmap and rmap are equivalent. You can define 'arr' given 'lmap': arr f = lmap f id From that you can define fmap. This leads to the conclusion that as soon as the arrow notation does more than simple composition you need a functor anyway.
## 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.
The idea is this: If there are both Arrow and Applicative instances (can you check this?), the arrow notation could use applicative combinators instead of arrowic ones where possible: proc x' -> do f <- comp1 -< x' x <- comp2 -< x' comp3 -< f x If this is possible, arrow notation would likely rewrite it to comp3 . ((\f x -> f x) <$> comp1 <*> comp2) and, as a nice bonus, recognize that \f x -> f x is really just id and optimize the fmap away: comp3 . (comp1 <*> comp2) The pattern is: A computation composed of subcomputations where each of them takes the same arrow variable as input. The corresponding arrow version is unnecessarily expensive because of the tuple wrapping and unwrapping, comp3 . arr (\(f, x) -> f x) . comp1 &&& comp2 whereas the applicative version is really straightforward and fast. Greets, Ertugrul -- Not to be or to be and (not to be or to be and (not to be or to be and (not to be or to be and ... that is the list monad.

On Mon, Feb 11, 2013 at 11:30 AM, Ertugrul Söylemez
The idea is this: If there are both Arrow and Applicative instances (can you check this?), the arrow notation could use applicative combinators instead of arrowic ones where possible:
I wonder if maybe this could be done with rewrite rules rather than on the syntax level?

2013/2/11 Ertugrul Söylemez
...
## 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.
I've been reading *Idioms are oblivious, arrows are meticulous, monads are promiscuous* recently, and if I understand it correctly, an arrow forms an applicative functor if it's possible to define a delaying operation on it, which separates the arrow's effect from its computation: class Arrow a => ArrowDelay a where delay :: a b c -> a () (b -> c) -- Definable for any arrow: force :: Arrow a => a () (b -> c) -> a b c force af = (,) () ^>> first af >>^ uncurry ($) and satisfying `force . delay = id = delay . force`. While the implementation of Applicative can be defined without actually using `delay`: newtype ArrowApp a b c = ArrowApp (a b c) instance Arrow a => Functor (ArrowApp a b) where fmap f (ArrowApp a) = ArrowApp (a >>^ f) instance ArrowDelay a => Applicative (ArrowApp a b) where pure x = ArrowApp $ arr (const x) (ArrowApp af) <*> (ArrowApp ax) = ArrowApp $ (af &&& ax) >>^ uncurry ($) I believe it only satisfies the laws only if the arrow satisfies delay/force laws. Perhaps it would be convenient to have ArrowDelay and the corresponding conversions included in the library so that defining and using Applicative instances for arrows would become more straightforward. Best regards, Petr Pudlak

Petr Pudlák
class Arrow a => ArrowDelay a where delay :: a b c -> a () (b -> c)
force :: Arrow a => a () (b -> c) -> a b c
Perhaps it would be convenient to have ArrowDelay and the corresponding conversions included in the library so that defining and using Applicative instances for arrows would become more straightforward.
I appreciate the idea from a theoretical standpoint, but you don't
actually have to define an ArrowDelay instance for the notation to work.
The compiler can't check the laws anyway.
Greets,
Ertugrul
--
Key-ID: E5DD8D11 "Ertugrul Soeylemez

2013/2/11 Ertugrul Söylemez
Petr Pudlák
wrote: class Arrow a => ArrowDelay a where delay :: a b c -> a () (b -> c)
force :: Arrow a => a () (b -> c) -> a b c
Perhaps it would be convenient to have ArrowDelay and the corresponding conversions included in the library so that defining and using Applicative instances for arrows would become more straightforward.
I appreciate the idea from a theoretical standpoint, but you don't actually have to define an ArrowDelay instance for the notation to work. The compiler can't check the laws anyway.
That's true. But I'm afraid that without the ArrowDelay constraint people would think that every arrow forms an applicative functor and eventually get into hard-to-trace problems with failing the applicative laws. The compiler can't check the laws, so somebody else has to. Should it be users of an arrow or its authors? Without the constraint, the burden would be on the users: "Before using the applicative instance, check if the arrow is really an applicative functor". That's something users of a library aren't supposed to do." With the constraint, the burden would be on the authors of the arrow - they'd have to define the instance and be responsible for satisfying the laws. I feel this is more appropriate. Best regards, Petr Pudlak

On Mon, Feb 11, 2013 at 09:32:25AM +0100, Petr Pudlák wrote:
While the implementation of Applicative can be defined without actually using `delay`:
newtype ArrowApp a b c = ArrowApp (a b c)
instance Arrow a => Functor (ArrowApp a b) where fmap f (ArrowApp a) = ArrowApp (a >>^ f) instance ArrowDelay a => Applicative (ArrowApp a b) where pure x = ArrowApp $ arr (const x) (ArrowApp af) <*> (ArrowApp ax) = ArrowApp $ (af &&& ax) >>^ uncurry ($)
I believe it only satisfies the laws only if the arrow satisfies delay/force laws.
This is a reader, which always satisfies the applicative laws. What ArrowDelay does is pick out the arrows that are equivalent to the static arrow, i.e. F(b->c), of some applicative functor F.
participants (6)
-
Conal Elliott
-
dag.odenhall@gmail.com
-
Ertugrul Söylemez
-
Julian Blake Kongslie
-
Petr Pudlák
-
Ross Paterson