module Test.Syd.Def.Golden
  ( module Test.Syd.Def.Golden,
    GoldenTest (..),
  )
where
import Data.ByteString (ByteString)
import qualified Data.ByteString as SB
import qualified Data.ByteString.Builder as SBB
import qualified Data.ByteString.Lazy as LB
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Encoding as TE
import Path
import Path.IO
import Test.Syd.Expectation
import Test.Syd.Run
import Text.Show.Pretty
pureGoldenByteStringFile :: FilePath -> ByteString -> GoldenTest ByteString
pureGoldenByteStringFile :: String -> ByteString -> GoldenTest ByteString
pureGoldenByteStringFile String
fp ByteString
bs = String -> IO ByteString -> GoldenTest ByteString
goldenByteStringFile String
fp (forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
bs)
goldenByteStringFile :: FilePath -> IO ByteString -> GoldenTest ByteString
goldenByteStringFile :: String -> IO ByteString -> GoldenTest ByteString
goldenByteStringFile String
fp IO ByteString
produceBS =
  GoldenTest
    { goldenTestRead :: IO (Maybe ByteString)
goldenTestRead = do
        Path Abs File
resolvedFile <- forall (m :: * -> *). MonadIO m => String -> m (Path Abs File)
resolveFile' String
fp
        forall (m :: * -> *) a.
(MonadIO m, MonadCatch m) =>
m a -> m (Maybe a)
forgivingAbsence forall a b. (a -> b) -> a -> b
$ String -> IO ByteString
SB.readFile forall a b. (a -> b) -> a -> b
$ Path Abs File -> String
fromAbsFile Path Abs File
resolvedFile,
      goldenTestProduce :: IO ByteString
goldenTestProduce = IO ByteString
produceBS,
      goldenTestWrite :: ByteString -> IO ()
goldenTestWrite = \ByteString
actual -> do
        Path Abs File
resolvedFile <- forall (m :: * -> *). MonadIO m => String -> m (Path Abs File)
resolveFile' String
fp
        forall (m :: * -> *) b. MonadIO m => Path b Dir -> m ()
ensureDir forall a b. (a -> b) -> a -> b
$ forall b t. Path b t -> Path b Dir
parent Path Abs File
resolvedFile
        String -> ByteString -> IO ()
SB.writeFile (Path Abs File -> String
fromAbsFile Path Abs File
resolvedFile) ByteString
actual,
      goldenTestCompare :: ByteString -> ByteString -> Maybe Assertion
goldenTestCompare = \ByteString
actual ByteString
expected ->
        if ByteString
actual forall a. Eq a => a -> a -> Bool
== ByteString
expected
          then forall a. Maybe a
Nothing
          else forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Assertion -> String -> Assertion
Context (ByteString -> ByteString -> Assertion
bytestringsNotEqualButShouldHaveBeenEqual ByteString
actual ByteString
expected) (String -> String
goldenContext String
fp)
    }
pureGoldenLazyByteStringFile :: FilePath -> LB.ByteString -> GoldenTest LB.ByteString
pureGoldenLazyByteStringFile :: String -> ByteString -> GoldenTest ByteString
pureGoldenLazyByteStringFile String
fp ByteString
bs = String -> IO ByteString -> GoldenTest ByteString
goldenLazyByteStringFile String
fp (forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
bs)
goldenLazyByteStringFile :: FilePath -> IO LB.ByteString -> GoldenTest LB.ByteString
goldenLazyByteStringFile :: String -> IO ByteString -> GoldenTest ByteString
goldenLazyByteStringFile String
fp IO ByteString
produceBS =
  GoldenTest
    { goldenTestRead :: IO (Maybe ByteString)
goldenTestRead = do
        Path Abs File
resolvedFile <- forall (m :: * -> *). MonadIO m => String -> m (Path Abs File)
resolveFile' String
fp
        forall (m :: * -> *) a.
(MonadIO m, MonadCatch m) =>
m a -> m (Maybe a)
forgivingAbsence forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> ByteString
LB.fromStrict forall a b. (a -> b) -> a -> b
$ String -> IO ByteString
SB.readFile forall a b. (a -> b) -> a -> b
$ Path Abs File -> String
fromAbsFile Path Abs File
resolvedFile,
      goldenTestProduce :: IO ByteString
goldenTestProduce = IO ByteString
produceBS,
      goldenTestWrite :: ByteString -> IO ()
goldenTestWrite = \ByteString
actual -> do
        Path Abs File
resolvedFile <- forall (m :: * -> *). MonadIO m => String -> m (Path Abs File)
resolveFile' String
fp
        forall (m :: * -> *) b. MonadIO m => Path b Dir -> m ()
ensureDir forall a b. (a -> b) -> a -> b
$ forall b t. Path b t -> Path b Dir
parent Path Abs File
resolvedFile
        String -> ByteString -> IO ()
SB.writeFile (Path Abs File -> String
fromAbsFile Path Abs File
resolvedFile) (ByteString -> ByteString
LB.toStrict ByteString
actual),
      goldenTestCompare :: ByteString -> ByteString -> Maybe Assertion
goldenTestCompare = \ByteString
actual ByteString
expected ->
        let actualBS :: ByteString
actualBS = ByteString -> ByteString
LB.toStrict ByteString
actual
            expectedBS :: ByteString
expectedBS = ByteString -> ByteString
LB.toStrict ByteString
expected
         in if ByteString
actualBS forall a. Eq a => a -> a -> Bool
== ByteString
expectedBS
              then forall a. Maybe a
Nothing
              else forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Assertion -> String -> Assertion
Context (ByteString -> ByteString -> Assertion
bytestringsNotEqualButShouldHaveBeenEqual ByteString
actualBS ByteString
expectedBS) (String -> String
goldenContext String
fp)
    }
