sydtest-0.15.0.0: A modern testing framework for Haskell with good defaults and advanced testing features.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.Syd.Def.Golden

Synopsis

Documentation

pureGoldenByteStringFile :: FilePath -> ByteString -> GoldenTest ByteString Source #

Test that the given bytestring is the same as what we find in the given golden file.

goldenByteStringFile :: FilePath -> IO ByteString -> GoldenTest ByteString Source #

Test that the produced bytestring is the same as what we find in the given golden file.

pureGoldenLazyByteStringFile :: FilePath -> ByteString -> GoldenTest ByteString Source #

Test that the given lazy bytestring is the same as what we find in the given golden file.

Note: This converts the lazy bytestring to a strict bytestring first.

goldenLazyByteStringFile :: FilePath -> IO ByteString -> GoldenTest ByteString Source #

Test that the produced bytestring is the same as what we find in the given golden file.

Note: This converts the lazy bytestring to a strict bytestring first.

pureGoldenByteStringBuilderFile :: FilePath -> Builder -> GoldenTest Builder Source #

Test that the given lazy bytestring is the same as what we find in the given golden file.

Note: This converts the builder to a strict bytestring first.

goldenByteStringBuilderFile :: FilePath -> IO Builder -> GoldenTest Builder Source #

Test that the produced bytestring is the same as what we find in the given golden file.

Note: This converts the builder to a strict bytestring first.

pureGoldenTextFile :: FilePath -> Text -> GoldenTest Text Source #

Test that the given text is the same as what we find in the given golden file.

goldenTextFile :: FilePath -> IO Text -> GoldenTest Text Source #

Test that the produced text is the same as what we find in the given golden file.

pureGoldenStringFile :: FilePath -> String -> GoldenTest String Source #

Test that the given string is the same as what we find in the given golden file.

goldenStringFile :: FilePath -> IO String -> GoldenTest String Source #

Test that the produced string is the same as what we find in the given golden file.

goldenShowInstance :: Show a => FilePath -> a -> GoldenTest String Source #

Test that the show instance has not changed for the given value.

goldenPrettyShowInstance :: Show a => FilePath -> a -> GoldenTest String Source #

Test that the show instance has not changed for the given value, via ppShow.

goldenContext :: FilePath -> String Source #

The golden test context for adding context to a golden test assertion:

goldenTestCompare = \actual expected ->
  if actual == expected
    then Nothing
    else Just $ Context (stringsNotEqualButShouldHaveBeenEqual actual expected) (goldenContext fp)

data GoldenTest a Source #

A golden test for output of type a.

The purpose of a golden test is to ensure that the output of a certain process does not change even over time.

Golden tests can also be used to show how the output of a certain process changes over time and force code reviewers to review the diff that they see in the PR.

This works by saving a golden output in the repository somewhere, committing it, and then compare that golden output to the output that is currently being produced. You can use `--golden-reset` to have sydtest update the golden output by writing the current output.

Constructors

GoldenTest 

Fields

Instances

Instances details
IsTest (IO (GoldenTest a)) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (IO (GoldenTest a)) Source #

type Arg2 (IO (GoldenTest a)) Source #

Methods

runTest :: IO (GoldenTest a) -> TestRunSettings -> ProgressReporter -> ((Arg1 (IO (GoldenTest a)) -> Arg2 (IO (GoldenTest a)) -> IO ()) -> IO ()) -> IO TestRunResult Source #

IsTest (GoldenTest a) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (GoldenTest a) Source #

type Arg2 (GoldenTest a) Source #

IsTest (arg -> IO (GoldenTest a)) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (arg -> IO (GoldenTest a)) Source #

type Arg2 (arg -> IO (GoldenTest a)) Source #

Methods

runTest :: (arg -> IO (GoldenTest a)) -> TestRunSettings -> ProgressReporter -> ((Arg1 (arg -> IO (GoldenTest a)) -> Arg2 (arg -> IO (GoldenTest a)) -> IO ()) -> IO ()) -> IO TestRunResult Source #

