| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Test.QuickCheck.Arbitrary.ADT
Description
Type classes to assist random generation of values for various types of abstract data types.
- data ConstructorArbitraryPair a = ConstructorArbitraryPair {
- _capConstructor :: String
- _capArbitrary :: a
- data ADTArbitrarySingleton a = ADTArbitrarySingleton {}
- data ADTArbitrary a = ADTArbitrary {}
- class Arbitrary a => ToADTArbitrary a where
- class GToADTArbitrarySingleton rep where
- class GToADTArbitrary rep where
- class GArbitrary rep where
- genericArbitrary :: (Generic a, GArbitrary (Rep a)) => Gen a
How to use this library
How to use ToADTArbitrary with Generic.
{-# LANGUAGE DeriveGeneric #-}
import Data.Proxy
import GHC.Generics
import Test.QuickCheck
import Test.QuickCheck.Arbitrary.ADT
-- Sum Type, multiple constructors with parameters
data Fruit = Apple Int
| Orange String Int
| PassionFruit Int String Int
deriving (Generic, Show)
-- Product Type, single constructor
data Person = Person {
name :: String
, age :: Int
} deriving (Generic, Show)Any type that implements ToADTArbitrary must also implement Arbitrary.
These examples all require that the data type is an instance of Generic.
instance Arbitrary Fruit where arbitrary =genericArbitraryinstanceToADTArbitraryFruit instance Arbitrary Person where arbitrary =genericArbitraryinstanceToADTArbitraryPerson
Now we can use toADTArbitrarySingleton to produce an arbitrary value of
one random constructor along with some metadata. toADTArbitrary will
produce an arbitrary value for each constructor and return it along with
a String of the constructor name.
λ> generate (toADTArbitrarySingleton (Proxy :: Proxy Fruit))
ADTArbitrarySingleton {
_adtasTypeName = "Fruit"
, _adtasCAP = ConstructorArbitraryPair {
_capConstructor = "Apple", _capArbitrary = Apple 30}}
λ> generate (toADTArbitrary (Proxy :: Proxy Fruit))
ADTArbitrary {
_adtTypeName = "Fruit"
, _adtCAPs = [
ConstructorArbitraryPair {
_capConstructor = "Apple"
, _capArbitrary = Apple 17}
, ConstructorArbitraryPair {
_capConstructor = "Orange"
, _capArbitrary = Orange "abcdef" 18}
, ConstructorArbitraryPair {
_capConstructor = "PassionFruit"
, _capArbitrary = PassionFruit 16 "datadata" 6}]}
λ> generate (toADTArbitrarySingleton (Proxy :: Proxy Person))
ADTArbitrarySingleton {
_adtasTypeName = "Person"
, _adtasCAP = ConstructorArbitraryPair {_capConstructor = "Person", _capArbitrary = Person {name = "John Doe", age = 30}}}
λ> generate (toADTArbitrary (Proxy :: Proxy Person))
ADTArbitrary {
_adtTypeName = "Person"
, _adtCAPs = [ConstructorArbitraryPair {_capConstructor = "Person", _capArbitrary = Person {name = "Jane Doe", age = 15}}]}
Data types
data ConstructorArbitraryPair a Source #
ConstructorArbitraryPair holds the construct name as a string and an arbitrary instance of that constructor.
Constructors
| ConstructorArbitraryPair | |
Fields
| |
Instances
| Functor ConstructorArbitraryPair Source # | fmap applies a function to |
| Eq a => Eq (ConstructorArbitraryPair a) Source # | |
| Read a => Read (ConstructorArbitraryPair a) Source # | |
| Show a => Show (ConstructorArbitraryPair a) Source # | |
| Generic (ConstructorArbitraryPair a) Source # | |
| Arbitrary a => Arbitrary (ConstructorArbitraryPair a) Source # | |
| type Rep (ConstructorArbitraryPair a) Source # | |
data ADTArbitrarySingleton a Source #
ADTArbitrarySingleton holds the type name and one ConstructorArbitraryPair.
Constructors
| ADTArbitrarySingleton | |
Fields | |
Instances
| Functor ADTArbitrarySingleton Source # | fmap applies a function to the ConstructorArbitraryPair in _adtasCAP. |
| Eq a => Eq (ADTArbitrarySingleton a) Source # | |
| Read a => Read (ADTArbitrarySingleton a) Source # | |
| Show a => Show (ADTArbitrarySingleton a) Source # | |
| Generic (ADTArbitrarySingleton a) Source # | |
| Arbitrary a => Arbitrary (ADTArbitrarySingleton a) Source # | |
| type Rep (ADTArbitrarySingleton a) Source # | |
data ADTArbitrary a Source #
ADTArbitrary holds the type name and a ConstructorArbitraryPair for each constructor.
Constructors
| ADTArbitrary | |
Fields
| |
Instances
| Functor ADTArbitrary Source # | fmap applies a function to each ConstructorArbitraryPair in _adtCAPs. |
| Eq a => Eq (ADTArbitrary a) Source # | |
| Read a => Read (ADTArbitrary a) Source # | |
| Show a => Show (ADTArbitrary a) Source # | |
| Generic (ADTArbitrary a) Source # | |
| Arbitrary a => Arbitrary (ADTArbitrary a) Source # | |
| type Rep (ADTArbitrary a) Source # | |
Type classes
class Arbitrary a => ToADTArbitrary a where Source #
ToADTArbitrary generalizes the production of arbitrary values for Sum types. and Product types.
Methods
toADTArbitrarySingleton :: Proxy a -> Gen (ADTArbitrarySingleton a) Source #
produce an arbitrary instance of one random constructor
toADTArbitrarySingleton :: (Arbitrary a, Generic a, GToADTArbitrarySingleton (Rep a), GToADTArbitrarySingleton (Rep (ADTArbitrarySingleton a))) => Proxy a -> Gen (ADTArbitrarySingleton a) Source #
produce an arbitrary instance of one random constructor
toADTArbitrary :: Proxy a -> Gen (ADTArbitrary a) Source #
produce an arbitrary instance for each constructor in type a.
toADTArbitrary :: (Arbitrary a, Generic a, GToADTArbitrary (Rep a), GToADTArbitrary (Rep (ADTArbitrary a))) => Proxy a -> Gen (ADTArbitrary a) Source #
produce an arbitrary instance for each constructor in type a.
Generic type classes
class GToADTArbitrarySingleton rep where Source #
GToADTArbitrarySingleton creates an arbitrary value and returns the name of the constructor that was used to create it and the type name.
Minimal complete definition
Methods
gToADTArbitrarySingleton :: Proxy rep -> Gen (ADTArbitrarySingleton (rep a)) Source #
Instances
| GToADTArbitrarySingleton U1 Source # | |
| Arbitrary a => GToADTArbitrarySingleton (K1 i a) Source # | |
| (GToADTArbitrarySingleton l, GToADTArbitrarySingleton r) => GToADTArbitrarySingleton ((:+:) l r) Source # | |
| (GToADTArbitrarySingleton l, GToADTArbitrarySingleton r) => GToADTArbitrarySingleton ((:*:) l r) Source # | |
| (Datatype Meta t, Typeable Meta t, GToADTArbitrarySingleton rep) => GToADTArbitrarySingleton (M1 D t rep) Source # | |
| (Constructor Meta c, GToADTArbitrarySingleton rep) => GToADTArbitrarySingleton (M1 C c rep) Source # | |
| GToADTArbitrarySingleton rep => GToADTArbitrarySingleton (M1 S t rep) Source # | |
class GToADTArbitrary rep where Source #
GToADTArbitrary is a typeclass for generalizing the creation of a list of arbitrary values for each constructor of a type. It also returns the name of the constructor and the type name for reference and file creation.
Minimal complete definition
Methods
gToADTArbitrary :: Proxy rep -> Gen (ADTArbitrary (rep a)) Source #
Instances
| GToADTArbitrary U1 Source # | |
| Arbitrary a => GToADTArbitrary (K1 i a) Source # | |
| (GToADTArbitrary l, GToADTArbitrary r) => GToADTArbitrary ((:+:) l r) Source # | |
| (GToADTArbitrarySingleton l, GToADTArbitrary l, GToADTArbitrarySingleton r, GToADTArbitrary r) => GToADTArbitrary ((:*:) l r) Source # | |
| (Datatype Meta t, GToADTArbitrary rep) => GToADTArbitrary (M1 D t rep) Source # | |
| (Constructor Meta c, GToADTArbitrary rep) => GToADTArbitrary (M1 C c rep) Source # | |
| GToADTArbitrary rep => GToADTArbitrary (M1 S t rep) Source # | |
class GArbitrary rep where Source #
GArbitrary is a typeclass for generalizing the creation of single arbitrary product and sum types. It creates an arbitrary generating function of this style: TypeName $ arbitrary * arbitrary.
Minimal complete definition
Methods
gArbitrary :: Gen (rep a) Source #
Instances
| GArbitrary U1 Source # | |
| Arbitrary a => GArbitrary (K1 i a) Source # | |
| (GArbitrary l, GArbitrary r) => GArbitrary ((:+:) l r) Source # | |
| (GArbitrary l, GArbitrary r) => GArbitrary ((:*:) l r) Source # | |
| GArbitrary rep => GArbitrary (M1 i t rep) Source # | |
genericArbitrary :: (Generic a, GArbitrary (Rep a)) => Gen a Source #