{-# language DerivingStrategies #-}
module Test.StrictCheck
(
Spec(..)
, getSpec
, StrictCheck
, strictCheckSpecExact
, strictCheckWithResults
, genViaProduce
, Shrink(..)
, shrinkViaArbitrary
, Strictness
, strictnessViaSized
, Evaluation(..)
, evaluationForall
, shrinkEvalWith
, DemandComparison(..)
, compareToSpecWith
, equalToSpec
, NP(..), I(..), All
, module Test.StrictCheck.Demand
, module Test.StrictCheck.Observe
, module Test.StrictCheck.Produce
, module Test.StrictCheck.Consume
, module Test.StrictCheck.Shaped
)
where
import Test.StrictCheck.Curry as Curry
import Test.StrictCheck.Produce
import Test.StrictCheck.Consume
import Test.StrictCheck.Observe
import Test.StrictCheck.Demand
import Test.StrictCheck.Shaped
import Test.StrictCheck.Internal.Omega
import Test.StrictCheck.Internal.Shrink
( Shrink(..), axialShrinks, fairInterleave )
import Generics.SOP hiding (Shape)
import Test.QuickCheck as Exported hiding (Args, Result, function)
import qualified Test.QuickCheck as QC
import Data.List
import Data.Maybe
import Data.IORef
import Type.Reflection
compareEquality :: All Shaped xs => NP DemandComparison xs
compareEquality = hcpure (Proxy @Shaped) (DemandComparison (==))
genViaProduce :: All Produce xs => NP Gen xs
genViaProduce = hcpure (Proxy @Produce) (freely produce)
shrinkViaArbitrary :: All Arbitrary xs => NP Shrink xs
shrinkViaArbitrary = hcpure (Proxy @Arbitrary) (Shrink shrink)
strictnessViaSized :: Gen Strictness
strictnessViaSized =
Strictness <$> (choose . (1,) =<< getSize)
newtype DemandComparison a =
DemandComparison (Demand a -> Demand a -> Bool)
newtype Spec (args :: [*]) (result :: *)
= Spec (forall r. (args ⋯-> r) -> result -> args ⋯-> r)
getSpec
:: forall r args result.
Spec args result
-> (args ⋯-> r)
-> result
-> args ⋯-> r
getSpec (Spec s) k d = s @r k d
compareToSpecWith
:: forall args result.
(All Shaped args, Curry args, Shaped result)
=> NP DemandComparison args
-> Spec args result
-> Evaluation args result
-> Maybe (NP Demand args)
compareToSpecWith comparisons spec (Evaluation inputs inputsD resultD) =
let prediction =
Curry.uncurry
(getSpec @(NP Demand args)
spec
collectDemands
(fromDemand $ E resultD))
inputs
correct =
all id . hcollapse $
hcliftA3 (Proxy @Shaped)
(\(DemandComparison c) iD iD' -> K $ iD `c` iD')
comparisons
inputsD
prediction
in if correct then Nothing else Just prediction
where
collectDemands :: args ⋯-> NP Demand args
collectDemands =
curryCollect @args (hcmap (Proxy @Shaped) (toDemand . unI))
curryCollect
:: forall (xs :: [*]) r. Curry xs => (NP I xs -> r) -> xs ⋯-> r
curryCollect k = Curry.curry @xs k
equalToSpec
:: forall args result.
(All Shaped args, Shaped result, Curry args)
=> Spec args result
-> Evaluation args result
-> Maybe (NP Demand args)
equalToSpec spec e =
compareToSpecWith compareEquality spec e
newtype Strictness
= Strictness Int
deriving stock (Eq, Ord)
deriving newtype (Show, Num)
type StrictCheck function =
( Shaped (Result function)
, Consume (Result function)
, Curry (Args function)
, All Typeable (Args function)
, All Shaped (Args function) )
strictCheckWithResults ::
forall function evidence.
StrictCheck function
=> QC.Args
-> NP Shrink (Args function)
-> NP Gen (Args function)
-> Gen Strictness
-> (Evaluation (Args function) (Result function) -> Maybe evidence)
-> function
-> IO ( Maybe ( Evaluation (Args function) (Result function)
, evidence )
, QC.Result )
strictCheckWithResults
qcArgs shrinks gens strictness predicate function = do
ref <- newIORef Nothing
result <-
quickCheckWithResult qcArgs{chatty = False} $
forAllShrink
(evaluationForall @function gens strictness function)
(shrinkEvalWith @function shrinks function) $
\example ->
case predicate example of
Nothing ->
property True
Just evidence ->
whenFail (writeIORef ref $ Just (example, evidence)) False
readIORef ref >>= \case
Nothing -> pure (Nothing, result)
Just example -> pure (Just example, result)
strictCheckSpecExact
:: forall function.
( StrictCheck function
, All Arbitrary (Args function)
, All Produce (Args function)
) => Spec (Args function) (Result function)
-> function
-> IO ()
strictCheckSpecExact spec function =
do (maybeExample, result) <-
strictCheckWithResults
stdArgs
shrinkViaArbitrary
genViaProduce
strictnessViaSized
(equalToSpec spec)
function
(putStrLn . head . lines) (output result)
case maybeExample of
Nothing -> return ()
Just example ->
putStrLn (Prelude.uncurry displayCounterSpec example)
data Evaluation args result =
Evaluation
{ inputs :: NP I args
, inputDemands :: NP Demand args
, resultDemand :: PosDemand result
}
instance (All Typeable args, Typeable result)
=> Show (Evaluation args result) where
show _ =
"<Evaluation> :: Evaluation"
++ " '[" ++ intercalate ", " argTypes ++ "]"
++ " " ++ show (typeRep :: TypeRep result)
where
argTypes :: [String]
argTypes =
hcollapse
$ hliftA (K . show)
$ (hcpure (Proxy @Typeable) typeRep :: NP TypeRep args)
evaluationForall
:: forall f.
( Curry (Args f)
, Consume (Result f)
, Shaped (Result f)
, All Shaped (Args f)
) => NP Gen (Args f)
-> Gen Strictness
-> f
-> Gen (Evaluation (Args f) (Result f))
evaluationForall gens strictnessGen function = do
inputs <- hsequence gens
strictness <- strictnessGen
toOmega <- freely produce
return (go strictness toOmega inputs)
where
go :: Strictness
-> (Result f -> Omega)
-> NP I (Args f)
-> Evaluation (Args f) (Result f)
go (Strictness s) tO is =
let (resultD, inputsD) =
observeNP (forceOmega s . tO) (uncurryAll @f function) is
in case resultD of
T -> go (Strictness s + 1) tO is
E posResultD ->
Evaluation is inputsD posResultD
shrinkEvalWith
:: forall f.
( Curry (Args f)
, Shaped (Result f)
, All Shaped (Args f)
) => NP Shrink (Args f)
-> f
-> Evaluation (Args f) (Result f)
-> [Evaluation (Args f) (Result f)]
shrinkEvalWith
shrinks (uncurryAll -> function) (Evaluation inputs _ resultD) =
let shrunkDemands = shrinkDemand @(Result f) resultD
shrunkInputs = fairInterleave (axialShrinks shrinks inputs)
shrinkingDemand = mapMaybe (reObserve inputs) shrunkDemands
shrinkingInputs = mapMaybe (flip reObserve resultD) shrunkInputs
in fairInterleave [ shrinkingDemand, shrinkingInputs ]
where
reObserve
:: NP I (Args f)
-> PosDemand (Result f)
-> Maybe (Evaluation (Args f) (Result f))
reObserve is rD =
let (rD', isD) = observeNP (evaluateDemand rD) function is
in fmap (Evaluation is isD) $
case rD' of
T -> Nothing
E pos -> Just pos
displayCounterSpec
:: forall args result.
(Shaped result, All Shaped args)
=> Evaluation args result
-> NP Demand args
-> String
displayCounterSpec (Evaluation inputs inputsD resultD) predictedInputsD =
beside inputBox (" " : "───" : repeat " ") resultBox
++ (flip replicate ' ' $
(2 `max` (subtract 2 $ (lineMax [inputString] `div` 2))))
++ "🡓 🡓 🡓\n"
++ beside
actualBox
(" " : " " : " ═╱═ " : repeat " ")
predictedBox
where
inputBox =
box "┌" '─' "┐"
"│" inputHeader "├"
"├" '─' "┤"
"│" inputString "│"
"└" '─' "┘"
resultBox =
box "┌" '─' "┐"
"┤" resultHeader "│"
"├" '─' "┤"
"│" resultString "│"
"└" '─' "┘"
actualBox =
box "┌" '─' "┐"
"│" actualHeader "│"
"├" '─' "┤"
"│" actualDemandString "│"
"└" '─' "┘"
predictedBox =
box "┌" '─' "┐"
"│" predictedHeader "│"
"├" '─' "┤"
"│" predictedDemandString "│"
"└" '─' "┘"
inputHeader = " Input" ++ plural
resultHeader = " Demand on result"
actualHeader = " Actual input demand" ++ plural
predictedHeader = " Spec's input demand" ++ plural
inputString =
showBulletedNPWith @Shaped (prettyDemand . interleave Eval . unI) inputs
resultString = " " ++ prettyDemand @result (E resultD)
actualDemandString =
showBulletedNPWith @Shaped prettyDemand inputsD
predictedDemandString =
showBulletedNPWith @Shaped prettyDemand predictedInputsD
rule w l c r = frame w l (replicate w c) r ++ "\n"
frame w before str after =
before ++ str
++ (replicate (w - length str) ' ')
++ after
frames w before para after =
unlines $ map (\str -> frame w before str after) (lines para)
beside l cs r =
unlines . take (length ls `max` length rs) $
zipWith3
(\x c y -> x ++ c ++ y)
(ls ++ repeat (replicate (lineMax [l]) ' '))
cs
(rs ++ repeat "")
where
ls = lines l
rs = lines r
box top_l top top_r
header_l header header_r
div_l div_c div_r
body_l body body_r
bottom_l bottom bottom_r =
let w = lineMax [header, body]
in rule w top_l top top_r
++ frames w header_l header header_r
++ rule w div_l div_c div_r
++ frames w body_l body body_r
++ rule w bottom_l bottom bottom_r
lineMax strs =
(maximum . map
(\(lines -> ls) -> maximum (map length ls) + 1) $ strs)
plural = case inputs of
(_ :* Nil) -> ""
_ -> "s"
showBulletedNPWith
:: forall c g xs. All c xs
=> (forall x. c x => g x -> String) -> NP g xs -> String
showBulletedNPWith display list = showNPWith' list
where
showNPWith' :: forall ys. All c ys => NP g ys -> String
showNPWith' Nil = ""
showNPWith' (y :* ys) =
" • " ++ display y ++ "\n" ++ showNPWith' ys