[Haskell-beginners] Simplifying code

Daniel Fischer daniel.is.fischer at web.de
Tue Feb 9 18:31:07 EST 2010


Am Dienstag 09 Februar 2010 23:07:55 schrieb Patrick LeBoutillier:
> Daniel,
>
> > Sure. If you don't mind that the mutations come in a different order,
> > one thing that works wonders is "sequence",
> >
> > sequence :: Monad m => [m a] -> m [a]
> >
> > In particular, for m = [], sequence :: [[a]] -> [[a]]. Then, knowing
> > what sequence does, we can write
> >
> > import Control.Monad (sequence)
> >
> > generateAll :: String -> [String]
> > generateAll word = sequence (map f word)
> >     where
> >     f c = case lookup c leat of
> >                Just r  -> [c,r]
> >                Nothing -> [c]
>
> That's very nice!

Thanks. But from a clean-code-higher-level perspective, it's even nicer 
with your

> -- Returns a list of possible characters for c
> mutateLetter :: Char -> [Char]
> mutateLetter c = c : (maybeToList $ lookup c leet)

(here is a point where it would be even nicer if lookup had the type

lookup :: (Eq a, MonadPlus m) => a -> [(a,b)] -> m b
). The performance-junkie in me would want to look at the core to make sure 
the maybeToList is eliminated by the compiler, though.

>
> One question though: In the docs sequence is described as:
>
>   "Evaluate each action in the sequence from left to right, and
> collect the results."
>
> How is one supposed to deduce what the behavior will be for the list
> monad (besides looking at the source)?

Given its polymorphic type

sequence :: Monad m => [m a] -> m [a]

, what can sequence do?

For
sequence []
, there's really only one possibility (not involving undefined/error), so
sequence [] = return []

Okay, that was the trivial part, now what can be done with nonempty lists?
It could ignore the input and return [] in any case, but that wouldn't be 
useful at all, so we can discard that possibility. What could be usefully 
done with

sequence (m1:ms) ?

It has to do something with m1 and something with ms, then combine the 
results to a list of [a], which it returns.
What can it do with m1? Since all that sequence knows about m1 is the type 
(Monad m => m a), it can't do anything but what's provided by that 
constraint. Basically, it can only put it on the left of a (>>=). There's 
on decision to be made, shall it be

sequence (m1:ms) = m1 >>= \x -> something with x and ms

or

something with ms >>= \xs -> (m1 >>= \x -> something with x and xs)
?
And what can it do with the tail of the list, ms? Why, sequence it of 
course.
So it's either

sequence (m1:ms) = m1 >>= \x -> (sequence ms >>= \xs -> return (fun x xs))
{-
sequence (m1:ms) = do
    x <- m1
    xs <- sequence ms
    return (fun x xs)
-}
or

sequence (m1:ms) = sequence ms >>= \xs -> (m1 >>= \x -> return (fun x xs))
{-
sequence (m1:ms) = do
    xs <- sequence ms
    x <- m1
    return (fun x xs)
-}

where

fun :: forall a. a -> [a] -> [a]

Now there's a lot of nonsense you could use for 'fun',

fun x xs = reverse (x:xs)
fun x xs = x:xs ++ [x,x,x]
fun x xs = front ++ x:back where (front,back) = splitAt 17 xs
...
, but the most prominent function of type forall a. a -> [a] -> [a] is the 
only one to be reasonably expected here, so

fun x xs = x : xs

and the only question that remains is in which order things are chained.
That is answered by the docs, left to right, so

sequence [] = return []
sequence (m1:ms) = m1 >>= \x -> sequence ms >>= \xs -> return (x:xs)
{-
sequence (m1:ms) = do
    x <- m1
    xs <- sequence ms
    return (x:xs)

sequence (m1:ms) = m1 >>= \x -> liftM (x :) (sequence ms)
-}
(or equivalent).
Now you need to know how (>>=) is defined for [], namely

ys >>= f = concatMap f ys.

The short answer is, you can't deduce it wihout knowing the Monad instance 
for [], and if you know that well enough to not be confused by "evaluate 
the action" (which takes time), it's fairly straightforward.

>
>
> Patrick



More information about the Beginners mailing list