
Hi, I have a list of index-value pairs and I want to get a list which is sorted by the index and which contains index-wise sums of all the values. Here is a function that does this (and a bit more). --- pixelHistogram samples = let index s t = let x = round $ (fromIntegral imageWidth) * (1-s) y = round $ (fromIntegral imageHeight) * (1-t) in y*imageWidth + x indexedSamples = [(index s t, color) | (s, t, color) <- samples] pixelArray :: Array Int Color pixelArray = accumArray (\+) black (0, imageWidth*imageHeight) indexedSamples in elems pixelArray --- The problem is that this function is very inefficient. It seems that the whole indexedSamples list is stored in memory when creating pixelArray. When I do some profiling I see that the heap consumption of this function grows linearly. If I just write the samples list to a file instead of first summing them, I get a nice and flat heap profile. So how to do this efficiently? Thanks, Lauri

Hello Lauri, Friday, May 16, 2008, 12:19:29 PM, you wrote:
pixelArray :: Array Int Color
it's boxed array which means that its elements are stored as thunks computed only when you actually use them. try UArray instead: http://haskell.org/haskellwiki/Modern_array_libraries -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Thanks for help. I did some tests with UArray and it does the trick.
The problem remaining is, how to implement UArray Int (Double, Double,
Double)?
UArray source code is far too cryptic for me.
Regards,
Lauri
On Fri, May 16, 2008 at 11:37 AM, Bulat Ziganshin
Hello Lauri,
Friday, May 16, 2008, 12:19:29 PM, you wrote:
pixelArray :: Array Int Color
it's boxed array which means that its elements are stored as thunks computed only when you actually use them. try UArray instead:
http://haskell.org/haskellwiki/Modern_array_libraries
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

