
On Wed, Jun 17, 2009 at 7:30 PM, GüŸnther Schmidt
Hi all,
you have come up with so many solutions it's embarrassing to admit that I didn't come up with even one.
I have the similarly difficulties, but I found to understand some of these answers, equational reasoning is a very useful tool, I have prepared a blog post for how I worked out some of these answers, here is the draft of it, I hope it can help you too. Oh, if it doesn't help you at all, please let know why :-) lee ==== Understanding Functions Which Use 'instance Monad []' by Equational Reasoning GüŸnther Schmidt asked in Haskell-Cafe how to get a stream like this: ["a", ... , "z", "aa", ... , "az", "ba", ... , "bz", ... ] and people in Haskell-Cafe offer some interesting answer for this question. On the one hand, these answers show the power of Haskell and GHC base libraries, but on the other hand, understanding them is a challenge for Haskell newbie like me. But I found to understand these answers, equational reasoning is very helpful, here is why I think so. Answer 1 (by Matthew Brecknell): concat $ tail $ iterate (map (:) ['a' .. 'z'] <*>) [[]] Well, how does this expression do what we want? concat, tail, iterate, map, are easy, looks like the magic is in (<*>). What's this operator mean? (<*>) comes from class Applicative of Control.Applicative, class Functor f => Applicative f where -- | Lift a value. pure :: a -> f a -- | Sequential application. (<*>) :: f (a -> b) -> f a -> f b and 'instance Applicative []' is instance Applicative [] where pure = return (<*>) = ap ap comes from Control.Monad ap :: (Monad m) => m (a -> b) -> m a -> m b ap = liftM2 id liftM2 :: (Monad m) => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r liftM2 f m1 m2 = do { x1 <- m1; x2 <- m2; return (f x1 x2) } so the key to understand (<*>) is understanding the meaning of liftM2. liftM2 uses, hum, do-notation, so by Haskell 98 report, this can be translated to liftM2 f m1 m2 (1.0) = m1 >>= \x1 -> m2 >>= \x2 -> return (f x1 x2) When it is applied to list (you can convince yourself of this by type inference), wee need 'instance Monad []' instance Monad [] where m >>= k = foldr ((++) . k) [] m m >> k = foldr ((++) . (\ _ -> k)) [] m return x = [x] fail _ = [] so liftM2 f m1 m2 = m1 >>= \x1 -> m2 >>= \x2 -> return (f x1 x2) let f1 = \x1 -> m2 >>= \x2 -> return (f x1 x2) f2 = \x2 -> return (f x1 x2) we can write m1 >>= f1 = foldr ((++) . f1) [] m1 m2 >>= f2 = foldr ((++) . f2) [] m2 Now we can see for list m1, m2, how does 'liftM2 f m1 m2' work z1 = [] foreach x1 in (reverse m1); do -- foldr ((++) . f1) [] m1 z2 = [] foreach x2 in (reverse m2); do -- foldr ((++) . f2) [] m2 z2 = [f x1 x2] ++ z2 done z1 = z2 ++ z1 done Now we are ready to see how to apply (<*>): map (:) ['a' .. 'z'] <*> [[]] = (map (:) ['a' .. 'z']) <*> [[]] = [('a':), ..., ('z':)] <*> [[]] -- misuse of [...] notation = ap [('a':), ..., ('z':)] [[]] = liftM2 id [('a':), ..., ('z':)] [[]] = [('a':), ..., ('z':)] >>= \x1 -> [[]] >>= \x2 -> return (id x1 x2) Here x1 bind to ('z':), ..., ('a':) in turn, x2 always bind to [], and noticed that return (id ('z':) []) -- f = id; x1 = ('a':); x2 = [] = return (('z':) []) = return ((:) 'z' []) = return "z" = ["z"] we have map (:) ['a', .., 'z'] <*> [[]] = liftM2 id [('a':), ..., ('z':)] [[]] = ["a", ..., "z"] (If you can't follow the this, work through the definition of foldr step by step will be very helpful.) map (:) ['a', .., 'z'] <*> (map (:) ['a', .., 'z'] <*> [[]]) = map (:) ['a', .., 'z'] <*> ["a", .., "z"] = liftM2 id [('a':), ..., ('z':)] ["a", ..., "z"] = ["aa", ..., "az", "ba", ..., "bz", ..., "za", ..., "zz"] Now it's easy to know what we get from iterate (map (:) ['a' .. 'z'] <*>) [[]] = [[], f [[]], f (f [[]]), ...] -- f = map (:) ['a' .. 'z'] <*> so concat $ tail $ iterate (map (:) ['a' .. 'z'] <*>) [[]] is exactly what we want. Understanding Haskell codes by equational reasoning could be a very tedious process, but it's also a very helpful and instructive process for the beginners, because it make you think slowly, check the computation process step by step, just like the compiler does. And in my opinion, this is exactly what a debugger does. Answer 2 (by Reid Barton): concatMap (\n -> replicateM n ['a'..'z']) [1..] In this solution, the hardest part is replicatM, which come from Control.Monad replicateM :: (Monad m) => Int -> m a -> m [a] replicateM n x = sequence (replicate n x) sequence :: Monad m => [m a] -> m [a] sequence ms = foldr k (return []) ms where k m m' = do { x <- m; xs <- m'; return (x:xs) } recall the defintion of liftM2: liftM2 :: (Monad m) => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r liftM2 f m1 m2 = do { x1 <- m1; x2 <- m2; return (f x1 x2) } so k in definition of sequence is an application of liftM2, and sequence itself is a normal foldr. Exercise 1: Prove that for n >= 1 replicateM n ['a' .. 'z'] = (iterate (map (:) ['a' .. 'z'] <*>) [[]]) !! n or more generally replicateM = \n xs -> (iterate (map (:) xs <*>) [[]]) !! n Answer: replicateM 1 ['a' .. 'z'] = sequence [ ['a' .. 'z'] ] = foldr k (return []) [['a' .. 'z']] = k ['a' .. 'z'] [[]] -- return [] = [[]] = liftM2 (:) ['a' .. 'z'] [[]] = map (:) ['a' .. 'z'] <*> [[]] = ["a", ..., "z"] replicateM 2 ['a' .. 'z'] = sequence [['a' .. 'z'], ['a' .. 'z']] = foldr k [[]] [['a' .. 'z'], ['a' .. 'z']] = k ['a' .. 'z'] (k ['a' .. 'z'] [[]]) = k ['a' .. 'z'] (f [[]]) -- f = map (:) ['a' .. 'z'] <*> = f (f [[]])