Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
- data HTTP2SessionException = forall e . Exception e => HTTP2SessionException e
- data FramerException = forall e . Exception e => FramerException e
- data BadPrefaceException = BadPrefaceException
- data HTTP11Exception = forall e . Exception e => HTTP11Exception e
- data HTTP11SyntaxException = HTTP11SyntaxException String
- data ClientSessionAbortedException = ClientSessionAbortedException ConnectionCloseReason
- data HTTP500PrecursorException = forall e . Exception e => HTTP500PrecursorException e
- data GatewayAbortedException = GatewayAbortedException
- data ConnectionCloseReason
- convertHTTP500PrecursorExceptionToException :: Exception e => e -> SomeException
- getHTTP500PrecursorExceptionFromException :: Exception e => SomeException -> Maybe e
- data ContentLengthMissingException = ContentLengthMissingException
- data IOProblem = forall e . Exception e => IOProblem e
- data GenericIOProblem = GenericIOProblem
- data StreamCancelledException = StreamCancelledException
- data NoMoreDataException = NoMoreDataException
- data SOCKS5ProtocolException = SOCKS5ProtocolException
- data HTTP2ProtocolException = HTTP2ProtocolException
- ignoreException :: Exception e => Proxy e -> a -> IO a -> IO a
- reportExceptions :: forall a. IO a -> IO a
- keyedReportExceptions :: forall a. String -> IO a -> IO a
- forkIOExc :: String -> IO () -> IO ThreadId
- blockedIndefinitelyOnMVar :: Proxy BlockedIndefinitelyOnMVar
- blockedIndefinitelyOnSTM :: Proxy BlockedIndefinitelyOnSTM
- noMoreDataException :: Proxy NoMoreDataException
- ioProblem :: Proxy IOProblem
- gatewayAbortedException :: Proxy GatewayAbortedException
- ioException :: Proxy IOException
Exceptions thrown by the HTTP/2 sessions
Abstract exception. All HTTP/2 exceptions derive from here
forall e . Exception e => HTTP2SessionException e |
data FramerException
Abstract exception. Thrown when encoding/decoding of a frame fails
forall e . Exception e => FramerException e |
data BadPrefaceException
Thrown when the HTTP/2 connection prefix doesn't match the expected prefix.
data HTTP11Exception
Abstract exception. All HTTP/1.1 related exceptions derive from here. Notice that this includes a lot of logical errors and they can be raised when handling HTTP/2 sessions as well
forall e . Exception e => HTTP11Exception e |
data ClientSessionAbortedException
Concrete Exception. Used internally to signal that the server broke the connection. This is a public exception that clients of the library will see when acting as an HTTP client.
data HTTP500PrecursorException
Abstract exception. It is an error if an exception of this type bubbles to this library, but we will do our best to handle it gracefully in the Session engines. All internal error precursors at the workers can thus inherit from here to have a fallback option in case they forget to handle the error. It should also be used for the case of streaming requests that are interrupted by the upstream server. This exception inherits from HTTP11Exception
forall e . Exception e => HTTP500PrecursorException e |
Used by the ReverseProxy to signal an error from the upstream/Gateway
Reasons for a remote server interrupting a connectionn of this client
NormalTermination_CCR | Corresponds to NO_ERROR |
SessionAlreadyClosed_CCR | A request was done after the session was previously closed. |
IOChannelClosed_CCR | This one happens when one of the IO channels is closed and a BlockedIndefinitelyOnMVar bubbles up. It should only happen in the test suite, as the OpenSSL_TLS channel uses a specialized exception type. If you see it in the wild, it is a bug. |
ProtocolError_CCR | Any other reason |
convertHTTP500PrecursorExceptionToException :: Exception e => e -> SomeException
Use the traditional idiom if you need to derive from HTTP500PrecursorException
,
this is one of the helpers
getHTTP500PrecursorExceptionFromException :: Exception e => SomeException -> Maybe e
Use the traditional idiom if you need to derive from HTTP500PrecursorException
,
this is one of the helpers
data ContentLengthMissingException
Thrown with HTTP1.1 over HTTP1.1 sessions when the response body or the request body doesn't include a Content-Length header field, given that should have included it
Exceptions related to the IO layer
data IOProblem
Throw exceptions derived from this (e.g, GenericIOProblem
below)
to have the HTTP/2 session to terminate gracefully.
data GenericIOProblem
A concrete case of the above exception. Throw one of this
if you don't want to implement your own type. Use
IOProblem
in catch signatures.
This exception will be raised inside a CoherentWorker
when the underlying
stream is cancelled (STREAM_RESET in HTTP/2). Do any necessary cleanup
in a handler, or simply use the fact that the exception is asynchronously
delivered
to your CoherentWorker Haskell thread, giving you an opportunity to
interrupt any blocked operations.
data NoMoreDataException
This is raised by the IOCallbacks when the endpoint is not willing to return or to accept more data
Exceptions related to SOCKS5
Exception to denote that something failed with the SOCKS5 protocol
Internal exceptions
Concrete exception. Used internally to signal that the client violated the protocol. Clients of the library shall never see this exception.
Utility functions
ignoreException :: Exception e => Proxy e -> a -> IO a -> IO a
Simple utility function that ignores an exception. Good to work on threads when we know stuff. It takes as a first parameter a proxy.
reportExceptions :: forall a. IO a -> IO a
Simple utility function that reports exceptions
keyedReportExceptions :: forall a. String -> IO a -> IO a