[Haskell-cafe] Crash in Data.ByteString.Lazy.hPut
Jamie Love
jamie.love at aviarc.com.au
Mon Jan 28 17:23:12 EST 2008
I should point out that this is on GHC 6.8.2 compiled from source on a
Mac powerpc.
Jamie Love wrote:
> Hi there,
>
> Not sure where to raise bugs in hackage libraries, so I'm posting
> here. If there is a better place, please let me know.
>
> The following code crashes with a divide by zero error when using the
> package 'binary-0.4.'
>
>
> module Main where
>
> import IO
> import Data.Binary
> import Data.Binary.Put
> import qualified Data.ByteString.Lazy as B
>
> simpleImage = take tot (map (\x -> x `mod` 256) [1..])
> where tot = 640 * 480
>
>
> main = do
> output <- openFile "test.tmp" WriteMode
> B.hPut output $ runPut $ mapM_ putWord8 simpleImage
>
>
>
>
>
--
Jamie Love
Senior Consultant
Aviarc Australia
Mobile: +61 400 548 048
------------------------------------------------------------
This message has been scanned for viruses and dangerous content
by MailScanner and is believed to be clean.
More information about the Haskell-Cafe
mailing list