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

-- * Register a formatter
, useFormatter
, liftFormatter

-- * Re-exports
, Config
) where

import           Test.Hspec.Core.Runner
import           Test.Hspec.Core.Format hiding (FormatConfig(..))
import qualified Test.Hspec.Core.Format as Latest

-- |
-- 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
#if MIN_VERSION_hspec_core(2,9,0)
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 }
#else
registerFormatter_ _ config = config
#endif

-- | 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
liftFormatConfig

data FormatConfig = FormatConfig {
  FormatConfig -> Bool
formatConfigUseColor :: Bool
, FormatConfig -> Bool
formatConfigUseDiff :: Bool
, FormatConfig -> Bool
formatConfigPrintTimes :: Bool
, FormatConfig -> Bool
formatConfigHtmlOutput :: Bool
, FormatConfig -> Bool
formatConfigPrintCpuTime :: Bool
, FormatConfig -> Integer
formatConfigUsedSeed :: Integer
, FormatConfig -> Int
formatConfigExpectedTotalCount :: Int
}

liftFormatConfig :: Latest.FormatConfig -> FormatConfig
liftFormatConfig :: FormatConfig -> FormatConfig
liftFormatConfig FormatConfig
config = FormatConfig {
  formatConfigUseColor :: Bool
formatConfigUseColor = FormatConfig -> Bool
Latest.formatConfigUseColor FormatConfig
config
, formatConfigUseDiff :: Bool
formatConfigUseDiff = FormatConfig -> Bool
Latest.formatConfigUseDiff FormatConfig
config
, formatConfigPrintTimes :: Bool
formatConfigPrintTimes = FormatConfig -> Bool
Latest.formatConfigPrintTimes FormatConfig
config
, formatConfigHtmlOutput :: Bool
formatConfigHtmlOutput = FormatConfig -> Bool
Latest.formatConfigHtmlOutput FormatConfig
config
, formatConfigPrintCpuTime :: Bool
formatConfigPrintCpuTime = FormatConfig -> Bool
Latest.formatConfigPrintCpuTime FormatConfig
config
, formatConfigUsedSeed :: Integer
formatConfigUsedSeed = FormatConfig -> Integer
Latest.formatConfigUsedSeed FormatConfig
config
#if MIN_VERSION_hspec_core(2,9,0)
, formatConfigExpectedTotalCount :: Int
formatConfigExpectedTotalCount = FormatConfig -> Int
Latest.formatConfigExpectedTotalCount FormatConfig
config
#else
, formatConfigExpectedTotalCount = Latest.formatConfigItemCount config
#endif
}