Safe Haskell | None |
---|---|
Language | Haskell2010 |
A Wai middleware that uniformly structures errors within a servant application.
The library assumes all HTTP responses with status codes greater than 200
and
lacking an HTTP content-type
are error responses. This assumption is derived
from servant server error handling implementation.
The formatting and structuring of errors rest on the implementation of HasErrorBody
class instances.
It's class parameters are a content-type eg JSON
or PlainText
and a type-level list of
options
e.g '["error", "status"]
. The library offers instances for JSON
and PlainText
content-types.
Sample usage with servant
A typical servant application is usually of this form:
main :: IO () main = run 8001 (serve proxyApi handlers)
With servant-errors as an error processing middleware:
main :: IO () main = run 8001 $ errorMw @JSON @'["error", "status"] -- ^ Structures error response as JSON objects -- witherror
andstatus
strings as error object field keys -- note they can be changed to any other preferred strings. $ serve proxyApi handlers
Synopsis
- errorMw :: forall ctyp opts. HasErrorBody ctyp opts => Application -> Application
- errorMwDefJson :: Application -> Application
- class Accept ctyp => HasErrorBody (ctyp :: Type) (opts :: [Symbol]) where
- encodeError :: StatusCode -> ErrorMsg -> ByteString
- newtype ErrorMsg = ErrorMsg {
- unErrorMsg :: Text
- newtype StatusCode = StatusCode {
- unStatusCode :: Int
- data ErrorLabels = ErrorLabels {
- errName :: Text
- errStatusName :: Text
- getErrorLabels :: forall errLabel statusLabel. (KnownSymbol errLabel, KnownSymbol statusLabel) => ErrorLabels
Error Middleware
errorMw :: forall ctyp opts. HasErrorBody ctyp opts => Application -> Application Source #
errorMw
functions provides Network.Wai middleware for formatting error responses
within a servant application.
Note that this function expects you to have TypeApplications
extension enabled
errorMw @JSON @'[ "error", "status"]
errorMwDefJson :: Application -> Application Source #
errorMwDefJson
is a convenience pre-configured function for middleware
that encodes error responses as JSON
objects using error
and status
for a JSON object
key fields
A resulting response may look like this:
{ error: "failed to decode request body", status: 400 }
HasErrorBody class
class Accept ctyp => HasErrorBody (ctyp :: Type) (opts :: [Symbol]) where Source #
The HasErrorBody
class is used for structuring servant error responses.
ctyp
is an HTTP content-type with an Accept
class instance. eg JSON
opts
is a type level list for customising error and status labels.
For example:
'["error-message", "status-code"]
When opts
is left as an Empty type level list, it default's to a type list of these values:
'["error", "status"]
for the library provided JSON
and PlainText
instances.
encodeError :: StatusCode -> ErrorMsg -> ByteString Source #
encodeError
formats error response.
The opts
type level list in the class definition is used by the getErrorLabels
function
to obtain error labels which are subsequently used in implementing encodeError
for class instances
Instances
HasErrorBody JSON ([] :: [Symbol]) Source # | |
Defined in Network.Wai.Middleware.Servant.Errors encodeError :: StatusCode -> ErrorMsg -> ByteString Source # | |
HasErrorBody PlainText ([] :: [Symbol]) Source # | |
Defined in Network.Wai.Middleware.Servant.Errors encodeError :: StatusCode -> ErrorMsg -> ByteString Source # | |
(KnownSymbol errLabel, KnownSymbol statusLabel) => HasErrorBody JSON (errLabel ': (statusLabel ': ([] :: [Symbol]))) Source # | |
Defined in Network.Wai.Middleware.Servant.Errors encodeError :: StatusCode -> ErrorMsg -> ByteString Source # | |
(KnownSymbol errLabel, KnownSymbol statusLabel) => HasErrorBody PlainText (errLabel ': (statusLabel ': ([] :: [Symbol]))) Source # | |
Defined in Network.Wai.Middleware.Servant.Errors encodeError :: StatusCode -> ErrorMsg -> ByteString Source # |
Helper functions and data types
ErrorMsg
holds HTTP error response body message
newtype StatusCode Source #
StatusCode
holds HTTP error status code
Instances
Eq StatusCode Source # | |
Defined in Network.Wai.Middleware.Servant.Errors (==) :: StatusCode -> StatusCode -> Bool # (/=) :: StatusCode -> StatusCode -> Bool # | |
Ord StatusCode Source # | |
Defined in Network.Wai.Middleware.Servant.Errors compare :: StatusCode -> StatusCode -> Ordering # (<) :: StatusCode -> StatusCode -> Bool # (<=) :: StatusCode -> StatusCode -> Bool # (>) :: StatusCode -> StatusCode -> Bool # (>=) :: StatusCode -> StatusCode -> Bool # max :: StatusCode -> StatusCode -> StatusCode # min :: StatusCode -> StatusCode -> StatusCode # | |
Show StatusCode Source # | |
Defined in Network.Wai.Middleware.Servant.Errors showsPrec :: Int -> StatusCode -> ShowS # show :: StatusCode -> String # showList :: [StatusCode] -> ShowS # |
data ErrorLabels Source #
ErrorLabels
is a configuration for holding error response labels
ErrorLabels | |
|
getErrorLabels :: forall errLabel statusLabel. (KnownSymbol errLabel, KnownSymbol statusLabel) => ErrorLabels Source #
getErrorLabels
is used to tranform type level list options provided via the
HasErrorBody
class into an ErrorLabels
data type.
ErrorLabels
is used with the error formatting and encoding
functions used in HasErrorBody class.