randomR too slow
randomR is considerably slower than implementing it manually. Maybe I have not re-implemented it precisely, maybe it is just not inlined.
module Main (main) where
import System.Random (RandomGen(..), randomR, )
import qualified Data.ByteString as B
newtype KnuthRandomGen = KnuthRandomGen Int
{-# INLINE knuthFactor #-}
knuthFactor :: Int
knuthFactor = 40692
{-# INLINE knuthModulus #-}
knuthModulus :: Int
knuthModulus = 2^(31::Int)-249
-- we have to split the 32 bit integer in order to avoid overflow on multiplication
knuthSplit :: Int
knuthSplit = succ $ div knuthModulus knuthFactor
knuthSplitRem :: Int
knuthSplitRem = knuthSplit * knuthFactor - knuthModulus
instance RandomGen KnuthRandomGen where
{-# INLINE next #-}
next (KnuthRandomGen s) =
-- efficient computation of @mod (s*knuthFactor) knuthModulus@ without Integer
let (sHigh, sLow) = divMod s knuthSplit
in (s, KnuthRandomGen $ flip mod knuthModulus $
knuthSplitRem*sHigh + knuthFactor*sLow)
{-# INLINE split #-}
split (KnuthRandomGen s) =
(KnuthRandomGen (s*s), KnuthRandomGen (13+s))
{-# INLINE genRange #-}
genRange _ = (1, pred knuthModulus)
main :: IO ()
main =
do
-- for comparison: that's very fast
putStrLn "constant"
B.writeFile "random.out" $ fst $
B.unfoldrN 10000000
(\g0@(KnuthRandomGen s) -> Just (fromIntegral s, g0))
(KnuthRandomGen 1)
-- 3 seconds on my machine
putStrLn "immediate"
B.writeFile "random.out" $ fst $
B.unfoldrN 10000000
(\g0 -> let (w,g1) = next g0
in Just (fromIntegral (mod w 256), g1))
(KnuthRandomGen 1)
-- 10 seconds on my machine
putStrLn "randomR"
B.writeFile "random.out" $ fst $
B.unfoldrN 10000000
(\g0 -> Just (let (w,g1) = randomR (0,255) g0
in (fromIntegral (w::Int), g1)))
(KnuthRandomGen 1)
{-
ghc -o dist/build/randomtest -O -Wall -package bytestring-0.9.0.5 -ddump-simpl-iterations speedtest/RandomTest.hs
-}
{-
bytestring-0.9.0.1 as shipped with GHC-6.8.2 does not inline Data.ByteString.unfoldrN
-}
Is this related to Ticket 427?
Trac metadata
Trac field | Value |
---|---|
Version | 6.8.2 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | libraries/random |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | ghc@henning-thielemann.de |
Operating system | |
Architecture |