[Haskell-cafe] Another Space Leak

Dominic Steinitz dominic.steinitz at blueyonder.co.uk
Sun Feb 4 13:03:19 EST 2007


Many thanks for the help on the original space leak which is now fixed -see 
the function pad below and test runs in small constant space. However, that 
has merely revealed the next space leak.

The problem appears to be

blockWord8sIn512 :: [Word8] -> [[Word8]]
blockWord8sIn512 =
   unfoldr g
   where
      g [] = Nothing
      g xs = Just (splitAt 64 xs)

or its alternative

bws :: [Word8] -> [[Word8]]
bws [] = []
bws xs = ys:(bws zs)
           where
             (ys,zs) = splitAt 64 xs

But I can't see why a big expression is being built up. Shouldn't these 
produce elements of the list when they are required and they are then 
consumed by foldl'?

Dominic.

module Main(main) where

import Data.Word
import Data.Bits
import Data.List

ss = [0x67452301, 0xefcdab89, 0x98badcfe, 0x10325476, 0xc3d2e1f0]

pad = pad' 0
  where pad' l [] = [0x80] ++ ps
          where pl = (64-(l+9)) `mod` 64
                ps = replicate pl 0x00
        pad' l (x:xs) = x : (pad' $! l+1) xs -- otherwise (l+1) it will be 
deferred until replicate

blockWord8sIn512 :: [Word8] -> [[Word8]]
blockWord8sIn512 =
   unfoldr g
   where
      g [] = Nothing
      g xs = Just (splitAt 64 xs)

bws :: [Word8] -> [[Word8]]
bws [] = []
bws xs = ys:(bws zs)
           where
             (ys,zs) = splitAt 64 xs

test :: Int -> Word8
test n = foldl' xor 0x55 (pad (replicate n 0x55))

test1 :: Int -> [Word8]
test1 n = foldl' (zipWith xor) [0x01..0x40] (blockWord8sIn512 (pad (replicate 
n 0x55)))

test2 :: Int -> [Word8]
test2 n = foldl' (zipWith xor) [0x01..0x40] (bws (pad (replicate n 0x55)))

main = 
   do putStrLn (show (test  1000000))
      putStrLn (show (test1 1000000))
      putStrLn (show (test2 1000000))



More information about the Haskell-Cafe mailing list