Applicative banana brackets

Hi, while learning about all the type classes and their relationships I came across something I found weird. If I understand it correctly, banana brackets where originally developed for Applicatives. The intent was to enable us to write something like (| (\a b c -> a + b + c), [3], [1,2], [5,0,7] |) and have it translated to liftA3 (\a b c -> a + b + c) [3] [1,2] [5,0,7] or alternatively, to allow us to write something like (| (pure $ \a b c -> a + b + c), [3], [1,2], [5,0,7] |) and have it translated directly to pure (\a b c -> a + b + c) <*> [3] <*> [1,2] <*> [5,0,7] A variant of banana brackets is implemented in ghc, but only for Arrows as part of -XArrowSyntax. Arrows are just the intersection of Applicative and Category, so this implementation seems to be a specialization. What's worse, I don't think -XRebindableSyntax extends to banana brackets. But why? Is it hard to have the notation work with both? (After all, the relationship between Arrows and Applicatives is not easily expressed in Haskell.) Was the demand for (Applicative) bananas not big enough? Is it just a relic? And more to the point: I have not looked at the ghc code base at all yet, but it's on my bucket list to hack on it one day. Right now, a generalization of banana brackets seems like a simple enough low pressure first project, but I fear that it might break code or that there is some pitfall I'm not seeing. Can anybody shed a bit of light on this? Thanks and cheers, Martin L. P.S.: If the list receives this mail several times, I apologize. The list management tool seems to be confused by gmail vs. googlemail. That's what you get for using non-Haskell software. ;)

I don't know how the arrow syntax works, but you can get banana brackets
for applicatives with a preprocessor—the Strathclyde Haskell Enhancement
(SHE)[1]. You can install it from cabal and enable it with {-# OPTIONS _GHC
-F -pgmF she #-} after which it just works (including, if I recall
correctly, ghci).
Personally, playing around with it convinced me that banana brackets aren't
quite as nice in practice as they look. They still make *certain*
expressions nicer (especially simple ones involving operators), but either
don't make a difference or actually make the code *less* readable in more
complicated cases. Of course, those more complicated cases end up being the
most common, so in a small project I only found something like two
applicative expressions where it helped (out of at least 20).
A particular problem I had is that, by necessity, $ works differently
inside banana brackets than normally. This is the only thing that makes
sense, of course, but it doesn't jell well with how I intuitively use $ as
more or less syntax for limiting nested parentheses.
I don't want to discourage you too much. They might work better for you
than they did for me. But you should definitely play around with them,
preferably on a real project, before you sink any time in trying to
implement them in GHC. You might like them but don't be surprised if you
don't.
Also, they'd be somewhat redundant with ApplicativeDo. The syntax is
different enough that both can be useful, but it's something to keep in
mind. At the very least, the ApplicativeDo extension is a good place to
start looking to understand how to desugar to applicative operators in GHC.
On Tue, Dec 8, 2015 at 9:09 PM, martin
Hi,
while learning about all the type classes and their relationships I came across something I found weird. If I understand it correctly, banana brackets where originally developed for Applicatives. The intent was to enable us to write something like
(| (\a b c -> a + b + c), [3], [1,2], [5,0,7] |)
and have it translated to
liftA3 (\a b c -> a + b + c) [3] [1,2] [5,0,7]
or alternatively, to allow us to write something like
(| (pure $ \a b c -> a + b + c), [3], [1,2], [5,0,7] |)
and have it translated directly to
pure (\a b c -> a + b + c) <*> [3] <*> [1,2] <*> [5,0,7]
A variant of banana brackets is implemented in ghc, but only for Arrows as part of -XArrowSyntax. Arrows are just the intersection of Applicative and Category, so this implementation seems to be a specialization. What's worse, I don't think -XRebindableSyntax extends to banana brackets. But why? Is it hard to have the notation work with both? (After all, the relationship between Arrows and Applicatives is not easily expressed in Haskell.) Was the demand for (Applicative) bananas not big enough? Is it just a relic? And more to the point: I have not looked at the ghc code base at all yet, but it's on my bucket list to hack on it one day. Right now, a generalization of banana brackets seems like a simple enough low pressure first project, but I fear that it might break code or that there is some pitfall I'm not seeing.
Can anybody shed a bit of light on this?
Thanks and cheers, Martin L.
P.S.: If the list receives this mail several times, I apologize. The list management tool seems to be confused by gmail vs. googlemail. That's what you get for using non-Haskell software. ;) _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

