Re: [Haskell-cafe] Generate random UArray in constant memory space.

Am Tuesday 09 February 2010 15:43:13 schrieben Sie:
Update:
I've implemented `enumFromToU` through `unfoldU`:
enumFromToU' from to = unfoldU (to - from) f from where f i = let i' = i + 1 in JustS (i' :*: i')
This code behaves similarly to `enumFromToU` (i.e. constantly uses ~25 kb of memory, runs in the same time as above).
Wait, $ cat venum2.hs module Main (main) where import Text.Printf import Control.Applicative import System.Environment import Data.Array.Vector main = do [size] <- map read <$> getArgs let ints = enumFromToU' 0 size :: UArr Int printf "%d\n" (sumU ints) enumFromToU' from to = unfoldU (to - from) f from where f i = let i' = i + 1 in JustS (i' :*: i') $ ghc -O2 --make venum2 [1 of 1] Compiling Main ( venum2.hs, venum2.o ) Linking venum2 ... $ ./venum2 +RTS -sstderr -RTS 1000000 ./venum2 1000000 +RTS -sstderr 1784293664 48,256,384 bytes allocated in the heap 6,256 bytes copied during GC 26,804 bytes maximum residency (1 sample(s)) 25,524 bytes maximum slop 1 MB total memory in use (0 MB lost due to fragmentation) $ ./venum2 +RTS -sstderr -RTS 10000000 ./venum2 10000000 +RTS -sstderr -2004260032 481,937,552 bytes allocated in the heap 19,516 bytes copied during GC 26,804 bytes maximum residency (1 sample(s)) 25,512 bytes maximum slop 1 MB total memory in use (0 MB lost due to fragmentation) So we have constant memory, but linear allocation, just like with the random numbers. With enumFromToU, also the allocation is constant, so unfoldU allocates, enumFromToU not.
So the question is why random number list generator eats O(n) memory ?
It doesn't, not here, at least. Using System.Random, the allocation figures are about ten times as high, but the residency is about the same. Putting the PRNG code in the same file and tweaking things a bit (eliminating all intermediate Integers, e.g.), I get $ cat ran2Vec.hs {-# LANGUAGE BangPatterns #-} module Main (main) where import Text.Printf import Control.Applicative import System.Environment import Data.Array.Vector randomListU :: (Int, Int) -> StdGen -> Int -> (UArr Int) randomListU b@(l,h) g size = unfoldU size gen g where !k = h-l+1 !b' = 2147483561 `rem` k gen !g = let (!x, !g') = stdNext g in JustS ((l+ (x+b') `rem` k) :*: g') main = do [size] <- map read <$> getArgs let ints = randomListU (-10, 10) (mkStdGen 1) size printf "%d\n" (sumU ints) data StdGen = StdGen {-# UNPACK #-} !Int {-# UNPACK #-} !Int mkStdGen :: Int -> StdGen mkStdGen s | s < 0 = mkStdGen (-s) | otherwise = StdGen (s1+1) (s2+1) where (q, s1) = s `divMod` 2147483562 s2 = q `mod` 2147483398 {-# INLINE stdNext #-} stdNext :: StdGen -> (Int, StdGen) -- Returns values in the range stdRange stdNext (StdGen s1 s2) = z' `seq` g' `seq` (z', g') where !g' = StdGen s1'' s2'' !z' = if z < 1 then z + 2147483562 else z !z = s1'' - s2'' !k = s1 `quot` 53668 !s1' = 40014 * (s1 - k * 53668) - k * 12211 !s1'' = if s1' < 0 then s1' + 2147483563 else s1' !k' = s2 `quot` 52774 !s2' = 40692 * (s2 - k' * 52774) - k' * 3791 !s2'' = if s2' < 0 then s2' + 2147483399 else s2' $ ghc -O2 -funbox-strict-fields -funfolding-use-threshold=16 --make ran2Vec -o ran2AVec5 Linking ran2AVec5 ... $ ./ran2AVec5 +RTS -sstderr -RTS 10000000 ./ran2AVec5 10000000 +RTS -sstderr 5130 521,828,888 bytes allocated in the heap 8,664 bytes copied during GC 26,788 bytes maximum residency (1 sample(s)) 25,636 bytes maximum slop 1 MB total memory in use (0 MB lost due to fragmentation) nearly the same allocation figures as for the *much* simpler enumFromToU', and it's about ten times as fast as System.Random.
Regards, Vasyl Pasternak
2010/2/9 Vasyl Pasternak
: Sorry, maybe I should ask more clearer.
I've looked at dons article "Haskell as fast as C"[1], and tried to implement similar algorithm but for list of random numbers.
Please look at code:
import Text.Printf import Control.Applicative import System.Environment import Data.Array.Vector
main = do [size] <- map read <$> getArgs let ints = enumFromToU 0 size :: UArr Int printf "%d\n" (sumU ints)
This code runs in constant space (on my pc ~25kb allocates on the heap) regardless of array size. So I tried to achieve similar with random list, just to replace `enumFromToU` with my own list generator.
So the question - is it possible to implement random list similary to enumFromToU?
[1]http://donsbot.wordpress.com/2008/06/04/haskell-as-fast-as-c-workin g-at-a-high-altitude-for-low-level-performance/
Thank you, Vasyl Pasternak
2010/2/9 Daniel Fischer
: Am Dienstag 09 Februar 2010 13:18:23 schrieb Vasyl Pasternak:
Hello Cafe,
I tried to generate memory-efficient list of random numbers, so I've used uvector library for this task. But it doesn't work, it still allocates more than 6Gb of memory for the random list of 10
million elements. Here is the code:
Hmm,
$ ghc -O2 --make ranVec [1 of 1] Compiling Main ( ranVec.hs, ranVec.o ) Linking ranVec ... $ ./ranVec 10000000 +RTS -sstderr 5130 4,919,912,080 bytes allocated in the heap 883,256 bytes copied during GC 26,896 bytes maximum residency (1 sample(s)) 25,620 bytes maximum slop 1 MB total memory in use (0 MB lost due to fragmentation)
maximum residency is just eight bytes more than for 100,000 or 1,000,000 numbers. I think that is constant space.
The ~5 GB total allocation is sequential, ten million new StdGens are produced and allocated, then immediately garbage collected. I see no problem (except that StdGen is slow, e.g. the Mersenne twister is much faster [and allocates less, but still linear in size]).
import Text.Printf import System.Random import Control.Applicative import System.Environment import Data.Array.Vector
randomListU :: (Int, Int) -> StdGen -> Int -> (UArr Int) randomListU b g size = unfoldU size gen g where gen g = let (x, g') = randomR b g in JustS (x :*: g')
main = do [size] <- map read <$> getArgs let ints = randomListU (-10, 10) (mkStdGen 1) size printf "%d\n" (sumU ints)
Could someone give a hint, how to implement this function in constant memory space?
Thank you in advance.
Best regards, Vasyl Pasternak
participants (1)
-
Daniel Fischer