http-rfc7807-0.2.0.0: RFC7807 style response messages
Copyright(c) 2020 Peter Trško
LicenseBSD3
Maintainerpeter.trsko@gmail.com
Stabilityexperimental
PortabilityGHC specific language extensions.
Safe HaskellNone
LanguageHaskell2010

Network.HTTP.RFC7807

Description

Synopsis

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:

  1. JSON (application/problem+json) and
  2. 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 $sel:error_:Rfc7807Error :: errorInfo and $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 a ToJSON, 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 ().

Constructors

Rfc7807Error 

Fields

  • type_ :: errorType

    (required) A URI reference (see RFC3986) that identifies the problem type. This specification encourages that, when dereferenced, it provide human-readable documentation for the problem type (e.g., using HTML W3C.REC-html5-20141028). When this member is not present, its value is assumed to be "about:blank".

    Consumers MUST use the "type" string as the primary identifier for the problem type; the "title" string is advisory and included only for users who are not aware of the semantics of the URI and do not have the ability to discover them (e.g., offline log analysis). Consumers SHOULD NOT automatically dereference the type URI.

    Relative URIs are accepted; this means that they must be resolved relative to the document's base URI, as per RFC3986, Section 5.

    Notes:

    In JSON this filed is named only "type".

  • title :: Maybe Text

    (optional) A short, human-readable summary of the problem type. It SHOULD NOT change from occurrence to occurrence of the problem, except for purposes of localization (e.g., using proactive content negotiation; see RFC7231, Section 3.4.

    Consumers MUST use the "type" string as the primary identifier for the problem type; the "title" string is advisory and included only for users who are not aware of the semantics of the URI and do not have the ability to discover them (e.g., offline log analysis). Consumers SHOULD NOT automatically dereference the type URI.

    Notes:

    In JSON this filed is named "title".

  • status :: Maybe Int

    (optional) The HTTP status code (see RFC7231, Section 6) generated by the origin server for this occurrence of the problem.

    If present, is only advisory; it conveys the HTTP status code used for the convenience of the consumer. Generators MUST use the same status code in the actual HTTP response, to assure that generic HTTP software that does not understand this format still behaves correctly. See RFC7807, Section 5 for further caveats regarding its use.

    Consumers can use the status member to determine what the original status code used by the generator was, in cases where it has been changed (e.g., by an intermediary or cache), and when message bodies persist without HTTP information. Generic HTTP software will still use the HTTP status code.

    Notes:

    In JSON this filed is named "status".

  • detail :: Maybe Text

    (optional) A human-readable explanation specific to this occurrence of the problem.

    If present, ought to focus on helping the client correct the problem, rather than giving debugging information. Consumers SHOULD NOT parse the "detail" member for information; extensions are more suitable and less error-prone ways to obtain such information.

    Notes:

    In JSON this filed is named "detail".

  • instance_ :: Maybe Text

    (optional) A URI reference that identifies the specific occurrence of the problem. It may or may not yield further information if dereferenced.

    Relative URIs are accepted; this means that they must be resolved relative to the document's base URI, as per RFC3986, Section 5.

    Notes:

    In JSON this filed ins named only "instance".

  • error_ :: Maybe errorInfo

    (optional, extension) An additional representation of the error. Lots of clients detect that the response is an error using simple algorithm of checking presence of the field "error" that has non-null value.

    Notes:

    How the field is named in the resulting JSON object is controlled by $sel:extensionFieldName:EncodingOptions, but by default it is "error".

  • context :: Maybe context

    (optional, extension) Extra information for the purposes of debugging.

    Notes:

    How the field is named in the resulting JSON object is controlled by $sel:extensionFieldName:EncodingOptions, but by default it is "context".

Instances

Instances details
(Eq errorType, Eq errorInfo, Eq context) => Eq (Rfc7807Error errorType errorInfo context) Source # 
Instance details

Defined in Network.HTTP.RFC7807

Methods

(==) :: 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 # 
Instance details

Defined in Network.HTTP.RFC7807

Methods

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 # 
Instance details

Defined in Network.HTTP.RFC7807

Associated Types

type Rep (Rfc7807Error errorType errorInfo context) :: Type -> Type #

Methods

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 toKeyValue defaultEncodingOptions.

Instance details

Defined in Network.HTTP.RFC7807

Methods

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 parseObject defaultEncodingOptions.

Instance details

Defined in Network.HTTP.RFC7807

Methods

parseJSON :: Value -> Parser (Rfc7807Error errorType errorInfo context) #

parseJSONList :: Value -> Parser [Rfc7807Error errorType errorInfo context] #

type Rep (Rfc7807Error errorType errorInfo context) Source # 
Instance details

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:

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.

Constructors

EncodingOptions 

Fields

  • omitNothingFields :: Bool

    Should empty fields be omitted in the JSON representation?

    If set to True (default)
    then record fields of Rfc7807Error with a Nothing value will be omitted from the resulting object instead of being represented as null.
    If set to False
    then the resulting JSON object will include those fields and the Nothing value will be mapped to null JSON value.

    Notes:

    This setting is ignored by parseObject function as respecting it would mean that even valid RFC7807 messages would fail to parse.

  • omitExtensionField :: ExtensionField -> Bool

    Should specified extension field be omitted in the JSON representation?

    If the function returns True
    then the specified record field of Rfc7807Error will be omitted entirely even if it contains Just value.
    If the function returns False
    then the specified record field is included in the serialised output. However, if the value of that field is Nothing and $sel:omitNothingFields:EncodingOptions is set to True then the field will once again be omitted from the resulting JSON object.

    Notes:

    This setting can be used in a similar fashion as verbosity level. For example, we can omit these fields on production and have them enabled in testing or dev environments.

    This setting is respected by parseObject function, which will ignore extension fields for which the function returns True. Ignored extension fields will always be set to Nothing.

  • extensionFieldName :: ExtensionField -> Text

    How should the extension fields be named?

    Fields $sel:error_:Rfc7807Error and $sel:context:Rfc7807Error are not defined by RFC7807 and as such their names may be adjusted depending on our particular needs and conventions. This function allows exactly that.

    Notes:

    This setting is respected by parseObject function, which will use this function when searching for extension fields in a JSON object.

Instances

Instances details
Generic EncodingOptions Source # 
Instance details

Defined in Network.HTTP.RFC7807

Associated Types

type Rep EncodingOptions :: Type -> Type #

type Rep EncodingOptions Source # 
Instance details

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)))))

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.

