3
3
{-# LANGUAGE FunctionalDependencies #-}
4
4
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
5
5
{-# LANGUAGE RankNTypes #-}
6
+ {-# LANGUAGE ScopedTypeVariables #-}
6
7
{-# LANGUAGE Trustworthy #-}
7
8
{-# LANGUAGE TypeFamilies #-}
8
9
{-# LANGUAGE UndecidableInstances #-}
@@ -29,11 +30,15 @@ module System.Random.Stateful
29
30
-- $interfaces
30
31
, StatefulGen (.. )
31
32
, FrozenGen (.. )
32
- , RandomGenM (.. )
33
33
, withMutableGen
34
34
, withMutableGen_
35
35
, randomM
36
36
, randomRM
37
+ , splitFrozenM
38
+ , splitMutableM
39
+
40
+ -- ** Deprecated
41
+ , RandomGenM (.. )
37
42
, splitGenM
38
43
39
44
-- * Monadic adapters for pure pseudo-random number generators #monadicadapters#
@@ -216,13 +221,16 @@ import System.Random.Internal
216
221
-- @since 1.2.0
217
222
class (RandomGen r , StatefulGen g m ) => RandomGenM g r m | g -> r where
218
223
applyRandomGenM :: (r -> (a , r )) -> g -> m a
224
+ {-# DEPRECATED applyRandomGenM "In favor of `modifyM`" #-}
225
+ {-# DEPRECATED RandomGenM "In favor of `FrozenGen`" #-}
219
226
220
227
-- | Splits a pseudo-random number generator into two. Overwrites the mutable
221
228
-- wrapper with one of the resulting generators and returns the other.
222
229
--
223
230
-- @since 1.2.0
224
231
splitGenM :: RandomGenM g r m => g -> m r
225
232
splitGenM = applyRandomGenM split
233
+ {-# DEPRECATED splitGenM "In favor of `splitM`" #-}
226
234
227
235
instance (RandomGen r , MonadIO m ) => RandomGenM (IOGenM r ) r m where
228
236
applyRandomGenM = applyIOGen
@@ -301,8 +309,8 @@ uniformListM n gen = replicateM n (uniformM gen)
301
309
-- 0.6268211351114487
302
310
--
303
311
-- @since 1.2.0
304
- randomM :: (Random a , RandomGenM g r m ) => g -> m a
305
- randomM = applyRandomGenM random
312
+ randomM :: forall a g m . (Random a , RandomGen g , FrozenGen g m ) => MutableGen g m -> m a
313
+ randomM = flip modifyM random
306
314
307
315
-- | Generates a pseudo-random value using monadic interface and `Random` instance.
308
316
--
@@ -321,8 +329,8 @@ randomM = applyRandomGenM random
321
329
-- 2
322
330
--
323
331
-- @since 1.2.0
324
- randomRM :: (Random a , RandomGenM g r m ) => (a , a ) -> g -> m a
325
- randomRM r = applyRandomGenM (randomR r)
332
+ randomRM :: forall a g m . (Random a , RandomGen g , FrozenGen g m ) => (a , a ) -> MutableGen g m -> m a
333
+ randomRM r = flip modifyM (randomR r)
326
334
327
335
-- | Wraps an 'IORef' that holds a pure pseudo-random number generator. All
328
336
-- operations are performed atomically.
@@ -379,6 +387,11 @@ instance (RandomGen g, MonadIO m) => FrozenGen (AtomicGen g) m where
379
387
type MutableGen (AtomicGen g ) m = AtomicGenM g
380
388
freezeGen = fmap AtomicGen . liftIO . readIORef . unAtomicGenM
381
389
thawGen (AtomicGen g) = newAtomicGenM g
390
+ modifyM (AtomicGenM ioRef) f =
391
+ liftIO $ atomicModifyIORef' ioRef $ \ g ->
392
+ case f (AtomicGen g) of
393
+ (a, AtomicGen g') -> (g', a)
394
+ {-# INLINE modifyM #-}
382
395
383
396
-- | Atomically applies a pure operation to the wrapped pseudo-random number
384
397
-- generator.
@@ -454,7 +467,12 @@ instance (RandomGen g, MonadIO m) => FrozenGen (IOGen g) m where
454
467
type MutableGen (IOGen g ) m = IOGenM g
455
468
freezeGen = fmap IOGen . liftIO . readIORef . unIOGenM
456
469
thawGen (IOGen g) = newIOGenM g
457
-
470
+ modifyM (IOGenM ref) f = liftIO $ do
471
+ g <- readIORef ref
472
+ let (a, IOGen g') = f (IOGen g)
473
+ g' `seq` writeIORef ref g'
474
+ pure a
475
+ {-# INLINE modifyM #-}
458
476
459
477
-- | Applies a pure operation to the wrapped pseudo-random number generator.
460
478
--
@@ -514,6 +532,12 @@ instance RandomGen g => FrozenGen (STGen g) (ST s) where
514
532
type MutableGen (STGen g ) (ST s ) = STGenM g s
515
533
freezeGen = fmap STGen . readSTRef . unSTGenM
516
534
thawGen (STGen g) = newSTGenM g
535
+ modifyM (STGenM ref) f = do
536
+ g <- readSTRef ref
537
+ let (a, STGen g') = f (STGen g)
538
+ g' `seq` writeSTRef ref g'
539
+ pure a
540
+ {-# INLINE modifyM #-}
517
541
518
542
519
543
-- | Applies a pure operation to the wrapped pseudo-random number generator.
@@ -609,6 +633,12 @@ instance RandomGen g => FrozenGen (TGen g) STM where
609
633
type MutableGen (TGen g ) STM = TGenM g
610
634
freezeGen = fmap TGen . readTVar . unTGenM
611
635
thawGen (TGen g) = newTGenM g
636
+ modifyM (TGenM ref) f = do
637
+ g <- readTVar ref
638
+ let (a, TGen g') = f (TGen g)
639
+ g' `seq` writeTVar ref g'
640
+ pure a
641
+ {-# INLINE modifyM #-}
612
642
613
643
614
644
-- | Applies a pure operation to the wrapped pseudo-random number generator.
0 commit comments