{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}

-- | Types and constants to describe HTTP status codes.
--
-- At the bottom are some functions to check if a given 'Status' is from a certain category. (i.e. @1XX@, @2XX@, etc.)
module Network.HTTP.Types.Status (
    -- * HTTP Status

    -- If we ever want to deprecate the 'Status' data constructor:
    -- #if __GLASGOW_HASKELL__ >= 908
    --   {-# DEPRECATED "Use 'mkStatus' when constructing a 'Status'" #-} Status(Status)
    -- #else
    Status (Status),
    -- #endif
    statusCode,
    statusMessage,
    mkStatus,

    -- * Common statuses
    status100,
    continue100,
    status101,
    switchingProtocols101,
    status200,
    ok200,
    status201,
    created201,
    status202,
    accepted202,
    status203,
    nonAuthoritative203,
    status204,
    noContent204,
    status205,
    resetContent205,
    status206,
    partialContent206,
    status300,
    multipleChoices300,
    status301,
    movedPermanently301,
    status302,
    found302,
    status303,
    seeOther303,
    status304,
    notModified304,
    status305,
    useProxy305,
    status307,
    temporaryRedirect307,
    status308,
    permanentRedirect308,
    status400,
    badRequest400,
    status401,
    unauthorized401,
    status402,
    paymentRequired402,
    status403,
    forbidden403,
    status404,
    notFound404,
    status405,
    methodNotAllowed405,
    status406,
    notAcceptable406,
    status407,
    proxyAuthenticationRequired407,
    status408,
    requestTimeout408,
    status409,
    conflict409,
    status410,
    gone410,
    status411,
    lengthRequired411,
    status412,
    preconditionFailed412,
    status413,
    requestEntityTooLarge413,
    status414,
    requestURITooLong414,
    status415,
    unsupportedMediaType415,
    status416,
    requestedRangeNotSatisfiable416,
    status417,
    expectationFailed417,
    status418,
    imATeapot418,
    status422,
    unprocessableEntity422,
    status426,
    upgradeRequired426,
    status428,
    preconditionRequired428,
    status429,
    tooManyRequests429,
    status431,
    requestHeaderFieldsTooLarge431,
    status500,
    internalServerError500,
    status501,
    notImplemented501,
    status502,
    badGateway502,
    status503,
    serviceUnavailable503,
    status504,
    gatewayTimeout504,
    status505,
    status511,
    networkAuthenticationRequired511,
    httpVersionNotSupported505,

    -- * Checking status code category
    statusIsInformational,
    statusIsSuccessful,
    statusIsRedirection,
    statusIsClientError,
    statusIsServerError,
) where

import Data.ByteString as B (ByteString, empty)
import Data.Data (Data)
import Data.Typeable (Typeable)
import GHC.Generics (Generic)

-- | HTTP Status.
--
-- Only the 'statusCode' is used for comparisons.
--
-- /Please use 'mkStatus' to create status codes from code and message, or the 'Enum' instance or the/
-- /status code constants (like 'ok200'). There might be additional record members in the future./
--
-- Note that the 'Show' instance is only for debugging.
data Status = Status
    { Status -> Int
statusCode :: Int
    , Status -> ByteString
statusMessage :: B.ByteString
    }
    deriving
        ( Int -> Status -> ShowS
[Status] -> ShowS
Status -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Status] -> ShowS
$cshowList :: [Status] -> ShowS
show :: Status -> String
$cshow :: Status -> String
showsPrec :: Int -> Status -> ShowS
$cshowsPrec :: Int -> Status -> ShowS
Show
        , Typeable
        , -- | @since 0.12.4
          Typeable Status
Status -> DataType
Status -> Constr
(forall b. Data b => b -> b) -> Status -> Status
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Status -> u
forall u. (forall d. Data d => d -> u) -> Status -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Status -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Status -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Status -> m Status
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Status -> m Status
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Status
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Status -> c Status
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Status)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Status)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Status -> m Status
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Status -> m Status
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Status -> m Status
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Status -> m Status
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Status -> m Status
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Status -> m Status
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Status -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Status -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Status -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Status -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Status -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Status -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Status -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Status -> r
gmapT :: (forall b. Data b => b -> b) -> Status -> Status
$cgmapT :: (forall b. Data b => b -> b) -> Status -> Status
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Status)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Status)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Status)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Status)
dataTypeOf :: Status -> DataType
$cdataTypeOf :: Status -> DataType
toConstr :: Status -> Constr
$ctoConstr :: Status -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Status
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Status
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Status -> c Status
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Status -> c Status
Data
        , -- | @since 0.12.4
          forall x. Rep Status x -> Status
