{-# LANGUAGE TypeSynonymInstances, FlexibleInstances, OverloadedStrings #-}
{-# LANGUAGE CPP #-}
module Test.Tasty.Silver
( goldenVsFile
, goldenVsProg
, goldenVsAction
, printProcResult
, findByExtension
)
where
import Control.Monad
#if !(MIN_VERSION_base(4,8,0))
import Data.Functor ( (<$>) )
#endif
import qualified Data.ByteString as BS
import qualified Data.Set as Set
import qualified Data.Text as T
import Data.Text.Encoding
import System.Directory
import System.Exit
import System.FilePath
import System.Process.Text as PT
import Test.Tasty.Providers (TestTree, TestName)
import Test.Tasty.Silver.Advanced
goldenVsFile
:: TestName
-> FilePath
-> FilePath
-> IO ()
-> TestTree
goldenVsFile :: TestName -> TestName -> TestName -> IO () -> TestTree
goldenVsFile TestName
name TestName
ref TestName
new IO ()
act =
TestName
-> IO (Maybe Text)
-> IO Text
-> (Text -> Text -> GDiff)
-> (Text -> GShow)
-> (Text -> IO ())
-> TestTree
forall a.
TestName
-> IO (Maybe a)
-> IO a
-> (a -> a -> GDiff)
-> (a -> GShow)
-> (a -> IO ())
-> TestTree
goldenTest1
TestName
name
((ByteString -> Text) -> Maybe ByteString -> Maybe Text
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Text
decodeUtf8 (Maybe ByteString -> Maybe Text)
-> IO (Maybe ByteString) -> IO (Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TestName -> IO (Maybe ByteString)
readFileMaybe TestName
ref)
(IO ()
act IO () -> IO Text -> IO Text
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (ByteString -> Text
decodeUtf8 (ByteString -> Text) -> IO ByteString -> IO Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TestName -> IO ByteString
BS.readFile TestName
new))
Text -> Text -> GDiff
textLikeDiff
Text -> GShow
textLikeShow
(Text -> IO ()
upd)
where upd :: Text -> IO ()
upd = TestName -> ByteString -> IO ()
BS.writeFile TestName
ref (ByteString -> IO ()) -> (Text -> ByteString) -> Text -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
encodeUtf8
goldenVsProg
:: TestName
-> FilePath
-> FilePath
-> [String]
-> T.Text
-> TestTree
goldenVsProg :: TestName -> TestName -> TestName -> [TestName] -> Text -> TestTree
goldenVsProg TestName
name TestName
ref TestName
cmd [TestName]
args Text
inp =
TestName
-> TestName
-> IO (ExitCode, Text, Text)
-> ((ExitCode, Text, Text) -> Text)
-> TestTree
forall a. TestName -> TestName -> IO a -> (a -> Text) -> TestTree
goldenVsAction TestName
name TestName
ref IO (ExitCode, Text, Text)
runProg (ExitCode, Text, Text) -> Text
printProcResult
where runProg :: IO (ExitCode, Text, Text)
runProg = TestName -> [TestName] -> Text -> IO (ExitCode, Text, Text)
PT.readProcessWithExitCode TestName
cmd [TestName]
args Text
inp
goldenVsAction
:: TestName
-> FilePath
-> IO a
-> (a -> T.Text)
-> TestTree
goldenVsAction :: forall a. TestName -> TestName -> IO a -> (a -> Text) -> TestTree
goldenVsAction TestName
name TestName
ref IO a
act a -> Text
toTxt =
TestName
-> IO (Maybe Text)
-> IO Text
-> (Text -> Text -> GDiff)
-> (Text -> GShow)
-> (Text -> IO ())
-> TestTree
forall a.
TestName
-> IO (Maybe a)
-> IO a
-> (a -> a -> GDiff)
-> (a -> GShow)
-> (a -> IO ())
-> TestTree
goldenTest1
TestName
name
((ByteString -> Text) -> Maybe ByteString -> Maybe Text
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Text
decodeUtf8 (Maybe ByteString -> Maybe Text)
-> IO (Maybe ByteString) -> IO (Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TestName -> IO (Maybe ByteString)
readFileMaybe TestName
ref)
(a -> Text
toTxt (a -> Text) -> IO a -> IO Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO a
act)
Text -> Text -> GDiff
textLikeDiff
Text -> GShow
textLikeShow
(TestName -> ByteString -> IO ()
BS.writeFile TestName
ref (ByteString -> IO ()) -> (Text -> ByteString) -> Text -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
encodeUtf8)
textLikeShow :: T.Text -> GShow
textLikeShow :: Text -> GShow
textLikeShow = Text -> GShow
ShowText
textLikeDiff :: T.Text -> T.Text -> GDiff
textLikeDiff :: Text -> Text -> GDiff
textLikeDiff Text
x Text
y | Text
x Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
y = GDiff
Equal
textLikeDiff Text
x Text
y | Bool
otherwise = Maybe TestName -> Text -> Text -> GDiff
DiffText Maybe TestName
forall a. Maybe a
Nothing Text
x Text
y
printProcResult :: (ExitCode, T.Text, T.Text) -> T.Text
printProcResult :: (ExitCode, Text, Text) -> Text
printProcResult (ExitCode
ex, Text
a, Text
b) = [Text] -> Text
T.unlines ([Text
"ret > " Text -> Text -> Text
`T.append` TestName -> Text
T.pack (ExitCode -> TestName
forall a. Show a => a -> TestName
show ExitCode
ex)]
[Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ Text -> Text -> [Text]
addPrefix Text
"out >" Text
a [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ Text -> Text -> [Text]
addPrefix Text
"err >" Text
b)
where addPrefix :: Text -> Text -> [Text]
addPrefix Text
_ Text
t | Text -> Bool
T.null Text
t = []
addPrefix Text
pref Text
t | Bool
otherwise = (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> Text -> Text
f Text
pref) (HasCallStack => Text -> Text -> [Text]
Text -> Text -> [Text]
T.splitOn Text
"\n" Text
t)
f :: Text -> Text -> Text
f Text
pref Text
ln | Text -> Bool
T.null Text
ln = Text
pref
f Text
pref Text
ln | Bool
otherwise = Text
pref Text -> Text -> Text
`T.append` Text
" " Text -> Text -> Text
`T.append` Text
ln
findByExtension
:: [FilePath]
-> FilePath
-> IO [FilePath]
findByExtension :: [TestName] -> TestName -> IO [TestName]
findByExtension [TestName]
extsList = TestName -> IO [TestName]
go
where
exts :: Set TestName
exts = [TestName] -> Set TestName
forall a. Ord a => [a] -> Set a
Set.fromList [TestName]
extsList
go :: TestName -> IO [TestName]
go TestName
dir = do
allEntries <- TestName -> IO [TestName]
getDirectoryContents TestName
dir
let entries = (TestName -> Bool) -> [TestName] -> [TestName]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (TestName -> Bool) -> TestName -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TestName -> [TestName] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [TestName
".", TestName
".."])) [TestName]
allEntries
liftM concat $ forM entries $ \TestName
e -> do
let path :: TestName
path = TestName
dir TestName -> TestName -> TestName
forall a. [a] -> [a] -> [a]
++ TestName
"/" TestName -> TestName -> TestName
forall a. [a] -> [a] -> [a]
++ TestName
e
isDir <- TestName -> IO Bool
doesDirectoryExist TestName
path
if isDir
then go path
else return [ path | takeExtension path `Set.member` exts ]