armor-0.2.0.1: Prevent serialization backwards compatibility problems using golden tests
Safe HaskellSafe-Inferred
LanguageHaskell2010

Armor

Synopsis

Documentation

newtype Version a Source #

Version numbers are simple monotonically increasing positive integers.

Constructors

Version 

Fields

Instances

Instances details
Eq (Version a) Source # 
Instance details

Defined in Armor

Methods

(==) :: Version a -> Version a -> Bool #

(/=) :: Version a -> Version a -> Bool #

Ord (Version a) Source # 
Instance details

Defined in Armor

Methods

compare :: Version a -> Version a -> Ordering #

(<) :: Version a -> Version a -> Bool #

(<=) :: Version a -> Version a -> Bool #

(>) :: Version a -> Version a -> Bool #

(>=) :: Version a -> Version a -> Bool #

max :: Version a -> Version a -> Version a #

min :: Version a -> Version a -> Version a #

Read (Version a) Source # 
Instance details

Defined in Armor

Show (Version a) Source # 
Instance details

Defined in Armor

Methods

showsPrec :: Int -> Version a -> ShowS #

show :: Version a -> String #

showList :: [Version a] -> ShowS #

class Armored a where Source #

Core type class for armoring types. Includes a version and all the type's serializations that you want to armor.

Methods

version :: Version a Source #

Current version number for the data type.

serializations :: Map String (APrism' ByteString a) Source #

Map of serializations keyed by a unique ID used to refer to each serialization. A serialization is a tuple of (a -> ByteString) and (ByteString -> Maybe a). Represented here as a prism.

data ArmorMode Source #

The mode of operation for armor test cases.

Constructors

SaveOnly

Write test files for serializations that don't have them, but don't do any tests to verify that existing files are deserialized properly.

TestOnly

Run tests to verify that existing files are deserialized properly, but don't write any missing files.

SaveAndTest

Do both the save and test phases.

data ArmorConfig Source #

Config data for armor tests.

Constructors

ArmorConfig 

Fields

  • acArmorMode :: ArmorMode
     
  • acStoreDir :: FilePath

    Directory where all the test serializations are stored.

  • acNumVersions :: Maybe Word

    How many versions back to test for backwards compatibility. A value of Just 0 means that it only tests that the current version satisfies parse . render == id. Just 1 means that it will verify that the previous version can still be parse. Just 2 the previous two versions, etc. Nothing means that all versions will be tested.

defArmorConfig :: ArmorConfig Source #

Default value for ArmorConfig.

testArmor :: (Eq a, Show a, Typeable a, Armored a) => ArmorConfig -> String -> a -> Test Source #

Tests the serialization backwards compatibility of a data type by storing serialized representations in .test files to be checked into your project's version control.

First, this function checks the directory acStoreDir for the existence of a file foo-000.test. If it doesn't exist, it creates it for each serialization with the serialized representation of the val parameter.

Next, it checks that the serialized formats in the most recent acNumVersions of the stored .test files are parsable by the current version of the serialization.

testArmorMany :: (Eq a, Show a, Typeable a, Armored a) => ArmorConfig -> Map String a -> Test Source #

Same as testArmor, but more convenient for testing several values of the same type.

testSerialization Source #

Arguments

:: forall a. (Eq a, Show a, Typeable a, Armored a) 
=> ArmorConfig 
-> (GoldenTest a -> FilePath)

Customizable location where the serializations will be stored. We recommend goldenFilePath as a standard out-of-the-box scheme.

-> String 
-> (String, APrism' ByteString a) 
-> a 
-> Assertion 

Lower level assertion function that works for a wider array of test frameworks.

This function can make two different assertions. It fails if the values fail to parse, and it asserts that the values are equal to the expected value. This latter assertion is only done for the most recent version because changes that impact the structure of a data type can result in erroneous failures due to changes in the order that the test cases are generated.

In other words, if you make an innocuous change like adding a constructor and start getting "values didn't match" failures, all you need to do is bump the data type's version. Armor will still guarantee that those serializations parse properly but the incorrect value failures will be suppressed.

data GoldenTest a Source #

Data structure that holds all the values needed for a golden test

goldenFilePath :: Typeable a => GoldenTest a -> FilePath Source #

Constructs the FilePath where the serialization will be stored (relative to the base directory defined in ArmorConfig).

This function uses typeOf as a part of the directory hierarchy to disambiguate tests for different data types. typeOf can contain single quotes, spaces, and parenthesis in the case of type constructors that have type variables so we only take the first alphanumeric characters so that the paths will be meaningful to humans and then add four characters of the type's hash for disambiguation.