| Copyright | (c) John Ericson 2023 Sorki 2023 |
|---|---|
| Stability | experimental |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Data.Serializer
Description
Serializer ties Get and PutM monads
into a single datatype and allows
transforming both monads with a monad transformer
for adding extra layers like ExceptT
(for example when putS can fail due to unsupported
version of a protocol) or ReaderT (when we need
to serialize a data type based differently based
on a protocol version).
Synopsis
- data Serializer t a = Serializer {}
- runGetS :: (Monad (t Get), MonadTrans t) => Serializer t a -> (t Get a -> Get b) -> ByteString -> Either String b
- runPutS :: (Monad (t PutM), MonadTrans t) => Serializer t a -> (t PutM () -> PutM b) -> a -> (b, ByteString)
- type SimpleSerializer a = Serializer IdentityT a
- runGetSimple :: SimpleSerializer a -> ByteString -> Either String a
- runPutSimple :: SimpleSerializer a -> a -> ByteString
- lift2 :: forall a t. MonadTrans t => Get a -> Putter a -> Serializer t a
- liftSerialize :: (Serialize a, MonadTrans t) => Serializer t a
- mapIsoSerializer :: Functor (t Get) => (a -> b) -> (b -> a) -> Serializer t a -> Serializer t b
- mapPrismSerializer :: MonadError eGet (t Get) => (a -> Either eGet b) -> (b -> a) -> Serializer t a -> Serializer t b
- tup :: (Applicative (t Get), Monad (t PutM)) => Serializer t a -> Serializer t b -> Serializer t (a, b)
- data GetSerializerError customGetError
- = SerializerError_GetFail String
- | SerializerError_Get customGetError
- transformGetError :: Either String (Either customGetError b) -> Either (GetSerializerError customGetError) b
- transformPutError :: (Either customPutError (), ByteString) -> Either customPutError ByteString
- data Get a
- data PutM a
Serializer
data Serializer t a Source #
Serializer ties Get and PutM monads
into a single datatype and allows
transforming the monads with a monad transformer
for e.g. adding ExceptT or ReaderT layers.
Constructors
| Serializer | |
Runners
Arguments
| :: (Monad (t Get), MonadTrans t) | |
| => Serializer t a | Serializer |
| -> (t Get a -> Get b) | Tranformer runner |
| -> ByteString | ByteString to parse |
| -> Either String b |
Runner for getS of Serializer
Arguments
| :: (Monad (t PutM), MonadTrans t) | |
| => Serializer t a | Serializer |
| -> (t PutM () -> PutM b) | Tranformer runner |
| -> a | Value to (out)put |
| -> (b, ByteString) |
Runner for putS of Serializer
Simple serializer
type SimpleSerializer a = Serializer IdentityT a Source #
Simple Serializer
Simple runners
runGetSimple :: SimpleSerializer a -> ByteString -> Either String a Source #
Runner for getS of SimpleSerializer
runPutSimple :: SimpleSerializer a -> a -> ByteString Source #
Runner for putS of SimpleSerializer
From Get/Put, Serialize
lift2 :: forall a t. MonadTrans t => Get a -> Putter a -> Serializer t a Source #
Lift Get a and Putter a into Serializer
liftSerialize :: (Serialize a, MonadTrans t) => Serializer t a Source #
Lift Serialize a instance into Serializer
Combinators
Arguments
| :: Functor (t Get) | |
| => (a -> b) | Map over |
| -> (b -> a) | Map over |
| -> Serializer t a | |
| -> Serializer t b |
Map over Serializer
Arguments
| :: MonadError eGet (t Get) | |
| => (a -> Either eGet b) | Map over |
| -> (b -> a) | Map over |
| -> Serializer t a | |
| -> Serializer t b |
Map over Serializer where getS
can return Either
tup :: (Applicative (t Get), Monad (t PutM)) => Serializer t a -> Serializer t b -> Serializer t (a, b) Source #
Tuple combinator
Utility
data GetSerializerError customGetError Source #
Wrapper for both GetS errors
- the one that occurs when
failis called - custom one when
ExceptTis used
Constructors
| SerializerError_GetFail String | |
| SerializerError_Get customGetError |
Instances
| Show customGetError => Show (GetSerializerError customGetError) Source # | |
Defined in Data.Serializer Methods showsPrec :: Int -> GetSerializerError customGetError -> ShowS # show :: GetSerializerError customGetError -> String # showList :: [GetSerializerError customGetError] -> ShowS # | |
| Eq customGetError => Eq (GetSerializerError customGetError) Source # | |
Defined in Data.Serializer Methods (==) :: GetSerializerError customGetError -> GetSerializerError customGetError -> Bool # (/=) :: GetSerializerError customGetError -> GetSerializerError customGetError -> Bool # | |
| Ord customGetError => Ord (GetSerializerError customGetError) Source # | |
Defined in Data.Serializer Methods compare :: GetSerializerError customGetError -> GetSerializerError customGetError -> Ordering # (<) :: GetSerializerError customGetError -> GetSerializerError customGetError -> Bool # (<=) :: GetSerializerError customGetError -> GetSerializerError customGetError -> Bool # (>) :: GetSerializerError customGetError -> GetSerializerError customGetError -> Bool # (>=) :: GetSerializerError customGetError -> GetSerializerError customGetError -> Bool # max :: GetSerializerError customGetError -> GetSerializerError customGetError -> GetSerializerError customGetError # min :: GetSerializerError customGetError -> GetSerializerError customGetError -> GetSerializerError customGetError # | |
transformGetError :: Either String (Either customGetError b) -> Either (GetSerializerError customGetError) b Source #
Helper for transforming nested Eithers
into GetSerializerError wrapper
transformPutError :: (Either customPutError (), ByteString) -> Either customPutError ByteString Source #
Helper for transforming runPutM result
Re-exports
The Get monad is an Exception and State monad.
Instances
| MonadFail Get | |
Defined in Data.Serialize.Get | |
| Alternative Get | |
| Applicative Get | |
| Functor Get | |
| Monad Get | |
| MonadPlus Get | |