Safe Haskell | None |
---|
The following class + helper functions implement law-agnostic testing functionality that is used to test laws for various classes.
- class TestEqual b where
- testRunEq :: Show r => (t -> p -> r) -> (r -> r -> Bool) -> Equal t -> p -> Property
- testEq :: Show a => (a -> a -> Bool) -> Equal a -> Property
- testRunEqPartial :: Show (Partial r) => (t -> p -> r) -> (r -> r -> Bool) -> Equal t -> p -> Property
- testEqPartial :: Show (Partial a) => (a -> a -> Bool) -> Equal a -> Property
- pairwiseEq :: (r -> r -> Bool) -> [r] -> Bool
- type Pos = Int
- failingPair :: (a -> a -> Bool) -> Equal a -> (Pos, a, a)
- failingPair' :: Num t => t -> (t1 -> t1 -> Bool) -> [t1] -> (t, t1, t1)
Documentation
(Eq a, Show a) => TestEqual [a] | |
(SemanticEq (Endo a), Show (Partial (Endo a))) => TestEqual (Endo a) | |
(Eq a, Show a) => TestEqual (Maybe a) | |
(Eq a, Show a) => TestEqual (MyList a) | |
(Eq a, Show a, Eq s, Show s) => TestEqual (State s a) | |
(SemanticEq a, Show (Partial a), SemanticEq s, Show (Partial s), Bounded s, Enum s) => TestEqual (SS s a) | |
(SemanticEq a, Show (Partial a), SemanticEq s, Show (Partial s), Bounded s, Enum s) => TestEqual (State s a) |
testEq :: Show a => (a -> a -> Bool) -> Equal a -> PropertySource
The second function, testEq
, does the same, but now for pairs
that are not necessarily runnable.
testRunEqPartial :: Show (Partial r) => (t -> p -> r) -> (r -> r -> Bool) -> Equal t -> p -> PropertySource
pairwiseEq :: (r -> r -> Bool) -> [r] -> BoolSource
Local helper
failingPair :: (a -> a -> Bool) -> Equal a -> (Pos, a, a)Source
Local helper
failingPair' :: Num t => t -> (t1 -> t1 -> Bool) -> [t1] -> (t, t1, t1)Source
Local helper