[Haskell-cafe] Crash in Data.ByteString.Lazy.hPut

2008-01-28 Thread 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.'



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.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Crash in Data.ByteString.Lazy.hPut

2008-01-28 Thread Jamie Love

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.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Crash in Data.ByteString.Lazy.hPut

2008-01-28 Thread 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?


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.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Crash in Data.ByteString.Lazy.hPut

2008-01-28 Thread Jamie Love


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.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Crash in Data.ByteString.Lazy.hPut

2008-01-28 Thread Jamie Love



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.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Binary IO of a list of ints

2008-01-24 Thread Jamie Love

Hi there

I have a list of ints, with values between 0 and 255 and I need to print 
them out in little endian form to a file.


I've been using Data.Binary for single values, e.g.

runPut $ do
   put 'B'
   put (0 :: Int32)


I'm wondering how I can go about writing a list of Ints out. My thought 
was to do something like:


foldr (\x B.hPut output (runPut $ do put (x :: Word8))) data

(where output is my file handle), but apart from giving me type errors, 
it seems a rather arduous way to do it.


Could anyone suggest a better way to do this?

--
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.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Binary IO of a list of ints

2008-01-24 Thread Jamie Love



Stephan Walter wrote:

Hi,

On 2008-01-24 12:14, Jamie Love wrote:
  
I have a list of ints, with values between 0 and 255 and I need to print 
them out in little endian form to a file.



How about just using Data.Char.chr ?
  


Essentially because I need to control the byte ordering, and it has to 
be in the current case the opposite to my computer's native ordering 
(the file is a binary file).

Prelude let a = [32..64] :: [Int]
Prelude map Data.Char.chr a
 !\#$%'()*+,-./0123456789:;=?@


--Stephan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


 

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.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Binary IO of a list of ints

2008-01-24 Thread Jamie Love

Thanks Jed,

That works (or at least it's taking ages to error :-) )


Jed Brown wrote:

On 24 Jan 2008, [EMAIL PROTECTED] wrote:

  

Hi there

I have a list of ints, with values between 0 and 255 and I need to print them
out in little endian form to a file.

I've been using Data.Binary for single values, e.g.

runPut $ do
put 'B'
put (0 :: Int32)



This will be big endian by default.  If it needs to be little endian,
use Data.Binary.Put.putWord32le and relatives.  With a list, you could
do something like:

  runPut $ mapM_ (putWord32le . fromIntegral) listOfInts

I hope this helps.

Jed
  


--
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.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Basic binary IO

2008-01-20 Thread Jamie Love

Ah, thanks Don, Brandon,


I looked at this but neglected to read through and understand the 
example enough.


Thanks for the tips, they're a great help.


Don Stewart wrote:

jamie.love:
  
bmpHeader = runPut $ do

put 'B'
put 'M'
put (0  :: Int32)
put (0  :: Int32)
put (14 :: Int32)

Yields the lazy bytestring,

BM\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\SO
  


--
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.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Basic binary IO

2008-01-19 Thread Jamie Love

Hello all,

I'm wondering if anyone has a reference to any binary IO and data 
conversion tutorials.


I'm playing around with generating a BMP file in haskell, and am a 
little stuck on the best way to go about the simple task of creating 
the BMP header. The header is


BM + 4 bytes for file size + 4 bytes reserved + 4 bytes for offset 
where data begins.


I have the basis starting off at:

bmpHeader = B.pack $
   [ 0x42, 0x4D ] ++
   [0 , 0, 0, 0] ++
   [0 , 0, 0, 0] ++
   [14 :: Int32]

(where B is Data.ByteString)

I'm wondering how I can:

1/ convert a 32 bit number (Int32, Char32) to 4 Char8 elements
2/ rotate bits/bytes in a 32 bit Char32 (or Int32) so they are 
explicitly little-endian (I work on a mac powerbook, and it is big-endian)

3/ convert an Integer or Int type to an Int32 type

Any pointers or suggestions would be helpful.

Thanks

--
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.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe