{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ConstraintKinds #-}
module Test.Hspec.Core.Spec (
it
, specify
, describe
, context
, pending
, pendingWith
, xit
, xspecify
, xdescribe
, xcontext
, focus
, fit
, fspecify
, fdescribe
, fcontext
, parallel
, sequential
, module Test.Hspec.Core.Spec.Monad
, module Test.Hspec.Core.Example
, module Test.Hspec.Core.Tree
) where
import Prelude ()
import Test.Hspec.Core.Compat
import qualified Control.Exception as E
import Data.CallStack
import Test.Hspec.Expectations (Expectation)
import Test.Hspec.Core.Example
import Test.Hspec.Core.Hooks
import Test.Hspec.Core.Tree
import Test.Hspec.Core.Spec.Monad
describe :: HasCallStack => String -> SpecWith a -> SpecWith a
describe label spec = runIO (runSpecM spec) >>= fromSpecList . return . specGroup label
context :: HasCallStack => String -> SpecWith a -> SpecWith a
context = describe
xdescribe :: HasCallStack => String -> SpecWith a -> SpecWith a
xdescribe label spec = before_ pending_ $ describe label spec
xcontext :: HasCallStack => String -> SpecWith a -> SpecWith a
xcontext = xdescribe
it :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a)
it label action = fromSpecList [specItem label action]
specify :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a)
specify = it
xit :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a)
xit label action = before_ pending_ $ it label action
xspecify :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a)
xspecify = xit
focus :: SpecWith a -> SpecWith a
focus spec = do
xs <- runIO (runSpecM spec)
let
ys
| any (any itemIsFocused) xs = xs
| otherwise = map (bimapTree id (\ item -> item {itemIsFocused = True})) xs
fromSpecList ys
fit :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a)
fit = fmap focus . it
fspecify :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a)
fspecify = fit
fdescribe :: HasCallStack => String -> SpecWith a -> SpecWith a
fdescribe = fmap focus . describe
fcontext :: HasCallStack => String -> SpecWith a -> SpecWith a
fcontext = fdescribe
parallel :: SpecWith a -> SpecWith a
parallel = mapSpecItem_ (setParallelizable True)
sequential :: SpecWith a -> SpecWith a
sequential = mapSpecItem_ (setParallelizable False)
setParallelizable :: Bool -> Item a -> Item a
setParallelizable value item = item {itemIsParallelizable = itemIsParallelizable item <|> Just value}
pending :: HasCallStack => Expectation
pending = E.throwIO (Pending location Nothing)
pending_ :: Expectation
pending_ = (E.throwIO (Pending Nothing Nothing))
pendingWith :: HasCallStack => String -> Expectation
pendingWith = E.throwIO . Pending location . Just