[Haskell-beginners] list monad question

Daniel Fischer daniel.is.fischer at web.de
Fri Oct 30 17:03:50 EDT 2009


Am Freitag 30 Oktober 2009 17:27:12 schrieb Stephen Tetley:
> 2009/10/30 Colin Paul Adams <colin at colina.demon.co.uk>:
> > Is there a "Bluffer's guide to Haskell"?
>
> Whilst not a bluffers guide, this one contains several dozen flavours
> of 'obscurantism' (** add your less pejorative term here **)
>
> http://www.willamette.edu/~fruehr/haskell/evolution.html
>
> Methinks your being a bit hard on the pointfree style, but it does
> often diminish an _operation reading_ of the code (you can tell what
> the code does from looking at it). So you either have to trust it, or
> work it out to some expanded form you are happy with.

Completely pointfree style tends to be unreadable except for the selected few.
It's fun to create pointfree versions of your functions, and you learn something by doing 
that, but it should appear rarely in your code.

Completely pointful style tends to be not unreadable, but often cluttered.

The most readable is usually a "partially pointfree" style. Which degree of pointfreeness 
is most readable depends of course on the reader, but there's a range which most can agree 
is good.

Function combinators and pipelines should be partially pointfree:
foo = bar . baz . hum

is better than

foo x = bar (baz (hum x))
or
foo x = bar $ baz $ hum x
or 
foo x = bar . baz . hum $ x

flurb f g = f . g . f

is better than

flurb f g = f (g (f x))

wibble f g = f &&& g >>> g *** f

is better than

wibble f g x = f &&& g >>> g *** f $ x

- but worse than

wibble f g = (f &&& g) >>> (g *** f)

because the latter doesn't require knowledge of the fixities to parse.
However,

wibble f g = (g . f) &&& (f . g)

is at least as good if you want it only for the Category (->). Whether that is better than

wibble f g x = (g (f x), f (g x))

depends on how familiar one is with Control.Arrow.
Writing flurb or wibble completely pointfree is a nightmare :)

Which is best:
a) incrementAll n xs = map (\x -> x+n) xs
b) incrementAll n xs = map (+n) xs
c) incrementAll n    = map (+n)
d) incrementAll      = map . (+)
?
None of them is unreadable - though d) is confusing in the first few weeks of Haskell - 
but b) and c) are clearly better than the other two and c) is a bit better than b) in my 
opinion.

Would you prefer:
a) comb         = flip (.) (flip (.)) (flip (.) (flip (.)))
b) comb         = (. flip (.)) . flip (.)
c) comb f       = (. f) . flip (.)
d) comb f g     = (. g) . f
e) comb f g x   = f x . g
f) comb f g x y = f x (g y)
?
a) is the prettiest, but honestly, I'd rather not meet it in code.
e) is best, f) is okay, d) acceptable.

>
> For what its worth I came up with this bit of golf which saves a few
> keystrokes if you're prepare not to count the helper functions

That's cheating (until they are in a library).

> (I consider them generally useful):

Yup.

>
>
> combinations :: Int -> [a] -> [[a]]
> combinations = foldr (<:>) [[]] `oo` replicate
>
> -- Helpers that I like but are not in the libraries
>
> -- | Applicative 'cons'. Equivalent to - liftA2 (:) - but I like
> having it around.
> -- The monadic version is attributable to a parser library in Clean.
>
> (<:>) :: Applicative f => f a -> f [a] -> f [a]
> (<:>) a b = (:) <$> a <*> b

I'd prefer either
(<:>) = liftA2 (:)
or
a <:> b = (:) <$> a <*> b

>
> -- | Compose an arity 1 function and an arity 2 function.
> --
> -- I call this combinator 'specs' (aka glasses) due to its infix
> -- appearance `oo` - I believe fans of Raymond Smullyan's
> -- 'To Mock a Mockingbird' call it blackbird...
>
> oo :: (c -> d) -> (a -> b -> c) -> a -> b -> d
> oo f g = (f .) . g

This is sometimes also denoted by (.:), it has the pretty definition

(.:) = (.) . (.)

>
> Best wishes
>
> Stephen




More information about the Beginners mailing list