one-liner-instances-0.1.3.0: Generics-based implementations for common typeclasses
Copyright(c) Justin Le 2021
LicenseBSD-3
Maintainerjustin@jle.im
Stabilityunstable
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

System.Random.OneLiner

Description

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

Single constructor

Newtype wrapper

newtype GRandom a Source #

If a is a data type with a single constructor whose fields are all instances of Random, then GRandom a has a Random 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

Constructors

GRandom 

Fields

Instances

Instances details
Functor GRandom Source # 
Instance details

Defined in System.Random.OneLiner

Methods

fmap :: (a -> b) -> GRandom a -> GRandom b #

(<$) :: a -> GRandom b -> GRandom a #

Foldable GRandom Source # 
Instance details

Defined in System.Random.OneLiner

Methods

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 #

toList :: GRandom a -> [a] #

null :: GRandom a -> Bool #

length :: GRandom a -> Int #

elem :: Eq a => a -> GRandom a -> Bool #

maximum :: Ord a => GRandom a -> a #

minimum :: Ord a => GRandom a -> a #

sum :: Num a => GRandom a -> a #

product :: Num a => GRandom a -> a #

Traversable GRandom Source # 
Instance details

Defined in System.Random.OneLiner

Methods

traverse :: Applicative f => (a -> f b) -> GRandom a -> f (GRandom b) #

sequenceA :: Applicative f => GRandom (f a) -> f (GRandom a) #

mapM :: Monad m => (a -> m b) -> GRandom a -> m (GRandom b) #

sequence :: Monad m => GRandom (m a) -> m (GRandom a) #

Eq a => Eq (GRandom a) Source # 
Instance details

Defined in System.Random.OneLiner

Methods

(==) :: GRandom a -> GRandom a -> Bool #

(/=) :: GRandom a -> GRandom a -> Bool #

Data a => Data (GRandom a) Source # 
Instance details

Defined in System.Random.OneLiner

Methods

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 # 
Instance details

Defined in System.Random.OneLiner

Methods

compare :: GRandom a -> GRandom a -> Ordering #

(<) :: GRandom a -> GRandom a -> Bool #

(<=) :: GRandom a -> GRandom a -> Bool #

(>) :: GRandom a -> GRandom a -> Bool #

(>=) :: GRandom a -> GRandom a -> Bool #

max :: GRandom a -> GRandom a -> GRandom a #

min :: GRandom a -> GRandom a -> GRandom a #

Read a => Read (GRandom a) Source # 
Instance details

Defined in System.Random.OneLiner

Show a => Show (GRandom a) Source # 
Instance details

Defined in System.Random.OneLiner

Methods

showsPrec :: Int -> GRandom a -> ShowS #

show :: GRandom a -> String #

showList :: [GRandom a] -> ShowS #

Generic (GRandom a) Source # 
Instance details

Defined in System.Random.OneLiner

Associated Types

type Rep (GRandom a) :: Type -> Type #

Methods

from :: GRandom a -> Rep (GRandom a) x #

to :: Rep (GRandom a) x -> GRandom a #

(ADTRecord a, Constraints a Random) => Random (GRandom a) Source # 
Instance details

Defined in System.Random.OneLiner

Methods

randomR :: RandomGen g => (GRandom a, GRandom a) -> g -> (GRandom a, g) #

random :: RandomGen g => g -> (GRandom a, g) #

randomRs :: RandomGen g => (GRandom a, GRandom a) -> g -> [GRandom a] #

randoms :: RandomGen g => g -> [GRandom a] #

type Rep (GRandom a) Source # 
Instance details

Defined in System.Random.OneLiner

