hspec-golden-aeson-0.4.0.0: Use tests to monitor changes in Aeson serialization

Copyright(c) Plow Technologies 2016
LicenseBSD3
Maintainermchaver@gmail.com
StabilityBeta
Safe HaskellNone
LanguageHaskell2010

Test.Aeson.GenericSpecs

Contents

Description

This package provides tools for testing Aeson serialization.

  • Test that ToJSON and FromJSON instances are isomorphic.
  • Alert you when unexpected changes in Aeson serialization occur.
  • Record JSON formatting of Haskell types.

Synopsis

Arbitrary testing

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

Tests to ensure that JSON encoding has not unintentionally changed. This could be caused by the following:

  • A type's instances of ToJSON or FromJSON have changed.
  • Selectors have been edited, added or deleted.
  • You have changed version of Aeson the way Aeson serialization has changed works.

If you run this function and the golden files do not exist, it will create them for each constructor. It they do exist, it will compare with golden file if it exists. Golden file encodes json format of a type. It is recommended that you put the golden files under revision control to help monitor changes.

roundtripSpecs :: forall a. (Typeable a, Arbitrary a, ToJSON a, FromJSON a) => Proxy a -> Spec Source #

A roundtrip test to check whether values of the given type can be successfully converted to JSON and back to a Haskell value.

roundtripSpecs will

  • create random values (using Arbitrary),
  • convert them into JSON (using ToJSON),
  • read them back into Haskell (using FromJSON) and
  • make sure that the result is the same as the value it started with (using Eq).

roundtripAndGoldenSpecs :: forall a. (Arbitrary a, ToJSON a, FromJSON a, Typeable a) => Proxy a -> Spec Source #

run roundtrip and golden test for a type. sampleSize is used only when creating the golden file. When it is compared, the sampleSize is derived from the file.

ToADTArbitrary testing

goldenADTSpecs :: forall a. (ToADTArbitrary a, Eq a, Show a, ToJSON a, FromJSON a) => Settings -> Proxy a -> Spec Source #

Tests to ensure that JSON encoding has not unintentionally changed. This could be caused by the following:

  • A type's instances of ToJSON or FromJSON have changed.
  • Selectors have been edited, added or deleted.
  • You have changed version of Aeson the way Aeson serialization has changed works.

If you run this function and the golden files do not exist, it will create them for each constructor. It they do exist, it will compare with golden file if it exists. Golden file encodes json format of a type. It is recommended that you put the golden files under revision control to help monitor changes.

roundtripADTSpecs :: forall a. (ToADTArbitrary a, Eq a, Show a, ToJSON a, FromJSON a) => Proxy a -> Spec Source #

A roundtrip test to check whether values of all of constructors of the given type can be successfully converted to JSON and back to a Haskell value.

roundtripADTSpecs will

  • create random values for each constructor using ToADTArbitrary,
  • convert them into JSON using ToJSON,
  • read them back into Haskell using FromJSON and
  • make sure that the result is the same as the value it started with using Eq.

roundtripAndGoldenADTSpecs :: forall a. (ToADTArbitrary a, Eq a, Show a, ToJSON a, FromJSON a) => Proxy a -> Spec Source #

run roundtrip and golden tests for all constructors of a type. sampleSize is used only when creating the golden files. When they are compared, the sampleSize is derived from the file.

Make Files

mkGoldenFileForType :: forall a. (ToJSON a, ToADTArbitrary a) => Int -> Proxy a -> FilePath -> IO () Source #

Make a Golden File for the Proxy of a type if the file does not exist.

Util

shouldBeIdentity :: (Eq a, Show a, Arbitrary a) => Proxy a -> (a -> IO a) -> Property Source #

hspec style combinator to easily write tests that check the a given operation returns the same value it was given, e.g. roundtrip tests.

data GoldenDirectoryOption Source #

A custom directory name or a preselected directory name.

data Settings Source #

Constructors

Settings 

Fields

defaultSettings :: Settings Source #

The default settings for general use cases.

re-exports

data Proxy k t :: forall k. k -> * #

A concrete, poly-kinded proxy type

Constructors

Proxy 

Instances

Monad (Proxy *) 

Methods

(>>=) :: Proxy * a -> (a -> Proxy * b) -> Proxy * b #

(>>) :: Proxy * a -> Proxy * b -> Proxy * b #

return :: a -> Proxy * a #

fail :: String -> Proxy * a #

Functor (Proxy *) 

Methods

fmap :: (a -> b) -> Proxy * a -> Proxy * b #

(<$) :: a -> Proxy * b -> Proxy * a #

Applicative (Proxy *) 

Methods

pure :: a -> Proxy * a #

(<*>) :: Proxy * (a -> b) -> Proxy * a -> Proxy * b #

(*>) :: Proxy * a -> Proxy * b -> Proxy * b #

(<*) :: Proxy * a -> Proxy * b -> Proxy * a #

Foldable (Proxy *) 

Methods

fold :: Monoid m => Proxy * m -> m #

foldMap :: Monoid m => (a -> m) -> Proxy * a -> m #

foldr :: (a -> b -> b) -> b -> Proxy * a -> b #

foldr' :: (a -> b -> b) -> b -> Proxy * a -> b #

foldl :: (b -> a -> b) -> b -> Proxy * a -> b #

foldl' :: (b -> a -> b) -> b -> Proxy * a -> b #

foldr1 :: (a -> a -> a) -> Proxy * a -> a #

foldl1 :: (a -> a -> a) -> Proxy * a -> a #

