{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE IncoherentInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-missing-signatures #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}

-- |
--
-- This redefines the HedgehogTest from tasty-hedgehog to display
-- color during the reporting
module Test.Tasty.HedgehogTest
  ( HedgehogTest (..),
    HedgehogTestLimit (..),
    HedgehogDiscardLimit (..),
    HedgehogShrinkLimit (..),
    HedgehogShrinkRetries (..),
    HedgehogReplay (..),
    HedgehogShowReplay (..),
    ModuleName (..),
    testProperty,
    groupByModuleName,
    getModuleName,
  )
where

import Data.MultiMap hiding (foldr, size)
import GHC.Stack
import Hedgehog hiding (test, (===))
import Hedgehog.Internal.Config (UseColor, detectColor)
import Hedgehog.Internal.Property
import Hedgehog.Internal.Report as Hedgehog
import Hedgehog.Internal.Runner as Hedgehog
import Hedgehog.Internal.Seed as Seed
import Protolude as P hiding (empty, toList, unwords, words)
import qualified Protolude as P
import Test.Tasty as Tasty
import Test.Tasty.Options as Tasty
import Test.Tasty.Providers as Tasty
import Test.Tasty.Runners as Tasty
  ( TestTree (..),
    foldSingle,
    foldTestTree,
    trivialFold,
  )
import Prelude (String, unwords, words)

-- | Hedgehog Property as a Tasty Test
data HedgehogTest = HedgehogTest Tasty.TestName Property
  deriving (Typeable)

-- | Create a 'Test' from a Hedgehog property
testProperty :: Tasty.TestName -> Property -> Tasty.TestTree
testProperty :: TestName -> Property -> TestTree
testProperty TestName
name Property
prop = TestName -> HedgehogTest -> TestTree
forall t. IsTest t => TestName -> t -> TestTree
singleTest TestName
name (TestName -> Property -> HedgehogTest
HedgehogTest TestName
name Property
prop)

instance Tasty.IsTest HedgehogTest where
  testOptions :: Tagged HedgehogTest [OptionDescription]
testOptions =
    [OptionDescription] -> Tagged HedgehogTest [OptionDescription]
forall (m :: * -> *) a. Monad m => a -> m a
return
      [ Proxy HedgehogReplay -> OptionDescription
forall v. IsOption v => Proxy v -> OptionDescription
Tasty.Option (Proxy HedgehogReplay
forall k (t :: k). Proxy t
Proxy :: Proxy HedgehogReplay),
        Proxy HedgehogShowReplay -> OptionDescription
forall v. IsOption v => Proxy v -> OptionDescription
Tasty.Option (Proxy HedgehogShowReplay
forall k (t :: k). Proxy t
Proxy :: Proxy HedgehogShowReplay),
        Proxy HedgehogTestLimit -> OptionDescription
forall v. IsOption v => Proxy v -> OptionDescription
Tasty.Option (Proxy HedgehogTestLimit
forall k (t :: k). Proxy t
Proxy :: Proxy HedgehogTestLimit),
        Proxy HedgehogDiscardLimit -> OptionDescription
forall v. IsOption v => Proxy v -> OptionDescription
Tasty.Option (Proxy HedgehogDiscardLimit
forall k (t :: k). Proxy t
Proxy :: Proxy HedgehogDiscardLimit),
        Proxy HedgehogShrinkLimit -> OptionDescription
forall v. IsOption v => Proxy v -> OptionDescription
Tasty.Option (Proxy HedgehogShrinkLimit
forall k (t :: k). Proxy t
Proxy :: Proxy HedgehogShrinkLimit),
        Proxy HedgehogShrinkRetries -> OptionDescription
forall v. IsOption v => Proxy v -> OptionDescription
Tasty.Option (Proxy HedgehogShrinkRetries
forall k (t :: k). Proxy t
Proxy :: Proxy HedgehogShrinkRetries)
      ]

  run :: OptionSet -> HedgehogTest -> (Progress -> IO ()) -> IO Result
run OptionSet
opts (HedgehogTest TestName
name (Property PropertyConfig
pConfig PropertyT IO ()
pTest)) Progress -> IO ()
yieldProgress = do
    UseColor
useColor <- IO UseColor
forall (m :: * -> *). MonadIO m => m UseColor
detectColor
    let HedgehogReplay Maybe (Size, Seed)
replay = OptionSet -> HedgehogReplay
forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
opts
        HedgehogTestLimit Maybe TestLimit
mTests = OptionSet -> HedgehogTestLimit
forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
opts
        HedgehogDiscardLimit Maybe DiscardLimit
mDiscards = OptionSet -> HedgehogDiscardLimit
forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
opts
        HedgehogShrinkLimit Maybe ShrinkLimit
mShrinks = OptionSet -> HedgehogShrinkLimit
forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
opts
        HedgehogShrinkRetries Maybe ShrinkRetries
mRetries = OptionSet -> HedgehogShrinkRetries
forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
opts
        showReplay :: HedgehogShowReplay
showReplay = OptionSet -> HedgehogShowReplay
forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
opts
        config :: PropertyConfig
config =
          DiscardLimit
-> ShrinkLimit
-> ShrinkRetries
-> TerminationCriteria
-> PropertyConfig
PropertyConfig
            (DiscardLimit -> Maybe DiscardLimit -> DiscardLimit
forall a. a -> Maybe a -> a
fromMaybe (PropertyConfig -> DiscardLimit
propertyDiscardLimit PropertyConfig
pConfig) Maybe DiscardLimit
mDiscards)
            (ShrinkLimit -> Maybe ShrinkLimit -> ShrinkLimit
forall a. a -> Maybe a -> a
fromMaybe (PropertyConfig -> ShrinkLimit
propertyShrinkLimit PropertyConfig
pConfig) Maybe ShrinkLimit
mShrinks)
            (ShrinkRetries -> Maybe ShrinkRetries -> ShrinkRetries
forall a. a -> Maybe a -> a
fromMaybe (PropertyConfig -> ShrinkRetries
propertyShrinkRetries PropertyConfig
pConfig) Maybe ShrinkRetries
mRetries)
            (TestLimit -> TerminationCriteria
NoConfidenceTermination (TestLimit -> TerminationCriteria)
-> TestLimit -> TerminationCriteria
forall a b. (a -> b) -> a -> b
$ TestLimit -> Maybe TestLimit -> TestLimit
forall a. a -> Maybe a -> a
fromMaybe (PropertyConfig -> TestLimit
propertyTestLimit PropertyConfig
pConfig) Maybe TestLimit
mTests)
    Seed
randSeed <- IO Seed
forall (m :: * -> *). MonadIO m => m Seed
Seed.random
    -- if we just run one test we choose a high size (knowing that the max size is 99)
    -- if the test fails we can turn it to a prop and let the shrinking process find a
    -- smaller counter-example
    let minSize :: Size
minSize = if PropertyConfig -> TestLimit
propertyTestLimit PropertyConfig
config TestLimit -> TestLimit -> Bool
forall a. Eq a => a -> a -> Bool
== TestLimit
1 then Size
50 else Size
0
    let size :: Size
size = Size -> ((Size, Seed) -> Size) -> Maybe (Size, Seed) -> Size
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe Size
minSize (Size, Seed) -> Size
forall a b. (a, b) -> a
fst Maybe (Size, Seed)
replay
        seed :: Seed
seed = Seed -> ((Size, Seed) -> Seed) -> Maybe (Size, Seed) -> Seed
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe Seed
randSeed (Size, Seed) -> Seed
forall a b. (a, b) -> b
snd Maybe (Size, Seed)
replay
    Report Result
report <- PropertyConfig
-> Size
-> Seed
-> PropertyT IO ()
-> (Report Progress -> IO ())
-> IO (Report Result)
forall (m :: * -> *).
(MonadIO m, MonadCatch m) =>
PropertyConfig
-> Size
-> Seed
-> PropertyT m ()
-> (Report Progress -> m ())
-> m (Report Result)
checkReport PropertyConfig
config Size
size Seed
seed PropertyT IO ()
pTest (Progress -> IO ()
yieldProgress (Progress -> IO ())
-> (Report Progress -> Progress) -> Report Progress -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PropertyConfig -> Report Progress -> Progress
reportToProgress PropertyConfig
config)
    let resultFn :: TestName -> Result
resultFn =
          if Report Result -> Result
forall a. Report a -> a
reportStatus Report Result
report Result -> Result -> Bool
forall a. Eq a => a -> a -> Bool
== Result
OK
            then TestName -> Result
testPassed
            else TestName -> Result
testFailed
    TestName
out <- HedgehogShowReplay
-> UseColor -> TestName -> Report Result -> IO TestName
reportOutput HedgehogShowReplay
showReplay UseColor
useColor TestName
name Report Result
report
    Result -> IO Result
forall (m :: * -> *) a. Monad m => a -> m a
return (Result -> IO Result) -> Result -> IO Result
forall a b. (a -> b) -> a -> b
$ TestName -> Result
resultFn TestName
out

reportToProgress ::
  PropertyConfig ->
  Report Hedgehog.Progress ->
  Tasty.Progress
reportToProgress :: PropertyConfig -> Report Progress -> Progress
reportToProgress PropertyConfig
config (Report TestCount
testsDone DiscardCount
_ Coverage CoverCount
_ Progress
status) =
  let TestLimit Int
testLimit = PropertyConfig -> TestLimit
propertyTestLimit PropertyConfig
config
      ShrinkLimit Int
shrinkLimit = PropertyConfig -> ShrinkLimit
propertyShrinkLimit PropertyConfig
config
      ratio :: a -> a -> a
ratio a
x a
y = a
1.0 a -> a -> a
forall a. Num a => a -> a -> a
* a -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
x a -> a -> a
forall a. Fractional a => a -> a -> a
/ a -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
y
   in -- TODO add details for tests run / discarded / shrunk
      case Progress
status of
        Progress
Running ->
          TestName -> Float -> Progress
Tasty.Progress TestName
"Running" (TestCount -> Int -> Float
forall a a a. (Fractional a, Integral a, Integral a) => a -> a -> a
ratio TestCount
testsDone Int
testLimit)
        Shrinking FailureReport
fr ->
          TestName -> Float -> Progress
Tasty.Progress TestName
"Shrinking" (ShrinkCount -> Int -> Float
forall a a a. (Fractional a, Integral a, Integral a) => a -> a -> a
ratio (FailureReport -> ShrinkCount
failureShrinks FailureReport
fr) Int
shrinkLimit)

reportOutput ::
  HedgehogShowReplay ->
  UseColor ->
  String ->
  Report Hedgehog.Result ->
  IO String
reportOutput :: HedgehogShowReplay
-> UseColor -> TestName -> Report Result -> IO TestName
reportOutput (HedgehogShowReplay Bool
showReplay) UseColor
useColor TestName
name Report Result
report = do
  TestName
s <- UseColor -> Maybe PropertyName -> Report Result -> IO TestName
forall (m :: * -> *).
MonadIO m =>
UseColor -> Maybe PropertyName -> Report Result -> m TestName
renderResult UseColor
useColor (PropertyName -> Maybe PropertyName
forall a. a -> Maybe a
Just (TestName -> PropertyName
PropertyName TestName
name)) Report Result
report
  TestName -> IO TestName
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TestName -> IO TestName) -> TestName -> IO TestName
forall a b. (a -> b) -> a -> b
$ case Report Result -> Result
forall a. Report a -> a
reportStatus Report Result
report of
    Failed FailureReport
