{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ImplicitParams #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeSynonymInstances #-}
module Test.Tasty.Checklist
(
withChecklist
, CanCheck
, check
, discardCheck
, checkValues
, DerivedVal(Val, Got, Observe)
, CheckResult
, ChecklistFailures
, TestShow(testShow)
, testShowList
, multiLineDiff
)
where
import Control.Exception ( evaluate )
import Control.Monad ( join, unless )
import Control.Monad.Catch
import Control.Monad.IO.Class ( MonadIO, liftIO )
import Data.IORef
import qualified Data.List as List
import qualified Data.Parameterized.Context as Ctx
import Data.Text ( Text )
import qualified Data.Text as T
import System.IO ( hFlush, hPutStrLn, stdout, stderr )
data ChecklistFailures = ChecklistFailures Text [CheckResult]
data CheckResult = CheckFailed Text Text
instance Exception ChecklistFailures
instance Show CheckResult where
show :: CheckResult -> String
show (CheckFailed Text
what Text
msg) =
String
"Failed check of " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack Text
what String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" with: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack Text
msg
instance Show ChecklistFailures where
show :: ChecklistFailures -> String
show (ChecklistFailures Text
topMsg [CheckResult]
fails) =
String
"ERROR: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack Text
topMsg String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"\n " String -> ShowS
forall a. Semigroup a => a -> a -> a
<>
Int -> String
forall a. Show a => a -> String
show ([CheckResult] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [CheckResult]
fails) String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" checks failed in this checklist:\n -" String -> ShowS
forall a. Semigroup a => a -> a -> a
<>
String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
List.intercalate String
"\n -" (CheckResult -> String
forall a. Show a => a -> String
show (CheckResult -> String) -> [CheckResult] -> [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [CheckResult]
fails)
type CanCheck = (?checker :: IORef [CheckResult])
withChecklist :: (MonadIO m, MonadMask m)
=> Text -> (CanCheck => m a) -> m a
withChecklist :: Text -> (CanCheck => m a) -> m a
withChecklist Text
topMsg CanCheck => m a
t = do
IORef [CheckResult]
checks <- IO (IORef [CheckResult]) -> m (IORef [CheckResult])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (IORef [CheckResult]) -> m (IORef [CheckResult]))
-> IO (IORef [CheckResult]) -> m (IORef [CheckResult])
forall a b. (a -> b) -> a -> b
$ [CheckResult] -> IO (IORef [CheckResult])
forall a. a -> IO (IORef a)
newIORef [CheckResult]
forall a. Monoid a => a
mempty
a
r <- (let ?checker = checks in m a
CanCheck => m a
t)
m a -> m () -> m a
forall (m :: * -> *) a b. MonadCatch m => m a -> m b -> m a
`onException` (IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$
do [CheckResult]
cs <- [CheckResult] -> [CheckResult]
forall a. [a] -> [a]
List.reverse ([CheckResult] -> [CheckResult])
-> IO [CheckResult] -> IO [CheckResult]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IORef [CheckResult] -> IO [CheckResult]
forall a. IORef a -> IO a
readIORef IORef [CheckResult]
checks
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([CheckResult] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [CheckResult]
cs) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Handle -> IO ()
hFlush Handle
stdout
Handle -> String -> IO ()
hPutStrLn Handle
stderr String
""
let pfx :: String
pfx = String
" WARN "
(CheckResult -> IO ()) -> [CheckResult] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Handle -> String -> IO ()
hPutStrLn Handle
stderr (String -> IO ())
-> (CheckResult -> String) -> CheckResult -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String
pfx String -> ShowS
forall a. Semigroup a => a -> a -> a
<>) ShowS -> (CheckResult -> String) -> CheckResult -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CheckResult -> String
forall a. Show a => a -> String
show) [CheckResult]
cs
Handle -> IO ()
hFlush Handle
stderr
)
IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
[CheckResult]
collected <- [CheckResult] -> [CheckResult]
forall a. [a] -> [a]
List.reverse ([CheckResult] -> [CheckResult])
-> IO [CheckResult] -> IO [CheckResult]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IORef [CheckResult] -> IO [CheckResult]
forall a. IORef a -> IO a
readIORef IORef [CheckResult]
checks
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([CheckResult] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [CheckResult]
collected) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
ChecklistFailures -> IO ()
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (Text -> [CheckResult] -> ChecklistFailures
ChecklistFailures Text
topMsg [CheckResult]
collected)
a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
r
check :: (CanCheck, TestShow a, MonadIO m)
=> Text -> (a -> Bool) -> a -> m ()
check :: Text -> (a -> Bool) -> a -> m ()
check = (a -> String) -> Text -> (a -> Bool) -> a -> m ()
forall (m :: * -> *) a.
(CanCheck, MonadIO m) =>
(a -> String) -> Text -> (a -> Bool) -> a -> m ()
checkShow a -> String
forall v. TestShow v => v -> String
testShow
checkShow :: (CanCheck, MonadIO m)
=> (a -> String) -> Text -> (a -> Bool) -> a -> m ()
checkShow :: (a -> String) -> Text -> (a -> Bool) -> a -> m ()
checkShow a -> String
showit Text
what a -> Bool
eval a
val = do
Bool
r <- IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ Bool -> IO Bool
forall a. a -> IO a
evaluate (a -> Bool
eval a
val)
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
r (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ do
let chk :: CheckResult
chk = Text -> Text -> CheckResult
CheckFailed Text
what (Text -> CheckResult) -> Text -> CheckResult
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ a -> String
showit a
val
IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ IORef [CheckResult] -> ([CheckResult] -> [CheckResult]) -> IO ()
forall a. IORef a -> (a -> a) -> IO ()
modifyIORef CanCheck
IORef [CheckResult]
?checker (CheckResult
chkCheckResult -> [CheckResult] -> [CheckResult]
forall a. a -> [a] -> [a]
:)
discardCheck :: (CanCheck, MonadIO m) => Text -> m ()
discardCheck :: Text -> m ()
discardCheck Text
what = do
let isCheck :: Text -> CheckResult -> Bool
isCheck Text
n (CheckFailed Text
n' Text
_) = Text
n Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
n'
IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ IORef [CheckResult] -> ([CheckResult] -> [CheckResult]) -> IO ()
forall a. IORef a -> (a -> a) -> IO ()
modifyIORef CanCheck
IORef [CheckResult]
?checker ((CheckResult -> Bool) -> [CheckResult] -> [CheckResult]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (CheckResult -> Bool) -> CheckResult -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> CheckResult -> Bool
isCheck Text
what))
checkValues :: CanCheck
=> TestShow dType
=> dType -> Ctx.Assignment (DerivedVal dType) idx -> IO ()
checkValues :: dType -> Assignment (DerivedVal dType) idx -> IO ()
checkValues dType
got Assignment (DerivedVal dType) idx
expF =
IO (IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (IO (IO ()) -> IO ()) -> IO (IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall a. a -> IO a
evaluate (() -> IO ()) -> IO () -> IO (IO ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall tp. Index idx tp -> DerivedVal dType tp -> IO ())
-> Assignment (DerivedVal dType) idx -> IO ()
forall k (m :: * -> *) (ctx :: Ctx k) (f :: k -> *).
Applicative m =>
(forall (tp :: k). Index ctx tp -> f tp -> m ())
-> Assignment f ctx -> m ()
Ctx.traverseWithIndex_ (dType -> Index idx tp -> DerivedVal dType tp -> IO ()
forall dType (idx :: Ctx *) valType.
(CanCheck, TestShow dType) =>
dType -> Index idx valType -> DerivedVal dType valType -> IO ()
chkValue dType
got) Assignment (DerivedVal dType) idx
expF
chkValue :: CanCheck
=> TestShow dType
=> dType -> Ctx.Index idx valType -> DerivedVal dType valType -> IO ()
chkValue :: dType -> Index idx valType -> DerivedVal dType valType -> IO ()
chkValue dType
got Index idx valType
_idx = \case
(Val Text
txt dType -> valType
fld valType
v) ->
let r :: valType
r = dType -> valType
fld dType
got
msg :: Text
msg = Text
txt Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" on input <<" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
ti Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
">>\n"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"expected: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
tv Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"failed"
ti :: Text
ti = String -> Text
T.pack (dType -> String
forall v. TestShow v => v -> String
testShow dType
got)
tv :: Text
tv = String -> Text
T.pack (valType -> String
forall v. TestShow v => v -> String
testShow valType
v)
in Text -> (valType -> Bool) -> valType -> IO ()
forall a (m :: * -> *).
(CanCheck, TestShow a, MonadIO m) =>
Text -> (a -> Bool) -> a -> m ()
check Text
msg (valType
v valType -> valType -> Bool
forall a. Eq a => a -> a -> Bool
==) valType
r
(Observe Text
txt dType -> valType
fld valType
v valType -> valType -> String
observationReport) ->
let r :: valType
r = dType -> valType
fld dType
got
msg :: Text
msg = Text
txt Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" observation failure"
in (valType -> String)
-> Text -> (valType -> Bool) -> valType -> IO ()
forall (m :: * -> *) a.
(CanCheck, MonadIO m) =>
(a -> String) -> Text -> (a -> Bool) -> a -> m ()
checkShow (valType -> valType -> String
observationReport valType
v) Text
msg (valType
v valType -> valType -> Bool
forall a. Eq a => a -> a -> Bool
==) valType
r
(Got Text
txt dType -> Bool
fld) ->
let r :: Bool
r = dType -> Bool
fld dType
got
msg :: Text
msg = Text
txt Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" on input <<" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
ti Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
">>"
ti :: Text
ti = String -> Text
T.pack (dType -> String
forall v. TestShow v => v -> String
testShow dType
got)
in Text -> (Bool -> Bool) -> Bool -> IO ()
forall a (m :: * -> *).
(CanCheck, TestShow a, MonadIO m) =>
Text -> (a -> Bool) -> a -> m ()
check Text
msg (Bool
True Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
==) Bool
r
data DerivedVal i d where
Val :: (TestShow d, Eq d) => Text -> (i -> d) -> d -> DerivedVal i d
Got :: Text -> (i -> Bool) -> DerivedVal i Bool
Observe :: (Eq d) => Text -> (i -> d) -> d -> (d -> d -> String) -> DerivedVal i d
class TestShow v where
testShow :: v -> String
default testShow :: Show v => v -> String
testShow = v -> String
forall a. Show a => a -> String
show
instance TestShow ()
instance TestShow Bool
instance TestShow Int
instance TestShow Integer
instance TestShow Float
instance TestShow Char
instance TestShow String
instance (TestShow a, TestShow b) => TestShow (a,b) where
testShow :: (a, b) -> String
testShow (a
a,b
b) = String
"(" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> a -> String
forall v. TestShow v => v -> String
testShow a
a String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
", " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> b -> String
forall v. TestShow v => v -> String
testShow b
b String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
")"
instance (TestShow a, TestShow b, TestShow c) => TestShow (a,b,c) where
testShow :: (a, b, c) -> String
testShow (a
a,b
b,c
c) = String
"(" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> a -> String
forall v. TestShow v => v -> String
testShow a
a String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
", " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> b -> String
forall v. TestShow v => v -> String
testShow b
b String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
", " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> c -> String
forall v. TestShow v => v -> String
testShow c
c String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
")"
testShowList :: TestShow v => [v] -> String
testShowList :: [v] -> String
testShowList [v]
l = String
"[ " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> (String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
List.intercalate String
", " (v -> String
forall v. TestShow v => v -> String
testShow (v -> String) -> [v] -> [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [v]
l)) String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" ]"
multiLineDiff :: T.Text -> T.Text -> String
multiLineDiff :: Text -> Text -> String
multiLineDiff Text
expected Text
actual =
let dl :: (a, a) -> a
dl (a
e,a
a) = if a
e a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
a then a -> a
forall a. (Semigroup a, IsString a) => a -> a
db a
e else a -> a -> a
forall a. (Semigroup a, IsString a) => a -> a -> a
de a
" ↱" a
e a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
"\n " a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a -> a -> a
forall a. (Semigroup a, IsString a) => a -> a -> a
da a
" ↳" a
a
db :: a -> a
db a
b = a
"| > " a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
b
de :: a -> a -> a
de a
m a
e = a
"|" a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
m a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
"expect> " a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
e
da :: a -> a -> a
da a
m a
a = a
"|" a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
m a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
"actual> " a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
a
el :: [Text]
el = Text -> [Text]
T.lines Text
expected
al :: [Text]
al = Text -> [Text]
T.lines Text
actual
addnum :: Int -> T.Text -> T.Text
addnum :: Int -> Text -> Text
addnum Int
n Text
l = let nt :: Text
nt = String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show Int
n)
nl :: Int
nl = Text -> Int
T.length Text
nt
in Int -> Text -> Text
T.take (Int
4 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
nl) Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
nt Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
l
banner :: Text
banner = Text
"MISMATCH between "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show (Int -> String) -> Int -> String
forall a b. (a -> b) -> a -> b
$ [Text] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Text]
el) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" expected and "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show (Int -> String) -> Int -> String
forall a b. (a -> b) -> a -> b
$ [Text] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Text]
al) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" actual"
diffReport :: [Text]
diffReport = ((Int, Text) -> Text) -> [(Int, Text)] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Int -> Text -> Text) -> (Int, Text) -> Text
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Int -> Text -> Text
addnum) ([(Int, Text)] -> [Text]) -> [(Int, Text)] -> [Text]
forall a b. (a -> b) -> a -> b
$
[Int] -> [Text] -> [(Int, Text)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
1..] ([Text] -> [(Int, Text)]) -> [Text] -> [(Int, Text)]
forall a b. (a -> b) -> a -> b
$ [[Text]] -> [Text]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Text]] -> [Text]) -> [[Text]] -> [Text]
forall a b. (a -> b) -> a -> b
$
[ ((Text, Text) -> Text) -> [(Text, Text)] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text, Text) -> Text
forall a. (Eq a, Semigroup a, IsString a) => (a, a) -> a
dl ([(Text, Text)] -> [Text]) -> [(Text, Text)] -> [Text]
forall a b. (a -> b) -> a -> b
$ [Text] -> [Text] -> [(Text, Text)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Text]
el [Text]
al
, (Text -> Text) -> [Text] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text -> Text -> Text
forall a. (Semigroup a, IsString a) => a -> a -> a
de Text
"∌ ") ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ Int -> [Text] -> [Text]
forall a. Int -> [a] -> [a]
drop ([Text] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Text]
al) [Text]
el
, (Text -> Text) -> [Text] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text -> Text -> Text
forall a. (Semigroup a, IsString a) => a -> a -> a
da Text
"∹ ") ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ Int -> [Text] -> [Text]
forall a. Int -> [a] -> [a]
drop ([Text] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Text]
el) [Text]
al
]
details :: [Text]
details = Text
banner Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text]
diffReport
in if Text
expected Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
actual then String
"<no difference>" else Text -> String
T.unpack ([Text] -> Text
T.unlines [Text]
details)