forall x. Status -> Rep Status x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Status x -> Status
$cfrom :: forall x. Status -> Rep Status x
Generic
        )

-- FIXME: If the data constructor of 'Status' is ever deprecated, we should define
-- a pattern synonym to minimize any breakage. This also involves changing the
-- name of the constructor, so that it doesn't clash with the new pattern synonym
-- that's replacing it.
--
-- > data Status = MkStatus ...
-- > pattern Status code msg = MkStatus code msg

-- | A 'Status' is equal to another 'Status' if the status codes are equal.
instance Eq Status where
    Status { statusCode :: Status -> Int
statusCode = Int
a } == :: Status -> Status -> Bool
== Status { statusCode :: Status -> Int
statusCode = Int
b } = Int
a forall a. Eq a => a -> a -> Bool
== Int
b

-- | 'Status'es are ordered according to their status codes only.
instance Ord Status where
    compare :: Status -> Status -> Ordering
compare Status { statusCode :: Status -> Int
statusCode = Int
a } Status { statusCode :: Status -> Int
statusCode = Int
b } = Int
a forall a. Ord a => a -> a -> Ordering
`compare` Int
b

-- | Be advised, that when using the \"enumFrom*\" family of methods or
-- ranges in lists, it will generate all possible status codes.
--
-- E.g. @[status100 .. status200]@ generates 'Status'es of @100, 101, 102 .. 198, 199, 200@
--
-- The statuses not included in this library will have an empty message.
--
-- @since 0.7.3
instance Enum Status where
    fromEnum :: Status -> Int
fromEnum = Status -> Int
statusCode
    toEnum :: Int -> Status
toEnum Int
100 = Status
status100
    toEnum Int
101 = Status
status101
    toEnum Int
200 = Status
status200
    toEnum Int
201 = Status
status201
    toEnum Int
202 = Status
status202
    toEnum Int
203 = Status
status203
    toEnum Int
204 = Status
status204
    toEnum Int
205 = Status
status205
    toEnum Int
206 = Status
status206
    toEnum Int
300 = Status
status300
    toEnum Int
301 = Status
status301
    toEnum Int
302 = Status
status302
    toEnum Int
303 = Status
status303
    toEnum Int
304 = Status
status304
    toEnum Int
305 = Status
status305
    toEnum Int
307 = Status
status307
    toEnum Int
308 = Status
status308
    toEnum Int
400 = Status
status400
    toEnum Int
401 = Status
status401
    toEnum Int
402 = Status
status402
    toEnum Int
403 = Status
status403
    toEnum Int
404 = Status
status404
    toEnum Int
405 = Status
status405
    toEnum Int
406 = Status
status406
    toEnum Int
407 = Status
status407
    toEnum Int
408 = Status
status408
    toEnum Int
409 = Status
status409
    toEnum Int
410 = Status
status410
    toEnum Int
411 = Status
status411
    toEnum Int
412 = Status
status412
    toEnum Int
413 = Status
status413
    toEnum Int
414 = Status
status414
    toEnum Int
415 = Status
status415
    toEnum Int
416 = Status
status416
    toEnum Int
417 = Status
status417
    toEnum Int
418 = Status
status418
    toEnum Int
422 = Status
status422
    toEnum Int
426 = Status
status426
    toEnum Int
428 = Status
status428
    toEnum Int
429 = Status
status429
    toEnum Int
431 = Status
status431
    toEnum Int
500 = Status
status500
    toEnum Int
501 = Status
status501
    toEnum Int
502 = Status
status502
    toEnum Int
503 = Status
status503
    toEnum Int
504 = Status
status504
    toEnum Int
505 = Status
status505
    toEnum Int
511 = Status
status511
    toEnum Int
c = Int -> ByteString -> Status
mkStatus Int
c ByteString
B.empty

