servant-aeson-specs-0.4.1: generic tests for aeson serialization in servant

Safe HaskellNone
LanguageHaskell2010

Test.Aeson.Internal.GoldenSpecs

Contents

Synopsis

Documentation

goldenSpecs :: (Eq a, Show a, Typeable a, Arbitrary a, ToJSON a, FromJSON a) => Proxy a -> Spec Source #

Allows to obtain tests that will try to ensure that the JSON encoding didn't change unintentionally. To this end goldenSpecs will

  • write a file golden.json/TYPENAME.json in the current directory containing a number of JSON-encoded sample values,
  • during subsequent tests it will encode the same sample values again and compare them with the saved golden encodings,
  • on failure it will create a file golden.json/TYPENAME.faulty.json for easy manual inspection.

You can consider putting the golden files under revision control. That way it'll be obvious when JSON encodings change.

createGoldenfile :: forall a. (Show a, Arbitrary a, ToJSON a) => Proxy a -> FilePath -> IO () Source #

setSeed :: Int -> Gen a -> Gen a Source #

compareWithGolden :: forall a. (Eq a, Show a, Typeable a, Arbitrary a, ToJSON a, FromJSON a) => Proxy a -> FilePath -> IO () Source #

RandomSamples

data RandomSamples a Source #

Constructors

RandomSamples 

Fields

Instances

Eq a => Eq (RandomSamples a) Source # 
Ord a => Ord (RandomSamples a) Source # 
Show a => Show (RandomSamples a) Source # 
Generic (RandomSamples a) Source # 

Associated Types

type Rep (RandomSamples a) :: * -> * #

ToJSON a => ToJSON (RandomSamples a) Source # 
FromJSON a => FromJSON (RandomSamples a) Source # 
type Rep (RandomSamples a) Source # 
type Rep (RandomSamples a) = D1 (MetaData "RandomSamples" "Test.Aeson.Internal.GoldenSpecs" "servant-aeson-specs-0.4.1-AsX1wyFthgUFU5mIoZzIg4" False) (C1 (MetaCons "RandomSamples" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "seed") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "samples") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [a]))))

mkRandomSamples :: forall a. Arbitrary a => Proxy a -> Int -> IO (RandomSamples a) Source #