I don't know how the arrow syntax works, but you can get banana brackets for applicatives with a preprocessor—the Strathclyde Haskell Enhancement (SHE)[1]. [...] I hadn't looked into preprocessors yet, but that sounds like a great idea. Thanks! Personally, playing around with it convinced me that banana brackets aren't quite as nice in practice as they look. [...] Of course, those more complicated cases end up being the most common. [...] I only played around with arrow brackets yet, but that sounds familiar. They can make your code really beautiful - but only rarely. I'm currently trying to convert some of my overcomplicated arrow structures to simpler applicative ones, which is one of my motivations here. But if it's of so little use, and with liftAn's already there... A particular problem I had is that, by necessity, $ works differently inside banana brackets than normally. [...] That sounds like it might not have been a problem for me yet because the natural composition of arrows is through (>>>) anyway. Interesting. I don't want to discourage you too much. Don't worry. There are always things to play around with and projects to try. It was just that I thought I might have found something far simpler that what I usually come up with, and thus something I could actually finish and share some day. ;) Also, they'd be somewhat redundant with ApplicativeDo. Yet another thing I hadn't thought of. I'm not a huge fan of do-notation and arrow-notation myself. They are useful, but can be overly verbose and distracting. So maybe I'll get more use out of brackets? Only one way to find out...
Anyway, thanks for all the great information. These are definitely things I'll consider!
Hi,
while learning about all the type classes and their relationships I came across something I found weird. If I understand it correctly, banana brackets where originally developed for Applicatives. The intent was to enable us to write something like
(| (\a b c -> a + b + c), [3], [1,2], [5,0,7] |)
and have it translated to
liftA3 (\a b c -> a + b + c) [3] [1,2] [5,0,7]
or alternatively, to allow us to write something like
(| (pure $ \a b c -> a + b + c), [3], [1,2], [5,0,7] |)
and have it translated directly to
pure (\a b c -> a + b + c) <*> [3] <*> [1,2] <*> [5,0,7]
A variant of banana brackets is implemented in ghc, but only for Arrows as part of -XArrowSyntax. Arrows are just the intersection of Applicative and Category, so this implementation seems to be a specialization. What's worse, I don't think -XRebindableSyntax extends to banana brackets. But why? Is it hard to have the notation work with both? (After all, the relationship between Arrows and Applicatives is not easily expressed in Haskell.) Was the demand for (Applicative) bananas not big enough? Is it just a relic? And more to the point: I have not looked at the ghc code base at all yet, but it's on my bucket list to hack on it one day. Right now, a generalization of banana brackets seems like a simple enough low pressure first project, but I fear that it might break code or that there is some pitfall I'm not seeing.
Can anybody shed a bit of light on this?
Thanks and cheers, Martin L.
P.S.: If the list receives this mail several times, I apologize. The list management tool seems to be confused by gmail vs. googlemail. That's what you get for using non-Haskell software. ;) _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