-- | @since 0.11
instance Bounded Status where
    minBound :: Status
minBound = Status
status100
    maxBound :: Status
maxBound = Status
status511

-- | Create a 'Status' from a status code and message.
mkStatus :: Int -> B.ByteString -> Status
mkStatus :: Int -> ByteString -> Status
mkStatus = Int -> ByteString -> Status
Status

-- | Continue 100
--
-- @since 0.6.6
status100 :: Status
status100 :: Status
status100 = Int -> ByteString -> Status
mkStatus Int
100 ByteString
"Continue"

-- | Continue 100
--
-- @since 0.6.6
continue100 :: Status
continue100 :: Status
continue100 = Status
status100

-- | Switching Protocols 101
--
-- @since 0.6.6
status101 :: Status
status101 :: Status
status101 = Int -> ByteString -> Status
mkStatus Int
101 ByteString
"Switching Protocols"

-- | Switching Protocols 101
--
-- @since 0.6.6
switchingProtocols101 :: Status
switchingProtocols101 :: Status
switchingProtocols101 = Status
status101

-- | OK 200
status200 :: Status
status200 :: Status
status200 = Int -> ByteString -> Status
mkStatus Int
200 ByteString
"OK"

-- | OK 200
ok200 :: Status
ok200 :: Status
ok200 = Status
status200

-- | Created 201
status201 :: Status
status201 :: Status
status201 = Int -> ByteString -> Status
mkStatus Int
201 ByteString
"Created"

-- | Created 201
created201 :: Status
created201 :: Status
created201 = Status
status201

-- | Accepted 202
--
-- @since 0.6.6
status202 :: Status
status202 :: Status
status202 = Int -> ByteString -> Status
mkStatus Int
202 ByteString
"Accepted"

-- | Accepted 202
--
-- @since 0.6.6
accepted202 :: Status
accepted202 :: Status
accepted202 = Status
status202

-- | Non-Authoritative Information 203
--
-- @since 0.6.6
status203 :: Status
status203 :: Status
status203 = Int -> ByteString -> Status
mkStatus Int
203 ByteString
"Non-Authoritative Information"

-- | Non-Authoritative Information 203
--
-- @since 0.6.6
nonAuthoritative203 :: Status
nonAuthoritative203 :: Status
nonAuthoritative203 = Status
status203

-- | No Content 204
--
-- @since 0.6.6
status204 :: Status
status204 :: Status
status204 = Int -> ByteString -> Status
mkStatus Int
204 ByteString
"No Content"

-- | No Content 204
--
-- @since 0.6.6
noContent204 :: Status
noContent204 :: Status
noContent204 = Status
status204

-- | Reset Content 205
--
-- @since 0.6.6
status205 :: Status
status205 :: Status
status205 = Int -> ByteString -> Status
mkStatus Int
205 ByteString
"Reset Content"

-- | Reset Content 205
--
-- @since 0.6.6
resetContent205 :: Status
resetContent205 :: Status
resetContent205 = Status
status205

-- | Partial Content 206
--
-- @since 0.5.1
status206 :: Status
status206 :: Status
status206 = Int -> ByteString -> Status
mkStatus Int
206 ByteString
"Partial Content"

-- | Partial Content 206
--
-- @since 0.5.1
partialContent206 :: Status
partialContent206 :: Status
partialContent206 = Status
status206

-- | Multiple Choices 300
status300 :: Status
status300 :: Status
status300 = Int -> ByteString -> Status
mkStatus Int
300 ByteString
"Multiple Choices"

-- | Multiple Choices 300
multipleChoices300 :: Status
multipleChoices300 :: Status
multipleChoices300 = Status
status300

-- | Moved Permanently 301
status301 :: Status
status301 :: Status
status301 = Int -> ByteString -> Status
mkStatus Int
301 ByteString
"Moved Permanently"

-- | Moved Permanently 301
movedPermanently301 :: Status
movedPermanently301 :: Status
movedPermanently301 = Status
status301

-- | Found 302
status302 :: Status
status302 :: Status
status302 = Int -> ByteString -> Status
mkStatus Int
302 ByteString
"Found"

-- | Found 302
found302 :: Status
found302 :: Status
found302 = Status
status302

