{-# LANGUAGE CPP, DeriveDataTypeable, GeneralizedNewtypeDeriving #-}
{-# OPTIONS_GHC -fno-warn-type-defaults #-}
module Test.Tasty.Options.Core
( NumThreads(..)
, Timeout(..)
, mkTimeout
, coreOptions
)
where
import Control.Monad (mfilter)
import Data.Proxy
import Data.Typeable
import Data.Fixed
import Options.Applicative hiding (str)
import GHC.Conc
#if !MIN_VERSION_base(4,11,0)
import Data.Monoid
#endif
import Test.Tasty.Options
import Test.Tasty.Patterns
newtype NumThreads = NumThreads { NumThreads -> Int
getNumThreads :: Int }
deriving (NumThreads -> NumThreads -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NumThreads -> NumThreads -> Bool
$c/= :: NumThreads -> NumThreads -> Bool
== :: NumThreads -> NumThreads -> Bool
$c== :: NumThreads -> NumThreads -> Bool
Eq, Eq NumThreads
NumThreads -> NumThreads -> Bool
NumThreads -> NumThreads -> Ordering
NumThreads -> NumThreads -> NumThreads
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: NumThreads -> NumThreads -> NumThreads
$cmin :: NumThreads -> NumThreads -> NumThreads
max :: NumThreads -> NumThreads -> NumThreads
$cmax :: NumThreads -> NumThreads -> NumThreads
>= :: NumThreads -> NumThreads -> Bool
$c>= :: NumThreads -> NumThreads -> Bool
> :: NumThreads -> NumThreads -> Bool
$c> :: NumThreads -> NumThreads -> Bool
<= :: NumThreads -> NumThreads -> Bool
$c<= :: NumThreads -> NumThreads -> Bool
< :: NumThreads -> NumThreads -> Bool
$c< :: NumThreads -> NumThreads -> Bool
compare :: NumThreads -> NumThreads -> Ordering
$ccompare :: NumThreads -> NumThreads -> Ordering
Ord, Integer -> NumThreads
NumThreads -> NumThreads
NumThreads -> NumThreads -> NumThreads
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> NumThreads
$cfromInteger :: Integer -> NumThreads
signum :: NumThreads -> NumThreads
$csignum :: NumThreads -> NumThreads
abs :: NumThreads -> NumThreads
$cabs :: NumThreads -> NumThreads
negate :: NumThreads -> NumThreads
$cnegate :: NumThreads -> NumThreads
* :: NumThreads -> NumThreads -> NumThreads
$c* :: NumThreads -> NumThreads -> NumThreads
- :: NumThreads -> NumThreads -> NumThreads
$c- :: NumThreads -> NumThreads -> NumThreads
+ :: NumThreads -> NumThreads -> NumThreads
$c+ :: NumThreads -> NumThreads -> NumThreads
Num, Typeable)
instance IsOption NumThreads where
defaultValue :: NumThreads
defaultValue = Int -> NumThreads
NumThreads Int
numCapabilities
parseValue :: String -> Maybe NumThreads
parseValue = forall (m :: * -> *) a. MonadPlus m => (a -> Bool) -> m a -> m a
mfilter NumThreads -> Bool
onlyPositive forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int -> NumThreads
NumThreads forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Read a => String -> Maybe a
safeRead
optionName :: Tagged NumThreads String
optionName = forall (m :: * -> *) a. Monad m => a -> m a
return String
"num-threads"
optionHelp :: Tagged NumThreads String
optionHelp = forall (m :: * -> *) a. Monad m => a -> m a
return String
"Number of threads to use for tests execution"
optionCLParser :: Parser NumThreads
optionCLParser = forall v. IsOption v => Mod OptionFields v -> Parser v
mkOptionCLParser (forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'j' forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"NUMBER")
showDefaultValue :: NumThreads -> Maybe String
showDefaultValue NumThreads
_ = forall a. a -> Maybe a
Just String
"# of cores/capabilities"
onlyPositive :: NumThreads -> Bool
onlyPositive :: NumThreads -> Bool
onlyPositive (NumThreads Int
x) = Int
x forall a. Ord a => a -> a -> Bool
> Int
0
data Timeout
= Timeout Integer String
| NoTimeout
deriving (Int -> Timeout -> ShowS
[Timeout] -> ShowS
Timeout -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Timeout] -> ShowS
$cshowList :: [Timeout] -> ShowS
show :: Timeout -> String
$cshow :: Timeout -> String
showsPrec :: Int -> Timeout -> ShowS
$cshowsPrec :: Int -> Timeout -> ShowS
Show, Typeable)
instance IsOption Timeout where
defaultValue :: Timeout
defaultValue = Timeout
NoTimeout
parseValue :: String -> Maybe Timeout
parseValue String
str =
Integer -> String -> Timeout
Timeout
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> Maybe Integer
parseTimeout String
str
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure String
str
optionName :: Tagged Timeout String
optionName = forall (m :: * -> *) a. Monad m => a -> m a
return String
"timeout"
optionHelp :: Tagged Timeout String
optionHelp = forall (m :: * -> *) a. Monad m => a -> m a
return String
"Timeout for individual tests (suffixes: ms,s,m,h; default: s)"
optionCLParser :: Parser Timeout
optionCLParser = forall v. IsOption v => Mod OptionFields v -> Parser v
mkOptionCLParser (forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
't' forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"DURATION")
parseTimeout :: String -> Maybe Integer
parseTimeout :: String -> Maybe Integer
parseTimeout String
str =
(forall a b. (RealFrac a, Integral b) => a -> b
round :: Micro -> Integer) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. Num a => a -> a -> a
* Micro
10forall a b. (Num a, Integral b) => a -> b -> a
^Integer
6) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
case forall a. Read a => ReadS a
reads String
str of
[(Micro
n, String
suffix)] ->
case String
suffix of
String
"ms" -> forall a. a -> Maybe a
Just (Micro
n forall a. Fractional a => a -> a -> a
/ Micro
10forall a b. (Num a, Integral b) => a -> b -> a
^Integer
3)
String
"" -> forall a. a -> Maybe a
Just Micro
n
String
"s" -> forall a. a -> Maybe a
Just Micro
n
String
"m" -> forall a. a -> Maybe a
Just (Micro
n forall a. Num a => a -> a -> a
* Micro
60)
String
"h" -> forall a. a -> Maybe a
Just (Micro
n forall a. Num a => a -> a -> a
* Micro
60forall a b. (Num a, Integral b) => a -> b -> a
^Integer
2)
String
_ -> forall a. Maybe a
Nothing
[(Micro, String)]
_ -> forall a. Maybe a
Nothing
mkTimeout
:: Integer
-> Timeout
mkTimeout :: Integer -> Timeout
mkTimeout Integer
n =
Integer -> String -> Timeout
Timeout Integer
n forall a b. (a -> b) -> a -> b
$
forall {k} (a :: k). HasResolution a => Bool -> Fixed a -> String
showFixed Bool
True (forall a. Num a => Integer -> a
fromInteger Integer
n forall a. Fractional a => a -> a -> a
/ (Micro
10forall a b. (Num a, Integral b) => a -> b -> a
^Integer
6) :: Micro) forall a. [a] -> [a] -> [a]
++ String
"s"
coreOptions :: [OptionDescription]
coreOptions :: [OptionDescription]
coreOptions =
[ forall v. IsOption v => Proxy v -> OptionDescription
Option (forall {k} (t :: k). Proxy t
Proxy :: Proxy TestPattern)
, forall v. IsOption v => Proxy v -> OptionDescription
Option (forall {k} (t :: k). Proxy t
Proxy :: Proxy Timeout)
]