In the Idioms module of uu-parsinglib: https://hackage.haskell.org/package/uu-parsinglib-2.9.1/docs/Text-ParserComb... I show how you can achieve what you want without any preprocessors. The idea is to overload based on the type of the operand: {-# LANGUAGE RankNTypes, MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, UndecidableInstances, FlexibleContexts, CPP #-} module Idiomatic where -- | The `Ii` is to be pronounced as @stop@ data Ii = Ii -- | The function `iI` is to be pronounced as @start@ iI ::Idiomatic (a -> a) g => g iI = idiomatic (pure id) class Idiomatic f g | g -> f where idiomatic :: [f] -> g instance Idiomatic x (Ii -> [x]) where idiomatic ix Ii = ix instance Idiomatic f g => Idiomatic (a -> f) ([a] -> g) where idiomatic isf is = idiomatic (isf <*> is) instance Idiomatic f g => Idiomatic ((a -> b) -> f) ((a -> b) -> g) where idiomatic isf f = idiomatic (isf <*> (pure f)) t :: [Int] t = iI (\ a b c -> a + b +c) [3] [1,2] [5,0,7] Ii So you get: *Idiomatic> show t "[9,4,11,10,5,12]" *Idiomatic>
On 14 Dec 2015, at 14:53 , martin
wrote: I don't know how the arrow syntax works, but you can get banana brackets for applicatives with a preprocessor—the Strathclyde Haskell Enhancement (SHE)[1]. [...] I hadn't looked into preprocessors yet, but that sounds like a great idea. Thanks! Personally, playing around with it convinced me that banana brackets aren't quite as nice in practice as they look. [...] Of course, those more complicated cases end up being the most common. [...] I only played around with arrow brackets yet, but that sounds familiar. They can make your code really beautiful - but only rarely. I'm currently trying to convert some of my overcomplicated arrow structures to simpler applicative ones, which is one of my motivations here. But if it's of so little use, and with liftAn's already there... A particular problem I had is that, by necessity, $ works differently inside banana brackets than normally. [...] That sounds like it might not have been a problem for me yet because the natural composition of arrows is through (>>>) anyway. Interesting. I don't want to discourage you too much. Don't worry. There are always things to play around with and projects to try. It was just that I thought I might have found something far simpler that what I usually come up with, and thus something I could actually finish and share some day. ;) Also, they'd be somewhat redundant with ApplicativeDo. Yet another thing I hadn't thought of. I'm not a huge fan of do-notation and arrow-notation myself. They are useful, but can be overly verbose and distracting. So maybe I'll get more use out of brackets? Only one way to find out...
Anyway, thanks for all the great information. These are definitely things I'll consider!
Hi,
while learning about all the type classes and their relationships I came across something I found weird. If I understand it correctly, banana brackets where originally developed for Applicatives. The intent was to enable us to write something like
(| (\a b c -> a + b + c), [3], [1,2], [5,0,7] |)
and have it translated to
liftA3 (\a b c -> a + b + c) [3] [1,2] [5,0,7]
or alternatively, to allow us to write something like
(| (pure $ \a b c -> a + b + c), [3], [1,2], [5,0,7] |)
and have it translated directly to
pure (\a b c -> a + b + c) <*> [3] <*> [1,2] <*> [5,0,7]
A variant of banana brackets is implemented in ghc, but only for Arrows as part of -XArrowSyntax. Arrows are just the intersection of Applicative and Category, so this implementation seems to be a specialization. What's worse, I don't think -XRebindableSyntax extends to banana brackets. But why? Is it hard to have the notation work with both? (After all, the relationship between Arrows and Applicatives is not easily expressed in Haskell.) Was the demand for (Applicative) bananas not big enough? Is it just a relic? And more to the point: I have not looked at the ghc code base at all yet, but it's on my bucket list to hack on it one day. Right now, a generalization of banana brackets seems like a simple enough low pressure first project, but I fear that it might break code or that there is some pitfall I'm not seeing.
Can anybody shed a bit of light on this?
Thanks and cheers, Martin L.
P.S.: If the list receives this mail several times, I apologize. The list management tool seems to be confused by gmail vs. googlemail. That's what you get for using non-Haskell software. ;) _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

