| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Data.Serializer.Example
Synopsis
- data OpCode
- data Cmd :: Type -> Type where
- cmdS :: forall t. (MonadTrans t, Monad (t Get), Monad (t PutM)) => Serializer t (Some Cmd)
- runG :: Serializer (ExceptT e) a -> ByteString -> Either (GetSerializerError e) a
- runP :: Serializer (ExceptT e) a -> a -> Either e ByteString
- data MyGetError = MyGetError_Example
- data MyPutError = MyPutError_NoLongerSupported
- cmdSPutError :: Serializer (ExceptT MyPutError) (Some Cmd)
- cmdSGetError :: Serializer (ExceptT MyGetError) (Some Cmd)
- cmdSGetFail :: (MonadTrans t, MonadFail (t Get), Monad (t PutM)) => Serializer t (Some Cmd)
- cmdSPutFail :: (MonadTrans t, MonadFail (t PutM), Monad (t Get)) => Serializer t (Some Cmd)
- cmdSRest :: Serializer (REST Bool e Int) (Some Cmd)
- runGRest :: Serializer (REST r e s) a -> r -> s -> ByteString -> Either (GetSerializerError e) a
- runPRest :: Serializer (REST r e s) a -> r -> s -> a -> Either e ByteString
Simple protocol
OpCode used to differentiate between operations
Constructors
| OpCode_Int | |
| OpCode_Bool |
data Cmd :: Type -> Type where Source #
Protocol operations
Cmd Serializer
cmdS :: forall t. (MonadTrans t, Monad (t Get), Monad (t PutM)) => Serializer t (Some Cmd) Source #
Cmd Serializer
Runners
runG :: Serializer (ExceptT e) a -> ByteString -> Either (GetSerializerError e) a Source #
runGetS specialized to ExceptT e
runP :: Serializer (ExceptT e) a -> a -> Either e ByteString Source #
runPutS specialized to ExceptT e
Custom errors
data MyGetError Source #
Constructors
| MyGetError_Example |
Instances
| Show MyGetError Source # | |
Defined in Data.Serializer.Example Methods showsPrec :: Int -> MyGetError -> ShowS # show :: MyGetError -> String # showList :: [MyGetError] -> ShowS # | |
| Eq MyGetError Source # | |
Defined in Data.Serializer.Example | |
data MyPutError Source #
Constructors
| MyPutError_NoLongerSupported |
Instances
| Show MyPutError Source # | |
Defined in Data.Serializer.Example Methods showsPrec :: Int -> MyPutError -> ShowS # show :: MyPutError -> String # showList :: [MyPutError] -> ShowS # | |
| Eq MyPutError Source # | |
Defined in Data.Serializer.Example | |
Erroring variants of cmdS
putS with throwError and MyPutError
cmdSPutError :: Serializer (ExceptT MyPutError) (Some Cmd) Source #
getS with throwError and MyGetError
cmdSGetError :: Serializer (ExceptT MyGetError) (Some Cmd) Source #
getS with fail
cmdSGetFail :: (MonadTrans t, MonadFail (t Get), Monad (t PutM)) => Serializer t (Some Cmd) Source #
putS with fail
cmdSPutFail :: (MonadTrans t, MonadFail (t PutM), Monad (t Get)) => Serializer t (Some Cmd) Source #
Unused as PutM doesn't have MonadFail
>>> serializerPutFail = cmdPutFail @(ExceptT MyGetError)
No instance for (MonadFail PutM)
as expected
Elaborate
runGRest :: Serializer (REST r e s) a -> r -> s -> ByteString -> Either (GetSerializerError e) a Source #
runPRest :: Serializer (REST r e s) a -> r -> s -> a -> Either e ByteString Source #