hedgehog-1.4: Release with confidence.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hedgehog.Internal.Barbie

Description

For compatibility across different versions of the barbie package.

Synopsis

Documentation

class FunctorB (b :: (k -> Type) -> Type) where #

Barbie-types that can be mapped over. Instances of FunctorB should satisfy the following laws:

bmap id = id
bmap f . bmap g = bmap (f . g)

There is a default bmap implementation for Generic types, so instances can derived automatically.

Minimal complete definition

Nothing

Methods

bmap :: (forall (a :: k). f a -> g a) -> b f -> b g #

Instances

Instances details
FunctorB (Var a :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Hedgehog.Internal.State

Methods

bmap :: (forall (a0 :: k). f a0 -> g a0) -> Var a f -> Var a g #

FunctorB (Proxy :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.FunctorB

Methods

bmap :: (forall (a :: k0). f a -> g a) -> Proxy f -> Proxy g #

FunctorB (Const x :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.FunctorB

Methods

bmap :: (forall (a :: k0). f a -> g a) -> Const x f -> Const x g #

FunctorB (Constant x :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.FunctorB

Methods

bmap :: (forall (a :: k0). f a -> g a) -> Constant x f -> Constant x g #

(FunctorB a, FunctorB b) => FunctorB (Product a b :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.FunctorB

Methods

bmap :: (forall (a0 :: k0). f a0 -> g a0) -> Product a b f -> Product a b g #

(FunctorB a, FunctorB b) => FunctorB (Sum a b :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.FunctorB

Methods

bmap :: (forall (a0 :: k0). f a0 -> g a0) -> Sum a b f -> Sum a b g #

(Functor f, FunctorB b) => FunctorB (Compose f b :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.FunctorB

Methods

bmap :: (forall (a :: k0). f0 a -> g a) -> Compose f b f0 -> Compose f b g #

class FunctorB b => TraversableB (b :: (k -> Type) -> Type) where #

Barbie-types that can be traversed from left to right. Instances should satisfy the following laws:

 t . btraverse f   = btraverse (t . f)  -- naturality
btraverse Identity = Identity           -- identity
btraverse (Compose . fmap g . f) = Compose . fmap (btraverse g) . btraverse f -- composition

There is a default btraverse implementation for Generic types, so instances can derived automatically.

Minimal complete definition

Nothing

Methods

btraverse :: Applicative e => (forall (a :: k). f a -> e (g a)) -> b f -> e (b g) #

Instances

Instances details
TraversableB (Var a :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Hedgehog.Internal.State

Methods

btraverse :: Applicative e => (forall (a0 :: k). f a0 -> e (g a0)) -> Var a f -> e (Var a g) #

TraversableB (Proxy :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.TraversableB

Methods

btraverse :: Applicative e => (forall (a :: k0). f a -> e (g a)) -> Proxy f -> e (Proxy g) #

TraversableB (Const a :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.TraversableB

Methods

btraverse :: Applicative e => (forall (a0 :: k0). f a0 -> e (g a0)) -> Const a f -> e (Const a g) #

TraversableB (Constant a :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.TraversableB

Methods

btraverse :: Applicative e => (forall (a0 :: k0). f a0 -> e (g a0)) -> Constant a f -> e (Constant a g) #

(TraversableB a, TraversableB b) => TraversableB (Product a b :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.TraversableB

Methods

btraverse :: Applicative e => (forall (a0 :: k0). f a0 -> e (g a0)) -> Product a b f -> e (Product a b g) #

(TraversableB a, TraversableB b) => TraversableB (Sum a b :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.TraversableB

Methods

btraverse :: Applicative e => (forall (a0 :: k0). f a0 -> e (g a0)) -> Sum a b f -> e (Sum a b g) #

(Traversable f, TraversableB b) => TraversableB (Compose f b :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.TraversableB

Methods

btraverse :: Applicative e => (forall (a :: k0). f0 a -> e (g a)) -> Compose f b f0 -> e (Compose f b g) #

newtype Rec p a (x :: k) #

Constructors

Rec 

Fields

Instances

Instances details
GConstraints n (c :: k1 -> Constraint) (f :: k2) (Rec a' a :: Type -> TYPE LiftedRep) (Rec b' b :: k3 -> TYPE LiftedRep) (Rec b' b :: k3 -> TYPE LiftedRep) 
Instance details

Defined in Barbies.Generics.Constraints

Methods

gaddDicts :: forall (x :: k20). GAll n c (Rec a' a) => Rec b' b x -> Rec b' b x #

GConstraints n (c :: k1 -> Constraint) (f :: k1 -> Type) (Rec (P n (X :: k1 -> Type) a') (X a) :: Type -> TYPE LiftedRep) (Rec (P n f a') (f a) :: k2 -> TYPE LiftedRep) (Rec (P n (Product (Dict c) f) a') (Product (Dict c) f a) :: k2 -> TYPE LiftedRep) 
Instance details

Defined in Barbies.Generics.Constraints

Methods

gaddDicts :: forall (x :: k20). GAll n c (Rec (P n X a') (X a)) => Rec (P n f a') (f a) x -> Rec (P n (Product (Dict c) f) a') (Product (Dict c) f a) x #

type GAll n (c :: k -> Constraint) (Rec l r :: Type -> TYPE LiftedRep) 
Instance details

Defined in Barbies.Generics.Constraints

type GAll n (c :: k -> Constraint) (Rec l r :: Type -> TYPE LiftedRep) = GAllRec n c l r