safe-json-1.1.3.1: Automatic JSON format versioning
Copyright(c) 2019 Felix Paulusma
LicenseMIT
Maintainerfelix.paulusma@gmail.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Data.SafeJSON.Test

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:

Expand
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 :: forall a. (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 b, Arbitrary b, SafeJSON a, Migrate a, MigrateFrom a ~ b) Source #

Constraints for migrating from a previous version

type TestReverseMigrate a b = (Eq a, Show b, Arbitrary b, 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:

Expand
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:

Expand
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:

Expand

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 (t :: k) #

Proxy is a type that holds no data, but has a phantom parameter of arbitrary type (or even kind). Its use is to provide type information, even though there is no value available of that type (or it may be too costly to create one).

Historically, Proxy :: Proxy a is a safer alternative to the undefined :: a idiom.

>>> Proxy :: Proxy (Void, Int -> Int)
Proxy

Proxy can even hold types of higher kinds,

>>> Proxy :: Proxy Either
Proxy
>>> Proxy :: Proxy Functor
Proxy
>>> Proxy :: Proxy complicatedStructure
Proxy

Constructors

Proxy 

Instances

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

Since: base-4.6.0.0

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)

Since: base-4.7.0.0

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)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

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

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

Applicative (Proxy :: Type -> Type)

Since: base-4.7.0.0

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)

Since: base-4.7.0.0

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)

Since: base-4.7.0.0

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

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 #

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

Alternative (Proxy :: Type -> Type)

Since: base-4.9.0.0

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)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

mzero :: Proxy a #

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

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

Defined in Data.Hashable.Class

Methods

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

Bounded (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

minBound :: Proxy t #

maxBound :: Proxy t #

Enum (Proxy s)

Since: base-4.7.0.0

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)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

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

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

Ord (Proxy s)

Since: base-4.7.0.0

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)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Show (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

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

show :: Proxy s -> String #

showList :: [Proxy s] -> ShowS #

Ix (Proxy s)

Since: base-4.7.0.0

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)

Since: base-4.6.0.0

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)

Since: base-4.9.0.0

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)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

mempty :: Proxy s #

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

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

Hashable (Proxy a) 
Instance details

Defined in Data.Hashable.Class

Methods

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

hash :: Proxy a -> Int #

ToJSON (Proxy a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

FromJSON (Proxy a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

SafeJSON (Proxy a) Source # 
Instance details

Defined in Data.SafeJSON.Internal

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