pureGoldenByteStringBuilderFile :: FilePath -> SBB.Builder -> GoldenTest SBB.Builder
pureGoldenByteStringBuilderFile :: String -> Builder -> GoldenTest Builder
pureGoldenByteStringBuilderFile String
fp Builder
bs = String -> IO Builder -> GoldenTest Builder
goldenByteStringBuilderFile String
fp (forall (f :: * -> *) a. Applicative f => a -> f a
pure Builder
bs)
goldenByteStringBuilderFile :: FilePath -> IO SBB.Builder -> GoldenTest SBB.Builder
goldenByteStringBuilderFile :: String -> IO Builder -> GoldenTest Builder
goldenByteStringBuilderFile String
fp IO Builder
produceBS =
  GoldenTest
    { goldenTestRead :: IO (Maybe Builder)
goldenTestRead = do
        Path Abs File
resolvedFile <- forall (m :: * -> *). MonadIO m => String -> m (Path Abs File)
resolveFile' String
fp
        forall (m :: * -> *) a.
(MonadIO m, MonadCatch m) =>
m a -> m (Maybe a)
forgivingAbsence forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Builder
SBB.byteString forall a b. (a -> b) -> a -> b
$ String -> IO ByteString
SB.readFile forall a b. (a -> b) -> a -> b
$ Path Abs File -> String
fromAbsFile Path Abs File
resolvedFile,
      goldenTestProduce :: IO Builder
goldenTestProduce = IO Builder
produceBS,
      goldenTestWrite :: Builder -> IO ()
goldenTestWrite = \Builder
actual -> do
        Path Abs File
resolvedFile <- forall (m :: * -> *). MonadIO m => String -> m (Path Abs File)
resolveFile' String
fp
        forall (m :: * -> *) b. MonadIO m => Path b Dir -> m ()
ensureDir forall a b. (a -> b) -> a -> b
$ forall b t. Path b t -> Path b Dir
parent Path Abs File
resolvedFile
        String -> ByteString -> IO ()
SB.writeFile (Path Abs File -> String
fromAbsFile Path Abs File
resolvedFile) (ByteString -> ByteString
LB.toStrict (Builder -> ByteString
SBB.toLazyByteString Builder
actual)),
      goldenTestCompare :: Builder -> Builder -> Maybe Assertion
goldenTestCompare = \Builder
actual Builder
expected ->
        let actualBS :: ByteString
actualBS = ByteString -> ByteString
LB.toStrict (Builder -> ByteString
SBB.toLazyByteString Builder
actual)
            expectedBS :: ByteString
expectedBS = ByteString -> ByteString
LB.toStrict (Builder -> ByteString
SBB.toLazyByteString Builder
expected)
         in if ByteString
actualBS forall a. Eq a => a -> a -> Bool
== ByteString
expectedBS
              then forall a. Maybe a
Nothing
              else forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Assertion -> String -> Assertion
Context (ByteString -> ByteString -> Assertion
bytestringsNotEqualButShouldHaveBeenEqual ByteString
actualBS ByteString
expectedBS) (String -> String
goldenContext String
fp)
    }
