quickcheck-state-machine-0.9.0: Test monadic programs using state machine based models
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.StateMachine.Lockstep.Auxiliary

Synopsis

Documentation

data Elem (xs :: [k]) (a :: k) where Source #

Constructors

ElemHead :: Elem (k ': ks) k 
ElemTail :: Elem ks k -> Elem (k' ': ks) k 

npAt :: NP f xs -> Elem xs a -> f a Source #

class NTraversable (f :: (k -> Type) -> [k] -> Type) where Source #

N-ary traversable functors

TODO: Don't provide Elem explicitly (just instantiate c)? TODO: Introduce HTraverse into SOP?

Methods

nctraverse :: (Applicative m, All c xs) => proxy c -> (forall a. c a => Elem xs a -> g a -> m (h a)) -> f g xs -> m (f h xs) Source #

Instances

Instances details
Traversable (Cmd t) => NTraversable (Cmd (Simple t) :: (Type -> Type) -> [Type] -> Type) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple

Methods

nctraverse :: forall m c (xs :: [k]) proxy g h. (Applicative m, All c xs) => proxy c -> (forall (a :: k). c a => Elem xs a -> g a -> m (h a)) -> Cmd (Simple t) g xs -> m (Cmd (Simple t) h xs) Source #

Traversable (Resp t) => NTraversable (Resp (Simple t) :: (Type -> Type) -> [Type] -> Type) Source # 
Instance details

Defined in Test.StateMachine.Lockstep.Simple

Methods

nctraverse :: forall m c (xs :: [k]) proxy g h. (Applicative m, All c xs) => proxy c -> (forall (a :: k). c a => Elem xs a -> g a -> m (h a)) -> Resp (Simple t) g xs -> m (Resp (Simple t) h xs) Source #

ntraverse :: (NTraversable f, Applicative m, SListI xs) => (forall a. Elem xs a -> g a -> m (h a)) -> f g xs -> m (f h xs) Source #

ncfmap :: (NTraversable f, All c xs) => proxy c -> (forall a. c a => Elem xs a -> g a -> h a) -> f g xs -> f h xs Source #

nfmap :: (NTraversable f, SListI xs) => (forall a. Elem xs a -> g a -> h a) -> f g xs -> f h xs Source #

ncfoldMap :: forall proxy f g m c xs. (NTraversable f, Monoid m, All c xs) => proxy c -> (forall a. c a => Elem xs a -> g a -> m) -> f g xs -> m Source #

nfoldMap :: (NTraversable f, Monoid m, SListI xs) => (forall a. Elem xs a -> g a -> m) -> f g xs -> m Source #