quickcheck-state-machine-0.4.3: Test monadic programs using state machine based models

Safe HaskellSafe
LanguageHaskell2010

Test.StateMachine.Types.Rank2

Documentation

class Functor (f :: (k -> Type) -> Type) Source #

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

Defined in Test.StateMachine.Types.Rank2

Methods

fmap :: (forall (x :: k0). p x -> q x) -> U1 p -> U1 q Source #

Functor f => Functor (Rec1 f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Types.Rank2

Methods

fmap :: (forall (x :: k0). p x -> q x) -> Rec1 f p -> Rec1 f q Source #

(Functor f, Functor g) => Functor (f :*: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Types.Rank2

Methods

fmap :: (forall (x :: k0). p x -> q x) -> (f :*: g) p -> (f :*: g) q Source #

(Functor f, Functor g) => Functor (f :+: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Types.Rank2

Methods

fmap :: (forall (x :: k0). p x -> q x) -> (f :+: g) p -> (f :+: g) q Source #

Functor (K1 i c :: (k -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Types.Rank2

Methods

fmap :: (forall (x :: k0). p x -> q x) -> K1 i c p -> K1 i c q Source #

Functor f => Functor (M1 i c f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Types.Rank2

Methods

fmap :: (forall (x :: k0). p x -> q x) -> M1 i c f p -> M1 i c f q Source #

(Functor f, Functor g) => Functor (f :.: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Types.Rank2

Methods

fmap :: (forall (x :: k0). p x -> q x) -> (f :.: g) p -> (f :.: g) q Source #

Functor (Reference a :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

fmap :: (forall (x :: k). p x -> q x) -> Reference a p -> Reference a q Source #

fmap :: Functor f => (forall x. p x -> q x) -> f p -> f q Source #

gfmap :: (Generic1 f, Functor (Rep1 f)) => (forall a. p a -> q a) -> f p -> f q Source #

(<$>) :: Functor f => (forall x. p x -> q x) -> f p -> f q Source #

class Foldable (f :: (k -> Type) -> Type) Source #

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

Defined in Test.StateMachine.Types.Rank2

Methods

foldMap :: Monoid m => (forall (x :: k0). p x -> m) -> U1 p -> m Source #

Foldable f => Foldable (Rec1 f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Types.Rank2

Methods

foldMap :: Monoid m => (forall (x :: k0). p x -> m) -> Rec1 f p -> m Source #

(Foldable f, Foldable g) => Foldable (f :*: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Types.Rank2

Methods

foldMap :: Monoid m => (forall (x :: k0). p x -> m) -> (f :*: g) p -> m Source #

(Foldable f, Foldable g) => Foldable (f :+: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Types.Rank2

Methods

foldMap :: Monoid m => (forall (x :: k0). p x -> m) -> (f :+: g) p -> m Source #

Foldable (K1 i c :: (k -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Types.Rank2

Methods

foldMap :: Monoid m => (forall (x :: k0). p x -> m) -> K1 i c p -> m Source #

Foldable f => Foldable (M1 i c f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Types.Rank2

Methods

foldMap :: Monoid m => (forall (x :: k0). p x -> m) -> M1 i c f p -> m Source #

(Foldable f, Foldable g) => Foldable (f :.: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Types.Rank2

Methods

foldMap :: Monoid m => (forall (x :: k0). p x -> m) -> (f :.: g) p -> m Source #

Foldable (Reference a :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

foldMap :: Monoid m => (forall (x :: k). p x -> m) -> Reference a p -> m Source #

foldMap :: (Foldable f, Monoid m) => (forall x. p x -> m) -> f p -> m Source #

gfoldMap :: (Generic1 f, Foldable (Rep1 f), Monoid m) => (forall a. p a -> m) -> f p -> m Source #

class (Functor t, Foldable t) => Traversable (t :: (k -> Type) -> Type) Source #

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

Defined in Test.StateMachine.Types.Rank2

Methods

traverse :: Applicative f => (forall (a :: k0). p a -> f (q a)) -> U1 p -> f (U1 q) Source #

Traversable f => Traversable (Rec1 f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Types.Rank2

Methods

traverse :: Applicative f0 => (forall (a :: k0). p a -> f0 (q a)) -> Rec1 f p -> f0 (Rec1 f q) Source #

(Traversable f, Traversable g) => Traversable (f :*: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Types.Rank2

Methods

traverse :: Applicative f0 => (forall (a :: k0). p a -> f0 (q a)) -> (f :*: g) p -> f0 ((f :*: g) q) Source #

(Traversable f, Traversable g) => Traversable (f :+: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Types.Rank2

Methods

traverse :: Applicative f0 => (forall (a :: k0). p a -> f0 (q a)) -> (f :+: g) p -> f0 ((f :+: g) q) Source #

Traversable (K1 i c :: (k -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Types.Rank2

Methods

traverse :: Applicative f => (forall (a :: k0). p a -> f (q a)) -> K1 i c p -> f (K1 i c q) Source #

Traversable f => Traversable (M1 i c f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Types.Rank2

Methods

traverse :: Applicative f0 => (forall (a :: k0). p a -> f0 (q a)) -> M1 i c f p -> f0 (M1 i c f q) Source #

(Traversable f, Traversable g) => Traversable (f :.: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Types.Rank2

Methods

traverse :: Applicative f0 => (forall (a :: k0). p a -> f0 (q a)) -> (f :.: g) p -> f0 ((f :.: g) q) Source #

Traversable (Reference a :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

traverse :: Applicative f => (forall (a0 :: k). p a0 -> f (q a0)) -> Reference a p -> f (Reference a q) Source #

traverse :: (Traversable t, Applicative f) => (forall a. p a -> f (q a)) -> t p -> f (t q) Source #

gtraverse :: (Generic1 t, Traversable (Rep1 t), Applicative f) => (forall a. p a -> f (q a)) -> t p -> f (t q) Source #