 
            Am Dienstag 09 Februar 2010 19:27:58 schrieb Bryan O'Sullivan:
On Tue, Feb 9, 2010 at 4:18 AM, Vasyl Pasternak
wrote: I tried to generate memory-efficient list of random numbers, so I've used uvector library for this task.
Use the mwc-random package. It provides a function that does exactly this, and produces better quality random numbers with much higher performance (1000x faster) than System.Random or even mersenne-random.
Not here. I may be doing it wrong, but ======================================== {-# LANGUAGE BangPatterns #-} module Main (main) where import Text.Printf import System.Random.MWC import Control.Applicative import System.Environment import Data.Array.Vector import Control.Monad.ST randomListU :: (Int, Int) -> Int -> Int -- (UArr Int) randomListU b@(l,h) size = runST $ do let !k = h-l+1 f !m = m `mod` k + l sg <- create sumU . mapU f <$> uniformArray sg size main = do [size] <- map read <$> getArgs let int = randomListU (-10, 10) size printf "%d\n" int ======================================== gives $ ghc -O2 -funfolding-use-threshold=32 -fforce-recomp --make mwcRanVec.hs - o mwcRanVec3 [1 of 1] Compiling Main ( mwcRanVec.hs, mwcRanVec.o ) Linking mwcRanVec3 ... $ ./mwcRanVec3 +RTS -s -RTS 10000000 ./mwcRanVec3 10000000 +RTS -s 22784 40,966,820 bytes allocated in the heap 3,696 bytes copied during GC 27,128 bytes maximum residency (1 sample(s)) 26,940 bytes maximum slop 40 MB total memory in use (0 MB lost due to fragmentation) Generation 0: 1 collections, 0 parallel, 0.00s, 0.00s elapsed Generation 1: 1 collections, 0 parallel, 0.00s, 0.00s elapsed INIT time 0.00s ( 0.00s elapsed) MUT time 1.09s ( 1.15s elapsed) GC time 0.00s ( 0.00s elapsed) EXIT time 0.00s ( 0.00s elapsed) Total time 1.10s ( 1.15s elapsed) %GC time 0.0% (0.0% elapsed) Alloc rate 37,376,166 bytes per MUT second Productivity 99.6% of total user, 95.2% of total elapsed , System.Random.Mersenne $ ./mtRanVec +RTS -s -RTS 10000000 ./mtRanVec 10000000 +RTS -s -24541 280,609,188 bytes allocated in the heap 17,404 bytes copied during GC 26,776 bytes maximum residency (1 sample(s)) 25,724 bytes maximum slop 1 MB total memory in use (0 MB lost due to fragmentation) Generation 0: 535 collections, 0 parallel, 0.00s, 0.00s elapsed Generation 1: 1 collections, 0 parallel, 0.00s, 0.00s elapsed INIT time 0.00s ( 0.00s elapsed) MUT time 1.10s ( 1.10s elapsed) GC time 0.00s ( 0.00s elapsed) EXIT time 0.00s ( 0.00s elapsed) Total time 1.10s ( 1.10s elapsed) %GC time 0.4% (0.4% elapsed) Alloc rate 255,083,261 bytes per MUT second Productivity 99.3% of total user, 99.5% of total elapsed more or less the same, the System.Random code gives $ ./uRanVec +RTS -s -RTS 10000000./uRanVec 10000000 +RTS -s 5130 4,515,826,700 bytes allocated in the heap 803,132 bytes copied during GC 26,852 bytes maximum residency (1 sample(s)) 25,716 bytes maximum slop 1 MB total memory in use (0 MB lost due to fragmentation) Generation 0: 8680 collections, 0 parallel, 0.10s, 0.10s elapsed Generation 1: 1 collections, 0 parallel, 0.00s, 0.00s elapsed INIT time 0.00s ( 0.00s elapsed) MUT time 9.12s ( 9.17s elapsed) GC time 0.10s ( 0.10s elapsed) EXIT time 0.00s ( 0.00s elapsed) Total time 9.22s ( 9.27s elapsed) %GC time 1.1% (1.1% elapsed) Alloc rate 495,342,570 bytes per MUT second Productivity 98.9% of total user, 98.3% of total elapsed (so a factor of a little above 8), and the specialised System.Random code in the source file, ==================================================== {-# 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' ==================================================== comes in fastest at $ ./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) Generation 0: 995 collections, 0 parallel, 0.00s, 0.01s elapsed Generation 1: 1 collections, 0 parallel, 0.00s, 0.00s elapsed INIT time 0.00s ( 0.00s elapsed) MUT time 0.94s ( 0.94s elapsed) GC time 0.00s ( 0.01s elapsed) EXIT time 0.00s ( 0.00s elapsed) Total time 0.94s ( 0.95s elapsed) %GC time 0.4% (1.0% elapsed) Alloc rate 557,474,951 bytes per MUT second Productivity 99.6% of total user, 98.8% of total elapsed