versioning-0.3.0.1: Type-safe data versioning.

Safe HaskellNone
LanguageHaskell2010

Versioning.JSON

Contents

Description

JSON-specific deserialization utilities.

Synopsis

Types

type family Applied (c :: Type -> Constraint) (a :: V -> Type) :: Type Source #

The result type of the action that has been applied to the decoded object with withAnyVersion or withAnyVersionM.

type JsonDecodableTo v a = JsonDecodableToFrom V0 v a Source #

Handy constraint synonym to be used with fromJsonAnyVersion

type JsonDecodableToFrom from v a = DecodableToFrom from FromJSON v a Source #

Like JsonDecodableTo, with an additional type-parameter indicating the oldest version you want to be able to decode

Decoding and upgrading

fromJsonAnyVersion :: forall v a. JsonDecodableTo v a => ByteString -> Maybe (a v) Source #

Decode a JSON string by trying all the versions decrementally and upgrade the decoded object to the newest version.

fromJsonAnyVersionStrict :: forall v a. JsonDecodableTo v a => ByteString -> Maybe (a v) Source #

Like fromJsonAnyVersion but it reads from a strict ByteString

fromJsonAnyVersionEither :: forall v a. JsonDecodableTo v a => ByteString -> Either String (a v) Source #

Like fromJsonAnyVersion but returns a message when decoding fails

fromJsonAnyVersionEitherStrict :: forall v a. JsonDecodableTo v a => ByteString -> Either String (a v) Source #

Like fromJsonAnyVersionStrict but returns a message when decoding fails

fromJsonAnyVersionFrom :: forall from v a. JsonDecodableToFrom from v a => ByteString -> Maybe (a v) Source #

Like fromJsonAnyVersion, with an additional type-parameter indicating the oldest version you want to be able to decode

Decoding and appyling an action

withJsonAnyVersion :: forall c a v. (WithAnyVersion v a c FromJSON, c (a v)) => Apply a c -> ByteString -> Maybe (Applied c a) Source #

Decode a JSON string by trying all the versions decrementally and apply a pure function to the decoded object at its original version.

withJsonAnyVersionStrict :: forall c a v. (WithAnyVersion v a c FromJSON, c (a v)) => Apply a c -> ByteString -> Maybe (Applied c a) Source #

Like withJsonAnyVersion but it reads from a strict ByteString

withJsonAnyVersionEither :: forall c a v. (WithAnyVersion v a c FromJSON, c (a v)) => Apply a c -> ByteString -> Either String (Applied c a) Source #

Like withJsonAnyVersion but returns a message when decoding fails

withJsonAnyVersionEitherStrict :: forall c a v. (WithAnyVersion v a c FromJSON, c (a v)) => Apply a c -> ByteString -> Either String (Applied c a) Source #

Like withJsonAnyVersionStrict but returns a message when decoding fails

withJsonAnyVersionFrom :: forall from c a v. (WithAnyVersionFrom from v a c FromJSON, c (a v)) => Apply a c -> ByteString -> Maybe (Applied c a) Source #

Like withJsonAnyVersion, with an additional type-parameter indicating the oldest version you want to be able to decode

withJsonAnyVersionM :: forall c a v m. (WithAnyVersion v a c FromJSON, Applicative m, c (a v)) => ApplyM m a c -> ByteString -> m (Maybe (Applied c a)) Source #

Decode a JSON string by trying all the versions decrementally and apply an action to the decoded object at its original version.

withJsonAnyVersionStrictM :: forall c a v m. (WithAnyVersion v a c FromJSON, Applicative m, c (a v)) => ApplyM m a c -> ByteString -> m (Maybe (Applied c a)) Source #

Like withJsonAnyVersionM but it reads from a strict ByteString

withJsonAnyVersionEitherM :: forall c a v m. (WithAnyVersion v a c FromJSON, Applicative m, c (a v)) => ApplyM m a c -> ByteString -> m (Either String (Applied c a)) Source #

Like withJsonAnyVersionM but returns a message when decoding fails

withJsonAnyVersionEitherStrictM :: forall c a v m. (WithAnyVersion v a c FromJSON, Applicative m, c (a v)) => ApplyM m a c -> ByteString -> m (Either String (Applied c a)) Source #

Like withJsonAnyVersionStrictM but returns a message when decoding fails

withJsonAnyVersionFromM :: forall from c a v m. (WithAnyVersionFrom from v a c FromJSON, Applicative m, c (a v)) => ApplyM m a c -> ByteString -> m (Maybe (Applied c a)) Source #

Like withJsonAnyVersionM, with an additional type-parameter indicating the oldest version you want to be able to decode