hspec-golden-0.1.0.1: Golden tests for hspec

CopyrightStack Builders (c) 2019
LicenseMIT
Maintainercmotoche@stackbuilders.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Test.Hspec.Golden

Description

Golden tests store the expected output in a separated file. Each time a golden test is executed the output of the subject under test (SUT) is compared with the expected output. If the output of the SUT changes then the test will fail until the expected output is updated. We expose defaultGolden for output of type String. If your SUT has a different output, you can use Golden.

Synopsis

Documentation

data Golden str Source #

Golden tests parameters

import           Data.Text (Text)
import qualified Data.Text.IO as T

goldenText :: String -> Text -> Golden Text
goldenText name actualOutput =
  Golden {
    output = actualOutput,
    encodePretty = prettyText,
    writeToFile = T.writeFile,
    readFromFile = T.readFile,
    testName = name,
    directory = ".specific-golden-dir"
  }

describe "myTextFunc" $
  it "generates the right output with the right params" $
    goldenText "myTextFunc" (myTextFunc params)

Constructors

Golden 

Fields

Instances
Eq str => Example (Golden str) Source # 
Instance details

Defined in Test.Hspec.Golden

Associated Types

type Arg (Golden str) :: Type #

Methods

evaluateExample :: Golden str -> Params -> (ActionWith (Arg (Golden str)) -> IO ()) -> ProgressCallback -> IO Result #

Eq str => Example (arg -> Golden str) Source # 
Instance details

Defined in Test.Hspec.Golden

Associated Types

type Arg (arg -> Golden str) :: Type #

Methods

evaluateExample :: (arg -> Golden str) -> Params -> (ActionWith (Arg (arg -> Golden str)) -> IO ()) -> ProgressCallback -> IO Result #

type Arg (Golden str) Source # 
Instance details

Defined in Test.Hspec.Golden

type Arg (Golden str) = ()
type Arg (arg -> Golden str) Source # 
Instance details

Defined in Test.Hspec.Golden

type Arg (arg -> Golden str) = arg

defaultGolden :: String -> String -> Golden String Source #

An example of Golden tests which output is String

 describe "html" $ do
   context "given a valid generated html" $
     it "generates html" $
       defaultGolden "html" someHtml