module Test.Hspec.JUnit.Formatter.Env
( whenEnabled
, use
, add
, register
, formatter
, module Api
) where
import Prelude
import Test.Hspec.Api.Format.V1 as Api
import Test.Hspec.Core.Spec (runIO)
import Test.Hspec.JUnit.Config
import Test.Hspec.JUnit.Config.Env
import qualified Test.Hspec.JUnit.Formatter as JUnit
whenEnabled :: (SpecWith a -> SpecWith a) -> SpecWith a -> SpecWith a
whenEnabled :: forall a. (SpecWith a -> SpecWith a) -> SpecWith a -> SpecWith a
whenEnabled SpecWith a -> SpecWith a
hook SpecWith a
spec = do
Bool
enabled <- IO Bool -> SpecM a Bool
forall r a. IO r -> SpecM a r
runIO IO Bool
envJUnitEnabled
if Bool
enabled then SpecWith a -> SpecWith a
hook SpecWith a
spec else SpecWith a
spec
withConfig
:: (JUnitConfig -> SpecWith a -> SpecWith a) -> SpecWith a -> SpecWith a
withConfig :: forall a.
(JUnitConfig -> SpecWith a -> SpecWith a)
-> SpecWith a -> SpecWith a
withConfig JUnitConfig -> SpecWith a -> SpecWith a
toHook SpecWith a
spec = do
JUnitConfig
config <- IO JUnitConfig -> SpecM a JUnitConfig
forall r a. IO r -> SpecM a r
runIO IO JUnitConfig
envJUnitConfig
JUnitConfig -> SpecWith a -> SpecWith a
toHook JUnitConfig
config SpecWith a
spec
use :: SpecWith a -> SpecWith a
use :: forall a. SpecWith a -> SpecWith a
use = (JUnitConfig -> SpecWith a -> SpecWith a)
-> SpecWith a -> SpecWith a
forall a.
(JUnitConfig -> SpecWith a -> SpecWith a)
-> SpecWith a -> SpecWith a
withConfig JUnitConfig -> SpecWith a -> SpecWith a
forall a. JUnitConfig -> SpecWith a -> SpecWith a
JUnit.use
add :: SpecWith a -> SpecWith a
add :: forall a. SpecWith a -> SpecWith a
add = (JUnitConfig -> SpecWith a -> SpecWith a)
-> SpecWith a -> SpecWith a
forall a.
(JUnitConfig -> SpecWith a -> SpecWith a)
-> SpecWith a -> SpecWith a
withConfig JUnitConfig -> SpecWith a -> SpecWith a
forall a. JUnitConfig -> SpecWith a -> SpecWith a
JUnit.add
register :: SpecWith a -> SpecWith a
register :: forall a. SpecWith a -> SpecWith a
register = (JUnitConfig -> SpecWith a -> SpecWith a)
-> SpecWith a -> SpecWith a
forall a.
(JUnitConfig -> SpecWith a -> SpecWith a)
-> SpecWith a -> SpecWith a
withConfig JUnitConfig -> SpecWith a -> SpecWith a
forall a. JUnitConfig -> SpecWith a -> SpecWith a
JUnit.register
formatter :: IO (String, FormatConfig -> IO Format)
formatter :: IO (String, FormatConfig -> IO Format)
formatter = JUnitConfig -> (String, FormatConfig -> IO Format)
JUnit.formatter (JUnitConfig -> (String, FormatConfig -> IO Format))
-> IO JUnitConfig -> IO (String, FormatConfig -> IO Format)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO JUnitConfig
envJUnitConfig