Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
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
- class Applicative gen => CoArbitrary gen a where
- coarbitrary :: forall r. Co gen a r
- cogenGeneric :: forall a r gen. (Generic a, GCoGen a, Applicative gen) => GSumCo gen a r -> Co gen a r
- data a :+ b = a :+ b
- cogenList :: forall a r gen. Applicative gen => Co gen a ([a] :-> r) -> Co gen [a] r
- class (Typeable_ a, GNormalize (Rep a), GenBranches (Rep a)) => GCoGen a
- shortTypeName :: forall a. Typeable_ a => TypeName
- class Typeable_ (a :: k) where
- shortTypeName_ :: String -> String
- type family Normalize (f :: Type -> Type) :: Type where ...
- type family (s :: Type) >*> (f :: Type -> Type) :: Type where ...
- type GSumCo gen a r = GSumCo_ gen (Rep a) r ()
- type family GSumCo_ (gen :: Type -> Type) (f :: Type -> Type) (r :: Type) (t :: Type) :: Type where ...
- type family (f :: Type -> Type) >-> (r :: Type) :: Type where ...
- class GNormalize f where
- gnormalize :: f p -> Normalize f
- class GToList f where
- genBranches :: forall f r gen. (Applicative gen, GenBranches f) => GSumCo_ gen f r () -> gen r -> gen (Branches (Normalize f) r)
- class GenBranches f where
- genBranches_ :: forall t r y gen. Applicative gen => gen r -> (gen (Branches (Normalize f) r) -> t -> y) -> GSumCo_ gen f r t -> y
- class MkFields f where
- coarbitraryGeneric :: forall a r gen. (Generic a, GCoArbitrary gen a) => Co gen a r
- class (GCoGen a, Applicative gen, GSumCoArb gen (Rep a)) => GCoArbitrary gen a
- class GSumCoArb gen f where
- class GProdCoArb gen f where
- gprodCoarb :: gen r -> gen (f >-> r)
CoArbitrary
class Applicative gen => CoArbitrary gen a where Source #
Implicit, default cogenerator.
coarbitrary :: forall r. Co gen a r Source #
Instances
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
-- 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):+
()
Heterogeneous products as nested pairs. These products must be terminated by ().
a :+ b :+ c :+ () -- the product of a, b, c
a :+ b infixr 2 |
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 # | |
Defined in Test.Fun.Internal.Generic |
Reify the name and arity of a type constructor
shortTypeName :: forall a. Typeable_ a => TypeName Source #
class Typeable_ (a :: k) where Source #
shortTypeName_ :: String -> String Source #
Instances
Typeable a => Typeable_ (a :: k) Source # | |
Defined in Test.Fun.Internal.Generic shortTypeName_ :: String -> String Source # | |
Typeable_ f => Typeable_ (f a :: k2) Source # | |
Defined in Test.Fun.Internal.Generic shortTypeName_ :: String -> String Source # |
Type-level functions on generic representations
type family Normalize (f :: Type -> Type) :: Type where ... Source #
type family (s :: Type) >*> (f :: Type -> Type) :: Type where ... infixl 9 Source #
Convert a (:*:)
product into a left-nested (,)
product.
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 #
Simplify the generic representation
class GNormalize f where Source #
gnormalize :: f p -> Normalize f Source #
Instances
GNormalize (V1 :: Type -> Type) Source # | |
Defined in Test.Fun.Internal.Generic | |
(GNormalize f, GNormalize g) => GNormalize (f :+: g) Source # | |
Defined in Test.Fun.Internal.Generic | |
GNormalize f => GNormalize (M1 D c f) Source # | |
Defined in Test.Fun.Internal.Generic | |
GToList f => GNormalize (M1 C c f) Source # | |
Defined in Test.Fun.Internal.Generic |
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 #
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 # | |
Defined in Test.Fun.Internal.Generic 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 # | |
Defined in Test.Fun.Internal.Generic 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 # | |
Defined in Test.Fun.Internal.Generic | |
(Constructor c, MkFields f) => GenBranches (M1 C c f) Source # | |
Defined in Test.Fun.Internal.Generic |
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 # | |
Defined in Test.Fun.Internal.Generic |
class GProdCoArb gen f where Source #
gprodCoarb :: gen r -> gen (f >-> r) Source #
Instances
GProdCoArb gen (U1 :: Type -> Type) Source # | |
Defined in Test.Fun.Internal.Generic gprodCoarb :: gen r -> gen (U1 >-> r) Source # | |
(GProdCoArb gen f, GProdCoArb gen g) => GProdCoArb gen (f :*: g) Source # | |
Defined in Test.Fun.Internal.Generic gprodCoarb :: gen r -> gen ((f :*: g) >-> r) Source # | |
CoArbitrary gen a => GProdCoArb gen (M1 S c (K1 R a :: Type -> Type)) Source # | |
Defined in Test.Fun.Internal.Generic |