-- | See Other 303
status303 :: Status
status303 :: Status
status303 = Int -> ByteString -> Status
mkStatus Int
303 ByteString
"See Other"

-- | See Other 303
seeOther303 :: Status
seeOther303 :: Status
seeOther303 = Status
status303

-- | Not Modified 304
--
-- @since 0.6.1
status304 :: Status
status304 :: Status
status304 = Int -> ByteString -> Status
mkStatus Int
304 ByteString
"Not Modified"

-- | Not Modified 304
--
-- @since 0.6.1
notModified304 :: Status
notModified304 :: Status
notModified304 = Status
status304

-- | Use Proxy 305
--
-- @since 0.6.6
status305 :: Status
status305 :: Status
status305 = Int -> ByteString -> Status
mkStatus Int
305 ByteString
"Use Proxy"

-- | Use Proxy 305
--
-- @since 0.6.6
useProxy305 :: Status
useProxy305 :: Status
useProxy305 = Status
status305

-- | Temporary Redirect 307
--
-- @since 0.6.6
status307 :: Status
status307 :: Status
status307 = Int -> ByteString -> Status
mkStatus Int
307 ByteString
"Temporary Redirect"

-- | Temporary Redirect 307
--
-- @since 0.6.6
temporaryRedirect307 :: Status
temporaryRedirect307 :: Status
temporaryRedirect307 = Status
status307

-- | Permanent Redirect 308
--
-- @since 0.9
status308 :: Status
status308 :: Status
status308 = Int -> ByteString -> Status
mkStatus Int
308 ByteString
"Permanent Redirect"

-- | Permanent Redirect 308
--
-- @since 0.9
permanentRedirect308 :: Status
permanentRedirect308 :: Status
permanentRedirect308 = Status
status308

-- | Bad Request 400
status400 :: Status
status400 :: Status
status400 = Int -> ByteString -> Status
mkStatus Int
400 ByteString
"Bad Request"

-- | Bad Request 400
badRequest400 :: Status
badRequest400 :: Status
badRequest400 = Status
status400

-- | Unauthorized 401
status401 :: Status
status401 :: Status
status401 = Int -> ByteString -> Status
mkStatus Int
401 ByteString
"Unauthorized"

-- | Unauthorized 401
unauthorized401 :: Status
unauthorized401 :: Status
unauthorized401 = Status
status401

-- | Payment Required 402
--
-- @since 0.6.6
status402 :: Status
status402 :: Status
status402 = Int -> ByteString -> Status
mkStatus Int
402 ByteString
"Payment Required"

-- | Payment Required 402
--
-- @since 0.6.6
paymentRequired402 :: Status
paymentRequired402 :: Status
paymentRequired402 = Status
status402

-- | Forbidden 403
status403 :: Status
status403 :: Status
status403 = Int -> ByteString -> Status
mkStatus Int
403 ByteString
"Forbidden"

-- | Forbidden 403
forbidden403 :: Status
forbidden403 :: Status
forbidden403 = Status
status403

-- | Not Found 404
status404 :: Status
status404 :: Status
status404 = Int -> ByteString -> Status
mkStatus Int
404 ByteString
"Not Found"

-- | Not Found 404
notFound404 :: Status
notFound404 :: Status
notFound404 = Status
status404

-- | Method Not Allowed 405
status405 :: Status
status405 :: Status
status405 = Int -> ByteString -> Status
mkStatus Int
405 ByteString
"Method Not Allowed"

-- | Method Not Allowed 405
methodNotAllowed405 :: Status
methodNotAllowed405 :: Status
methodNotAllowed405 = Status
status405

-- | Not Acceptable 406
--
-- @since 0.6.6
status406 :: Status
status406 :: Status
status406 = Int -> ByteString -> Status
mkStatus Int
406 ByteString
"Not Acceptable"

-- | Not Acceptable 406
--
-- @since 0.6.6
notAcceptable406 :: Status
notAcceptable406 :: Status
notAcceptable406 = Status
status406

-- | Proxy Authentication Required 407
--
-- @since 0.6.6
status407 :: Status
status407 :: Status
status407 = Int -> ByteString -> Status
mkStatus Int
407 ByteString
"Proxy Authentication Required"

