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 |
RFC7807 — Problem Details for HTTP APIs style response messages.
Synopsis
- data Rfc7807Error errorType errorInfo context = Rfc7807Error {}
- rfc7807Error :: errorType -> Rfc7807Error errorType errorInfo context
- toKeyValue :: forall kv errorType errorInfo context. (ToJSON errorType, ToJSON errorInfo, ToJSON context, KeyValue kv, Monoid kv) => EncodingOptions -> Rfc7807Error errorType errorInfo context -> kv
- parseObject :: forall errorType errorInfo context. (FromJSON errorType, FromJSON errorInfo, FromJSON context) => EncodingOptions -> Object -> Parser (Rfc7807Error errorType errorInfo context)
- data EncodingOptions = EncodingOptions {}
- defaultEncodingOptions :: EncodingOptions
- data ExtensionField
Documentation
This module defines Rfc7807Error
data type that represents
RFC7807 style response message along
with few extensions that are not defined by the standard, but allowed by it.
The sandard specifies two serialisation formats:
- JSON (
application/problem+json
) and - XML (
application/problem+xml
)
This package supports only JSON serialisation, but it should not be hard to build XML serialisation yourself, if required. We also expose few low-level definitions for cases when you want to build your own JSON serialisation that is compatible with the standard. If you're interested in that then best to look at Usage Examples and Encoding and Decoding sections.
This package also provides Servant integration that is defined in a separate module Servant.Server.RFC7807.
If you want to jump straight to using this then go directly to Usage Examples section.
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)))))) |
rfc7807Error :: errorType -> Rfc7807Error errorType errorInfo context Source #
Constructor for Rfc7807Error
that set's only $sel:type_:Rfc7807Error
and everything else
is set to Nothing
.
Usage Example
This example illustrates how the function is used, not necessarily the best error response you can provide to your client:
(rfc7807Error
"/errors#not-found"){$sel:status:Rfc7807Error
= 404}
Encoding and Decoding
Definitions in this section are useful for defining your own JSON encoding/decoding. See Usage Examples section for ideas on how to use them.
What's provided in here are:
- Function
toKeyValue
for generic serialisation ofRfc7807Error
into JSON object representation. - Function
parseObject
for parsing JSONObject
(key-value map) intoRfc7807Error
. - Parameters that modify behaviour of
toKeyValue
and 'parseObject:EncodingOptions
,defaultEncodingOptions
, andExtensionField
.
toKeyValue :: forall kv errorType errorInfo context. (ToJSON errorType, ToJSON errorInfo, ToJSON context, KeyValue kv, Monoid kv) => EncodingOptions -> Rfc7807Error errorType errorInfo context -> kv Source #
Serialise Rfc7807Error
into a key-value pairs. It's abstract to support
both types of Aeson encodings (Object
and Encoding
) at once.
Usage Examples
Object
.toKeyValue
defaultEncodingOptions
:: (ToJSON
errorType ,ToJSON
errorInfo ,ToJSON
context ) =>Rfc7807Error
errorType errorInfo context ->Value
pairs
.toKeyValue
defaultEncodingOptions
:: (ToJSON
errorType ,ToJSON
errorInfo ,ToJSON
context ) =>Rfc7807Error
errorType errorInfo context ->Encoding
parseObject :: forall errorType errorInfo context. (FromJSON errorType, FromJSON errorInfo, FromJSON context) => EncodingOptions -> Object -> Parser (Rfc7807Error errorType errorInfo context) Source #
Parse JSON value into Rfc7807Error
. Reason for taking Object
instead of Value
is that it allows us to define serialisation for
our own data types with extra fields while preserving RFC7807 message
structure.
Usage example
withObject
"ErrorResponse" \o ->parseObject
defaultEncodingOptions
o
data EncodingOptions Source #
Parameters that allow us to control certain aspects of how Rfc7807Error
is encoded/decoded to/from JSON.
EncodingOptions | |
|
Instances
Generic EncodingOptions Source # | |
Defined in Network.HTTP.RFC7807 type Rep EncodingOptions :: Type -> Type # from :: EncodingOptions -> Rep EncodingOptions x # to :: Rep EncodingOptions x -> EncodingOptions # | |
type Rep EncodingOptions Source # | |
Defined in Network.HTTP.RFC7807 type Rep EncodingOptions = D1 ('MetaData "EncodingOptions" "Network.HTTP.RFC7807" "http-rfc7807-0.2.0.0-6au3NoWFtoWA71C7NGJZQz" 'False) (C1 ('MetaCons "EncodingOptions" 'PrefixI 'True) (S1 ('MetaSel ('Just "omitNothingFields") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "omitExtensionField") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ExtensionField -> Bool)) :*: S1 ('MetaSel ('Just "extensionFieldName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ExtensionField -> Text))))) |
defaultEncodingOptions :: EncodingOptions Source #
Default EncodingOptions
:
defaultEncodingOptions =EncodingOptions
{$sel:omitNothingFields:EncodingOptions
= True ,$sel:omitExtensionField:EncodingOptions
= const False }
data ExtensionField Source #
Enum representing the extension fields $sel:error_:Rfc7807Error
and $sel:context:Rfc7807Error
that are not
defined by RFC7807.
This allows us to reference the field in EncodingOptions
and later in
toKeyValue
and parseObject
without resolving to using Text
.
ErrorField | Represents the name of the |
ContextField | Represents the name of the |
Instances
Eq ExtensionField Source # | |
Defined in Network.HTTP.RFC7807 (==) :: ExtensionField -> ExtensionField -> Bool # (/=) :: ExtensionField -> ExtensionField -> Bool # | |
Show ExtensionField Source # | |
Defined in Network.HTTP.RFC7807 showsPrec :: Int -> ExtensionField -> ShowS # show :: ExtensionField -> String # showList :: [ExtensionField] -> ShowS # | |
Generic ExtensionField Source # | |
Defined in Network.HTTP.RFC7807 type Rep ExtensionField :: Type -> Type # from :: ExtensionField -> Rep ExtensionField x # to :: Rep ExtensionField x -> ExtensionField # | |
type Rep ExtensionField Source # | |
Defined in Network.HTTP.RFC7807 |
Usage Examples
We start with a simple use case in Type Alias section and we get progressively more complicated. Which one is best for you depends on many factors. There's a little guidance that we can give you in that regard, but maybe consider following:
- If you are just exploring or evaluating multiple options then maybe start with the simple example first.
- If you want to integrate RFC7807 style messages into existing system, while requiring backward compatibility, then go with the more complicated example. It will allow you to merge existing error responses with RFC7807 style ones more easily.
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.LambdaCase
— allows us to use\case
as a short hand for\x -> case x of
. See GHC User's Guide — Lambda-case for more information.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.
Type Alias
The easiest way how to use Rfc7807Error
data type without always needing
to pass all the type arguments is by creating a type alias like this:
type ErrorResponse =Rfc7807Error
ErrorType () () data ErrorType = DocumentNotFound {- ... -} instanceToJSON
ErrorType where toJSON = \case DocumentNotFound ->String
"https://example.com/docs/error#document-not-found" {- ... -}
If you want custom value in "error"
field then you can either specify
the type to the one you're using or leave errorInfo
type variable
polymorphic. The later has the advantage that different types can be used
for different REST API resources/endpoints:
type ErrorResponse errorInfo =Rfc7807Error
ErrorType errorInfo () data ErrorType = DocumentNotFound {- ... -} instanceToJSON
ErrorType where toJSON = \case DocumentNotFound -> -- The URL doesn't have to be absolute. See description of --$sel:type_:Rfc7807Error
field ofRfc7807Error
for more information.String
"https://example.com/docs/error#document-not-found" {- ... -}
Newtype
While it is possible to use Rfc7807Error
directly, using newtype allows to
be more flexible with how things are encoded. If you're expecting your use
cases to evolve over time it is good to start with something like this:
-- | See "Type Alias" section for @ErrorType@ example. data ErrorType = {- ... -} newtype ErrorResponse = ErrorResponse { errorResponse ::Rfc7807Error
ErrorType () () } -- Following encoding example is very simple, basicaly the same thing as the -- defaultRfc7807Error
encoding. However, it's a template that when -- copied allows us to adjust bits that we want different. errorResponseEncodingOptions ::EncodingOptions
errorResponseEncodingOptions =defaultEncodingOptions
{$sel:omitExtensionField:EncodingOptions
= const True } instanceToJSON
ErrorResponse wheretoJSON
:: ErrorResponse ->Value
toJSON
ErrorResponse{..} =object
.toKeyValue
errorResponseEncodingOptions {- ... -} instanceFromJSON
ErrorResponse whereparseJSON
:: ErrorResponse ->Value
parseJSON
=withObject
"ErrorResponse" \o -> ErrorResponse $parseObject
errorResponseEncodingOptions o
Extra Fields Example
This is an elaboration of the previous "Newtype" example. We will use
errorInfo
and context
type arguments of Rfc7807Error
to include more
information. The errorInfo
will be kept polymorphic so that each HTTP
response can use a different one, depending on its needs.
-- | See "Type Alias" section for @ErrorType@ example. data ErrorType = {- ... -} -- | We can use a concrete data type or we can use something flexible like --Object
(actually a @HashMap TextValue
@) allowing us to -- include any kind of metadata. -- -- This approach intentionally resembles structured logging approach like -- the one used by katip library. type ErrorContext =Object
newtype ErrorResponse e = ErrorResponse { errorResponse ::Rfc7807Error
ErrorType e ErrorContext } -- Following serialisation example is just one of many possibilities. What -- it illustrates is how much flexibility we have. Not only we can rename -- fields through$sel:extensionFieldName:EncodingOptions
, we can also play with the encoding -- to get something that is more suitable for our system. -- | What we'll do is serialise the @ErrorContext@ manually. To be able to -- do that we need to telltoKeyValue
andparseObject
to ignore the -- extension field. -- -- Another thing that we'll do is that we'll rename the"error"
field to --"error_message"
. This is one of those things that are useful when -- we are changing existing error responses. errorResponseEncodingOptions ::EncodingOptions
errorResponseEncodingOptions =defaultEncodingOptions
{$sel:omitExtensionField:EncodingOptions
= \caseErrorField
-> FalseContextField
-> True ,$sel:extensionFieldName:EncodingOptions
= \caseErrorField
-> "error_message" name ->$sel:extensionFieldName:EncodingOptions
defaultEncodingOptions
name } instanceToJSON
=>ToJSON
(ErrorResponse e) wheretoJSON
:: ErrorResponse ->Value
toJSON
ErrorResponse{errorResponse} =Object
(toKeyValue
errorResponseEncodingOptions errorResponse -- We'll take everything that's in context and put it directly into -- the top-level JSON object. -- -- The downside of this approach is that we need to be careful not -- to redefine already existing fields. What we could do is change -- the field names. It is quite common to use "@fieldName" or -- similar convention for metadata. -- -- If we go with custom data type we can then examine if it's JSON -- object or not. If not we can instead put it into the "context" -- field as a kind of a default. <> context errorResponse ) {- ... -} instanceFromJSON
e =>FromJSON
(ErrorResponse e) whereparseJSON
:: ErrorResponse ->Value
parseJSON
=withObject
"ErrorResponse" \o -> errorResponse <-parseObject
errorResponseEncodingOptions o -- Now we'll take all the fields that are not part of RFC7807 or -- "error" and put them into context. let context = flip filterWithKey o \k _v -> knotElem
parsedFields pure ErrorResponse { errorResponse = errorResponse{context} } where parsedFields = -- These hardcoded values are okay since RFC7807 defines the -- names and we cannot change them. [ "type", "title", "status", "detail", "instance" ,$sel:extensionFieldName:EncodingOptions
ErrorField
]
At this point we may want to provide few helper functions for constructing
ErrorResponse
(also known as smart constructors) to fit in nicely with the
rest of our code base and HTTP framework we are using. You may want to look
at Servant.Server.RFC7807 module, even if you're using a different
framework. It should give you few ideas on how to proceed.