fr ->
      let size :: Size
size = FailureReport -> Size
failureSize FailureReport
fr
          seed :: Seed
seed = FailureReport -> Seed
failureSeed FailureReport
fr
          replayStr :: TestName
replayStr =
            if Bool
showReplay
              then
                TestName
"  --hedgehog-replay \""
                  TestName -> TestName -> TestName
forall a. [a] -> [a] -> [a]
++ Size -> TestName
forall a b. (Show a, StringConv TestName b) => a -> b
show Size
size
                  TestName -> TestName -> TestName
forall a. [a] -> [a] -> [a]
++ TestName
" "
                  TestName -> TestName -> TestName
forall a. [a] -> [a] -> [a]
++ Seed -> TestName
forall a b. (Show a, StringConv TestName b) => a -> b
show Seed
seed
                  TestName -> TestName -> TestName
forall a. [a] -> [a] -> [a]
++ TestName
"\""
              else TestName
""
       in TestName
s TestName -> TestName -> TestName
forall a. [a] -> [a] -> [a]
++ TestName
replayStr TestName -> TestName -> TestName
forall a. [a] -> [a] -> [a]
++ TestName
"\n"
    Result
GaveUp ->
      TestName
s
    Result
OK ->
      -- do not report hedgehog successes because they are redundant with the Tasty report
      -- except if there is coverage information
      if Bool -> Bool
