tasty-bdd-0.1.0.1: BDD tests language and tasty provider

Copyright(c) Paolo Veronelli Pavlo Kerestey 2017-2020
LicenseAll rights reserved
Maintainerpaolo.veronelli@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Test.Tasty.Bdd

Contents

Description

Tasty driver for Language

Synopsis

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 Phase Source #

Separating the 2 phases by type

Constructors

Preparing 
Testing 

data Language m t q a where Source #

Bare hoare language

Constructors

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

testBehavior Source #

Arguments

:: (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

testBehaviorIO Source #

Arguments

:: (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

Methods

runCase :: m Result -> IO Result Source #

Instances
TestableMonad IO Source # 
Instance details

Defined in Test.Tasty.Bdd

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

beforeEach :: IO () -> TestTree -> TestTree Source #

recursively prepend an action

afterEach :: IO () -> TestTree -> TestTree Source #

recursively append an action

before :: IO () -> TestTree -> TestTree Source #

specialize withResource to prepend an action

after :: IO () -> TestTree -> TestTree Source #

specialize withResource to append an action

onEach :: (TestTree -> TestTree) -> TestTree -> TestTree Source #

recursively modify a TestTree

Orphan instances

(Typeable t, TestableMonad m) => IsTest (BDDTest m t ()) Source #

any testable monad can make a BDDTest a tasty test

Instance details

Methods

run :: OptionSet -> BDDTest m t () -> (Progress -> IO ()) -> IO Result #

testOptions :: Tagged (BDDTest m t ()) [OptionDescription] #