toList :: Proxy * a -> [a] #

null :: Proxy * a -> Bool #

length :: Proxy * a -> Int #

elem :: Eq a => a -> Proxy * a -> Bool #

maximum :: Ord a => Proxy * a -> a #

minimum :: Ord a => Proxy * a -> a #

sum :: Num a => Proxy * a -> a #

product :: Num a => Proxy * a -> a #

Generic1 (Proxy *) 

Associated Types

type Rep1 (Proxy * :: * -> *) :: * -> * #

Methods

from1 :: Proxy * a -> Rep1 (Proxy *) a #

to1 :: Rep1 (Proxy *) a -> Proxy * a #

FromJSON1 (Proxy *) 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Proxy * a) #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Proxy * a] #

ToJSON1 (Proxy *) 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Proxy * a -> Value #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Proxy * a] -> Value #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Proxy * a -> Encoding #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Proxy * a] -> Encoding #

Alternative (Proxy *) 

Methods

empty :: Proxy * a #

(<|>) :: Proxy * a -> Proxy * a -> Proxy * a #

some :: Proxy * a -> Proxy * [a] #

many :: Proxy * a -> Proxy * [a] #

MonadPlus (Proxy *) 

Methods

mzero :: Proxy * a #

mplus :: Proxy * a -> Proxy * a -> Proxy * a #

Eq1 (Proxy *)

Since: 4.9.0.0

Methods

liftEq :: (a -> b -> Bool) -> Proxy * a -> Proxy * b -> Bool #

Ord1 (Proxy *)

Since: 4.9.0.0

Methods

liftCompare :: (a -> b -> Ordering) -> Proxy * a -> Proxy * b -> Ordering #

Read1 (Proxy *)

Since: 4.9.0.0

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Proxy * a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Proxy * a] #

Show1 (Proxy *)

Since: 4.9.0.0

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Proxy * a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Proxy * a] -> ShowS #

Hashable1 (Proxy *) 

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Proxy * a -> Int #

Bounded (Proxy k s) 

Methods

minBound :: Proxy k s #

maxBound :: Proxy k s #

Enum (Proxy k s) 

Methods

succ :: Proxy k s -> Proxy k s #

pred :: Proxy k s -> Proxy k s #

toEnum :: Int -> Proxy k s #

fromEnum :: Proxy k s -> Int #

enumFrom :: Proxy k s -> [Proxy k s] #

enumFromThen :: Proxy k s -> Proxy k s -> [Proxy k s] #

enumFromTo :: Proxy k s -> Proxy k s -> [Proxy k s] #

enumFromThenTo :: Proxy k s -> Proxy k s -> Proxy k s -> [Proxy k s] #

Eq (Proxy k s) 

Methods

(==) :: Proxy k s -> Proxy k s -> Bool #

(/=) :: Proxy k s -> Proxy k s -> Bool #

Ord (Proxy k s) 

Methods

compare :: Proxy k s -> Proxy k s -> Ordering #

(<) :: Proxy k s -> Proxy k s -> Bool #

(<=) :: Proxy k s -> Proxy k s -> Bool #

(>) :: Proxy k s -> Proxy k s -> Bool #

(>=) :: Proxy k s -> Proxy k s -> Bool #

max :: Proxy k s -> Proxy k s -> Proxy k s #

min :: Proxy k s -> Proxy k s -> Proxy k s #

Read (Proxy k s) 
Show (Proxy k s) 

Methods

showsPrec :: Int -> Proxy k s -> ShowS #

show :: Proxy k s -> String #

showList :: [Proxy k s] -> ShowS #

Ix (Proxy k s) 

Methods

range :: (Proxy k s, Proxy k s) -> [Proxy k s] #

index :: (Proxy k s, Proxy k s) -> Proxy k s -> Int #

unsafeIndex :: (Proxy k s, Proxy k s) -> Proxy k s -> Int

inRange :: (Proxy k s, Proxy k s) -> Proxy k s -> Bool #

rangeSize :: (Proxy k s, Proxy k s) -> Int #

unsafeRangeSize :: (Proxy k s, Proxy k s) -> Int

Generic (Proxy k t) 

Associated Types

type Rep (Proxy k t) :: * -> * #

Methods

from :: Proxy k t -> Rep (Proxy k t) x #

to :: Rep (Proxy k t) x -> Proxy k t #

Semigroup (Proxy k s) 

Methods

(<>) :: Proxy k s -> Proxy k s -> Proxy k s #

sconcat :: NonEmpty (Proxy k s) -> Proxy k s #

stimes :: Integral b => b -> Proxy k s -> Proxy k s #

Monoid (Proxy k s) 

Methods

mempty :: Proxy k s #

mappend :: Proxy k s -> Proxy k s -> Proxy k s #

mconcat :: [Proxy k s] -> Proxy k s #

Hashable (Proxy * a) 

Methods

hashWithSalt :: Int -> Proxy * a -> Int #

hash :: Proxy * a -> Int #

FromJSON (Proxy k a) 

Methods

parseJSON :: Value -> Parser (Proxy k a) #

parseJSONList :: Value -> Parser [Proxy k a] #

ToJSON (Proxy k a) 

Methods

toJSON :: Proxy k a -> Value #

toEncoding :: Proxy k a -> Encoding #

toJSONList :: [Proxy k a] -> Value #

toEncodingList :: [Proxy k a] -> Encoding #

type Rep1 (Proxy *) 
type Rep1 (Proxy *) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) U1)
type Rep (Proxy k t) 
type Rep (Proxy k t) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) U1)