hnix-store-remote-0.7.0.0: Remote hnix store
Copyright(c) John Ericson 2023
Sorki 2023
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

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).

See Data.Serializer.Example

Synopsis

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 

Fields

Runners

runGetS Source #

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

runPutS Source #

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

mapIsoSerializer Source #

Arguments

:: Functor (t Get) 
=> (a -> b)

Map over getS

-> (b -> a)

Map over putS

-> Serializer t a 
-> Serializer t b 

Map over Serializer

mapPrismSerializer Source #

Arguments

:: MonadError eGet (t Get) 
=> (a -> Either eGet b)

Map over getS

-> (b -> a)

Map over putS

-> 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 fail is called
  • custom one when ExceptT is used

Constructors

SerializerError_GetFail String 
SerializerError_Get customGetError 

Instances

Instances details
Show customGetError => Show (GetSerializerError customGetError) Source # 
Instance details

Defined in Data.Serializer

Methods

showsPrec :: Int -> GetSerializerError customGetError -> ShowS #

show :: GetSerializerError customGetError -> String #

showList :: [GetSerializerError customGetError] -> ShowS #

Eq customGetError => Eq (GetSerializerError customGetError) Source # 
Instance details

Defined in Data.Serializer

Methods

(==) :: GetSerializerError customGetError -> GetSerializerError customGetError -> Bool #

(/=) :: GetSerializerError customGetError -> GetSerializerError customGetError -> Bool #

Ord customGetError => Ord (GetSerializerError customGetError) Source # 
Instance details

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

data Get a #

The Get monad is an Exception and State monad.

Instances

Instances details
MonadFail Get 
Instance details

Defined in Data.Serialize.Get

Methods

fail :: String -> Get a #

Alternative Get 
Instance details

Defined in Data.Serialize.Get

Methods

empty :: Get a #

(<|>) :: Get a -> Get a -> Get a #

some :: Get a -> Get [a] #

many :: Get a -> Get [a] #

Applicative Get 
Instance details

Defined in Data.Serialize.Get

Methods

pure :: a -> Get a #

(<*>) :: Get (a -> b) -> Get a -> Get b #

liftA2 :: (a -> b -> c) -> Get a -> Get b -> Get c #

(*>) :: Get a -> Get b -> Get b #

(<*) :: Get a -> Get b -> Get a #

Functor Get 
Instance details

Defined in Data.Serialize.Get

Methods

fmap :: (a -> b) -> Get a -> Get b #

(<$) :: a -> Get b -> Get a #

Monad Get 
Instance details

Defined in Data.Serialize.Get

Methods

(>>=) :: Get a -> (a -> Get b) -> Get b #

(>>) :: Get a -> Get b -> Get b #

return :: a -> Get a #

MonadPlus Get 
Instance details

Defined in Data.Serialize.Get

Methods

mzero :: Get a #

mplus :: Get a -> Get a -> Get a #

data PutM a #

The PutM type. A Writer monad over the efficient Builder monoid.

Instances

Instances details
Applicative PutM 
Instance details

Defined in Data.Serialize.Put

Methods

pure :: a -> PutM a #

(<*>) :: PutM (a -> b) -> PutM a -> PutM b #

liftA2 :: (a -> b -> c) -> PutM a -> PutM b -> PutM c #

(*>) :: PutM a -> PutM b -> PutM b #

(<*) :: PutM a -> PutM b -> PutM a #

Functor PutM 
Instance details

Defined in Data.Serialize.Put

Methods

fmap :: (a -> b) -> PutM a -> PutM b #

(<$) :: a -> PutM b -> PutM a #

Monad PutM 
Instance details

Defined in Data.Serialize.Put

Methods

(>>=) :: PutM a -> (a -> PutM b) -> PutM b #

(>>) :: PutM a -> PutM b -> PutM b #

return :: a -> PutM a #

Monoid (PutM ()) 
Instance details

Defined in Data.Serialize.Put

Methods

mempty :: PutM () #

mappend :: PutM () -> PutM () -> PutM () #

mconcat :: [PutM ()] -> PutM () #

Semigroup (PutM ()) 
Instance details

Defined in Data.Serialize.Put

Methods

(<>) :: PutM () -> PutM () -> PutM () #

sconcat :: NonEmpty (PutM ()) -> PutM () #

stimes :: Integral b => b -> PutM () -> PutM () #