generic-arbitrary: Generic implementation for QuickCheck's Arbitrary

[ generic, library, mit ] [ Propose Tags ]

Generic implementations of methods of the Arbitrary class from the QuickCheck library. The approach taken here can lead to diverging instances for mutually recursive types but is safe for simply recursive ones and guarantees flat distribution for constructors of sum-types.


[Skip to Readme]

Modules

[Index] [Quick Jump]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1.0, 0.2.0, 0.2.1, 0.2.2, 1.0.0, 1.0.1
Change log CHANGELOG.md
Dependencies base (>=4.8 && <5), QuickCheck [details]
License MIT
Author Typeable.io contributors
Maintainer makeit@typeable.io
Category Generic
Home page http://github.com/typeable/generic-arbitrary#readme
Source repo head: git clone https://github.com/typeable/generic-arbitrary.git
Uploaded by AlekseyUymanov at 2022-08-12T07:36:58Z
Distributions LTSHaskell:1.0.1, NixOS:1.0.1, Stackage:1.0.1
Reverse Dependencies 6 direct, 2 indirect [details]
Downloads 12901 total (111 in the last 30 days)
Rating 2.0 (votes: 1) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2022-08-12 [all 1 reports]

Readme for generic-arbitrary-1.0.0

[back to package description]

generic-arbitrary

Haskell-CI

What?

Package for deriving Arbitrary via Generic.

import           GHC.Generics                      (Generic)
import           Test.QuickCheck
import           Test.QuickCheck.Arbitrary.Generic

data Expr
  = Lit Int
  | Add Expr Expr
  | Mul Expr Expr
  deriving (Eq, Show, Generic)
  deriving Arbitrary via (GenericArbitrary Expr)

Older versions of this package had a problem with hanging arbitrary method. Since 1.0.0 this problem almost solved.

For QuickCheck older than 2.14.0 the GenericArbitrary is not available, so you will need to write instances more verbosely

data Expr
  = Lit Int
  | Add Expr Expr
  | Mul Expr Expr
  deriving (Eq, Show, Generic)

instance Arbitrary Expr where
  arbitrary = genericArbitrary
  shrink = genericShrink

Which is generally the same.

Infinite terms problem

The generic-arbitrary can partially handle the problem with recursive types. Assume the type R

data R = R R
  deriving Generic

there is no instance

instance Arbitrary R where
  arbitrary = genericArbitrary
  shrink = genericShrink

If you try to compile this you will get a type level error

• R refers to itself in all constructors

Which means that there is no finite term for R because it is recursive in all it's constructors. But, if you correct the definition of R like this.

data R = R R | F
  deriving Generic

Then it will compile. And the arbitrary generated will not hang forever, because it respects the size parameter.

Limitation

There is a limitation of recursion detection:

data R1 = R1 R2
  deriving (Eq, Ord, Show, Generic)
  deriving anyclass NFData
  deriving Arbitrary via (GenericArbitrary R1)

data R2 = R2 R1
  deriving (Eq, Ord, Show, Generic)
  deriving anyclass NFData
  deriving Arbitrary via (GenericArbitrary R2)

This code will compile and the arbitrary generated will always hang. Yes, there is a problem with mutually recursive types.

Type parameters

Now let's see an example of datatype with parameters

data A a = A a
  deriving (Eq, Ord, Show)
  deriving anyclass NFData
  deriving (Generic)

instance (Arbitrary a) => Arbitrary (A a) where
  arbitrary = genericArbitrary
  shrink = genericShrink

It should work from first glance, but when compile it will throw an error:

• Could not deduce (Test.QuickCheck.Arbitrary.Generic.GArbitrary
                          (A a)
                          (GHC.Generics.D1
                             ('GHC.Generics.MetaData "A" "ParametersTest" "main" 'False)
                             (GHC.Generics.C1
                                ('GHC.Generics.MetaCons "A" 'GHC.Generics.PrefixI 'False)
                                (GHC.Generics.S1
                                   ('GHC.Generics.MetaSel
                                      'Nothing
                                      'GHC.Generics.NoSourceUnpackedness
                                      'GHC.Generics.NoSourceStrictness
                                      'GHC.Generics.DecidedLazy)
                                   (GHC.Generics.Rec0 a))))
                          (TypesDiffer (A a) a))
        arising from a use of ‘genericArbitrary’

Here the TypesDiffer is a type familty dealing with recursive types and helping us to eliminate inproper instances. To convince the compiller, that the a parameter is not an A a we must fix the instance with additional constraint Arg (A a) a

instance (Arg (A a) a, Arbitrary a) => Arbitrary (A a) where
  arbitrary = genericArbitrary
  shrink = genericShrink

Now everything compiles and works as expected.