Crash in Data.ByteString.Lazy.hPut

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.

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.

jamie.love:
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.'
Can you repeat this with binary 0.4.1 please? (And yes, this is a fine place to report bugs).

jamie.love:
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.'
Oh, hehe. \x -> x `mod` 256 doesn't work if x :: Word8 That's your bug :) -- Don

Ah, of course. Thanks. I removed the hPut and it runs smoothly. I had forgotten that haskell chooses the types dynamically. Shouldn't haskell pick up that there is no 'mod' for Word8? I mean, shouldn't I get a nicer error message? Don Stewart wrote:
jamie.love:
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.'
Oh, hehe. \x -> x `mod` 256 doesn't work if x :: Word8 That's your bug :)
-- Don
------------------------------------------------------------
This message has been scanned for viruses and dangerous content by MailScanner and is believed to be clean.
-- 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.

jamie.love:
Ah, of course.
Thanks. I removed the hPut and it runs smoothly. I had forgotten that haskell chooses the types dynamically.
Shouldn't haskell pick up that there is no 'mod' for Word8? I mean, shouldn't I get a nicer error message?
Well, it inferred Word8 for your generated values, so 256 overflowed to 0. Stating the expected type here would prevent that. (And is why mandatory top level declarations are good -- they can prevent bugs caused by an unexpected type being inferred).

Oh, I see I wasn't thinking through the code (and I'm still in the honeymoon phase with Haskell, thinking it can do no wrong). Don Stewart wrote:
jamie.love:
Ah, of course.
Thanks. I removed the hPut and it runs smoothly. I had forgotten that haskell chooses the types dynamically.
Shouldn't haskell pick up that there is no 'mod' for Word8? I mean, shouldn't I get a nicer error message?
Well, it inferred Word8 for your generated values, so 256 overflowed to 0. Stating the expected type here would prevent that. (And is why mandatory top level declarations are good -- they can prevent bugs caused by an unexpected type being inferred).
------------------------------------------------------------
This message has been scanned for viruses and dangerous content by MailScanner and is believed to be clean.
-- 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.

Just to clarify, I know it was my mistake, and so I'm not blaming Haskell or Ghc. The first few times you realise the compiler isn't a magic wand that stops you being silly are the hardest. Jamie Love wrote:
Oh, I see
I wasn't thinking through the code (and I'm still in the honeymoon phase with Haskell, thinking it can do no wrong).
Don Stewart wrote:
jamie.love:
Ah, of course.
Thanks. I removed the hPut and it runs smoothly. I had forgotten that haskell chooses the types dynamically.
Shouldn't haskell pick up that there is no 'mod' for Word8? I mean, shouldn't I get a nicer error message?
Well, it inferred Word8 for your generated values, so 256 overflowed to 0. Stating the expected type here would prevent that. (And is why mandatory top level declarations are good -- they can prevent bugs caused by an unexpected type being inferred).
------------------------------------------------------------ This message has been scanned for viruses and dangerous content by MailScanner and is believed to be clean.

On Jan 28, 2008, at 17:33 , Jamie Love wrote:
Shouldn't haskell pick up that there is no 'mod' for Word8? I mean, shouldn't I get a nicer error message?
Hm? mod works fine for Word8, unless you specify a multiple of the type's bound. I think it's still hard for compilers to catch that for you (very few compilers I know of will catch even an explicit divide-by-zero at compile time). -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

Brandon S. Allbery KF8NH wrote:
On Jan 28, 2008, at 17:33 , Jamie Love wrote:
Shouldn't haskell pick up that there is no 'mod' for Word8? I mean, shouldn't I get a nicer error message?
Hm? mod works fine for Word8, unless you specify a multiple of the type's bound. I think it's still hard for compilers to catch that for you
Finding out if a variable will have a value of 0 is undecidable at compile time, isn't it? //Stephan -- Früher hieß es ja: Ich denke, also bin ich. Heute weiß man: Es geht auch so. - Dieter Nuhr
participants (4)
-
Brandon S. Allbery KF8NH
-
Don Stewart
-
Jamie Love
-
Stephan Friedrichs