{-# LANGUAGE ViewPatterns #-}
module Test.Hspec.Api.Format.V2 (
Format
, FormatConfig(..)
, defaultFormatConfig
, Event(..)
, Progress
, Path
, Location(..)
, Seconds(..)
, Item(..)
, Result(..)
, FailureReason(..)
, monadic
, registerFormatter
, useFormatter
, liftFormatter
, SpecWith
, Config
, modifyConfig
) where
import Test.Hspec.Core.Runner (Config(..))
import Test.Hspec.Core.Spec (modifyConfig, SpecWith)
import Test.Hspec.Core.Format hiding (FormatConfig(..), defaultFormatConfig)
import qualified Test.Hspec.Core.Format as Latest
import Test.Hspec.Api.Format.V2.Config
registerFormatter :: (String, FormatConfig -> IO Format) -> Config -> Config
registerFormatter :: (String, FormatConfig -> IO Format) -> Config -> Config
registerFormatter = (String, FormatConfig -> IO Format) -> Config -> Config
registerFormatter_ ((String, FormatConfig -> IO Format) -> Config -> Config)
-> ((String, FormatConfig -> IO Format)
-> (String, FormatConfig -> IO Format))
-> (String, FormatConfig -> IO Format)
-> Config
-> Config
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String, FormatConfig -> IO Format)
-> (String, FormatConfig -> IO Format)
liftFormatter
useFormatter :: (String, FormatConfig -> IO Format) -> Config -> Config
useFormatter :: (String, FormatConfig -> IO Format) -> Config -> Config
useFormatter ((String, FormatConfig -> IO Format)
-> (String, FormatConfig -> IO Format)
liftFormatter -> formatter :: (String, FormatConfig -> IO Format)
formatter@(String
_, FormatConfig -> IO Format
format)) Config
config = ((String, FormatConfig -> IO Format) -> Config -> Config
registerFormatter_ (String, FormatConfig -> IO Format)
formatter Config
config) { configFormat = Just format }
registerFormatter_ :: (String, Latest.FormatConfig -> IO Latest.Format) -> Config -> Config
registerFormatter_ :: (String, FormatConfig -> IO Format) -> Config -> Config
registerFormatter_ (String, FormatConfig -> IO Format)
formatter Config
config = Config
config { configAvailableFormatters = formatter : configAvailableFormatters config }
liftFormatter :: (String, FormatConfig -> IO Format) -> (String, Latest.FormatConfig -> IO Format)
liftFormatter :: (String, FormatConfig -> IO Format)
-> (String, FormatConfig -> IO Format)
liftFormatter = ((FormatConfig -> IO Format) -> FormatConfig -> IO Format)
-> (String, FormatConfig -> IO Format)
-> (String, FormatConfig -> IO Format)
forall a b. (a -> b) -> (String, a) -> (String, b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (FormatConfig -> IO Format) -> FormatConfig -> IO Format
liftFormat
where
liftFormat :: (FormatConfig -> IO Format) -> Latest.FormatConfig -> IO Format
liftFormat :: (FormatConfig -> IO Format) -> FormatConfig -> IO Format
liftFormat FormatConfig -> IO Format
format = FormatConfig -> IO Format
format (FormatConfig -> IO Format)
-> (FormatConfig -> FormatConfig) -> FormatConfig -> IO Format
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FormatConfig -> FormatConfig
unliftFormatConfig