IsTest (arg -> GoldenTest a) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (arg -> GoldenTest a) Source #

type Arg2 (arg -> GoldenTest a) Source #

Methods

runTest :: (arg -> GoldenTest a) -> TestRunSettings -> ProgressReporter -> ((Arg1 (arg -> GoldenTest a) -> Arg2 (arg -> GoldenTest a) -> IO ()) -> IO ()) -> IO TestRunResult Source #

IsTest (outerArgs -> innerArg -> IO (GoldenTest a)) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (outerArgs -> innerArg -> IO (GoldenTest a)) Source #

type Arg2 (outerArgs -> innerArg -> IO (GoldenTest a)) Source #

Methods

runTest :: (outerArgs -> innerArg -> IO (GoldenTest a)) -> TestRunSettings -> ProgressReporter -> ((Arg1 (outerArgs -> innerArg -> IO (GoldenTest a)) -> Arg2 (outerArgs -> innerArg -> IO (GoldenTest a)) -> IO ()) -> IO ()) -> IO TestRunResult Source #

IsTest (outerArgs -> innerArg -> GoldenTest a) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (outerArgs -> innerArg -> GoldenTest a) Source #

type Arg2 (outerArgs -> innerArg -> GoldenTest a) Source #

Methods

runTest :: (outerArgs -> innerArg -> GoldenTest a) -> TestRunSettings -> ProgressReporter -> ((Arg1 (outerArgs -> innerArg -> GoldenTest a) -> Arg2 (outerArgs -> innerArg -> GoldenTest a) -> IO ()) -> IO ()) -> IO TestRunResult Source #

type Arg1 (IO (GoldenTest a)) Source # 
Instance details

Defined in Test.Syd.Run

type Arg1 (IO (GoldenTest a)) = ()
type Arg1 (GoldenTest a) Source # 
Instance details

Defined in Test.Syd.Run

type Arg1 (GoldenTest a) = ()
type Arg2 (IO (GoldenTest a)) Source # 
Instance details

Defined in Test.Syd.Run

type Arg2 (IO (GoldenTest a)) = ()
type Arg2 (GoldenTest a) Source # 
Instance details

Defined in Test.Syd.Run

type Arg2 (GoldenTest a) = ()
type Arg1 (arg -> IO (GoldenTest a)) Source # 
Instance details

Defined in Test.Syd.Run

type Arg1 (arg -> IO (GoldenTest a)) = ()
type Arg1 (arg -> GoldenTest a) Source # 
Instance details

Defined in Test.Syd.Run

type Arg1 (arg -> GoldenTest a) = ()
type Arg1 (outerArgs -> innerArg -> IO (GoldenTest a)) Source # 
Instance details

Defined in Test.Syd.Run

type Arg1 (outerArgs -> innerArg -> IO (GoldenTest a)) = outerArgs
type Arg1 (outerArgs -> innerArg -> GoldenTest a) Source # 
Instance details

Defined in Test.Syd.Run

type Arg1 (outerArgs -> innerArg -> GoldenTest a) = outerArgs
type Arg2 (arg -> IO (GoldenTest a)) Source # 
Instance details

Defined in Test.Syd.Run

type Arg2 (arg -> IO (GoldenTest a)) = arg
type Arg2 (arg -> GoldenTest a) Source # 
Instance details

Defined in Test.Syd.Run

type Arg2 (arg -> GoldenTest a) = arg
type Arg2 (outerArgs -> innerArg -> IO (GoldenTest a)) Source # 
Instance details

Defined in Test.Syd.Run

type Arg2 (outerArgs -> innerArg -> IO (GoldenTest a)) = innerArg
type Arg2 (outerArgs -> innerArg -> GoldenTest a) Source # 
Instance details

Defined in Test.Syd.Run

type Arg2 (outerArgs -> innerArg -> GoldenTest a) = innerArg