wai-problem-details-0.1.1.0: Problem details middleware for WAI
Safe HaskellSafe-Inferred
LanguageHaskell2010

Network.Wai.Middleware.ProblemDetails

Description

Middleware for WAI that implements the problem details RFC specified in https://www.rfc-editor.org/rfc/rfc7807.

Example:

{-# LANGUAGE OverloadedStrings #-}

module Main where

import Network.Wai.Handler.Warp (run)
import Data.Default
import Network.Wai.Middleware.ProblemDetails

main :: IO ()
main = run 8080 $ problemDetails $ app
  where
    app request respond = throwProblemDetails def

See the project's README and tests for more examples.

Synopsis

Documentation

data ProblemDetails Source #

The problem details data type.

Instances

Instances details
ToJSON ProblemDetails Source # 
Instance details

Defined in Network.Wai.Middleware.ProblemDetails.Internal.Types

Generic ProblemDetails Source # 
Instance details

Defined in Network.Wai.Middleware.ProblemDetails.Internal.Types

Associated Types

type Rep ProblemDetails :: Type -> Type #

Show ProblemDetails Source # 
Instance details

Defined in Network.Wai.Middleware.ProblemDetails.Internal.Types

Default ProblemDetails Source # 
Instance details

Defined in Network.Wai.Middleware.ProblemDetails.Internal.Types

Methods

def :: ProblemDetails #

type Rep ProblemDetails Source # 
Instance details

Defined in Network.Wai.Middleware.ProblemDetails.Internal.Types

type Rep ProblemDetails = D1 ('MetaData "ProblemDetails" "Network.Wai.Middleware.ProblemDetails.Internal.Types" "wai-problem-details-0.1.1.0-7KTz629N8OeJtVEh92E1wM" 'False) (C1 ('MetaCons "ProblemDetails" 'PrefixI 'True) ((S1 ('MetaSel ('Just "pdType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "pdTitle") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "pdStatus") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int)))) :*: (S1 ('MetaSel ('Just "pdDetail") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "pdInstance") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "pdExtensions") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Value))))))

setType :: URI -> ProblemDetails -> ProblemDetails Source #

setType sets the type field of the problem details object.

setTitle :: Text -> ProblemDetails -> ProblemDetails Source #

setTitle sets the title field of the problem details object.

title :: ProblemDetails -> Maybe Text Source #

title return the title for this ProblemDetails

setDetail :: Text -> ProblemDetails -> ProblemDetails Source #

setDetail sets the detail field of the problem details object.

setInstance :: URI -> ProblemDetails -> ProblemDetails Source #

setInstance sets the instance field of the problem details object.

setExtensions :: Value -> ProblemDetails -> ProblemDetails Source #

setExtensions adds the provided extensions to the problem details object.

setStatus :: Int -> ProblemDetails -> ProblemDetails Source #

setStatus sets the status field of the problem details object.

status :: ProblemDetails -> Maybe Int Source #

status return the status for this ProblemDetails

problemDetails :: Middleware Source #

Middleware that sends a problem+json response when an exception of type ProblemDetailsException is thrown from a WAI application.