| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
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 defSee the project's README and tests for more examples.
Synopsis
- data ProblemDetails
- setType :: URI -> ProblemDetails -> ProblemDetails
- setTitle :: Text -> ProblemDetails -> ProblemDetails
- title :: ProblemDetails -> Maybe Text
- setDetail :: Text -> ProblemDetails -> ProblemDetails
- setInstance :: URI -> ProblemDetails -> ProblemDetails
- setExtensions :: Value -> ProblemDetails -> ProblemDetails
- setStatus :: Int -> ProblemDetails -> ProblemDetails
- status :: ProblemDetails -> Maybe Int
- newtype ProblemDetailsException = ProblemDetailsException ProblemDetails
- throwProblemDetails :: ProblemDetails -> a
- throwProblemDetailsIO :: ProblemDetails -> IO a
- problemDetails400 :: ProblemDetails
- problemDetails401 :: ProblemDetails
- problemDetails403 :: ProblemDetails
- problemDetails404 :: ProblemDetails
- problemDetails409 :: ProblemDetails
- problemDetails :: Middleware
Documentation
data ProblemDetails Source #
The problem details data type.
Instances
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
newtype ProblemDetailsException Source #
The exception that can be thrown from WAI applications when using the problem details middleware to send a problem details response.
Constructors
| ProblemDetailsException ProblemDetails |
Instances
throwProblemDetails :: ProblemDetails -> a Source #
Throw a ProblemDetailsException from a pure context.
throwProblemDetailsIO :: ProblemDetails -> IO a Source #
Throw a ProblemDetailsException from an IO context.
problemDetails :: Middleware Source #
Middleware that sends a problem+json response when an exception of type
ProblemDetailsException is thrown from a WAI application.