test-fun-0.1.0.0: Testable functions

Safe HaskellSafe
LanguageHaskell2010

Test.Fun.Internal.Generic

Contents

Description

Generic cogenerators

Warning

This is an internal module: it is not subject to any versioning policy, breaking changes can happen at any time. It is made available only for debugging. Otherwise, use Test.Fun.

If something here seems useful, please open an issue to export it from an external module.

Synopsis

CoArbitrary

class Applicative gen => CoArbitrary gen a where Source #

Implicit, default cogenerator.

Methods

coarbitrary :: forall r. Co gen a r Source #

Instances
Applicative gen => CoArbitrary gen Ordering Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

coarbitrary :: Co gen Ordering r Source #

Applicative gen => CoArbitrary gen Bool Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

coarbitrary :: Co gen Bool r Source #

Applicative gen => CoArbitrary gen Word Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

coarbitrary :: Co gen Word r Source #

Applicative gen => CoArbitrary gen Int Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

coarbitrary :: Co gen Int r Source #

Applicative gen => CoArbitrary gen Integer Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

coarbitrary :: Co gen Integer r Source #

Applicative gen => CoArbitrary gen Void Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

coarbitrary :: Co gen Void r Source #

Applicative gen => CoArbitrary gen () Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

coarbitrary :: Co gen () r Source #

CoArbitrary gen a => CoArbitrary gen (Sum a) Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

coarbitrary :: Co gen (Sum a) r Source #

CoArbitrary gen a => CoArbitrary gen (Identity a) Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

coarbitrary :: Co gen (Identity a) r Source #

CoArbitrary gen a => CoArbitrary gen (Maybe a) Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

coarbitrary :: Co gen (Maybe a) r Source #

CoArbitrary gen a => CoArbitrary gen [a] Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

coarbitrary :: Co gen [a] r Source #

(CoArbitrary gen a, CoArbitrary gen b) => CoArbitrary gen (Either a b) Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

coarbitrary :: Co gen (Either a b) r Source #

(CoArbitrary gen a, CoArbitrary gen b) => CoArbitrary gen (a, b) Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

coarbitrary :: Co gen (a, b) r Source #

Generics

cogenGeneric :: forall a r gen. (Generic a, GCoGen a, Applicative gen) => GSumCo gen a r -> Co gen a r Source #

Cogenerator for generic types, parameterized by a list of cogenerators, one for each constructor.

The list is constructed with (:+) (pairs) and ().

Example

Expand
-- Cogenerator for lists, parameterized by a cogenerator for elements.
cogenList :: forall a. (forall r. Co Gen a r) -> (forall r. Co Gen [a] r)
cogenList coa = cogenGeneric gs where
  -- gs :: GSumCo Gen [a] r  -- unfolds to --
  gs ::
    (gen r -> gen r)                 :+  -- Cogenerator for the empty list
    (gen r -> gen (a :-> [a] :-> r)) :+  -- Cogenerator for non-empty lists
    ()
  gs = id :+ (coa . cogenList coa) :+ ()

data a :+ b infixr 2 Source #

Heterogeneous products as nested pairs. These products must be terminated by ().

a :+ b :+ c :+ ()  -- the product of a, b, c

Constructors

a :+ b infixr 2 

cogenList :: forall a r gen. Applicative gen => Co gen a ([a] :-> r) -> Co gen [a] r Source #

Cogenerator for lists.

Implementation note

Expand

The cogenerator of a is made monomorphic only to keep the type of cogenList at rank 1. But really, don't pay attention to the last type argument of Co.

cogenList :: ... => Co gen a _ -> Co gen [a] _

Internals

Generic cogenerators

class (Typeable_ a, GNormalize (Rep a), GenBranches (Rep a)) => GCoGen a Source #

Class of types with generic cogenerators.

Instances
(Typeable_ a, GNormalize (Rep a), GenBranches (Rep a)) => GCoGen a Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Reify the name and arity of a type constructor

class Typeable_ (a :: k) where Source #

Instances
Typeable a => Typeable_ (a :: k) Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Typeable_ f => Typeable_ (f a :: k2) Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Type-level functions on generic representations

type family Normalize (f :: Type -> Type) :: Type where ... Source #

Convert a generic Rep into a sum of products made of Either and (,), where products are nested to the left (i.e., ((((), a), b), c)).

Equations

Normalize (M1 D c f) = Normalize f 
Normalize (f :+: g) = Either (Normalize f) (Normalize g) 
Normalize V1 = Void 
Normalize (M1 C c f) = () >*> f 

type family (s :: Type) >*> (f :: Type -> Type) :: Type where ... infixl 9 Source #

Convert a (:*:) product into a left-nested (,) product.

Equations

s >*> (f :*: g) = (s >*> f) >*> g 
s >*> (M1 S c (K1 R a)) = (s, a) 
s >*> U1 = s 

type GSumCo gen a r = GSumCo_ gen (Rep a) r () Source #

The list of cogenerators for a generic type, one for each constructor.

type family GSumCo_ (gen :: Type -> Type) (f :: Type -> Type) (r :: Type) (t :: Type) :: Type where ... Source #

Equations

GSumCo_ gen (M1 D c f) r t = GSumCo_ gen f r t 
GSumCo_ gen (f :+: g) r t = GSumCo_ gen f r (GSumCo_ gen g r t) 
GSumCo_ gen (M1 C c f) r t = (gen r -> gen (f >-> r)) :+ t 
GSumCo_ gen V1 r t = t 

type family (f :: Type -> Type) >-> (r :: Type) :: Type where ... infixr 9 Source #

Equations

