Copyright | Plow Technologies LLC |
---|---|
License | BSD3 |
Maintainer | mchaver@gmail.com |
Stability | Beta |
Safe Haskell | Safe |
Language | Haskell2010 |
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 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 =genericArbitrary
instanceToADTArbitrary
Fruit instance Arbitrary Person where arbitrary =genericArbitrary
instanceToADTArbitrary
Person
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 { adtasModuleName = "Ghci1" , adtasTypeName = "Fruit" , adtasCAP = ConstructorArbitraryPair { capConstructor = "Apple", capArbitrary = Apple 30}} λ> generate (toADTArbitrary (Proxy :: Proxy Fruit)) ADTArbitrary { adtModuleName = "Ghci1" , 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 { adtasModuleName = "Ghci1" , adtasTypeName = "Person" , adtasCAP = ConstructorArbitraryPair {capConstructor = "Person", capArbitrary = Person {name = "John Doe", age = 30}}} λ> generate (toADTArbitrary (Proxy :: Proxy Person)) ADTArbitrary { adtModuleName = "Ghci1" , 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.
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.
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.
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 ToADTArbitrary a where Source #
ToADTArbitrary generalizes the production of arbitrary values for Sum types. and Product types.
toADTArbitrarySingleton :: Proxy a -> Gen (ADTArbitrarySingleton a) Source #
produce an arbitrary instance of one random constructor
toADTArbitrarySingleton :: (Generic a, GToADTArbitrarySingleton (Rep 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 :: (Generic a, GToADTArbitrary (Rep 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.
gToADTArbitrarySingleton :: Proxy rep -> Gen (ADTArbitrarySingleton (rep a)) Source #
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.
gToADTArbitrary :: Proxy rep -> Gen (ADTArbitrary (rep a)) Source #
GToADTArbitrary (U1 *) Source # | |
Arbitrary a => GToADTArbitrary (K1 * i a) Source # | |
(GToADTArbitrary l, GToADTArbitrary r) => GToADTArbitrary ((:+:) * l r) Source # | |
(GToADTArbitrarySingleton l, GToADTArbitrarySingleton 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
.
gArbitrary :: Gen (rep a) Source #
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 #
Create a arbitrary generator for a specified a type in a naive way. Please be careful when using this function, particularly for recursive types.