not (Bool -> Bool) -> (Report Result -> Bool) -> Report Result -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Label CoverCount] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
P.null ([Label CoverCount] -> Bool)
-> (Report Result -> [Label CoverCount]) -> Report Result -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map LabelName (Label CoverCount) -> [Label CoverCount]
forall (t :: * -> *) a. Foldable t => t a -> [a]
P.toList (Map LabelName (Label CoverCount) -> [Label CoverCount])
-> (Report Result -> Map LabelName (Label CoverCount))
-> Report Result
-> [Label CoverCount]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Coverage CoverCount -> Map LabelName (Label CoverCount)
forall a. Coverage a -> Map LabelName (Label a)
coverageLabels (Coverage CoverCount -> Map LabelName (Label CoverCount))
-> (Report Result -> Coverage CoverCount)
-> Report Result
-> Map LabelName (Label CoverCount)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Report Result -> Coverage CoverCount
forall a. Report a -> Coverage CoverCount
reportCoverage (Report Result -> Bool) -> Report Result -> Bool
forall a b. (a -> b) -> a -> b
$ Report Result
report
        then TestName
s
        else TestName
""

propertyTestLimit :: PropertyConfig -> TestLimit
propertyTestLimit :: PropertyConfig -> TestLimit
propertyTestLimit =
  let getTestLimit :: TerminationCriteria -> TestLimit
getTestLimit (EarlyTermination Confidence
_ TestLimit
tests) = TestLimit
tests
      getTestLimit (NoEarlyTermination Confidence
_ TestLimit
tests) = TestLimit
tests
      getTestLimit (NoConfidenceTermination TestLimit
tests) = TestLimit
tests
   in TerminationCriteria -> TestLimit
getTestLimit (TerminationCriteria -> TestLimit)
-> (PropertyConfig -> TerminationCriteria)
-> PropertyConfig
-> TestLimit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PropertyConfig -> TerminationCriteria
propertyTerminationCriteria

-- * OPTIONS DEFINITIONS

-- | The replay token to use for replaying a previous test run
newtype HedgehogReplay = HedgehogReplay (Maybe (Size, Seed))
  deriving (Typeable)

instance IsOption HedgehogReplay where
  defaultValue :: HedgehogReplay
defaultValue = Maybe (Size, Seed) -> HedgehogReplay
HedgehogReplay Maybe (Size, Seed)
forall a. Maybe a
Nothing

  parseValue :: TestName -> Maybe HedgehogReplay
parseValue TestName
v = Maybe (Size, Seed) -> HedgehogReplay
HedgehogReplay (Maybe (Size, Seed) -> HedgehogReplay)
-> ((Size, Seed) -> Maybe (Size, Seed))
-> (Size, Seed)
-> HedgehogReplay
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Size, Seed) -> Maybe (Size, Seed)
forall a. a -> Maybe a
Just ((Size, Seed) -> HedgehogReplay)
-> Maybe (Size, Seed) -> Maybe HedgehogReplay
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (Size, Seed)
replay
    where
      -- Reads a replay token in the form "{size} {seed}"
      replay :: Maybe (Size, Seed)
replay = (,) (Size -> Seed -> (Size, Seed))
-> Maybe Size -> Maybe (Seed -> (Size, Seed))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TestName -> Maybe Size
forall a. Read a => TestName -> Maybe a
safeRead ([TestName] -> TestName
unwords [TestName]
size) Maybe (Seed -> (Size, Seed)) -> Maybe Seed -> Maybe (Size, Seed)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> TestName -> Maybe Seed
forall a. Read a => TestName -> Maybe a
safeRead ([TestName] -> TestName
unwords [TestName]
seed)
      ([TestName]
size, [TestName]
seed) = Int -> [TestName] -> ([TestName], [TestName])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
2 ([TestName] -> ([TestName], [TestName]))
-> [TestName] -> ([TestName], [TestName])
forall a b. (a -> b) -> a -> b
$ TestName -> [TestName]
words TestName
v

  optionName :: Tagged HedgehogReplay TestName
optionName = TestName -> Tagged HedgehogReplay TestName
forall (m :: * -> *) a. Monad m => a -> m a
return TestName
"hedgehog-replay"

  optionHelp :: Tagged HedgehogReplay TestName
optionHelp = TestName -> Tagged HedgehogReplay TestName
forall (m :: * -> *) a. Monad m => a -> m a
return TestName
"Replay token to use for replaying a previous test run"

-- | If a test case fails, show a replay token for replaying tests
newtype HedgehogShowReplay = HedgehogShowReplay Bool
  deriving (Typeable)

instance IsOption HedgehogShowReplay where
  defaultValue :: HedgehogShowReplay
defaultValue = Bool -> HedgehogShowReplay
HedgehogShowReplay Bool
True

  parseValue :: TestName -> Maybe HedgehogShowReplay
parseValue = (Bool -> HedgehogShowReplay)
-> Maybe Bool -> Maybe HedgehogShowReplay
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Bool -> HedgehogShowReplay
HedgehogShowReplay (Maybe Bool -> Maybe HedgehogShowReplay)
-> (TestName -> Maybe Bool) -> TestName -> Maybe HedgehogShowReplay
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestName -> Maybe Bool
forall a. Read a => TestName -> Maybe a
safeRead

  optionName :: Tagged HedgehogShowReplay TestName
optionName = TestName -> Tagged HedgehogShowReplay TestName
forall (m :: * -> *) a. Monad m => a -> m a
return TestName
"hedgehog-show-replay"

  optionHelp :: Tagged HedgehogShowReplay TestName
optionHelp = TestName -> Tagged HedgehogShowReplay TestName
forall (m :: * -> *) a. Monad m => a -> m a
return TestName
"Show a replay token for replaying tests"