That's... just brilliant! I think I'll sneak back to the beginners' play room now... On 2015-12-14 15:16, S. Doaitse Swierstra wrote:
In the Idioms module of uu-parsinglib:
https://hackage.haskell.org/package/uu-parsinglib-2.9.1/docs/Text-ParserComb...
I show how you can achieve what you want without any preprocessors. The idea is to overload based on the type of the operand:
{-# LANGUAGE RankNTypes, MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, UndecidableInstances, FlexibleContexts, CPP #-}
module Idiomatic where
-- | The `Ii` is to be pronounced as @stop@ data Ii = Ii
-- | The function `iI` is to be pronounced as @start@ iI ::Idiomatic (a -> a) g => g iI = idiomatic (pure id)
class Idiomatic f g | g -> f where idiomatic :: [f] -> g
instance Idiomatic x (Ii -> [x]) where idiomatic ix Ii = ix
instance Idiomatic f g => Idiomatic (a -> f) ([a] -> g) where idiomatic isf is = idiomatic (isf <*> is)
instance Idiomatic f g => Idiomatic ((a -> b) -> f) ((a -> b) -> g) where idiomatic isf f = idiomatic (isf <*> (pure f))
t :: [Int] t = iI (\ a b c -> a + b +c) [3] [1,2] [5,0,7] Ii
So you get:
*Idiomatic> show t "[9,4,11,10,5,12]" *Idiomatic>
On 14 Dec 2015, at 14:53 , martin
wrote: I don't know how the arrow syntax works, but you can get banana brackets for applicatives with a preprocessor—the Strathclyde Haskell Enhancement (SHE)[1]. [...] I hadn't looked into preprocessors yet, but that sounds like a great idea. Thanks! Personally, playing around with it convinced me that banana brackets aren't quite as nice in practice as they look. [...] Of course, those more complicated cases end up being the most common. [...] I only played around with arrow brackets yet, but that sounds familiar. They can make your code really beautiful - but only rarely. I'm currently trying to convert some of my overcomplicated arrow structures to simpler applicative ones, which is one of my motivations here. But if it's of so little use, and with liftAn's already there... A particular problem I had is that, by necessity, $ works differently inside banana brackets than normally. [...] That sounds like it might not have been a problem for me yet because the natural composition of arrows is through (>>>) anyway. Interesting. I don't want to discourage you too much. Don't worry. There are always things to play around with and projects to try. It was just that I thought I might have found something far simpler that what I usually come up with, and thus something I could actually finish and share some day. ;) Also, they'd be somewhat redundant with ApplicativeDo. Yet another thing I hadn't thought of. I'm not a huge fan of do-notation and arrow-notation myself. They are useful, but can be overly verbose and distracting. So maybe I'll get more use out of brackets? Only one way to find out...
Anyway, thanks for all the great information. These are definitely things I'll consider!
Hi,
while learning about all the type classes and their relationships I came across something I found weird. If I understand it correctly, banana brackets where originally developed for Applicatives. The intent was to enable us to write something like
(| (\a b c -> a + b + c), [3], [1,2], [5,0,7] |)
and have it translated to
liftA3 (\a b c -> a + b + c) [3] [1,2] [5,0,7]
or alternatively, to allow us to write something like
(| (pure $ \a b c -> a + b + c), [3], [1,2], [5,0,7] |)
and have it translated directly to
pure (\a b c -> a + b + c) <*> [3] <*> [1,2] <*> [5,0,7]
A variant of banana brackets is implemented in ghc, but only for Arrows as part of -XArrowSyntax. Arrows are just the intersection of Applicative and Category, so this implementation seems to be a specialization. What's worse, I don't think -XRebindableSyntax extends to banana brackets. But why? Is it hard to have the notation work with both? (After all, the relationship between Arrows and Applicatives is not easily expressed in Haskell.) Was the demand for (Applicative) bananas not big enough? Is it just a relic? And more to the point: I have not looked at the ghc code base at all yet, but it's on my bucket list to hack on it one day. Right now, a generalization of banana brackets seems like a simple enough low pressure first project, but I fear that it might break code or that there is some pitfall I'm not seeing.
Can anybody shed a bit of light on this?
Thanks and cheers, Martin L.
P.S.: If the list receives this mail several times, I apologize. The list management tool seems to be confused by gmail vs. googlemail. That's what you get for using non-Haskell software. ;) _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

