<div>Hey Zemyla,<br></div><div><br></div><div>> And can you explain how to take an existing RNG and write it in this new format?<br></div><div><br></div><div>This question is a bit vague, so I'll try to elaborate on all aspects of new format. New interface supports both stateful and pure RNGs, so I assume you are asking how to use them with the new format, rather than how to create instances, because the latter is only important for maintainers of PRNG libraries and a user will never need to create any instances. If you are still curious about how to write them there is example for stateful mwc-random, which can be found in the generated haddock and in the beginning of this thread, as Dominic pointed out. For pure RNGs I included links to repositories that contain adjusted RandomGen instances below in this email.<br></div><div><br></div><div>As far as pure RNGs, such as the default splitmix and tf-random, etc. Any of them can be used with monadic interface by the means of any `MonadState`. There is a newtype wrapper `StateGen` that allows us to use new monadic interface without any runtime overhead and any other work on the user's part. Let's look at some examples of why this monadic interface is extremely powerful.<br></div><div><br></div><div>We can write our code in this monadic style once:<br></div><div><br></div><div>-- | Generate a random alpha string with random length up to a specified value.<br></div><div>randomStringN :: MonadRandom g s m => Int -> g s -> m (Int, String)<br></div><div>randomStringN upperBound gen = do<br></div><div>  n <- uniformRM (0, upperBound) gen<br></div><div>  xs <- replicateM n $ uniformRM ('a', 'z') gen<br></div><div>  pure (n, xs)<br></div><div><br></div><div>And then we can use such function with any of the available PRNG in Haskell. There are some helper functions that allow using pure RNGs that have RandomGen instance with this monadic style, like `runStateGen`<br></div><div><br></div><div>>>> runStateGen (mkStdGen 217) (randomStringN 10)<br></div><div>((6,"ihhtwd"),StdGen {unStdGen = SMGen 16329862649850020527 15251669095119325999})<br></div><div><br></div><div>which is equivalent to:<br></div><div><br></div><div>>>> runState (randomStringN 10 StateGenM) (mkStdGen 217)<br></div><div>((6,"ihhtwd"),StdGen {unStdGen = SMGen 16329862649850020527 15251669095119325999})<br></div><div><br></div><div>There is also IOGen, that is a wrapper around IORef, which can be used in places where `StateT` can't be used, such as in presence of `bracket` for example:<br></div><div><br></div><div>>>> gen <- thawGen (IOGen (mkStdGen 217))<br></div><div>>>> randomStringN 10 gen<br></div><div>(6,"ihhtwd")<br></div><div><br></div><div>It is just as easily can be used with mwc-random or pcg-random packages in IO:<br></div><div><br></div><div>>>> import System.Random.MWC as MWC<br></div><div>>>> gen <- MWC.createSystemRandom<br></div><div>>>> randomStringN 10 gen<br></div><div>(7,"gfcfodz")<br></div><div><br></div><div>and of course in ST:<br></div><div><br></div><div>>>> import Control.Monad.ST<br></div><div>>>> seed <- MWC.save =<< MWC.createSystemRandom<br></div><div>>>> runST $ thawGen seed >>= randomStringN 10<br></div><div>(9,"wuzudihnd")<br></div><div><br></div><div>It is important to note, that we didn't have to define any new monads or transformers, which saves us from a need to create thousands of different instances and force a user to use yet another monad. All of our machinery from Haskell ecosystem will work perfectly fine with this new interface.<br></div><div><br></div><div><br></div><div>With regards to Carter's remark:<br></div><div>> Yeah, absolutely agree that their pr has the wrong shape for monad random<br></div><div><br></div><div>It is possible to drop state token `s`, but we would have to loose `Frozen` type and ability to use functions like `thawGen`, `freezeGen` and consequently `runGenM` which  make `MonadRandom` even so more useful. That being said, if that is a deal breaker, I can submit a PR that removes this functionality.<br></div><div><br></div><div><br></div><div>Here is also an answer to David's question:<br></div><div><br></div><div>> Could you explain the reasoning behind the deprecations?<br></div><div><br></div><div>`next` and `genRange` are the actual  reason behind the slowness of `random` all these years. It is not feasible to convert an arbitrary `Int` sub range (which is what `next`+`genRange` give us) to another arbitrary subrange of another type efficiently. All prior versions of random go through `Integer` to generate ranges for almost all types, precisely because of this problem. The great part about this problem is that the poor quality `StdGen` in `random-1.1` is the only pure RNG in Haskell that relies in this property of having unusual min and max value in `genRange`. Most of RNGs out there produce pseudo random numbers in a n-bit range, where n is usually 32 or 64 bits. Once you have that property available it is possible to utilize it to get really fast generation of random numbers of any type in any range. Therefore this is the reason for addition of `genWord32`, `genWord64` ... and deprecation of `next` and `genRange`. Nice thing the approach we took is that it makes it backwards compatible, in other words any instance that only defined `next` and `genRange` will still work, albeit slower than it could if it were to implement either `genWord32` or `genWord64`.<br></div><div><br></div><div>In case you are curious, I've went through all packages that implement `RandomGen` instance and none of them will miss these two functions, here is a list of some of the repos with branches that contain fixed instances:<br></div><div>* <a href="https://github.com/lehins/quickcheck/tree/new-random">https://github.com/lehins/quickcheck/tree/new-random</a><br></div><div>* <a href="https://github.com/lehins/tf-random/tree/new-random">https://github.com/lehins/tf-random/tree/new-random</a><br></div><div>* <a href="https://github.com/lehins/mersenne-random-pure64/tree/new-random">https://github.com/lehins/mersenne-random-pure64/tree/new-random</a><br></div><div>* <a href="https://github.com/lehins/pcg-random/tree/new-random">https://github.com/lehins/pcg-random/tree/new-random</a><br></div><div>* <a href="https://github.com/lehins/pcgen/tree/new-random">https://github.com/lehins/pcgen/tree/new-random</a><br></div><div><br></div><div><div>Alexey.<br></div><div><br></div><div>PS. I didn't realize I my last email was not posted to libraries because my email was not registered, so I resent it again.<br></div></div><div class="protonmail_signature_block protonmail_signature_block-empty"><div class="protonmail_signature_block-user protonmail_signature_block-empty"><br></div><div class="protonmail_signature_block-proton protonmail_signature_block-empty"><br></div></div><div><br></div><div>‐‐‐‐‐‐‐ Original Message ‐‐‐‐‐‐‐<br></div><div> On Wednesday, May 27, 2020 5:13 AM, Carter Schonwald <carter.schonwald@gmail.com> wrote:<br></div><div> <br></div><blockquote class="protonmail_quote" type="cite"><div><div><div dir="auto">Zemyla! <br></div></div></div><div dir="auto"><br></div><div dir="auto">Yeah, absolutely agree that their pr has the wrong shape for monad random, which is why I’m confused by dominics pronouncement :), though its a great contrib.<br></div><div dir="auto"><br></div><div dir="auto">It should be (ignoring m being applicative vs monad)<br></div><div dir="auto">(For context, their design is roughly  ... MonadRandom m s g | m,g -> s ?  I’m typing on a phone so i might be restating it wrong ... :) )<br></div><div dir="auto"><br></div><div dir="auto"><br></div><div dir="auto">The *better* choice is <br></div><div dir="auto">Class PRNG g =>  MonadRandom m g | m-> g where ... <br></div><div dir="auto"><br></div><div dir="auto">And then their example instance  should be something like <br></div><div dir="auto"><br></div><div dir="auto">Newtype MWCT  m a = ... newtype wrapper around StateT m a threading an MWC indexed by the state token of the underlying PrimMonad<br></div><div dir="auto">(Or newtype MWCT s m a = .... stateT thing)<br></div><div dir="auto"><br></div><div dir="auto">Instance (PrimMonad m) => MonadRandom  (MWCT m) (MCWGen (PrimState m)) where ... <br></div><div dir="auto"><br></div><div dir="auto">Or something along those lines.  It absolutely shouldn’t be in the style of being on any PrimMonad, but part of a stack that provides that instance.  <br></div><div dir="auto"><br></div><div dir="auto">This is ignoring the freeze/thaw stuff which really is just “record and restore RNG state”, and i think is  an artifact of ther design choice in their PR. Which has a lot of great stuff I’m reviewing and poking at.<br></div><div dir="auto"><br></div><div dir="auto"><br></div><div dir="auto">Nothing is set in stone about deprecation and migration story, cause improving everything and making sure everyone has a zero pain/ or at least tolerable upgrade path is step zero.  (And making sure good stable interfaces persists is key! )<br></div><div dir="auto"><br></div><div dir="auto">I hope everyone is having a safe and healthy start to their summers, <br></div><div dir="auto"><br></div><div dir="auto">and I’m sorry for any confusions Dominics email about his collab Pr announcement has created.  But cest lie vie! Though sharing excitement about a great Pr is great! <br></div><div dir="auto"><br></div><div dir="auto">Stay well!<br></div><div dir="auto">-Carter <br></div><div dir="auto"><br></div><div dir="auto">On Tue, May 26, 2020 at 6:48 PM Zemyla <<a href="mailto:zemyla@gmail.com" target="_blank">zemyla@gmail.com</a>> wrote:<br></div><div><div><div class="gmail_quote"><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left-width:1px;border-left-style:solid;padding-left:1ex;border-left-color:rgb(204,204,204)"><div dir="auto">And can you explain how to take an existing RNG and write it in this new format?<br></div><div><br></div><div class="gmail_quote"><div dir="ltr">On Tue, May 26, 2020, 15:54 David Feuer <<a href="mailto:david.feuer@gmail.com" target="_blank">david.feuer@gmail.com</a>> wrote:<br></div><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left-width:1px;border-left-style:solid;padding-left:1ex;border-left-color:rgb(204,204,204)"><div dir="auto">Could you explain the reasoning behind the deprecations?<br></div><div><br></div><div class="gmail_quote"><div dir="ltr">On Tue, May 26, 2020, 6:00 AM  <<a href="mailto:dominic@steinitz.org" rel="noreferrer" target="_blank">dominic@steinitz.org</a>> wrote:<br></div><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left-width:1px;border-left-style:solid;padding-left:1ex;border-left-color:rgb(204,204,204)"><div style="word-wrap:break-word;line-break:after-white-space"><p>Hello Libraries,<br></p><p>You may recall that following the blog <a href="https://alexey.kuleshevi.ch/blog/2019/12/21/random-benchmarks/" rel="noreferrer noreferrer" target="_blank">post</a> by @lehins, a group of us
(@curiousleo, @lehins and me) invited participation in <a href="https://mail.haskell.org/pipermail/libraries/2020-February/030261.html" rel="noreferrer noreferrer" target="_blank">February</a> to
take this work and apply it to improving the current <code style="font-family:monospace">random</code> library.<br></p><p>Our proximate goals were to fix <a href="https://github.com/haskell/random/issues/25" rel="noreferrer noreferrer" target="_blank">#25</a> (filed in 2015) and <a href="https://github.com/haskell/random/issues/51" rel="noreferrer noreferrer" target="_blank">#51</a> (filed in
2018). After a lot of discussion and experimentation, we have a
proposal that addresses both these issues and also: <a href="https://github.com/haskell/random/issues/26" rel="noreferrer noreferrer" target="_blank">#26</a>, <a href="https://github.com/haskell/random/issues/44" rel="noreferrer noreferrer" target="_blank">#44</a>, <a href="https://github.com/haskell/random/issues/53" rel="noreferrer noreferrer" target="_blank">#53</a>, <a href="https://github.com/haskell/random/issues/55" rel="noreferrer noreferrer" target="_blank">#55</a>, <a href="https://github.com/haskell/random/issues/58" rel="noreferrer noreferrer" target="_blank">#58</a> and <a href="https://github.com/haskell/random/issues/59" rel="noreferrer noreferrer" target="_blank">#59</a>.<br></p><p>For backwards compatibility, the proposal retains the old style
classes and enhances them. Thus in 1.1 we have<br></p><pre style="font-family:monospace"><code style="font-family:monospace">class RandomGen g where
    next :: g -> (Int, g)
    genRange :: g -> (Int, Int)
    split :: g -> (g, g)
    {-# MINIMAL next, split #-}
</code><br></pre><p>and in 1.2 we have<br></p><pre style="font-family:monospace"><code style="font-family:monospace">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) #-}
</code><br></pre><p>and <code style="font-family:monospace">next</code> and <code style="font-family:monospace">genRange</code> are deprecated. This interface is what
allows the significantly faster performance as no longer is everything
forced to go via <code style="font-family:monospace">Integer</code>.<br></p><p>Several new interfaces are introduced and it is recommended that new
applications use these and, where feasible, existing applications
migrate to using them.<br></p><p>The major API addition in this PR is the definition of a new class <code style="font-family:monospace">MonadRandom</code>:<br></p><pre style="font-family:monospace"><code style="font-family:monospace">-- | '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
</code><br></pre><p>Conceptually, in <code style="font-family:monospace">MonadRandom g s m</code>, <code style="font-family:monospace">g s</code> is the type of the
generator, <code style="font-family:monospace">s</code> is the state type, and <code style="font-family:monospace">m</code> the underlying monad. Via
the functional dependency <code style="font-family:monospace">g m -> s</code>, the state type is determined by
the generator and monad.<br></p><p><code style="font-family:monospace">Frozen</code> is the type of the generator's state "at rest". It is defined
as an injective type family via <code style="font-family:monospace">f -> g</code>, so there is no ambiguity as
to which <code style="font-family:monospace">g</code> any <code style="font-family:monospace">Frozen g</code> belongs to.<br></p><p>This definition is generic enough to accommodate, for example, the <code style="font-family:monospace">Gen</code> type from <code style="font-family:monospace">mwc-random</code>, 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 <code style="font-family:monospace">random</code> as <code style="font-family:monospace">random</code> does not depend on <code style="font-family:monospace">mwc-random</code>):<br></p><pre style="font-family:monospace"><code style="font-family:monospace">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))
</code><br></pre><p>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 <code style="font-family:monospace">StdGen</code> is
provided.<br></p><p>The <code style="font-family:monospace">Random</code> typeclass has conceptually been split into <code style="font-family:monospace">Uniform</code> and <code style="font-family:monospace">UniformRange</code>. The <code style="font-family:monospace">Random</code> typeclass is still included for backwards
compatibility. <code style="font-family:monospace">Uniform</code> is for types where it is possible to sample
from the type's entire domain; <code style="font-family:monospace">UniformRange</code> is for types where one
can sample from a specified range:<br></p><pre style="font-family:monospace"><code style="font-family:monospace">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
</code><br></pre><p>The proposal is a breaking change but the changes are not very
intrusive and we have PRs ready for the affected downstream libraries:<br></p><ul><li>requires <code style="font-family:monospace">base</code> >= 4.10 (GHC-8.2)<br></li><li><code style="font-family:monospace">StdGen</code> is no longer an instance of <code style="font-family:monospace">Read</code><br></li><li><code style="font-family:monospace">randomIO</code> and <code style="font-family:monospace">randomRIO</code> were extracted from the <code style="font-family:monospace">Random</code> class
into separate functions<br></li></ul><p>In addition, there may be import clashes with new functions,
e.g. <code style="font-family:monospace">uniform</code> and <code style="font-family:monospace">uniformR</code>.<br></p><p>Further explanatory details may be found <a href="https://github.com/idontgetoutmuch/random/blob/v1.2-release-notes/RELEASE-NOTES-v1.2.md#api-changes" rel="noreferrer noreferrer" target="_blank">here</a> and the PR for the proposed new version is <a href="https://github.com/haskell/random/pull/61" rel="noreferrer noreferrer" target="_blank">here</a>.<br></p><p>Here are some benchmarks run on a 3.1 GHz Intel Core i7. The full
benchmarks can be run using e.g. <code style="font-family:monospace">stack bench</code>. 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.<br></p><pre style="font-family:monospace"><code style="font-family:monospace">| 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|
</code><br></pre><div><br></div><div><br></div><div><div dir="auto" style="word-wrap:break-word;line-break:after-white-space"><div style="font-family:Helvetica;font-size:12px;font-style:normal;font-variant-caps:normal;font-weight:normal;letter-spacing:normal;text-align:start;text-indent:0px;text-transform:none;white-space:normal;word-spacing:0px;color:rgb(0,0,0)">Dominic Steinitz<br></div><div style="font-family:Helvetica;font-size:12px;font-style:normal;font-variant-caps:normal;font-weight:normal;letter-spacing:normal;text-align:start;text-indent:0px;text-transform:none;white-space:normal;word-spacing:0px;color:rgb(0,0,0)"><a href="mailto:dominic@steinitz.org" rel="noreferrer noreferrer" style="font-family:Helvetica" target="_blank">dominic@steinitz.org</a><br></div><div style="font-family:Helvetica;font-size:12px;font-style:normal;font-variant-caps:normal;font-weight:normal;letter-spacing:normal;text-align:start;text-indent:0px;text-transform:none;white-space:normal;word-spacing:0px;color:rgb(0,0,0)"><a href="http://idontgetoutmuch.org" rel="noreferrer noreferrer" style="font-family:Helvetica" target="_blank">http://idontgetoutmuch.org</a><br></div><div style="font-family:Helvetica;font-size:12px;font-style:normal;font-variant-caps:normal;font-weight:normal;letter-spacing:normal;text-align:start;text-indent:0px;text-transform:none;white-space:normal;word-spacing:0px;color:rgb(0,0,0)">Twitter: @idontgetoutmuch<br></div><div style="font-family:Helvetica;font-size:12px;font-style:normal;font-variant-caps:normal;font-weight:normal;letter-spacing:normal;text-align:start;text-indent:0px;text-transform:none;white-space:normal;word-spacing:0px;color:rgb(0,0,0)"><br></div><div><br></div></div><div><br></div></div><div><br></div></div><div>_______________________________________________<br></div><div> Libraries mailing list<br></div><div> <a href="mailto:Libraries@haskell.org" rel="noreferrer noreferrer" target="_blank">Libraries@haskell.org</a><br></div><div> <a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries" rel="noreferrer noreferrer noreferrer" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries</a><br></div></blockquote></div><div>_______________________________________________<br></div><div> Libraries mailing list<br></div><div> <a href="mailto:Libraries@haskell.org" rel="noreferrer" target="_blank">Libraries@haskell.org</a><br></div><div> <a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries" rel="noreferrer noreferrer" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries</a><br></div></blockquote></div><div>_______________________________________________<br></div><div> Libraries mailing list<br></div><div> <a href="mailto:Libraries@haskell.org" target="_blank">Libraries@haskell.org</a><br></div><div> <a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries</a><br></div></blockquote></div></div></div></blockquote><div><br></div>