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

Data.SafeJSON

Description

Please read the

README on GitHub

for an extensive explanation of this library, why and how to use it, and examples.

Synopsis

Conversion to/from versioned JSON

These functions are the workhorses of the library.

As long as a type has a SafeJSON instance and, if conversion from other types is required, a Migrate instance, these will make sure to add and read version numbers, and handle migration.

safeToJSON :: forall a. SafeJSON a => a -> Value Source #

Use this exactly how you would use toJSON from Data.Aeson. Though most use cases will probably use one of the encode functions from Data.Aeson.Safe.

safeToJSON will add a version tag to the Value created. If the Value resulting from safeTo (by default the same as toJSON) is an Object, an extra field with the version number will be added.

Example value:
  {"type":"test", "data":true}

Resulting object:
  {"!v": 1, "type":"test", "data":true}

If the resulting Value is not an Object, it will be wrapped in one, with a version field:

Example value:
  "arbitrary string"

Resulting object:
  {"~v": 1, "~d": "arbitrary string"}

This function does not check consistency of the SafeJSON instances. It is advised to always testConsistency for all your instances in a production setting.

safeFromJSON :: forall a. SafeJSON a => Value -> Parser a Source #

Use this exactly how you would use parseJSON from Data.Aeson. Though most use cases will probably use one of the decode functions from Data.Aeson.Safe.

safeFromJSON tries to find the version number in the JSON Value provided, find the appropriate parser and migrate the parsed result back to the requested type using Migrate instances.

If there is no version number (that means this can also happen with completely unrelated JSON messages), and there is a SafeJSON instance in the chain that has version defined as noVersion, it will try to parse that type.

N.B. If the consistency of the SafeJSON instance in question is faulty, this will always fail.

SafeJSON Class

This class, together with Migrate, is where the magic happens!

Using the SafeJSON class to define the form and expected migration to a type, and defining Migrate instances to describe how to handle the conversion from older versions (or maybe a newer version) to the type, you can be sure that your programs will still parse the JSON of types it is expecting.

class SafeJSON a where Source #

A type that can be converted from and to JSON with versioning baked in, using Migrate to automate migration between versions, reducing headaches when the need arrises to modify JSON formats while old formats can't simply be disregarded.

Minimal complete definition

Nothing

Methods

version :: Version a Source #

The version of the type.

Only used as a key so it must be unique (this is checked at run-time)

Version numbering doesn't have to be sequential or continuous.

The default version is 0 (zero).

kind :: Kind a Source #

The kind specifies how versions are dealt with. By default, values are tagged with version 0 and don't have any previous versions.

The default kind is base

safeTo :: a -> Contained Value Source #

This method defines how a value should be serialized without worrying about adding the version. The default implementation uses toJSON, but can be modified if need be.

This function cannot be used directly. Use safeToJSON, instead.

default safeTo :: ToJSON a => a -> Contained Value Source #

safeFrom :: Value -> Contained (Parser a) Source #

This method defines how a value should be parsed without also worrying about writing out the version tag. The default implementation uses parseJSON, but can be modified if need be.

This function cannot be used directly. Use safeFromJSON, instead.

default safeFrom :: FromJSON a => Value -> Contained (Parser a) Source #

typeName :: Proxy a -> String Source #

The name of the type. This is used in error message strings and the Profile report.

Doesn't have to be defined if your type is Typeable. The default implementation is typeName0. (cf. typeName1, typeName2, etc.)

default typeName :: Typeable a => Proxy a -> String Source #

objectProfile :: Profile a Source #

Version profile.

Shows the current version of the type and all supported versions it can migrate from.

Instances

Instances details
SafeJSON Bool Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON Char Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON Double Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON Float Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON Int Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON Int8 Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON Int16 Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON Int32 Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON Int64 Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON Integer Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON Natural Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON Ordering Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON Word Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON Word8 Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON Word16 Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON Word32 Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON Word64 Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON () Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON String Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON Version Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON Scientific Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON Text Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON UTCTime Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON Value Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON DotNetTime Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON Text Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON Void Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON CTime Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON IntSet Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON ZonedTime Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON LocalTime Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON TimeOfDay Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON NominalDiffTime Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON DiffTime Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON Day Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON UUID Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON a => SafeJSON [a] Source #