On Wed, Dec 09, 2015 at 06:09:21AM +0100, martin wrote:
while learning about all the type classes and their relationships I came across something I found weird. If I understand it correctly, banana brackets where originally developed for Applicatives. The intent was to enable us to write something like
(| (\a b c -> a + b + c), [3], [1,2], [5,0,7] |)
and have it translated to
liftA3 (\a b c -> a + b + c) [3] [1,2] [5,0,7]
or alternatively, to allow us to write something like
(| (pure $ \a b c -> a + b + c), [3], [1,2], [5,0,7] |)
and have it translated directly to
pure (\a b c -> a + b + c) <*> [3] <*> [1,2] <*> [5,0,7]
A variant of banana brackets is implemented in ghc, but only for Arrows as part of -XArrowSyntax.
I don't think Arrow banana brackets are related to these Applicative (or "Idiom") brackets. Tom

On 2015-12-09 22:20, Tom Ellis wrote:
while learning about all the type classes and their relationships I came across something I found weird. If I understand it correctly, banana brackets where originally developed for Applicatives. The intent was to enable us to write something like I don't think Arrow banana brackets are related to these Applicative (or "Idiom") brackets.
Let me try to convince you. ;) Actually I have no idea if there is a historical relationship, but there is definitely a semantic one. Consider this: 1) An alternative definition of Applicative is as a monoidal, with the operation comma :: f a -> f b -> f (a,b) "comma" is connected with (<*>) through the Functor superclass. It's typically named (**), but I'll use a prefix version. 2) Every arrow a b c is an applicative (a b) c, because comma = (&&&). Conversely, every applicative that is polymorphic over some "internal" variable is automatically an arrow, through (&&&) = comma. 3) Let's rename (&&&) to "andA". It's trivial to think of "comma" and "andA" as the special versions "comma2" and "andA2" of more general forms commaN and andAn for all natural numbers n. The equivalence of both functions extends naturally for all n. (N.B.: comma0/andA0 and comma1/andA1 are very interesting functions and one of the reasons I left out all the stuff from Pointed/CoPointed/Unit. The other reason is simplification.) 4) An idiom bracket (| f x1 x2 ... xn |) translates very roughly to liftA (uncurryN f) (commaN x1 x2 ... xn) while a banana bracket (| f x1 x2 ... xn |) translates very roughly to liftA' (uncurryN f) (andAn x1 x2 ... xn) And as commaN and andAn are equivalent, the relation should be obvious now. Of course that's a very very rough sketch without any proofs, without looking at the wrappers, and with slightly modified semantics in the first argument. Still, I'm convinced both are (almost) the same. But then I might be overlooking something important...

On Mon, Dec 14, 2015 at 9:38 PM, martin
Conversely, every applicative that is polymorphic over some "internal" variable is automatically an arrow, through (&&&) = comma.
Where is the proof that (a b) is a Functor? Recall that the class method arr -- the closest kin to fmap -- has the type: (b -> c) -> a b c. -- Kim-Ee

Every Arrow is a Functor through:
fmapA :: Arrow arr => (a -> b) -> arr i a -> arr i b
fmapA f a = arr f . a
Right?
Erik
On 14 December 2015 at 15:53, Kim-Ee Yeoh
On Mon, Dec 14, 2015 at 9:38 PM, martin
wrote: 2) Every arrow a b c is an applicative (a b) c, because comma = (&&&). Conversely, every applicative that is polymorphic over some "internal" variable is automatically an arrow, through (&&&) = comma.
Where is the proof that (a b) is a Functor?
Recall that the class method arr -- the closest kin to fmap -- has the type:
(b -> c) -> a b c.
-- Kim-Ee
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

On Mon, Dec 14, 2015 at 10:10 PM, Erik Hesselink
fmapA :: Arrow arr => (a -> b) -> arr i a -> arr i b fmapA f a = arr f . a
Right?
That's one of the missing holes in Martin's claim. In cases like this, it would help to avoid any risk that the usual abuse of language brings. So an arrow is not a functor but it does give rise to one. More precisely, there would be an instance Arrow a => Functor (a b). -- Kim-Ee

