one-liner-instances-0.1.2.1: Generics-based implementations for common typeclasses

Copyright(c) Justin Le 2018
LicenseBSD-3
Maintainerjustin@jle.im
Stabilityunstable
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

System.Random.OneLiner

Contents

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.

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.

Constructors

GRandom 

Fields

Instances

Functor GRandom Source # 

Methods

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

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

Foldable GRandom Source # 

Methods

fold :: Monoid m => GRandom m -> 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 # 

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 # 

Methods

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

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

Data a => Data (GRandom a) Source # 

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 :: (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 # 

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 # 
Show a => Show (GRandom a) Source # 

Methods

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

show :: GRandom a -> String #

showList :: [GRandom a] -> ShowS #

Generic (GRandom a) Source # 

Associated Types

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

Methods

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

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

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

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] #

randomRIO :: (GRandom a, GRandom a) -> IO (GRandom a) #

randomIO :: IO (GRandom a) #

type Rep (GRandom a) Source # 
type Rep (GRandom a) = D1 * (MetaData "GRandom" "System.Random.OneLiner" "one-liner-instances-0.1.2.1-4srMrmBSn2tGc07ShrSKFD" True) (C1 * (MetaCons "GRandom" PrefixI True) (S1 * (MetaSel (Just Symbol "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.

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.

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

randomRs implemented by repeatedly calling gRandomR.

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

randoms implemented by repeatedly calling gRandom.

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

randomRIO implemented by calling gRandomR on the global seed.

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

randomIO implemented by calling gRandom on the global seed.

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!

Constructors

GRandomSum 

Fields

Instances

Functor GRandomSum Source # 

Methods

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

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

Foldable GRandomSum Source # 

Methods

fold :: Monoid m => GRandomSum m -> 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 # 

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 # 

Methods

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

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

Data a => Data (GRandomSum a) Source # 

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 :: (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 # 
Read a => Read (GRandomSum a) Source # 
Show a => Show (GRandomSum a) Source # 
Generic (GRandomSum a) Source # 

Associated Types

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

Methods

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

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

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

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] #

randomRIO :: (GRandomSum a, GRandomSum a) -> IO (GRandomSum a) #

randomIO :: IO (GRandomSum a) #

type Rep (GRandomSum a) Source # 
type Rep (GRandomSum a) = D1 * (MetaData "GRandomSum" "System.Random.OneLiner" "one-liner-instances-0.1.2.1-4srMrmBSn2tGc07ShrSKFD" True) (C1 * (MetaCons "GRandomSum" PrefixI True) (S1 * (MetaSel (Just Symbol "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!

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.

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!

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

randoms implemented by repeatedly calling gRandomSum.

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!

gRandomIOSum :: forall a. (ADT a, Constraints a Random) => IO a Source #

randomIO implemented by calling gRandom on the global seed.