module Test.Hspec.Core.Extension.Item {-# WARNING "This API is experimental." #-} (
Item(..)
, Location(..)
, Params(..)
, ActionWith
, Progress
, ProgressCallback
, Result(..)
, ResultStatus(..)
, FailureReason(..)
, isFocused
, pending
, pendingWith
, setAnnotation
, getAnnotation
) where
import Prelude ()
import Test.Hspec.Core.Compat
import Test.Hspec.Core.Spec hiding (pending, pendingWith)
import Test.Hspec.Core.Tree
isFocused :: Item a -> Bool
isFocused :: forall a. Item a -> Bool
isFocused = Item a -> Bool
forall a. Item a -> Bool
itemIsFocused
pending :: Item a -> Item a
pending :: forall a. Item a -> Item a
pending Item a
item = Item a
item { itemExample = \ Params
_params ActionWith a -> IO ()
_hook ProgressCallback
_progress -> IO Result
result }
where
result :: IO Result
result :: IO Result
result = Result -> IO Result
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Result -> IO Result) -> Result -> IO Result
forall a b. (a -> b) -> a -> b
$ String -> ResultStatus -> Result
Result String
"" (Maybe Location -> Maybe String -> ResultStatus
Pending Maybe Location
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing)
pendingWith :: String -> Item a -> Item a
pendingWith :: forall a. String -> Item a -> Item a
pendingWith String
reason Item a
item = Item a
item { itemExample = \ Params
_params ActionWith a -> IO ()
_hook ProgressCallback
_progress -> IO Result
result }
where
result :: IO Result
result :: IO Result
result = Result -> IO Result
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Result -> IO Result) -> Result -> IO Result
forall a b. (a -> b) -> a -> b
$ String -> ResultStatus -> Result
Result String
"" (Maybe Location -> Maybe String -> ResultStatus
Pending Maybe Location
forall a. Maybe a
Nothing (String -> Maybe String
forall a. a -> Maybe a
Just String
reason))
setAnnotation :: Typeable value => value -> Item a -> Item a
setAnnotation :: forall value a. Typeable value => value -> Item a -> Item a
setAnnotation = value -> Item a -> Item a
forall value a. Typeable value => value -> Item a -> Item a
setItemAnnotation
getAnnotation :: Typeable value => Item a -> Maybe value
getAnnotation :: forall value a. Typeable value => Item a -> Maybe value
getAnnotation = Item a -> Maybe value
forall value a. Typeable value => Item a -> Maybe value
getItemAnnotation