module Test.SmartCheck
(
smartCheck
, ScProperty()
, (-->)
, runQCInit
, module Test.SmartCheck.Args
, SubTypes(..)
, gst
, grc
, gtc
, gsf
, gsz
) where
import Test.SmartCheck.Args
import Test.SmartCheck.Types
import Test.SmartCheck.Matches
import Test.SmartCheck.Reduce
import Test.SmartCheck.Extrapolate
import Test.SmartCheck.Render
import Test.SmartCheck.ConstructorGen
import qualified Test.QuickCheck as Q
import Generics.Deriving
smartCheck :: forall a prop.
( Read a, Q.Arbitrary a, SubTypes a
, Generic a, ConNames (Rep a)
, ScProp prop, Q.Testable prop
) => ScArgs -> (a -> prop) -> IO ()
smartCheck args scProp = do
(mcex, prop) <-
if qc args then runQCInit (qcArgs args) scProp
else do smartPrtLn "Input value to SmartCheck:"
mcex <- fmap Just (readLn :: IO a)
return (mcex, propify scProp)
smartPrtLn $
"(If any stage takes too long, try modifying the standard "
++ "arguments (see Args.hs).)"
runSmartCheck prop mcex
where
runSmartCheck :: (a -> Q.Property) -> Maybe a -> IO ()
runSmartCheck origProp = smartCheck' [] origProp
where
smartCheck' :: [(a, Replace Idx)]
-> (a -> Q.Property)
-> Maybe a
-> IO ()
smartCheck' ds prop mcex = do
maybe (maybeDoneMsg >> return ()) go mcex
where
go cex = do
d <- smartRun args cex prop
valIdxs <- forallExtrap args d origProp
csIdxs <- existsExtrap args d valIdxs origProp
let replIdxs = Replace valIdxs csIdxs
showExtrapOutput args valIdxs csIdxs replIdxs d
runAgainMsg
s <- getLine
if s == ""
then do let oldVals = (d,replIdxs):ds
let matchesProp a =
not (matchesShapes a oldVals)
Q.==> prop a
mcex' <- runQC (qcArgs args) matchesProp
smartCheck' oldVals matchesProp mcex'
else smartPrtLn "Done."
maybeDoneMsg = smartPrtLn "No value to smart-shrink; done."
existsExtrap :: (Generic a, SubTypes a, ConNames (Rep a))
=> ScArgs -> a -> [Idx] -> (a -> Q.Property) -> IO [Idx]
existsExtrap args d valIdxs origProp =
if runExists args
then constrsGen args d origProp valIdxs
else return []
forallExtrap :: SubTypes a => ScArgs -> a -> (a -> Q.Property) -> IO [Idx]
forallExtrap args d origProp =
if runForall args
then
extrapolate args d origProp
else return []
showExtrapOutput :: SubTypes a1
=> ScArgs -> [a] -> [a] -> Replace Idx -> a1 -> IO ()
showExtrapOutput args valIdxs csIdxs replIdxs d =
if (runForall args || runExists args) && (not $ null (valIdxs ++ csIdxs))
then output
else smartPrtLn "Could not extrapolate a new value."
where
output = do
putStrLn ""
smartPrtLn "Extrapolated value:"
renderWithVars (format args) d replIdxs
runAgainMsg :: IO ()
runAgainMsg = putStrLn $
"\nAttempt to find a new counterexample?\n"
++ " ('Enter' to continue;"
++ " any character then 'Enter' to quit.)"
runQCInit :: (Show a, Read a, Q.Arbitrary a, ScProp prop, Q.Testable prop)
=> Q.Args -> (a -> prop) -> IO (Maybe a, a -> Q.Property)
runQCInit args scProp = do
res <- Q.quickCheckWithResult args (genProp $ propify scProp)
return $ maybe
(Nothing, errorMsg "Bug in runQCInit")
((\(cex, p) -> (Just cex, p)) . parse)
(getOut res)
where
parse outs = (read $ head cexs, prop')
where cexs = lenChk ((< 2) . length) outs
prop' = propifyWithArgs (tail cexs) scProp
runQC :: (Show a, Read a, Q.Arbitrary a)
=> Q.Args -> (a -> Q.Property) -> IO (Maybe a)
runQC args prop = do
res <- Q.quickCheckWithResult args (genProp prop)
return $ fmap parse (getOut res)
where
parse outs = read $ head cexs
where cexs = lenChk ((/= 2) . length) outs
lenChk :: ([String] -> Bool) -> [String] -> [String]
lenChk chk ls = if chk ls then errorMsg "No value to SmartCheck!"
else tail ls
getOut :: Q.Result -> Maybe [String]
getOut res =
case res of
Q.Failure _ _ _ _ _ _ _ out -> Just $ lines out
_ -> Nothing
genProp :: (Show a, Q.Testable prop, Q.Arbitrary a)
=> (a -> prop) -> Q.Property
genProp prop = Q.forAllShrink Q.arbitrary Q.shrink prop
data ScProperty = Implies (Bool, Bool)
| Simple Bool
deriving (Show, Read, Eq)
instance Q.Testable ScProperty where
property (Simple prop) = Q.property prop
property (Implies prop) = Q.property (toQCImp prop)
exhaustive (Simple prop) = Q.exhaustive prop
exhaustive (Implies prop) = Q.exhaustive (toQCImp prop)
infixr 0 -->
(-->) :: Bool -> Bool -> ScProperty
pre --> post = Implies (pre, post)
toQCImp :: (Bool, Bool) -> Q.Property
toQCImp (pre, post) = pre Q.==> post
class ScProp prop where
scProperty :: [String] -> prop -> Q.Property
qcProperty :: prop -> Q.Property
instance ScProp Bool where
scProperty _ res = Q.property res
qcProperty = Q.property
instance ScProp ScProperty where
scProperty _ (Simple res) = Q.property res
scProperty _ (Implies prop) = Q.property $ toQCImp prop
qcProperty (Simple res) = Q.property res
qcProperty (Implies prop) = Q.property $ toQCImp prop
instance (Q.Arbitrary a, Q.Testable prop, Show a, Read a, ScProp prop)
=> ScProp (a -> prop) where
scProperty (str:strs) f = Q.property $ scProperty strs (f (read str))
scProperty _ _ = errorMsg "Insufficient values applied to property!"
qcProperty = Q.property
propifyWithArgs :: (Read a, ScProp prop)
=> [String] -> (a -> prop) -> (a -> Q.Property)
propifyWithArgs strs prop = \a -> scProperty strs (prop a)
propify :: ScProp prop => (a -> prop) -> (a -> Q.Property)
propify prop = \a -> qcProperty (prop a)