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

Servant.Server.RFC7807

Description

Servant support for RFC7807 — Problem Details for HTTP APIs style response messages.

Synopsis

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.

rfc7807ServerError Source #

Arguments

:: 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. JSON or ProblemJSON.

-> ServerError

One of Servant error values e.g. err400.

-> errorType

Value of the $sel:type_:Rfc7807Error field ("type" in JSON), the only mandatory parameter for RFC7807 content.

-> (Rfc7807Error errorType errorInfo context -> body)

Modify the Rfc7807Error type to your hearts desire.

The Rfc7807Error errorType errorInfo context given to this function will have type, title, and status set. Values for title and status are taken from Servant's ServerError. It is highly advised to modify the title to something more useful.

Reason for the return type to be polymorphic (i.e. body) is that we may want to use a newtype to use a different encoding. This still allows us to use the Rfc7807Error errorType errorInfo context type as a return type if errorType, errorInfo, and context can be encoded into JSON. In other words, id is a valid fit.

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

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

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:

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