{-# LANGUAGE OverloadedStrings #-}
module Test.Tasty.Golden
( goldenVsFile
, goldenVsString
, goldenVsFileDiff
, goldenVsStringDiff
, SizeCutoff(..)
, writeBinaryFile
, findByExtension
, createDirectoriesAndWriteFile
)
where
import Test.Tasty
import Test.Tasty.Golden.Advanced
import Test.Tasty.Golden.Internal
import Text.Printf
import qualified Data.ByteString.Lazy as LBS
import Data.Monoid
import qualified Data.Text.Lazy as LT
import qualified Data.Text.Lazy.Encoding as LT
import System.IO
import System.IO.Temp
import System.Process
import System.Exit
import System.FilePath
import System.Directory
import Control.Exception
import Control.Monad
import qualified Data.Set as Set
goldenVsFile
:: TestName
-> FilePath
-> FilePath
-> IO ()
-> TestTree
goldenVsFile :: TestName -> TestName -> TestName -> IO () -> TestTree
goldenVsFile name :: TestName
name ref :: TestName
ref new :: TestName
new act :: IO ()
act =
TestName
-> IO ByteString
-> IO ByteString
-> (ByteString -> ByteString -> IO (Maybe TestName))
-> (ByteString -> IO ())
-> TestTree
forall a.
TestName
-> IO a
-> IO a
-> (a -> a -> IO (Maybe TestName))
-> (a -> IO ())
-> TestTree
goldenTest
TestName
name
(TestName -> IO ByteString
readFileStrict TestName
ref)
(IO ()
act IO () -> IO ByteString -> IO ByteString
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> TestName -> IO ByteString
readFileStrict TestName
new)
ByteString -> ByteString -> IO (Maybe TestName)
cmp
ByteString -> IO ()
upd
where
cmp :: ByteString -> ByteString -> IO (Maybe TestName)
cmp = TestName -> ByteString -> ByteString -> IO (Maybe TestName)
forall a. Eq a => TestName -> a -> a -> IO (Maybe TestName)
simpleCmp (TestName -> ByteString -> ByteString -> IO (Maybe TestName))
-> TestName -> ByteString -> ByteString -> IO (Maybe TestName)
forall a b. (a -> b) -> a -> b
$ TestName -> TestName -> TestName -> TestName
forall r. PrintfType r => TestName -> r
printf "Files '%s' and '%s' differ" TestName
ref TestName
new
upd :: ByteString -> IO ()
upd = TestName -> ByteString -> IO ()
createDirectoriesAndWriteFile TestName
ref
goldenVsString
:: TestName
-> FilePath
-> IO LBS.ByteString
-> TestTree
goldenVsString :: TestName -> TestName -> IO ByteString -> TestTree
goldenVsString name :: TestName
name ref :: TestName
ref act :: IO ByteString
act =
(SizeCutoff -> TestTree) -> TestTree
forall v. IsOption v => (v -> TestTree) -> TestTree
askOption ((SizeCutoff -> TestTree) -> TestTree)
-> (SizeCutoff -> TestTree) -> TestTree
forall a b. (a -> b) -> a -> b
$ \sizeCutoff :: SizeCutoff
sizeCutoff ->
TestName
-> IO ByteString
-> IO ByteString
-> (ByteString -> ByteString -> IO (Maybe TestName))
-> (ByteString -> IO ())
-> TestTree
forall a.
TestName
-> IO a
-> IO a
-> (a -> a -> IO (Maybe TestName))
-> (a -> IO ())
-> TestTree
goldenTest
TestName
name
(TestName -> IO ByteString
readFileStrict TestName
ref)
IO ByteString
act
(SizeCutoff -> ByteString -> ByteString -> IO (Maybe TestName)
cmp SizeCutoff
sizeCutoff)
ByteString -> IO ()
upd
where
cmp :: SizeCutoff -> ByteString -> ByteString -> IO (Maybe TestName)
cmp sizeCutoff :: SizeCutoff
sizeCutoff x :: ByteString
x y :: ByteString
y = TestName -> ByteString -> ByteString -> IO (Maybe TestName)
forall a. Eq a => TestName -> a -> a -> IO (Maybe TestName)
simpleCmp TestName
msg ByteString
x ByteString
y
where
msg :: TestName
msg = TestName -> TestName -> TestName
forall r. PrintfType r => TestName -> r
printf "Test output was different from '%s'. It was:\n" TestName
ref TestName -> TestName -> TestName
forall a. Semigroup a => a -> a -> a
<>
ByteString -> TestName
unpackUtf8 (SizeCutoff -> ByteString -> ByteString
truncateLargeOutput SizeCutoff
sizeCutoff ByteString
y)
upd :: ByteString -> IO ()
upd = TestName -> ByteString -> IO ()
createDirectoriesAndWriteFile TestName
ref
simpleCmp :: Eq a => String -> a -> a -> IO (Maybe String)
simpleCmp :: TestName -> a -> a -> IO (Maybe TestName)
simpleCmp e :: TestName
e x :: a
x y :: a
y =
Maybe TestName -> IO (Maybe TestName)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe TestName -> IO (Maybe TestName))
-> Maybe TestName -> IO (Maybe TestName)
forall a b. (a -> b) -> a -> b
$ if a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
y then Maybe TestName
forall a. Maybe a
Nothing else TestName -> Maybe TestName
forall a. a -> Maybe a
Just TestName
e
goldenVsFileDiff
:: TestName
-> (FilePath -> FilePath -> [String])
-> FilePath
-> FilePath
-> IO ()
-> TestTree
goldenVsFileDiff :: TestName
-> (TestName -> TestName -> [TestName])
-> TestName
-> TestName
-> IO ()
-> TestTree
goldenVsFileDiff name :: TestName
name cmdf :: TestName -> TestName -> [TestName]
cmdf ref :: TestName
ref new :: TestName
new act :: IO ()
act =
(SizeCutoff -> TestTree) -> TestTree
forall v. IsOption v => (v -> TestTree) -> TestTree
askOption ((SizeCutoff -> TestTree) -> TestTree)
-> (SizeCutoff -> TestTree) -> TestTree
forall a b. (a -> b) -> a -> b
$ \sizeCutoff :: SizeCutoff
sizeCutoff ->
TestName
-> IO ()
-> IO ()
-> (() -> () -> IO (Maybe TestName))
-> (() -> IO ())
-> TestTree
forall a.
TestName
-> IO a
-> IO a
-> (a -> a -> IO (Maybe TestName))
-> (a -> IO ())
-> TestTree
goldenTest
TestName
name
(() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())
IO ()
act
(SizeCutoff -> () -> () -> IO (Maybe TestName)
forall p p. SizeCutoff -> p -> p -> IO (Maybe TestName)
cmp SizeCutoff
sizeCutoff)
() -> IO ()
forall p. p -> IO ()
upd
where
cmd :: [TestName]
cmd = TestName -> TestName -> [TestName]
cmdf TestName
ref TestName
new
cmp :: SizeCutoff -> p -> p -> IO (Maybe TestName)
cmp sizeCutoff :: SizeCutoff
sizeCutoff _ _
| [TestName] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [TestName]
cmd = TestName -> IO (Maybe TestName)
forall a. HasCallStack => TestName -> a
error "goldenVsFileDiff: empty command line"
| Bool
otherwise = do
(_, Just sout :: Handle
sout, _, pid :: ProcessHandle
pid) <- CreateProcess
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
createProcess (TestName -> [TestName] -> CreateProcess
proc ([TestName] -> TestName
forall a. [a] -> a
head [TestName]
cmd) ([TestName] -> [TestName]
forall a. [a] -> [a]
tail [TestName]
cmd)) { std_out :: StdStream
std_out = StdStream
CreatePipe }
ByteString
out <- Handle -> IO ByteString
hGetContentsStrict Handle
sout
ExitCode
r <- ProcessHandle -> IO ExitCode
waitForProcess ProcessHandle
pid
Maybe TestName -> IO (Maybe TestName)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe TestName -> IO (Maybe TestName))
-> Maybe TestName -> IO (Maybe TestName)
forall a b. (a -> b) -> a -> b
$ case ExitCode
r of
ExitSuccess -> Maybe TestName
forall a. Maybe a
Nothing
_ -> TestName -> Maybe TestName
forall a. a -> Maybe a
Just (TestName -> Maybe TestName)
-> (ByteString -> TestName) -> ByteString -> Maybe TestName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> TestName
unpackUtf8 (ByteString -> TestName)
-> (ByteString -> ByteString) -> ByteString -> TestName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SizeCutoff -> ByteString -> ByteString
truncateLargeOutput SizeCutoff
sizeCutoff (ByteString -> Maybe TestName) -> ByteString -> Maybe TestName
forall a b. (a -> b) -> a -> b
$ ByteString
out
upd :: p -> IO ()
upd _ = TestName -> IO ByteString
readFileStrict TestName
new IO ByteString -> (ByteString -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= TestName -> ByteString -> IO ()
createDirectoriesAndWriteFile TestName
ref
goldenVsStringDiff
:: TestName
-> (FilePath -> FilePath -> [String])
-> FilePath
-> IO LBS.ByteString
-> TestTree
goldenVsStringDiff :: TestName
-> (TestName -> TestName -> [TestName])
-> TestName
-> IO ByteString
-> TestTree
goldenVsStringDiff name :: TestName
name cmdf :: TestName -> TestName -> [TestName]
cmdf ref :: TestName
ref act :: IO ByteString
act =
(SizeCutoff -> TestTree) -> TestTree
forall v. IsOption v => (v -> TestTree) -> TestTree
askOption ((SizeCutoff -> TestTree) -> TestTree)
-> (SizeCutoff -> TestTree) -> TestTree
forall a b. (a -> b) -> a -> b
$ \sizeCutoff :: SizeCutoff
sizeCutoff ->
TestName
-> IO ByteString
-> IO ByteString
-> (ByteString -> ByteString -> IO (Maybe TestName))
-> (ByteString -> IO ())
-> TestTree
forall a.
TestName
-> IO a
-> IO a
-> (a -> a -> IO (Maybe TestName))
-> (a -> IO ())
-> TestTree
goldenTest
TestName
name
(TestName -> IO ByteString
readFileStrict TestName
ref)
(IO ByteString
act)
(SizeCutoff -> ByteString -> ByteString -> IO (Maybe TestName)
forall p. SizeCutoff -> p -> ByteString -> IO (Maybe TestName)
cmp SizeCutoff
sizeCutoff)
ByteString -> IO ()
upd
where
template :: TestName
template = TestName -> TestName
takeBaseName TestName
ref TestName -> TestName -> TestName
<.> "actual"
cmp :: SizeCutoff -> p -> ByteString -> IO (Maybe TestName)
cmp sizeCutoff :: SizeCutoff
sizeCutoff _ actBS :: ByteString
actBS = TestName
-> (TestName -> Handle -> IO (Maybe TestName))
-> IO (Maybe TestName)
forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
TestName -> (TestName -> Handle -> m a) -> m a
withSystemTempFile TestName
template ((TestName -> Handle -> IO (Maybe TestName))
-> IO (Maybe TestName))
-> (TestName -> Handle -> IO (Maybe TestName))
-> IO (Maybe TestName)
forall a b. (a -> b) -> a -> b
$ \tmpFile :: TestName
tmpFile tmpHandle :: Handle
tmpHandle -> do
Handle -> ByteString -> IO ()
LBS.hPut Handle
tmpHandle ByteString
actBS IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Handle -> IO ()
hFlush Handle
tmpHandle
let cmd :: [TestName]
cmd = TestName -> TestName -> [TestName]
cmdf TestName
ref TestName
tmpFile
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ([TestName] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [TestName]
cmd) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ TestName -> IO ()
forall a. HasCallStack => TestName -> a
error "goldenVsFileDiff: empty command line"
(_, Just sout :: Handle
sout, _, pid :: ProcessHandle
pid) <- CreateProcess
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
createProcess (TestName -> [TestName] -> CreateProcess
proc ([TestName] -> TestName
forall a. [a] -> a
head [TestName]
cmd) ([TestName] -> [TestName]
forall a. [a] -> [a]
tail [TestName]
cmd)) { std_out :: StdStream
std_out = StdStream
CreatePipe }
ByteString
out <- Handle -> IO ByteString
hGetContentsStrict Handle
sout
ExitCode
r <- ProcessHandle -> IO ExitCode
waitForProcess ProcessHandle
pid
Maybe TestName -> IO (Maybe TestName)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe TestName -> IO (Maybe TestName))
-> Maybe TestName -> IO (Maybe TestName)
forall a b. (a -> b) -> a -> b
$ case ExitCode
r of
ExitSuccess -> Maybe TestName
forall a. Maybe a
Nothing
_ -> TestName -> Maybe TestName
forall a. a -> Maybe a
Just (TestName -> TestName -> TestName -> TestName
forall r. PrintfType r => TestName -> r
printf "Test output was different from '%s'. Output of %s:\n" TestName
ref ([TestName] -> TestName
forall a. Show a => a -> TestName
show [TestName]
cmd) TestName -> TestName -> TestName
forall a. Semigroup a => a -> a -> a
<> ByteString -> TestName
unpackUtf8 (SizeCutoff -> ByteString -> ByteString
truncateLargeOutput SizeCutoff
sizeCutoff ByteString
out))
upd :: ByteString -> IO ()
upd = TestName -> ByteString -> IO ()
createDirectoriesAndWriteFile TestName
ref
truncateLargeOutput
:: SizeCutoff
-> LBS.ByteString
-> LBS.ByteString
truncateLargeOutput :: SizeCutoff -> ByteString -> ByteString
truncateLargeOutput (SizeCutoff n :: Int64
n) str :: ByteString
str =
if ByteString -> Int64
LBS.length ByteString
str Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Int64
n
then ByteString
str
else
Int64 -> ByteString -> ByteString
LBS.take Int64
n ByteString
str ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> "<truncated>" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<>
"\nUse --accept or increase --size-cutoff to see full output."
writeBinaryFile :: FilePath -> String -> IO ()
writeBinaryFile :: TestName -> TestName -> IO ()
writeBinaryFile f :: TestName
f txt :: TestName
txt = TestName -> IOMode -> (Handle -> IO ()) -> IO ()
forall r. TestName -> IOMode -> (Handle -> IO r) -> IO r
withBinaryFile TestName
f IOMode
WriteMode (\hdl :: Handle
hdl -> Handle -> TestName -> IO ()
hPutStr Handle
hdl TestName
txt)
findByExtension
:: [FilePath]
-> FilePath
-> IO [FilePath]
findByExtension :: [TestName] -> TestName -> IO [TestName]
findByExtension extsList :: [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 dir :: TestName
dir = do
[TestName]
allEntries <- TestName -> IO [TestName]
getDirectoryContents TestName
dir
let entries :: [TestName]
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 (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [".", ".."])) [TestName]
allEntries
([[TestName]] -> [TestName]) -> IO [[TestName]] -> IO [TestName]
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM [[TestName]] -> [TestName]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (IO [[TestName]] -> IO [TestName])
-> IO [[TestName]] -> IO [TestName]
forall a b. (a -> b) -> a -> b
$ [TestName] -> (TestName -> IO [TestName]) -> IO [[TestName]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [TestName]
entries ((TestName -> IO [TestName]) -> IO [[TestName]])
-> (TestName -> IO [TestName]) -> IO [[TestName]]
forall a b. (a -> b) -> a -> b
$ \e :: TestName
e -> do
let path :: TestName
path = TestName
dir TestName -> TestName -> TestName
forall a. [a] -> [a] -> [a]
++ "/" TestName -> TestName -> TestName
forall a. [a] -> [a] -> [a]
++ TestName
e
Bool
isDir <- TestName -> IO Bool
doesDirectoryExist TestName
path
if Bool
isDir
then TestName -> IO [TestName]
go TestName
path
else
[TestName] -> IO [TestName]
forall (m :: * -> *) a. Monad m => a -> m a
return ([TestName] -> IO [TestName]) -> [TestName] -> IO [TestName]
forall a b. (a -> b) -> a -> b
$
if TestName -> TestName
takeExtension TestName
path TestName -> Set TestName -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set TestName
exts
then [TestName
path]
else []
createDirectoriesAndWriteFile
:: FilePath
-> LBS.ByteString
-> IO ()
createDirectoriesAndWriteFile :: TestName -> ByteString -> IO ()
createDirectoriesAndWriteFile path :: TestName
path bs :: ByteString
bs = do
let dir :: TestName
dir = TestName -> TestName
takeDirectory TestName
path
Bool -> TestName -> IO ()
createDirectoryIfMissing
Bool
True
TestName
dir
TestName -> ByteString -> IO ()
LBS.writeFile TestName
path ByteString
bs
forceLbs :: LBS.ByteString -> ()
forceLbs :: ByteString -> ()
forceLbs = (Word8 -> () -> ()) -> () -> ByteString -> ()
forall a. (Word8 -> a -> a) -> a -> ByteString -> a
LBS.foldr Word8 -> () -> ()
forall a b. a -> b -> b
seq ()
readFileStrict :: FilePath -> IO LBS.ByteString
readFileStrict :: TestName -> IO ByteString
readFileStrict path :: TestName
path = do
ByteString
s <- TestName -> IO ByteString
LBS.readFile TestName
path
() -> IO ()
forall a. a -> IO a
evaluate (() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ByteString -> ()
forceLbs ByteString
s
ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
s
hGetContentsStrict :: Handle -> IO LBS.ByteString
hGetContentsStrict :: Handle -> IO ByteString
hGetContentsStrict h :: Handle
h = do
Handle -> Bool -> IO ()
hSetBinaryMode Handle
h Bool
True
ByteString
s <- Handle -> IO ByteString
LBS.hGetContents Handle
h
() -> IO ()
forall a. a -> IO a
evaluate (() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ByteString -> ()
forceLbs ByteString
s
ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
s
unpackUtf8 :: LBS.ByteString -> String
unpackUtf8 :: ByteString -> TestName
unpackUtf8 = Text -> TestName
LT.unpack (Text -> TestName)
-> (ByteString -> Text) -> ByteString -> TestName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
LT.decodeUtf8