{- |

== Getting Started
To get started with golden testing and this library, see
<https://ro-che.info/articles/2017-12-04-golden-tests Introduction to golden testing>.

This module provides a simplified interface. If you want more, see
"Test.Tasty.Golden.Advanced".

== Filenames
Filenames are looked up in the usual way, Thus relative
names are relative to the processes current working directory.
It is common to run tests from the package's root directory (via @cabal
test@ or @cabal install --enable-tests@), so if your test files are under
the @tests\/@ subdirectory, your relative file names should start with
@tests\/@ (even if your @test.hs@ is itself under @tests\/@, too).

== Line endings

The best way to avoid headaches with line endings
(when running tests both on UNIX and Windows) is to treat your golden files
as binary, even when they are actually textual.

This means:

* When writing output files from Haskell code, open them in binary mode
(see 'openBinaryFile', 'withBinaryFile' and 'hSetBinaryMode'). This will
disable automatic @\\n -> \\r\\n@ conversion on Windows. For convenience, this
module exports 'writeBinaryFile' which is just like `writeFile` but opens
the file in binary mode. When using 'ByteString's note that
"Data.ByteString" and "Data.ByteString.Lazy" use binary mode for
@writeFile@, while "Data.ByteString.Char8" and "Data.ByteString.Lazy.Char8"
use text mode.

* Tell your VCS not to do any newline conversion for golden files. For
 git check in a @.gitattributes@ file with the following contents (assuming
 your golden files have @.golden@ extension):

>*.golden	-text

On its side, tasty-golden reads and writes files in binary mode, too.

Why not let Haskell/git do automatic conversion on Windows? Well, for
instance, @tar@ will not do the conversion for you when unpacking a release
tarball, so when you run @cabal install your-package --enable-tests@, the
tests will be broken.

As a last resort, you can strip all @\\r@s from both arguments in your
comparison function when necessary. But most of the time treating the files
as binary does the job.

== Linking
The test suite should be compiled with @-threaded@ if you want to avoid
blocking any other threads while 'goldenVsFileDiff' and similar functions
wait for the result of the diff command.

== Windows limitations
When using 'goldenVsFileDiff' or 'goldenVsStringDiff' under Windows the exit
code from the diff program that you specify will not be captured correctly
if that program uses @exec@.

More specifically, you will get the exit code of the /original child/
(which always exits with code 0, since it called @exec@), not the exit
code of the process which carried on with execution after @exec@.
This is different from the behavior prescribed by POSIX but is the best
approximation that can be realised under the restrictions of the
Windows process model.  See 'System.Process' for further details or
<https://github.com/haskell/process/pull/168> for even more.

-}

