Proposal: Add (&) to Data.Function

Andreas Abel andreas.abel at ifi.lmu.de
Tue Nov 20 18:30:49 CET 2012


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 <gale at sefer.org
> <mailto:gale at 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 at haskell.org <mailto:Libraries at haskell.org>
>  > http://www.haskell.org/mailman/listinfo/libraries
>  >
>
>
> _______________________________________________
> Libraries mailing list
> Libraries at 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 at ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/



More information about the Libraries mailing list