-- | The number of successful test cases required before Hedgehog will pass a test
newtype HedgehogTestLimit = HedgehogTestLimit (Maybe TestLimit)
  deriving (HedgehogTestLimit -> HedgehogTestLimit -> Bool
(HedgehogTestLimit -> HedgehogTestLimit -> Bool)
-> (HedgehogTestLimit -> HedgehogTestLimit -> Bool)
-> Eq HedgehogTestLimit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HedgehogTestLimit -> HedgehogTestLimit -> Bool
$c/= :: HedgehogTestLimit -> HedgehogTestLimit -> Bool
== :: HedgehogTestLimit -> HedgehogTestLimit -> Bool
$c== :: HedgehogTestLimit -> HedgehogTestLimit -> Bool
Eq, Eq HedgehogTestLimit
Eq HedgehogTestLimit
-> (HedgehogTestLimit -> HedgehogTestLimit -> Ordering)
-> (HedgehogTestLimit -> HedgehogTestLimit -> Bool)
-> (HedgehogTestLimit -> HedgehogTestLimit -> Bool)
-> (HedgehogTestLimit -> HedgehogTestLimit -> Bool)
-> (HedgehogTestLimit -> HedgehogTestLimit -> Bool)
-> (HedgehogTestLimit -> HedgehogTestLimit -> HedgehogTestLimit)
-> (HedgehogTestLimit -> HedgehogTestLimit -> HedgehogTestLimit)
-> Ord HedgehogTestLimit
HedgehogTestLimit -> HedgehogTestLimit -> Bool
HedgehogTestLimit -> HedgehogTestLimit -> Ordering
HedgehogTestLimit -> HedgehogTestLimit -> HedgehogTestLimit
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 :: HedgehogTestLimit -> HedgehogTestLimit -> HedgehogTestLimit
$cmin :: HedgehogTestLimit -> HedgehogTestLimit -> HedgehogTestLimit
max :: HedgehogTestLimit -> HedgehogTestLimit -> HedgehogTestLimit
$cmax :: HedgehogTestLimit -> HedgehogTestLimit -> HedgehogTestLimit
>= :: HedgehogTestLimit -> HedgehogTestLimit -> Bool
$c>= :: HedgehogTestLimit -> HedgehogTestLimit -> Bool
> :: HedgehogTestLimit -> HedgehogTestLimit -> Bool
$c> :: HedgehogTestLimit -> HedgehogTestLimit -> Bool
<= :: HedgehogTestLimit -> HedgehogTestLimit -> Bool
$c<= :: HedgehogTestLimit -> HedgehogTestLimit -> Bool
< :: HedgehogTestLimit -> HedgehogTestLimit -> Bool
$c< :: HedgehogTestLimit -> HedgehogTestLimit -> Bool
compare :: HedgehogTestLimit -> HedgehogTestLimit -> Ordering
$ccompare :: HedgehogTestLimit -> HedgehogTestLimit -> Ordering
$cp1Ord :: Eq HedgehogTestLimit
Ord, Int -> HedgehogTestLimit -> TestName -> TestName
[HedgehogTestLimit] -> TestName -> TestName
HedgehogTestLimit -> TestName
(Int -> HedgehogTestLimit -> TestName -> TestName)
-> (HedgehogTestLimit -> TestName)
-> ([HedgehogTestLimit] -> TestName -> TestName)
-> Show HedgehogTestLimit
forall a.
(Int -> a -> TestName -> TestName)
-> (a -> TestName) -> ([a] -> TestName -> TestName) -> Show a
showList :: [HedgehogTestLimit] -> TestName -> TestName
$cshowList :: [HedgehogTestLimit] -> TestName -> TestName
show :: HedgehogTestLimit -> TestName
$cshow :: HedgehogTestLimit -> TestName
showsPrec :: Int -> HedgehogTestLimit -> TestName -> TestName
$cshowsPrec :: Int -> HedgehogTestLimit -> TestName -> TestName
Show, Typeable)

instance IsOption HedgehogTestLimit where
  defaultValue :: HedgehogTestLimit
defaultValue = Maybe TestLimit -> HedgehogTestLimit
HedgehogTestLimit Maybe TestLimit
forall a. Maybe a
Nothing

  parseValue :: TestName -> Maybe HedgehogTestLimit
parseValue = (Int -> HedgehogTestLimit) -> Maybe Int -> Maybe HedgehogTestLimit
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Maybe TestLimit -> HedgehogTestLimit
HedgehogTestLimit (Maybe TestLimit -> HedgehogTestLimit)
-> (Int -> Maybe TestLimit) -> Int -> HedgehogTestLimit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestLimit -> Maybe TestLimit
forall a. a -> Maybe a
Just (TestLimit -> Maybe TestLimit)
-> (Int -> TestLimit) -> Int -> Maybe TestLimit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> TestLimit
TestLimit) (Maybe Int -> Maybe HedgehogTestLimit)
-> (TestName -> Maybe Int) -> TestName -> Maybe HedgehogTestLimit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestName -> Maybe Int
forall a. Read a => TestName -> Maybe a
safeRead

  optionName :: Tagged HedgehogTestLimit TestName
optionName = TestName -> Tagged HedgehogTestLimit TestName
forall (m :: * -> *) a. Monad m => a -> m a
return TestName
"hedgehog-tests"

  optionHelp :: Tagged HedgehogTestLimit TestName
optionHelp = TestName -> Tagged HedgehogTestLimit TestName
forall (m :: * -> *) a. Monad m => a -> m a
return TestName
"Number of successful test cases required before Hedgehog will pass a test"

