Re: [Haskell-cafe] Help needed for converting IOArray to ByteString

2011-02-17 Thread Henning Thielemann


On Tue, 8 Feb 2011, C K Kashyap wrote:


I need to convert IOArray to bytestring as shown below - 

import Data.Array.IO
import Data.Binary.Put
import qualified Data.ByteString.Lazy as BS
import Data.Word

main = do
arr <- newArray (0,9) 0 :: IO (IOArray Int Int)
let bs=toByteString arr
return ()

How can I implement the 'toByteString' function?


Why do you want to convert? If you process images you might consider one 
of the Vector libraries like storable-vector or vector. You can work on 
them in a mutable way, write them to disk, pass them to C libraries and so 
on.


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


Re: [Haskell-cafe] Help needed for converting IOArray to ByteString

2011-02-08 Thread Gábor Lehel
On Tue, Feb 8, 2011 at 10:39 AM, C K Kashyap  wrote:
>>
>> 1) Just use Data.Word.Word8 instead of the second Int in your type sig
>> for IOArray
>> 2) Use getElems to get a [Word8]
>> 3) Data.ByteString.pack converts a [Word8] into a ByteString
>>
>> Michael
>
> I am currently using a list of tuples - [(Int,Int,Int)] to represent an
> image buffer. You can see it in the getImageByteString
> function at https://github.com/ckkashyap/Chitra/blob/master/RFB/Encoding.hs
> Looks like this is pretty slow, and hence I am exploring Arrays.
> I wonder if working with [Word8] will also suffer from performance hit?
> Regards,
> Kashyap

Using Data.ByteString.Internal.create along with readArray to fill in
the contents seems like it would be a fast option (though I haven't
tried it).

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



-- 
Work is punishment for failing to procrastinate effectively.

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


Re: [Haskell-cafe] Help needed for converting IOArray to ByteString

2011-02-08 Thread Ketil Malde
C K Kashyap  writes:

> I am currently using a list of tuples - [(Int,Int,Int)] to represent an
> image buffer.
  [...]
> Looks like this is pretty slow, 

Unsurprisingly, as there's a huge space overhead, and (depending on
usage, but probably even worse) linear access time.

> I wonder if working with [Word8] will also suffer from performance hit?

If the only thing you use [Word8] for is converting between arrays (for
image processing) and bytestrings (for IO), it is an O(n) cost added to
an already O(n) operation, so it's probably liveable.  

The intermediate list might be optimized away, and in any case, your
program might still be limited by disk bandwidth, so if you're lucky,
it boils down to a matter of using 20% or 40% CPU when doing file IO.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants

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


Re: [Haskell-cafe] Help needed for converting IOArray to ByteString

2011-02-08 Thread C K Kashyap
>
>
> 1) Just use Data.Word.Word8 instead of the second Int in your type sig
> for IOArray
> 2) Use getElems to get a [Word8]
> 3) Data.ByteString.pack converts a [Word8] into a ByteString
>
> Michael
>

I am currently using a list of tuples - [(Int,Int,Int)] to represent an
image buffer. You can see it in the getImageByteString
function at https://github.com/ckkashyap/Chitra/blob/master/RFB/Encoding.hs
Looks like this is pretty slow, and hence I am exploring Arrays.

I wonder if working with [Word8] will also suffer from performance hit?

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


Re: [Haskell-cafe] Help needed for converting IOArray to ByteString

2011-02-08 Thread Michael Snoyman
On Tue, Feb 8, 2011 at 11:13 AM, C K Kashyap  wrote:
>
>
> On Tue, Feb 8, 2011 at 2:26 PM, Michael Snoyman  wrote:
>>
>> Your array contains machine-sized Ints, which in practice are likely
>> either 32-bit or 64-bit, while a ByteString is the equivalent of an
>> array or 8-bit values. So you'll need to somehow convert the Ints to
>> Word8s. Do you know if you need big or little endian?
>>
>> A basic approach would be:
>>
>> * Use freeze to convert your IOArray into an IArray
>> * Use putIArrayOf and put (from cereal) to generate a Putter value
>> * Use runPut to generate a ByteString from that
>>
>
> Thanks Michael,
> Actually, I need an array of 8-bit words - Is that available?
> Also, would be hard to do it without cereal?
> Regards,
> Kashyap

1) Just use Data.Word.Word8 instead of the second Int in your type sig
for IOArray
2) Use getElems to get a [Word8]
3) Data.ByteString.pack converts a [Word8] into a ByteString

Michael

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


Re: [Haskell-cafe] Help needed for converting IOArray to ByteString

2011-02-08 Thread C K Kashyap
On Tue, Feb 8, 2011 at 2:26 PM, Michael Snoyman  wrote:

> Your array contains machine-sized Ints, which in practice are likely
> either 32-bit or 64-bit, while a ByteString is the equivalent of an
> array or 8-bit values. So you'll need to somehow convert the Ints to
> Word8s. Do you know if you need big or little endian?
>
> A basic approach would be:
>
> * Use freeze to convert your IOArray into an IArray
> * Use putIArrayOf and put (from cereal) to generate a Putter value
> * Use runPut to generate a ByteString from that
>
>
Thanks Michael,
Actually, I need an array of 8-bit words - Is that available?

Also, would be hard to do it without cereal?

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


Re: [Haskell-cafe] Help needed for converting IOArray to ByteString

2011-02-08 Thread Michael Snoyman
Your array contains machine-sized Ints, which in practice are likely
either 32-bit or 64-bit, while a ByteString is the equivalent of an
array or 8-bit values. So you'll need to somehow convert the Ints to
Word8s. Do you know if you need big or little endian?

A basic approach would be:

* Use freeze to convert your IOArray into an IArray
* Use putIArrayOf and put (from cereal) to generate a Putter value
* Use runPut to generate a ByteString from that

Michael

On Tue, Feb 8, 2011 at 10:49 AM, C K Kashyap  wrote:
> Hi,
> I need to convert IOArray to bytestring as shown below -
> import Data.Array.IO
> import Data.Binary.Put
> import qualified Data.ByteString.Lazy as BS
> import Data.Word
> main = do
> arr <- newArray (0,9) 0 :: IO (IOArray Int Int)
> let bs=toByteString arr
> return ()
> How can I implement the 'toByteString' function?
> Regards,
> Kashyap
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>

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


[Haskell-cafe] Help needed for converting IOArray to ByteString

2011-02-08 Thread C K Kashyap
Hi,
I need to convert IOArray to bytestring as shown below -

import Data.Array.IO
import Data.Binary.Put
import qualified Data.ByteString.Lazy as BS
import Data.Word

main = do
arr <- newArray (0,9) 0 :: IO (IOArray Int Int)
let bs=toByteString arr
return ()

How can I implement the 'toByteString' function?

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