Lists and any other "container" are seen as only that: a container for SafeJSON values.

"Containers" are implemented in such a way that when parsing a collection of all migratable versions, the result will be a list of that type where each element has been migrated as appropriate.

Instance details

Defined in Data.SafeJSON.Internal

SafeJSON a => SafeJSON (Maybe a) Source # 
Instance details

Defined in Data.SafeJSON.Internal

(FromJSON a, ToJSON a, Integral a) => SafeJSON (Ratio a) Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON a => SafeJSON (Min a) Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON a => SafeJSON (Max a) Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON a => SafeJSON (First a) Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON a => SafeJSON (Last a) Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON a => SafeJSON (Identity a) Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON a => SafeJSON (Dual a) Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON a => SafeJSON (NonEmpty a) Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON a => SafeJSON (IntMap a) Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON a => SafeJSON (Tree a) Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON a => SafeJSON (Seq a) Source # 
Instance details

Defined in Data.SafeJSON.Internal

(SafeJSON a, Ord a) => SafeJSON (Set a) Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON a => SafeJSON (DList a) Source # 
Instance details

Defined in Data.SafeJSON.Internal

(SafeJSON a, Eq a, Hashable a) => SafeJSON (HashSet a) Source # 
Instance details

Defined in Data.SafeJSON.Internal

(SafeJSON a, Vector Vector a) => SafeJSON (Vector a) Source # 
Instance details

Defined in Data.SafeJSON.Internal

(SafeJSON a, Storable a) => SafeJSON (Vector a) Source # 
Instance details

Defined in Data.SafeJSON.Internal

(SafeJSON a, Prim a) => SafeJSON (Vector a) Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON a => SafeJSON (Vector a) Source # 
Instance details

Defined in Data.SafeJSON.Internal

(SafeJSON a, SafeJSON b) => SafeJSON (Either a b) Source # 
Instance details

Defined in Data.SafeJSON.Internal

(SafeJSON a, SafeJSON b) => SafeJSON (a, b) Source # 
Instance details

Defined in Data.SafeJSON.Internal

Methods

version :: Version (a, b) Source #

kind :: Kind (a, b) Source #

safeTo :: (a, b) -> Contained Value Source #

safeFrom :: Value -> Contained (Parser (a, b)) Source #

typeName :: Proxy (a, b) -> String Source #

internalConsistency :: Consistency (a, b)

objectProfile :: Profile (a, b) Source #

(Hashable a, FromJSONKey a, ToJSONKey a, Eq a, SafeJSON b) => SafeJSON (HashMap a b) Source # 
Instance details

Defined in Data.SafeJSON.Internal

(Ord k, FromJSONKey k, ToJSONKey k, SafeJSON a) => SafeJSON (Map k a) Source # 
Instance details

Defined in Data.SafeJSON.Internal

HasResolution a => SafeJSON (Fixed a) Source # 
Instance details

Defined in Data.SafeJSON.Internal

SafeJSON (Proxy a) Source # 
Instance details

Defined in Data.SafeJSON.Internal

(SafeJSON a, SafeJSON b, SafeJSON c) => SafeJSON (a, b, c) Source # 
Instance details

Defined in Data.SafeJSON.Internal

Methods

version :: Version (a, b, c) Source #

kind :: Kind (a, b, c) Source #

safeTo :: (a, b, c) -> Contained Value Source #

safeFrom :: Value -> Contained (Parser (a, b, c)) Source #

typeName :: Proxy (a, b, c) -> String Source #

internalConsistency :: Consistency (a, b, c)

objectProfile :: Profile (a, b, c) Source #

SafeJSON a => SafeJSON (Const a b) Source # 
Instance details