-- | The number of discarded cases allowed before Hedgehog will fail a test
newtype HedgehogDiscardLimit = HedgehogDiscardLimit (Maybe DiscardLimit)
  deriving (HedgehogDiscardLimit -> HedgehogDiscardLimit -> Bool
(HedgehogDiscardLimit -> HedgehogDiscardLimit -> Bool)
-> (HedgehogDiscardLimit -> HedgehogDiscardLimit -> Bool)
-> Eq HedgehogDiscardLimit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HedgehogDiscardLimit -> HedgehogDiscardLimit -> Bool
$c/= :: HedgehogDiscardLimit -> HedgehogDiscardLimit -> Bool
== :: HedgehogDiscardLimit -> HedgehogDiscardLimit -> Bool
$c== :: HedgehogDiscardLimit -> HedgehogDiscardLimit -> Bool
Eq, Eq HedgehogDiscardLimit
Eq HedgehogDiscardLimit
-> (HedgehogDiscardLimit -> HedgehogDiscardLimit -> Ordering)
-> (HedgehogDiscardLimit -> HedgehogDiscardLimit -> Bool)
-> (HedgehogDiscardLimit -> HedgehogDiscardLimit -> Bool)
-> (HedgehogDiscardLimit -> HedgehogDiscardLimit -> Bool)
-> (HedgehogDiscardLimit -> HedgehogDiscardLimit -> Bool)
-> (HedgehogDiscardLimit
    -> HedgehogDiscardLimit -> HedgehogDiscardLimit)
-> (HedgehogDiscardLimit
    -> HedgehogDiscardLimit -> HedgehogDiscardLimit)
-> Ord HedgehogDiscardLimit
HedgehogDiscardLimit -> HedgehogDiscardLimit -> Bool
HedgehogDiscardLimit -> HedgehogDiscardLimit -> Ordering
HedgehogDiscardLimit
-> HedgehogDiscardLimit -> HedgehogDiscardLimit
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 :: HedgehogDiscardLimit
-> HedgehogDiscardLimit -> HedgehogDiscardLimit
$cmin :: HedgehogDiscardLimit
-> HedgehogDiscardLimit -> HedgehogDiscardLimit
max :: HedgehogDiscardLimit
-> HedgehogDiscardLimit -> HedgehogDiscardLimit
$cmax :: HedgehogDiscardLimit
-> HedgehogDiscardLimit -> HedgehogDiscardLimit
>= :: HedgehogDiscardLimit -> HedgehogDiscardLimit -> Bool
$c>= :: HedgehogDiscardLimit -> HedgehogDiscardLimit -> Bool
> :: HedgehogDiscardLimit -> HedgehogDiscardLimit -> Bool
$c> :: HedgehogDiscardLimit -> HedgehogDiscardLimit -> Bool
<= :: HedgehogDiscardLimit -> HedgehogDiscardLimit -> Bool
$c<= :: HedgehogDiscardLimit -> HedgehogDiscardLimit -> Bool
< :: HedgehogDiscardLimit -> HedgehogDiscardLimit -> Bool
$c< :: HedgehogDiscardLimit -> HedgehogDiscardLimit -> Bool
compare :: HedgehogDiscardLimit -> HedgehogDiscardLimit -> Ordering
$ccompare :: HedgehogDiscardLimit -> HedgehogDiscardLimit -> Ordering
$cp1Ord :: Eq HedgehogDiscardLimit
Ord, Int -> HedgehogDiscardLimit -> TestName -> TestName
[HedgehogDiscardLimit] -> TestName -> TestName
HedgehogDiscardLimit -> TestName
(Int -> HedgehogDiscardLimit -> TestName -> TestName)
-> (HedgehogDiscardLimit -> TestName)
-> ([HedgehogDiscardLimit] -> TestName -> TestName)
-> Show HedgehogDiscardLimit
forall a.
(Int -> a -> TestName -> TestName)
-> (a -> TestName) -> ([a] -> TestName -> TestName) -> Show a
showList :: [HedgehogDiscardLimit] -> TestName -> TestName
$cshowList :: [HedgehogDiscardLimit] -> TestName -> TestName
show :: HedgehogDiscardLimit -> TestName
$cshow :: HedgehogDiscardLimit -> TestName
showsPrec :: Int -> HedgehogDiscardLimit -> TestName -> TestName
$cshowsPrec :: Int -> HedgehogDiscardLimit -> TestName -> TestName
Show, Typeable)

instance IsOption HedgehogDiscardLimit where
  defaultValue :: HedgehogDiscardLimit
defaultValue = Maybe DiscardLimit -> HedgehogDiscardLimit
HedgehogDiscardLimit Maybe DiscardLimit
forall a. Maybe a
Nothing

  parseValue :: TestName -> Maybe HedgehogDiscardLimit
parseValue = (Int -> HedgehogDiscardLimit)
-> Maybe Int -> Maybe HedgehogDiscardLimit
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Maybe DiscardLimit -> HedgehogDiscardLimit
HedgehogDiscardLimit (Maybe DiscardLimit -> HedgehogDiscardLimit)
-> (Int -> Maybe DiscardLimit) -> Int -> HedgehogDiscardLimit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DiscardLimit -> Maybe DiscardLimit
forall a. a -> Maybe a
Just (DiscardLimit -> Maybe DiscardLimit)
-> (Int -> DiscardLimit) -> Int -> Maybe DiscardLimit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> DiscardLimit
DiscardLimit) (Maybe Int -> Maybe HedgehogDiscardLimit)
-> (TestName -> Maybe Int)
-> TestName
-> Maybe HedgehogDiscardLimit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestName -> Maybe Int
forall a. Read a => TestName -> Maybe a
safeRead

  optionName :: Tagged HedgehogDiscardLimit TestName
optionName = TestName -> Tagged HedgehogDiscardLimit TestName
forall (m :: * -> *) a. Monad m => a -> m a
return TestName
"hedgehog-discards"

  optionHelp :: Tagged HedgehogDiscardLimit TestName
optionHelp = TestName -> Tagged HedgehogDiscardLimit TestName
forall (m :: * -> *) a. Monad m => a -> m a
return TestName
"Number of discarded cases allowed before Hedgehog will fail a test"

