hspec-golden-aeson-0.9.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

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. (Arbitrary 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.

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

roundtripAndGoldenSpecs with custom settings.

roundtripAndGoldenADTSpecs :: forall a. (Arbitrary 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.

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

roundtripAndGoldenADTSpecs with custom settings.

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.

Constructors

CustomDirectoryName String 
GoldenDirectory 

data Settings Source #

Constructors

Settings 

Fields

defaultSettings :: Settings Source #

The default settings for general use cases.

re-exports

data Proxy (t :: k) #

Constructors

Proxy 

Instances

Instances details
Generic1 (Proxy :: k -> Type) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Proxy :: k -> Type

Methods

from1 :: forall (a :: k0). Proxy a -> Rep1 Proxy a

to1 :: forall (a :: k0). Rep1 Proxy a -> Proxy a

Monad (Proxy :: Type -> Type) 
Instance details

Defined in Data.Proxy

Methods

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

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

return :: a -> Proxy a

Functor (Proxy :: Type -> Type) 
Instance details

Defined in Data.Proxy

Methods

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

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

Applicative (Proxy :: Type -> Type) 
Instance details

Defined in Data.Proxy

Methods

pure :: a -> Proxy a

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

liftA2 :: (a -> b -> c) -> Proxy a -> Proxy b -> Proxy c

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

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

Foldable (Proxy :: Type -> Type) 
Instance details

Defined in Data.Foldable

Methods

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

foldMap :: Monoid m => (a -> m) -> Proxy a -> 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

Traversable (Proxy :: Type -> Type) 
Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Proxy a -> f (Proxy b)

sequenceA :: Applicative f => Proxy (f a) -> f (Proxy a)

mapM :: Monad m => (a -> m b) -> Proxy a -> m (Proxy b)

sequence :: Monad m => Proxy (m a) -> m (Proxy a)

Alternative (Proxy :: Type -> Type) 
Instance details

Defined in Data.Proxy

Methods

empty :: Proxy a

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

some :: Proxy a -> Proxy [a]

many :: Proxy a -> Proxy [a]

MonadPlus (Proxy :: Type -> Type) 
Instance details

Defined in Data.Proxy

Methods

mzero :: Proxy a

mplus :: Proxy a -> Proxy a -> Proxy a

FromJSON1 (Proxy :: Type -> Type) 
Instance details

Defined in Data.Aeson.Types.FromJSON

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 :: Type -> Type) 
Instance details

Defined in Data.Aeson.Types.ToJSON

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

Hashable1 (Proxy :: Type -> Type) 
Instance details

Defined in Data.Hashable.Class

Methods

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

Eq1 (Proxy :: Type -> Type) 
Instance details

Defined in Data.Functor.Classes

Methods

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

Ord1 (Proxy :: Type -> Type) 
Instance details

Defined in Data.Functor.Classes

Methods

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

Read1 (Proxy :: Type -> Type) 
Instance details

Defined in Data.Functor.Classes

Methods

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

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

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Proxy a)

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Proxy a]

Show1 (Proxy :: Type -> Type) 
Instance details

Defined in Data.Functor.Classes

Methods

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

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

Bounded (Proxy t) 
Instance details

Defined in Data.Proxy

Methods

minBound :: Proxy t

maxBound :: Proxy t

Enum (Proxy s) 
Instance details

Defined in Data.Proxy

Methods

succ :: Proxy s -> Proxy s

pred :: Proxy s -> Proxy s

toEnum :: Int -> Proxy s

fromEnum :: Proxy s -> Int

enumFrom :: Proxy s -> [Proxy s]

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

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

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

Eq (Proxy s) 
Instance details

Defined in Data.Proxy

Methods

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

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

Ord (Proxy s) 
Instance details

Defined in Data.Proxy

Methods

compare :: Proxy s -> Proxy s -> Ordering

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

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

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

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

max :: Proxy s -> Proxy s -> Proxy s

min :: Proxy s -> Proxy s -> Proxy s

Read (Proxy t) 
Instance details

Defined in Data.Proxy

Methods

readsPrec :: Int -> ReadS (Proxy t)

readList :: ReadS [Proxy t]

readPrec :: ReadPrec (Proxy t)

readListPrec :: ReadPrec [Proxy t]

Show (Proxy s) 
Instance details

Defined in Data.Proxy

Methods

showsPrec :: Int -> Proxy s -> ShowS

show :: Proxy s -> String

showList :: [Proxy s] -> ShowS

Ix (Proxy s) 
Instance details

Defined in Data.Proxy

Methods

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

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

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

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

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

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

Generic (Proxy t) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Proxy t) :: Type -> Type

Methods

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

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

Semigroup (Proxy s) 
Instance details

Defined in Data.Proxy

Methods

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

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

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

Monoid (Proxy s) 
Instance details

Defined in Data.Proxy

Methods

mempty :: Proxy s

mappend :: Proxy s -> Proxy s -> Proxy s

mconcat :: [Proxy s] -> Proxy s

FromJSON (Proxy a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Proxy a)

parseJSONList :: Value -> Parser [Proxy a]

ToJSON (Proxy a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Proxy a -> Value

toEncoding :: Proxy a -> Encoding

toJSONList :: [Proxy a] -> Value

toEncodingList :: [Proxy a] -> Encoding

Hashable (Proxy a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Proxy a -> Int

hash :: Proxy a -> Int

type Rep1 (Proxy :: k -> Type) 
Instance details

Defined in GHC.Generics

type Rep1 (Proxy :: k -> Type) = D1 ('MetaData "Proxy" "Data.Proxy" "base" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: k -> Type))
type Rep (Proxy t) 
Instance details

Defined in GHC.Generics

type Rep (Proxy t) = D1 ('MetaData "Proxy" "Data.Proxy" "base" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: Type -> Type))