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
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 <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,
LauriOn 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