| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Polysemy.Check.Arbitrary.Generic
Synopsis
- type (:~~~:) a b = ('Kon (~~) :@: a) :@: b
- class GArbitraryK (a :: Type) (f :: LoT Type -> Type) where
- garbitraryk :: [Gen (f x)]
- genEff :: forall e a m. (GArbitraryK a (RepK (e m a)), GenericK (e m a)) => Gen (e m a)
- class GArbitraryK1 (f :: LoT Type -> Type) where
- garbitraryk1 :: [Gen (f x)]
- class GArbitraryKTerm (t :: Type) where
- garbitrarykterm :: Gen t
Documentation
class GArbitraryK (a :: Type) (f :: LoT Type -> Type) where Source #
Given , this typeclass computes
generators for every well-typed constructor of GArbitraryK a (RepK (e m a))e m a. It is capable of
building generators for GADTs.
Methods
garbitraryk :: [Gen (f x)] Source #
Instances
| GArbitraryK a (U1 :: LoT Type -> Type) Source # | |
Defined in Polysemy.Check.Arbitrary.Generic | |
| GArbitraryK1 (Field b) => GArbitraryK a (Field b) Source # | |
Defined in Polysemy.Check.Arbitrary.Generic | |
| GArbitraryK a (('Kon (b ~~ c) :: Atom Type Constraint) :=>: f) Source # | |
Defined in Polysemy.Check.Arbitrary.Generic | |
| GArbitraryK a (('Kon (a ~~ b) :: Atom Type Constraint) :=>: f) Source # | |
Defined in Polysemy.Check.Arbitrary.Generic | |
| GArbitraryK1 f => GArbitraryK a (('Kon (a ~~ a) :: Atom Type Constraint) :=>: f) Source # | |
Defined in Polysemy.Check.Arbitrary.Generic | |
| (GArbitraryK a f, GArbitraryK a g) => GArbitraryK a (f :+: g) Source # | |
Defined in Polysemy.Check.Arbitrary.Generic | |
| GArbitraryK1 (f :*: g) => GArbitraryK a (f :*: g) Source # | |
Defined in Polysemy.Check.Arbitrary.Generic | |
| GArbitraryK a f => GArbitraryK a (M1 _1 _2 f) Source # | |
Defined in Polysemy.Check.Arbitrary.Generic | |
genEff :: forall e a m. (GArbitraryK a (RepK (e m a)), GenericK (e m a)) => Gen (e m a) Source #
genEff @e @a @m gets a generator capable of producing every
well-typed GADT constructor of e m a.
class GArbitraryK1 (f :: LoT Type -> Type) where Source #
Like GArbitraryK, but gets run after we've already discharged the a
~ T GADT constraint.
Methods
garbitraryk1 :: [Gen (f x)] Source #
Instances
| GArbitraryK1 (U1 :: LoT Type -> Type) Source # | |
Defined in Polysemy.Check.Arbitrary.Generic | |
| GArbitraryKTerm t => GArbitraryK1 (Field ('Kon t :: Atom Type Type)) Source # | |
Defined in Polysemy.Check.Arbitrary.Generic | |
| (GArbitraryK1 f, GArbitraryK1 g) => GArbitraryK1 (f :*: g) Source # | |
Defined in Polysemy.Check.Arbitrary.Generic | |
| GArbitraryK1 f => GArbitraryK1 (M1 _1 _2 f) Source # | |
Defined in Polysemy.Check.Arbitrary.Generic | |
class GArbitraryKTerm (t :: Type) where Source #
Methods
garbitrarykterm :: Gen t Source #
Instances
| Arbitrary a => GArbitraryKTerm a Source # | |
Defined in Polysemy.Check.Arbitrary.Generic Methods garbitrarykterm :: Gen a Source # | |
| (CoArbitrary a, GArbitraryKTerm b) => GArbitraryKTerm (a -> b) Source # | |
Defined in Polysemy.Check.Arbitrary.Generic Methods garbitrarykterm :: Gen (a -> b) Source # | |
| ArbitraryEffOfType a r r => GArbitraryKTerm (Sem r a) Source # | |
Defined in Polysemy.Check.Arbitrary.Generic Methods garbitrarykterm :: Gen (Sem r a) Source # | |