Copyright | (c) Pawel Nosal 2021 |
---|---|
License | MIT |
Maintainer | p.nosal1986@gmail.com |
Stability | experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Extensions |
|
This library aims to provide a set of combinators to assert arbitrary nested data structures.
The inspiration of this library is AssertJ for Java, the composition of assertions was inspired by lens
library.
Example:
data Foo = Foo {name :: String, age :: Int} deriving (Show, Eq) assertThat (Foo "someName" 15) $ isEqualTo (Foo "someN1ame" 15) . focus age . tag "age" . isGreaterThan 20
result in
given Foo {name = "someName", age = 15} should be equal to Foo {name = "someN1ame", age = 15} Foo {name = "someName", age = 15} ╷ │ ╵ Foo {name = "someN1ame", age = 15} ▲ [age] given 15 should be greater than 20
Synopsis
- simpleAssertion :: HasCallStack => (a -> Bool) -> (a -> String) -> Assertion a
- isEqualTo :: (Eq a, Show a, HasCallStack) => a -> Assertion a
- isNotEqualTo :: (Eq a, Show a, HasCallStack) => a -> Assertion a
- isGreaterThan :: (Ord a, Show a, HasCallStack) => a -> Assertion a
- isGreaterEqualThan :: (Ord a, Show a, HasCallStack) => a -> Assertion a
- isLowerThan :: (Ord a, Show a, HasCallStack) => a -> Assertion a
- isLowerEqualThan :: (Ord a, Show a, HasCallStack) => a -> Assertion a
- shouldSatisfy :: (Show a, HasCallStack) => (a -> Bool) -> Assertion a
- hasSize :: (Foldable t, HasCallStack) => Int -> Assertion (t a)
- isEmpty :: (Foldable t, HasCallStack) => Assertion (t a)
- isNotEmpty :: (Foldable t, HasCallStack) => Assertion (t a)
- contains :: (Foldable t, Eq a, Show a, HasCallStack) => a -> Assertion (t a)
- focus :: (a -> b) -> Assertion' a b
- inside :: (b -> a) -> Assertion a -> Assertion b
- tag :: String -> Assertion a
- forceError :: Assertion a -> Assertion a
- data AssertionConfig
- defaultConfig :: AssertionConfig
- setAssertionTimeout :: Int -> AssertionConfig -> AssertionConfig
- type Assertion a = Assertion' a a
- type Assertion' a b = Assertion'' a a b b
- data FluentTestFailure = FluentTestFailure {}
Assertions
Basic assertions
:: HasCallStack | |
=> (a -> Bool) | A predicate that should be met by the subject under test |
-> (a -> String) | A function that allows formatting an error message once the predicate is not met |
-> Assertion a |
The simpleAssertion
function is a building block of more complicated assertions.
It takes one predicate and function to format error message.
myIsEqual x = simpleAssertion (== x) (\x' -> show x' <> " is not equal to " <> show x)
isEqualTo :: (Eq a, Show a, HasCallStack) => a -> Assertion a Source #
assert if subject under test is equal to given value
assertThat 15 $ isEqualTo 16
result
given 15 should be equal to 16 ▼ 15 ╷ │ ╵ 16 ▲
isNotEqualTo :: (Eq a, Show a, HasCallStack) => a -> Assertion a Source #
isGreaterThan :: (Ord a, Show a, HasCallStack) => a -> Assertion a Source #
assert if the subject under test is greater than given value
assertThat 15 $ isGreaterThan 16
result
given 15 should be greater than 16
isGreaterEqualThan :: (Ord a, Show a, HasCallStack) => a -> Assertion a Source #
isLowerThan :: (Ord a, Show a, HasCallStack) => a -> Assertion a Source #
assert if the subject under test is lower than given value
assertThat 16 $ isLowerThan 15
result
given 16 should be lower than 15
isLowerEqualThan :: (Ord a, Show a, HasCallStack) => a -> Assertion a Source #
shouldSatisfy :: (Show a, HasCallStack) => (a -> Bool) -> Assertion a Source #
isNotEmpty :: (Foldable t, HasCallStack) => Assertion (t a) Source #
Assertion util functions
focus :: (a -> b) -> Assertion' a b Source #
allow changing subject under test using a transformation function
assertThat "1 " $ isNotEqualTo "" . focus length . isEqualTo 10
result
given 5 should be equal to 10 ▼ 5 ╷ │ ╵ 10 ▲▲
inside :: (b -> a) -> Assertion a -> Assertion b Source #
like focus
, this function allow changing subject under test, it takes an assertion for modified value, then it allows us to continue assertion on the original value
assertThat (Foo "someName" 15) $ isEqualTo (Foo "someN1ame" 15) . inside age (tag "age" . isGreaterThan 20 . isLowerThan 10) . isEqualTo (Foo "someName" 15)
result
given Foo {name = "someName", age = 15} should be equal to Foo {name = "someN1ame", age = 15} Foo {name = "someName", age = 15} ╷ │ ╵ Foo {name = "someN1ame", age = 15} ▲ [age] given 15 should be greater than 20 [age] given 15 should be lower than 10
tag :: String -> Assertion a Source #
this combinator allows marking following assertion with a given prefix
assertThat (Foo "someName" 15) $ tag "foo" . isEqualTo (Foo "someN1ame" 15) . inside age (tag "age" . isGreaterThan 20 . isLowerThan 10) . tag "foo not equal" . isNotEqualTo (Foo "someName" 15)
result
[foo] given Foo {name = "someName", age = 15} should be equal to Foo {name = "someN1ame", age = 15} Foo {name = "someName", age = 15} ╷ │ ╵ Foo {name = "someN1ame", age = 15} ▲ [foo.age] given 15 should be greater than 20 [foo.age] given 15 should be lower than 10 [foo.not equal to] given Foo {name = "someName", age = 15} should be not equal to Foo {name = "someName", age = 15} Foo {name = "someName", age = 15} ╷ │ ╵ Foo {name = "someName", age = 15}
forceError :: Assertion a -> Assertion a Source #
Sometimes it is handy to stop the assertions chain.
This combinator gets an assertion that should be forced, any following assertion will be not executed then
extracting :: HasCallStack => Assertion' (Maybe a) a extracting = forceError isJust . focus Maybe.fromJust
Assertion configuration
data AssertionConfig Source #
Instances
Show AssertionConfig Source # | |
Defined in Test.Fluent.Internal.AssertionConfig showsPrec :: Int -> AssertionConfig -> ShowS # show :: AssertionConfig -> String # showList :: [AssertionConfig] -> ShowS # |
defaultConfig :: AssertionConfig Source #
Default configuration used for assertThat
and assertThatIO
.
- default timeout is set to 5 seconds
setAssertionTimeout :: Int -> AssertionConfig -> AssertionConfig Source #
Allow to modify timeout of single assertion
Types
Assertion defitions
type Assertion a = Assertion' a a Source #
type Assertion' a b = Assertion'' a a b b Source #
Assertion failure
data FluentTestFailure Source #
Instances
Show FluentTestFailure Source # | |
Defined in Test.Fluent.Internal.Assertions showsPrec :: Int -> FluentTestFailure -> ShowS # show :: FluentTestFailure -> String # showList :: [FluentTestFailure] -> ShowS # | |
Exception FluentTestFailure Source # | |