Safe Haskell | None |
---|---|
Language | Haskell2010 |
JSON-specific deserialization utilities.
- type family Applied (c :: Type -> Constraint) (a :: V -> Type) :: Type
- type JsonDecodableTo v a = DecodableTo FromJSON v a
- fromJsonAnyVersion :: forall v a. JsonDecodableTo v a => ByteString -> Maybe (a v)
- fromJsonAnyVersionStrict :: forall v a. JsonDecodableTo v a => ByteString -> Maybe (a v)
- fromJsonAnyVersionEither :: forall v a. JsonDecodableTo v a => ByteString -> Either String (a v)
- fromJsonAnyVersionEitherStrict :: forall v a. JsonDecodableTo v a => ByteString -> Either String (a v)
- withJsonAnyVersion :: forall c a v. (WithAnyVersion v a c FromJSON, c (a v)) => Apply a c -> ByteString -> Maybe (Applied c a)
- withJsonAnyVersionStrict :: forall c a v. (WithAnyVersion v a c FromJSON, c (a v)) => Apply a c -> ByteString -> Maybe (Applied c a)
- withJsonAnyVersionEither :: forall c a v. (WithAnyVersion v a c FromJSON, c (a v)) => Apply a c -> ByteString -> Either String (Applied c a)
- withJsonAnyVersionEitherStrict :: forall c a v. (WithAnyVersion v a c FromJSON, c (a v)) => Apply a c -> ByteString -> Either String (Applied c a)
- 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))
- 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))
- 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))
- 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))
Documentation
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 = DecodableTo FromJSON v a Source #
Handy constraint synonym to be used with fromJsonAnyVersion
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
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
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