safe-json-0.1.0: Automatic JSON format versioning

Copyright(c) 2019 Felix Paulusma
LicenseMIT
Maintainerfelix.paulusma@gmail.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Data.SafeJSON.Test

Contents

Description

This module contains some functions to use for testing SafeJSON and Migrate instances.

Synopsis

Consistency checks

It is advised to always run testConsistency (or testConsistency') for all your types that have a SafeJSON instance.

Note that any type that fails this test will also fail any safeFromJSON parsing!

Using TypeApplications

testConsistency :: forall a. SafeJSON a => Assertion Source #

Useful in test suites. Will fail if anything in the chain of your types is inconsistent.

Example usage:

testConsistency @MyType

Using a Proxy argument

testConsistency' :: forall a. SafeJSON a => Proxy a -> Assertion Source #

Useful in test suites. Will fail if anything in the chain of your types is inconsistent.

Unit tests

Migration tests

These tests can be used to verify the implemented migrate function acts as expected.

testMigration :: (Show a, Eq a, Migrate a) => MigrateFrom a -> a -> Assertion Source #

Migration test. Mostly useful as regression test.

First argument is the older type which should turn into the second argument after migrating using migrate.

Just (migrate a) == parseMaybe (safeFromJSON . safeToJSON) a

testReverseMigration :: (Show a, Eq a, Migrate (Reverse a)) => MigrateFrom (Reverse a) -> a -> Assertion Source #

Similar to testMigration, but using Migrate (Reverse a).

The first argument here is the newer type, which will be migrated back to the expected second argument (older type).

Just (unReverse $ migrate a) == parseMaybe (safeFromJSON . safeToJSON) a

Synonyms

(<=?) :: (Show a, Eq a, Migrate a) => MigrateFrom a -> a -> Assertion infix 1 Source #

Operator synonymous with testMigration

(>=?) :: (Show a, Eq a, Migrate (Reverse a)) => MigrateFrom (Reverse a) -> a -> Assertion infix 1 Source #

Operator synonymous with testReverseMigration

Round trip tests

These tests can be used to verify that round trips are consistent. Either directly (testRoundTrip), through a forward migration (migrateRoundTrip) or a reversed backward migration (migrateReverseRoundTrip).

testRoundTrip :: (Show a, Eq a, SafeJSON a) => a -> Assertion Source #

Tests that the following holds:

Just a == parseMaybe (safeFromJSON . safeToJSON) a

migrateRoundTrip :: forall a. (Eq a, Show a, SafeJSON a, Migrate a) => MigrateFrom a -> Assertion Source #

This test verifies that direct migration, and migration through encoding and decoding to the newer type, is equivalent.

migrateReverseRoundTrip :: forall a. (Eq a, Show a, SafeJSON a, Migrate (Reverse a)) => MigrateFrom (Reverse a) -> Assertion Source #

Similar to migrateRoundTrip, but tests the migration from a newer type to the older type, in case of a Migrate (Reverse a) instance

Property tests

Useful if your types also have Arbitrary instances.

Constraint synonyms for readability

type TestMigrate a b = (Eq a, Show (MigrateFrom a), Arbitrary (MigrateFrom a), SafeJSON a, SafeJSON (MigrateFrom a), Migrate a, MigrateFrom a ~ b) Source #

Constraints for migrating from a previous version

type TestReverseMigrate a b = (Eq a, Show (MigrateFrom (Reverse a)), Arbitrary (MigrateFrom (Reverse a)), SafeJSON a, Migrate (Reverse a), MigrateFrom (Reverse a) ~ b) Source #

Constraints for migrating from a future version

Using TypeApplications

testRoundTripProp :: forall a. (Eq a, Show a, Arbitrary a, SafeJSON a) => String -> TestTree Source #

Tests that the following holds for all a:

Just a == parseMaybe (safeFromJSON . safeToJSON) a

Example usage:

testRoundTripProp @MyType s

migrateRoundTripProp :: forall a b. TestMigrate a b => String -> TestTree Source #

This test verifies that direct migration, and migration through encoding and decoding to the newer type, is equivalent for all a.

Just (migrate a) == parseMaybe (safeFromJSON . safeToJSON) a

Example usage:

migrateRoundTripProp @NewType @OldType s

migrateReverseRoundTripProp :: forall a b. TestReverseMigrate a b => String -> TestTree Source #

Similar to migrateRoundTripProp, but tests the migration from a newer type to the older type, in case of a Migrate (Reverse a) instance.

Just (unReverse $ migrate a) == parseMaybe (safeFromJSON . safeToJSON) a

Example usage:

Please also note the reversing of the type applications.

migrateReverseRoundTripProp @OldType @NewType s

Using a Proxy argument

testRoundTripProp' :: forall a. (Eq a, Show a, Arbitrary a, SafeJSON a) => Proxy a -> String -> TestTree Source #

Tests that the following holds for all a:

Just a == parseMaybe (safeFromJSON . safeToJSON) a

migrateRoundTripProp' :: forall a b. TestMigrate a b => Proxy (a, b) -> String -> TestTree Source #

This test verifies that direct migration, and migration through encoding and decoding to the newer type, is equivalent for all a.

Just (migrate a) == parseMaybe (safeFromJSON . safeToJSON) a

migrateReverseRoundTripProp' :: forall a b. TestReverseMigrate a b => Proxy (a, b) -> String -> TestTree Source #

Similar to 'migrateRoundTripProp, but tests the migration from a newer type to the older type, in case of a Migrate (Reverse a) instance.

Just (unReverse $ migrate a) == parseMaybe (safeFromJSON . safeToJSON) a

Re-export for convenience

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 #

Traversable (Proxy *) 

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) #

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 #

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)