{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
module Test.Tasty.Hedgehog.Coverage
(
Cover (..)
, Tally (..)
, testPropertyCoverage
, withCoverage
, classify
, label
, collect
, withTests
, withRetries
, withDiscards
, withShrinks
) where
import Data.Typeable (Proxy (..))
import Control.Monad (when)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.State (MonadState, StateT (..), modify,
runStateT)
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import qualified Data.Text as Text
import Hedgehog (evalM)
import Hedgehog.Internal.Property (DiscardLimit,
PropertyConfig (..),
PropertyName (..),
PropertyT (..),
ShrinkLimit (..), ShrinkRetries,
TestLimit (..), defaultConfig,
propertyShrinkLimit,
propertyTestLimit)
import Hedgehog.Internal.Report (FailureReport (FailureReport, failureShrinks),
Progress (..), Report (..),
Result (..), ShrinkCount (..),
TestCount (..))
import qualified Hedgehog.Internal.Report as Report
import Hedgehog.Internal.Runner (checkReport)
import qualified Hedgehog.Internal.Seed as Seed
import Hedgehog.Internal.Source (HasCallStack,
withFrozenCallStack)
import Text.PrettyPrint.Annotated.WL (Doc, (<#>), (<+>), (</>))
import qualified Text.PrettyPrint.Annotated.WL as PP
import Text.Printf (printf)
import Test.Tasty.Options
import qualified Test.Tasty.Providers as T
import Test.Tasty.Hedgehog (HedgehogDiscardLimit (..),
HedgehogReplay (..),
HedgehogShowReplay (..),
HedgehogShrinkLimit (..),
HedgehogShrinkRetries (..),
HedgehogTestLimit (..))
newtype Tally = Tally
{ unTally :: Map Text Int
}
deriving (Eq, Show)
data CoveredProperty = CoveredProperty
{ _coverName :: PropertyName
, _coverProp :: Cover
}
data Cover = Cover
{ _coverageConf :: !PropertyConfig
, _coverageProp :: PropertyT (StateT Tally IO) ()
}
mapPropertyConfig :: (PropertyConfig -> PropertyConfig) -> Cover -> Cover
mapPropertyConfig f cover = cover { _coverageConf = f (_coverageConf cover) }
withTests :: TestLimit -> Cover -> Cover
withTests lim = mapPropertyConfig (\c -> c { propertyTestLimit = lim })
withDiscards :: DiscardLimit -> Cover -> Cover
withDiscards n = mapPropertyConfig $ \c -> c { propertyDiscardLimit = n }
withShrinks :: ShrinkLimit -> Cover -> Cover
withShrinks n = mapPropertyConfig $ \c -> c { propertyShrinkLimit = n }
withRetries :: ShrinkRetries -> Cover -> Cover
withRetries n = mapPropertyConfig $ \c -> c { propertyShrinkRetries = n }
classify
:: MonadState Tally m
=> Bool
-> Text
-> m ()
classify b l = when b $
modify (Tally . Map.alter (Just . maybe 1 (+1)) l . unTally)
label
:: MonadState Tally m
=> Text
-> m ()
label =
classify True
collect
:: ( MonadState Tally m
, Show a
)
=> a
-> m ()
collect =
label . Text.pack . show
withCoverage
:: HasCallStack
=> PropertyT (StateT Tally IO) ()
-> Cover
withCoverage m =
Cover defaultConfig $ withFrozenCallStack (evalM m)
testPropertyCoverage
:: T.TestName
-> Cover
-> T.TestTree
testPropertyCoverage name cov =
T.singleTest name (CoveredProperty (PropertyName name) cov)
ratio :: Integral n => n -> Int -> Double
ratio x y = fromIntegral x / fromIntegral y
prettyTally
:: PropertyConfig
-> Report Result
-> Tally
-> Doc a
prettyTally _config report (Tally tally) =
let
TestCount testCount = reportTests report
shrinkCount = case reportStatus report of
Failed FailureReport {failureShrinks = ShrinkCount n} -> 1 + n
_ -> 0
ntests = shrinkCount + testCount
ppTally (l,t) =
PP.text (printf "%.2f%%" (100.0 * ratio t ntests)) <+>
PP.text (Text.unpack l)
in
PP.vsep $ ppTally <$> Map.toList tally
reportToProgress
:: PropertyConfig
-> Report Progress
-> T.Progress
reportToProgress config (Report testsDone _ status) =
let
TestLimit testLimit = propertyTestLimit config
ShrinkLimit shrinkLimit = propertyShrinkLimit config
ratio'd :: Integral n => n -> Int -> Float
ratio'd x y = 1.0 * realToFrac (ratio x y)
in
case status of
Running -> T.Progress "Running" (ratio'd testsDone testLimit)
Shrinking fr -> T.Progress "Shrinking" (ratio'd (Report.failureShrinks fr) shrinkLimit)
reportOutput
:: PropertyConfig
-> Bool
-> String
-> Tally
-> Report Result
-> IO String
reportOutput config showReplay name tally report@(Report _ _ status) = do
rpt <- Report.ppResult (Just (PropertyName name)) report
let
toStr = PP.display . PP.renderPrettyDefault
tal = prettyTally config report tally
pure $ case status of
Failed fr -> do
let
size = PP.text . show $ Report.failureSize fr
seed = PP.text . show $ Report.failureSeed fr
replayStr = if showReplay
then PP.text "Use"
<+> PP.squotes ("--hedgehog-replay" <+> PP.dquotes (size <+> seed))
<+> "to reproduce"
else mempty
toStr $ PP.align tal </> PP.line <#> rpt <#> replayStr
GaveUp -> "Gave up"
OK -> toStr tal
instance T.IsTest CoveredProperty where
testOptions =
return [ Option (Proxy :: Proxy HedgehogReplay)
, Option (Proxy :: Proxy HedgehogShowReplay)
, Option (Proxy :: Proxy HedgehogTestLimit)
, Option (Proxy :: Proxy HedgehogDiscardLimit)
, Option (Proxy :: Proxy HedgehogShrinkLimit)
, Option (Proxy :: Proxy HedgehogShrinkRetries)
]
run opts (CoveredProperty name (Cover conf prop)) yieldProgress = do
let
HedgehogReplay replay = lookupOption opts
HedgehogShowReplay showReplay = lookupOption opts
HedgehogTestLimit mTests = lookupOption opts
HedgehogDiscardLimit mDiscards = lookupOption opts
HedgehogShrinkLimit mShrinks = lookupOption opts
HedgehogShrinkRetries mRetries = lookupOption opts
config =
PropertyConfig
(fromMaybe (propertyTestLimit conf) mTests)
(fromMaybe (propertyDiscardLimit conf) mDiscards)
(fromMaybe (propertyShrinkLimit conf) mShrinks)
(fromMaybe (propertyShrinkRetries conf) mRetries)
randSeed <- Seed.random
let
size = maybe 0 fst replay
seed = maybe randSeed snd replay
runProp = checkReport config size seed prop
(liftIO . yieldProgress . reportToProgress config)
(rresult, tally) <- runStateT runProp (Tally mempty)
let
resultFn = if reportStatus rresult == OK
then T.testPassed
else T.testFailed
out <- reportOutput config showReplay (unPropertyName name) tally rresult
return $ resultFn out