As far as I know, you can't. It needs machine representable types, such as
Int, Double, Char, etc. But making a tuple of three UArray Int Double may
help.
2008/5/16 Lauri Oksanen
Thanks for help. I did some tests with UArray and it does the trick. The problem remaining is, how to implement UArray Int (Double, Double, Double)? UArray source code is far too cryptic for me.
Regards, Lauri
On Fri, May 16, 2008 at 11:37 AM, Bulat Ziganshin < bulat.ziganshin@gmail.com> wrote:
Hello Lauri,
Friday, May 16, 2008, 12:19:29 PM, you wrote:
pixelArray :: Array Int Color
it's boxed array which means that its elements are stored as thunks computed only when you actually use them. try UArray instead:
http://haskell.org/haskellwiki/Modern_array_libraries
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Thanks again. Here is my solution in case that somebody else runs into
similar problem. This isn't very elegant and I would be interested to know
if somebody has a better solution. Surely many people have encountered this
kind of problem where you want to force evaluation of some expression at
given point of program flow. Here evaluation of sum must be forced for every
update of array element or otherwise memory consumption is proportional to
the number of samples (100 000) instead of being proportional to the size of
the array (10).
---
import Data.Array.IO
import Test.QuickCheck
import System.Random
uniformSampler :: Gen Double
uniformSampler = choose (0,1)
withSeed sampler seed = generate 1 (mkStdGen seed) sampler
ac = 10
sc = 100000
triplet = do
i <- uniformSampler
s <- uniformSampler
t <- uniformSampler
return (round $ i * fromIntegral ac, (s,t))
sampling = sequence $ repeat triplet
samples = take sc $ withSeed sampling 1
showElems xs = foldr1 (++) [show x ++ "\n" | x <- xs]
main = do
a1 <- newArray (0,ac) 0 :: IO (IOUArray Int Double)
a2 <- newArray (0,ac) 0 :: IO (IOUArray Int Double)
let addtoElem i s t = do
s' <- readArray a1 i
writeArray a1 i (s'+s)
t' <- readArray a2 i
writeArray a2 i (t'+t)
writes = [addtoElem i s t | (i,(s,t)) <- samples]
sequence writes
ss <- getElems a1
ts <- getElems a2
putStrLn $ showElems (zip ss ts)
---
Regards,
Lauri
On Fri, May 16, 2008 at 2:52 PM, Abhay Parvate
As far as I know, you can't. It needs machine representable types, such as Int, Double, Char, etc. But making a tuple of three UArray Int Double may help.
2008/5/16 Lauri Oksanen
: Thanks for help. I did some tests with UArray and it does the trick. The problem remaining is, how to implement UArray Int (Double, Double, Double)? UArray source code is far too cryptic for me.
Regards, Lauri
On Fri, May 16, 2008 at 11:37 AM, Bulat Ziganshin < bulat.ziganshin@gmail.com> wrote:
Hello Lauri,
Friday, May 16, 2008, 12:19:29 PM, you wrote:
pixelArray :: Array Int Color
it's boxed array which means that its elements are stored as thunks computed only when you actually use them. try UArray instead:
http://haskell.org/haskellwiki/Modern_array_libraries
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

You'd have to write a wrapper that implements an array of triples as a triple of arrays. This isn't too hard. There's a new library in the works that should make this a lot easier -- Don abhay.parvate:
As far as I know, you can't. It needs machine representable types, such as Int, Double, Char, etc. But making a tuple of three UArray Int Double may help.
2008/5/16 Lauri Oksanen <[1]lassoken@gmail.com>:
Thanks for help. I did some tests with UArray and it does the trick. The problem remaining is, how to implement UArray Int (Double, Double, Double)? UArray source code is far too cryptic for me.
Regards, Lauri
On Fri, May 16, 2008 at 11:37 AM, Bulat Ziganshin <[2]bulat.ziganshin@gmail.com> wrote:
Hello Lauri,
Friday, May 16, 2008, 12:19:29 PM, you wrote:
> pixelArray :: Array Int Color
it's boxed array which means that its elements are stored as thunks computed only when you actually use them. try UArray instead:
[3]http://haskell.org/haskellwiki/Modern_array_libraries
-- Best regards, Bulat mailto:[4]Bulat.Ziganshin@gmail.com
_______________________________________________ Haskell-Cafe mailing list [5]Haskell-Cafe@haskell.org [6]http://www.haskell.org/mailman/listinfo/haskell-cafe
References
Visible links 1. mailto:lassoken@gmail.com 2. mailto:bulat.ziganshin@gmail.com 3. http://haskell.org/haskellwiki/Modern_array_libraries 4. mailto:Bulat.Ziganshin@gmail.com 5. mailto:Haskell-Cafe@haskell.org 6. http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hello Lauri, Friday, May 16, 2008, 3:44:19 PM, you wrote: impossible. you can try parallel arrays
Thanks for help. I did some tests with UArray and it does the trick. The problem remaining is, how to implement UArray Int (Double, Double, Double)? UArray source code is far too cryptic for me.
Regards, Lauri
On Fri, May 16, 2008 at 11:37 AM, Bulat Ziganshin
wrote: Hello Lauri, Friday, May 16, 2008, 12:19:29 PM, you wrote:
pixelArray :: Array Int Color
it's boxed array which means that its elements are stored as thunks computed only when you actually use them. try UArray instead:
http://haskell.org/haskellwiki/Modern_array_libraries
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Fri, 16 May 2008, Lauri Oksanen wrote:
Thanks for help. I did some tests with UArray and it does the trick. The problem remaining is, how to implement UArray Int (Double, Double, Double)?
Maybe an (UArray (Int,Int) Double) could help, where the second index range is fixed to (0,2).

Yes, of course. How blind of me. Here is one more question. If you change IOUArray to IOArray and add $! in front of the two summations in the previous code, it still works correctly. But can you do similar trick with Array and accumArray? I have tried to put $! in different places in the first code that I posted but nothing seems to work. On Fri, May 16, 2008 at 4:26 PM, Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Fri, 16 May 2008, Lauri Oksanen wrote:
Thanks for help. I did some tests with UArray and it does the trick.
The problem remaining is, how to implement UArray Int (Double, Double, Double)?
Maybe an (UArray (Int,Int) Double) could help, where the second index range is fixed to (0,2).

Hello Lauri, Friday, May 16, 2008, 5:45:50 PM, you wrote:
Yes, of course. How blind of me. Here is one more question. If you change IOUArray to IOArray and add $! in front of the two summations in the previous code, it still works correctly. But can you do similar trick with Array and accumArray? I have tried to put $! in different places in the first code that I posted but nothing seems to work.
accumArray internally uses more or less the same code with imperative array as you wrote. so if you replace accumArray with your implementation with all those $! - it will work. otherwise you just don't get any chance :) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

"Lauri Oksanen"
Thanks for help. I did some tests with UArray and it does the trick. The problem remaining is, how to implement UArray Int (Double, Double, Double)?
As (UArray Int Double, UArray Int Double, UArray Int Double). Or as UArray Int Double, but with a specialized lookup function: mylookup array index = (array!3*index, array!3*index+1, array!3*index+2) I guess it would be possible to have UArray Int (# Double, Double, Double #) - packing all three Doubles unboxed into the array, but I've no clue how to go about automating that. -k -- If I haven't seen further, it is by standing in the footprints of giants

Hello Ketil, Friday, May 16, 2008, 5:27:29 PM, you wrote:
I guess it would be possible to have UArray Int (# Double, Double, Double #) - packing all three Doubles unboxed into the array, but I've no clue how to go about automating that.
unoxed tuple doesn't have a box so it cannot be instance of typeclass. actually, ordinary tuple will solve this problem unless one problem in GHC - it's UArray indexing primitives use *element* indexes inatead of *byte* indexes. although at least we can implement UArray ix (a,a), UArray ix (a,a,a) and so on -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
participants (6)
-
Abhay Parvate
-
Bulat Ziganshin
-
Don Stewart
-
Henning Thielemann
-
Ketil Malde
-
Lauri Oksanen