Proposal: Add (&) to Data.Function

Bas van Dijk v.dijk.bas at gmail.com
Tue Nov 20 22:18:04 CET 2012


+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 <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
> http://www.haskell.org/mailman/listinfo/libraries
>



More information about the Libraries mailing list