Copyright | (c) Paolo Veronelli Pavlo Kerestey 2017 |
---|---|
License | All rights reserved |
Maintainer | paolo.veronelli@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Tasty driver for Language
Synopsis
- (@?=) :: (ToExpr a, Eq a, Typeable a, MonadThrow m) => a -> a -> m ()
- (@?/=) :: (ToExpr a, Eq a, Typeable a, MonadThrow m) => a -> a -> m ()
- (^?=) :: (ToExpr a, Eq a, Typeable a, MonadThrow m) => m a -> a -> b -> m ()
- (^?/=) :: (ToExpr a, Eq a, Typeable a, MonadThrow m) => m a -> a -> b -> m ()
- acquire :: MonadIO m => IO a -> (m a -> TestTree) -> TestTree
- acquirePure :: IO a -> (a -> TestTree) -> TestTree
- data Phase
- data Language m t q a where
- Given :: m () -> Language m t q Preparing -> Language m t q Preparing
- GivenAndAfter :: m r -> (r -> m ()) -> Language m t q Preparing -> Language m t q Preparing
- When :: m t -> Language m t q Testing -> Language m t q Preparing
- Then :: (t -> m q) -> Language m t q Testing -> Language m t q Testing
- End :: Language m t q Testing
- testBehavior :: (MonadIO m, TestableMonad m, Typeable t) => String -> BDDPreparing m t () -> TestTree
- testBehaviorIO :: (Typeable t, MonadIO m, TestableMonad m) => String -> IO (BDDPreparing m t ()) -> TestTree
- type BDDTesting m t q = Language m t q Testing
- type BDDPreparing m t q = Language m t q Preparing
- class (MonadCatch m, MonadIO m, Monad m, Typeable m) => TestableMonad m where
- failFastIngredients :: [Ingredient]
- failFastTester :: TestTree -> IO ()
- prettyDifferences :: ToExpr a => a -> a -> String
- beforeEach :: IO () -> TestTree -> TestTree
- afterEach :: IO () -> TestTree -> TestTree
- before :: IO () -> TestTree -> TestTree
- after :: IO () -> TestTree -> TestTree
- onEach :: (TestTree -> TestTree) -> TestTree -> TestTree
- captureStdout :: String -> IO () -> IO Text
- testBehaviorF :: (Typeable m, MonadCatch m) => (m Result -> IO Result) -> String -> FreeBDD m x -> TestTree
Documentation
(@?=) :: (ToExpr a, Eq a, Typeable a, MonadThrow m) => a -> a -> m () infixl 4 Source #
equality test which show pretty differences on fail
(@?/=) :: (ToExpr a, Eq a, Typeable a, MonadThrow m) => a -> a -> m () Source #
inequality test which show pretty differences on fail
(^?=) :: (ToExpr a, Eq a, Typeable a, MonadThrow m) => m a -> a -> b -> m () Source #
shortcut to ignore the input and run another action instead in Then matching equality
(^?/=) :: (ToExpr a, Eq a, Typeable a, MonadThrow m) => m a -> a -> b -> m () Source #
shortcut to ignore the input and run another action instead in Then matching inequality
acquire :: MonadIO m => IO a -> (m a -> TestTree) -> TestTree Source #
specialize withResource to just acquire a resource
data Language m t q a where Source #
Bare hoare language
Given :: m () -> Language m t q Preparing -> Language m t q Preparing | action to prepare the test |
GivenAndAfter :: m r -> (r -> m ()) -> Language m t q Preparing -> Language m t q Preparing | action to prepare the test, and related teardown action |
When :: m t -> Language m t q Testing -> Language m t q Preparing | core logic of the test (last preparing action) |
Then :: (t -> m q) -> Language m t q Testing -> Language m t q Testing | action producing a test |
End :: Language m t q Testing | final placeholder |
:: (MonadIO m, TestableMonad m, Typeable t) | |
=> String | test name |
-> BDDPreparing m t () | bdd test definition |
-> TestTree | resulting tasty test |
interpret Bdd
sentence to a single TestTree
:: (Typeable t, MonadIO m, TestableMonad m) | |
=> String | test name |
-> IO (BDDPreparing m t ()) | bdd test definition |
-> TestTree | resulting tasty test |
type BDDTesting m t q = Language m t q Testing Source #
Testing language types
type BDDPreparing m t q = Language m t q Preparing Source #
Preparing language types
class (MonadCatch m, MonadIO m, Monad m, Typeable m) => TestableMonad m where Source #
testable monads can map to IO a Tasty Result
failFastIngredients :: [Ingredient] Source #
basic ingredients fail-fast aware
failFastTester :: TestTree -> IO () Source #
default test runner fail-fast aware
prettyDifferences :: ToExpr a => a -> a -> String Source #
show a coloured difference of 2 values
testBehaviorF :: (Typeable m, MonadCatch m) => (m Result -> IO Result) -> String -> FreeBDD m x -> TestTree Source #