pureGoldenTextFile :: FilePath -> Text -> GoldenTest Text
pureGoldenTextFile :: String -> Text -> GoldenTest Text
pureGoldenTextFile String
fp Text
bs = String -> IO Text -> GoldenTest Text
goldenTextFile String
fp (forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
bs)
goldenTextFile :: FilePath -> IO Text -> GoldenTest Text
goldenTextFile :: String -> IO Text -> GoldenTest Text
goldenTextFile String
fp IO Text
produceBS =
  GoldenTest
    { goldenTestRead :: IO (Maybe Text)
goldenTestRead = do
        Path Abs File
resolvedFile <- forall (m :: * -> *). MonadIO m => String -> m (Path Abs File)
resolveFile' String
fp
        forall (m :: * -> *) a.
(MonadIO m, MonadCatch m) =>
m a -> m (Maybe a)
forgivingAbsence forall a b. (a -> b) -> a -> b
$ ByteString -> Text
TE.decodeUtf8 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO ByteString
SB.readFile (Path Abs File -> String
fromAbsFile Path Abs File
resolvedFile),
      goldenTestProduce :: IO Text
goldenTestProduce = IO Text
produceBS,
      goldenTestWrite :: Text -> IO ()
goldenTestWrite = \Text
actual -> do
        Path Abs File
resolvedFile <- forall (m :: * -> *). MonadIO m => String -> m (Path Abs File)
resolveFile' String
fp
        forall (m :: * -> *) b. MonadIO m => Path b Dir -> m ()
ensureDir forall a b. (a -> b) -> a -> b
$ forall b t. Path b t -> Path b Dir
parent Path Abs File
resolvedFile
        String -> ByteString -> IO ()
SB.writeFile (Path Abs File -> String
fromAbsFile Path Abs File
resolvedFile) (Text -> ByteString
TE.encodeUtf8 Text
actual),
      goldenTestCompare :: Text -> Text -> Maybe Assertion
goldenTestCompare = \Text
actual Text
expected ->
        if Text
actual forall a. Eq a => a -> a -> Bool
== Text
expected
          then forall a. Maybe a
Nothing
          else forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Assertion -> String -> Assertion
Context (Text -> Text -> Assertion
textsNotEqualButShouldHaveBeenEqual Text
actual Text
expected) (String -> String
goldenContext String
fp)
    }
pureGoldenStringFile :: FilePath -> String -> GoldenTest String
pureGoldenStringFile :: String -> String -> GoldenTest String
pureGoldenStringFile String
fp String
bs = String -> IO String -> GoldenTest String
goldenStringFile String
fp (forall (f :: * -> *) a. Applicative f => a -> f a
pure String
bs)
goldenStringFile :: FilePath -> IO String -> GoldenTest String
goldenStringFile :: String -> IO String -> GoldenTest String
goldenStringFile String
fp IO String
produceBS =
  GoldenTest
    { goldenTestRead :: IO (Maybe String)
goldenTestRead = do
        Path Abs File
resolvedFile <- forall (m :: * -> *). MonadIO m => String -> m (Path Abs File)
resolveFile' String
fp
        forall (m :: * -> *) a.
(MonadIO m, MonadCatch m) =>
m a -> m (Maybe a)
forgivingAbsence forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> String
T.unpack forall a b. (a -> b) -> a -> b
$ ByteString -> Text
TE.decodeUtf8 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO ByteString
SB.readFile (Path Abs File -> String
fromAbsFile Path Abs File
resolvedFile),
      goldenTestProduce :: IO String
goldenTestProduce = IO String
produceBS,
      goldenTestWrite :: String -> IO ()
goldenTestWrite = \String
actual -> do
        Path Abs File
resolvedFile <- forall (m :: * -> *). MonadIO m => String -> m (Path Abs File)
resolveFile' String
fp
        forall (m :: * -> *) b. MonadIO m => Path b Dir -> m ()
ensureDir forall a b. (a -> b) -> a -> b
$ forall b t. Path b t -> Path b Dir
parent Path Abs File
resolvedFile
        String -> ByteString -> IO ()
SB.writeFile (Path Abs File -> String
fromAbsFile Path Abs File
resolvedFile) (Text -> ByteString
TE.encodeUtf8 (String -> Text
T.pack String
actual)),
      goldenTestCompare :: String -> String -> Maybe Assertion
goldenTestCompare = \String
actual String
expected ->
        if String
actual forall a. Eq a => a -> a -> Bool
== String
expected
          then forall a. Maybe a
Nothing
          else forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Assertion -> String -> Assertion
Context (String -> String -> Assertion
stringsNotEqualButShouldHaveBeenEqual String
actual String
expected) (String -> String
goldenContext String
fp)
    }
goldenShowInstance :: Show a => FilePath -> a -> GoldenTest String
goldenShowInstance :: forall a. Show a => String -> a -> GoldenTest String
goldenShowInstance String
fp a
a = String -> String -> GoldenTest String
pureGoldenStringFile String
fp (forall a. Show a => a -> String
show a
a)
goldenPrettyShowInstance :: Show a => FilePath -> a -> GoldenTest String
goldenPrettyShowInstance :: forall a. Show a => String -> a -> GoldenTest String
goldenPrettyShowInstance String
fp a
a = String -> String -> GoldenTest String
pureGoldenStringFile String
fp (forall a. Show a => a -> String
ppShow a
a)
goldenContext :: FilePath -> String
goldenContext :: String -> String
goldenContext String
fp = String
"The golden results are in: " forall a. Semigroup a => a -> a -> a
<> String
fp