Defined in Data.SafeJSON.Internal

(SafeJSON a, SafeJSON b, SafeJSON c, SafeJSON d) => SafeJSON (a, b, c, d) Source # 
Instance details

Defined in Data.SafeJSON.Internal

Methods

version :: Version (a, b, c, d) Source #

kind :: Kind (a, b, c, d) Source #

safeTo :: (a, b, c, d) -> Contained Value Source #

safeFrom :: Value -> Contained (Parser (a, b, c, d)) Source #

typeName :: Proxy (a, b, c, d) -> String Source #

internalConsistency :: Consistency (a, b, c, d)

objectProfile :: Profile (a, b, c, d) Source #

(SafeJSON a, SafeJSON b, SafeJSON c, SafeJSON d, SafeJSON e) => SafeJSON (a, b, c, d, e) Source # 
Instance details

Defined in Data.SafeJSON.Internal

Methods

version :: Version (a, b, c, d, e) Source #

kind :: Kind (a, b, c, d, e) Source #

safeTo :: (a, b, c, d, e) -> Contained Value Source #

safeFrom :: Value -> Contained (Parser (a, b, c, d, e)) Source #

typeName :: Proxy (a, b, c, d, e) -> String Source #

internalConsistency :: Consistency (a, b, c, d, e)

objectProfile :: Profile (a, b, c, d, e) Source #

Contained

data Contained a Source #

This is an impenetrable container. A security measure used to ensure safeFrom and safeTo are never used directly. Instead, always use safeFromJSON and safeToJSON.

contain :: a -> Contained a Source #

Used when defining safeFrom or safeTo.

Defining safeFrom and safeTo

If the type doesn't already have FromJSON and ToJSON instances, the following functions can help in defining the safeFrom and safeTo methods.

safeFrom = containWithObject "MyType" $ \o ->
  MyType <$> o .:  "regular_value"
         <*> o .:$ "safe_value"

safeTo (MyType regular safe) =
  contain . object $
    [ "regular_value" .=  regular
    , "safe_value"    .=$ safe
    ]

Inspecting values in safeFrom

The following functions are helpful when defining safeFrom. They are basically contain composed with the corresponding Data.Aeson function, so they can be used in the same fashion as said Data.Aeson function.

containWithObject :: String -> (Object -> Parser a) -> Value -> Contained (Parser a) Source #

Similar to withObject, but contained to be used in safeFrom definitions

Since: 1.0.0

containWithArray :: String -> (Array -> Parser a) -> Value -> Contained (Parser a) Source #

Similar to withArray, but contained to be used in safeFrom definitions

Since: 1.0.0

containWithText :: String -> (Text -> Parser a) -> Value -> Contained (Parser a) Source #

Similar to withText, but contained to be used in safeFrom definitions

Since: 1.0.0

containWithScientific :: String -> (Scientific -> Parser a) -> Value -> Contained (Parser a) Source #

Similar to withScientific, but contained to be used in safeFrom definitions

Since: 1.0.0

containWithBool :: String -> (Bool -> Parser a) -> Value -> Contained (Parser a) Source #

Similar to withBool, but contained to be used in safeFrom definitions

Since: 1.0.0

Accessors

These accessors can be used like their Data.Aeson counterparts. The only difference is that the expected value is parsed using safeFromJSON instead of parseJSON.

(.:$) :: SafeJSON a => Object -> Text -> Parser a Source #

Similar to .:, but uses safeFromJSON instead of parseJSON to parse the value in the given field.

Since: 1.0.0

(.:$?) :: SafeJSON a => Object -> Text -> Parser (Maybe a) Source #

Similar to .:?, but uses safeFromJSON instead of parseJSON to maybe parse the value in the given field.

Since: 1.0.0

(.:$!) :: SafeJSON a => Object -> Text -> Parser (Maybe a) Source #

Similar to .:!, but uses safeFromJSON instead of parseJSON to maybe parse the value in the given field.

