-- | -- Stability: stable -- -- Hspec is a testing framework for Haskell. -- -- This is the library reference for Hspec. -- The contains more in-depth -- documentation. module Test.Hspec ( -- * Types Spec , Arg , SpecWith , ActionWith , Example -- * Setting expectations , module Test.Hspec.Expectations -- * Defining a spec , describe , context , it , specify , example , pending , pendingWith , before , beforeWith , beforeAll , beforeAllWith , after , after_ , afterAll , afterAll_ , around , around_ , aroundWith , parallel , runIO -- * Running a spec , hspec ) where import Control.Exception (finally) import Control.Concurrent.MVar 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 -- | Combine a list of specs into a larger spec. describe :: String -> SpecWith a -> SpecWith a describe label spec = runIO (runSpecM spec) >>= fromSpecList . return . Core.describe label -- | An alias for `describe`. context :: String -> SpecWith a -> SpecWith a context = describe -- | Create a spec item. -- -- A spec item consists of: -- -- * a textual description of a desired behavior -- -- * an example for that behavior -- -- > describe "absolute" $ do -- > it "returns a positive number when given a negative number" $ -- > absolute (-1) == 1 it :: Example e => String -> e -> SpecWith (Arg e) it label action = fromSpecList [Core.it label action] -- | An alias for `it`. specify :: Example e => String -> e -> SpecWith (Arg e) specify = it -- | This is a type restricted version of `id`. It can be used to get better -- error messages on type mismatches. -- -- Compare e.g. -- -- > it "exposes some behavior" $ example $ do -- > putStrLn -- -- with -- -- > it "exposes some behavior" $ do -- > putStrLn example :: Expectation -> Expectation example = id -- | Run spec items of given `Spec` in parallel. parallel :: SpecWith a -> SpecWith a parallel = mapSpecItem_ $ \item -> item {itemIsParallelizable = True} -- | Run a custom action before every spec item. before :: IO a -> SpecWith a -> Spec before action = around (action >>=) -- | Run a custom action before every spec item. beforeWith :: (b -> IO a) -> SpecWith a -> SpecWith b beforeWith action = aroundWith $ \e x -> action x >>= e -- | Run a custom action before the first spec item. beforeAll :: IO a -> SpecWith a -> Spec beforeAll action spec = do mvar <- runIO (newMVar Nothing) let action_ = memoize mvar action before action_ spec memoize :: MVar (Maybe a) -> IO a -> IO a memoize mvar action = modifyMVar mvar $ \ma -> case ma of Just a -> return (ma, a) Nothing -> do a <- action return (Just a, a) -- | Run a custom action before all spec items. beforeAllWith :: (b -> IO a) -> SpecWith a -> SpecWith b beforeAllWith action spec = do mvar <- runIO (newMVar Nothing) let action_ = memoize mvar . action aroundWith (\e x -> action_ x >>= e) spec -- | Run a custom action after every spec item. after :: ActionWith a -> SpecWith a -> SpecWith a after action = aroundWith $ \e x -> e x `finally` action x -- | Run a custom action after every spec item. after_ :: IO () -> Spec -> Spec after_ action = after $ \() -> action -- | Run a custom action before and/or after every spec item. around :: (ActionWith a -> IO ()) -> SpecWith a -> Spec around action = aroundWith $ \e () -> action e -- | Run a custom action after the last spec item. afterAll :: ActionWith a -> SpecWith a -> SpecWith a afterAll action spec = runIO (runSpecM spec) >>= fromSpecList . return . SpecWithCleanup action -- | Run a custom action after the last spec item. afterAll_ :: IO () -> Spec -> Spec afterAll_ action = afterAll (\() -> action) -- | Run a custom action before and/or after every spec item. around_ :: (IO () -> IO ()) -> Spec -> Spec around_ action = around $ action . ($ ()) -- | Run a custom action before and/or after every spec item. aroundWith :: (ActionWith a -> ActionWith b) -> SpecWith a -> SpecWith b aroundWith action = mapAround (. action) mapAround :: ((ActionWith b -> IO ()) -> ActionWith a -> IO ()) -> SpecWith a -> SpecWith b mapAround f = mapSpecItem (untangle f) $ \i@Item{itemExample = e} -> i{itemExample = (. f) . e} untangle :: ((ActionWith b -> IO ()) -> ActionWith a -> IO ()) -> ActionWith a -> ActionWith b untangle f g = \b -> f ($ b) g