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

Safe HaskellNone
LanguageHaskell2010

Test.Aeson.GenericSpecs

Contents

Synopsis

Arbitrary testing

goldenSpecs :: (Eq a, Show a, Typeable a, Arbitrary a, ToJSON a, FromJSON a) => Int -> 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.

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

Allows to obtain a roundtrip test to check whether values of the given type can be successfully converted to JSON and back.

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, Eq a, Show a, ToJSON a, FromJSON a, Typeable a) => Int -> 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, Arbitrary a, ToJSON a, FromJSON a) => Int -> Proxy a -> Spec Source #

for a type a, create a set of golden files if they do not exist, compare with golden file if it exists. Golden file encodes json format of a type

roundtripADTSpecs :: forall a. (ToADTArbitrary a, Eq a, Show 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.

roundtripAndGoldenADTSpecs :: forall a. (Arbitrary a, ToADTArbitrary a, Eq a, Show a, ToJSON a, FromJSON a) => Int -> 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.

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.

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 #

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 #

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 #

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)