[Haskell-cafe] Lazy ByteString Problem

Dominic Steinitz dominic.steinitz at blueyonder.co.uk
Sun Jan 28 10:01:23 EST 2007


I've been playing around with streams as a way of implementing cryptographic 
functions as they seem to allow you to write code that reads more like the 
specification.

However, I believe (and profiling seems to confirm this) that this builds up a 
large expression which only gets evaluated at the very end. I naively thought 
that using lazy bytestrings would solve the problem but the bytestring 
version just hangs even for small numbers.

So two questions:

1. Are lazy bytestrings the answer but I am using them incorrectly?

2. What techniques are there to force evaluation and throw things that are no 
longer needed away? And can this be done without losing the spirit of the 
specification?

Dominic.

module Main(main) where

import Data.Word
import Data.Bits
import Data.Char
import System.Environment

import qualified Data.ByteString.Lazy as BS

-- ByteString version

cbcl iv ps =
   ciphers where
      ciphers = 0xff `BS.cons` (BS.pack (BS.zipWith (+) feedIns ciphers))
      feedIns = BS.pack (BS.zipWith xor (iv `BS.cons` ciphers) ps)

-- Made up function to illustrate problem

cbc iv ps =
   ciphers where
      ciphers = 0xff:(zipWith (+) feedIns ciphers)
      feedIns = zipWith xor (iv:ciphers) ps

testl n =
   BS.last (cbcl 0x55 ((BS.pack . take n . repeat . fromIntegral . ord) 'a'))

test :: Int -> Word8
test n =
   last (cbc 0x55 ((take n . repeat . fromIntegral . ord) 'a'))

main =
   do progName <- getProgName
      args <- getArgs
      if length args /= 1
         then putStrLn ("Usage: " ++ progName ++ " <length of string>")
         else (putStrLn . show . test . read) (args!!0)



More information about the Haskell-Cafe mailing list