module Test.Hspec (
Spec
, SpecWith
, Example
, module Test.Hspec.Expectations
, describe
, context
, it
, example
, pending
, pendingWith
, before
, after
, after_
, around
, around_
, parallel
, hspec
) where
import Control.Exception (finally)
import Test.Hspec.Core.Type hiding (describe, it)
import Test.Hspec.Runner
import Test.Hspec.HUnit ()
import Test.Hspec.Expectations
import qualified Test.Hspec.Core as Core
describe :: String -> SpecWith a -> SpecWith a
describe label action = fromSpecList [Core.describe label (runSpecM action)]
context :: String -> SpecWith a -> SpecWith a
context = describe
it :: Example e => String -> e -> SpecWith (Arg e)
it label action = fromSpecList [Core.it label action]
example :: Expectation -> Expectation
example = id
parallel :: SpecWith a -> SpecWith a
parallel = mapSpecItem $ \item -> item {itemIsParallelizable = True}
before :: IO a -> SpecWith a -> Spec
before action = around (action >>=)
after :: (a -> IO ()) -> SpecWith a -> SpecWith a
after a2 = mapSpecItem $ \item -> item {itemExample = \params a1 -> itemExample item params (\f -> a1 (\a -> f a `finally` a2 a))}
after_ :: IO () -> Spec -> Spec
after_ action = after $ \() -> action
around :: ((a -> IO ()) -> IO ()) -> SpecWith a -> Spec
around a2 = mapSpecItem $ \item -> item {itemExample = \params a1 -> itemExample item params (\x -> a1 $ \() -> a2 x)}
around_ :: (IO () -> IO ()) -> Spec -> Spec
around_ action = around $ action . ($ ())