Safe Haskell | None |
---|---|
Language | Haskell2010 |
Encoding-agnosting deserialization utilities.
Synopsis
- type family Applied (c :: Type -> Constraint) (a :: V -> Type) :: Type
- type Apply a c = forall v. c (a v) => a v -> Applied c a
- type ApplyM m a c = forall v. c (a v) => a v -> m (Applied c a)
- type DecodableTo dec v a = DecodableToFrom V0 dec v a
- type DecodableToFrom from dec v a = DecodeAnyVersionFrom from v v a dec
- type DecodeAnyVersion v w a dec = DecodeAnyVersionFrom V0 v w a dec
- newtype Decoder dec enc t a = Decoder (forall v. dec (a v) => enc -> t (a v))
- type WithAnyVersion v a c dec = WithAnyVersionFrom V0 v a c dec
- type WithAnyVersionFrom from v a c dec = WithAnyVersion' (from == v) from v a c dec
- decodeAnyVersion :: forall v a dec enc t. (Alt t, Applicative t, DecodableTo dec v a) => Decoder dec enc t a -> enc -> t (a v)
- decodeAnyVersionFrom :: forall from v a dec enc t. (Alt t, Applicative t, DecodableToFrom from dec v a) => Decoder dec enc t a -> enc -> t (a v)
- withAnyVersion :: forall v c a dec enc t. (WithAnyVersion v a c dec, c (a v), Alt t, Applicative t, Traversable t) => Decoder dec enc t a -> Apply a c -> enc -> t (Applied c a)
- withAnyVersionM :: forall v c a dec enc m t. (WithAnyVersion v a c dec, Alt t, Applicative t, Traversable t, Applicative m, c (a v)) => Decoder dec enc t a -> ApplyM m a c -> enc -> m (t (Applied c a))
- withAnyVersionFromM :: forall from v c a dec enc m t. (WithAnyVersionFrom from v a c dec, Alt t, Applicative t, Traversable t, Applicative m, c (a v)) => Decoder dec enc t a -> ApplyM m a c -> enc -> m (t (Applied c a))
- withAnyVersionFrom :: forall from v c a dec enc t. (WithAnyVersionFrom from v a c dec, c (a v), Alt t, Applicative t, Traversable t) => Decoder dec enc t a -> Apply a c -> enc -> t (Applied c a)
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 Apply a c = forall v. c (a v) => a v -> Applied c a Source #
The pure function to apply to the decoded object with withAnyVersion
type ApplyM m a c = forall v. c (a v) => a v -> m (Applied c a) Source #
The action to apply to the decoded object with withAnyVersionM
type DecodableTo dec v a = DecodableToFrom V0 dec v a Source #
Handy constraint synonym to be used with decodeAnyVersion
type DecodableToFrom from dec v a = DecodeAnyVersionFrom from v v a dec Source #
type DecodeAnyVersion v w a dec = DecodeAnyVersionFrom V0 v w a dec Source #
newtype Decoder dec enc t a Source #
The function that will perform the actual decoding
Decoder (forall v. dec (a v) => enc -> t (a v)) |
type WithAnyVersion v a c dec = WithAnyVersionFrom V0 v a c dec Source #
type WithAnyVersionFrom from v a c dec = WithAnyVersion' (from == v) from v a c dec Source #
Decoding and upgrading
decodeAnyVersion :: forall v a dec enc t. (Alt t, Applicative t, DecodableTo dec v a) => Decoder dec enc t a -> enc -> t (a v) Source #
decodeAnyVersionFrom :: forall from v a dec enc t. (Alt t, Applicative t, DecodableToFrom from dec v a) => Decoder dec enc t a -> enc -> t (a v) Source #
Decode by trying all the versions decrementally and upgrade the decoded object to the newest version.
Decoding and applying an action
withAnyVersion :: forall v c a dec enc t. (WithAnyVersion v a c dec, c (a v), Alt t, Applicative t, Traversable t) => Decoder dec enc t a -> Apply a c -> enc -> t (Applied c a) Source #
Pure version of withAnyVersionM
.
withAnyVersionM :: forall v c a dec enc m t. (WithAnyVersion v a c dec, Alt t, Applicative t, Traversable t, Applicative m, c (a v)) => Decoder dec enc t a -> ApplyM m a c -> enc -> m (t (Applied c a)) Source #
Decode by trying all the versions decrementally and apply an action to the decoded object at its original version.
withAnyVersionFromM :: forall from v c a dec enc m t. (WithAnyVersionFrom from v a c dec, Alt t, Applicative t, Traversable t, Applicative m, c (a v)) => Decoder dec enc t a -> ApplyM m a c -> enc -> m (t (Applied c a)) Source #
Like withAnyVersionM
, with an additional type-parameter
indicating the oldest version you want to be able to decode
withAnyVersionFrom :: forall from v c a dec enc t. (WithAnyVersionFrom from v a c dec, c (a v), Alt t, Applicative t, Traversable t) => Decoder dec enc t a -> Apply a c -> enc -> t (Applied c a) Source #
Pure version of withAnyVersionFromM
.