hedgehog-golden-1.0.0: Golden testing capabilities for hedgehog using Aeson

Safe HaskellNone
LanguageHaskell2010

Hedgehog.Golden.Aeson

Contents

Description

This module can be used in order to create golden tests for Aeson serializers and deserializers

  {-# LANGUAGE TemplateHaskell #-}

  import           Hedgehog
  import qualified Hedgehog.Gen as Gen
  import qualified Hedgehog.Golden.Aeson as Aeson

  -- | A golden test for characters in the hex range
  prop_char_golden :: Property
  prop_char_golden = Aeson.goldenProperty Gen.hexit

  tests :: IO Bool
  tests = checkParallel $$discover
  
Synopsis

Golden tests for generators

goldenProperty :: forall a. HasCallStack => Typeable a => FromJSON a => ToJSON a => Gen a -> Property Source #

Run a golden test on the given generator

This will create a file in golden/TypeName.json.new in case it does not exist. If it does exist - the golden tests will be run against it

goldenProperty' :: forall a. HasCallStack => Typeable a => FromJSON a => ToJSON a => FilePath -> Gen a -> Property Source #

Same as goldenProperty but allows specifying the directory