Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- type ClientIO = ExceptT ClientError IO
- data ClientError = EarlyEndOfStream
- runClientIO :: ClientIO a -> IO (Either ClientError a)
- lift :: (MonadTrans t, Monad m) => m a -> t m a
- data ExceptT e (m :: Type -> Type) a
- throwError :: MonadError e m => e -> m a
- runExceptT :: ExceptT e m a -> m (Either e a)
Documentation
data ClientError Source #
A set of errors as observed from the client.
EarlyEndOfStream | We received a TCP end-of-stream and there will be no further read-IOs possible on the connection. |
Instances
Eq ClientError Source # | |
Defined in Network.HTTP2.Client.Exceptions (==) :: ClientError -> ClientError -> Bool # (/=) :: ClientError -> ClientError -> Bool # | |
Ord ClientError Source # | |
Defined in Network.HTTP2.Client.Exceptions compare :: ClientError -> ClientError -> Ordering # (<) :: ClientError -> ClientError -> Bool # (<=) :: ClientError -> ClientError -> Bool # (>) :: ClientError -> ClientError -> Bool # (>=) :: ClientError -> ClientError -> Bool # max :: ClientError -> ClientError -> ClientError # min :: ClientError -> ClientError -> ClientError # | |
Show ClientError Source # | |
Defined in Network.HTTP2.Client.Exceptions showsPrec :: Int -> ClientError -> ShowS # show :: ClientError -> String # showList :: [ClientError] -> ShowS # | |
Exception ClientError Source # | |
Defined in Network.HTTP2.Client.Exceptions |
runClientIO :: ClientIO a -> IO (Either ClientError a) Source #
lift :: (MonadTrans t, Monad m) => m a -> t m a #
Lift a computation from the argument monad to the constructed monad.
data ExceptT e (m :: Type -> Type) a #
A monad transformer that adds exceptions to other monads.
ExceptT
constructs a monad parameterized over two things:
- e - The exception type.
- m - The inner monad.
The return
function yields a computation that produces the given
value, while >>=
sequences two subcomputations, exiting on the
first exception.
Instances
throwError :: MonadError e m => e -> m a #
Is used within a monadic computation to begin exception processing.
runExceptT :: ExceptT e m a -> m (Either e a) #
The inverse of ExceptT
.