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 :: 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.
:: 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 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 wheretoJSON
= \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 # |
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.1.0.0-D6HqAGioRJtIjgJE9PHCP5" '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)))))) |