Since: 1.0.0

Constructor for safeTo

This constructor of key-value pairs can be used exactly like its Data.Aeson counterpart (.=), but converts the given value with safeToJSON instead of toJSON

(.=$) :: (SafeJSON a, KeyValue kv) => Text -> a -> kv Source #

Similarly to .=, but uses safeToJSON instead of toJSON to convert the value in that key-value pair.

Since: 1.0.0

Version

All SafeJSON instances have a version. This version will be attached to the JSON format and used to figure out which parser (and as such, which type in the chain) should be used to parse the given JSON.

data Version a Source #

A simple numeric version id.

Version has a Num instance and should be declared using integer literals: version = 2

Instances

Instances details
Eq (Version a) Source # 
Instance details

Defined in Data.SafeJSON.Internal

Methods

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

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

Num (Version a) Source #

It is strongly discouraged to use any methods other than fromInteger of Version's Num instance.

Instance details

Defined in Data.SafeJSON.Internal

Methods

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

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

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

negate :: Version a -> Version a #

abs :: Version a -> Version a #

signum :: Version a -> Version a #

fromInteger :: Integer -> Version a #

Show (Version a) Source # 
Instance details

Defined in Data.SafeJSON.Internal

Methods

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

show :: Version a -> String #

showList :: [Version a] -> ShowS #

Arbitrary (Version a) Source #

This instance explicitly doesn't consider noVersion, since it is an exception in almost every sense.

Instance details

Defined in Data.SafeJSON.Internal

Methods

arbitrary :: Gen (Version a) #

shrink :: Version a -> [Version a] #

noVersion :: Version a Source #

This is used for types that don't have a version tag.

This is used for primitive values that are not tagged with a version number, like Int, Text, [a], etc.

But also when implementing SafeJSON after the fact, when a format is already in use, but you still want to be able to migrate from it to a newer type or format.

N.B. version = noVersion is distinctively different from version = 0, which will add a version tag with the number 0 (zero), whereas noVersion will not add a version tag.

setVersion :: forall a. SafeJSON a => Value -> Value Source #

CAUTION: Only use this function if you know what you're doing. The version will be set top-level, without inspection of the Value!

(cf. removeVersion) In some rare cases, you might want to interpret a versionless Value as a certain type/version. setVersion allows you to (unsafely) insert a version field.

