{-# LANGUAGE CPP #-}
module Test.Hspec.Core.Config (
Config (..)
, ColorMode(..)
, defaultConfig
, readConfig
, configAddFilter
, configQuickCheckArgs
, readFailureReportOnRerun
, applyFailureReport
#ifdef TEST
, readConfigFiles
#endif
) where
import Prelude ()
import Test.Hspec.Core.Compat
import Control.Exception
import Data.Maybe
import System.IO
import System.IO.Error
import System.Exit
import System.FilePath
import System.Directory
import System.Environment (getProgName)
import qualified Test.QuickCheck as QC
import Test.Hspec.Core.Util
import Test.Hspec.Core.Config.Options
import Test.Hspec.Core.FailureReport
import Test.Hspec.Core.QuickCheckUtil (mkGen)
import Test.Hspec.Core.Example (Params(..), defaultParams)
configAddFilter :: (Path -> Bool) -> Config -> Config
configAddFilter :: (Path -> Bool) -> Config -> Config
configAddFilter Path -> Bool
p1 Config
c = Config
c {
configFilterPredicate :: Maybe (Path -> Bool)
configFilterPredicate = (Path -> Bool) -> Maybe (Path -> Bool)
forall a. a -> Maybe a
Just Path -> Bool
p1 Maybe (Path -> Bool)
-> Maybe (Path -> Bool) -> Maybe (Path -> Bool)
`filterOr` Config -> Maybe (Path -> Bool)
configFilterPredicate Config
c
}
applyFailureReport :: Maybe FailureReport -> Config -> Config
applyFailureReport :: Maybe FailureReport -> Config -> Config
applyFailureReport Maybe FailureReport
mFailureReport Config
opts = Config
opts {
configFilterPredicate :: Maybe (Path -> Bool)
configFilterPredicate = Maybe (Path -> Bool)
matchFilter Maybe (Path -> Bool)
-> Maybe (Path -> Bool) -> Maybe (Path -> Bool)
`filterOr` Maybe (Path -> Bool)
rerunFilter
, configQuickCheckSeed :: Maybe Integer
configQuickCheckSeed = Maybe Integer
mSeed
, configQuickCheckMaxSuccess :: Maybe Int
configQuickCheckMaxSuccess = Maybe Int
mMaxSuccess
, configQuickCheckMaxDiscardRatio :: Maybe Int
configQuickCheckMaxDiscardRatio = Maybe Int
mMaxDiscardRatio
, configQuickCheckMaxSize :: Maybe Int
configQuickCheckMaxSize = Maybe Int
mMaxSize
}
where
mSeed :: Maybe Integer
mSeed = Config -> Maybe Integer
configQuickCheckSeed Config
opts Maybe Integer -> Maybe Integer -> Maybe Integer
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (FailureReport -> Integer
failureReportSeed (FailureReport -> Integer) -> Maybe FailureReport -> Maybe Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe FailureReport
mFailureReport)
mMaxSuccess :: Maybe Int
mMaxSuccess = Config -> Maybe Int
configQuickCheckMaxSuccess Config
opts Maybe Int -> Maybe Int -> Maybe Int
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (FailureReport -> Int
failureReportMaxSuccess (FailureReport -> Int) -> Maybe FailureReport -> Maybe Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe FailureReport
mFailureReport)
mMaxSize :: Maybe Int
mMaxSize = Config -> Maybe Int
configQuickCheckMaxSize Config
opts Maybe Int -> Maybe Int -> Maybe Int
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (FailureReport -> Int
failureReportMaxSize (FailureReport -> Int) -> Maybe FailureReport -> Maybe Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe FailureReport
mFailureReport)
mMaxDiscardRatio :: Maybe Int
mMaxDiscardRatio = Config -> Maybe Int
configQuickCheckMaxDiscardRatio Config
opts Maybe Int -> Maybe Int -> Maybe Int
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (FailureReport -> Int
failureReportMaxDiscardRatio (FailureReport -> Int) -> Maybe FailureReport -> Maybe Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe FailureReport
mFailureReport)
matchFilter :: Maybe (Path -> Bool)
matchFilter = Config -> Maybe (Path -> Bool)
configFilterPredicate Config
opts
rerunFilter :: Maybe (Path -> Bool)
rerunFilter = case FailureReport -> [Path]
failureReportPaths (FailureReport -> [Path]) -> Maybe FailureReport -> Maybe [Path]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe FailureReport
mFailureReport of
Just [] -> Maybe (Path -> Bool)
forall a. Maybe a
Nothing
Just [Path]
xs -> (Path -> Bool) -> Maybe (Path -> Bool)
forall a. a -> Maybe a
Just (Path -> [Path] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Path]
xs)
Maybe [Path]
Nothing -> Maybe (Path -> Bool)
forall a. Maybe a
Nothing
configQuickCheckArgs :: Config -> QC.Args
configQuickCheckArgs :: Config -> Args
configQuickCheckArgs Config
c = Args
qcArgs
where
qcArgs :: Args
qcArgs = (
(Args -> Args)
-> (Integer -> Args -> Args) -> Maybe Integer -> Args -> Args
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Args -> Args
forall a. a -> a
id Integer -> Args -> Args
setSeed (Config -> Maybe Integer
configQuickCheckSeed Config
c)
(Args -> Args) -> (Args -> Args) -> Args -> Args
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Args -> Args)
-> (Int -> Args -> Args) -> Maybe Int -> Args -> Args
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Args -> Args
forall a. a -> a
id Int -> Args -> Args
setMaxDiscardRatio (Config -> Maybe Int
configQuickCheckMaxDiscardRatio Config
c)
(Args -> Args) -> (Args -> Args) -> Args -> Args
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Args -> Args)
-> (Int -> Args -> Args) -> Maybe Int -> Args -> Args
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Args -> Args
forall a. a -> a
id Int -> Args -> Args
setMaxSize (Config -> Maybe Int
configQuickCheckMaxSize Config
c)
(Args -> Args) -> (Args -> Args) -> Args -> Args
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Args -> Args)
-> (Int -> Args -> Args) -> Maybe Int -> Args -> Args
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Args -> Args
forall a. a -> a
id Int -> Args -> Args
setMaxSuccess (Config -> Maybe Int
configQuickCheckMaxSuccess Config
c)) (Params -> Args
paramsQuickCheckArgs Params
defaultParams)
setMaxSuccess :: Int -> QC.Args -> QC.Args
setMaxSuccess :: Int -> Args -> Args
setMaxSuccess Int
n Args
args = Args
args {maxSuccess :: Int
QC.maxSuccess = Int
n}
setMaxSize :: Int -> QC.Args -> QC.Args
setMaxSize :: Int -> Args -> Args
setMaxSize Int
n Args
args = Args
args {maxSize :: Int
QC.maxSize = Int
n}
setMaxDiscardRatio :: Int -> QC.Args -> QC.Args
setMaxDiscardRatio :: Int -> Args -> Args
setMaxDiscardRatio Int
n Args
args = Args
args {maxDiscardRatio :: Int
QC.maxDiscardRatio = Int
n}
setSeed :: Integer -> QC.Args -> QC.Args
setSeed :: Integer -> Args -> Args
setSeed Integer
n Args
args = Args
args {replay :: Maybe (QCGen, Int)
QC.replay = (QCGen, Int) -> Maybe (QCGen, Int)
forall a. a -> Maybe a
Just (Int -> QCGen
mkGen (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
n), Int
0)}
readConfig :: Config -> [String] -> IO Config
readConfig :: Config -> [String] -> IO Config
readConfig Config
opts_ [String]
args = do
String
prog <- IO String
getProgName
[ConfigFile]
configFiles <- do
Bool
ignore <- Config -> [String] -> IO Bool
ignoreConfigFile Config
opts_ [String]
args
case Bool
ignore of
Bool
True -> [ConfigFile] -> IO [ConfigFile]
forall (m :: * -> *) a. Monad m => a -> m a
return []
Bool
False -> IO [ConfigFile]
readConfigFiles
Maybe [String]
envVar <- (String -> [String]) -> Maybe String -> Maybe [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> [String]
words (Maybe String -> Maybe [String])
-> IO (Maybe String) -> IO (Maybe [String])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO (Maybe String)
lookupEnv String
envVarName
case Config
-> String
-> [ConfigFile]
-> Maybe [String]
-> [String]
-> Either (ExitCode, String) Config
parseOptions Config
opts_ String
prog [ConfigFile]
configFiles Maybe [String]
envVar [String]
args of
Left (ExitCode
err, String
msg) -> ExitCode -> String -> IO Config
forall a. ExitCode -> String -> IO a
exitWithMessage ExitCode
err String
msg
Right Config
opts -> Config -> IO Config
forall (m :: * -> *) a. Monad m => a -> m a
return Config
opts
readFailureReportOnRerun :: Config -> IO (Maybe FailureReport)
readFailureReportOnRerun :: Config -> IO (Maybe FailureReport)
readFailureReportOnRerun Config
config
| Config -> Bool
configRerun Config
config = Config -> IO (Maybe FailureReport)
readFailureReport Config
config
| Bool
otherwise = Maybe FailureReport -> IO (Maybe FailureReport)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FailureReport
forall a. Maybe a
Nothing
readConfigFiles :: IO [ConfigFile]
readConfigFiles :: IO [ConfigFile]
readConfigFiles = do
Maybe ConfigFile
global <- IO (Maybe ConfigFile)
readGlobalConfigFile
Maybe ConfigFile
local <- IO (Maybe ConfigFile)
readLocalConfigFile
[ConfigFile] -> IO [ConfigFile]
forall (m :: * -> *) a. Monad m => a -> m a
return ([ConfigFile] -> IO [ConfigFile])
-> [ConfigFile] -> IO [ConfigFile]
forall a b. (a -> b) -> a -> b
$ [Maybe ConfigFile] -> [ConfigFile]
forall a. [Maybe a] -> [a]
catMaybes [Maybe ConfigFile
global, Maybe ConfigFile
local]
readGlobalConfigFile :: IO (Maybe ConfigFile)
readGlobalConfigFile :: IO (Maybe ConfigFile)
readGlobalConfigFile = do
Either () String
mHome <- (IOError -> Maybe ()) -> IO String -> IO (Either () String)
forall e b a.
Exception e =>
(e -> Maybe b) -> IO a -> IO (Either b a)
tryJust (Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Maybe ()) -> (IOError -> Bool) -> IOError -> Maybe ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IOError -> Bool
isDoesNotExistError) IO String
getHomeDirectory
case Either () String
mHome of
Left ()
_ -> Maybe ConfigFile -> IO (Maybe ConfigFile)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ConfigFile
forall a. Maybe a
Nothing
Right String
home -> String -> IO (Maybe ConfigFile)
readConfigFile (String
home String -> String -> String
</> String
".hspec")
readLocalConfigFile :: IO (Maybe ConfigFile)
readLocalConfigFile :: IO (Maybe ConfigFile)
readLocalConfigFile = do
Either () String
mName <- (IOError -> Maybe ()) -> IO String -> IO (Either () String)
forall e b a.
Exception e =>
(e -> Maybe b) -> IO a -> IO (Either b a)
tryJust (Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Maybe ()) -> (IOError -> Bool) -> IOError -> Maybe ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IOError -> Bool
isDoesNotExistError) (String -> IO String
canonicalizePath String
".hspec")
case Either () String
mName of
Left ()
_ -> Maybe ConfigFile -> IO (Maybe ConfigFile)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ConfigFile
forall a. Maybe a
Nothing
Right String
name -> String -> IO (Maybe ConfigFile)
readConfigFile String
name
readConfigFile :: FilePath -> IO (Maybe ConfigFile)
readConfigFile :: String -> IO (Maybe ConfigFile)
readConfigFile String
name = do
Bool
exists <- String -> IO Bool
doesFileExist String
name
if Bool
exists then ConfigFile -> Maybe ConfigFile
forall a. a -> Maybe a
Just (ConfigFile -> Maybe ConfigFile)
-> (String -> ConfigFile) -> String -> Maybe ConfigFile
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (,) String
name ([String] -> ConfigFile)
-> (String -> [String]) -> String -> ConfigFile
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
words (String -> Maybe ConfigFile) -> IO String -> IO (Maybe ConfigFile)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO String
readFile String
name else Maybe ConfigFile -> IO (Maybe ConfigFile)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ConfigFile
forall a. Maybe a
Nothing
exitWithMessage :: ExitCode -> String -> IO a
exitWithMessage :: ExitCode -> String -> IO a
exitWithMessage ExitCode
err String
msg = do
Handle -> String -> IO ()
hPutStr Handle
h String
msg
ExitCode -> IO a
forall a. ExitCode -> IO a
exitWith ExitCode
err
where
h :: Handle
h = case ExitCode
err of
ExitCode
ExitSuccess -> Handle
stdout
ExitCode
_ -> Handle
stderr