Yes, I know, my sketch is like a swiss cheese. Also, I apologize for my abuse of language. My excuse is that my training did not involve the precise terms used in English proofs. (It's not my first language, after all.) Indeed it did not even expand to proofs in this area at all. The only language I know how to express proofs in unambiguously is Haskell itself - but I haven't found a way to express the relationships here. Most importantly: instance (forall b.Applicative (a b)) => Arrow a where ... That's not idiomatic, and I haven't found any idiomatic way to express that relationship yet. As a result (and to keep the sketch short), my goal was more on the level of transporting intuition. So, to quell your hunger for proofs, here's a proof that fmapA is indeed a suitable definition for fmap: # Definition fmapA f = \a -> a >>> arr f -- equivalent through currying and the definition of (>>>) # fmap id == id fmapA id = \a -> a >>> arr id -- definition of fmapA = \a -> a >>> id -- Arrow law = \a -> id . a -- definition of (>>>) = \a -> a -- definition of id = id -- definition of id # fmap (f . g) == (fmap f) . (fmap g) fmapA (f . g) = \a -> a >>> arr (f . g) -- definition of fmapA = \a -> a >>> arr (g >>> f) -- definition of (>>>) = \a -> a >>> (arr g >>> arr f) -- Arrow law = \a -> (a >>> arr g) >>> arr f -- Category law = \a -> (fmapA g a) >>> arr f -- definition of fmapA = \a -> fmapA f (fmapA g a) -- definition of fmapA = \a -> (fmapA f) . (fmapA g) a -- definition of (.) = (fmapA f) . (fmapA g) -- currying And here's the blog post that initially convinced me of the relationship between Arrows and Applicatives: http://just-bottom.blogspot.de/2010/04/programming-with-effects-story-so-far... The alternative definition of Applicative as Monoidal can be found in the Typeclassopedia: https://wiki.haskell.org/Typeclassopedia#Alternative_formulation There are still holes to be filled, but these are more or less all the pieces of the puzzle I have so far. On 2015-12-14 16:41, Kim-Ee Yeoh wrote:
On Mon, Dec 14, 2015 at 10:10 PM, Erik Hesselink
wrote: Every Arrow is a Functor through:
fmapA :: Arrow arr => (a -> b) -> arr i a -> arr i b fmapA f a = arr f . a
Right?
That's one of the missing holes in Martin's claim.
In cases like this, it would help to avoid any risk that the usual abuse of language brings. So an arrow is not a functor but it does give rise to one. More precisely, there would be an instance Arrow a => Functor (a b).
-- Kim-Ee

On Mon, Dec 14, 2015 at 11:18 PM, martin
My excuse is that my training did not involve the precise terms used in English proofs. (It's not my first language, after all.)
A smart man once wrote that Fate has imposed upon my writing the yoke of a foreign tongue that was not sung at my cradle. That makes two of us. (See what I wrote about "missing holes"? There was a hole. Erik filled it. No-one misses it.) Indeed it did not even expand to proofs in this area at all. The
only language I know how to express proofs in unambiguously is Haskell itself - but I haven't found a way to express the relationships here. Most importantly:
instance (forall b.Applicative (a b)) => Arrow a where ...
You're referring to http://just-bottom.blogspot.de/2010/04/programming-with-effects-story-so-far... ? Superclassing Applicative over Arrow appears off.
That's not idiomatic, and I haven't found any idiomatic way to express that relationship yet. As a result (and to keep the sketch short), my goal was more on the level of transporting intuition.
So, to quell your hunger for proofs, here's a proof that fmapA is indeed a suitable definition for fmap:
Or we could just cite "instance Arrow a => Applicative (WrappedArrow a b)" in https://hackage.haskell.org/package/base-4.8.1.0/docs/Control-Applicative.ht... Make no mistake: The goal here isn't pedantry. We retrace the steps (1) to (4) with a fine-toothed comb to understand the claimed equivalence of brackets. -- Kim-Ee
# Definition fmapA f = \a -> a >>> arr f -- equivalent through currying and the definition of (>>>)
# fmap id == id fmapA id = \a -> a >>> arr id -- definition of fmapA = \a -> a >>> id -- Arrow law = \a -> id . a -- definition of (>>>) = \a -> a -- definition of id = id -- definition of id
# fmap (f . g) == (fmap f) . (fmap g) fmapA (f . g) = \a -> a >>> arr (f . g) -- definition of fmapA = \a -> a >>> arr (g >>> f) -- definition of (>>>) = \a -> a >>> (arr g >>> arr f) -- Arrow law = \a -> (a >>> arr g) >>> arr f -- Category law = \a -> (fmapA g a) >>> arr f -- definition of fmapA = \a -> fmapA f (fmapA g a) -- definition of fmapA = \a -> (fmapA f) . (fmapA g) a -- definition of (.) = (fmapA f) . (fmapA g) -- currying
And here's the blog post that initially convinced me of the relationship between Arrows and Applicatives:
http://just-bottom.blogspot.de/2010/04/programming-with-effects-story-so-far...
The alternative definition of Applicative as Monoidal can be found in the Typeclassopedia: https://wiki.haskell.org/Typeclassopedia#Alternative_formulation
There are still holes to be filled, but these are more or less all the pieces of the puzzle I have so far.
On 2015-12-14 16:41, Kim-Ee Yeoh wrote:
On Mon, Dec 14, 2015 at 10:10 PM, Erik Hesselink
wrote: Every Arrow is a Functor through:
fmapA :: Arrow arr => (a -> b) -> arr i a -> arr i b fmapA f a = arr f . a
Right?
That's one of the missing holes in Martin's claim.
In cases like this, it would help to avoid any risk that the usual abuse of language brings. So an arrow is not a functor but it does give rise to one. More precisely, there would be an instance Arrow a => Functor (a b).
-- Kim-Ee
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

On 2015-12-15 00:23 +0700, Kim-Ee Yeoh wrote:
A smart man once wrote that Fate has imposed upon my writing the yoke of a foreign tongue that was not sung at my cradle.
<click/> Hermann Weyl? https://en.wikipedia.org/wiki/Hermann_Weyl -- Please *no* private copies of mailing list or newsgroup messages. Rule 420: All persons more than eight miles high to leave the court.

On Mon, Dec 14, 2015 at 03:38:34PM +0100, martin wrote:
On 2015-12-09 22:20, Tom Ellis wrote:
while learning about all the type classes and their relationships I came across something I found weird. If I understand it correctly, banana brackets where originally developed for Applicatives. The intent was to enable us to write something like
I don't think Arrow banana brackets are related to these Applicative (or "Idiom") brackets.
Let me try to convince you. ;)
OK :)
Actually I have no idea if there is a historical relationship, but there is definitely a semantic one. Consider this:
1) - 3), all agreed.
4) An idiom bracket (| f x1 x2 ... xn |) translates very roughly to liftA (uncurryN f) (commaN x1 x2 ... xn) while a banana bracket (| f x1 x2 ... xn |) translates very roughly to liftA' (uncurryN f) (andAn x1 x2 ... xn)
But in an Applicative or Idiom bracket expression of the form (| f x1 ... xn |), f is a pure function. In the Applicative banana bracket, the expression that is in f's position is *not* pure, instead it's an operator on arrows. In the GHC users' guide we have https://downloads.haskell.org/~ghc/7.2.2/docs/html/users_guide/arrow-notatio... untilA :: ArrowChoice a => a e () -> a e Bool -> a e () ... ... (|untilA (increment -< x+y) (within 0.5 -< x)|) untilA is manifestly not a pure function. So, I don't think these brackets are the same thing. I may have been wrong to say they are not related, but I can't see that there's as close a correspondence as you are trying to make out. Tom
participants (7)
-
Erik Hesselink
-
Ian Zimmerman
-
Kim-Ee Yeoh
-
martin
-
S. Doaitse Swierstra
-
Tikhon Jelvis
-
Tom Ellis