If possible, it is advised to use a FromJSON instance instead. (One that doesn't also use safeFromJSON in its methods!)

This might be needed when data sent to an API endpoint doesn't need to implement SafeJSON standards. E.g. in the case of endpoints for third parties or customers.

USAGE:

{-# LANGUAGE TypeApplications #-}
data Test = Test String
instance SafeJSON Test where ...

>>> val = String "test" :: Value
String "test"
>>> encode val
""test""
>>> encode $ setVersion @Test val
"{"~v":0,"~d":"test"}"
>>> parseMaybe safeFromJSON $ setVersion @Test val
Just (Test "test")

Since: 1.0.0

setVersion' :: forall a. SafeJSON a => Version a -> Value -> Value Source #

Same as setVersion, but requires a Version parameter.

>>> encode $ setVersion' (version :: Version Test) val
"{\"~v\":0,\"~d\":\"test\"}"

Since: 1.0.0

removeVersion :: Value -> Value Source #

CAUTION: Only use this function if you know what you're doing.

(cf. setVersion) removeVersion removes all the SafeJSON versioning from a JSON Value. Even recursively.

This might be necessary if the resulting JSON is sent to a third party (e.g. customer) and the SafeJSON versioning should be hidden.

Since: 1.0.0

Kind

All SafeJSON instance have a declared kind, indicating if any migration needs to happen when parsing using safeFromJSON.

  • The Base kind (see base) is at the bottom of the chain and will not be migrated to. They can optionally have no version tag by defining: version = noVersion. N.B. base and extended_base are the only kinds that can be paired with noVersion.
  • Extensions (see extension and extended_extension) tell the system that there exists at least one previous version of the data type which should be migrated from if needed. (This requires the data type to also have a Migrate a instance)
  • Forward extensions (see extended_base and extended_extension) tell the system there exists at least one next version from which the data type can be reverse-migrated. (This requires the data type to also have a Migrate (Reverse a) instance)

data Kind a Source #

The kind of a SafeJSON type determines how it can be migrated to.

base :: Kind a Source #

Used to define kind. Base types do not extend any type.

extension :: (SafeJSON a, Migrate a) => Kind a Source #

Used to define kind. Extends a previous version.

extended_base :: (SafeJSON a, Migrate (Reverse a)) => Kind a Source #

Used to define kind. Types that are extended_base, are extended by a future version and as such can migrate backward from that future version. (cf. extended_extension, base)

extended_extension :: (SafeJSON a, Migrate a, Migrate (Reverse a)) => Kind a Source #

Used to define kind. Types that are extended_extension are extended by a future version and as such can migrate from that future version, but they also extend a previous version. (cf. extended_base, extension)

Showing the type

These helper functions can be used to easily define typeName. As long as the type being defined has a Typeable instance.

typeName0 :: Typeable a => Proxy a -> String Source #

Type name string representation of a nullary type constructor.

typeName1 :: forall t a. Typeable t => Proxy (t a) -> String Source #

Type name string representation of a unary type constructor.

typeName2 :: forall t a b. Typeable t => Proxy (t a b) -> String Source #

Type name string representation of a binary type constructor.

typeName3 :: forall t a b c. Typeable t => Proxy (t a b c) -> String Source #

Type name string representation of a ternary type constructor.

typeName4 :: forall t a b c d. Typeable t => Proxy (t a b c d) -> String Source #

Type name string representation of a 4-ary type constructor.

typeName5 :: forall t a b c d e. Typeable t => Proxy (t a b c d e) -> String Source #

Type name string representation of a 5-ary type constructor.

Consistency

data Profile a Source #

Profile of the internal consistency of a SafeJSON instance.

N.B. noVersion shows as null instead of a number.

Constructors

InvalidProfile String

There is something wrong with versioning

Profile ProfileVersions

Profile of consistent versions

Instances

Instances details
Eq (Profile a) Source # 
Instance details

Defined in Data.SafeJSON.Internal

Methods

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

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

Typeable a => Show (Profile a) Source # 
Instance details

Defined in Data.SafeJSON.Internal

Methods

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

show :: Profile a -> String #

showList :: [Profile a] -> ShowS #

data ProfileVersions Source #

Version profile of a consistent SafeJSON instance.

Constructors

ProfileVersions 

Fields

Instances

Instances details
Eq ProfileVersions Source # 
Instance details

Defined in Data.SafeJSON.Internal

Show ProfileVersions Source #

Version Nothing shows as null

Instance details

Defined in Data.SafeJSON.Internal

Migration

class SafeJSON (MigrateFrom a) => Migrate a where Source #

This instance is needed to handle the migration between older and newer versions.

Note that, where (Migrate a) migrates from the previous version to the type a, (Migrate (Reverse a)) migrates from the future version to the type a.

Example

Expand

Two types that can migrate to each other.

(Don't forget to give OldType one of the extended kinds, and NewType one of the extension kinds.)

instance Migrate NewType where
  type MigrateFrom NewType = OldType
  migrate OldType = NewType

instance Migrate (Reverse OldType) where
  type MigrateFrom (Reverse OldType) = NewType
  migrate NewType = Reverse OldType

Associated Types

type MigrateFrom a Source #

The type from which will be migrated to type a

Methods

migrate :: MigrateFrom a -> a Source #

The migration from the previous version to the current type a. OR, in case of a (Reverse a), the migration from the future version back to the current type a

newtype Reverse a Source #

This is a wrapper type used migrating backwards in the chain of compatible types.

This is useful when running updates in production where new-format JSON will be received by old-format expecting programs.

Constructors

Reverse 

Fields