tasty-golden-2.3.1.2/Test/0000755000000000000000000000000013211262541013371 5ustar0000000000000000tasty-golden-2.3.1.2/Test/Tasty/0000755000000000000000000000000013211264143014475 5ustar0000000000000000tasty-golden-2.3.1.2/Test/Tasty/Golden/0000755000000000000000000000000013211263677015720 5ustar0000000000000000tasty-golden-2.3.1.2/tests/0000755000000000000000000000000013211262541013614 5ustar0000000000000000tasty-golden-2.3.1.2/Test/Tasty/Golden.hs0000644000000000000000000001751413211264143016251 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. -} module Test.Tasty.Golden ( goldenVsFile , goldenVsString , goldenVsFileDiff , goldenVsStringDiff , writeBinaryFile , findByExtension ) where import Test.Tasty.Providers import Test.Tasty.Golden.Advanced import Text.Printf import qualified Data.ByteString as BS import qualified Data.ByteString.Lazy as LBS 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 Control.Applicative import Control.DeepSeq import qualified Data.Set as Set -- | Compare a given file contents against the golden file contents 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 (BS.readFile ref) (act >> BS.readFile new) cmp upd where cmp = simpleCmp $ printf "Files '%s' and '%s' differ" ref new upd = BS.writeFile ref -- | Compare a given string against the golden file 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 = goldenTest name (BS.readFile ref) (LBS.toStrict <$> act) cmp upd where cmp x y = simpleCmp msg x y where msg = printf "Test output was different from '%s'. It was: %s" ref (show y) upd = BS.writeFile 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 = goldenTest name (return ()) act cmp upd where cmd = cmdf ref new cmp _ _ | null cmd = error "goldenVsFileDiff: empty command line" cmp _ _ = 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 <- hGetContents sout evaluate . rnf $ out r <- waitForProcess pid return $ case r of ExitSuccess -> Nothing _ -> Just out upd _ = BS.readFile new >>= BS.writeFile 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 = goldenTest name (BS.readFile ref) (LBS.toStrict <$> act) cmp upd where template = takeFileName ref <.> "actual" cmp _ actBS = withSystemTempFile template $ \tmpFile tmpHandle -> do -- Write act output to temporary ("new") file BS.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 <- hGetContents sout evaluate . rnf $ out r <- waitForProcess pid return $ case r of ExitSuccess -> Nothing _ -> Just (printf "Test output was different from '%s'. Output of %s:\n%s" ref (show cmd) out) upd = BS.writeFile ref -- | 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 [] tasty-golden-2.3.1.2/Test/Tasty/Golden/Advanced.hs0000644000000000000000000000211213211262541017742 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.1.2/Test/Tasty/Golden/Manage.hs0000644000000000000000000000212313211262541017427 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.1.2/Test/Tasty/Golden/Internal.hs0000644000000000000000000000460113211262541020016 0ustar0000000000000000{-# LANGUAGE RankNTypes, ExistentialQuantification, DeriveDataTypeable, MultiParamTypeClasses, GeneralizedNewtypeDeriving #-} module Test.Tasty.Golden.Internal where import Control.DeepSeq import Control.Exception import Data.Typeable (Typeable) import Options.Applicative import Data.Monoid import Data.Tagged import Data.Proxy import System.IO.Error (isDoesNotExistError) import Test.Tasty.Providers import Test.Tasty.Options -- | 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 . safeRead optionName = return "accept" optionHelp = return "Accept current results of golden tests" optionCLParser = fmap AcceptTests $ switch ( long (untag (optionName :: Tagged AcceptTests String)) <> help (untag (optionHelp :: Tagged AcceptTests String)) ) instance IsTest Golden where run opts golden _ = runGolden golden (lookupOption opts) testOptions = return [Option (Proxy :: Proxy AcceptTests)] runGolden :: Golden -> AcceptTests -> IO Result runGolden (Golden getGolden getTested cmp update) (AcceptTests accept) = 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 -> 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 "" tasty-golden-2.3.1.2/tests/test.hs0000644000000000000000000000134713211262541015134 0ustar0000000000000000import Test.Tasty import Test.Tasty.HUnit import Test.Tasty.Golden import System.IO.Temp import System.FilePath import System.Directory import Data.List (sort) touch f = writeFile f "" main = defaultMain $ testCase "findByExtension" $ withSystemTempDirectory "golden-test" $ \basedir -> do setCurrentDirectory basedir createDirectory ("d1") createDirectory ("d1" "d2") touch ("f1.c") touch ("f2.h") touch ("f2.exe") touch ("d1" "g1.c") touch ("d1" "d2" "h1.c") touch ("d1" "d2" "h1.exe") touch ("d1" "d2" "h1") files <- findByExtension [".c", ".h"] "." sort files @?= sort ["./d1/d2/h1.c","./d1/g1.c","./f1.c","./f2.h"] tasty-golden-2.3.1.2/LICENSE0000644000000000000000000000204313211262541013456 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.1.2/Setup.hs0000644000000000000000000000005613211262541014107 0ustar0000000000000000import Distribution.Simple main = defaultMain tasty-golden-2.3.1.2/tasty-golden.cabal0000644000000000000000000000347513215461214016063 0ustar0000000000000000name: tasty-golden version: 2.3.1.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 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.*, tasty >= 0.8, bytestring >= 0.10, process, mtl, optparse-applicative, filepath, temporary, tagged, deepseq, containers, directory, async 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 >= 0.8 , tasty-hunit , tasty-golden , filepath , directory , process , temporary-rc tasty-golden-2.3.1.2/CHANGELOG.md0000644000000000000000000000502113215461274014271 0ustar0000000000000000Changes ======= 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`)