-- | The number of shrinks allowed before Hedgehog will fail a test
newtype HedgehogShrinkLimit = HedgehogShrinkLimit (Maybe ShrinkLimit)
  deriving (HedgehogShrinkLimit -> HedgehogShrinkLimit -> Bool
(HedgehogShrinkLimit -> HedgehogShrinkLimit -> Bool)
-> (HedgehogShrinkLimit -> HedgehogShrinkLimit -> Bool)
-> Eq HedgehogShrinkLimit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HedgehogShrinkLimit -> HedgehogShrinkLimit -> Bool
$c/= :: HedgehogShrinkLimit -> HedgehogShrinkLimit -> Bool
== :: HedgehogShrinkLimit -> HedgehogShrinkLimit -> Bool
$c== :: HedgehogShrinkLimit -> HedgehogShrinkLimit -> Bool
Eq, Eq HedgehogShrinkLimit
Eq HedgehogShrinkLimit
-> (HedgehogShrinkLimit -> HedgehogShrinkLimit -> Ordering)
-> (HedgehogShrinkLimit -> HedgehogShrinkLimit -> Bool)
-> (HedgehogShrinkLimit -> HedgehogShrinkLimit -> Bool)
-> (HedgehogShrinkLimit -> HedgehogShrinkLimit -> Bool)
-> (HedgehogShrinkLimit -> HedgehogShrinkLimit -> Bool)
-> (HedgehogShrinkLimit
    -> HedgehogShrinkLimit -> HedgehogShrinkLimit)
-> (HedgehogShrinkLimit
    -> HedgehogShrinkLimit -> HedgehogShrinkLimit)
-> Ord HedgehogShrinkLimit
HedgehogShrinkLimit -> HedgehogShrinkLimit -> Bool
HedgehogShrinkLimit -> HedgehogShrinkLimit -> Ordering
HedgehogShrinkLimit -> HedgehogShrinkLimit -> HedgehogShrinkLimit
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 :: HedgehogShrinkLimit -> HedgehogShrinkLimit -> HedgehogShrinkLimit
$cmin :: HedgehogShrinkLimit -> HedgehogShrinkLimit -> HedgehogShrinkLimit
max :: HedgehogShrinkLimit -> HedgehogShrinkLimit -> HedgehogShrinkLimit
$cmax :: HedgehogShrinkLimit -> HedgehogShrinkLimit -> HedgehogShrinkLimit
>= :: HedgehogShrinkLimit -> HedgehogShrinkLimit -> Bool
$c>= :: HedgehogShrinkLimit -> HedgehogShrinkLimit -> Bool
> :: HedgehogShrinkLimit -> HedgehogShrinkLimit -> Bool
$c> :: HedgehogShrinkLimit -> HedgehogShrinkLimit -> Bool
<= :: HedgehogShrinkLimit -> HedgehogShrinkLimit -> Bool
$c<= :: HedgehogShrinkLimit -> HedgehogShrinkLimit -> Bool
< :: HedgehogShrinkLimit -> HedgehogShrinkLimit -> Bool
$c< :: HedgehogShrinkLimit -> HedgehogShrinkLimit -> Bool
compare :: HedgehogShrinkLimit -> HedgehogShrinkLimit -> Ordering
$ccompare :: HedgehogShrinkLimit -> HedgehogShrinkLimit -> Ordering
$cp1Ord :: Eq HedgehogShrinkLimit
Ord, Int -> HedgehogShrinkLimit -> TestName -> TestName
[HedgehogShrinkLimit] -> TestName -> TestName
HedgehogShrinkLimit -> TestName
(Int -> HedgehogShrinkLimit -> TestName -> TestName)
-> (HedgehogShrinkLimit -> TestName)
-> ([HedgehogShrinkLimit] -> TestName -> TestName)
-> Show HedgehogShrinkLimit
forall a.
(Int -> a -> TestName -> TestName)
-> (a -> TestName) -> ([a] -> TestName -> TestName) -> Show a
showList :: [HedgehogShrinkLimit] -> TestName -> TestName
$cshowList :: [HedgehogShrinkLimit] -> TestName -> TestName
show :: HedgehogShrinkLimit -> TestName
$cshow :: HedgehogShrinkLimit -> TestName
showsPrec :: Int -> HedgehogShrinkLimit -> TestName -> TestName
$cshowsPrec :: Int -> HedgehogShrinkLimit -> TestName -> TestName
Show, Typeable)

instance IsOption HedgehogShrinkLimit where
  defaultValue :: HedgehogShrinkLimit
defaultValue = Maybe ShrinkLimit -> HedgehogShrinkLimit
HedgehogShrinkLimit Maybe ShrinkLimit
forall a. Maybe a
Nothing

  parseValue :: TestName -> Maybe HedgehogShrinkLimit
parseValue = (Int -> HedgehogShrinkLimit)
-> Maybe Int -> Maybe HedgehogShrinkLimit
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Maybe ShrinkLimit -> HedgehogShrinkLimit
HedgehogShrinkLimit (Maybe ShrinkLimit -> HedgehogShrinkLimit)
-> (Int -> Maybe ShrinkLimit) -> Int -> HedgehogShrinkLimit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShrinkLimit -> Maybe ShrinkLimit
forall a. a -> Maybe a
Just (ShrinkLimit -> Maybe ShrinkLimit)
-> (Int -> ShrinkLimit) -> Int -> Maybe ShrinkLimit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ShrinkLimit
ShrinkLimit) (Maybe Int -> Maybe HedgehogShrinkLimit)
-> (TestName -> Maybe Int) -> TestName -> Maybe HedgehogShrinkLimit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestName -> Maybe Int
forall a. Read a => TestName -> Maybe a
safeRead

  optionName :: Tagged HedgehogShrinkLimit TestName
optionName = TestName -> Tagged HedgehogShrinkLimit TestName
forall (m :: * -> *) a. Monad m => a -> m a
return TestName
"hedgehog-shrinks"

  optionHelp :: Tagged HedgehogShrinkLimit TestName
optionHelp = TestName -> Tagged HedgehogShrinkLimit TestName
forall (m :: * -> *) a. Monad m => a -> m a
return TestName
"Number of shrinks allowed before Hedgehog will fail a test"

