Hello Libraries,
You may recall that following the blog post by @lehins, a group of us
(@curiousleo, @lehins and me) invited participation in February to
take this work and apply it to improving the current random
library.
Our proximate goals were to fix #25 (filed in 2015) and #51 (filed in 2018). After a lot of discussion and experimentation, we have a proposal that addresses both these issues and also: #26, #44, #53, #55, #58 and #59.
For backwards compatibility, the proposal retains the old style classes and enhances them. Thus in 1.1 we have
class RandomGen g where
next :: g -> (Int, g)
genRange :: g -> (Int, Int)
split :: g -> (g, g)
{-# MINIMAL next, split #-}
and in 1.2 we have
class RandomGen g where
next :: g -> (Int, g)
genWord8 :: g -> (Word8, g)
genWord16 :: g -> (Word16, g)
genWord32 :: g -> (Word32, g)
genWord64 :: g -> (Word64, g)
genWord32R :: Word32 -> g -> (Word32, g)
genWord64R :: Word64 -> g -> (Word64, g)
genShortByteString :: Int
-> g -> (Data.ByteString.Short.Internal.ShortByteString, g)
genRange :: g -> (Int, Int)
split :: g -> (g, g)
{-# MINIMAL split, (genWord32 | genWord64 | next, genRange) #-}
and next
and genRange
are deprecated. This interface is what
allows the significantly faster performance as no longer is everything
forced to go via Integer
.
Several new interfaces are introduced and it is recommended that new applications use these and, where feasible, existing applications migrate to using them.
The major API addition in this PR is the definition of a new class MonadRandom
:
-- | 'MonadRandom' is an interface to monadic pseudo-random number generators.
class Monad m => MonadRandom g s m | g m -> s where
{-# MINIMAL freezeGen,thawGen,(uniformWord32|uniformWord64) #-}
type Frozen g = (f :: Type) | f -> g
freezeGen :: g s -> m (Frozen g)
thawGen :: Frozen g -> m (g s)
uniformWord32 :: g s -> m Word32 -- default implementation in terms of uniformWord64
uniformWord64 :: g s -> m Word64 -- default implementation in terms of uniformWord32
-- plus methods for other word sizes and for byte strings
-- all have default implementations so the MINIMAL pragma holds
Conceptually, in MonadRandom g s m
, g s
is the type of the
generator, s
is the state type, and m
the underlying monad. Via
the functional dependency g m -> s
, the state type is determined by
the generator and monad.
Frozen
is the type of the generator's state "at rest". It is defined
as an injective type family via f -> g
, so there is no ambiguity as
to which g
any Frozen g
belongs to.
This definition is generic enough to accommodate, for example, the
Gen
type from mwc-random
, which itself abstracts over the
underlying primitive monad and state token. This is the full instance
declaration (provided here as an example - this instance is not part
of random
as random
does not depend on mwc-random
):
instance (s ~ PrimState m, PrimMonad m) => MonadRandom MWC.Gen s m where
type Frozen MWC.Gen = MWC.Seed
freezeGen = MWC.save
thawGen = MWC.restore
uniformWord8 = MWC.uniform
uniformWord16 = MWC.uniform
uniformWord32 = MWC.uniform
uniformWord64 = MWC.uniform
uniformShortByteString n g = unsafeSTToPrim (genShortByteStringST n (MWC.uniform g))
Pure random number generators can also be made instances of this class
providing a uniform interface to both pure and stateful random number
generators. An instance for the standard number generator StdGen
is
provided.
The Random
typeclass has conceptually been split into Uniform
and
UniformRange
. The Random
typeclass is still included for backwards
compatibility. Uniform
is for types where it is possible to sample
from the type's entire domain; UniformRange
is for types where one
can sample from a specified range:
class Uniform a where
uniformM :: MonadRandom g s m => g s -> m a
class UniformRange a where
uniformRM :: MonadRandom g s m => (a, a) -> g s -> m a
The proposal is a breaking change but the changes are not very intrusive and we have PRs ready for the affected downstream libraries:
base
>= 4.10 (GHC-8.2)StdGen
is no longer an instance of Read
randomIO
and randomRIO
were extracted from the Random
class
into separate functionsIn addition, there may be import clashes with new functions,
e.g. uniform
and uniformR
.
Further explanatory details may be found here and the PR for the proposed new version is here.
Here are some benchmarks run on a 3.1 GHz Intel Core i7. The full
benchmarks can be run using e.g. stack bench
. The benchmarks are
measured in milliseconds per 100,000 generations. In some cases, the
performance is over x1000(!) times better; the minimum performance
increase for the types listed below is more than x35.
| Name | Mean (1.1) | Mean (1.2) | Improvement|
| ----------------------- | ---------- | ---------- | ---------- |
| pure/random/Float | 30 | 0.03 | 1038|
| pure/random/Double | 52 | 0.03 | 1672|
| pure/random/Integer | 43 | 0.33 | 131|
| pure/uniform/Word8 | 14 | 0.03 | 422|
| pure/uniform/Word16 | 13 | 0.03 | 375|
| pure/uniform/Word32 | 21 | 0.03 | 594|
| pure/uniform/Word64 | 42 | 0.03 | 1283|
| pure/uniform/Word | 44 | 0.03 | 1491|
| pure/uniform/Int8 | 15 | 0.03 | 511|
| pure/uniform/Int16 | 15 | 0.03 | 507|
| pure/uniform/Int32 | 22 | 0.03 | 749|
| pure/uniform/Int64 | 44 | 0.03 | 1405|
| pure/uniform/Int | 43 | 0.03 | 1512|
| pure/uniform/Char | 17 | 0.49 | 35|
| pure/uniform/Bool | 18 | 0.03 | 618|
| pure/uniform/CChar | 14 | 0.03 | 485|
| pure/uniform/CSChar | 14 | 0.03 | 455|
| pure/uniform/CUChar | 13 | 0.03 | 448|
| pure/uniform/CShort | 14 | 0.03 | 473|
| pure/uniform/CUShort | 13 | 0.03 | 457|
| pure/uniform/CInt | 21 | 0.03 | 737|
| pure/uniform/CUInt | 21 | 0.03 | 742|
| pure/uniform/CLong | 43 | 0.03 | 1544|
| pure/uniform/CULong | 42 | 0.03 | 1460|
| pure/uniform/CPtrdiff | 43 | 0.03 | 1494|
| pure/uniform/CSize | 43 | 0.03 | 1475|
| pure/uniform/CWchar | 22 | 0.03 | 785|
| pure/uniform/CSigAtomic | 21 | 0.03 | 749|
| pure/uniform/CLLong | 43 | 0.03 | 1554|
| pure/uniform/CULLong | 42 | 0.03 | 1505|
| pure/uniform/CIntPtr | 43 | 0.03 | 1476|
| pure/uniform/CUIntPtr | 42 | 0.03 | 1463|
| pure/uniform/CIntMax | 43 | 0.03 | 1535|
| pure/uniform/CUIntMax | 42 | 0.03 | 1493|