module Test.Tasty.Options.Core
( NumThreads(..)
, Timeout(..)
, mkTimeout
, coreOptions
)
where
import Control.Monad (mfilter)
import Data.Typeable
import Data.Proxy
import Data.Tagged
import Data.Fixed
import Options.Applicative
import GHC.Conc
import Test.Tasty.Options
import Test.Tasty.Patterns
newtype NumThreads = NumThreads { getNumThreads :: Int }
deriving (Eq, Ord, Num, Typeable)
instance IsOption NumThreads where
defaultValue = NumThreads numCapabilities
parseValue = mfilter onlyPositive . fmap NumThreads . safeRead
optionName = return "num-threads"
optionHelp = return "Number of threads to use for tests execution"
optionCLParser =
option parse
( short 'j'
<> long name
<> help (untag (optionHelp :: Tagged NumThreads String))
)
where
name = untag (optionName :: Tagged NumThreads String)
parse = str >>=
maybe (readerError $ "Could not parse " ++ name) pure <$> parseValue
onlyPositive :: NumThreads -> Bool
onlyPositive (NumThreads x) = x > 0
data Timeout
= Timeout Integer String
| NoTimeout
deriving (Show, Typeable)
instance IsOption Timeout where
defaultValue = NoTimeout
parseValue str =
Timeout
<$> parseTimeout str
<*> pure str
optionName = return "timeout"
optionHelp = return "Timeout for individual tests (suffixes: ms,s,m,h; default: s)"
optionCLParser =
option parse
( short 't'
<> long name
<> help (untag (optionHelp :: Tagged Timeout String))
)
where
name = untag (optionName :: Tagged Timeout String)
parse = str >>=
maybe (readerError $ "Could not parse " ++ name) pure <$> parseValue
parseTimeout :: String -> Maybe Integer
parseTimeout str =
(round :: Micro -> Integer) . (* 10^6) <$>
case reads str of
[(n, suffix)] ->
case suffix of
"ms" -> Just (n / 10^3)
"" -> Just n
"s" -> Just n
"m" -> Just (n * 60)
"h" -> Just (n * 60^2)
_ -> Nothing
_ -> Nothing
mkTimeout
:: Integer
-> Timeout
mkTimeout n =
Timeout n $
showFixed True (fromInteger n / (10^6) :: Micro) ++ "s"
coreOptions :: [OptionDescription]
coreOptions =
[ Option (Proxy :: Proxy TestPattern)
, Option (Proxy :: Proxy Timeout)
]