Proposal: Add (&) to Data.Function

It is a common idiom to write a sequence of composed combinators in reverse order to the way they would be written with ($) or (.). That naturally expresses the idea of the combinators as operations being applied in the given order. This comes up so often, and is commonly used so many times in a single expression, that Control.Arrow.>>> is far too wordy, and even a two- character operator is awkward. Surprisingly, until recently the operator (&) was still not used in any of the popular libraries, and its name naturally expresses the idea we are looking for. This operator has now been defined in the lens package. We hereby propose to move it to its natural home for more general use, Data.Function. As in the lens package, we define the operator as a flipped version of ($), but with slightly higher precedence for better interaction with ($), and with left associativity. This definition has already proven useful and convenient even in the presence of the large and varied corpus of combinators and operators in the lens package. (There it was formerly known as (%), but that clashed with the usual meaning of (%) from Data.Ratio.) infixl 1 & (&) :: a -> (a -> b) -> b a & f = f a {-# INLINE (&) #-} Discussion period: 2 weeks http://hackage.haskell.org/trac/ghc/ticket/7434 Thanks, Yitz

Just to bring up some prior art, from what I've heard, F# calls this |>. In
Clojure the -> function takes a value and a series of functions, and
applies them in order from left to right, e.g. (-> 5 zero? not) ;;=> true.
Obviously, In OO languages, this is usually accomplished by chaining calls
foo.bar().baz().quux().
I agree that Haskell should provide this idiom. I find & to be a strange
name for it, but to be honest, it's no stranger than $ so I say go for it.
I would suggest | to mimic the unix pipe, but this obviously clashes with
Haskell guard syntax. I think |> is a reasonable name, but Data.Sequence
has already claimed it.
-- Dan Burton
On Tue, Nov 20, 2012 at 9:59 AM, Yitzchak Gale
It is a common idiom to write a sequence of composed combinators in reverse order to the way they would be written with ($) or (.). That naturally expresses the idea of the combinators as operations being applied in the given order.
This comes up so often, and is commonly used so many times in a single expression, that Control.Arrow.>>> is far too wordy, and even a two- character operator is awkward.
Surprisingly, until recently the operator (&) was still not used in any of the popular libraries, and its name naturally expresses the idea we
are
looking for. This operator has now been defined in the lens package. We hereby propose to move it to its natural home for more general use, Data.Function.
As in the lens package, we define the operator as a flipped version of ($), but with slightly higher precedence for better interaction with ($), and with left associativity. This definition has already proven useful and convenient even in the presence of the large and varied corpus of combinators and operators in the lens package. (There it was formerly known as (%), but that clashed with the usual meaning of (%) from Data.Ratio.)
infixl 1 & (&) :: a -> (a -> b) -> b a & f = f a {-# INLINE (&) #-}
Discussion period: 2 weeks
http://hackage.haskell.org/trac/ghc/ticket/7434
Thanks, Yitz
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Tue, Nov 20, 2012 at 9:19 AM, Dan Burton
I agree that Haskell should provide this idiom. I find & to be a strange name for it, but to be honest, it's no stranger than $ so I say go for it. I would suggest | to mimic the unix pipe, but this obviously clashes with Haskell guard syntax. I think |> is a reasonable name, but Data.Sequence has already claimed it.
I also like |> for the color of this shed, as there's prior art for it.
but Data.Sequence has already claimed it.
We should use namespaces for these things instead of trying to come up with globally unique names (be they symbols). Trying to be globally unique doesn't scale to large codebases and eventually gives =>@@@@#$>. ;)

On 20.11.2012 18:25, Johan Tibell wrote:
On Tue, Nov 20, 2012 at 9:19 AM, Dan Burton
mailto:danburton.email@gmail.com> wrote: I agree that Haskell should provide this idiom. I find & to be a strange name for it, but to be honest, it's no stranger than $ so I say go for it. I would suggest | to mimic the unix pipe, but this obviously clashes with Haskell guard syntax. I think |> is a reasonable name, but Data.Sequence has already claimed it.
I also like |> for the color of this shed, as there's prior art for it.
but Data.Sequence has already claimed it.
We should use namespaces for these things instead of trying to come up with globally unique names (be they symbols). Trying to be globally unique doesn't scale to large codebases and eventually gives =>@@@@#$>. ;)
+1 -- Andreas Abel <>< Du bist der geliebte Mensch. Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/

On 20.11.2012 18:19, Dan Burton wrote:
I think |> is a reasonable name, but Data.Sequence has already claimed it.
Well, disown Data.Sequence. Application is more important than some data type. Cheers, Andreas
On Tue, Nov 20, 2012 at 9:59 AM, Yitzchak Gale
mailto:gale@sefer.org> wrote: It is a common idiom to write a sequence of composed combinators in reverse order to the way they would be written with ($) or (.). That naturally expresses the idea of the combinators as operations being applied in the given order.
This comes up so often, and is commonly used so many times in a single expression, that Control.Arrow.>>> is far too wordy, and even a two- character operator is awkward.
Surprisingly, until recently the operator (&) was still not used in any of the popular libraries, and its name naturally expresses the idea
we are
looking for. This operator has now been defined in the lens package. We hereby propose to move it to its natural home for more general use, Data.Function.
As in the lens package, we define the operator as a flipped version of ($), but with slightly higher precedence for better interaction with ($), and with left associativity. This definition has already proven useful and convenient even in the presence of the large and varied corpus of combinators and operators in the lens package. (There it was formerly known as (%), but that clashed with the usual meaning of (%) from Data.Ratio.)
infixl 1 & (&) :: a -> (a -> b) -> b a & f = f a {-# INLINE (&) #-}
Discussion period: 2 weeks
http://hackage.haskell.org/trac/ghc/ticket/7434
Thanks, Yitz
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Andreas Abel <>< Du bist der geliebte Mensch. Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/

"Haskell" called this operator (#) about 12 years ago - see Peter
Thiemann's WASH and Eric Meijer and colleagues MS Agent scripting.
I'd much prefer (#) if it didn't interfere with GHC's magic hash, I
suspect the above authors were using Hugs...
On 20 November 2012 17:19, Dan Burton
Just to bring up some prior art, from what I've heard, F# calls this |>.

(#) is also used by the diagrams library, mainly for using functions as if
they were "attributes".
In the context of lens, this is discussed a bit here:
https://github.com/ekmett/lens/issues/17
On Tue, Nov 20, 2012 at 9:31 AM, Stephen Tetley
"Haskell" called this operator (#) about 12 years ago - see Peter Thiemann's WASH and Eric Meijer and colleagues MS Agent scripting.
I'd much prefer (#) if it didn't interfere with GHC's magic hash, I suspect the above authors were using Hugs...
On 20 November 2012 17:19, Dan Burton
wrote: Just to bring up some prior art, from what I've heard, F# calls this |>.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

And the results of the IRC discussion on lens:
https://github.com/ekmett/lens/issues/100
I do think that this looks nicer, for whatever reason. While the mnemonic
of "mod"ulus can suggest modify once you know that, (&) somewhat naturally
suggests "and then" ... "and then". I still prefer (#) for overall
consistency and history, but other than its conjunction connotations, (&)
is mnemonically better.
It'll be funny to mix diagrams and lens code - (&) is used for sticking
coordinates together for points / vectors - while (#) would stand in for
(&).
On Tue, Nov 20, 2012 at 10:17 AM, Michael Sloan
(#) is also used by the diagrams library, mainly for using functions as if they were "attributes".
In the context of lens, this is discussed a bit here: https://github.com/ekmett/lens/issues/17
On Tue, Nov 20, 2012 at 9:31 AM, Stephen Tetley
wrote: "Haskell" called this operator (#) about 12 years ago - see Peter Thiemann's WASH and Eric Meijer and colleagues MS Agent scripting.
I'd much prefer (#) if it didn't interfere with GHC's magic hash, I suspect the above authors were using Hugs...
On 20 November 2012 17:19, Dan Burton
wrote: Just to bring up some prior art, from what I've heard, F# calls this |>.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

& also means bitwise-and to most of the world's programmers, so it may be more confusing for beginners.

They are already stymied by the fact that | is used as part of the syntax,
so it isn't bitwise-or. =P
On Tue, Nov 20, 2012 at 1:37 PM, Johan Tibell
& also means bitwise-and to most of the world's programmers, so it may be more confusing for beginners.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

I'm a strong +1 for accepting this proposal as it stands.
I'm decidedly lukewarm / a weak -1 on switching it to (|>).
Another popular color of this bikeshed, (#) as is used in diagrams,
interacts very poorly with MagicHash and has a very high precedence that
ruins it for most dsl purposes.
We had it as (|>) in lens for a while and it didn't read well. It is often
used in long compositions and the extra character adds up when chained
several times.
-- >>> zipper ("hello","world") & down _1 & fromWithin traverse &
focus .~ 'J' & rightmost & focus .~ 'y' & rezip
-- ("Jelly","world")
isoRules = defaultRules
& handleSingletons .~ True
& singletonRequired .~ True
& singletonAndField .~ True
Both of those examples read much better with & than (|>).
We had switched to % from (|>) to be consistent with the other (+=) (*=)
operators where (%=) was being read as 'mod-equals' as a bit of a pun, and
could be seen as the application of the % operator to the target.
However this led to issues with a vocal minority who objected to it
changing the meaning of 4 % 3 on lambdabot when combined with NumInstances.
We converted to (&) because of its incredible terseness and general lack of
use across hackage. For DSL purposes, to me it is key that this operator be
as succinct as possible and (&) is remarkably underutilized in haskell
libraries today, due to the fact that (|) is taken by syntax, and our
C-inspired brains tend to pair them.
-Edward
On Tue, Nov 20, 2012 at 1:27 PM, Michael Sloan
And the results of the IRC discussion on lens: https://github.com/ekmett/lens/issues/100
I do think that this looks nicer, for whatever reason. While the mnemonic of "mod"ulus can suggest modify once you know that, (&) somewhat naturally suggests "and then" ... "and then". I still prefer (#) for overall consistency and history, but other than its conjunction connotations, (&) is mnemonically better.
It'll be funny to mix diagrams and lens code - (&) is used for sticking coordinates together for points / vectors - while (#) would stand in for (&).
On Tue, Nov 20, 2012 at 10:17 AM, Michael Sloan
wrote: (#) is also used by the diagrams library, mainly for using functions as if they were "attributes".
In the context of lens, this is discussed a bit here: https://github.com/ekmett/lens/issues/17
On Tue, Nov 20, 2012 at 9:31 AM, Stephen Tetley
wrote:
"Haskell" called this operator (#) about 12 years ago - see Peter Thiemann's WASH and Eric Meijer and colleagues MS Agent scripting.
I'd much prefer (#) if it didn't interfere with GHC's magic hash, I suspect the above authors were using Hugs...
On 20 November 2012 17:19, Dan Burton
wrote: Just to bring up some prior art, from what I've heard, F# calls this |>.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Tue, Nov 20, 2012 at 10:39 AM, Edward Kmett
We converted to (&) because of its incredible terseness and general lack of use across hackage. For DSL purposes, to me it is key that this operator be as succinct as possible and (&) is remarkably underutilized in haskell libraries today, due to the fact that (|) is taken by syntax, and our C-inspired brains tend to pair them.
That seems fairly convincing to me. Count me as a +1 on Yitz's original proposal of & *or* on |> instead, whichever wins in the court of popular opinion. I assume this will have the not-very exciting type of (a -> b) -> (b -> c) -> a -> c ?

On Tue, Nov 20, 2012 at 1:44 PM, Bryan O'Sullivan
On Tue, Nov 20, 2012 at 10:39 AM, Edward Kmett
wrote: We converted to (&) because of its incredible terseness and general lack of use across hackage. For DSL purposes, to me it is key that this operator be as succinct as possible and (&) is remarkably underutilized in haskell libraries today, due to the fact that (|) is taken by syntax, and our C-inspired brains tend to pair them.
That seems fairly convincing to me. Count me as a +1 on Yitz's original proposal of & *or* on |> instead, whichever wins in the court of popular opinion.
I assume this will have the not-very exciting type of
(a -> b) -> (b -> c) -> a -> c
?
(&) :: a -> (a -> b) -> b it is just flip ($)
("hello","world") & _1.traverse %~ toUpper & _2 .~ 42 ("HELLO",42)
could be written _2 .~ 42 $ _1.traverse .~ toUpper $ ("hello","world") but that goes in the opposite direction of the corresponding code for working with the state monad with lenses: foo = do _1.traverse %= toUpper _2 .~ "42" -Edward

On 20 November 2012 18:52, Edward Kmett
("hello","world") & _1.traverse %~ toUpper & _2 .~ 42 ("HELLO",42)
could be written
_2 .~ 42 $ _1.traverse .~ toUpper $ ("hello","world")
Surely, you must be joking. That's some butt-ugly piece of code. Let's not try to turn Haskell into J or Perl. Personally, I like neither (&) nor (|>). The latter is used in OCaml/F# but looks quite ugly (I know rendering it as a latex triangle would look pretty nice, but we can't rely on everyone having that option). Regarding, (&) I agree that it looks a bit like bitwise or, but I suspect that is something that people can get used to quite quickly. I agree with Johan that "works well with <some-non-platform-library>" should not be a criterion. +0.2 for (&), and +0.1 for (|>)

Edward Kmett
writes:
We had switched to % from (|>) to be consistent with the other (+=) (*=) operators where (%=) was being read as 'mod-equals' as a bit of a pun, and could be seen as the application of the % operator to the target.
Yes, a strong positive in favor of & of |> is that it allows the lens library to offer the highly useful variants &= and &~, which have obvious (and related) meanings to someone using lens. |>= and |>~ would get a bit awkward in comparison. -- John Wiegley FP Complete Haskell tools, training and consulting http://fpcomplete.com johnw on #haskell/irc.freenode.net

On 20.11.2012 19:46, John Wiegley wrote:
Edward Kmett
writes: We had switched to % from (|>) to be consistent with the other (+=) (*=) operators where (%=) was being read as 'mod-equals' as a bit of a pun, and could be seen as the application of the % operator to the target.
Yes, a strong positive in favor of & of |> is that it allows the lens library to offer the highly useful variants &= and &~, which have obvious (and related) meanings
Well, the obvious meaning of &= is bitwise-and-with, like in x &= 0xff7f; isn't it? ;-)
to someone using lens. |>= and |>~ would get a bit awkward in comparison.
The symbol |> combines the pipe | with an arrow > indicating the direction of information flow. And it is used in ML already. Hard to beat. -- Andreas Abel <>< Du bist der geliebte Mensch. Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/

Andreas Abel
writes:
Well, the obvious meaning of &= is bitwise-and-with, like in x &= 0xff7f; isn't it? ;-)
I realize this is tongue-in-cheek, but & is not universally the "bit-wise and" operator. In the POSIX shell saying "foo & bar" means to start processing foo asynchronously and then run "bar". But that also breaks the piping analogy lens is using & for, so hmm... I think |>= and |>~ would just be unfortunate, and lens is likely to be one of the biggest users of this new operator (at least at this point in time). -- John Wiegley FP Complete Haskell tools, training and consulting http://fpcomplete.com johnw on #haskell/irc.freenode.net

Hi,
On Tue, Nov 20, 2012 at 11:02 AM, John Wiegley
I think |>= and |>~ would just be unfortunate, and lens is likely to be one of the biggest users of this new operator (at least at this point in time).
I think the biggest user will be Haskell code in general, because you can now use |> instead of ".", so we should be optimizing for that, not for any particular library. Cheers, Johan

On Tue, Nov 20, 2012 at 2:10 PM, Johan Tibell
Hi,
On Tue, Nov 20, 2012 at 11:02 AM, John Wiegley
wrote: I think |>= and |>~ would just be unfortunate, and lens is likely to be one of the biggest users of this new operator (at least at this point in time).
I think the biggest user will be Haskell code in general, because you can now use |> instead of ".", so we should be optimizing for that, not for any particular library.
Great! And using & instead of the longer line-noisier identifier cuts down on the visual clutter in that code tremendously. =P $ is one symbol. & is one symbol. ("hello","world" ) & fst & length grows on you ;) -Edward

On Tue, Nov 20, 2012 at 2:10 PM, Johan Tibell
I think the biggest user will be Haskell code in general, because you can now use |> instead of ".", so we should be optimizing for that, not for any particular library.
I'm already thinking that (|>) looks clunky compared to (.) even if the latter seems "backwards". -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix/linux, openafs, kerberos, infrastructure http://sinenomine.net

Johan Tibell wrote:
I think the biggest user will be Haskell code in general,
because you can now use |> instead of ".", so we
should be optimizing for that, not for any particular
library.
I agree with that sentiment. The main reason I proposed what the lens people are using is because the lens world is such a good testing bed for this. Lens covers quite a large swath of interesting types, paradigms, and use cases. And of course a large number of combinators and operators. There seems to be a good size group of people hacking on all that and using it in practice. For something as basic as this, all the little details matter. All of those details have gotten some real-world testing, and comparison with their alternatives. Making it flip ($) instead of flip (.). The precedence. The fixity. And also the color of the bikeshed. It turns out that the difference between a one-character name and two-character name really is significant in practice, more than you might realize, even without factoring in the grand operator-naming scheme in lens. Thanks, Yitz

On Tue, Nov 20, 2012 at 10:46 AM, John Wiegley
Yes, a strong positive in favor of & of |> is that it allows the lens library to offer the highly useful variants &= and &~, which have obvious (and related) meanings to someone using lens. |>= and |>~ would get a bit awkward in comparison.
I don't think embedding APL in Haskell should be a guiding principle. ;)

My major point was originally that code written with & 'reads' well if the
person reads the operator as 'and' or 'and then', but with '|>' you have to
mix metaphors involving pipes that don't quite exactly hold and further
exacerbate the common complaint that Haskell has a ton of complex
multicharacter operators that nobody knows how to pronounce.
On Tue, Nov 20, 2012 at 1:59 PM, Johan Tibell
On Tue, Nov 20, 2012 at 10:46 AM, John Wiegley
wrote: Yes, a strong positive in favor of & of |> is that it allows the lens library to offer the highly useful variants &= and &~, which have obvious (and related) meanings to someone using lens. |>= and |>~ would get a bit awkward in comparison.
I don't think embedding APL in Haskell should be a guiding principle. ;)
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

At this time I haven't switched the %~ operators from %. I will miss the
consistency that operator= or operator~ applies the operator to the target
of the lens, like how += applies (+) to the target of an l-value, in this
case, but i think it'd be silly to try too hard to be consistent across
every use of % in lens and that %= for mod-equals still reads better than
&=, which _is_ used in lens for bitwise .&. in data.bits.lens mosty because
.&.= is silly looking ;)
-Edward
On Tue, Nov 20, 2012 at 1:46 PM, John Wiegley
Edward Kmett
writes: We had switched to % from (|>) to be consistent with the other (+=) (*=) operators where (%=) was being read as 'mod-equals' as a bit of a pun, and could be seen as the application of the % operator to the target.
Yes, a strong positive in favor of & of |> is that it allows the lens library to offer the highly useful variants &= and &~, which have obvious (and related) meanings to someone using lens. |>= and |>~ would get a bit awkward in comparison.
-- John Wiegley FP Complete Haskell tools, training and consulting http://fpcomplete.com johnw on #haskell/irc.freenode.net
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Edward Kmett
writes:
At this time I haven't switched the %~ operators from %. I will miss the consistency that operator= or operator~ applies the operator to the target of the lens, like how += applies (+) to the target of an l-value, in this case, but i think it'd be silly to try too hard to be consistent across every use of % in lens and that %= for mod-equals still reads better than &=, which _is_ used in lens for bitwise .&. in data.bits.lens mosty because .&.= is silly looking ;)
And let's not forget that the current <%= operator would turn into <|>=, which is completely unfortunate because it has nothing to do with <|>. -- John Wiegley FP Complete Haskell tools, training and consulting http://fpcomplete.com johnw on #haskell/irc.freenode.net

On Tue, Nov 20, 2012 at 11:11 AM, John Wiegley
And let's not forget that the current <%= operator would turn into <|>=, which is completely unfortunate because it has nothing to do with <|>.
lens currently defines 99 operators. As much as I admire Edward's work, I don't think we should take the interaction of these operators into account when we define a very important, standard operator for composing functions that's supposed to be used by the Haskell ecosystem as a whole.

Is it safe to say that most of us are agreeing that *something* like this should be included in the Prelude? Does anyone feel strongly that this should *not* be in the Prelude? If such is the case, then it seems we have three popular options for the color of this shed: & as seen currently in lens |> as seen in ML # as seen in diagrams I find these to all be acceptable options, and would be happy to see any of them defined in the Prelude as x `op` f = f x. My 2c: I lean towards |> because it is already used in ML, and because I believe it is the most foreign to newcomers, and therefore the most likely to *not* be misinterpreted. On a huge tangent, suppose we used Lisk, which supports "chaining" the same operator as if it were a var-arg function. (|> 5 isZero not) is very close to the equivalent Clojure (-> 5 zero? not). Presumably -> as a Haskell operator name is out of the question. -- Dan Burton

On Tue, Nov 20, 2012 at 12:45:04PM -0700, Dan Burton wrote:
Is it safe to say that most of us are agreeing that *something* like this should be included in the Prelude? Does anyone feel strongly that this should *not* be in the Prelude?
The proposal is to add it to Data.Function, not to the Prelude. Thanks Ian

On Tue, Nov 20, 2012 at 2:20 PM, Johan Tibell
On Tue, Nov 20, 2012 at 11:11 AM, John Wiegley
wrote: And let's not forget that the current <%= operator would turn into <|>=, which is completely unfortunate because it has nothing to do with <|>.
lens currently defines 99 operators. As much as I admire Edward's work, I don't think we should take the interaction of these operators into account when we define a very important, standard operator for composing functions that's supposed to be used by the Haskell ecosystem as a whole.
Yes, lens defines 99 operators. The vast majority of them fall into a
common scheme;
operator~ for functional update using a well known operatr
operator= for an update into state.

I strongly support to have a standard, succinct notation for arg-fun-application. Here are my two reservations about your proposal: 1. First, I think there should be a type class of functions, such that the application operator can be overloaded. (Should also happen for $). 2. (&) just has a too strong connotation of conjunction to stand for application. ML has (|>) which also looks a bit similar to (>>=), see, e.g. http://isabelle.in.tum.de/repos/isabelle/file/Isabelle2011-1/src/Pure/Genera... Andreas On 20.11.2012 17:59, Yitzchak Gale wrote:
It is a common idiom to write a sequence of composed combinators in reverse order to the way they would be written with ($) or (.). That naturally expresses the idea of the combinators as operations being applied in the given order.
This comes up so often, and is commonly used so many times in a single expression, that Control.Arrow.>>> is far too wordy, and even a two- character operator is awkward.
Surprisingly, until recently the operator (&) was still not used in any of the popular libraries, and its name naturally expresses the idea we are looking for. This operator has now been defined in the lens package. We hereby propose to move it to its natural home for more general use, Data.Function.
As in the lens package, we define the operator as a flipped version of ($), but with slightly higher precedence for better interaction with ($), and with left associativity. This definition has already proven useful and convenient even in the presence of the large and varied corpus of combinators and operators in the lens package. (There it was formerly known as (%), but that clashed with the usual meaning of (%) from Data.Ratio.)
infixl 1 & (&) :: a -> (a -> b) -> b a & f = f a {-# INLINE (&) #-}
Discussion period: 2 weeks
http://hackage.haskell.org/trac/ghc/ticket/7434
Thanks, Yitz
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Andreas Abel <>< Du bist der geliebte Mensch. Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/

On Tue, 20 Nov 2012, Yitzchak Gale wrote:
It is a common idiom to write a sequence of composed combinators in reverse order to the way they would be written with ($) or (.). That naturally expresses the idea of the combinators as operations being applied in the given order.
This comes up so often, and is commonly used so many times in a single expression, that Control.Arrow.>>> is far too wordy, and even a two- character operator is awkward.
Functional metapost called it (#). But for me (>>>) is ok. It is even more descriptive than (&).

Note: (>>>) is a completely different operator.
is flipped (.). The proposed & is flipped $.
(>>>) :: Category cat => cat a b -> cat b c -> cat a c (&) :: a -> (a -> b) -> b -Edward On Tue, Nov 20, 2012 at 3:14 PM, Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Tue, 20 Nov 2012, Yitzchak Gale wrote:
It is a common idiom to write a sequence of composed combinators in
reverse order to the way they would be written with ($) or (.). That naturally expresses the idea of the combinators as operations being applied in the given order.
This comes up so often, and is commonly used so many times in a single expression, that Control.Arrow.>>> is far too wordy, and even a two- character operator is awkward.
Functional metapost called it (#). But for me (>>>) is ok. It is even more descriptive than (&).
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Tue, Nov 20, 2012 at 9:27 PM, Edward Kmett
Note: (>>>) is a completely different operator.
is flipped (.). The proposed & is flipped $.
(>>>) :: Category cat => cat a b -> cat b c -> cat a c
(&) :: a -> (a -> b) -> b
-Edward
...and my quibble with (&) as flip ($) is that I think it would, in fact, be more mnemonic as a synonym for (>>>). Consider: filter even & map (*2) & sum That reads naturally and obviously as "filter by even and double and sum". It's an operation. What if we apply it to an argument? (filter even & map (*2) & sum) theList Still works. Filter by even and double and sum the list. What if (&) is flip ($) instead? theList & filter even & map (*2) & sum The second two are fine enough (same as before), but the first one is weird. What does it mean to "the list and filter by even"? It feels like a type error.
On Tue, Nov 20, 2012 at 3:14 PM, Henning Thielemann
wrote: On Tue, 20 Nov 2012, Yitzchak Gale wrote:
It is a common idiom to write a sequence of composed combinators in reverse order to the way they would be written with ($) or (.). That naturally expresses the idea of the combinators as operations being applied in the given order.
This comes up so often, and is commonly used so many times in a single expression, that Control.Arrow.>>> is far too wordy, and even a two- character operator is awkward.
Functional metapost called it (#). But for me (>>>) is ok. It is even more descriptive than (&).
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Your ship was destroyed in a monadic eruption.

Gábor Lehel
writes:
What if (&) is flip ($) instead?
theList & filter even & map (*2) & sum
Take the list as given and filter the evens and multiply each element by two and take the sum. theList |> filter even |> map (*2) |> sum Is your argument against the operator in general? The |> usage has the same problem. Also, |> feels like something related to Alternative, a point Edward mentioned. -- John Wiegley FP Complete Haskell tools, training and consulting http://fpcomplete.com johnw on #haskell/irc.freenode.net

Functional metapost called it (#). But for me (>>>) is ok. It is even more descriptive than (&).
The reason I feel that >>> is inadequate is because it requires that you use either parens or $ in order to finally apply the chain of functions to a value. Also, being part of a typeclass can scare newcomers from using/understanding it. (foo >>> bar >>> baz) val foo >>> bar >>> baz $ val Blegh. Part of the reason I like |> is because it *is* a little more clutter-y than &. This forces you to use it prudently, with adequate whitespace. For example, when I was writing a StackOverflow answer[1] a few days ago, I found that using this operator was unreadable unless I used additional newlines. Lining up the |> operators actually produces a rather nice visual effect, as if you were entering each transformation at a command prompt. The vertical bars lining up is also nice. Consider the "butt-ugly" code (according to Thomas): ("hello","world") & _1.traverse %~ toUpper & _2 .~ 42 Rewritten with whitespace, it can look much prettier: ("Hello", "world") |> _1.traverse %~ toUpper |> _2 .~ 42 This style is reminiscent of the style often used for long chains of object-oriented method calls. & works just as well with the additional whitespace, but complaints about the line noise caused by |> go away also. [1] http://stackoverflow.com/a/13432926/208257 -- Dan Burton

On Tue, Nov 20, 2012 at 3:32 PM, Dan Burton
Functional metapost called it (#). But for me (>>>) is ok. It is even more
descriptive than (&).
The reason I feel that >>> is inadequate is because it requires that you use either parens or $ in order to finally apply the chain of functions to a value. Also, being part of a typeclass can scare newcomers from using/understanding it.
(foo >>> bar >>> baz) val foo >>> bar >>> baz $ val
Blegh.
Part of the reason I like |> is because it *is* a little more clutter-y than &. This forces you to use it prudently, with adequate whitespace. For example, when I was writing a StackOverflow answer[1] a few days ago, I found that using this operator was unreadable unless I used additional newlines. Lining up the |> operators actually produces a rather nice visual effect, as if you were entering each transformation at a command prompt. The vertical bars lining up is also nice. Consider the "butt-ugly" code (according to Thomas):
("hello","world") & _1.traverse %~ toUpper & _2 .~ 42
Rewritten with whitespace, it can look much prettier:
("Hello", "world") |> _1.traverse %~ toUpper |> _2 .~ 42
You can make pretty much any mishmash of operators more palatable by creative spacing and lots of newlines. If you dig around in the lens code, many of the uses of (&) are spaced exactly this way. The case is perhaps made better by DSLs that themselves aren't operator ridden, so we don't get muddled in precedence issues:
def & forward 10 & down & turn (pi/2) & forward 5 Turtle {_tPoint = Point {_x = 5.0, _y = 10.0}, _tColor = Color {_r = 0, _g = 0, _b = 0}, _heading = 1.5707963267948966, _penDown = True}
When the operations are as individually small as I sketched above though, the overhead of that operator accretes pretty fast, and the overhead of all those newlines gets silly. =) Admittedly, I perhaps should have chosen an example where the (|>) looks less like the turtle in question. ;) -Edward

Dan Burton
writes:
Rewritten with whitespace, it can look much prettier:
("Hello", "world") |> _1.traverse %~ toUpper |> _2 .~ 42
Or: ("Hello", "world") & _1.traverse %~ toUpper & _2 .~ 42 But now we are just arguing aesthetics. Please keep in mind that choosing |> over & on aesthetic grounds has an unfortunate casualty: |> doesn't fit into the operator hierarchy of lens, while & does quite nicely. So while I can't argue |> over &, or vice-versa, for their own sake, we should not lose sight of this clear cost to lens in choosing |>. And I feel this is important, because as lens matures it could become one of the shining features of Haskell. There are certain lens traversals that are able to work pure magic in nice, compact expressions, while remaining quite readable over their non-lens counterparts -- such as picking all Int's out of an arbitrarily complex structure: ghci> (("hello","world"),"!!!", 2 :: Int, ()) ^..biplate :: [Int] [2] Once lens catches on, the operator we're calling |> or & will become an operator that gets used many times a day by lens users, so it should be as unobtrusive as possible, and fit with the natural pattern of other, related operators. I realize Johan suggested we not consider the choice of operator in the context of any one library, but we also shouldn't ignore a prominent library that has a significant use case for that operator. In fact, not having this operator hasn't been an issue for nearly many years now, but the reason we're discussing it today is due to lens. -- John Wiegley FP Complete Haskell tools, training and consulting http://fpcomplete.com johnw on #haskell/irc.freenode.net

Another option that was raised in a mailing list thread at some point
(I think it was one about records): $.
The idea being to evoke the dot operator of object-oriented languages
together with the existing ($) of function application.
theList $. filter even $. map (*2) $. sum
If you read it by focusing on the dots as in an OO language it sort of
works. Not sure how I feel about it, throwing it out there. As a
candidate for the least bad choice I think it at least qualifies.
On Tue, Nov 20, 2012 at 5:59 PM, Yitzchak Gale
It is a common idiom to write a sequence of composed combinators in reverse order to the way they would be written with ($) or (.). That naturally expresses the idea of the combinators as operations being applied in the given order.
This comes up so often, and is commonly used so many times in a single expression, that Control.Arrow.>>> is far too wordy, and even a two- character operator is awkward.
Surprisingly, until recently the operator (&) was still not used in any of the popular libraries, and its name naturally expresses the idea we are looking for. This operator has now been defined in the lens package. We hereby propose to move it to its natural home for more general use, Data.Function.
As in the lens package, we define the operator as a flipped version of ($), but with slightly higher precedence for better interaction with ($), and with left associativity. This definition has already proven useful and convenient even in the presence of the large and varied corpus of combinators and operators in the lens package. (There it was formerly known as (%), but that clashed with the usual meaning of (%) from Data.Ratio.)
infixl 1 & (&) :: a -> (a -> b) -> b a & f = f a {-# INLINE (&) #-}
Discussion period: 2 weeks
http://hackage.haskell.org/trac/ghc/ticket/7434
Thanks, Yitz
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Your ship was destroyed in a monadic eruption.

$. is kind of the worst of all possible worlds to me.
(|>) at least has the ML precedent going for it, but ($.) using the . to
indicate the side that the function is on offers very little to visually
distinguish it from ($) and no such precedent to motivate it.
The first time I read your post I read the . as the end of sentence marker.
=P
-Edward
On Tue, Nov 20, 2012 at 4:08 PM, Gábor Lehel
Another option that was raised in a mailing list thread at some point (I think it was one about records): $.
The idea being to evoke the dot operator of object-oriented languages together with the existing ($) of function application.
theList $. filter even $. map (*2) $. sum
If you read it by focusing on the dots as in an OO language it sort of works. Not sure how I feel about it, throwing it out there. As a candidate for the least bad choice I think it at least qualifies.
On Tue, Nov 20, 2012 at 5:59 PM, Yitzchak Gale
wrote: It is a common idiom to write a sequence of composed combinators in reverse order to the way they would be written with ($) or (.). That naturally expresses the idea of the combinators as operations being applied in the given order.
This comes up so often, and is commonly used so many times in a single expression, that Control.Arrow.>>> is far too wordy, and even a two- character operator is awkward.
Surprisingly, until recently the operator (&) was still not used in any of the popular libraries, and its name naturally expresses the idea we are looking for. This operator has now been defined in the lens package. We hereby propose to move it to its natural home for more general use, Data.Function.
As in the lens package, we define the operator as a flipped version of ($), but with slightly higher precedence for better interaction with ($), and with left associativity. This definition has already proven useful and convenient even in the presence of the large and varied corpus of combinators and operators in the lens package. (There it was formerly known as (%), but that clashed with the usual meaning of (%) from Data.Ratio.)
infixl 1 & (&) :: a -> (a -> b) -> b a & f = f a {-# INLINE (&) #-}
Discussion period: 2 weeks
http://hackage.haskell.org/trac/ghc/ticket/7434
Thanks, Yitz
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Your ship was destroyed in a monadic eruption.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

If you're having bikeshedding problems, I feel bad for you son. Lens got
99 operators, but a (|>) ain't one.
In all seriousness though, in light of edward's detailed reasonings, I'm
fully behind (&) instead of (#). ML-compatibility shouldn't be the
concern, and the happenstance of (&) being relatively unused is a great
opportunity. Frequently used operators with concise meanings should have
concise symbols - works out well!
-Michael
On Tue, Nov 20, 2012 at 1:22 PM, Bryan O'Sullivan
On Tue, Nov 20, 2012 at 1:21 PM, Edward Kmett
wrote: $. is kind of the worst of all possible worlds to me.
Agreed.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Nov 20, 2012, at 5:31 PM, Michael Sloan
If you're having bikeshedding problems, I feel bad for you son. Lens got 99 operators, but a (|>) ain't one.
In all seriousness though, in light of edward's detailed reasonings, I'm fully behind (&) instead of (#). ML-compatibility shouldn't be the concern, and the happenstance of (&) being relatively unused is a great opportunity. Frequently used operators with concise meanings should have concise symbols - works out well!
-Michael
If we had a nice LaTeX triangle for |>, I'd be for that. But we live in a symbol impoverished world, and I prefer & to the old lens standby of %. So, for today's Haskell, I'm a +1 for &. Anthony

On 21 November 2012 14:00, Anthony Cowley
On Nov 20, 2012, at 5:31 PM, Michael Sloan
wrote: If you're having bikeshedding problems, I feel bad for you son. Lens got 99 operators, but a (|>) ain't one.
In all seriousness though, in light of edward's detailed reasonings, I'm fully behind (&) instead of (#). ML-compatibility shouldn't be the concern, and the happenstance of (&) being relatively unused is a great opportunity. Frequently used operators with concise meanings should have concise symbols - works out well!
-Michael
If we had a nice LaTeX triangle for |>, I'd be for that. But we live in a symbol impoverished world, and I prefer & to the old lens standby of %. So, for today's Haskell, I'm a +1 for &.
fgl - which is in the Platform - uses &. Admittedly this isn't likely to affect many people though.
Anthony _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com

On Wed, Nov 21, 2012 at 12:19 AM, Ivan Lazar Miljenovic < ivan.miljenovic@gmail.com> wrote:
fgl - which is in the Platform - uses &.
Admittedly this isn't likely to affect many people though.
Also, keep in mind that this is an import you'd have to go explicitly get
from Data.Function.

On Wed, Nov 21, 2012 at 12:23 AM, Edward Kmett
On Wed, Nov 21, 2012 at 12:19 AM, Ivan Lazar Miljenovic < ivan.miljenovic@gmail.com> wrote:
fgl - which is in the Platform - uses &.
Admittedly this isn't likely to affect many people though.
FWIW, th alternative color for this bikeshed that has been proposed (|>) collides with Data.Sequence from containers, which is also in the platform, and with Data.FingerTree, which isn't, but its pretty much impossible to avoid colliding with every package everywhere.

+1 for &
One other thing to consider: Three years ago I proposed[3962] adding a
flipped fmap to Data.Functor:
(<$$>) :: Functor f => f a -> (a -> b) -> f b
This proposal failed. However, when & gets added I can see myself
defining the following instead:
(<&>) :: Functor f => f a -> (a -> b) -> f b
Regards,
Bas
[3962] http://hackage.haskell.org/trac/ghc/ticket/3962
On 20 November 2012 17:59, Yitzchak Gale
It is a common idiom to write a sequence of composed combinators in reverse order to the way they would be written with ($) or (.). That naturally expresses the idea of the combinators as operations being applied in the given order.
This comes up so often, and is commonly used so many times in a single expression, that Control.Arrow.>>> is far too wordy, and even a two- character operator is awkward.
Surprisingly, until recently the operator (&) was still not used in any of the popular libraries, and its name naturally expresses the idea we are looking for. This operator has now been defined in the lens package. We hereby propose to move it to its natural home for more general use, Data.Function.
As in the lens package, we define the operator as a flipped version of ($), but with slightly higher precedence for better interaction with ($), and with left associativity. This definition has already proven useful and convenient even in the presence of the large and varied corpus of combinators and operators in the lens package. (There it was formerly known as (%), but that clashed with the usual meaning of (%) from Data.Ratio.)
infixl 1 & (&) :: a -> (a -> b) -> b a & f = f a {-# INLINE (&) #-}
Discussion period: 2 weeks
http://hackage.haskell.org/trac/ghc/ticket/7434
Thanks, Yitz
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

+1 for (&) or (#), -1 for (|>), because that name strongly suggests that there is also an (<|) operator. Of course we could add (<|) as a synonym for ($), but that would be unnecessary and confusing. Twan On 20/11/12 17:59, Yitzchak Gale wrote:
It is a common idiom to write a sequence of composed combinators in reverse order to the way they would be written with ($) or (.). That naturally expresses the idea of the combinators as operations being applied in the given order.
This comes up so often, and is commonly used so many times in a single expression, that Control.Arrow.>>> is far too wordy, and even a two- character operator is awkward.
Surprisingly, until recently the operator (&) was still not used in any of the popular libraries, and its name naturally expresses the idea we are looking for. This operator has now been defined in the lens package. We hereby propose to move it to its natural home for more general use, Data.Function.
As in the lens package, we define the operator as a flipped version of ($), but with slightly higher precedence for better interaction with ($), and with left associativity. This definition has already proven useful and convenient even in the presence of the large and varied corpus of combinators and operators in the lens package. (There it was formerly known as (%), but that clashed with the usual meaning of (%) from Data.Ratio.)
infixl 1 & (&) :: a -> (a -> b) -> b a & f = f a {-# INLINE (&) #-}
Discussion period: 2 weeks
http://hackage.haskell.org/trac/ghc/ticket/7434
Thanks, Yitz
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Hi all, +1 for (&), -1 for (|>). Cheers, Milan
It is a common idiom to write a sequence of composed combinators in reverse order to the way they would be written with ($) or (.). That naturally expresses the idea of the combinators as operations being applied in the given order.
This comes up so often, and is commonly used so many times in a single expression, that Control.Arrow.>>> is far too wordy, and even a two- character operator is awkward.
Surprisingly, until recently the operator (&) was still not used in any of the popular libraries, and its name naturally expresses the idea we are looking for. This operator has now been defined in the lens package. We hereby propose to move it to its natural home for more general use, Data.Function.
As in the lens package, we define the operator as a flipped version of ($), but with slightly higher precedence for better interaction with ($), and with left associativity. This definition has already proven useful and convenient even in the presence of the large and varied corpus of combinators and operators in the lens package. (There it was formerly known as (%), but that clashed with the usual meaning of (%) from Data.Ratio.)
infixl 1 & (&) :: a -> (a -> b) -> b a & f = f a {-# INLINE (&) #-}
Discussion period: 2 weeks
http://hackage.haskell.org/trac/ghc/ticket/7434
Thanks, Yitz
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Tue, Nov 20, 2012 at 11:59 AM, Yitzchak Gale
It is a common idiom to write a sequence of composed combinators in reverse order to the way they would be written with ($) or (.). That naturally expresses the idea of the combinators as operations being applied in the given order.
I think the bar should be pretty high before we add a third way to write function application to base. How common is this? Common among whom? Why can't the existing idioms of (.) and ($) work just as well? My own opinion is that this will only serve to confuse new people.
Discussion period: 2 weeks
I am currently opposed.
--
Dave Menendez

Admittedly the (flip ($)) operator is much more basic than lenses and
deserves some scrutiny. Chaining many operations "foo $ bar $ baz bag"
reads "the wrong way"; one has to maintain a mental stack of the operations
to figure out what's going on. OTOH, "bag & baz & bar & foo" reads "the
right way". "Take bag, and then apply baz, and then apply bar, and then
apply foo". Sort of like a UNIX pipeline.
I think (&) is worthy of inclusion in Prelude :-) That aside, in the
context of lenses, (record & foo .~ value) is even more essential than the
above general case. This is also the order that Structured/OO-style code is
written (record.foo = value, in C/Ruby/Python/C++/Java/...) - for a good
reason. The short of it is that IMVHO, it does meet the high bar of a
universal single-character operator. I certainly use it a lot in my code.
As a side note, it would have been awesome if we could have used (:)
("record : field :~ value", and the truly elegant state-monad "field :=
value"). Alas, "everybody wants the (:)" - in Haskell it is used for cons,
and any operator starting with ":" must be a type operator, so this is out
of the question.
(&) seems like the best of the viable options, given (%) was snatched by
Data.Ratio. I still prefer (%) better, but I can live with (&).
Oren.
On Wed, Nov 21, 2012 at 4:55 PM, David Menendez
On Tue, Nov 20, 2012 at 11:59 AM, Yitzchak Gale
wrote: It is a common idiom to write a sequence of composed combinators in reverse order to the way they would be written with ($) or (.). That naturally expresses the idea of the combinators as operations being applied in the given order.
I think the bar should be pretty high before we add a third way to write function application to base. How common is this? Common among whom? Why can't the existing idioms of (.) and ($) work just as well?
My own opinion is that this will only serve to confuse new people.
Discussion period: 2 weeks
I am currently opposed.
-- Dave Menendez
http://www.eyrie.org/~zednenem/ _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Wed, 21 Nov 2012, Oren Ben-Kiki wrote:
I think (&) is worthy of inclusion in Prelude :-)
The proposal was to include it in Data.Function, not Prelude. And I think this is good and lowers the barrier for addition. People only have to think about it only if they explicitly import it from Data.Function.

Sure, I didn't mean that we should push it to Prelude - just that it was "worthy" of it (in the context of the bar David mentioned). Putting it in Data.Function is much more practical at this point in time. Oren. On Wed, Nov 21, 2012 at 5:32 PM, Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Wed, 21 Nov 2012, Oren Ben-Kiki wrote:
I think (&) is worthy of inclusion in Prelude :-)
The proposal was to include it in Data.Function, not Prelude. And I think this is good and lowers the barrier for addition. People only have to think about it only if they explicitly import it from Data.Function.

As others have mentioned, diagrams already uses (#) for reverse application (but with a high precedence instead of low). We also already use (&) for something else -- namely constructing literal points and vectors, e.g. (1 & 2) or (3 & 0 & 4). But these are fairly minor considerations. I'm still in favor of the proposal (especially given that (&) will not be exported by the Prelude). So, +1 from me. -Brent

Brent Yorgey
writes:
As others have mentioned, diagrams already uses (#) for reverse application (but with a high precedence instead of low). We also already use (&) for something else -- namely constructing literal points and vectors, e.g. (1 & 2) or (3 & 0 & 4). But these are fairly minor considerations. I'm still in favor of the proposal (especially given that (&) will not be exported by the Prelude).
If we get & in Data.Function, might we also want to add <&> to Control.Applicative as a flipped fmap? -- John Wiegley FP Complete Haskell tools, training and consulting http://fpcomplete.com johnw on #haskell/irc.freenode.net

Hi, -1 for adding such an operator at all. Languages benefit from consistnet idiom; too many ways of doing the same thing are not always good. If such an operator is added, then -1 for & (I don’t see any useful hint for that) and +1 for |> (looks self-explanatory, prior art). Greetings, Joachim -- Joachim "nomeata" Breitner mail@joachim-breitner.de | nomeata@debian.org | GPG: 0x4743206C xmpp: nomeata@joachim-breitner.de | http://www.joachim-breitner.de/

On Thursday, November 22, 2012, Joachim Breitner wrote:
Hi,
-1 for adding such an operator at all. Languages benefit from consistnet idiom; too many ways of doing the same thing are not always good.
-1 for me for the same reason. After looking at examples in this thread I don't find that the loss in readability is worth it. Also for beginners I don't want to explain yet another way to write function application.

+1 for &; I think it reads really well, and I think it's silly to go for consistency with C (especially when we can't have | anyway). I know some beginners struggle with function application ordering in Haskell because they find it unnatural and you have to backtrack more when reading such code. I'm sure those people would like (&). -1 for |>; there are reasons I rarely use >>> for flip (.), and I wouldn't use |> either.

On 22 November 2012 11:46, Johan Tibell
On Thursday, November 22, 2012, Joachim Breitner wrote:
Hi,
-1 for adding such an operator at all. Languages benefit from consistnet idiom; too many ways of doing the same thing are not always good.
-1 for me for the same reason. After looking at examples in this thread I don't find that the loss in readability is worth it.
Also for beginners I don't want to explain yet another way to write function application.
-1 for more or less the same reason. This is one of those little things which seems innocuous, but I don't trust people enough to not use it to write horrible backward messes that I'd rather not have to read. At one point, the code in PLEAC for Haskell redefined (.) to be flipped application, and the result was... let's say highly unidiomatic. Even without the travesty of stealing composition for an operation which doesn't generalise it, I'd rather not encourage this sort of thing.

Cale Gibbard
On 22 November 2012 11:46, Johan Tibell
wrote: On Thursday, November 22, 2012, Joachim Breitner wrote:
Hi,
-1 for adding such an operator at all. Languages benefit from consistnet idiom; too many ways of doing the same thing are not always good.
-1 for me for the same reason. After looking at examples in this thread I don't find that the loss in readability is worth it.
Also for beginners I don't want to explain yet another way to write function application.
-1 for more or less the same reason.
And -1 from me for the same reason. The more ways there are of writing the same thing, the more effort it takes to read them. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

Johan Tibell wrote:
On Thursday, November 22, 2012, Joachim Breitner wrote:
Hi,
-1 for adding such an operator at all. Languages benefit from consistnet idiom; too many ways of doing the same thing are not always good.
-1 for me for the same reason. After looking at examples in this thread I don't find that the loss in readability is worth it.
Also for beginners I don't want to explain yet another way to write function application.
-1 from me as well. The (#) operator is quite natural and useful in the diagrams library, but the thing is that even though it is *implemented* as function application, it is *semantically* not a function application. It only serves to furnish shapes and diagrams with additional properties; it's type is very restricted, so to speak. Since the use cases mentioned (diagrams, lenses) are very similar, perhaps there is a general combinator (&) that does the job for both, but which has a much more restricted type and is not equivalent to reverse function application. Maybe an abstraction like "Settable functors", "Thingomorphisms with properties" or something like that. Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

On Fri, Nov 23, 2012 at 6:34 AM, Heinrich Apfelmus < apfelmus@quantentunnel.de> wrote:
The (#) operator is quite natural and useful in the diagrams library, but the thing is that even though it is *implemented* as function application, it is *semantically* not a function application. It only serves to furnish shapes and diagrams with additional properties; it's type is very restricted, so to speak.
Since the use cases mentioned (diagrams, lenses) are very similar, perhaps there is a general combinator (&) that does the job for both, but which has a much more restricted type and is not equivalent to reverse function application. Maybe an abstraction like "Settable functors", "Thingomorphisms with properties" or something like that.
In lens and in diagrams the type signature really does have to be a -> (a -> b) -> b, because the type of the underlying object could (and often is) changed. A critical part of lens is support for changing field types:
("Hello","Heinrich") & over both length (5, 8)
there it goes from (String,String) -> (Int,Int). There isn't any usable commonality between the input and output type. Similarly in diagrams you can use it to change it between R2 to R3, or otherwise enrich the target in ways that change its type.

On 20/11/2012 16:59, Yitzchak Gale wrote:
infixl 1 & (&) :: a -> (a -> b) -> b a & f = f a {-# INLINE (&) #-}
Discussion period: 2 weeks
-1 for &, for me it's too unintuitive and different from any other language. I'd be +1 for |> but perhaps that's just because I do a lot of F#. I'd be ok with # too but perhaps MagicHash is an obstacle there. Ganesh

At this point, it appears we've come to an impasse.
If you just run through the rather enormous thread that has erupted and
just counted the votes (&) has a slight lead over not including it -- it is
up 4.2 votes at my last rough count. The other colors of the bikeshed are
all well into the negatives, see the table below.
That said, the libraries process is focused on reaching "broad consensus",
not just counting up and down votes, and it is clear, even just a week in,
with 25 people weighing in that there is not broad consensus on adding such
an operator and we no longer seem to be heading in that direction.
Even though I am in favor of it, I would like to suggest we withdraw this
proposal.
user & |> $. # Edward Kmett 1 -1 -1 -1 Bryan O'Sullivan 1 1 -1 Yitzchak
Gale 1 Dan Burton 1 Johan Tibell -1 -1 -1 -1 Andreas Gal 1 Stephen
Tetley 1 Michael Sloan 1 John Weigley 1 Oren Ben-Kiki 1 Brandon
Allbery 1 Thomas Schiling 0.2 0.1 Gabor Lehel 1 Bas van Dijk 1 Anthony
Cowley 1 Twan Van Laarhoven 1 1 Milan Straka 1 Cale Gibbard -1 -1 -1
-1 David Menendez -1 -1 -1 -1 John Lato -1 -1 -1 -1 Joachim
Breitner -1 1 Dag
Odenhall 1 -1 Heinrich Apfelmus -1 -1 -1 -1 Jon Fairbairn -1 -1 -1
-1 Ganesh
Sittampalam -1 1 1 Total 4.2 -2.9 -7 -4
(My apologies if I mischaracterized or misreported any of your stated
opinions, I was just building a list for my own purposes.)
-Edward
On Sat, Nov 24, 2012 at 4:38 AM, Ganesh Sittampalam
On 20/11/2012 16:59, Yitzchak Gale wrote:
infixl 1 & (&) :: a -> (a -> b) -> b a & f = f a {-# INLINE (&) #-}
Discussion period: 2 weeks
-1 for &, for me it's too unintuitive and different from any other language.
I'd be +1 for |> but perhaps that's just because I do a lot of F#. I'd be ok with # too but perhaps MagicHash is an obstacle there.
Ganesh
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On 25 November 2012 19:47, Edward Kmett
Andreas Gal
You meant Andreas Abel. Andreas Gal is the tracing JIT researcher now at Mozilla. I agree that there is no broad consensus. If the authors of the packages using such an operator feel the need to unify notation, they can create a new package. If it gets adopted later on there can be another proposal, but at the moment the wider Haskell community isn't ready for it yet.

Hah, so I did. :)
Sent from my iPhone
On Nov 25, 2012, at 3:15 PM, Thomas Schilling
On 25 November 2012 19:47, Edward Kmett
wrote: Andreas Gal
You meant Andreas Abel. Andreas Gal is the tracing JIT researcher now at Mozilla.
I agree that there is no broad consensus. If the authors of the packages using such an operator feel the need to unify notation, they can create a new package. If it gets adopted later on there can be another proposal, but at the moment the wider Haskell community isn't ready for it yet.

Agreed. There does seem to be quite a bit
of support, but it's not a clear enough
consensus to add the operator to
Data.Function at this time. Therefore, the
proposal is withdrawn.
Thanks to everyone who participated in the
discussion, and special thanks to Edward for
the nice summary.
-Yitz
On Sun, Nov 25, 2012 at 9:47 PM, Edward Kmett
At this point, it appears we've come to an impasse.
If you just run through the rather enormous thread that has erupted and just counted the votes (&) has a slight lead over not including it -- it is up 4.2 votes at my last rough count. The other colors of the bikeshed are all well into the negatives, see the table below.
That said, the libraries process is focused on reaching "broad consensus", not just counting up and down votes, and it is clear, even just a week in, with 25 people weighing in that there is not broad consensus on adding such an operator and we no longer seem to be heading in that direction.
Even though I am in favor of it, I would like to suggest we withdraw this proposal.
user & |> $. # Edward Kmett 1 -1 -1 -1 Bryan O'Sullivan 1 1 -1 Yitzchak Gale 1 Dan Burton 1 Johan Tibell -1 -1 -1 -1 Andreas Gal 1 Stephen Tetley 1 Michael Sloan 1 John Weigley 1 Oren Ben-Kiki 1 Brandon Allbery 1 Thomas Schiling 0.2 0.1 Gabor Lehel 1 Bas van Dijk 1 Anthony Cowley 1 Twan Van Laarhoven 1 1 Milan Straka 1 Cale Gibbard -1 -1 -1 -1 David Menendez -1 -1 -1 -1 John Lato -1 -1 -1 -1 Joachim Breitner -1 1 Dag Odenhall 1 -1 Heinrich Apfelmus -1 -1 -1 -1 Jon Fairbairn -1 -1 -1 -1 Ganesh Sittampalam -1 1 1 Total 4.2 -2.9 -7 -4
(My apologies if I mischaracterized or misreported any of your stated opinions, I was just building a list for my own purposes.)
-Edward
On Sat, Nov 24, 2012 at 4:38 AM, Ganesh Sittampalam
wrote: On 20/11/2012 16:59, Yitzchak Gale wrote:
infixl 1 & (&) :: a -> (a -> b) -> b a & f = f a {-# INLINE (&) #-}
Discussion period: 2 weeks
-1 for &, for me it's too unintuitive and different from any other language.
I'd be +1 for |> but perhaps that's just because I do a lot of F#. I'd be ok with # too but perhaps MagicHash is an obstacle there.
Ganesh
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
participants (29)
-
Andreas Abel
-
Anthony Cowley
-
Bas van Dijk
-
Brandon Allbery
-
Brent Yorgey
-
Bryan O'Sullivan
-
Cale Gibbard
-
dag.odenhall@gmail.com
-
Dan Burton
-
David Menendez
-
Edward A Kmett
-
Edward Kmett
-
Ganesh Sittampalam
-
Gábor Lehel
-
Heinrich Apfelmus
-
Henning Thielemann
-
Ian Lynagh
-
Ivan Lazar Miljenovic
-
Joachim Breitner
-
Johan Tibell
-
John Wiegley
-
Jon Fairbairn
-
Michael Sloan
-
Milan Straka
-
Oren Ben-Kiki
-
Stephen Tetley
-
Thomas Schilling
-
Twan van Laarhoven
-
Yitzchak Gale