-- | Proxy Authentication Required 407
--
-- @since 0.6.6
proxyAuthenticationRequired407 :: Status
proxyAuthenticationRequired407 :: Status
proxyAuthenticationRequired407 = Status
status407

-- | Request Timeout 408
--
-- @since 0.6.6
status408 :: Status
status408 :: Status
status408 = Int -> ByteString -> Status
mkStatus Int
408 ByteString
"Request Timeout"

-- | Request Timeout 408
--
-- @since 0.6.6
requestTimeout408 :: Status
requestTimeout408 :: Status
requestTimeout408 = Status
status408

-- | Conflict 409
--
-- @since 0.6.6
status409 :: Status
status409 :: Status
status409 = Int -> ByteString -> Status
mkStatus Int
409 ByteString
"Conflict"

-- | Conflict 409
--
-- @since 0.6.6
conflict409 :: Status
conflict409 :: Status
conflict409 = Status
status409

-- | Gone 410
--
-- @since 0.6.6
status410 :: Status
status410 :: Status
status410 = Int -> ByteString -> Status
mkStatus Int
410 ByteString
"Gone"

-- | Gone 410
--
-- @since 0.6.6
gone410 :: Status
gone410 :: Status
gone410 = Status
status410

-- | Length Required 411
--
-- @since 0.6.6
status411 :: Status
status411 :: Status
status411 = Int -> ByteString -> Status
mkStatus Int
411 ByteString
"Length Required"

-- | Length Required 411
--
-- @since 0.6.6
lengthRequired411 :: Status
lengthRequired411 :: Status
lengthRequired411 = Status
status411

-- | Precondition Failed 412
--
-- @since 0.6.1
status412 :: Status
status412 :: Status
status412 = Int -> ByteString -> Status
mkStatus Int
412 ByteString
"Precondition Failed"

-- | Precondition Failed 412
--
-- @since 0.6.1
preconditionFailed412 :: Status
preconditionFailed412 :: Status
preconditionFailed412 = Status
status412

-- | Request Entity Too Large 413
--
-- @since 0.6.6
status413 :: Status
status413 :: Status
status413 = Int -> ByteString -> Status
mkStatus Int
413 ByteString
"Request Entity Too Large"

-- | Request Entity Too Large 413
--
-- @since 0.6.6
requestEntityTooLarge413 :: Status
requestEntityTooLarge413 :: Status
requestEntityTooLarge413 = Status
status413

-- | Request-URI Too Long 414
--
-- @since 0.6.6
status414 :: Status
status414 :: Status
status414 = Int -> ByteString -> Status
mkStatus Int
414 ByteString
"Request-URI Too Long"

-- | Request-URI Too Long 414
--
-- @since 0.6.6
requestURITooLong414 :: Status
requestURITooLong414 :: Status
requestURITooLong414 = Status
status414

-- | Unsupported Media Type 415
--
-- @since 0.6.6
status415 :: Status
status415 :: Status
status415 = Int -> ByteString -> Status
mkStatus Int
415 ByteString
"Unsupported Media Type"

-- | Unsupported Media Type 415
--
-- @since 0.6.6
unsupportedMediaType415 :: Status
unsupportedMediaType415 :: Status
unsupportedMediaType415 = Status
status415

-- | Requested Range Not Satisfiable 416
--
-- @since 0.6.1
status416 :: Status
status416 :: Status
status416 = Int -> ByteString -> Status
mkStatus Int
416 ByteString
"Requested Range Not Satisfiable"

-- | Requested Range Not Satisfiable 416
--
-- @since 0.6.1
requestedRangeNotSatisfiable416 :: Status
requestedRangeNotSatisfiable416 :: Status
requestedRangeNotSatisfiable416 = Status
status416

-- | Expectation Failed 417
--
-- @since 0.6.6
status417 :: Status
status417 :: Status
status417 = Int -> ByteString -> Status
mkStatus Int
417 ByteString
"Expectation Failed"

-- | Expectation Failed 417
--
-- @since 0.6.6
expectationFailed417 :: Status
expectationFailed417 :: Status
expectationFailed417 = Status
status417

