[Haskell-beginners] Using the Get monad lazily

MAN elviotoccalino at gmail.com
Fri Jul 16 23:49:47 EDT 2010


I'm sorry if this matter has already been discussed, but I'm going nuts
here. Attached is the code for a small program, an ubber simplification
of something I'm trying to do which would enormously gain from lazy
serialization. The code, however, is broken... It runs, and does the
job, but it does so strictly.
It's more a self imposed exercise than anything else, but I'd really
like to understand what's going on with this snippet, why it didn't
worked as I thought it would.

The objective is to read a binary file, checking to see if a particular
bit (bit zero) is set or not.
My idea was to use the Get monad to get one Word8 at a time, do the
check, and cons the True/False result of that check with a "results
list".
The reason for this results list lies in that I'll later read through
this results, and it would be great if I could do so lazily, aiming for
the producer-consumer pattern. The 
As you'll see, my code fails to produce the results list lazily. At
first I thought that the list would only escape the Get monad if fully
evaluated. So I added the 'testIn' function, which offers only the head
of that list, running inside the Get monad... but even this triggers the
full traversal of the file.

I've attempted several combinations of "let", trying to induce laziness,
but always to no avail. I am at a loss. Any help is most welcomed.


--- BEGIN CODE ---

import Data.Bits (testBit)
import Data.Word
import System.IO (openBinaryFile, withBinaryFile, IOMode(..))
import Data.Binary.Get
import qualified Data.ByteString.Lazy as B
import Control.Monad (liftM, liftM2)

-- | Check the LSB in a word against the symbol.
check :: Bool -> Word8 -> Bool
{-# INLINE check #-}
check s w = testBit w 0 == s

-- Algorithm to implement:
--   - get a word from lazy buffer.
--   - check whether 'least/most' significant byte is as expected.
--   - cons result in output buffer.
-- The result contains a stream of "checks".

checker :: Bool -> Get Bool
checker s = getWord8 >>= return . check s

go :: Symbol -> Get [Bool]
go s = do
  eof <- isEmpty
  case eof of True  -> return []
              False -> let res = liftM2 (:) (checker s) (go s) in res

--

-- Work inside the Get monad.

-- | return the head of the results... this shouldn't take long!
testIn :: Get Bool
testIn = liftM (head) (go True)

--
--

-- gimmi only the head of the results list
runnerIn :: IO Bool
runnerIn = openBinaryFile testFile ReadMode >>= B.hGetContents >>=
return . runGet testIn

test = openBinaryFile testFile ReadMode >>= B.hGetContents >>= \b -> do
  let rs = runGet (go True) b
  return rs



More information about the Beginners mailing list