-- | The number of times to re-run a test during shrinking
newtype HedgehogShrinkRetries = HedgehogShrinkRetries (Maybe ShrinkRetries)
  deriving (HedgehogShrinkRetries -> HedgehogShrinkRetries -> Bool
(HedgehogShrinkRetries -> HedgehogShrinkRetries -> Bool)
-> (HedgehogShrinkRetries -> HedgehogShrinkRetries -> Bool)
-> Eq HedgehogShrinkRetries
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HedgehogShrinkRetries -> HedgehogShrinkRetries -> Bool
$c/= :: HedgehogShrinkRetries -> HedgehogShrinkRetries -> Bool
== :: HedgehogShrinkRetries -> HedgehogShrinkRetries -> Bool
$c== :: HedgehogShrinkRetries -> HedgehogShrinkRetries -> Bool
Eq, Eq HedgehogShrinkRetries
Eq HedgehogShrinkRetries
-> (HedgehogShrinkRetries -> HedgehogShrinkRetries -> Ordering)
-> (HedgehogShrinkRetries -> HedgehogShrinkRetries -> Bool)
-> (HedgehogShrinkRetries -> HedgehogShrinkRetries -> Bool)
-> (HedgehogShrinkRetries -> HedgehogShrinkRetries -> Bool)
-> (HedgehogShrinkRetries -> HedgehogShrinkRetries -> Bool)
-> (HedgehogShrinkRetries
    -> HedgehogShrinkRetries -> HedgehogShrinkRetries)
-> (HedgehogShrinkRetries
    -> HedgehogShrinkRetries -> HedgehogShrinkRetries)
-> Ord HedgehogShrinkRetries
HedgehogShrinkRetries -> HedgehogShrinkRetries -> Bool
HedgehogShrinkRetries -> HedgehogShrinkRetries -> Ordering
HedgehogShrinkRetries
-> HedgehogShrinkRetries -> HedgehogShrinkRetries
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 :: HedgehogShrinkRetries
-> HedgehogShrinkRetries -> HedgehogShrinkRetries
$cmin :: HedgehogShrinkRetries
-> HedgehogShrinkRetries -> HedgehogShrinkRetries
max :: HedgehogShrinkRetries
-> HedgehogShrinkRetries -> HedgehogShrinkRetries
$cmax :: HedgehogShrinkRetries
-> HedgehogShrinkRetries -> HedgehogShrinkRetries
>= :: HedgehogShrinkRetries -> HedgehogShrinkRetries -> Bool
$c>= :: HedgehogShrinkRetries -> HedgehogShrinkRetries -> Bool
> :: HedgehogShrinkRetries -> HedgehogShrinkRetries -> Bool
$c> :: HedgehogShrinkRetries -> HedgehogShrinkRetries -> Bool
<= :: HedgehogShrinkRetries -> HedgehogShrinkRetries -> Bool
$c<= :: HedgehogShrinkRetries -> HedgehogShrinkRetries -> Bool
< :: HedgehogShrinkRetries -> HedgehogShrinkRetries -> Bool
$c< :: HedgehogShrinkRetries -> HedgehogShrinkRetries -> Bool
compare :: HedgehogShrinkRetries -> HedgehogShrinkRetries -> Ordering
$ccompare :: HedgehogShrinkRetries -> HedgehogShrinkRetries -> Ordering
$cp1Ord :: Eq HedgehogShrinkRetries
Ord, Int -> HedgehogShrinkRetries -> TestName -> TestName
[HedgehogShrinkRetries] -> TestName -> TestName
HedgehogShrinkRetries -> TestName
(Int -> HedgehogShrinkRetries -> TestName -> TestName)
-> (HedgehogShrinkRetries -> TestName)
-> ([HedgehogShrinkRetries] -> TestName -> TestName)
-> Show HedgehogShrinkRetries
forall a.
(Int -> a -> TestName -> TestName)
-> (a -> TestName) -> ([a] -> TestName -> TestName) -> Show a
showList :: [HedgehogShrinkRetries] -> TestName -> TestName
$cshowList :: [HedgehogShrinkRetries] -> TestName -> TestName
show :: HedgehogShrinkRetries -> TestName
$cshow :: HedgehogShrinkRetries -> TestName
showsPrec :: Int -> HedgehogShrinkRetries -> TestName -> TestName
$cshowsPrec :: Int -> HedgehogShrinkRetries -> TestName -> TestName
Show, Typeable)

instance IsOption HedgehogShrinkRetries where
  defaultValue :: HedgehogShrinkRetries
defaultValue = Maybe ShrinkRetries -> HedgehogShrinkRetries
HedgehogShrinkRetries Maybe ShrinkRetries
forall a. Maybe a
Nothing

  parseValue :: TestName -> Maybe HedgehogShrinkRetries
parseValue = (Int -> HedgehogShrinkRetries)
-> Maybe Int -> Maybe HedgehogShrinkRetries
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Maybe ShrinkRetries -> HedgehogShrinkRetries
HedgehogShrinkRetries (Maybe ShrinkRetries -> HedgehogShrinkRetries)
-> (Int -> Maybe ShrinkRetries) -> Int -> HedgehogShrinkRetries
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShrinkRetries -> Maybe ShrinkRetries
forall a. a -> Maybe a
Just (ShrinkRetries -> Maybe ShrinkRetries)
-> (Int -> ShrinkRetries) -> Int -> Maybe ShrinkRetries
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ShrinkRetries
ShrinkRetries) (Maybe Int -> Maybe HedgehogShrinkRetries)
-> (TestName -> Maybe Int)
-> TestName
-> Maybe HedgehogShrinkRetries
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestName -> Maybe Int
forall a. Read a => TestName -> Maybe a
safeRead

  optionName :: Tagged HedgehogShrinkRetries TestName
optionName = TestName -> Tagged HedgehogShrinkRetries TestName
forall (m :: * -> *) a. Monad m => a -> m a
return TestName
"hedgehog-retries"

  optionHelp :: Tagged HedgehogShrinkRetries TestName
optionHelp = TestName -> Tagged HedgehogShrinkRetries TestName
forall (m :: * -> *) a. Monad m => a -> m a
return TestName
"Number of times to re-run a test during shrinking"

-- * GROUPING

-- | This allows the discovery of Hedgehog properties and their grouping by module name
--   in the test report.
--   Extract the ModuleName option value for a given test and
--   group all the tests with that option into the same test group
groupByModuleName :: TestTree -> TestTree
groupByModuleName :: TestTree -> TestTree
groupByModuleName TestTree
testTree =
  let grouped :: [(TestName, [TestTree])]
grouped =
        MultiMap TestName TestTree -> [(TestName, [TestTree])]
forall k a. MultiMap k a -> [(k, [a])]
assocs (MultiMap TestName TestTree -> [(TestName, [TestTree])])
-> MultiMap TestName TestTree -> [(TestName, [TestTree])]
forall a b. (a -> b) -> a -> b
$
          TreeFold (MultiMap TestName TestTree)
-> OptionSet -> TestTree -> MultiMap TestName TestTree
forall b. Monoid b => TreeFold b -> OptionSet -> TestTree -> b
foldTestTree
            ( TreeFold (MultiMap TestName TestTree)
forall b. Monoid b => TreeFold b
trivialFold
                { foldSingle :: forall t.
IsTest t =>
OptionSet -> TestName -> t -> MultiMap TestName TestTree
foldSingle = \OptionSet
os TestName
n t
t ->
                    let (ModuleName Text
aModuleName) = OptionSet -> ModuleName
forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
os :: ModuleName
                     in TestName
-> TestTree
-> MultiMap TestName TestTree
-> MultiMap TestName TestTree
forall k a. Ord k => k -> a -> MultiMap k a -> MultiMap k a
insert (Text -> TestName
forall a b. ConvertText a b => a -> b
toS Text
aModuleName) (OptionSet -> TestTree -> TestTree
setOptionSet OptionSet
os (TestTree -> TestTree) -> TestTree -> TestTree
forall a b. (a -> b) -> a -> b
$ TestName -> t -> TestTree
forall t. IsTest t => TestName -> t -> TestTree
singleTest TestName
n t
t) MultiMap TestName TestTree
forall k a. MultiMap k a
empty
                }
            )
            OptionSet