type Rep (GRandom a) = D1 ('MetaData "GRandom" "System.Random.OneLiner" "one-liner-instances-0.1.3.0-KGYaKgOm9Pn8Wcz4AhCIIX" 'True) (C1 ('MetaCons "GRandom" 'PrefixI 'True) (S1 ('MetaSel ('Just "getGRandom") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Generics-derived methods

gRandomR :: forall a g. (ADTRecord a, Constraints a Random, RandomGen g) => (a, a) -> g -> (a, g) Source #

randomR implemented by sequencing randomR between all components

Requires the type to have only a single constructor.

Since: 0.1.2.1

gRandom :: forall a g. (ADTRecord a, Constraints a Random, RandomGen g) => g -> (a, g) Source #

random implemented by sequencing random for all components.

Requires the type to have only a single constructor.

Since: 0.1.2.1

gRandomRs :: forall a g. (ADTRecord a, Constraints a Random, RandomGen g) => (a, a) -> g -> [a] Source #

randomRs implemented by repeatedly calling gRandomR.

Since: 0.1.2.1

gRandoms :: forall a g. (ADTRecord a, Constraints a Random, RandomGen g) => g -> [a] Source #

randoms implemented by repeatedly calling gRandom.

Since: 0.1.2.1

gRandomRIO :: forall a. (ADTRecord a, Constraints a Random) => (a, a) -> IO a Source #

randomRIO implemented by calling gRandomR on the global seed.

Since: 0.1.2.1

gRandomIO :: forall a. (ADTRecord a, Constraints a Random) => IO a Source #

randomIO implemented by calling gRandom on the global seed.

Since: 0.1.2.1

Multiple constructor

Newtype wrapper

newtype GRandomSum a Source #

If a is a data type whose fields are all instances of Random, then GRandom a has a Random 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

Constructors

GRandomSum 

Fields

Instances

Instances details
Functor GRandomSum Source # 
Instance details

Defined in System.Random.OneLiner

Methods

fmap :: (a -> b) -> GRandomSum a -> GRandomSum b #

(<$) :: a -> GRandomSum b -> GRandomSum a #

Foldable GRandomSum Source # 
Instance details

Defined in System.Random.OneLiner

Methods

fold :: Monoid m => GRandomSum m -> m #

foldMap :: Monoid m => (a -> m) -> GRandomSum a -> m #

foldMap' :: Monoid m => (a -> m) -> GRandomSum a -> m #

foldr :: (a -> b -> b) -> b -> GRandomSum a -> b #

foldr' :: (a -> b -> b) -> b -> GRandomSum a -> b #

foldl :: (b -> a -> b) -> b -> GRandomSum a -> b #

foldl' :: (b -> a -> b) -> b -> GRandomSum a -> b #

foldr1 :: (a -> a -> a) -> GRandomSum a -> a #

foldl1 :: (a -> a -> a) -> GRandomSum a -> a #

toList :: GRandomSum a -> [a] #

null :: GRandomSum a -> Bool #

length :: GRandomSum a -> Int #

elem :: Eq a => a -> GRandomSum a -> Bool #

maximum :: Ord a => GRandomSum a -> a #

minimum :: Ord a => GRandomSum a -> a #

sum :: Num a => GRandomSum a -> a #

product :: Num a => GRandomSum a -> a #

Traversable GRandomSum Source # 
Instance details

Defined in System.Random.OneLiner

Methods

traverse :: Applicative f => (a -> f b) -> GRandomSum a -> f (GRandomSum b) #

sequenceA :: Applicative f => GRandomSum (f a) -> f (GRandomSum a) #

mapM :: Monad m => (a -> m b) -> GRandomSum a -> m (GRandomSum b) #

sequence :: Monad m => GRandomSum (m a) -> m (GRandomSum a) #

Eq a => Eq (GRandomSum a) Source # 
Instance details

Defined in System.Random.OneLiner

Methods

(==) :: GRandomSum a -> GRandomSum a -> Bool #

(/=) :: GRandomSum a -> GRandomSum a -> Bool #

Data a => Data (GRandomSum a) Source # 
Instance details

Defined in System.Random.OneLiner

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRandomSum a -> c (GRandomSum a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRandomSum a) #

toConstr :: GRandomSum a -> Constr #

dataTypeOf :: GRandomSum a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRandomSum a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRandomSum a)) #

gmapT :: (forall b. Data b => b -> b) -> GRandomSum a -> GRandomSum a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRandomSum a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRandomSum a -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRandomSum a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRandomSum a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRandomSum a -> m (GRandomSum a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRandomSum a -> m (GRandomSum a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRandomSum a -> m (GRandomSum a) #

Ord a => Ord (GRandomSum a) Source # 
Instance details

Defined in System.Random.OneLiner

Read a => Read (GRandomSum a) Source # 
Instance details

Defined in System.Random.OneLiner

Show a => Show (GRandomSum a) Source # 
Instance details

Defined in System.Random.OneLiner

Generic (GRandomSum a) Source # 
Instance details

Defined in System.Random.OneLiner

Associated Types

type Rep (GRandomSum a) :: Type -> Type #

Methods

from :: GRandomSum a -> Rep (GRandomSum a) x #

to :: Rep (GRandomSum a) x -> GRandomSum a #

(ADT a, Constraints a Random) => Random (GRandomSum a) Source # 
Instance details

Defined in System.Random.OneLiner

Methods

randomR :: RandomGen g => (GRandomSum a, GRandomSum a) -> g -> (GRandomSum a, g) #

random :: RandomGen g => g -> (GRandomSum a, g) #

randomRs :: RandomGen g => (GRandomSum a, GRandomSum a) -> g -> [GRandomSum a] #

randoms :: RandomGen g => g -> [GRandomSum a] #

type Rep (GRandomSum a) Source # 
Instance details

Defined in System.Random.OneLiner

type Rep (GRandomSum a) = D1 ('MetaData "GRandomSum" "System.Random.OneLiner" "one-liner-instances-0.1.3.0-KGYaKgOm9Pn8Wcz4AhCIIX" 'True) (C1 ('MetaCons "GRandomSum" 'PrefixI 'True) (S1 ('MetaSel ('Just "getGRandomSum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Generics-derived methods

gRandomRSum :: forall a g. (ADT a, Constraints a Random, RandomGen g) => (a, a) -> g -> (a, g) Source #

randomR implemented by sequencing randomR between all components.

If given a range of items made with different constructors, will be error!

Since: 0.1.2.1

gRandomSum :: forall a g. (ADT a, Constraints a Random, RandomGen g) => g -> (a, g) Source #

random implemented by selecting a random constructor and sequencing random for all components.

Since: 0.1.2.1

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 #

randomIO implemented by calling gRandom on the global seed.