tasty-golden-2.3.3.2/Test/0000755000000000000000000000000013211262541013373 5ustar0000000000000000tasty-golden-2.3.3.2/Test/Tasty/0000755000000000000000000000000013644517260014512 5ustar0000000000000000tasty-golden-2.3.3.2/Test/Tasty/Golden/0000755000000000000000000000000013644517260015722 5ustar0000000000000000tasty-golden-2.3.3.2/example/0000755000000000000000000000000013651637304014122 5ustar0000000000000000tasty-golden-2.3.3.2/example/golden/0000755000000000000000000000000013623564127015373 5ustar0000000000000000tasty-golden-2.3.3.2/example/golden/fail/0000755000000000000000000000000013623745465016314 5ustar0000000000000000tasty-golden-2.3.3.2/example/golden/success/0000755000000000000000000000000013623745465017051 5ustar0000000000000000tasty-golden-2.3.3.2/tests/0000755000000000000000000000000013623745465013640 5ustar0000000000000000tasty-golden-2.3.3.2/tests/golden/0000755000000000000000000000000013623745465015110 5ustar0000000000000000tasty-golden-2.3.3.2/Test/Tasty/Golden.hs0000644000000000000000000002300513644517260016256 0ustar0000000000000000{- | To get started with golden testing and this library, see . This module provides a simplified interface. If you want more, see "Test.Tasty.Golden.Advanced". Note about filenames. They 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). Note about 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. -} {-# 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 -- | 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 name ref new act = goldenTest name (readFileStrict ref) (act >> readFileStrict new) cmp upd where cmp = simpleCmp $ printf "Files '%s' and '%s' differ" ref new upd = createDirectoriesAndWriteFile ref -- | 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 name ref act = askOption $ \sizeCutoff -> goldenTest name (readFileStrict ref) act (cmp sizeCutoff) upd where cmp sizeCutoff x y = simpleCmp msg x y where msg = printf "Test output was different from '%s'. It was:\n" ref <> unpackUtf8 (truncateLargeOutput sizeCutoff y) upd = createDirectoriesAndWriteFile ref simpleCmp :: Eq a => String -> a -> a -> IO (Maybe String) simpleCmp e x y = return $ if x == y then Nothing else Just e -- | Same as 'goldenVsFile', but invokes an external diff command. 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 name cmdf ref new act = askOption $ \sizeCutoff -> goldenTest name (return ()) act (cmp sizeCutoff) upd where cmd = cmdf ref new cmp sizeCutoff _ _ | null cmd = error "goldenVsFileDiff: empty command line" | otherwise = do (_, Just sout, _, pid) <- createProcess (proc (head cmd) (tail cmd)) { std_out = CreatePipe } -- strictly read the whole output, so that the process can terminate out <- hGetContentsStrict sout r <- waitForProcess pid return $ case r of ExitSuccess -> Nothing _ -> Just . unpackUtf8 . truncateLargeOutput sizeCutoff $ out upd _ = readFileStrict new >>= createDirectoriesAndWriteFile ref -- | Same as 'goldenVsString', but invokes an external diff command. 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 name cmdf ref act = askOption $ \sizeCutoff -> goldenTest name (readFileStrict ref) (act) (cmp sizeCutoff) upd where template = takeBaseName ref <.> "actual" cmp sizeCutoff _ actBS = withSystemTempFile template $ \tmpFile tmpHandle -> do -- Write act output to temporary ("new") file LBS.hPut tmpHandle actBS >> hFlush tmpHandle let cmd = cmdf ref tmpFile when (null cmd) $ error "goldenVsFileDiff: empty command line" (_, Just sout, _, pid) <- createProcess (proc (head cmd) (tail cmd)) { std_out = CreatePipe } -- strictly read the whole output, so that the process can terminate out <- hGetContentsStrict sout r <- waitForProcess pid return $ case r of ExitSuccess -> Nothing _ -> Just (printf "Test output was different from '%s'. Output of %s:\n" ref (show cmd) <> unpackUtf8 (truncateLargeOutput sizeCutoff out)) upd = createDirectoriesAndWriteFile ref truncateLargeOutput :: SizeCutoff -> LBS.ByteString -> LBS.ByteString truncateLargeOutput (SizeCutoff n) str = if LBS.length str <= n then str else LBS.take n str <> "" <> "\nUse --accept or increase --size-cutoff to see full output." -- | Like 'writeFile', but uses binary mode. writeBinaryFile :: FilePath -> String -> IO () writeBinaryFile f txt = withBinaryFile f WriteMode (\hdl -> hPutStr hdl 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 extsList = go where exts = Set.fromList extsList go dir = do allEntries <- getDirectoryContents dir let entries = filter (not . (`elem` [".", ".."])) allEntries liftM concat $ forM entries $ \e -> do let path = dir ++ "/" ++ e isDir <- doesDirectoryExist path if isDir then go path else return $ if takeExtension path `Set.member` exts then [path] else [] -- | Like 'BS.writeFile', but also create parent directories if they are -- missing. createDirectoriesAndWriteFile :: FilePath -> LBS.ByteString -> IO () createDirectoriesAndWriteFile path bs = do let dir = takeDirectory path createDirectoryIfMissing True -- create parents too dir LBS.writeFile path bs -- | Force the evaluation of a lazily-produced bytestring. -- -- This is important to close the file handles. -- -- See . forceLbs :: LBS.ByteString -> () forceLbs = LBS.foldr seq () readFileStrict :: FilePath -> IO LBS.ByteString readFileStrict path = do s <- LBS.readFile path evaluate $ forceLbs s return s hGetContentsStrict :: Handle -> IO LBS.ByteString hGetContentsStrict h = do hSetBinaryMode h True s <- LBS.hGetContents h evaluate $ forceLbs s return s unpackUtf8 :: LBS.ByteString -> String unpackUtf8 = LT.unpack . LT.decodeUtf8 tasty-golden-2.3.3.2/Test/Tasty/Golden/Advanced.hs0000644000000000000000000000211213211262541017744 0ustar0000000000000000{-# LANGUAGE RankNTypes #-} module Test.Tasty.Golden.Advanced ( -- * The main function goldenTest ) where import Test.Tasty.Providers import Test.Tasty.Golden.Internal -- | A very general testing function. goldenTest :: TestName -- ^ test name -> (IO a) -- ^ get the golden correct value -- -- Note that this action may be followed by the update function call. -- -- Therefore, this action *should avoid* reading the file lazily; -- otherwise, the file may remain half-open and the update action will -- fail. -> (IO a) -- ^ get the tested value -> (a -> a -> IO (Maybe String)) -- ^ comparison function. -- -- If two values are the same, it should return 'Nothing'. If they are -- different, it should return an error that will be printed to the user. -- First argument is the golden value. -- -- The function may use 'IO', for example, to launch an external @diff@ -- command. -> (a -> IO ()) -- ^ update the golden file -> TestTree goldenTest t golden test cmp upd = singleTest t $ Golden golden test cmp upd tasty-golden-2.3.3.2/Test/Tasty/Golden/Manage.hs0000644000000000000000000000212313313253475017442 0ustar0000000000000000{-# LANGUAGE GeneralizedNewtypeDeriving, PatternGuards, DeriveDataTypeable #-} -- | Previously, accepting tests (by the @--accept@ flag) was done by this -- module, and there was an ingredient to handle that mode. -- -- Now it's done as part of a normal test run. When the `--accept` flag is -- given, it makes golden tests to update the files whenever there is -- a mismatch. So you no longer need this module. It remains only for -- backwards compatibility. module Test.Tasty.Golden.Manage ( -- * Command line helpers defaultMain -- * The ingredient , acceptingTests , AcceptTests(..) ) where import Test.Tasty hiding (defaultMain) import Test.Tasty.Runners import Test.Tasty.Golden.Internal -- | This exists only for backwards compatibility. Use -- 'Test.Tasty.defaultMain' instead. defaultMain :: TestTree -> IO () defaultMain = defaultMainWithIngredients [acceptingTests, listingTests, consoleTestReporter] -- | This exists only for backwards compatibility. You don't need to -- include this anymore. acceptingTests :: Ingredient acceptingTests = TestManager [] $ \_ _ -> Nothing tasty-golden-2.3.3.2/Test/Tasty/Golden/Internal.hs0000644000000000000000000000727213651637235020045 0ustar0000000000000000{-# LANGUAGE RankNTypes, ExistentialQuantification, DeriveDataTypeable, MultiParamTypeClasses, GeneralizedNewtypeDeriving, CPP #-} module Test.Tasty.Golden.Internal where import Control.DeepSeq import Control.Exception import Data.Typeable (Typeable) import Data.Proxy import Data.Int import System.IO.Error (isDoesNotExistError) import Options.Applicative (metavar) import Test.Tasty.Providers import Test.Tasty.Options #if !MIN_VERSION_base(4,11,0) import Data.Monoid ((<>)) #endif -- | See 'goldenTest' for explanation of the fields data Golden = forall a . Golden (IO a) (IO a) (a -> a -> IO (Maybe String)) (a -> IO ()) deriving Typeable -- | This option, when set to 'True', specifies that we should run in the -- «accept tests» mode newtype AcceptTests = AcceptTests Bool deriving (Eq, Ord, Typeable) instance IsOption AcceptTests where defaultValue = AcceptTests False parseValue = fmap AcceptTests . safeReadBool optionName = return "accept" optionHelp = return "Accept current results of golden tests" optionCLParser = flagCLParser Nothing (AcceptTests True) -- | This option, when set to 'True', specifies to error when a file does -- not exist, instead of creating a new file. newtype NoCreateFile = NoCreateFile Bool deriving (Eq, Ord, Typeable) instance IsOption NoCreateFile where defaultValue = NoCreateFile False parseValue = fmap NoCreateFile . safeReadBool optionName = return "no-create" optionHelp = return "Error when golden file does not exist" optionCLParser = flagCLParser Nothing (NoCreateFile True) -- | The size, in bytes, such that the (incorrect) test output is not -- displayed when it exceeds this size. Numeric underscores are accepted -- for readability. -- -- The default value is 1000 (i.e. 1Kb). newtype SizeCutoff = SizeCutoff { getSizeCutoff :: Int64 } deriving (Eq, Ord, Typeable, Num, Real, Enum, Integral) instance IsOption SizeCutoff where defaultValue = 1000 parseValue = fmap SizeCutoff . safeRead . filter (/= '_') optionName = return "size-cutoff" optionHelp = return "hide golden test output if it's larger than n bytes (default: 1000)" optionCLParser = mkOptionCLParser $ metavar "n" instance IsTest Golden where run opts golden _ = runGolden golden opts testOptions = return [ Option (Proxy :: Proxy AcceptTests) , Option (Proxy :: Proxy NoCreateFile) , Option (Proxy :: Proxy SizeCutoff) ] runGolden :: Golden -> OptionSet -> IO Result runGolden (Golden getGolden getTested cmp update) opts = do do mbNew <- try getTested case mbNew of Left e -> do return $ testFailed $ show (e :: SomeException) Right new -> do mbRef <- try getGolden case mbRef of Left e | isDoesNotExistError e -> if noCreate then return $ testFailed "Golden file does not exist; --no-create flag specified" else do update new return $ testPassed "Golden file did not exist; created" | otherwise -> throwIO e Right ref -> do result <- cmp ref new case result of Just _reason | accept -> do -- test failed; accept the new version update new return $ testPassed "Accepted the new version" Just reason -> do -- Make sure that the result is fully evaluated and doesn't depend -- on yet un-read lazy input evaluate . rnf $ reason return $ testFailed reason Nothing -> return $ testPassed "" where AcceptTests accept = lookupOption opts NoCreateFile noCreate = lookupOption opts tasty-golden-2.3.3.2/example/example.hs0000644000000000000000000000275613623745465016132 0ustar0000000000000000import Test.Tasty import Test.Tasty.Golden import System.FilePath import qualified Data.ByteString.Lazy.Char8 as LBS all_numbers, non_square_numbers :: [Int] all_numbers = [1..1000] non_square_numbers = filter (\x -> (round . sqrt . fromIntegral) x ^ 2 /= x) all_numbers all_numbers_str = LBS.pack $ unlines $ map show all_numbers non_square_numbers_str = LBS.pack $ unlines $ map show non_square_numbers diff ref new = ["diff", ref, new] main = defaultMain $ localOption (SizeCutoff 140) $ testGroup "Tests" [ testGroup (if success then "Successful tests" else "Failing tests") $ let dir = "example/golden" if success then "success" else "fail" value = if success then all_numbers_str else non_square_numbers_str in [ let golden = dir "goldenVsFile.golden" actual = dir "goldenVsFile.actual" in goldenVsFile "goldenVsFile" golden actual (createDirectoriesAndWriteFile actual value) , let golden = dir "goldenVsFileDiff.golden" actual = dir "goldenVsFileDiff.actual" in goldenVsFileDiff "goldenVsFileDiff" diff golden actual (createDirectoriesAndWriteFile actual value) , let golden = dir "goldenVsString.golden" in goldenVsString "goldenVsString" golden (return value) , let golden = dir "goldenVsStringDiff.golden" in goldenVsStringDiff "goldenVsStringDiff" diff golden (return value) ] | success <- [True, False] ] tasty-golden-2.3.3.2/tests/test.hs0000644000000000000000000000532113623745465015154 0ustar0000000000000000{-# LANGUAGE CPP #-} import Test.Tasty import Test.Tasty.HUnit import Test.Tasty.Golden import System.IO.Temp import System.FilePath import System.Directory import System.Process import Data.List (sort) touch f = writeFile f "" diff ref new = ["diff", "-u", ref, new] main = defaultMain $ testGroup "Tests" [ testCase "findByExtension" $ withSystemTempDirectory "golden-test" $ \basedir -> do createDirectory (basedir "d1") createDirectory (basedir "d1" "d2") touch (basedir "f1.c") touch (basedir "f2.h") touch (basedir "f2.exe") touch (basedir "d1" "g1.c") touch (basedir "d1" "d2" "h1.c") touch (basedir "d1" "d2" "h1.exe") touch (basedir "d1" "d2" "h1") files <- findByExtension [".c", ".h"] basedir sort files @?= (sort . map (basedir )) ["d1/d2/h1.c","d1/g1.c","f1.c","f2.h"] #ifdef BUILD_EXAMPLE , withResource (do tmp0 <- getCanonicalTemporaryDirectory tmp <- createTempDirectory tmp0 "golden-test" callProcess "cp" ["-r", "example", tmp] return tmp ) ({-removeDirectoryRecursive-}const $ return ()) $ \tmpIO -> testGroup "Example test suite" [ goldenVsFileDiff "before --accept" diff "tests/golden/before-accept.golden" "tests/golden/before-accept.actual" (do tmp <- tmpIO our <- getCurrentDirectory -- The sed invocation is used to get rid of the differences -- caused by random file names in goldenVsStringDiff and by the -- timings. -- -- NB: cannot use multiline literals because of CPP. callCommand ("cd " ++ tmp ++ " && example | " ++ "sed -Ee 's/[[:digit:]-]+\\.actual/.actual/g; s/ \\([[:digit:].]+s\\)//' > " ++ our"tests/golden/before-accept.actual || true") ) , after AllFinish "/before --accept/" $ goldenVsFileDiff "with --accept" diff "tests/golden/with-accept.golden" "tests/golden/with-accept.actual" (do tmp <- tmpIO our <- getCurrentDirectory callCommand ("cd " ++ tmp ++ " && example --accept | sed -Ee 's/ \\([[:digit:].]+s\\)//' > " ++ our "tests/golden/with-accept.actual") ) , after AllFinish "/with --accept/" $ goldenVsFileDiff "after --accept" diff "tests/golden/after-accept.golden" "tests/golden/after-accept.actual" (do tmp <- tmpIO our <- getCurrentDirectory callCommand ("cd " ++ tmp ++ " && example | sed -Ee 's/ \\([[:digit:].]+s\\)//' > " ++ our"tests/golden/after-accept.actual") ) ] #endif ] tasty-golden-2.3.3.2/LICENSE0000644000000000000000000000204313211262541013460 0ustar0000000000000000Copyright (c) 2012 Roman Cheplyaka Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the "Software"), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. tasty-golden-2.3.3.2/Setup.hs0000644000000000000000000000005613211262541014111 0ustar0000000000000000import Distribution.Simple main = defaultMain tasty-golden-2.3.3.2/tasty-golden.cabal0000644000000000000000000000520213651640106016056 0ustar0000000000000000name: tasty-golden version: 2.3.3.2 synopsis: Golden tests support for tasty description: This package provides support for «golden testing». A golden test is an IO action that writes its result to a file. To pass the test, this output file should be identical to the corresponding «golden» file, which contains the correct result for the test. To get started with golden testing and this library, see . license: MIT license-file: LICENSE Homepage: https://github.com/feuerbach/tasty-golden Bug-reports: https://github.com/feuerbach/tasty-golden/issues author: Roman Cheplyaka maintainer: Roman Cheplyaka -- copyright: category: Testing build-type: Simple cabal-version: >=1.14 extra-source-files: CHANGELOG.md example/golden/fail/*.golden example/golden/success/*.golden tests/golden/*.golden Tested-With: GHC ==7.8.4 || ==7.10.3 || ==8.0.2 || ==8.2.2 || ==8.4.4 || ==8.6.5 || ==8.8.2 Source-repository head type: git location: git://github.com/feuerbach/tasty-golden.git library Default-language: Haskell2010 exposed-modules: Test.Tasty.Golden Test.Tasty.Golden.Advanced Test.Tasty.Golden.Manage other-modules: Test.Tasty.Golden.Internal ghc-options: -Wall build-depends: base >= 4.7, tasty >= 1.0.1, bytestring >= 0.9.2.1, process, mtl, optparse-applicative >= 0.3.1, filepath, temporary, tagged, deepseq, containers, directory, async, text Test-suite test Default-language: Haskell2010 Type: exitcode-stdio-1.0 Hs-source-dirs: tests Main-is: test.hs Build-depends: base >= 4 && < 5 , tasty >= 1.2 , tasty-hunit , tasty-golden , filepath , directory , process , temporary if (flag(build-example)) cpp-options: -DBUILD_EXAMPLE flag build-example default: False manual: True -- An example test suite used for testing. -- Tries to exercise all ways to create golden tests. -- Not built by default. To build it, turn on the build-example flag: -- -- stack build :example --flag tasty-golden:build-example executable example Default-language: Haskell2010 Hs-source-dirs: example Main-is: example.hs if (! flag(build-example)) buildable: False Build-depends: base >= 4 && < 5 , filepath , bytestring , tasty , tasty-golden tasty-golden-2.3.3.2/CHANGELOG.md0000644000000000000000000000622313651640325014300 0ustar0000000000000000Changes ======= Version 2.3.3.2 --------------- * Fix a bug where the `TASTY_SIZE_CUTOFF` env. variable would be ignored Version 2.3.3.1 --------------- * Fix a bug with UTF-8 output Version 2.3.3 ------------- * Expose `createDirectoriesAndWriteFile` * Add `--size-cutoff` to truncate large golden test output * Restore support for GHC >= 7.8 Version 2.3.2.1 --------------- Create missing directories when writing golden files Version 2.3.2 ------------- Add a `--no-create` flag Version 2.3.1.3 --------------- Make the environment variable `TASTY_ACCEPT=True` work, and make the value case-insensitive (so `TASTY_ACCEPT=true` works, too) Version 2.3.1.2 --------------- Docs: link to an introductory blog post Version 2.3.1.1 --------------- Fix compatibility with `optparse-applicative-0.13` Version 2.3.1 ------------- Intercept exceptions thrown by the test, adhering to the new tasty API contract. Version 2.3.0.2 --------------- Switch from temporary-rc to temporary Version 2.3.0.1 --------------- Impose a lower bound version constraint on bytestring. Version 2.3 ----------- * Accepting tests is no longer done by a separate ingredient; instead it is now an option that affects tests themselves. * `--accept` used to run only golden tests; now all tests are run, but only golden tests are affected by this option * when accepting, all the usual options apply (such as `-j`) * when accepting, the interace is the same as when running * `defaultMain` and `acceptingTests` are kept for compatibility, but do not do anything and are obsolete * When a golden test file does not exist, it is created automatically, even when `--accept` is not specified. You'll see a message like UnboxedTuples: OK (0.04s) Golden file did not exist; created * No longer use lazy IO * `ValueGetter` type is gone (replaced by `IO`) * Because of that, the type of the primitive `goldenTest` is changed * `vgReadFile` function is gone (replaced by `Data.ByteString.readFile`) Version 2.2.2.4 --------------- * Warn when some tests threw exceptions during `--accept` * Properly handle exceptions; don't swallow Ctrl-C Version 2.2.2.3 --------------- Restore compatibility with older compilers Version 2.2.2.1 --------------- Relax `Cabal` dependency Version 2.2.2 ------------- Add `findByExtension` Version 2.2.1.2 --------------- Catch exceptions when accepting golden tests Version 2.2.1.1 --------------- Switch to `temporary-rc` Version 2.2.1 ------------- * Fix a bug where the result of the comparison function would reference yet unread data from a semiclosed file and the file gets closed, leading to a runtime exception * Export `writeBinaryFile` * Improve the docs * Update to work with `tasty-0.8` Version 2.2.0.2 --------------- Update to work with `tasty-0.7` Version 2.2.0.1 --------------- Update to work with `tasty-0.5` Version 2.2 ----------- Migrate to ingredients Version 2.1 ----------- Add `goldenVsStringDiff` Version 2.0.1 ------------- Update to work with `tasty-0.2` Version 2.0 ----------- Initial release of `tasty-golden` (derived from `test-framework-golden-1.1.x`) tasty-golden-2.3.3.2/example/golden/fail/goldenVsFileDiff.golden0000644000000000000000000000746513623745465022674 0ustar00000000000000001 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64 65 66 67 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 100 101 102 103 104 105 106 107 108 109 110 111 112 113 114 115 116 117 118 119 120 121 122 123 124 125 126 127 128 129 130 131 132 133 134 135 136 137 138 139 140 141 142 143 144 145 146 147 148 149 150 151 152 153 154 155 156 157 158 159 160 161 162 163 164 165 166 167 168 169 170 171 172 173 174 175 176 177 178 179 180 181 182 183 184 185 186 187 188 189 190 191 192 193 194 195 196 197 198 199 200 201 202 203 204 205 206 207 208 209 210 211 212 213 214 215 216 217 218 219 220 221 222 223 224 225 226 227 228 229 230 231 232 233 234 235 236 237 238 239 240 241 242 243 244 245 246 247 248 249 250 251 252 253 254 255 256 257 258 259 260 261 262 263 264 265 266 267 268 269 270 271 272 273 274 275 276 277 278 279 280 281 282 283 284 285 286 287 288 289 290 291 292 293 294 295 296 297 298 299 300 301 302 303 304 305 306 307 308 309 310 311 312 313 314 315 316 317 318 319 320 321 322 323 324 325 326 327 328 329 330 331 332 333 334 335 336 337 338 339 340 341 342 343 344 345 346 347 348 349 350 351 352 353 354 355 356 357 358 359 360 361 362 363 364 365 366 367 368 369 370 371 372 373 374 375 376 377 378 379 380 381 382 383 384 385 386 387 388 389 390 391 392 393 394 395 396 397 398 399 400 401 402 403 404 405 406 407 408 409 410 411 412 413 414 415 416 417 418 419 420 421 422 423 424 425 426 427 428 429 430 431 432 433 434 435 436 437 438 439 440 441 442 443 444 445 446 447 448 449 450 451 452 453 454 455 456 457 458 459 460 461 462 463 464 465 466 467 468 469 470 471 472 473 474 475 476 477 478 479 480 481 482 483 484 485 486 487 488 489 490 491 492 493 494 495 496 497 498 499 500 501 502 503 504 505 506 507 508 509 510 511 512 513 514 515 516 517 518 519 520 521 522 523 524 525 526 527 528 529 530 531 532 533 534 535 536 537 538 539 540 541 542 543 544 545 546 547 548 549 550 551 552 553 554 555 556 557 558 559 560 561 562 563 564 565 566 567 568 569 570 571 572 573 574 575 576 577 578 579 580 581 582 583 584 585 586 587 588 589 590 591 592 593 594 595 596 597 598 599 600 601 602 603 604 605 606 607 608 609 610 611 612 613 614 615 616 617 618 619 620 621 622 623 624 625 626 627 628 629 630 631 632 633 634 635 636 637 638 639 640 641 642 643 644 645 646 647 648 649 650 651 652 653 654 655 656 657 658 659 660 661 662 663 664 665 666 667 668 669 670 671 672 673 674 675 676 677 678 679 680 681 682 683 684 685 686 687 688 689 690 691 692 693 694 695 696 697 698 699 700 701 702 703 704 705 706 707 708 709 710 711 712 713 714 715 716 717 718 719 720 721 722 723 724 725 726 727 728 729 730 731 732 733 734 735 736 737 738 739 740 741 742 743 744 745 746 747 748 749 750 751 752 753 754 755 756 757 758 759 760 761 762 763 764 765 766 767 768 769 770 771 772 773 774 775 776 777 778 779 780 781 782 783 784 785 786 787 788 789 790 791 792 793 794 795 796 797 798 799 800 801 802 803 804 805 806 807 808 809 810 811 812 813 814 815 816 817 818 819 820 821 822 823 824 825 826 827 828 829 830 831 832 833 834 835 836 837 838 839 840 841 842 843 844 845 846 847 848 849 850 851 852 853 854 855 856 857 858 859 860 861 862 863 864 865 866 867 868 869 870 871 872 873 874 875 876 877 878 879 880 881 882 883 884 885 886 887 888 889 890 891 892 893 894 895 896 897 898 899 900 901 902 903 904 905 906 907 908 909 910 911 912 913 914 915 916 917 918 919 920 921 922 923 924 925 926 927 928 929 930 931 932 933 934 935 936 937 938 939 940 941 942 943 944 945 946 947 948 949 950 951 952 953 954 955 956 957 958 959 960 961 962 963 964 965 966 967 968 969 970 971 972 973 974 975 976 977 978 979 980 981 982 983 984 985 986 987 988 989 990 991 992 993 994 995 996 997 998 999 1000 tasty-golden-2.3.3.2/example/golden/fail/goldenVsString.golden0000644000000000000000000000746513623745465022472 0ustar00000000000000001 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64 65 66 67 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 100 101 102 103 104 105 106 107 108 109 110 111 112 113 114 115 116 117 118 119 120 121 122 123 124 125 126 127 128 129 130 131 132 133 134 135 136 137 138 139 140 141 142 143 144 145 146 147 148 149 150 151 152 153 154 155 156 157 158 159 160 161 162 163 164 165 166 167 168 169 170 171 172 173 174 175 176 177 178 179 180 181 182 183 184 185 186 187 188 189 190 191 192 193 194 195 196 197 198 199 200 201 202 203 204 205 206 207 208 209 210 211 212 213 214 215 216 217 218 219 220 221 222 223 224 225 226 227 228 229 230 231 232 233 234 235 236 237 238 239 240 241 242 243 244 245 246 247 248 249 250 251 252 253 254 255 256 257 258 259 260 261 262 263 264 265 266 267 268 269 270 271 272 273 274 275 276 277 278 279 280 281 282 283 284 285 286 287 288 289 290 291 292 293 294 295 296 297 298 299 300 301 302 303 304 305 306 307 308 309 310 311 312 313 314 315 316 317 318 319 320 321 322 323 324 325 326 327 328 329 330 331 332 333 334 335 336 337 338 339 340 341 342 343 344 345 346 347 348 349 350 351 352 353 354 355 356 357 358 359 360 361 362 363 364 365 366 367 368 369 370 371 372 373 374 375 376 377 378 379 380 381 382 383 384 385 386 387 388 389 390 391 392 393 394 395 396 397 398 399 400 401 402 403 404 405 406 407 408 409 410 411 412 413 414 415 416 417 418 419 420 421 422 423 424 425 426 427 428 429 430 431 432 433 434 435 436 437 438 439 440 441 442 443 444 445 446 447 448 449 450 451 452 453 454 455 456 457 458 459 460 461 462 463 464 465 466 467 468 469 470 471 472 473 474 475 476 477 478 479 480 481 482 483 484 485 486 487 488 489 490 491 492 493 494 495 496 497 498 499 500 501 502 503 504 505 506 507 508 509 510 511 512 513 514 515 516 517 518 519 520 521 522 523 524 525 526 527 528 529 530 531 532 533 534 535 536 537 538 539 540 541 542 543 544 545 546 547 548 549 550 551 552 553 554 555 556 557 558 559 560 561 562 563 564 565 566 567 568 569 570 571 572 573 574 575 576 577 578 579 580 581 582 583 584 585 586 587 588 589 590 591 592 593 594 595 596 597 598 599 600 601 602 603 604 605 606 607 608 609 610 611 612 613 614 615 616 617 618 619 620 621 622 623 624 625 626 627 628 629 630 631 632 633 634 635 636 637 638 639 640 641 642 643 644 645 646 647 648 649 650 651 652 653 654 655 656 657 658 659 660 661 662 663 664 665 666 667 668 669 670 671 672 673 674 675 676 677 678 679 680 681 682 683 684 685 686 687 688 689 690 691 692 693 694 695 696 697 698 699 700 701 702 703 704 705 706 707 708 709 710 711 712 713 714 715 716 717 718 719 720 721 722 723 724 725 726 727 728 729 730 731 732 733 734 735 736 737 738 739 740 741 742 743 744 745 746 747 748 749 750 751 752 753 754 755 756 757 758 759 760 761 762 763 764 765 766 767 768 769 770 771 772 773 774 775 776 777 778 779 780 781 782 783 784 785 786 787 788 789 790 791 792 793 794 795 796 797 798 799 800 801 802 803 804 805 806 807 808 809 810 811 812 813 814 815 816 817 818 819 820 821 822 823 824 825 826 827 828 829 830 831 832 833 834 835 836 837 838 839 840 841 842 843 844 845 846 847 848 849 850 851 852 853 854 855 856 857 858 859 860 861 862 863 864 865 866 867 868 869 870 871 872 873 874 875 876 877 878 879 880 881 882 883 884 885 886 887 888 889 890 891 892 893 894 895 896 897 898 899 900 901 902 903 904 905 906 907 908 909 910 911 912 913 914 915 916 917 918 919 920 921 922 923 924 925 926 927 928 929 930 931 932 933 934 935 936 937 938 939 940 941 942 943 944 945 946 947 948 949 950 951 952 953 954 955 956 957 958 959 960 961 962 963 964 965 966 967 968 969 970 971 972 973 974 975 976 977 978 979 980 981 982 983 984 985 986 987 988 989 990 991 992 993 994 995 996 997 998 999 1000 tasty-golden-2.3.3.2/example/golden/fail/goldenVsFile.golden0000644000000000000000000000746513623745465022103 0ustar00000000000000001 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64 65 66 67 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 100 101 102 103 104 105 106 107 108 109 110 111 112 113 114 115 116 117 118 119 120 121 122 123 124 125 126 127 128 129 130 131 132 133 134 135 136 137 138 139 140 141 142 143 144 145 146 147 148 149 150 151 152 153 154 155 156 157 158 159 160 161 162 163 164 165 166 167 168 169 170 171 172 173 174 175 176 177 178 179 180 181 182 183 184 185 186 187 188 189 190 191 192 193 194 195 196 197 198 199 200 201 202 203 204 205 206 207 208 209 210 211 212 213 214 215 216 217 218 219 220 221 222 223 224 225 226 227 228 229 230 231 232 233 234 235 236 237 238 239 240 241 242 243 244 245 246 247 248 249 250 251 252 253 254 255 256 257 258 259 260 261 262 263 264 265 266 267 268 269 270 271 272 273 274 275 276 277 278 279 280 281 282 283 284 285 286 287 288 289 290 291 292 293 294 295 296 297 298 299 300 301 302 303 304 305 306 307 308 309 310 311 312 313 314 315 316 317 318 319 320 321 322 323 324 325 326 327 328 329 330 331 332 333 334 335 336 337 338 339 340 341 342 343 344 345 346 347 348 349 350 351 352 353 354 355 356 357 358 359 360 361 362 363 364 365 366 367 368 369 370 371 372 373 374 375 376 377 378 379 380 381 382 383 384 385 386 387 388 389 390 391 392 393 394 395 396 397 398 399 400 401 402 403 404 405 406 407 408 409 410 411 412 413 414 415 416 417 418 419 420 421 422 423 424 425 426 427 428 429 430 431 432 433 434 435 436 437 438 439 440 441 442 443 444 445 446 447 448 449 450 451 452 453 454 455 456 457 458 459 460 461 462 463 464 465 466 467 468 469 470 471 472 473 474 475 476 477 478 479 480 481 482 483 484 485 486 487 488 489 490 491 492 493 494 495 496 497 498 499 500 501 502 503 504 505 506 507 508 509 510 511 512 513 514 515 516 517 518 519 520 521 522 523 524 525 526 527 528 529 530 531 532 533 534 535 536 537 538 539 540 541 542 543 544 545 546 547 548 549 550 551 552 553 554 555 556 557 558 559 560 561 562 563 564 565 566 567 568 569 570 571 572 573 574 575 576 577 578 579 580 581 582 583 584 585 586 587 588 589 590 591 592 593 594 595 596 597 598 599 600 601 602 603 604 605 606 607 608 609 610 611 612 613 614 615 616 617 618 619 620 621 622 623 624 625 626 627 628 629 630 631 632 633 634 635 636 637 638 639 640 641 642 643 644 645 646 647 648 649 650 651 652 653 654 655 656 657 658 659 660 661 662 663 664 665 666 667 668 669 670 671 672 673 674 675 676 677 678 679 680 681 682 683 684 685 686 687 688 689 690 691 692 693 694 695 696 697 698 699 700 701 702 703 704 705 706 707 708 709 710 711 712 713 714 715 716 717 718 719 720 721 722 723 724 725 726 727 728 729 730 731 732 733 734 735 736 737 738 739 740 741 742 743 744 745 746 747 748 749 750 751 752 753 754 755 756 757 758 759 760 761 762 763 764 765 766 767 768 769 770 771 772 773 774 775 776 777 778 779 780 781 782 783 784 785 786 787 788 789 790 791 792 793 794 795 796 797 798 799 800 801 802 803 804 805 806 807 808 809 810 811 812 813 814 815 816 817 818 819 820 821 822 823 824 825 826 827 828 829 830 831 832 833 834 835 836 837 838 839 840 841 842 843 844 845 846 847 848 849 850 851 852 853 854 855 856 857 858 859 860 861 862 863 864 865 866 867 868 869 870 871 872 873 874 875 876 877 878 879 880 881 882 883 884 885 886 887 888 889 890 891 892 893 894 895 896 897 898 899 900 901 902 903 904 905 906 907 908 909 910 911 912 913 914 915 916 917 918 919 920 921 922 923 924 925 926 927 928 929 930 931 932 933 934 935 936 937 938 939 940 941 942 943 944 945 946 947 948 949 950 951 952 953 954 955 956 957 958 959 960 961 962 963 964 965 966 967 968 969 970 971 972 973 974 975 976 977 978 979 980 981 982 983 984 985 986 987 988 989 990 991 992 993 994 995 996 997 998 999 1000 tasty-golden-2.3.3.2/example/golden/fail/goldenVsStringDiff.golden0000644000000000000000000000746513623745465023263 0ustar00000000000000001 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64 65 66 67 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 100 101 102 103 104 105 106 107 108 109 110 111 112 113 114 115 116 117 118 119 120 121 122 123 124 125 126 127 128 129 130 131 132 133 134 135 136 137 138 139 140 141 142 143 144 145 146 147 148 149 150 151 152 153 154 155 156 157 158 159 160 161 162 163 164 165 166 167 168 169 170 171 172 173 174 175 176 177 178 179 180 181 182 183 184 185 186 187 188 189 190 191 192 193 194 195 196 197 198 199 200 201 202 203 204 205 206 207 208 209 210 211 212 213 214 215 216 217 218 219 220 221 222 223 224 225 226 227 228 229 230 231 232 233 234 235 236 237 238 239 240 241 242 243 244 245 246 247 248 249 250 251 252 253 254 255 256 257 258 259 260 261 262 263 264 265 266 267 268 269 270 271 272 273 274 275 276 277 278 279 280 281 282 283 284 285 286 287 288 289 290 291 292 293 294 295 296 297 298 299 300 301 302 303 304 305 306 307 308 309 310 311 312 313 314 315 316 317 318 319 320 321 322 323 324 325 326 327 328 329 330 331 332 333 334 335 336 337 338 339 340 341 342 343 344 345 346 347 348 349 350 351 352 353 354 355 356 357 358 359 360 361 362 363 364 365 366 367 368 369 370 371 372 373 374 375 376 377 378 379 380 381 382 383 384 385 386 387 388 389 390 391 392 393 394 395 396 397 398 399 400 401 402 403 404 405 406 407 408 409 410 411 412 413 414 415 416 417 418 419 420 421 422 423 424 425 426 427 428 429 430 431 432 433 434 435 436 437 438 439 440 441 442 443 444 445 446 447 448 449 450 451 452 453 454 455 456 457 458 459 460 461 462 463 464 465 466 467 468 469 470 471 472 473 474 475 476 477 478 479 480 481 482 483 484 485 486 487 488 489 490 491 492 493 494 495 496 497 498 499 500 501 502 503 504 505 506 507 508 509 510 511 512 513 514 515 516 517 518 519 520 521 522 523 524 525 526 527 528 529 530 531 532 533 534 535 536 537 538 539 540 541 542 543 544 545 546 547 548 549 550 551 552 553 554 555 556 557 558 559 560 561 562 563 564 565 566 567 568 569 570 571 572 573 574 575 576 577 578 579 580 581 582 583 584 585 586 587 588 589 590 591 592 593 594 595 596 597 598 599 600 601 602 603 604 605 606 607 608 609 610 611 612 613 614 615 616 617 618 619 620 621 622 623 624 625 626 627 628 629 630 631 632 633 634 635 636 637 638 639 640 641 642 643 644 645 646 647 648 649 650 651 652 653 654 655 656 657 658 659 660 661 662 663 664 665 666 667 668 669 670 671 672 673 674 675 676 677 678 679 680 681 682 683 684 685 686 687 688 689 690 691 692 693 694 695 696 697 698 699 700 701 702 703 704 705 706 707 708 709 710 711 712 713 714 715 716 717 718 719 720 721 722 723 724 725 726 727 728 729 730 731 732 733 734 735 736 737 738 739 740 741 742 743 744 745 746 747 748 749 750 751 752 753 754 755 756 757 758 759 760 761 762 763 764 765 766 767 768 769 770 771 772 773 774 775 776 777 778 779 780 781 782 783 784 785 786 787 788 789 790 791 792 793 794 795 796 797 798 799 800 801 802 803 804 805 806 807 808 809 810 811 812 813 814 815 816 817 818 819 820 821 822 823 824 825 826 827 828 829 830 831 832 833 834 835 836 837 838 839 840 841 842 843 844 845 846 847 848 849 850 851 852 853 854 855 856 857 858 859 860 861 862 863 864 865 866 867 868 869 870 871 872 873 874 875 876 877 878 879 880 881 882 883 884 885 886 887 888 889 890 891 892 893 894 895 896 897 898 899 900 901 902 903 904 905 906 907 908 909 910 911 912 913 914 915 916 917 918 919 920 921 922 923 924 925 926 927 928 929 930 931 932 933 934 935 936 937 938 939 940 941 942 943 944 945 946 947 948 949 950 951 952 953 954 955 956 957 958 959 960 961 962 963 964 965 966 967 968 969 970 971 972 973 974 975 976 977 978 979 980 981 982 983 984 985 986 987 988 989 990 991 992 993 994 995 996 997 998 999 1000 tasty-golden-2.3.3.2/example/golden/success/goldenVsFileDiff.golden0000644000000000000000000000746513623745465023431 0ustar00000000000000001 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64 65 66 67 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 100 101 102 103 104 105 106 107 108 109 110 111 112 113 114 115 116 117 118 119 120 121 122 123 124 125 126 127 128 129 130 131 132 133 134 135 136 137 138 139 140 141 142 143 144 145 146 147 148 149 150 151 152 153 154 155 156 157 158 159 160 161 162 163 164 165 166 167 168 169 170 171 172 173 174 175 176 177 178 179 180 181 182 183 184 185 186 187 188 189 190 191 192 193 194 195 196 197 198 199 200 201 202 203 204 205 206 207 208 209 210 211 212 213 214 215 216 217 218 219 220 221 222 223 224 225 226 227 228 229 230 231 232 233 234 235 236 237 238 239 240 241 242 243 244 245 246 247 248 249 250 251 252 253 254 255 256 257 258 259 260 261 262 263 264 265 266 267 268 269 270 271 272 273 274 275 276 277 278 279 280 281 282 283 284 285 286 287 288 289 290 291 292 293 294 295 296 297 298 299 300 301 302 303 304 305 306 307 308 309 310 311 312 313 314 315 316 317 318 319 320 321 322 323 324 325 326 327 328 329 330 331 332 333 334 335 336 337 338 339 340 341 342 343 344 345 346 347 348 349 350 351 352 353 354 355 356 357 358 359 360 361 362 363 364 365 366 367 368 369 370 371 372 373 374 375 376 377 378 379 380 381 382 383 384 385 386 387 388 389 390 391 392 393 394 395 396 397 398 399 400 401 402 403 404 405 406 407 408 409 410 411 412 413 414 415 416 417 418 419 420 421 422 423 424 425 426 427 428 429 430 431 432 433 434 435 436 437 438 439 440 441 442 443 444 445 446 447 448 449 450 451 452 453 454 455 456 457 458 459 460 461 462 463 464 465 466 467 468 469 470 471 472 473 474 475 476 477 478 479 480 481 482 483 484 485 486 487 488 489 490 491 492 493 494 495 496 497 498 499 500 501 502 503 504 505 506 507 508 509 510 511 512 513 514 515 516 517 518 519 520 521 522 523 524 525 526 527 528 529 530 531 532 533 534 535 536 537 538 539 540 541 542 543 544 545 546 547 548 549 550 551 552 553 554 555 556 557 558 559 560 561 562 563 564 565 566 567 568 569 570 571 572 573 574 575 576 577 578 579 580 581 582 583 584 585 586 587 588 589 590 591 592 593 594 595 596 597 598 599 600 601 602 603 604 605 606 607 608 609 610 611 612 613 614 615 616 617 618 619 620 621 622 623 624 625 626 627 628 629 630 631 632 633 634 635 636 637 638 639 640 641 642 643 644 645 646 647 648 649 650 651 652 653 654 655 656 657 658 659 660 661 662 663 664 665 666 667 668 669 670 671 672 673 674 675 676 677 678 679 680 681 682 683 684 685 686 687 688 689 690 691 692 693 694 695 696 697 698 699 700 701 702 703 704 705 706 707 708 709 710 711 712 713 714 715 716 717 718 719 720 721 722 723 724 725 726 727 728 729 730 731 732 733 734 735 736 737 738 739 740 741 742 743 744 745 746 747 748 749 750 751 752 753 754 755 756 757 758 759 760 761 762 763 764 765 766 767 768 769 770 771 772 773 774 775 776 777 778 779 780 781 782 783 784 785 786 787 788 789 790 791 792 793 794 795 796 797 798 799 800 801 802 803 804 805 806 807 808 809 810 811 812 813 814 815 816 817 818 819 820 821 822 823 824 825 826 827 828 829 830 831 832 833 834 835 836 837 838 839 840 841 842 843 844 845 846 847 848 849 850 851 852 853 854 855 856 857 858 859 860 861 862 863 864 865 866 867 868 869 870 871 872 873 874 875 876 877 878 879 880 881 882 883 884 885 886 887 888 889 890 891 892 893 894 895 896 897 898 899 900 901 902 903 904 905 906 907 908 909 910 911 912 913 914 915 916 917 918 919 920 921 922 923 924 925 926 927 928 929 930 931 932 933 934 935 936 937 938 939 940 941 942 943 944 945 946 947 948 949 950 951 952 953 954 955 956 957 958 959 960 961 962 963 964 965 966 967 968 969 970 971 972 973 974 975 976 977 978 979 980 981 982 983 984 985 986 987 988 989 990 991 992 993 994 995 996 997 998 999 1000 tasty-golden-2.3.3.2/example/golden/success/goldenVsString.golden0000644000000000000000000000746513623745465023227 0ustar00000000000000001 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64 65 66 67 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 100 101 102 103 104 105 106 107 108 109 110 111 112 113 114 115 116 117 118 119 120 121 122 123 124 125 126 127 128 129 130 131 132 133 134 135 136 137 138 139 140 141 142 143 144 145 146 147 148 149 150 151 152 153 154 155 156 157 158 159 160 161 162 163 164 165 166 167 168 169 170 171 172 173 174 175 176 177 178 179 180 181 182 183 184 185 186 187 188 189 190 191 192 193 194 195 196 197 198 199 200 201 202 203 204 205 206 207 208 209 210 211 212 213 214 215 216 217 218 219 220 221 222 223 224 225 226 227 228 229 230 231 232 233 234 235 236 237 238 239 240 241 242 243 244 245 246 247 248 249 250 251 252 253 254 255 256 257 258 259 260 261 262 263 264 265 266 267 268 269 270 271 272 273 274 275 276 277 278 279 280 281 282 283 284 285 286 287 288 289 290 291 292 293 294 295 296 297 298 299 300 301 302 303 304 305 306 307 308 309 310 311 312 313 314 315 316 317 318 319 320 321 322 323 324 325 326 327 328 329 330 331 332 333 334 335 336 337 338 339 340 341 342 343 344 345 346 347 348 349 350 351 352 353 354 355 356 357 358 359 360 361 362 363 364 365 366 367 368 369 370 371 372 373 374 375 376 377 378 379 380 381 382 383 384 385 386 387 388 389 390 391 392 393 394 395 396 397 398 399 400 401 402 403 404 405 406 407 408 409 410 411 412 413 414 415 416 417 418 419 420 421 422 423 424 425 426 427 428 429 430 431 432 433 434 435 436 437 438 439 440 441 442 443 444 445 446 447 448 449 450 451 452 453 454 455 456 457 458 459 460 461 462 463 464 465 466 467 468 469 470 471 472 473 474 475 476 477 478 479 480 481 482 483 484 485 486 487 488 489 490 491 492 493 494 495 496 497 498 499 500 501 502 503 504 505 506 507 508 509 510 511 512 513 514 515 516 517 518 519 520 521 522 523 524 525 526 527 528 529 530 531 532 533 534 535 536 537 538 539 540 541 542 543 544 545 546 547 548 549 550 551 552 553 554 555 556 557 558 559 560 561 562 563 564 565 566 567 568 569 570 571 572 573 574 575 576 577 578 579 580 581 582 583 584 585 586 587 588 589 590 591 592 593 594 595 596 597 598 599 600 601 602 603 604 605 606 607 608 609 610 611 612 613 614 615 616 617 618 619 620 621 622 623 624 625 626 627 628 629 630 631 632 633 634 635 636 637 638 639 640 641 642 643 644 645 646 647 648 649 650 651 652 653 654 655 656 657 658 659 660 661 662 663 664 665 666 667 668 669 670 671 672 673 674 675 676 677 678 679 680 681 682 683 684 685 686 687 688 689 690 691 692 693 694 695 696 697 698 699 700 701 702 703 704 705 706 707 708 709 710 711 712 713 714 715 716 717 718 719 720 721 722 723 724 725 726 727 728 729 730 731 732 733 734 735 736 737 738 739 740 741 742 743 744 745 746 747 748 749 750 751 752 753 754 755 756 757 758 759 760 761 762 763 764 765 766 767 768 769 770 771 772 773 774 775 776 777 778 779 780 781 782 783 784 785 786 787 788 789 790 791 792 793 794 795 796 797 798 799 800 801 802 803 804 805 806 807 808 809 810 811 812 813 814 815 816 817 818 819 820 821 822 823 824 825 826 827 828 829 830 831 832 833 834 835 836 837 838 839 840 841 842 843 844 845 846 847 848 849 850 851 852 853 854 855 856 857 858 859 860 861 862 863 864 865 866 867 868 869 870 871 872 873 874 875 876 877 878 879 880 881 882 883 884 885 886 887 888 889 890 891 892 893 894 895 896 897 898 899 900 901 902 903 904 905 906 907 908 909 910 911 912 913 914 915 916 917 918 919 920 921 922 923 924 925 926 927 928 929 930 931 932 933 934 935 936 937 938 939 940 941 942 943 944 945 946 947 948 949 950 951 952 953 954 955 956 957 958 959 960 961 962 963 964 965 966 967 968 969 970 971 972 973 974 975 976 977 978 979 980 981 982 983 984 985 986 987 988 989 990 991 992 993 994 995 996 997 998 999 1000 tasty-golden-2.3.3.2/example/golden/success/goldenVsFile.golden0000644000000000000000000000746513623745465022640 0ustar00000000000000001 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64 65 66 67 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 100 101 102 103 104 105 106 107 108 109 110 111 112 113 114 115 116 117 118 119 120 121 122 123 124 125 126 127 128 129 130 131 132 133 134 135 136 137 138 139 140 141 142 143 144 145 146 147 148 149 150 151 152 153 154 155 156 157 158 159 160 161 162 163 164 165 166 167 168 169 170 171 172 173 174 175 176 177 178 179 180 181 182 183 184 185 186 187 188 189 190 191 192 193 194 195 196 197 198 199 200 201 202 203 204 205 206 207 208 209 210 211 212 213 214 215 216 217 218 219 220 221 222 223 224 225 226 227 228 229 230 231 232 233 234 235 236 237 238 239 240 241 242 243 244 245 246 247 248 249 250 251 252 253 254 255 256 257 258 259 260 261 262 263 264 265 266 267 268 269 270 271 272 273 274 275 276 277 278 279 280 281 282 283 284 285 286 287 288 289 290 291 292 293 294 295 296 297 298 299 300 301 302 303 304 305 306 307 308 309 310 311 312 313 314 315 316 317 318 319 320 321 322 323 324 325 326 327 328 329 330 331 332 333 334 335 336 337 338 339 340 341 342 343 344 345 346 347 348 349 350 351 352 353 354 355 356 357 358 359 360 361 362 363 364 365 366 367 368 369 370 371 372 373 374 375 376 377 378 379 380 381 382 383 384 385 386 387 388 389 390 391 392 393 394 395 396 397 398 399 400 401 402 403 404 405 406 407 408 409 410 411 412 413 414 415 416 417 418 419 420 421 422 423 424 425 426 427 428 429 430 431 432 433 434 435 436 437 438 439 440 441 442 443 444 445 446 447 448 449 450 451 452 453 454 455 456 457 458 459 460 461 462 463 464 465 466 467 468 469 470 471 472 473 474 475 476 477 478 479 480 481 482 483 484 485 486 487 488 489 490 491 492 493 494 495 496 497 498 499 500 501 502 503 504 505 506 507 508 509 510 511 512 513 514 515 516 517 518 519 520 521 522 523 524 525 526 527 528 529 530 531 532 533 534 535 536 537 538 539 540 541 542 543 544 545 546 547 548 549 550 551 552 553 554 555 556 557 558 559 560 561 562 563 564 565 566 567 568 569 570 571 572 573 574 575 576 577 578 579 580 581 582 583 584 585 586 587 588 589 590 591 592 593 594 595 596 597 598 599 600 601 602 603 604 605 606 607 608 609 610 611 612 613 614 615 616 617 618 619 620 621 622 623 624 625 626 627 628 629 630 631 632 633 634 635 636 637 638 639 640 641 642 643 644 645 646 647 648 649 650 651 652 653 654 655 656 657 658 659 660 661 662 663 664 665 666 667 668 669 670 671 672 673 674 675 676 677 678 679 680 681 682 683 684 685 686 687 688 689 690 691 692 693 694 695 696 697 698 699 700 701 702 703 704 705 706 707 708 709 710 711 712 713 714 715 716 717 718 719 720 721 722 723 724 725 726 727 728 729 730 731 732 733 734 735 736 737 738 739 740 741 742 743 744 745 746 747 748 749 750 751 752 753 754 755 756 757 758 759 760 761 762 763 764 765 766 767 768 769 770 771 772 773 774 775 776 777 778 779 780 781 782 783 784 785 786 787 788 789 790 791 792 793 794 795 796 797 798 799 800 801 802 803 804 805 806 807 808 809 810 811 812 813 814 815 816 817 818 819 820 821 822 823 824 825 826 827 828 829 830 831 832 833 834 835 836 837 838 839 840 841 842 843 844 845 846 847 848 849 850 851 852 853 854 855 856 857 858 859 860 861 862 863 864 865 866 867 868 869 870 871 872 873 874 875 876 877 878 879 880 881 882 883 884 885 886 887 888 889 890 891 892 893 894 895 896 897 898 899 900 901 902 903 904 905 906 907 908 909 910 911 912 913 914 915 916 917 918 919 920 921 922 923 924 925 926 927 928 929 930 931 932 933 934 935 936 937 938 939 940 941 942 943 944 945 946 947 948 949 950 951 952 953 954 955 956 957 958 959 960 961 962 963 964 965 966 967 968 969 970 971 972 973 974 975 976 977 978 979 980 981 982 983 984 985 986 987 988 989 990 991 992 993 994 995 996 997 998 999 1000 tasty-golden-2.3.3.2/example/golden/success/goldenVsStringDiff.golden0000644000000000000000000000746513623745465024020 0ustar00000000000000001 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64 65 66 67 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 100 101 102 103 104 105 106 107 108 109 110 111 112 113 114 115 116 117 118 119 120 121 122 123 124 125 126 127 128 129 130 131 132 133 134 135 136 137 138 139 140 141 142 143 144 145 146 147 148 149 150 151 152 153 154 155 156 157 158 159 160 161 162 163 164 165 166 167 168 169 170 171 172 173 174 175 176 177 178 179 180 181 182 183 184 185 186 187 188 189 190 191 192 193 194 195 196 197 198 199 200 201 202 203 204 205 206 207 208 209 210 211 212 213 214 215 216 217 218 219 220 221 222 223 224 225 226 227 228 229 230 231 232 233 234 235 236 237 238 239 240 241 242 243 244 245 246 247 248 249 250 251 252 253 254 255 256 257 258 259 260 261 262 263 264 265 266 267 268 269 270 271 272 273 274 275 276 277 278 279 280 281 282 283 284 285 286 287 288 289 290 291 292 293 294 295 296 297 298 299 300 301 302 303 304 305 306 307 308 309 310 311 312 313 314 315 316 317 318 319 320 321 322 323 324 325 326 327 328 329 330 331 332 333 334 335 336 337 338 339 340 341 342 343 344 345 346 347 348 349 350 351 352 353 354 355 356 357 358 359 360 361 362 363 364 365 366 367 368 369 370 371 372 373 374 375 376 377 378 379 380 381 382 383 384 385 386 387 388 389 390 391 392 393 394 395 396 397 398 399 400 401 402 403 404 405 406 407 408 409 410 411 412 413 414 415 416 417 418 419 420 421 422 423 424 425 426 427 428 429 430 431 432 433 434 435 436 437 438 439 440 441 442 443 444 445 446 447 448 449 450 451 452 453 454 455 456 457 458 459 460 461 462 463 464 465 466 467 468 469 470 471 472 473 474 475 476 477 478 479 480 481 482 483 484 485 486 487 488 489 490 491 492 493 494 495 496 497 498 499 500 501 502 503 504 505 506 507 508 509 510 511 512 513 514 515 516 517 518 519 520 521 522 523 524 525 526 527 528 529 530 531 532 533 534 535 536 537 538 539 540 541 542 543 544 545 546 547 548 549 550 551 552 553 554 555 556 557 558 559 560 561 562 563 564 565 566 567 568 569 570 571 572 573 574 575 576 577 578 579 580 581 582 583 584 585 586 587 588 589 590 591 592 593 594 595 596 597 598 599 600 601 602 603 604 605 606 607 608 609 610 611 612 613 614 615 616 617 618 619 620 621 622 623 624 625 626 627 628 629 630 631 632 633 634 635 636 637 638 639 640 641 642 643 644 645 646 647 648 649 650 651 652 653 654 655 656 657 658 659 660 661 662 663 664 665 666 667 668 669 670 671 672 673 674 675 676 677 678 679 680 681 682 683 684 685 686 687 688 689 690 691 692 693 694 695 696 697 698 699 700 701 702 703 704 705 706 707 708 709 710 711 712 713 714 715 716 717 718 719 720 721 722 723 724 725 726 727 728 729 730 731 732 733 734 735 736 737 738 739 740 741 742 743 744 745 746 747 748 749 750 751 752 753 754 755 756 757 758 759 760 761 762 763 764 765 766 767 768 769 770 771 772 773 774 775 776 777 778 779 780 781 782 783 784 785 786 787 788 789 790 791 792 793 794 795 796 797 798 799 800 801 802 803 804 805 806 807 808 809 810 811 812 813 814 815 816 817 818 819 820 821 822 823 824 825 826 827 828 829 830 831 832 833 834 835 836 837 838 839 840 841 842 843 844 845 846 847 848 849 850 851 852 853 854 855 856 857 858 859 860 861 862 863 864 865 866 867 868 869 870 871 872 873 874 875 876 877 878 879 880 881 882 883 884 885 886 887 888 889 890 891 892 893 894 895 896 897 898 899 900 901 902 903 904 905 906 907 908 909 910 911 912 913 914 915 916 917 918 919 920 921 922 923 924 925 926 927 928 929 930 931 932 933 934 935 936 937 938 939 940 941 942 943 944 945 946 947 948 949 950 951 952 953 954 955 956 957 958 959 960 961 962 963 964 965 966 967 968 969 970 971 972 973 974 975 976 977 978 979 980 981 982 983 984 985 986 987 988 989 990 991 992 993 994 995 996 997 998 999 1000 tasty-golden-2.3.3.2/tests/golden/after-accept.golden0000644000000000000000000000042513623745465020641 0ustar0000000000000000Tests Successful tests goldenVsFile: OK goldenVsFileDiff: OK goldenVsString: OK goldenVsStringDiff: OK Failing tests goldenVsFile: OK goldenVsFileDiff: OK goldenVsString: OK goldenVsStringDiff: OK All 8 tests passed tasty-golden-2.3.3.2/tests/golden/before-accept.golden0000644000000000000000000000361313623745465021004 0ustar0000000000000000Tests Successful tests goldenVsFile: OK goldenVsFileDiff: OK goldenVsString: OK goldenVsStringDiff: OK Failing tests goldenVsFile: FAIL Files 'example/golden/fail/goldenVsFile.golden' and 'example/golden/fail/goldenVsFile.actual' differ goldenVsFileDiff: FAIL 1d0 < 1 4d2 < 4 9d6 < 9 16d12 < 16 25d20 < 25 36d30 < 36 49d42 < 49 64d56 < 64 81d72 < 81 100d90 < 100 121d110 < 121 144d132 < 144 169d156 < Use --accept or increase --size-cutoff to see full output. goldenVsString: FAIL Test output was different from 'example/golden/fail/goldenVsString.golden'. It was: 2 3 5 6 7 8 10 11 12 13 14 15 17 18 19 20 21 22 23 24 26 27 28 29 30 31 32 33 34 35 37 38 39 40 41 42 43 44 45 46 47 48 50 51 52 53 54 55 56 Use --accept or increase --size-cutoff to see full output. goldenVsStringDiff: FAIL Test output was different from 'example/golden/fail/goldenVsStringDiff.golden'. Output of ["diff","example/golden/fail/goldenVsStringDiff.golden","/tmp/goldenVsStringDiff.actual"]: 1d0 < 1 4d2 < 4 9d6 < 9 16d12 < 16 25d20 < 25 36d30 < 36 49d42 < 49 64d56 < 64 81d72 < 81 100d90 < 100 121d110 < 121 144d132 < 144 169d156 < Use --accept or increase --size-cutoff to see full output. 4 out of 8 tests failed tasty-golden-2.3.3.2/tests/golden/with-accept.golden0000644000000000000000000000062113623745465020511 0ustar0000000000000000Tests Successful tests goldenVsFile: OK goldenVsFileDiff: OK goldenVsString: OK goldenVsStringDiff: OK Failing tests goldenVsFile: OK Accepted the new version goldenVsFileDiff: OK Accepted the new version goldenVsString: OK Accepted the new version goldenVsStringDiff: OK Accepted the new version All 8 tests passed