Copyright | (c) 2019 Felix Paulusma |
---|---|
License | MIT |
Maintainer | felix.paulusma@gmail.com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
- testConsistency :: forall a. SafeJSON a => Assertion
- testConsistency' :: forall a. SafeJSON a => Proxy a -> Assertion
- testMigration :: (Show a, Eq a, Migrate a) => MigrateFrom a -> a -> Assertion
- testReverseMigration :: (Show a, Eq a, Migrate (Reverse a)) => MigrateFrom (Reverse a) -> a -> Assertion
- (<=?) :: (Show a, Eq a, Migrate a) => MigrateFrom a -> a -> Assertion
- (>=?) :: (Show a, Eq a, Migrate (Reverse a)) => MigrateFrom (Reverse a) -> a -> Assertion
- testRoundTrip :: forall a. (Show a, Eq a, SafeJSON a) => a -> Assertion
- migrateRoundTrip :: forall a. (Eq a, Show a, SafeJSON a, Migrate a) => MigrateFrom a -> Assertion
- migrateReverseRoundTrip :: forall a. (Eq a, Show a, SafeJSON a, Migrate (Reverse a)) => MigrateFrom (Reverse a) -> Assertion
- type TestMigrate a b = (Eq a, Show (MigrateFrom a), Arbitrary (MigrateFrom a), SafeJSON a, SafeJSON (MigrateFrom a), Migrate a, MigrateFrom a ~ b)
- type TestReverseMigrate a b = (Eq a, Show (MigrateFrom (Reverse a)), Arbitrary (MigrateFrom (Reverse a)), SafeJSON a, Migrate (Reverse a), MigrateFrom (Reverse a) ~ b)
- testRoundTripProp :: forall a. (Eq a, Show a, Arbitrary a, SafeJSON a) => String -> TestTree
- migrateRoundTripProp :: forall a b. TestMigrate a b => String -> TestTree
- migrateReverseRoundTripProp :: forall a b. TestReverseMigrate a b => String -> TestTree
- testRoundTripProp' :: forall a. (Eq a, Show a, Arbitrary a, SafeJSON a) => Proxy a -> String -> TestTree
- migrateRoundTripProp' :: forall a b. TestMigrate a b => Proxy (a, b) -> String -> TestTree
- migrateReverseRoundTripProp' :: forall a b. TestReverseMigrate a b => Proxy (a, b) -> String -> TestTree
- data Proxy k t :: forall k. k -> * = Proxy
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 :: 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 (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
Monad (Proxy *) | |
Functor (Proxy *) | |
Applicative (Proxy *) | |
Traversable (Proxy *) | |
Generic1 (Proxy *) | |
FromJSON1 (Proxy *) | |
ToJSON1 (Proxy *) | |
Alternative (Proxy *) | |
MonadPlus (Proxy *) | |
Hashable1 (Proxy *) | |
Bounded (Proxy k s) | |
Enum (Proxy k s) | |
Eq (Proxy k s) | |
Ord (Proxy k s) | |
Read (Proxy k s) | |
Show (Proxy k s) | |
Ix (Proxy k s) | |
Generic (Proxy k t) | |
Semigroup (Proxy k s) | |
Monoid (Proxy k s) | |
Hashable (Proxy * a) | |
FromJSON (Proxy k a) | |
ToJSON (Proxy k a) | |
SafeJSON (Proxy * a) Source # | |
type Rep1 (Proxy *) | |
type Rep (Proxy k t) | |