quickcheck-arbitrary-adt-0.3.1.0: Generic typeclasses for generating arbitrary ADTs

CopyrightPlow Technologies LLC
LicenseBSD3
Maintainermchaver@gmail.com
StabilityBeta
Safe HaskellSafe
LanguageHaskell2010

Test.QuickCheck.Arbitrary.ADT

Contents

Description

Type classes to assist random generation of values for various types of abstract data types.

Synopsis

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

instance ToADTArbitrary Fruit

instance Arbitrary Person where
  arbitrary = genericArbitrary

instance ToADTArbitrary 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.

Instances

Functor ConstructorArbitraryPair Source #

fmap applies a function to capArbitrary

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 # 
type Rep (ConstructorArbitraryPair a) = D1 * (MetaData "ConstructorArbitraryPair" "Test.QuickCheck.Arbitrary.ADT" "quickcheck-arbitrary-adt-0.3.1.0-3cXVxXLLUTHJdcN2TZ3pno" False) (C1 * (MetaCons "ConstructorArbitraryPair" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "capConstructor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "capArbitrary") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))))

data ADTArbitrarySingleton a Source #

ADTArbitrarySingleton holds the type name and one ConstructorArbitraryPair.

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 # 
type Rep (ADTArbitrarySingleton a) = D1 * (MetaData "ADTArbitrarySingleton" "Test.QuickCheck.Arbitrary.ADT" "quickcheck-arbitrary-adt-0.3.1.0-3cXVxXLLUTHJdcN2TZ3pno" False) (C1 * (MetaCons "ADTArbitrarySingleton" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "adtasModuleName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) ((:*:) * (S1 * (MetaSel (Just Symbol "adtasTypeName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "adtasCAP") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (ConstructorArbitraryPair a))))))

data ADTArbitrary a Source #

ADTArbitrary holds the type name and a ConstructorArbitraryPair for each constructor.

Instances

Functor ADTArbitrary Source #

fmap applies a function to each ConstructorArbitraryPair in adtCAPs.

Methods

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

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

Eq a => Eq (ADTArbitrary a) Source # 
Read a => Read (ADTArbitrary a) Source # 
Show a => Show (ADTArbitrary a) Source # 
Generic (ADTArbitrary a) Source # 

Associated Types

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

Methods

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

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

Arbitrary a => Arbitrary (ADTArbitrary a) Source # 
type Rep (ADTArbitrary a) Source # 
type Rep (ADTArbitrary a) = D1 * (MetaData "ADTArbitrary" "Test.QuickCheck.Arbitrary.ADT" "quickcheck-arbitrary-adt-0.3.1.0-3cXVxXLLUTHJdcN2TZ3pno" False) (C1 * (MetaCons "ADTArbitrary" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "adtModuleName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) ((:*:) * (S1 * (MetaSel (Just Symbol "adtTypeName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "adtCAPs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ConstructorArbitraryPair a])))))

Type classes

 

class 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 :: (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.

Minimal complete definition

gToADTArbitrarySingleton

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

gToADTArbitrary

Methods

gToADTArbitrary :: Proxy rep -> Gen (ADTArbitrary (rep a)) Source #

Instances

GToADTArbitrary (U1 *) Source # 

Methods

gToADTArbitrary :: Proxy (* -> *) (U1 *) -> Gen (ADTArbitrary (U1 * a)) Source #

Arbitrary a => GToADTArbitrary (K1 * i a) Source # 

Methods

gToADTArbitrary :: Proxy (* -> *) (K1 * i a) -> Gen (ADTArbitrary (K1 * i a a)) Source #

(GToADTArbitrary l, GToADTArbitrary r) => GToADTArbitrary ((:+:) * l r) Source # 

Methods

gToADTArbitrary :: Proxy (* -> *) ((* :+: l) r) -> Gen (ADTArbitrary ((* :+: l) r a)) Source #

(GToADTArbitrarySingleton l, GToADTArbitrarySingleton r) => GToADTArbitrary ((:*:) * l r) Source # 

Methods

gToADTArbitrary :: Proxy (* -> *) ((* :*: l) r) -> Gen (ADTArbitrary ((* :*: l) r a)) Source #

(Datatype Meta t, GToADTArbitrary rep) => GToADTArbitrary (M1 * D t rep) Source # 

Methods

gToADTArbitrary :: Proxy (* -> *) (M1 * D t rep) -> Gen (ADTArbitrary (M1 * D t rep a)) Source #

(Constructor Meta c, GToADTArbitrary rep) => GToADTArbitrary (M1 * C c rep) Source # 

Methods

gToADTArbitrary :: Proxy (* -> *) (M1 * C c rep) -> Gen (ADTArbitrary (M1 * C c rep a)) Source #

GToADTArbitrary rep => GToADTArbitrary (M1 * S t rep) Source # 

Methods

gToADTArbitrary :: Proxy (* -> *) (M1 * S t rep) -> Gen (ADTArbitrary (M1 * S t rep a)) 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

gArbitrary

Methods

gArbitrary :: Gen (rep a) Source #

Instances

GArbitrary (U1 *) Source # 

Methods

gArbitrary :: Gen (U1 * a) Source #

Arbitrary a => GArbitrary (K1 * i a) Source # 

Methods

gArbitrary :: Gen (K1 * i a a) Source #

(GArbitrary l, GArbitrary r) => GArbitrary ((:+:) * l r) Source # 

Methods

gArbitrary :: Gen ((* :+: l) r a) Source #

(GArbitrary l, GArbitrary r) => GArbitrary ((:*:) * l r) Source # 

Methods

gArbitrary :: Gen ((* :*: l) r a) Source #

GArbitrary rep => GArbitrary (M1 * i t rep) Source # 

Methods

gArbitrary :: Gen (M1 * i t rep a) 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.