[Haskell-cafe] message passing style like in Haskell?

Ketil Malde ketil at malde.org
Thu Jun 19 03:35:08 EDT 2008


jinjing <nfjinjing at gmail.com> writes:

> Any way here's the code:

> module Dot where
> import Prelude hiding ( (.) )

> (.) :: a -> (a -> b) -> b
> a . f = f a

> infixl 9 .

Isn't this (roughly?) the same as flip ($)?

As a side note, may I advise you to use another symbol, and leave the
poor dot alone? Overloading it as a module separator is bad enough.
If you have a keyboard that allows greater-than-ascii input, there are
plenty of options: « » ¡ £ ¥ ł € ® ª...

> comparing:

> encode xs = map (\x -> (length x,head x)) (group xs)

> encode xs = xs.group.map token where token x = (x.length, x.head)

To be fair, you could write the first line as:

   encode xs = map token (group xs) where token x = (length x, head x)

I'm not normally too enthusiastic about point-free style, but when the
left and right side of the = both end with the same term, there's
really no need to name them, so:

   encode = map token . group where token x = (length x, head x)
   -- using function composition (.), not your definition

I'm not sure that would work with left-to-right composition.

> I found starting with data and working my way to a solution seems to be
> easier to think with, or maybe it's just me ...

For monadic code, there "default" is >>= and >> which pass things
forward.  There's also =<< which goes the other way - so I guess
opinions differ.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants


More information about the Haskell-Cafe mailing list