{-# 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 :: String -> SpecWith a -> SpecWith a
describe String
label SpecWith a
spec = IO [SpecTree a] -> SpecM a [SpecTree a]
forall r a. IO r -> SpecM a r
runIO (SpecWith a -> IO [SpecTree a]
forall a. SpecWith a -> IO [SpecTree a]
runSpecM SpecWith a
spec) SpecM a [SpecTree a] -> ([SpecTree a] -> SpecWith a) -> SpecWith a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [SpecTree a] -> SpecWith a
forall a. [SpecTree a] -> SpecWith a
fromSpecList ([SpecTree a] -> SpecWith a)
-> ([SpecTree a] -> [SpecTree a]) -> [SpecTree a] -> SpecWith a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SpecTree a -> [SpecTree a]
forall (m :: * -> *) a. Monad m => a -> m a
return (SpecTree a -> [SpecTree a])
-> ([SpecTree a] -> SpecTree a) -> [SpecTree a] -> [SpecTree a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [SpecTree a] -> SpecTree a
forall a. HasCallStack => String -> [SpecTree a] -> SpecTree a
specGroup String
label
context :: HasCallStack => String -> SpecWith a -> SpecWith a
context :: String -> SpecWith a -> SpecWith a
context = String -> SpecWith a -> SpecWith a
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe
xdescribe :: HasCallStack => String -> SpecWith a -> SpecWith a
xdescribe :: String -> SpecWith a -> SpecWith a
xdescribe String
label SpecWith a
spec = IO () -> SpecWith a -> SpecWith a
forall a. IO () -> SpecWith a -> SpecWith a
before_ IO ()
pending_ (SpecWith a -> SpecWith a) -> SpecWith a -> SpecWith a
forall a b. (a -> b) -> a -> b
$ String -> SpecWith a -> SpecWith a
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
label SpecWith a
spec
xcontext :: HasCallStack => String -> SpecWith a -> SpecWith a
xcontext :: String -> SpecWith a -> SpecWith a
xcontext = String -> SpecWith a -> SpecWith a
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
xdescribe
it :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a)
it :: String -> a -> SpecWith (Arg a)
it String
label a
action = [SpecTree (Arg a)] -> SpecWith (Arg a)
forall a. [SpecTree a] -> SpecWith a
fromSpecList [String -> a -> SpecTree (Arg a)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecTree (Arg a)
specItem String
label a
action]
specify :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a)
specify :: String -> a -> SpecWith (Arg a)
specify = String -> a -> SpecWith (Arg a)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it
xit :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a)
xit :: String -> a -> SpecWith (Arg a)
xit String
label a
action = IO () -> SpecWith (Arg a) -> SpecWith (Arg a)
forall a. IO () -> SpecWith a -> SpecWith a
before_ IO ()
pending_ (SpecWith (Arg a) -> SpecWith (Arg a))
-> SpecWith (Arg a) -> SpecWith (Arg a)
forall a b. (a -> b) -> a -> b
$ String -> a -> SpecWith (Arg a)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
label a
action
xspecify :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a)
xspecify :: String -> a -> SpecWith (Arg a)
xspecify = String -> a -> SpecWith (Arg a)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
xit
focus :: SpecWith a -> SpecWith a
focus :: SpecWith a -> SpecWith a
focus SpecWith a
spec = do
[SpecTree a]
xs <- IO [SpecTree a] -> SpecM a [SpecTree a]
forall r a. IO r -> SpecM a r
runIO (SpecWith a -> IO [SpecTree a]
forall a. SpecWith a -> IO [SpecTree a]
runSpecM SpecWith a
spec)
let
ys :: [SpecTree a]
ys
| (SpecTree a -> Bool) -> [SpecTree a] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ((Item a -> Bool) -> SpecTree a -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Item a -> Bool
forall a. Item a -> Bool
itemIsFocused) [SpecTree a]
xs = [SpecTree a]
xs
| Bool
otherwise = (ActionWith a -> ActionWith a)
-> (Item a -> Item a) -> [SpecTree a] -> [SpecTree a]
forall a b c d. (a -> b) -> (c -> d) -> [Tree a c] -> [Tree b d]
bimapForest ActionWith a -> ActionWith a
forall a. a -> a
id (\ Item a
item -> Item a
item {itemIsFocused :: Bool
itemIsFocused = Bool
True}) [SpecTree a]
xs
[SpecTree a] -> SpecWith a
forall a. [SpecTree a] -> SpecWith a
fromSpecList [SpecTree a]
ys
fit :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a)
fit :: String -> a -> SpecWith (Arg a)
fit = (SpecWith (Arg a) -> SpecWith (Arg a))
-> (a -> SpecWith (Arg a)) -> a -> SpecWith (Arg a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SpecWith (Arg a) -> SpecWith (Arg a)
forall a. SpecWith a -> SpecWith a
focus ((a -> SpecWith (Arg a)) -> a -> SpecWith (Arg a))
-> (String -> a -> SpecWith (Arg a))
-> String
-> a
-> SpecWith (Arg a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> a -> SpecWith (Arg a)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it
fspecify :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a)
fspecify :: String -> a -> SpecWith (Arg a)
fspecify = String -> a -> SpecWith (Arg a)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
fit
fdescribe :: HasCallStack => String -> SpecWith a -> SpecWith a
fdescribe :: String -> SpecWith a -> SpecWith a
fdescribe = (SpecWith a -> SpecWith a)
-> (SpecWith a -> SpecWith a) -> SpecWith a -> SpecWith a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SpecWith a -> SpecWith a
forall a. SpecWith a -> SpecWith a
focus ((SpecWith a -> SpecWith a) -> SpecWith a -> SpecWith a)
-> (String -> SpecWith a -> SpecWith a)
-> String
-> SpecWith a
-> SpecWith a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> SpecWith a -> SpecWith a
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe
fcontext :: HasCallStack => String -> SpecWith a -> SpecWith a
fcontext :: String -> SpecWith a -> SpecWith a
fcontext = String -> SpecWith a -> SpecWith a
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
fdescribe
parallel :: SpecWith a -> SpecWith a
parallel :: SpecWith a -> SpecWith a
parallel = (Item a -> Item a) -> SpecWith a -> SpecWith a
forall a. (Item a -> Item a) -> SpecWith a -> SpecWith a
mapSpecItem_ (Bool -> Item a -> Item a
forall a. Bool -> Item a -> Item a
setParallelizable Bool
True)
sequential :: SpecWith a -> SpecWith a
sequential :: SpecWith a -> SpecWith a
sequential = (Item a -> Item a) -> SpecWith a -> SpecWith a
forall a. (Item a -> Item a) -> SpecWith a -> SpecWith a
mapSpecItem_ (Bool -> Item a -> Item a
forall a. Bool -> Item a -> Item a
setParallelizable Bool
False)
setParallelizable :: Bool -> Item a -> Item a
setParallelizable :: Bool -> Item a -> Item a
setParallelizable Bool
value Item a
item = Item a
item {itemIsParallelizable :: Maybe Bool
itemIsParallelizable = Item a -> Maybe Bool
forall a. Item a -> Maybe Bool
itemIsParallelizable Item a
item Maybe Bool -> Maybe Bool -> Maybe Bool
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
value}
pending :: HasCallStack => Expectation
pending :: IO ()
pending = ResultStatus -> IO ()
forall e a. Exception e => e -> IO a
E.throwIO (Maybe Location -> Maybe String -> ResultStatus
Pending Maybe Location
HasCallStack => Maybe Location
location Maybe String
forall a. Maybe a
Nothing)
pending_ :: Expectation
pending_ :: IO ()
pending_ = (ResultStatus -> IO ()
forall e a. Exception e => e -> IO a
E.throwIO (Maybe Location -> Maybe String -> ResultStatus
Pending Maybe Location
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing))
pendingWith :: HasCallStack => String -> Expectation
pendingWith :: String -> IO ()
pendingWith = ResultStatus -> IO ()
forall e a. Exception e => e -> IO a
E.throwIO (ResultStatus -> IO ())
-> (String -> ResultStatus) -> String -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe Location -> Maybe String -> ResultStatus
Pending Maybe Location
HasCallStack => Maybe Location
location (Maybe String -> ResultStatus)
-> (String -> Maybe String) -> String -> ResultStatus
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe String
forall a. a -> Maybe a
Just