module Test.Feat.Driver(
test
, Result
, counterexamples
, testOptions
, Options(..)
, defOptions
, testFlex
, FlexibleOptions(..)
, FlexOptions(..)
, defFlex
, toFlex
, toFlexWith
) where
import Control.Enumerable
import Test.Feat.Access
import Test.Feat.Finite
import Test.Feat.Enumerate
import System.Timeout
import Data.IORef
data Options = Options
{ oTimeoutSec :: Maybe Int
, oSizeFromTo :: Maybe (Int,Int)
, oMaxCounter :: Maybe Int
, oSilent :: Bool
, oSkipping :: Maybe (Index, Integer)
, oBounded :: Maybe Integer
} deriving (Show,Read)
type FlexibleOptions a = IO (FlexOptions a)
data FlexOptions a = FlexOptions
{ fIO :: IO Bool -> IO (Result a)
, fReport :: a -> IO Bool
, fOutput :: String -> IO ()
, fProcess :: Enumerate a -> Enumerate a
, fEnum :: Enumerate a
}
data Result a = Exhausted [a]
| Quota [a]
| TimedOut [a]
deriving Show
counterexamples :: Result a -> [a]
counterexamples (Exhausted xs) = xs
counterexamples (Quota xs) = xs
counterexamples (TimedOut xs) = xs
defOptions :: Options
defOptions = Options
{ oTimeoutSec = Just 60
, oSizeFromTo = Just (0,100)
, oSilent = False
, oSkipping = Nothing
, oBounded = Just 100000
, oMaxCounter = Just 1
}
defFlex :: Enumerable a => FlexibleOptions a
defFlex = defFlexWith optimal
defFlexWith :: Enumerate a -> FlexibleOptions a
defFlexWith e = toFlexWith e defOptions
toFlex :: Enumerable a => Options -> FlexibleOptions a
toFlex = toFlexWith optimal
toFlexWith :: Enumerate a -> Options -> FlexibleOptions a
toFlexWith e o = do
res <- newIORef []
count <- newIORef 0
let doReport x = do
modifyIORef res (x:)
modifyIORef count (+1)
maybe (return True) (checkCount) (oMaxCounter o)
checkCount mx = do
n <- readIORef count
return (n < mx)
doIO io = do
mb <- maybe (fmap Just io) (\t -> timeout (t*1000000) io) (oTimeoutSec o)
res <- readIORef res
return $ maybe (TimedOut res) (\b -> if b then Exhausted res else Quota res) mb
skip = maybe id (\(i,n) e -> skipping e i n) (oSkipping o)
bound = maybe id (\n e -> bounded e n) (oBounded o)
sizes = maybe id (\bs e -> sizeRange e bs) (oSizeFromTo o)
return $ FlexOptions
{ fIO = doIO
, fOutput = if oSilent o then const (return ()) else putStr
, fReport = doReport
, fProcess = bound . skip . sizes
, fEnum = e
}
test :: Enumerable a => (a -> Bool) -> IO (Result a)
test = testFlex defFlex
testOptions :: Enumerable a => Options -> (a -> Bool) -> IO (Result a)
testOptions = testFlex . toFlex
testFlex :: FlexibleOptions a -> (a -> Bool) -> IO (Result a)
testFlex ioOp p = do
op <- ioOp
let e = fProcess op (fEnum op)
lazyResult = [(n,filter (not . p) xs) | (n,xs) <- valuesWith e]
runSize k (n,cs) = do
fOutput op $ "*** Searching in " ++ show n ++ " values of size " ++ show k ++ "\n"
doWhile (map (\x -> fOutput op "Counterexample found!\n" >> fReport op x) cs)
fIO op ((doWhile $ zipWith runSize [0..] lazyResult))
doWhile :: [IO Bool] -> IO Bool
doWhile [] = return True
doWhile (iob:iobs) = iob >>= \b -> if b then doWhile iobs else return False