無限リストを作成出来ない例(foldl)

http://en.wikibooks.org/wiki/Haskell/List_processing
replicate は第 2 引数の値を要素とする長さ第 1 引数のリストを作る関数

ghci> replicate 3 "abc"
["abc","abc","abc"]

echoesR は foldr を使用した要素の数を連続させる関数

ghci> echoesR = foldr (\x xs -> (replicate x x) ++ xs) []
ghci> echoesR [7,2,4,5] 
[7,7,7,7,7,7,7,2,2,4,4,4,4,5,5,5,5,5]
ghci> echoesR [1..3]
[1,2,2,3,3,3]

echoesL は foldl を使用した要素の数を連続させる関数

ghci> let echoesL = foldl (\xs x -> xs ++ (replicate x x)) []
ghci> echoesL [1..3]                                        
[1,2,2,3,3,3]

foldr を使用した echoesR は無限リストを作成出来るが、foldl を使用したechoesL は本当に無限リストを完成させてから take 10 を実行しようとする。

ghci> take 10 $ echoesR [1..] 
[1,2,2,3,3,3,4,4,4,4]
ghci> take 10 $ echoesL [1..] 

Prelude:Reducing lists (folds)

----------------------------------------------
--      foldr/build/augment
----------------------------------------------
  
\begin{code}
-- | 'foldr', applied to a binary operator, a starting value (typically
-- the right-identity of the operator), and a list, reduces the list
-- using the binary operator, from right to left:
--
-- > foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...)

foldr            :: (a -> b -> b) -> b -> [a] -> b
-- foldr _ z []     =  z
-- foldr f z (x:xs) =  f x (foldr f z xs)
{-# INLINE [0] foldr #-}
-- Inline only in the final stage, after the foldr/cons rule has had a chance
foldr k z xs = go xs
             where
               go []     = z
               go (y:ys) = y `k` go ys
-- | 'foldl', applied to a binary operator, a starting value (typically
-- the left-identity of the operator), and a list, reduces the list
-- using the binary operator, from left to right:
--
-- > foldl f z [x1, x2, ..., xn] == (...((z `f` x1) `f` x2) `f`...) `f` xn
--
-- The list must be finite.

-- We write foldl as a non-recursive thing, so that it
-- can be inlined, and then (often) strictness-analysed,
-- and hence the classic space leak on foldl (+) 0 xs

foldl        :: (a -> b -> a) -> a -> [b] -> a
foldl f z0 xs0 = lgo z0 xs0
             where
                lgo z []     =  z
                lgo z (x:xs) = lgo (f z x) xs

展開される様子を見てみる。

import Debug.Trace

echoesL = testFoldl (\xs x -> xs ++ (replicate x x)) []
echoesR = testFoldr (\x xs -> (replicate x x) ++ xs) []

testFoldl f z0 xs0 = lgo z0 xs0
             where
                lgo z []     = trace(show z) z
                lgo z (x:xs) = trace("lgo (f "++show z++" "++show x++") "++show xs)(lgo (f z x) xs)

testFoldr k z xs = go xs
             where
               go []     =  trace(show z) z
               go (y:ys) = trace(show y++" `k` go "++show ys)(y `k` go ys)

foldlを使用したものは全部リストを作成している。

*Main>  take 10 $ echoesR [1..10]
1 `k` go [2,3,4,5,6,7,8,9,10]
2 `k` go [3,4,5,6,7,8,9,10]
3 `k` go [4,5,6,7,8,9,10]
4 `k` go [5,6,7,8,9,10]
[1,2,2,3,3,3,4,4,4,4]

*Main>  take 10 $ echoesL [1..10]
lgo (f [] 1) [2,3,4,5,6,7,8,9,10]
lgo (f [1] 2) [3,4,5,6,7,8,9,10]
lgo (f [1,2,2] 3) [4,5,6,7,8,9,10]
lgo (f [1,2,2,3,3,3] 4) [5,6,7,8,9,10]
lgo (f [1,2,2,3,3,3,4,4,4,4] 5) [6,7,8,9,10]
lgo (f [1,2,2,3,3,3,4,4,4,4,5,5,5,5,5] 6) [7,8,9,10]
lgo (f [1,2,2,3,3,3,4,4,4,4,5,5,5,5,5,6,6,6,6,6,6] 7) [8,9,10]
lgo (f [1,2,2,3,3,3,4,4,4,4,5,5,5,5,5,6,6,6,6,6,6,7,7,7,7,7,7,7] 8) [9,10]
lgo (f [1,2,2,3,3,3,4,4,4,4,5,5,5,5,5,6,6,6,6,6,6,7,7,7,7,7,7,7,8,8,8,8,8,8,8,8] 9) [10]
lgo (f [1,2,2,3,3,3,4,4,4,4,5,5,5,5,5,6,6,6,6,6,6,7,7,7,7,7,7,7,8,8,8,8,8,8,8,8,9,9,9,9,9,9,9,9,9] 10) []
[1,2,2,3,3,3,4,4,4,4,5,5,5,5,5,6,6,6,6,6,6,7,7,7,7,7,7,7,8,8,8,8,8,8,8,8,9,9,9,9,9,9,9,9,9,10,10,10,10,10,10,10,10,10,10]
[1,2,2,3,3,3,4,4,4,4]