Copyright | (c) Justin Le 2021 |
---|---|
License | BSD-3 |
Maintainer | justin@jle.im |
Stability | unstable |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Derived methods for Random
, using Generics.OneLiner and
GHC.Generics.
Can be used for any types (deriving Generic
) made with a single
constructor, where every field is an instance of Random
.
Also includes a newtype wrapper that imbues any such data type with
instant Random
instances, which can one day be used with DerivingVia
syntax to derive instances automatically.
Since: 0.1.2.1
Synopsis
- newtype GRandom a = GRandom {
- getGRandom :: a
- gRandomR :: forall a g. (ADTRecord a, Constraints a Random, RandomGen g) => (a, a) -> g -> (a, g)
- gRandom :: forall a g. (ADTRecord a, Constraints a Random, RandomGen g) => g -> (a, g)
- gRandomRs :: forall a g. (ADTRecord a, Constraints a Random, RandomGen g) => (a, a) -> g -> [a]
- gRandoms :: forall a g. (ADTRecord a, Constraints a Random, RandomGen g) => g -> [a]
- gRandomRIO :: forall a. (ADTRecord a, Constraints a Random) => (a, a) -> IO a
- gRandomIO :: forall a. (ADTRecord a, Constraints a Random) => IO a
- newtype GRandomSum a = GRandomSum {
- getGRandomSum :: a
- gRandomRSum :: forall a g. (ADT a, Constraints a Random, RandomGen g) => (a, a) -> g -> (a, g)
- gRandomSum :: forall a g. (ADT a, Constraints a Random, RandomGen g) => g -> (a, g)
- gRandomRSums :: forall a g. (ADT a, Constraints a Random, RandomGen g) => (a, a) -> g -> [a]
- gRandomSums :: forall a g. (ADT a, Constraints a Random, RandomGen g) => g -> [a]
- gRandomRIOSum :: forall a. (ADT a, Constraints a Random) => (a, a) -> IO a
- gRandomIOSum :: forall a. (ADT a, Constraints a Random) => IO a
Single constructor
Newtype wrapper
If a
is a data type with a single constructor whose fields are all
instances of Random
, then
has a GRandom
aRandom
instance.
Will one day be able to be used with DerivingVia syntax, to derive instances automatically.
Only works with data types with single constructors. If you need it to
work with types of multiple constructors, consider GRandomSum
.
Since: 0.1.2.1
GRandom | |
|
Instances
Functor GRandom Source # | |
Foldable GRandom Source # | |
Defined in System.Random.OneLiner fold :: Monoid m => GRandom m -> m # foldMap :: Monoid m => (a -> m) -> GRandom a -> m # foldMap' :: Monoid m => (a -> m) -> GRandom a -> m # foldr :: (a -> b -> b) -> b -> GRandom a -> b # foldr' :: (a -> b -> b) -> b -> GRandom a -> b # foldl :: (b -> a -> b) -> b -> GRandom a -> b # foldl' :: (b -> a -> b) -> b -> GRandom a -> b # foldr1 :: (a -> a -> a) -> GRandom a -> a # foldl1 :: (a -> a -> a) -> GRandom a -> a # elem :: Eq a => a -> GRandom a -> Bool # maximum :: Ord a => GRandom a -> a # minimum :: Ord a => GRandom a -> a # | |
Traversable GRandom Source # | |
Eq a => Eq (GRandom a) Source # | |
Data a => Data (GRandom a) Source # | |
Defined in System.Random.OneLiner gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRandom a -> c (GRandom a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRandom a) # toConstr :: GRandom a -> Constr # dataTypeOf :: GRandom a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRandom a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRandom a)) # gmapT :: (forall b. Data b => b -> b) -> GRandom a -> GRandom a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRandom a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRandom a -> r # gmapQ :: (forall d. Data d => d -> u) -> GRandom a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> GRandom a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRandom a -> m (GRandom a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRandom a -> m (GRandom a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRandom a -> m (GRandom a) # | |
Ord a => Ord (GRandom a) Source # | |
Defined in System.Random.OneLiner | |
Read a => Read (GRandom a) Source # | |
Show a => Show (GRandom a) Source # | |
Generic (GRandom a) Source # | |
(ADTRecord a, Constraints a Random) => Random (GRandom a) Source # | |
type Rep (GRandom a) Source # | |
Defined in System.Random.OneLiner |
Generics-derived methods
gRandomR :: forall a g. (ADTRecord a, Constraints a Random, RandomGen g) => (a, a) -> g -> (a, g) Source #
gRandomRs :: forall a g. (ADTRecord a, Constraints a Random, RandomGen g) => (a, a) -> g -> [a] Source #
gRandomRIO :: forall a. (ADTRecord a, Constraints a Random) => (a, a) -> IO a Source #
Multiple constructor
Newtype wrapper
newtype GRandomSum a Source #
If a
is a data type whose fields are all instances of Random
, then
has a GRandom
aRandom
instance.
Will one day be able to be used with DerivingVia syntax, to derive instances automatically.
A version of GRandom
that works for data types with multiple
constructors. If your type has only one constructor, it might be more
performant to use GRandom
.
Note that the "ranged" variants are partial: if given a range of items
made with different constructors, will be error
!
Since: 0.1.2.1
GRandomSum | |
|
Instances
Generics-derived methods
gRandomRSum :: forall a g. (ADT a, Constraints a Random, RandomGen g) => (a, a) -> g -> (a, g) Source #
gRandomSum :: forall a g. (ADT a, Constraints a Random, RandomGen g) => g -> (a, g) Source #
gRandomRSums :: forall a g. (ADT a, Constraints a Random, RandomGen g) => (a, a) -> g -> [a] Source #
randomRs
implemented by repeatedly calling gRandomRSum
.
If given a range of items made with different constructors, will be
error
!
Since: 0.1.2.1
gRandomSums :: forall a g. (ADT a, Constraints a Random, RandomGen g) => g -> [a] Source #
randoms
implemented by repeatedly calling gRandomSum
.
Since: 0.1.2.1
gRandomRIOSum :: forall a. (ADT a, Constraints a Random) => (a, a) -> IO a Source #
randomRIO
implemented by calling gRandomRSum
on the global seed.
If given a range of items made with different constructors, will be
error
!
Since: 0.1.2.1
gRandomIOSum :: forall a. (ADT a, Constraints a Random) => IO a Source #