Skip to content

Commit

Permalink
StdGen: constructor accessible via Internal only (#123)
Browse files Browse the repository at this point in the history
Fixes haskell#59 by making 'StdGen' not
an instance of 'Read'.
  • Loading branch information
curiousleo authored May 8, 2020
1 parent f2319cc commit 9ee79a7
Show file tree
Hide file tree
Showing 4 changed files with 12 additions and 10 deletions.
2 changes: 1 addition & 1 deletion System/Random.hs
Original file line number Diff line number Diff line change
Expand Up @@ -293,7 +293,7 @@ getStdGen :: MonadIO m => m StdGen
getStdGen = liftIO $ readIORef theStdGen

theStdGen :: IORef StdGen
theStdGen = unsafePerformIO $ SM.initSMGen >>= newIORef
theStdGen = unsafePerformIO $ SM.initSMGen >>= newIORef . StdGen
{-# NOINLINE theStdGen #-}

-- |Applies 'split' to the current global pseudo-random generator,
Expand Down
10 changes: 6 additions & 4 deletions System/Random/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GHCForeignImportPrim #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
Expand Down Expand Up @@ -32,7 +33,7 @@ module System.Random.Internal
, MonadRandom(..)

-- ** Standard pseudo-random number generator
, StdGen
, StdGen(..)
, mkStdGen

-- * Monadic adapters for pure pseudo-random number generators
Expand Down Expand Up @@ -404,9 +405,10 @@ runStateGenST g action = runST $ runStateGenT g action


-- | The standard pseudo-random number generator.
type StdGen = SM.SMGen
newtype StdGen = StdGen { unStdGen :: SM.SMGen }
deriving (RandomGen, Show)

instance RandomGen StdGen where
instance RandomGen SM.SMGen where
next = SM.nextInt
genWord32 = SM.nextWord32
genWord64 = SM.nextWord64
Expand All @@ -420,7 +422,7 @@ instance RandomGen SM32.SMGen where

-- | Constructs a 'StdGen' deterministically.
mkStdGen :: Int -> StdGen
mkStdGen s = SM.mkSMGen $ fromIntegral s
mkStdGen = StdGen . SM.mkSMGen . fromIntegral

-- | The class of types for which a uniformly distributed value can be drawn
-- from all possible values of the type.
Expand Down
2 changes: 1 addition & 1 deletion System/Random/Monad.hs
Original file line number Diff line number Diff line change
Expand Up @@ -211,7 +211,7 @@ instance RandomGen r => RandomGenM STGenM r s (ST s) where
--
-- >>> import Data.Int (Int8)
-- >>> runGenM (IOGen (mkStdGen 217)) (`uniformListM` 5) :: IO ([Int8], IOGen StdGen)
-- ([-74,37,-50,-2,3],IOGen {unIOGen = SMGen 4273268533320920145 15251669095119325999})
-- ([-74,37,-50,-2,3],IOGen {unIOGen = StdGen {unStdGen = SMGen 4273268533320920145 15251669095119325999}})
--
-- @since 1.2
runGenM :: MonadRandom g s m => Frozen g -> (g s -> m a) -> m (a, Frozen g)
Expand Down
8 changes: 4 additions & 4 deletions bench/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,10 +22,10 @@ main = do
let !sz = 100000
defaultMain
[ bgroup "baseline"
[ let !stdGen = mkStdGen 1337 in bench "nextWord32" $ nf (genMany SM.nextWord32 stdGen) sz
, let !stdGen = mkStdGen 1337 in bench "nextWord64" $ nf (genMany SM.nextWord64 stdGen) sz
, let !stdGen = mkStdGen 1337 in bench "nextInt" $ nf (genMany SM.nextInt stdGen) sz
, let !stdGen = mkStdGen 1337 in bench "split" $ nf (genMany SM.splitSMGen stdGen) sz
[ let !smGen = SM.mkSMGen 1337 in bench "nextWord32" $ nf (genMany SM.nextWord32 smGen) sz
, let !smGen = SM.mkSMGen 1337 in bench "nextWord64" $ nf (genMany SM.nextWord64 smGen) sz
, let !smGen = SM.mkSMGen 1337 in bench "nextInt" $ nf (genMany SM.nextInt smGen) sz
, let !smGen = SM.mkSMGen 1337 in bench "split" $ nf (genMany SM.splitSMGen smGen) sz
]
, bgroup "pure"
[ bgroup "random"
Expand Down

0 comments on commit 9ee79a7

Please sign in to comment.