Copyright | (c) Plow Technologies 2016 |
---|---|
License | BSD3 |
Maintainer | mchaver@gmail.com |
Stability | Beta |
Safe Haskell | None |
Language | Haskell2010 |
This package provides tools for testing Aeson serialization.
- Test that
ToJSON
andFromJSON
instances are isomorphic. - Alert you when unexpected changes in Aeson serialization occur.
- Record JSON formatting of Haskell types.
Synopsis
- goldenSpecs :: (Typeable a, Arbitrary a, ToJSON a, FromJSON a) => Settings -> Proxy a -> Spec
- roundtripSpecs :: forall a. (Typeable a, Arbitrary a, ToJSON a, FromJSON a) => Proxy a -> Spec
- roundtripAndGoldenSpecs :: forall a. (Arbitrary a, ToJSON a, FromJSON a, Typeable a) => Proxy a -> Spec
- goldenADTSpecs :: forall a. (ToADTArbitrary a, Eq a, Show a, ToJSON a, FromJSON a) => Settings -> Proxy a -> Spec
- roundtripADTSpecs :: forall a. (Arbitrary a, ToADTArbitrary a, Eq a, Show a, ToJSON a, FromJSON a) => Proxy a -> Spec
- roundtripAndGoldenSpecsWithSettings :: forall a. (Arbitrary a, ToJSON a, FromJSON a, Typeable a) => Settings -> Proxy a -> Spec
- roundtripAndGoldenADTSpecs :: forall a. (Arbitrary a, ToADTArbitrary a, Eq a, Show a, ToJSON a, FromJSON a) => Proxy a -> Spec
- roundtripAndGoldenADTSpecsWithSettings :: forall a. (Arbitrary a, ToADTArbitrary a, Eq a, Show a, ToJSON a, FromJSON a) => Settings -> Proxy a -> Spec
- mkGoldenFileForType :: forall a. (ToJSON a, ToADTArbitrary a) => Int -> Proxy a -> FilePath -> IO ()
- shouldBeIdentity :: (Eq a, Show a, Arbitrary a) => Proxy a -> (a -> IO a) -> Property
- data GoldenDirectoryOption
- = CustomDirectoryName String
- | GoldenDirectory
- data Settings = Settings {}
- defaultSettings :: Settings
- data Proxy (t :: k) = Proxy
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
orFromJSON
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
orFromJSON
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.
Settings | |
|
defaultSettings :: Settings Source #
The default settings for general use cases.
re-exports
Instances
Generic1 (Proxy :: k -> Type) | |
Monad (Proxy :: Type -> Type) | |
Functor (Proxy :: Type -> Type) | |
Applicative (Proxy :: Type -> Type) | |
Foldable (Proxy :: Type -> Type) | |
Defined in Data.Foldable 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 elem :: Eq a => a -> Proxy a -> Bool maximum :: Ord a => Proxy a -> a | |
Traversable (Proxy :: Type -> Type) | |
Alternative (Proxy :: Type -> Type) | |
MonadPlus (Proxy :: Type -> Type) | |
FromJSON1 (Proxy :: Type -> Type) | |
Defined in Data.Aeson.Types.FromJSON 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) | |
Defined in Data.Aeson.Types.ToJSON 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) | |
Defined in Data.Hashable.Class liftHashWithSalt :: (Int -> a -> Int) -> Int -> Proxy a -> Int | |
Eq1 (Proxy :: Type -> Type) | |
Defined in Data.Functor.Classes | |
Ord1 (Proxy :: Type -> Type) | |
Defined in Data.Functor.Classes liftCompare :: (a -> b -> Ordering) -> Proxy a -> Proxy b -> Ordering | |
Read1 (Proxy :: Type -> Type) | |
Defined in Data.Functor.Classes 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) | |
Defined in Data.Functor.Classes liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Proxy a -> ShowS liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Proxy a] -> ShowS | |
Bounded (Proxy t) | |
Defined in Data.Proxy | |
Enum (Proxy s) | |
Defined in Data.Proxy | |
Eq (Proxy s) | |
Ord (Proxy s) | |
Read (Proxy t) | |
Defined in Data.Proxy | |
Show (Proxy s) | |
Ix (Proxy s) | |
Generic (Proxy t) | |
Semigroup (Proxy s) | |
Monoid (Proxy s) | |
FromJSON (Proxy a) | |
Defined in Data.Aeson.Types.FromJSON parseJSON :: Value -> Parser (Proxy a) parseJSONList :: Value -> Parser [Proxy a] | |
ToJSON (Proxy a) | |
Defined in Data.Aeson.Types.ToJSON toEncoding :: Proxy a -> Encoding toJSONList :: [Proxy a] -> Value toEncodingList :: [Proxy a] -> Encoding | |
Hashable (Proxy a) | |
Defined in Data.Hashable.Class hashWithSalt :: Int -> Proxy a -> Int | |
type Rep1 (Proxy :: k -> Type) | |
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) | |
Defined in GHC.Generics type Rep (Proxy t) = D1 ('MetaData "Proxy" "Data.Proxy" "base" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: Type -> Type)) |