forall a. Monoid a => a
mempty
            TestTree
testTree
   in TestName -> [TestTree] -> TestTree
TestGroup TestName
"All" ((TestName -> [TestTree] -> TestTree)
-> (TestName, [TestTree]) -> TestTree
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry TestName -> [TestTree] -> TestTree
TestGroup ((TestName, [TestTree]) -> TestTree)
-> [(TestName, [TestTree])] -> [TestTree]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(TestName, [TestTree])]
grouped)

-- | Option describing the current module name
newtype ModuleName = ModuleName Text deriving (ModuleName -> ModuleName -> Bool
(ModuleName -> ModuleName -> Bool)
-> (ModuleName -> ModuleName -> Bool) -> Eq ModuleName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModuleName -> ModuleName -> Bool
$c/= :: ModuleName -> ModuleName -> Bool
== :: ModuleName -> ModuleName -> Bool
$c== :: ModuleName -> ModuleName -> Bool
Eq, Int -> ModuleName -> TestName -> TestName
[ModuleName] -> TestName -> TestName
ModuleName -> TestName
(Int -> ModuleName -> TestName -> TestName)
-> (ModuleName -> TestName)
-> ([ModuleName] -> TestName -> TestName)
-> Show ModuleName
forall a.
(Int -> a -> TestName -> TestName)
-> (a -> TestName) -> ([a] -> TestName -> TestName) -> Show a
showList :: [ModuleName] -> TestName -> TestName
$cshowList :: [ModuleName] -> TestName -> TestName
show :: ModuleName -> TestName
$cshow :: ModuleName -> TestName
showsPrec :: Int -> ModuleName -> TestName -> TestName
$cshowsPrec :: Int -> ModuleName -> TestName -> TestName
Show)

-- | This option is not used on the command line, it is just used to annotate test groups
instance IsOption ModuleName where
  defaultValue :: ModuleName
defaultValue = Text -> ModuleName
ModuleName Text
"root"
  parseValue :: TestName -> Maybe ModuleName
parseValue = (Text -> ModuleName) -> Maybe Text -> Maybe ModuleName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ModuleName
ModuleName (Maybe Text -> Maybe ModuleName)
-> (TestName -> Maybe Text) -> TestName -> Maybe ModuleName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestName -> Maybe Text
forall a. Read a => TestName -> Maybe a
safeRead
  optionName :: Tagged ModuleName TestName
optionName = TestName -> Tagged ModuleName TestName
forall (f :: * -> *) a. Applicative f => a -> f a
pure TestName
"module-name"
  optionHelp :: Tagged ModuleName TestName
optionHelp = TestName -> Tagged ModuleName TestName
forall (f :: * -> *) a. Applicative f => a -> f a
pure TestName
"internal option used to group tests into the same module"
  optionCLParser :: Parser ModuleName
optionCLParser = Mod FlagFields ModuleName -> ModuleName -> Parser ModuleName
forall v. IsOption v => Mod FlagFields v -> v -> Parser v
mkFlagCLParser Mod FlagFields ModuleName
forall a. Monoid a => a
mempty (Text -> ModuleName
ModuleName Text
"root")

instance (Ord k) => Semigroup (MultiMap k v) where
  <> :: MultiMap k v -> MultiMap k v -> MultiMap k v
(<>) MultiMap k v
m1 MultiMap k v
m2 = [(k, v)] -> MultiMap k v
forall k a. Ord k => [(k, a)] -> MultiMap k a
fromList (MultiMap k v -> [(k, v)]
forall k a. MultiMap k a -> [(k, a)]
toList MultiMap k v
m1 [(k, v)] -> [(k, v)] -> [(k, v)]
forall a. Semigroup a => a -> a -> a
<> MultiMap k v -> [(k, v)]
forall k a. MultiMap k a -> [(k, a)]
toList MultiMap k v
m2)

instance (Ord k) => Monoid (MultiMap k v) where
  mempty :: MultiMap k v
mempty = MultiMap k v
forall k a. MultiMap k a
empty
  mappend :: MultiMap k v -> MultiMap k v -> MultiMap k v
mappend = MultiMap k v -> MultiMap k v -> MultiMap k v
forall a. Semigroup a => a -> a -> a
(<>)

-- | This is unfortunate. Due to the API for `foldTestTree` in Tasty
--   giving back the current `OptionSet` applicable to a single test
--   it is not possible to re-set those option values on that test
--   without listing them exhaustively. This means
--   that if other options are set on tests in that file, they need to be
--   added in that function
setOptionSet :: OptionSet -> TestTree -> TestTree
setOptionSet :: OptionSet -> TestTree -> TestTree
setOptionSet OptionSet
os =
  HedgehogTestLimit -> TestTree -> TestTree
forall v. IsOption v => v -> TestTree -> TestTree
localOption (OptionSet -> HedgehogTestLimit
forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
os :: HedgehogTestLimit)
    (TestTree -> TestTree)
-> (TestTree -> TestTree) -> TestTree -> TestTree
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HedgehogShrinkLimit -> TestTree -> TestTree
forall v. IsOption v => v -> TestTree -> TestTree
localOption (OptionSet -> HedgehogShrinkLimit
forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
os :: HedgehogShrinkLimit)
    (TestTree -> TestTree)
-> (TestTree -> TestTree) -> TestTree -> TestTree
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HedgehogReplay -> TestTree -> TestTree
forall v. IsOption v => v -> TestTree -> TestTree
localOption (OptionSet -> HedgehogReplay
forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
os :: HedgehogReplay)

-- | Return the module name of the current callstack
getModuleName :: HasCallStack => Prelude.String
getModuleName :: TestName
getModuleName =
  case CallStack -> [(TestName, SrcLoc)]
getCallStack CallStack
HasCallStack => CallStack
callStack of
    ((TestName
_, SrcLoc
loc) : [(TestName, SrcLoc)]
_) -> SrcLoc -> TestName
srcLocModule SrcLoc
loc
    [(TestName, SrcLoc)]
_ -> TestName
"root"