{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
module Test.Tasty.Golden
  (
    -- * Functions to create a golden test
    goldenVsFile
  , goldenVsString
  , goldenVsFileDiff
  , goldenVsStringDiff
    -- * Options
  , SizeCutoff(..)
  , DeleteOutputFile(..)
    -- * Various utilities
  , 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 qualified Data.Text.Lazy as LT
import qualified Data.Text.Lazy.Encoding as LT
import System.IO
import System.IO.Temp
import qualified System.Process.Typed as PT
import System.Exit
import System.FilePath
import System.Directory
import Control.Exception
import Control.Monad
import qualified Data.Set as Set
import Foreign.C.Error
#if !MIN_VERSION_base(4,11,0)
import Data.Monoid
#endif

-- | Compare the output file's contents against the golden file's contents
-- after the given action has created the output file.
goldenVsFile
  :: TestName -- ^ test name
  -> FilePath -- ^ path to the «golden» file (the file that contains correct output)
  -> FilePath -- ^ path to the output file
  -> IO () -- ^ action that creates the output file
  -> TestTree -- ^ the test verifies that the output file contents is the same as the golden file contents
goldenVsFile :: TestName -> TestName -> TestName -> IO () -> TestTree
goldenVsFile TestName
name TestName
ref TestName
new IO ()
act =
  TestName
-> IO ByteString
-> IO ByteString
-> (ByteString -> ByteString -> IO (Maybe TestName))
-> (ByteString -> IO ())
-> IO ()
-> TestTree
forall a.
TestName
-> IO a
-> IO a
-> (a -> a -> IO (Maybe TestName))
-> (a -> IO ())
-> IO ()
-> TestTree
goldenTest2
    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
    IO ()
del
  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 TestName
"Files '%s' and '%s' differ" TestName
ref TestName
new
  upd :: ByteString -> IO ()
upd = TestName -> ByteString -> IO ()
createDirectoriesAndWriteFile TestName
ref
  del :: IO ()
del = TestName -> IO ()
removeFile TestName
new

-- | Compare a given string against the golden file's contents.
goldenVsString
  :: TestName -- ^ test name
  -> FilePath -- ^ path to the «golden» file (the file that contains correct output)
  -> IO LBS.ByteString -- ^ action that returns a string
  -> TestTree -- ^ the test verifies that the returned string is the same as the golden file contents
goldenVsString :: TestName -> TestName -> IO ByteString -> TestTree
goldenVsString TestName
name TestName
ref 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 ->
  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 ByteString
x 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 TestName
"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 TestName
e a
x 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

-- | Same as 'goldenVsFile', but invokes an external diff command.
--
-- See the notes at the top of this module regarding linking with
-- @-threaded@ and Windows-specific issues.
goldenVsFileDiff
  :: TestName -- ^ test name
  -> (FilePath -> FilePath -> [String])
    -- ^ function that constructs the command line to invoke the diff
    -- command.
    --
    -- E.g.
    --
    -- >\ref new -> ["diff", "-u", ref, new]
  -> FilePath -- ^ path to the golden file
  -> FilePath -- ^ path to the output file
  -> IO ()    -- ^ action that produces the output file
  -> TestTree
goldenVsFileDiff :: TestName
-> (TestName -> TestName -> [TestName])
-> TestName
-> TestName
-> IO ()
-> TestTree
goldenVsFileDiff TestName
name TestName -> TestName -> [TestName]
cmdf TestName
ref TestName
new 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 ->
  TestName
-> IO ()
-> IO ()
-> (() -> () -> IO (Maybe TestName))
-> (() -> IO ())
-> IO ()
-> TestTree
forall a.
TestName
-> IO a
-> IO a
-> (a -> a -> IO (Maybe TestName))
-> (a -> IO ())
-> IO ()
-> TestTree
goldenTest2
    TestName
name
    (TestName -> IO ()
throwIfDoesNotExist TestName
ref)
    IO ()
act
    (\()
_ ()
_ -> [TestName] -> SizeCutoff -> IO (Maybe TestName)
runDiff (TestName -> TestName -> [TestName]
cmdf TestName
ref TestName
new) SizeCutoff
sizeCutoff)
    () -> IO ()
forall p. p -> IO ()
upd
    IO ()
del
  where
  upd :: p -> IO ()
upd p
_ = 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
  del :: IO ()
del = TestName -> IO ()
removeFile TestName
new

-- If the golden file doesn't exist, throw an isDoesNotExistError that
-- runGolden will handle by creating the golden file before proceeding.
-- See #32.
throwIfDoesNotExist :: FilePath -> IO ()
throwIfDoesNotExist :: TestName -> IO ()
throwIfDoesNotExist TestName
ref = do
  Bool
exists <- TestName -> IO Bool
doesFileExist TestName
ref
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
exists (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ IOError -> IO ()
forall a. IOError -> IO a
ioError (IOError -> IO ()) -> IOError -> IO ()
forall a b. (a -> b) -> a -> b
$
    TestName -> Errno -> Maybe Handle -> Maybe TestName -> IOError
errnoToIOError TestName
"goldenVsFileDiff" Errno
eNOENT Maybe Handle
forall a. Maybe a
Nothing Maybe TestName
forall a. Maybe a
Nothing

-- | Same as 'goldenVsString', but invokes an external diff command.
--
-- See the notes at the top of this module regarding linking with
-- @-threaded@ and Windows-specific issues.
goldenVsStringDiff
  :: TestName -- ^ test name
  -> (FilePath -> FilePath -> [String])
    -- ^ function that constructs the command line to invoke the diff
    -- command.
    --
    -- E.g.
    --
    -- >\ref new -> ["diff", "-u", ref, new]
  -> FilePath -- ^ path to the golden file
  -> IO LBS.ByteString -- ^ action that returns a string
  -> TestTree
goldenVsStringDiff :: TestName
-> (TestName -> TestName -> [TestName])
-> TestName
-> IO ByteString
-> TestTree
goldenVsStringDiff TestName
name TestName -> TestName -> [TestName]
cmdf TestName
ref 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 ->
  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
<.> TestName
"actual"
  cmp :: SizeCutoff -> p -> ByteString -> IO (Maybe TestName)
cmp SizeCutoff
sizeCutoff p
_ 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
$ \TestName
tmpFile Handle
tmpHandle -> do

    -- Write act output to temporary ("new") file
    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
    Maybe TestName
diff_result :: Maybe String <- [TestName] -> SizeCutoff -> IO (Maybe TestName)
runDiff [TestName]
cmd SizeCutoff
sizeCutoff

    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
$ ((TestName -> TestName) -> Maybe TestName -> Maybe TestName)
-> Maybe TestName -> (TestName -> TestName) -> Maybe TestName
forall a b c. (a -> b -> c) -> b -> a -> c
flip (TestName -> TestName) -> Maybe TestName -> Maybe TestName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe TestName
diff_result ((TestName -> TestName) -> Maybe TestName)
-> (TestName -> TestName) -> Maybe TestName
forall a b. (a -> b) -> a -> b
$ \TestName
diff ->
      TestName -> TestName -> TestName -> TestName
forall r. PrintfType r => TestName -> r
printf TestName
"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
<> TestName
diff

  upd :: ByteString -> IO ()
upd = TestName -> ByteString -> IO ()
createDirectoriesAndWriteFile TestName
ref

truncateLargeOutput
  :: SizeCutoff
  -> LBS.ByteString
  -> LBS.ByteString
truncateLargeOutput :: SizeCutoff -> ByteString -> ByteString
truncateLargeOutput (SizeCutoff Int64
n) 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
<> ByteString
"<truncated>" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<>
      ByteString
"\nUse --accept or increase --size-cutoff to see full output."

-- | Like 'writeFile', but uses binary mode. (Needed only when you work
-- with 'String'.)
writeBinaryFile :: FilePath -> String -> IO ()
writeBinaryFile :: TestName -> TestName -> IO ()
writeBinaryFile TestName
f TestName
txt = TestName -> IOMode -> (Handle -> IO ()) -> IO ()
forall r. TestName -> IOMode -> (Handle -> IO r) -> IO r
withBinaryFile TestName
f IOMode
WriteMode (\Handle
hdl -> Handle -> TestName -> IO ()
hPutStr Handle
hdl TestName
txt)

-- | Find all files in the given directory and its subdirectories that have
-- the given extensions.
--
-- It is typically used to find all test files and produce a golden test
-- per test file.
--
-- The returned paths use forward slashes to separate path components,
-- even on Windows. Thus if the file name ends up in a golden file, it
-- will not differ when run on another platform.
--
-- The semantics of extensions is the same as in 'takeExtension'. In
-- particular, non-empty extensions should have the form @".ext"@.
--
-- This function may throw any exception that 'getDirectoryContents' may
-- throw.
--
-- It doesn't do anything special to handle symlinks (in particular, it
-- probably won't work on symlink loops).
--
-- Nor is it optimized to work with huge directory trees (you'd probably
-- want to use some form of coroutines for that).
findByExtension
  :: [FilePath] -- ^ extensions
  -> FilePath -- ^ directory
  -> IO [FilePath] -- ^ paths
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
    [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
".", TestName
".."])) [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
$ \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
      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 []

-- | Like 'LBS.writeFile', but also create parent directories if they are
-- missing.
createDirectoriesAndWriteFile
  :: FilePath
  -> LBS.ByteString
  -> IO ()
createDirectoriesAndWriteFile :: TestName -> ByteString -> IO ()
createDirectoriesAndWriteFile TestName
path ByteString
bs = do
  let dir :: TestName
dir = TestName -> TestName
takeDirectory TestName
path
  Bool -> TestName -> IO ()
createDirectoryIfMissing
    Bool
True -- create parents too
    TestName
dir
  TestName -> ByteString -> IO ()
LBS.writeFile TestName
path ByteString
bs

-- | Force the evaluation of a lazily-produced bytestring.
--
-- This is important to close the file handles.
--
-- See <https://ro-che.info/articles/2015-05-28-force-list>.
forceLbs :: LBS.ByteString -> ()
forceLbs :: ByteString -> ()
forceLbs = (Word8 -> () -> ()) -> () -> ByteString -> ()
forall a. (Word8 -> a -> a) -> a -> ByteString -> a
LBS.foldr Word8 -> () -> ()
seq ()

readFileStrict :: FilePath -> IO LBS.ByteString
readFileStrict :: TestName -> IO ByteString
readFileStrict 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

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

runDiff
  :: [String] -- ^ the diff command
  -> SizeCutoff
  -> IO (Maybe String)
runDiff :: [TestName] -> SizeCutoff -> IO (Maybe TestName)
runDiff [TestName]
cmd SizeCutoff
sizeCutoff =
  case [TestName]
cmd of
    [] -> ErrorCall -> IO (Maybe TestName)
forall e a. Exception e => e -> IO a
throwIO (ErrorCall -> IO (Maybe TestName))
-> ErrorCall -> IO (Maybe TestName)
forall a b. (a -> b) -> a -> b
$ TestName -> ErrorCall
ErrorCall TestName
"tasty-golden: empty diff command"
    TestName
prog : [TestName]
args -> do
      let
        procConf :: ProcessConfig () () ()
procConf =
          StreamSpec 'STInput ()
-> ProcessConfig () () () -> ProcessConfig () () ()
forall stdin stdin0 stdout stderr.
StreamSpec 'STInput stdin
-> ProcessConfig stdin0 stdout stderr
-> ProcessConfig stdin stdout stderr
PT.setStdin StreamSpec 'STInput ()
forall (anyStreamType :: StreamType). StreamSpec anyStreamType ()
PT.closed
          (ProcessConfig () () () -> ProcessConfig () () ())
-> (ProcessConfig () () () -> ProcessConfig () () ())
-> ProcessConfig () () ()
-> ProcessConfig () () ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StreamSpec 'STOutput ()
-> ProcessConfig () () () -> ProcessConfig () () ()
forall stderr stdin stdout stderr0.
StreamSpec 'STOutput stderr
-> ProcessConfig stdin stdout stderr0
-> ProcessConfig stdin stdout stderr
PT.setStderr StreamSpec 'STOutput ()
forall (anyStreamType :: StreamType). StreamSpec anyStreamType ()
PT.inherit
          (ProcessConfig () () () -> ProcessConfig () () ())
-> ProcessConfig () () () -> ProcessConfig () () ()
forall a b. (a -> b) -> a -> b
$ TestName -> [TestName] -> ProcessConfig () () ()
PT.proc TestName
prog [TestName]
args

      (ExitCode
exitCode, ByteString
out) <- ProcessConfig () () () -> IO (ExitCode, ByteString)
forall (m :: * -> *) stdin stdoutIgnored stderr.
MonadIO m =>
ProcessConfig stdin stdoutIgnored stderr
-> m (ExitCode, ByteString)
PT.readProcessStdout ProcessConfig () () ()
procConf
      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
exitCode of
        ExitCode
ExitSuccess -> Maybe TestName
forall a. Maybe a
Nothing
        ExitCode
_ -> 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