Constructors

ErrorField

Represents the name of the $sel:error_:Rfc7807Error field of Rfc7807Error data type.

ContextField

Represents the name of the $sel:context:Rfc7807Error field of Rfc7807Error data type.

Instances

Instances details
Eq ExtensionField Source # 
Instance details

Defined in Network.HTTP.RFC7807

Show ExtensionField Source # 
Instance details

Defined in Network.HTTP.RFC7807

Generic ExtensionField Source # 
Instance details

Defined in Network.HTTP.RFC7807

Associated Types

type Rep ExtensionField :: Type -> Type #

type Rep ExtensionField Source # 
Instance details

Defined in Network.HTTP.RFC7807

type Rep ExtensionField = D1 ('MetaData "ExtensionField" "Network.HTTP.RFC7807" "http-rfc7807-0.2.0.0-6au3NoWFtoWA71C7NGJZQz" 'False) (C1 ('MetaCons "ErrorField" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ContextField" 'PrefixI 'False) (U1 :: Type -> Type))

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:

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
    {- ... -}

instance ToJSON 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
    {- ... -}

instance ToJSON ErrorType where
    toJSON = \case
        DocumentNotFound ->
            -- The URL doesn't have to be absolute. See description of
            -- $sel:type_:Rfc7807Error field of Rfc7807Error 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
-- default Rfc7807Error 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
    }

instance ToJSON ErrorResponse where
    toJSON :: ErrorResponse -> Value
    toJSON ErrorResponse{..} =
         object . toKeyValue errorResponseEncodingOptions
    {- ... -}

instance FromJSON ErrorResponse where
    parseJSON :: 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 Text Value@) 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 tell toKeyValue and parseObject 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 = \case
        ErrorField -> False
        ContextField -> True

    , $sel:extensionFieldName:EncodingOptions = \case
        ErrorField -> "error_message"
        name -> $sel:extensionFieldName:EncodingOptions defaultEncodingOptions name
    }

instance ToJSON => ToJSON (ErrorResponse e) where
    toJSON :: 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
        )
    {- ... -}

instance FromJSON e => FromJSON (ErrorResponse e) where
    parseJSON :: 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 ->
                 k notElem 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.