Copyright | (c) 2020 Peter Trško |
---|---|
License | BSD3 |
Maintainer | peter.trsko@gmail.com |
Stability | experimental |
Portability | GHC specific language extensions. |
Safe Haskell | None |
Language | Haskell2010 |
Servant support for RFC7807 — Problem Details for HTTP APIs style response messages.
Synopsis
- rfc7807ServerError :: forall body ctype errorType errorInfo context. MimeRender ctype body => Proxy ctype -> ServerError -> errorType -> (Rfc7807Error errorType errorInfo context -> body) -> ServerError
- data ProblemJSON
- data Rfc7807Error errorType errorInfo context = Rfc7807Error {}
Documentation
The main functionality of this module is rfc7807ServerError
, which allows
us to create Servant's ServerError
values with RFC7807 style body.
Implementation is more abstract than strictly necessary to account for the
fact that application/problem+json
may not always be the best mime type to
use. This is especially true if we are migrating existing error responses.
Another benefit of the abstract way it's defined is that we can potentially
use different encoding or serialisation libraries.
If you're interested in using this module right away then jump straight to Usage Examples section.
:: forall body ctype errorType errorInfo context. MimeRender ctype body | |
=> Proxy ctype | Media type to use when encoding the error response body. This allows
us to select appropriate mime type, e.g. |
-> ServerError | One of Servant error values e.g. |
-> errorType | Value of the |
-> (Rfc7807Error errorType errorInfo context -> body) | Modify the The Reason for the return type to be polymorphic (i.e. |
-> ServerError |
Construct Servant ServerError
with RFC7807 style response body.
By using Servant abstractions (like MimeRender
and Accept
) we are able
to easily integrate with existing code bases.
Usage Example
data ErrorType = ValidationError -- ... instanceToJSON
ErrorType where toJSON = \case ValidationError ->String
"/errors#validation-error" {- ... -} = do {- ... -} unless validationSuccessful do throwError $rfc7807ServerError
(Proxy @ProblemJSON
)err400
ValidationError \e -> e {$sel:title:Rfc7807Error
= "Request failed to pass data validation" -- ... }
Mime Type application/problem+json
data ProblemJSON Source #
Media type defined by
RFC7807:
application/problem+json
The way how this mime type is handled is the same as
JSON
.
Instances
Accept ProblemJSON Source # | application/problem+json; charset=utf-8 |
Defined in Servant.Server.RFC7807 contentType :: Proxy ProblemJSON -> MediaType # | |
ToJSON a => MimeRender ProblemJSON a Source # | |
Defined in Servant.Server.RFC7807 mimeRender :: Proxy ProblemJSON -> a -> ByteString # | |
FromJSON a => MimeUnrender ProblemJSON a Source # | |
Defined in Servant.Server.RFC7807 mimeUnrender :: Proxy ProblemJSON -> ByteString -> Either String a # mimeUnrenderWithType :: Proxy ProblemJSON -> MediaType -> ByteString -> Either String a # |
Usage Examples
These examples focus on usage of rfc7807ServerError
, to see examples more
related to the Rfc7807Error
messages go to Network.HTTP.RFC7807 module.
Haskell/GHC language extensions being used in the examples:
RecordWildCards
andNamedFieldPuns
— please read this great article if you're not familiar with these extensions: The Power of RecordWildCards by Dmitrii Kovanikov.OverloadedStrings
— allows us to define string literals for types likeText
without needing to manually pack/convertString
values. See GHC User's Guide — Overloaded string literals for more information.
Direct Use Example
This example is intended to illustrate how we can start producing RFC7807
style responses without too much fuss. No complex abstractions, no custom
wrappers for Rfc7807Error
, no custom serialisation, and no extra context
.
@ -- | Servant definition of an endpoint. type SomeEndpoint = {- ... -}
- - | This code is not complex enough to actually need to be in a function,
- - but it makes some things more obious and easier to change.
badRequest
:: ( MonadError
ServerError
m ,ToJSON
errorType ,ToJSON
errorInfo ) => errorType - > (
Rfc7807Error
errorType errorInfo () - >
Rfc7807Error
errorType errorInfo () ) - > m a
badRequest errorType =
throwError .
rfc7807ServerError
(Proxy @ProblemJSON
)err400
errorType - - | See Network.HTTP.RFC7807 module for more information and examples on
- - how to use and define data types to be used for
errorType
. data ErrorType = ValidationError - - ...
instance ToJSON
ErrorType where
toJSON = \case
ValidationError ->
String
"/errors#some-endpoint-validation-error"
someHandler :: ServerT
SomeEndpoint m
someHandler request = do
response <- doTheEndpointStuffBasedOn request
case response of Success r -> pure r
InvalidRequest error_@DataValidationFailed ->
badRequest ValidationError \e -> e
{ title = "Request data validation failed"
, detail = "One or more members of request's 'data' field-- \ failed validation, see error
field"
Re-exported
When using Rfc7807Error
in more complex way, please, depend on
Network.HTTP.RFC7807 module directly. More information and more
detailed usage examples can be found in Network.HTTP.RFC7807 module
documentation.
data Rfc7807Error errorType errorInfo context Source #
Based on RFC7807 with few
additional fields
and $sel:error_:Rfc7807Error
:: errorInfo
.$sel:context:Rfc7807Error
:: context
Meaning of individual type parameters:
errorType
- Represents an URI reference. Easiest to start with is just
using
Text
type; simplest and most extensible is defining an enum with aToJSON
, see Usage Examples section for an enum example. errorInfo
- Not defined by RFC7807. This type is intended to provide a
different representation of the error. This is very useful when you're
retrofitting RFC7807 style messages into an existing error reporting.
Another common use case is when client needs to understand the error
response. For example, form validation errors that need to be displayed in
context of the element that failed validation. If you're not using this
you can set the type to
()
. context
- Not defined by RFC3986. This type is intended to provide more
details/context to what has happened. For example, IDs of entities that
were involved. If you're not using this you can set the type to
()
.
Rfc7807Error | |
|
Instances
(Eq errorType, Eq errorInfo, Eq context) => Eq (Rfc7807Error errorType errorInfo context) Source # | |
Defined in Network.HTTP.RFC7807 (==) :: Rfc7807Error errorType errorInfo context -> Rfc7807Error errorType errorInfo context -> Bool # (/=) :: Rfc7807Error errorType errorInfo context -> Rfc7807Error errorType errorInfo context -> Bool # | |
(Show errorType, Show errorInfo, Show context) => Show (Rfc7807Error errorType errorInfo context) Source # | |
Defined in Network.HTTP.RFC7807 showsPrec :: Int -> Rfc7807Error errorType errorInfo context -> ShowS # show :: Rfc7807Error errorType errorInfo context -> String # showList :: [Rfc7807Error errorType errorInfo context] -> ShowS # | |
Generic (Rfc7807Error errorType errorInfo context) Source # | |
Defined in Network.HTTP.RFC7807 type Rep (Rfc7807Error errorType errorInfo context) :: Type -> Type # from :: Rfc7807Error errorType errorInfo context -> Rep (Rfc7807Error errorType errorInfo context) x # to :: Rep (Rfc7807Error errorType errorInfo context) x -> Rfc7807Error errorType errorInfo context # | |
(ToJSON errorType, ToJSON errorInfo, ToJSON context) => ToJSON (Rfc7807Error errorType errorInfo context) Source # | Encode using |
Defined in Network.HTTP.RFC7807 toJSON :: Rfc7807Error errorType errorInfo context -> Value # toEncoding :: Rfc7807Error errorType errorInfo context -> Encoding # toJSONList :: [Rfc7807Error errorType errorInfo context] -> Value # toEncodingList :: [Rfc7807Error errorType errorInfo context] -> Encoding # | |
(FromJSON errorType, FromJSON errorInfo, FromJSON context, Typeable errorType, Typeable errorInfo, Typeable context) => FromJSON (Rfc7807Error errorType errorInfo context) Source # | Decode using |
Defined in Network.HTTP.RFC7807 parseJSON :: Value -> Parser (Rfc7807Error errorType errorInfo context) # parseJSONList :: Value -> Parser [Rfc7807Error errorType errorInfo context] # | |
type Rep (Rfc7807Error errorType errorInfo context) Source # | |
Defined in Network.HTTP.RFC7807 type Rep (Rfc7807Error errorType errorInfo context) = D1 ('MetaData "Rfc7807Error" "Network.HTTP.RFC7807" "http-rfc7807-0.2.0.0-6au3NoWFtoWA71C7NGJZQz" 'False) (C1 ('MetaCons "Rfc7807Error" 'PrefixI 'True) ((S1 ('MetaSel ('Just "type_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 errorType) :*: (S1 ('MetaSel ('Just "title") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "status") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)))) :*: ((S1 ('MetaSel ('Just "detail") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "instance_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "error_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe errorInfo)) :*: S1 ('MetaSel ('Just "context") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe context)))))) |