ClassLaws-0.3.0.2: Stating and checking laws for type class methods

Safe HaskellNone

Test.ClassLaws.TestingState

Description

Implementations of the infrastructure needed to test state monad laws.

Documentation

data Pair a b Source

Constructors

Pair a b 

Instances

(Show (Partial a), Show (Partial b)) => Show (Partial (Pair a b)) 
(Eq a, Eq b) => Eq (Pair a b) 
(Show a, Show b) => Show (Pair a b) 
(Arbitrary a, Arbitrary b) => Arbitrary (Pair a b) 
(SemanticEq a, SemanticEq b) => SemanticEq (Pair a b) 
(SemanticEq (Pair a b), SemanticOrd a, SemanticOrd b) => SemanticOrd (Pair a b) 
(CoArbitrary a, CoArbitrary b) => CoArbitrary (Pair a b) 
(ArbitraryPartial a, ArbitraryPartial b) => ArbitraryPartial (Pair a b) 

fstP :: Pair t t1 -> tSource

sndP :: Pair t t1 -> t1Source

newtype State s a Source

Constructors

S 

Fields

runS :: s -> Pair a s
 

Instances

putState :: s -> State s ()Source

bindStateL :: State t1 t -> (t -> State t1 a) -> State t1 aSource

fmapStateL :: (t -> a) -> State t1 t -> State t1 aSource

bindStateS :: State s a1 -> (a1 -> State s a) -> State s aSource

fmapStateS :: (a1 -> a) -> State s a1 -> State s aSource

pairFromGen :: Gen a -> Gen b -> Gen (Pair a b)Source

basicPairShow :: (a -> String) -> (b -> String) -> Pair a b -> StringSource

pairRecPatt :: (a -> a -> ta) -> (b -> b -> tb) -> (ta -> tb -> t) -> Pair a b -> Pair a b -> tSource

statePatt :: ((t1 -> Pair t2 t1) -> (t3 -> Pair t4 t3) -> t) -> State t1 t2 -> State t3 t4 -> tSource

enumTotArb :: [(Int, a)] -> Gen aSource

newtype SS s a Source

Constructors

SS 

Fields

unSS :: State s a
 

Instances

Monad (SS s) => MonadState s (SS s) 
MonadState s (SS s) => MonadStateLaws s (SS s) 
Monad (SS s) 
Functor (SS s) 
(Enum s, Bounded s, Show (Partial a), Show (Partial s)) => Show (Partial (SS s a)) 
(Functor (SS s), Monad (SS s)) => FunctorMonadLaws (SS s) 
Monad (SS s) => MonadLaws (SS s) 
Functor (SS s) => FunctorLaws (SS s) 
(Bounded s, Enum s, Show s, Show a) => Show (SS s a) 
(Arbitrary s, Arbitrary a, CoArbitrary s) => Arbitrary (SS s a) 
(Bounded s, Enum s, SemanticEq s, SemanticEq a) => SemanticEq (SS s a) 
(SemanticEq (SS s a), Bounded s, Enum s, SemanticOrd s, SemanticOrd a) => SemanticOrd (SS s a) 
(Bounded s, Enum s, Eq s, SemanticOrd s, SemanticOrd a, ArbitraryPartial s, ArbitraryPartial a) => ArbitraryPartial (SS s a) 
(SemanticEq a, Show (Partial a), SemanticEq s, Show (Partial s), Bounded s, Enum s) => TestEqual (SS s a)