[Haskell-beginners] numerical types, the $ operator

Zachary Turner divisortheory at gmail.com
Mon Mar 30 00:37:57 EDT 2009


On Sun, Mar 29, 2009 at 6:47 PM, Daniel Fischer <daniel.is.fischer at web.de>wrote:

> Am Montag 30 März 2009 00:53:15 schrieb Zachary Turner:
> > On Sat, Mar 28, 2009 at 4:53 PM, John Dorsey <haskell at colquitt.org>
> wrote:
> > > > > How would an experienced guy write this without parentheses?
> > > >
> > > > I'm fairly certain it's impossible to write it without using
> > > > parentheses.  I would probably just write
> > > >
> > > >   x - fromInteger (floor x)
> > >
> > > Never impossible!
> > >
> > > flip subtract x . fromInteger $ floor x
> > > case floor x of y -> x - fromInteger y
> > > let y = floor x in x - fromInteger y
> >
> > I'm a bit of a beginner myself, but I came up with this:
> >
> > let (|>) x f = f x
> > let mapping f x = (x, f x)
> > let mapping2 f (x,y) = (x, f y)
> > let frac x = x |> mapping id |> mapping2 floor |> mapping2 fromInteger |>
> > uncurry (-)
>
> But John didn't use
>
> (-) x . fromInteger . floor $ x
>
> because it has parentheses, like your version :)
> That is easily fixed, though, and since almost everything you ever need has
> already been coded by somebody else, let's use a library instead of (|>),
> mapping and mapping2:
>
> import Control.Arrow
>
> frac :: RealFrac a => a -> a
> frac = fromInteger . floor &&& id >>> uncurry subtract
>
> pointfree and without parentheses.
>
> f &&& g = \x -> (f x, g x)
> (for functions, it's more generally applicable to arrows), so your
> 'mapping f' is 'id &&& f', your 'mapping2 f' would be 'second f', also
> defined in
> Control.Arrow.
> You see that these functions are so generally useful that they already are
> in a
> library :)
>
> (>>>) is forward composition (for functions, it's defined in
> Control.Category for
> more general settings), useful and readable. You can't use it to inject the
> value
> into the pipeline, though.
> But often that is not necessary and pointfree style is equally readable
> (sometimes even more readable).
>
> >
> > A little extreme, but I still like that it illustrates the |> operator,
> > which is actually really useful, I borrowed the concept from F#.  I
> > redefined it because I actually have no idea if F# has a similar
> operator.
> > Does it? It's obviously still easier to read the original parenthesized
> > version, but sometimes the |> operator really makes things very readable,
> > because it emphasizes the fact that you start with a single value, and
> send
> > that value through a series of transformations one after the other, and
> you
> > can read each transformation in the order that it happens, rather than
> with
> > function composition where you have to scan to the end first to see which
> > operation gets applied first.
>

The &&& operator is pretty sweet, thanks for pointing it out.  That's pretty
much what I was trying to come up with the mapping and mapping2, but it's
more general and hence more useful.

The "pipelining" operator I defined should definitely be used with care.
For example, it requires the pipelined argument to be the last argument,
which is not always the case.  And I've also found that with it I tend to
think about the problem less, and write less efficient code as a result.
For example given a list of integers, an easy and very readable way to
remove all multiples of 2 from a list, and then double the remaining items
could be like this:

let doit x = x |> filter (\y -> y `mod` 2 == 0) |> map (* 2)

as opposed to the more efficient

doit [] = []
doit (x:xs) | (x `mod` 2 == 0) = doit xs
doit (x:xs) = (2 * x) : doit xs

since the list is walked twice.  (I'm betting someone will respond with a
cool one-liner here involving function composition or something else that I
can't think of yet :)
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/beginners/attachments/20090329/f3f6a85e/attachment.htm


More information about the Beginners mailing list