-- | I'm a teapot 418
--
-- @since 0.6.6
status418 :: Status
status418 :: Status
status418 = Int -> ByteString -> Status
mkStatus Int
418 ByteString
"I'm a teapot"

-- | I'm a teapot 418
--
-- @since 0.6.6
imATeapot418 :: Status
imATeapot418 :: Status
imATeapot418 = Status
status418

-- | Unprocessable Entity 422
-- (<https://tools.ietf.org/html/rfc4918 RFC 4918>)
--
-- @since 0.9.1
status422 :: Status
status422 :: Status
status422 = Int -> ByteString -> Status
mkStatus Int
422 ByteString
"Unprocessable Entity"

-- | Unprocessable Entity 422
-- (<https://tools.ietf.org/html/rfc4918 RFC 4918>)
--
-- @since 0.9.1
unprocessableEntity422 :: Status
unprocessableEntity422 :: Status
unprocessableEntity422 = Status
status422

-- | Upgrade Required 426
-- (<https://tools.ietf.org/html/rfc7231#section-6.5.15>)
--
-- @since 0.10
status426 :: Status
status426 :: Status
status426 = Int -> ByteString -> Status
mkStatus Int
426 ByteString
"Upgrade Required"

-- | Upgrade Required 426
-- (<https://tools.ietf.org/html/rfc7231#section-6.5.15>)
--
-- @since 0.10
upgradeRequired426 :: Status
upgradeRequired426 :: Status
upgradeRequired426 = Status
status426

-- | Precondition Required 428
-- (<https://tools.ietf.org/html/rfc6585 RFC 6585>)
--
-- @since 0.8.5
status428 :: Status
status428 :: Status
status428 = Int -> ByteString -> Status
mkStatus Int
428 ByteString
"Precondition Required"

-- | Precondition Required 428
-- (<https://tools.ietf.org/html/rfc6585 RFC 6585>)
--
-- @since 0.8.5
preconditionRequired428 :: Status
preconditionRequired428 :: Status
preconditionRequired428 = Status
status428

-- | Too Many Requests 429
-- (<https://tools.ietf.org/html/rfc6585 RFC 6585>)
--
-- @since 0.8.5
status429 :: Status
status429 :: Status
status429 = Int -> ByteString -> Status
mkStatus Int
429 ByteString
"Too Many Requests"

-- | Too Many Requests 429
-- (<https://tools.ietf.org/html/rfc6585 RFC 6585>)
--
-- @since 0.8.5
tooManyRequests429 :: Status
tooManyRequests429 :: Status
tooManyRequests429 = Status
status429

-- | Request Header Fields Too Large 431
-- (<https://tools.ietf.org/html/rfc6585 RFC 6585>)
--
-- @since 0.8.5
status431 :: Status
status431 :: Status
status431 = Int -> ByteString -> Status
mkStatus Int
431 ByteString
"Request Header Fields Too Large"

-- | Request Header Fields Too Large 431
-- (<https://tools.ietf.org/html/rfc6585 RFC 6585>)
--
-- @since 0.8.5
requestHeaderFieldsTooLarge431 :: Status
requestHeaderFieldsTooLarge431 :: Status
requestHeaderFieldsTooLarge431 = Status
status431

-- | Internal Server Error 500
status500 :: Status
status500 :: Status
status500 = Int -> ByteString -> Status
mkStatus Int
500 ByteString
"Internal Server Error"

-- | Internal Server Error 500
internalServerError500 :: Status
internalServerError500 :: Status
internalServerError500 = Status
status500

-- | Not Implemented 501
--
-- @since 0.6.1
status501 :: Status
status501 :: Status
status501 = Int -> ByteString -> Status
mkStatus Int
501 ByteString
"Not Implemented"

-- | Not Implemented 501
--
-- @since 0.6.1
notImplemented501 :: Status
notImplemented501 :: Status
notImplemented501 = Status
status501

-- | Bad Gateway 502
--
-- @since 0.6.6
status502 :: Status
status502 :: Status
status502 = Int -> ByteString -> Status
mkStatus Int
502 ByteString
"Bad Gateway"

-- | Bad Gateway 502
--
-- @since 0.6.6
badGateway502 :: Status
badGateway502 :: Status
badGateway502 = Status
status502

-- | Service Unavailable 503
--
-- @since 0.6.6
status503 :: Status
status503 :: Status
status503 = Int -> ByteString -> Status
mkStatus Int
503 ByteString
"Service Unavailable"

-- | Service Unavailable 503
--
-- @since 0.6.6
serviceUnavailable503 :: Status
serviceUnavailable503 :: Status
serviceUnavailable503 = Status
status503

-- | Gateway Timeout 504
--
-- @since 0.6.6
status504 :: Status
status504 :: Status
status504 = Int -> ByteString -> Status
mkStatus Int
504 ByteString
"Gateway Timeout"

-- | Gateway Timeout 504
--
-- @since 0.6.6
gatewayTimeout504 :: Status
gatewayTimeout504 :: Status
gatewayTimeout504 = Status
status504

-- | HTTP Version Not Supported 505
--
-- @since 0.6.6
status505 :: Status
status505 :: Status
status505 = Int -> ByteString -> Status
mkStatus Int
505 ByteString
"HTTP Version Not Supported"

-- | HTTP Version Not Supported 505
--
-- @since 0.6.6
httpVersionNotSupported505 :: Status
httpVersionNotSupported505 :: Status
httpVersionNotSupported505 = Status
status505

-- | Network Authentication Required 511
-- (<https://tools.ietf.org/html/rfc6585 RFC 6585>)
--
-- @since 0.8.5
status511 :: Status
status511 :: Status
status511 = Int -> ByteString -> Status
mkStatus Int
511 ByteString
"Network Authentication Required"

-- | Network Authentication Required 511
-- (<https://tools.ietf.org/html/rfc6585 RFC 6585>)
--
-- @since 0.8.5
networkAuthenticationRequired511 :: Status
networkAuthenticationRequired511 :: Status
networkAuthenticationRequired511 = Status
status511

-- | Informational class
--
-- Checks if the status is in the 1XX range.
--
-- @since 0.8.0
statusIsInformational :: Status -> Bool
statusIsInformational :: Status -> Bool
statusIsInformational (Status {statusCode :: Status -> Int
statusCode=Int
code}) = Int
code forall a. Ord a => a -> a -> Bool
>= Int
100 Bool -> Bool -> Bool
&& Int
code forall a. Ord a => a -> a -> Bool
< Int
200

-- | Successful class
--
-- Checks if the status is in the 2XX range.
--
-- @since 0.8.0
statusIsSuccessful :: Status -> Bool
statusIsSuccessful :: Status -> Bool
statusIsSuccessful (Status {statusCode :: Status -> Int
statusCode=Int
code}) = Int
code forall a. Ord a => a -> a -> Bool
>= Int
200 Bool -> Bool -> Bool
&& Int
code forall a. Ord a => a -> a -> Bool
< Int
300

-- | Redirection class
--
-- Checks if the status is in the 3XX range.
--
-- @since 0.8.0
statusIsRedirection :: Status -> Bool
statusIsRedirection :: Status -> Bool
statusIsRedirection (Status {statusCode :: Status -> Int
statusCode=Int
code}) = Int
code forall a. Ord a => a -> a -> Bool
>= Int
300 Bool -> Bool -> Bool
&& Int
code forall a. Ord a => a -> a -> Bool
< Int
400

-- | Client Error class
--
-- Checks if the status is in the 4XX range.
--
-- @since 0.8.0
statusIsClientError :: Status -> Bool
statusIsClientError :: Status -> Bool
statusIsClientError (Status {statusCode :: Status -> Int
statusCode=Int
code}) = Int
code forall a. Ord a => a -> a -> Bool
>= Int
400 Bool -> Bool -> Bool
&& Int
code forall a. Ord a => a -> a -> Bool
< Int
500

-- | Server Error class
--
-- Checks if the status is in the 5XX range.
--
-- @since 0.8.0
statusIsServerError :: Status -> Bool
statusIsServerError :: Status -> Bool
statusIsServerError (Status {statusCode :: Status -> Int
statusCode=Int
code}) = Int
code forall a. Ord a => a -> a -> Bool
>= Int
500 Bool -> Bool -> Bool
&& Int
code forall a. Ord a => a -> a -> Bool
< Int
600