{-# LANGUAGE ViewPatterns #-}
-- |
-- Stability: stable
module Test.Hspec.Api.Format.V2 (
  Format
, FormatConfig(..)
, defaultFormatConfig
, Event(..)
, Progress
, Path
, Location(..)
, Seconds(..)
, Item(..)
, Result(..)
, FailureReason(..)
, monadic

-- * Register a formatter
, registerFormatter
, useFormatter
, liftFormatter

-- * Re-exports
, 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

-- |
-- Make a formatter available for use with @--format@.
registerFormatter :: (String, FormatConfig -> IO Format) -> Config -> Config
registerFormatter :: (String, FormatConfig -> IO Format) -> Config -> Config
registerFormatter = (String, FormatConfig -> IO Format) -> Config -> Config
registerFormatter_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String, FormatConfig -> IO Format)
-> (String, FormatConfig -> IO Format)
liftFormatter

-- |
-- Make a formatter available for use with @--format@ and use it by default.
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 :: Maybe (FormatConfig -> IO Format)
configFormat = forall a. a -> Maybe a
Just FormatConfig -> IO Format
format }

-- copy of Test.Hspec.Core.Runner.registerFormatter
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 :: [(String, FormatConfig -> IO Format)]
configAvailableFormatters = (String, FormatConfig -> IO Format)
formatter forall a. a -> [a] -> [a]
: Config -> [(String, FormatConfig -> IO Format)]
configAvailableFormatters Config
config }

-- | Make a formatter compatible with types from "Test.Hspec.Core.Format".
liftFormatter :: (String, FormatConfig -> IO Format) -> (String, Latest.FormatConfig -> IO Format)
liftFormatter :: (String, FormatConfig -> IO Format)
-> (String, FormatConfig -> IO Format)
liftFormatter = 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 forall b c a. (b -> c) -> (a -> b) -> a -> c
. FormatConfig -> FormatConfig
unliftFormatConfig