(f :*: g) >-> r = f >-> (g >-> r) 
(M1 S c (K1 R a)) >-> r = a :-> r 
U1 >-> r = r 

Simplify the generic representation

class GNormalize f where Source #

Methods

gnormalize :: f p -> Normalize f Source #

Instances
GNormalize (V1 :: Type -> Type) Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

gnormalize :: V1 p -> Normalize V1 Source #

(GNormalize f, GNormalize g) => GNormalize (f :+: g) Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

gnormalize :: (f :+: g) p -> Normalize (f :+: g) Source #

GNormalize f => GNormalize (M1 D c f) Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

gnormalize :: M1 D c f p -> Normalize (M1 D c f) Source #

GToList f => GNormalize (M1 C c f) Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

gnormalize :: M1 C c f p -> Normalize (M1 C c f) Source #

class GToList f where Source #

Methods

gToList :: y -> f p -> y >*> f Source #

Instances
GToList (U1 :: Type -> Type) Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

gToList :: y -> U1 p -> y >*> U1 Source #

(GToList f, GToList g) => GToList (f :*: g) Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

gToList :: y -> (f :*: g) p -> y >*> (f :*: g) Source #

GToList (M1 S c (K1 R a :: Type -> Type)) Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

gToList :: y -> M1 S c (K1 R a) p -> y >*> M1 S c (K1 R a) Source #

Construct the case branches

genBranches :: forall f r gen. (Applicative gen, GenBranches f) => GSumCo_ gen f r () -> gen r -> gen (Branches (Normalize f) r) Source #

class GenBranches f where Source #

Methods

genBranches_ :: forall t r y gen. Applicative gen => gen r -> (gen (Branches (Normalize f) r) -> t -> y) -> GSumCo_ gen f r t -> y Source #

Instances
GenBranches (V1 :: Type -> Type) Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

genBranches_ :: Applicative gen => gen r -> (gen (Branches (Normalize V1) r) -> t -> y) -> GSumCo_ gen V1 r t -> y Source #

(GenBranches f, GenBranches g) => GenBranches (f :+: g) Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

genBranches_ :: Applicative gen => gen r -> (gen (Branches (Normalize (f :+: g)) r) -> t -> y) -> GSumCo_ gen (f :+: g) r t -> y Source #

GenBranches f => GenBranches (M1 D c f) Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

genBranches_ :: Applicative gen => gen r -> (gen (Branches (Normalize (M1 D c f)) r) -> t -> y) -> GSumCo_ gen (M1 D c f) r t -> y Source #

(Constructor c, MkFields f) => GenBranches (M1 C c f) Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

genBranches_ :: Applicative gen => gen r -> (gen (Branches (Normalize (M1 C c f)) r) -> t -> y) -> GSumCo_ gen (M1 C c f) r t -> y Source #

class MkFields f where Source #

Methods

mkFields :: Fields x (f >-> r) -> Fields (x >*> f) r Source #

Instances
MkFields (U1 :: Type -> Type) Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

mkFields :: Fields x (U1 >-> r) -> Fields (x >*> U1) r Source #

(MkFields f, MkFields g) => MkFields (f :*: g) Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

mkFields :: Fields x ((f :*: g) >-> r) -> Fields (x >*> (f :*: g)) r Source #

MkFields (M1 S c (K1 R a :: Type -> Type)) Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

mkFields :: Fields x (M1 S c (K1 R a) >-> r) -> Fields (x >*> M1 S c (K1 R a)) r Source #

Generic CoArbitrary

coarbitraryGeneric :: forall a r gen. (Generic a, GCoArbitrary gen a) => Co gen a r Source #

Generic implementation of coarbitrary.

-- Assuming MyData is a data type whose fields are all instances of CoArbitrary.

instance CoArbitrary MyData where
  coarbitrary = coarbitraryGeneric

class (GCoGen a, Applicative gen, GSumCoArb gen (Rep a)) => GCoArbitrary gen a Source #

Constraint for coarbitraryGeneric.

Instances
(GCoGen a, Applicative gen, GSumCoArb gen (Rep a)) => GCoArbitrary gen a Source # 
Instance details

Defined in Test.Fun.Internal.Generic

class GSumCoArb gen f where Source #

Methods

gsumCoarb :: forall r t. Proxy r -> t -> GSumCo_ gen f r t Source #

Instances
GSumCoArb gen (V1 :: Type -> Type) Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

gsumCoarb :: Proxy r -> t -> GSumCo_ gen V1 r t Source #

(GSumCoArb gen f, GSumCoArb gen g) => GSumCoArb gen (f :+: g) Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

gsumCoarb :: Proxy r -> t -> GSumCo_ gen (f :+: g) r t Source #

GProdCoArb gen f => GSumCoArb gen (M1 C c f) Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

gsumCoarb :: Proxy r -> t -> GSumCo_ gen (M1 C c f) r t Source #

GSumCoArb gen f => GSumCoArb gen (M1 D c f) Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

gsumCoarb :: Proxy r -> t -> GSumCo_ gen (M1 D c f) r t Source #

class GProdCoArb gen f where Source #

Methods

gprodCoarb :: gen r -> gen (f >-> r) Source #

Instances
GProdCoArb gen (U1 :: Type -> Type) Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

gprodCoarb :: gen r -> gen (U1 >-> r) Source #

(GProdCoArb gen f, GProdCoArb gen g) => GProdCoArb gen (f :*: g) Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

gprodCoarb :: gen r -> gen ((f :*: g) >-> r) Source #

CoArbitrary gen a => GProdCoArb gen (M1 S c (K1 R a :: Type -> Type)) Source # 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

gprodCoarb :: gen r -> gen (M1 S c (K1 R a) >-> r) Source #