WIP: Separate request and response headers

- Add simplified headers creation mechanism
This commit is contained in:
sigma-andex 2022-06-13 20:28:24 +01:00
parent d63e03a9be
commit f8e53eca35
6 changed files with 191 additions and 176 deletions

View File

@ -22,8 +22,8 @@ module HTTPurple
import Data.Generic.Rep (class Generic) import Data.Generic.Rep (class Generic)
import HTTPurple.Body (toBuffer, toStream, toString) import HTTPurple.Body (toBuffer, toStream, toString)
import HTTPurple.Cont (usingCont) import HTTPurple.Cont (usingCont)
import HTTPurple.Headers (Headers, empty, header, headers) import HTTPurple.Headers (RequestHeaders, ResponseHeaders, empty, header, headers)
import HTTPurple.Json (JsonDecoder(..), JsonEncoder(..), fromJson, jsonHeader, jsonHeaders, toJson) import HTTPurple.Json (JsonDecoder(..), JsonEncoder(..), fromJson, jsonHeaders, toJson)
import HTTPurple.Lookup (at, has, lookup, (!!), (!?), (!@)) import HTTPurple.Lookup (at, has, lookup, (!!), (!?), (!@))
import HTTPurple.Method (Method(..)) import HTTPurple.Method (Method(..))
import HTTPurple.Path (Path) import HTTPurple.Path (Path)

View File

@ -19,7 +19,7 @@ import Effect.Aff.Class (class MonadAff, liftAff)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Effect.Ref (Ref) import Effect.Ref (Ref)
import Effect.Ref (modify, new, read, write) as Ref import Effect.Ref (modify, new, read, write) as Ref
import HTTPurple.Headers (Headers, header) import HTTPurple.Headers (RequestHeaders, mkRequestHeader)
import Node.Buffer (Buffer, concat, fromString, size) import Node.Buffer (Buffer, concat, fromString, size)
import Node.Buffer (toString) as Buffer import Node.Buffer (toString) as Buffer
import Node.Encoding (Encoding(UTF8)) import Node.Encoding (Encoding(UTF8))
@ -103,7 +103,7 @@ class Body b where
-- | things like `Content-Type`, `Content-Length`, and `Transfer-Encoding`. -- | things like `Content-Type`, `Content-Length`, and `Transfer-Encoding`.
-- | Note that any headers passed in a response helper such as `ok'` will take -- | Note that any headers passed in a response helper such as `ok'` will take
-- | precedence over these. -- | precedence over these.
defaultHeaders :: b -> Effect Headers defaultHeaders :: b -> Effect RequestHeaders
-- | Given a body value and a Node HTTP `Response` value, write the body value -- | Given a body value and a Node HTTP `Response` value, write the body value
-- | to the Node response. -- | to the Node response.
write :: b -> Response -> Aff Unit write :: b -> Response -> Aff Unit
@ -126,7 +126,7 @@ instance Body String where
-- | using `Buffer.size`, and to send the response, we just write the buffer to -- | using `Buffer.size`, and to send the response, we just write the buffer to
-- | the stream and end the stream. -- | the stream and end the stream.
instance Body Buffer where instance Body Buffer where
defaultHeaders buf = header "Content-Length" <$> show <$> size buf defaultHeaders buf = mkRequestHeader "Content-Length" <$> show <$> size buf
write body response = makeAff \done -> do write body response = makeAff \done -> do
let stream = responseAsStream response let stream = responseAsStream response
void $ Stream.write stream body $ const $ end stream $ const $ done $ Right unit void $ Stream.write stream body $ const $ end stream $ const $ done $ Right unit
@ -138,7 +138,7 @@ instance Body Buffer where
instance instance
TypeEquals (Stream r) (Readable s) => TypeEquals (Stream r) (Readable s) =>
Body (Stream r) where Body (Stream r) where
defaultHeaders _ = pure $ header "Transfer-Encoding" "chunked" defaultHeaders _ = pure $ mkRequestHeader "Transfer-Encoding" "chunked"
write body response = makeAff \done -> do write body response = makeAff \done -> do
let stream = to body let stream = to body
void $ pipe stream $ responseAsStream response void $ pipe stream $ responseAsStream response

View File

@ -1,76 +1,158 @@
module HTTPurple.Headers module HTTPurple.Headers
( Headers(..) ( RequestHeaders(..)
, ResponseHeaders(..)
, class ToHeaders
, class ToHeadersHelper
, empty , empty
, headers
, header , header
, headers
, headersImpl
, mkRequestHeader
, mkRequestHeaders
, read , read
, toResponseHeaders
, write , write
) where )
where
import Prelude import Prelude
import Data.Array as Array
import Data.Foldable (foldl) import Data.Foldable (foldl)
import Data.FoldableWithIndex (foldMapWithIndex) import Data.FoldableWithIndex (foldMapWithIndex)
import Data.Map (Map, insert, singleton, union) import Data.Map (Map, insert, singleton, union)
import Data.Map (empty) as Map import Data.Map (empty) as Map
import Data.Newtype (class Newtype, unwrap) import Data.Newtype (class Newtype, un, unwrap)
import Data.String.CaseInsensitive (CaseInsensitiveString(CaseInsensitiveString)) import Data.String.CaseInsensitive (CaseInsensitiveString(CaseInsensitiveString))
import Data.Symbol (class IsSymbol, reflectSymbol)
import Data.TraversableWithIndex (traverseWithIndex) import Data.TraversableWithIndex (traverseWithIndex)
import Data.Tuple (Tuple(Tuple)) import Data.Tuple (Tuple(Tuple))
import Effect (Effect) import Effect (Effect)
import Foreign.Object (fold) import Foreign.Object (fold)
import HTTPurple.Lookup (class Lookup, (!!)) import HTTPurple.Lookup (class Lookup, (!!))
import Node.HTTP (Request, Response, requestHeaders, setHeader) import Node.HTTP (Request, Response, requestHeaders, setHeaders)
import Prim.Row as Row
import Prim.RowList (class RowToList, Cons, Nil)
import Record as Record
import Type.Proxy (Proxy(..))
-- | The `Headers` type is just sugar for a `Object` of `Strings` -- | The `RequestHeaders` type is just sugar for a `Object` of `Strings`
-- | that represents the set of headers in an HTTP request or response. -- | that represents the set of headers in an HTTP request or response.
newtype Headers = Headers (Map CaseInsensitiveString String) newtype RequestHeaders = RequestHeaders (Map CaseInsensitiveString String)
derive instance newtypeHeaders :: Newtype Headers _ derive instance Newtype RequestHeaders _
-- | Given a string, return a `Maybe` containing the value of the matching -- | Given a string, return a `Maybe` containing the value of the matching
-- | header, if there is any. -- | header, if there is any.
instance lookup :: Lookup Headers String String where instance Lookup RequestHeaders String String where
lookup (Headers headers') key = headers' !! key lookup (RequestHeaders headers') key = headers' !! key
-- | Allow a `Headers` to be represented as a string. This string is formatted -- | Allow a `Headers` to be represented as a string. This string is formatted
-- | in HTTP headers format. -- | in HTTP headers format.
instance show :: Show Headers where instance Show RequestHeaders where
show (Headers headers') = foldMapWithIndex showField headers' <> "\n" show (RequestHeaders headers') = foldMapWithIndex showField headers' <> "\n"
where where
showField key value = unwrap key <> ": " <> value <> "\n" showField key value = unwrap key <> ": " <> value <> "\n"
-- | Compare two `Headers` objects by comparing the underlying `Objects`. -- | Compare two `Headers` objects by comparing the underlying `Objects`.
instance eq :: Eq Headers where instance Eq RequestHeaders where
eq (Headers a) (Headers b) = eq a b eq (RequestHeaders a) (RequestHeaders b) = eq a b
-- | Allow one `Headers` objects to be appended to another. -- | Allow one `RequestHeaders` objects to be appended to another.
instance semigroup :: Semigroup Headers where instance Semigroup RequestHeaders where
append (Headers a) (Headers b) = Headers $ union b a append (RequestHeaders a) (RequestHeaders b) = RequestHeaders $ union b a
-- | The `RequestHeaders` type is just sugar for a `Object` of `Strings`
-- | that represents the set of headers in an HTTP request or response.
newtype ResponseHeaders = ResponseHeaders (Map CaseInsensitiveString (Array String))
-- | Allow one `ResponseHeaders` objects to be appended to another.
instance Semigroup ResponseHeaders where
append (ResponseHeaders a) (ResponseHeaders b) = ResponseHeaders $ union b a
-- | Allow a `RequestHeaders` to be represented as a string. This string is formatted
-- | in HTTP headers format.
instance Show ResponseHeaders where
show (ResponseHeaders headers') = foldMapWithIndex showField headers' <> "\n"
where
showField key value = Array.foldMap (\v -> unwrap key <> ": " <> v <> "\n") value
-- | Get the headers out of a HTTP `Request` object. -- | Get the headers out of a HTTP `Request` object.
read :: Request -> Headers read :: Request -> RequestHeaders
read = requestHeaders >>> fold insertField Map.empty >>> Headers read = requestHeaders >>> fold insertField Map.empty >>> RequestHeaders
where where
insertField x key value = insert (CaseInsensitiveString key) value x insertField x key value = insert (CaseInsensitiveString key) value x
-- | Given an HTTP `Response` and a `Headers` object, return an effect that will -- | Given an HTTP `Response` and a `ResponseHeaders` object, return an effect that will
-- | write the `Headers` to the `Response`. -- | write the `ResponseHeaders` to the `Response`.
write :: Response -> Headers -> Effect Unit write :: Response -> ResponseHeaders -> Effect Unit
write response (Headers headers') = void $ traverseWithIndex writeField headers' write response (ResponseHeaders headers') = void $ traverseWithIndex writeField headers'
where where
writeField key value = setHeader response (unwrap key) value writeField key values = setHeaders response (unwrap key) values
-- | Return a `Headers` containing nothing. -- | Return a `ResponseHeaders` containing nothing.
empty :: Headers empty :: ResponseHeaders
empty = Headers Map.empty empty = ResponseHeaders Map.empty
-- | Convert an `Array` of `Tuples` of 2 `Strings` to a `Headers` object.
headers :: Array (Tuple String String) -> Headers -- -- | Convert an `Array` of `Tuples` of 2 `Strings` to a `Headers` object.
headers = foldl insertField Map.empty >>> Headers mkRequestHeaders :: Array (Tuple String String) -> RequestHeaders
mkRequestHeaders = foldl insertField Map.empty >>> RequestHeaders
where where
insertField x (Tuple key value) = insert (CaseInsensitiveString key) value x insertField x (Tuple key value) = insert (CaseInsensitiveString key) value x
-- | Create a singleton header from a key-value pair. -- | Create a singleton header from a key-value pair.
header :: String -> String -> Headers mkRequestHeader :: String -> String -> RequestHeaders
header key = singleton (CaseInsensitiveString key) >>> Headers mkRequestHeader key = singleton (CaseInsensitiveString key) >>> RequestHeaders
-- | Create a singleton header from a key-value pair.
header :: String -> String -> ResponseHeaders
header key = Array.singleton >>> singleton (CaseInsensitiveString key) >>> ResponseHeaders
toResponseHeaders :: RequestHeaders -> ResponseHeaders
toResponseHeaders = un RequestHeaders >>> map (Array.singleton) >>> ResponseHeaders
class ToHeadersHelper :: forall k. Row Type -> k -> Constraint
class ToHeadersHelper r rl where
headersImpl :: Proxy rl -> Record r -> ResponseHeaders
instance ToHeadersHelper r (Nil) where
headersImpl _ _ = empty
else instance
( IsSymbol sym
, RowToList r rl
, RowToList tail tailRL
, Row.Cons sym String tail r
, Row.Lacks sym tail
, ToHeadersHelper tail tailRL
) =>
ToHeadersHelper r (Cons sym String tailRL) where
headersImpl _ rec = header key value <> headersImpl (Proxy :: Proxy tailRL) tail
where
key = reflectSymbol (Proxy :: Proxy sym)
value = Record.get (Proxy :: Proxy sym) rec
tail = Record.delete (Proxy :: Proxy sym) rec
else instance
( IsSymbol sym
, RowToList r rl
, RowToList tail tailRL
, Row.Cons sym (Array String) tail r
, Row.Lacks sym tail
, ToHeadersHelper tail tailRL
) =>
ToHeadersHelper r (Cons sym (Array String) tailRL) where
headersImpl _ rec = constructHeaders key value <> headersImpl (Proxy :: Proxy tailRL) tail
where
constructHeaders k = singleton (CaseInsensitiveString k) >>> ResponseHeaders
key = reflectSymbol (Proxy :: Proxy sym)
value = Record.get (Proxy :: Proxy sym) rec
tail = Record.delete (Proxy :: Proxy sym) rec
class ToHeaders r where
headers :: r -> ResponseHeaders
instance (RowToList r rl, ToHeadersHelper r rl) => ToHeaders (Record r) where
headers = headersImpl (Proxy :: Proxy rl)

View File

@ -3,7 +3,6 @@ module HTTPurple.Json
, JsonEncoder(..) , JsonEncoder(..)
, fromJson , fromJson
, fromJsonE , fromJsonE
, jsonHeader
, jsonHeaders , jsonHeaders
, toJson , toJson
) where ) where
@ -14,10 +13,9 @@ import Control.Monad.Cont (ContT(..))
import Data.Either (Either, either) import Data.Either (Either, either)
import Data.Function as Function import Data.Function as Function
import Data.Newtype (class Newtype, un) import Data.Newtype (class Newtype, un)
import Data.Tuple (Tuple(..))
import Effect.Aff.Class (class MonadAff) import Effect.Aff.Class (class MonadAff)
import HTTPurple.Body (RequestBody, toString) import HTTPurple.Body (RequestBody, toString)
import HTTPurple.Headers (Headers, headers) import HTTPurple.Headers (ResponseHeaders, headers)
import HTTPurple.Response (Response, badRequest) import HTTPurple.Response (Response, badRequest)
newtype JsonDecoder err json = JsonDecoder (String -> Either err json) newtype JsonDecoder err json = JsonDecoder (String -> Either err json)
@ -28,11 +26,8 @@ newtype JsonEncoder json = JsonEncoder (json -> String)
instance Newtype (JsonEncoder json) (json -> String) instance Newtype (JsonEncoder json) (json -> String)
jsonHeader :: Tuple String String jsonHeaders :: ResponseHeaders
jsonHeader = Tuple "Content-Type" "application/json" jsonHeaders = headers { "Content-Type": "application/json" }
jsonHeaders :: Headers
jsonHeaders = headers [ jsonHeader ]
fromJsonContinuation :: fromJsonContinuation ::
forall err json m. forall err json m.

View File

@ -14,7 +14,7 @@ import Effect.Class (liftEffect)
import Foreign.Object (isEmpty, toArrayWithKey) import Foreign.Object (isEmpty, toArrayWithKey)
import HTTPurple.Body (RequestBody) import HTTPurple.Body (RequestBody)
import HTTPurple.Body (read) as Body import HTTPurple.Body (read) as Body
import HTTPurple.Headers (Headers) import HTTPurple.Headers (RequestHeaders)
import HTTPurple.Headers (read) as Headers import HTTPurple.Headers (read) as Headers
import HTTPurple.Method (Method) import HTTPurple.Method (Method)
import HTTPurple.Method (read) as Method import HTTPurple.Method (read) as Method
@ -36,7 +36,7 @@ type Request route =
, path :: Path , path :: Path
, query :: Query , query :: Query
, route :: route , route :: route
, headers :: Headers , headers :: RequestHeaders
, body :: RequestBody , body :: RequestBody
, httpVersion :: Version , httpVersion :: Version
, url :: String , url :: String

View File

@ -139,72 +139,10 @@ import Effect.Aff (Aff)
import Effect.Aff.Class (class MonadAff, liftAff) import Effect.Aff.Class (class MonadAff, liftAff)
import Effect.Class (class MonadEffect, liftEffect) import Effect.Class (class MonadEffect, liftEffect)
import HTTPurple.Body (class Body, defaultHeaders, write) import HTTPurple.Body (class Body, defaultHeaders, write)
import HTTPurple.Headers (Headers, empty) import HTTPurple.Headers (RequestHeaders, ResponseHeaders, empty, toResponseHeaders)
import HTTPurple.Headers (write) as Headers import HTTPurple.Headers (write) as Headers
import HTTPurple.Status (Status) import HTTPurple.Status (Status)
import HTTPurple.Status import HTTPurple.Status (accepted, alreadyReported, badGateway, badRequest, conflict, continue, created, expectationFailed, failedDependency, forbidden, found, gatewayTimeout, gone, hTTPVersionNotSupported, iMUsed, imATeapot, insufficientStorage, internalServerError, lengthRequired, locked, loopDetected, methodNotAllowed, misdirectedRequest, movedPermanently, multiStatus, multipleChoices, networkAuthenticationRequired, noContent, nonAuthoritativeInformation, notAcceptable, notExtended, notFound, notImplemented, notModified, ok, partialContent, payloadTooLarge, paymentRequired, permanentRedirect, preconditionFailed, preconditionRequired, processing, proxyAuthenticationRequired, rangeNotSatisfiable, requestHeaderFieldsTooLarge, requestTimeout, resetContent, seeOther, serviceUnavailable, switchingProtocols, temporaryRedirect, tooManyRequests, uRITooLong, unauthorized, unavailableForLegalReasons, unprocessableEntity, unsupportedMediaType, upgradeRequired, useProxy, variantAlsoNegotiates, write) as Status
( accepted
, alreadyReported
, badGateway
, badRequest
, conflict
, continue
, created
, expectationFailed
, failedDependency
, forbidden
, found
, gatewayTimeout
, gone
, hTTPVersionNotSupported
, iMUsed
, imATeapot
, insufficientStorage
, internalServerError
, lengthRequired
, locked
, loopDetected
, methodNotAllowed
, misdirectedRequest
, movedPermanently
, multiStatus
, multipleChoices
, networkAuthenticationRequired
, noContent
, nonAuthoritativeInformation
, notAcceptable
, notExtended
, notFound
, notImplemented
, notModified
, ok
, partialContent
, payloadTooLarge
, paymentRequired
, permanentRedirect
, preconditionFailed
, preconditionRequired
, processing
, proxyAuthenticationRequired
, rangeNotSatisfiable
, requestHeaderFieldsTooLarge
, requestTimeout
, resetContent
, seeOther
, serviceUnavailable
, switchingProtocols
, temporaryRedirect
, tooManyRequests
, uRITooLong
, unauthorized
, unavailableForLegalReasons
, unprocessableEntity
, unsupportedMediaType
, upgradeRequired
, useProxy
, variantAlsoNegotiates
, write
) as Status
import Node.HTTP (Response) as HTTP import Node.HTTP (Response) as HTTP
-- | The `ResponseM` type simply conveniently wraps up an HTTPurple monad that -- | The `ResponseM` type simply conveniently wraps up an HTTPurple monad that
@ -215,7 +153,7 @@ type ResponseM = Aff Response
-- | A `Response` is a status code, headers, and a body. -- | A `Response` is a status code, headers, and a body.
type Response = type Response =
{ status :: Status { status :: Status
, headers :: Headers , headers :: ResponseHeaders
, writeBody :: HTTP.Response -> Aff Unit , writeBody :: HTTP.Response -> Aff Unit
} }
@ -239,14 +177,14 @@ response' ::
MonadAff m => MonadAff m =>
Body b => Body b =>
Status -> Status ->
Headers -> ResponseHeaders ->
b -> b ->
m Response m Response
response' status headers body = liftEffect do response' status headers body = liftEffect do
defaultHeaders' <- defaultHeaders body defaultHeaders' <- defaultHeaders body
pure pure
{ status { status
, headers: defaultHeaders' <> headers , headers: toResponseHeaders defaultHeaders' <> headers
, writeBody: write body , writeBody: write body
} }
@ -255,7 +193,7 @@ emptyResponse :: forall m. MonadAff m => Status -> m Response
emptyResponse status = emptyResponse' status empty emptyResponse status = emptyResponse' status empty
-- | The same as `emptyResponse` but with headers. -- | The same as `emptyResponse` but with headers.
emptyResponse' :: forall m. MonadAff m => Status -> Headers -> m Response emptyResponse' :: forall m. MonadAff m => Status -> ResponseHeaders -> m Response
emptyResponse' status headers = response' status headers "" emptyResponse' status headers = response' status headers ""
--------- ---------
@ -266,7 +204,7 @@ continue :: forall m. MonadAff m => m Response
continue = continue' empty continue = continue' empty
-- | 100 with headers -- | 100 with headers
continue' :: forall m. MonadAff m => Headers -> m Response continue' :: forall m. MonadAff m => ResponseHeaders -> m Response
continue' = emptyResponse' Status.continue continue' = emptyResponse' Status.continue
-- | 101 -- | 101
@ -274,7 +212,7 @@ switchingProtocols :: forall m. MonadAff m => m Response
switchingProtocols = switchingProtocols' empty switchingProtocols = switchingProtocols' empty
-- | 101 with headers -- | 101 with headers
switchingProtocols' :: forall m. MonadAff m => Headers -> m Response switchingProtocols' :: forall m. MonadAff m => ResponseHeaders -> m Response
switchingProtocols' = emptyResponse' Status.switchingProtocols switchingProtocols' = emptyResponse' Status.switchingProtocols
-- | 102 -- | 102
@ -282,7 +220,7 @@ processing :: forall m. MonadAff m => m Response
processing = processing' empty processing = processing' empty
-- | 102 with headers -- | 102 with headers
processing' :: forall m. MonadAff m => Headers -> m Response processing' :: forall m. MonadAff m => ResponseHeaders -> m Response
processing' = emptyResponse' Status.processing processing' = emptyResponse' Status.processing
--------- ---------
@ -293,7 +231,7 @@ ok :: forall m b. MonadAff m => Body b => b -> m Response
ok = ok' empty ok = ok' empty
-- | 200 with headers -- | 200 with headers
ok' :: forall m b. MonadAff m => Body b => Headers -> b -> m Response ok' :: forall m b. MonadAff m => Body b => ResponseHeaders -> b -> m Response
ok' = response' Status.ok ok' = response' Status.ok
-- | 201 -- | 201
@ -301,7 +239,7 @@ created :: forall m. MonadAff m => m Response
created = created' empty created = created' empty
-- | 201 with headers -- | 201 with headers
created' :: forall m. MonadAff m => Headers -> m Response created' :: forall m. MonadAff m => ResponseHeaders -> m Response
created' = emptyResponse' Status.created created' = emptyResponse' Status.created
-- | 202 -- | 202
@ -309,7 +247,7 @@ accepted :: forall m. MonadAff m => m Response
accepted = accepted' empty accepted = accepted' empty
-- | 202 with headers -- | 202 with headers
accepted' :: forall m. MonadAff m => Headers -> m Response accepted' :: forall m. MonadAff m => ResponseHeaders -> m Response
accepted' = emptyResponse' Status.accepted accepted' = emptyResponse' Status.accepted
-- | 203 -- | 203
@ -321,7 +259,7 @@ nonAuthoritativeInformation' ::
forall m b. forall m b.
MonadAff m => MonadAff m =>
Body b => Body b =>
Headers -> ResponseHeaders ->
b -> b ->
m Response m Response
nonAuthoritativeInformation' = response' Status.nonAuthoritativeInformation nonAuthoritativeInformation' = response' Status.nonAuthoritativeInformation
@ -331,7 +269,7 @@ noContent :: forall m. MonadAff m => m Response
noContent = noContent' empty noContent = noContent' empty
-- | 204 with headers -- | 204 with headers
noContent' :: forall m. MonadAff m => Headers -> m Response noContent' :: forall m. MonadAff m => ResponseHeaders -> m Response
noContent' = emptyResponse' Status.noContent noContent' = emptyResponse' Status.noContent
-- | 205 -- | 205
@ -339,7 +277,7 @@ resetContent :: forall m. MonadAff m => m Response
resetContent = resetContent' empty resetContent = resetContent' empty
-- | 205 with headers -- | 205 with headers
resetContent' :: forall m. MonadAff m => Headers -> m Response resetContent' :: forall m. MonadAff m => ResponseHeaders -> m Response
resetContent' = emptyResponse' Status.resetContent resetContent' = emptyResponse' Status.resetContent
-- | 206 -- | 206
@ -347,7 +285,7 @@ partialContent :: forall m b. MonadAff m => Body b => b -> m Response
partialContent = partialContent' empty partialContent = partialContent' empty
-- | 206 with headers -- | 206 with headers
partialContent' :: forall m b. MonadAff m => Body b => Headers -> b -> m Response partialContent' :: forall m b. MonadAff m => Body b => ResponseHeaders -> b -> m Response
partialContent' = response' Status.partialContent partialContent' = response' Status.partialContent
-- | 207 -- | 207
@ -355,7 +293,7 @@ multiStatus :: forall m b. MonadAff m => Body b => b -> m Response
multiStatus = multiStatus' empty multiStatus = multiStatus' empty
-- | 207 with headers -- | 207 with headers
multiStatus' :: forall m b. MonadAff m => Body b => Headers -> b -> m Response multiStatus' :: forall m b. MonadAff m => Body b => ResponseHeaders -> b -> m Response
multiStatus' = response' Status.multiStatus multiStatus' = response' Status.multiStatus
-- | 208 -- | 208
@ -363,7 +301,7 @@ alreadyReported :: forall m. MonadAff m => m Response
alreadyReported = alreadyReported' empty alreadyReported = alreadyReported' empty
-- | 208 with headers -- | 208 with headers
alreadyReported' :: forall m. MonadAff m => Headers -> m Response alreadyReported' :: forall m. MonadAff m => ResponseHeaders -> m Response
alreadyReported' = emptyResponse' Status.alreadyReported alreadyReported' = emptyResponse' Status.alreadyReported
-- | 226 -- | 226
@ -371,7 +309,7 @@ iMUsed :: forall m b. MonadAff m => Body b => b -> m Response
iMUsed = iMUsed' empty iMUsed = iMUsed' empty
-- | 226 with headers -- | 226 with headers
iMUsed' :: forall m b. MonadAff m => Body b => Headers -> b -> m Response iMUsed' :: forall m b. MonadAff m => Body b => ResponseHeaders -> b -> m Response
iMUsed' = response' Status.iMUsed iMUsed' = response' Status.iMUsed
--------- ---------
@ -382,7 +320,7 @@ multipleChoices :: forall m b. MonadAff m => Body b => b -> m Response
multipleChoices = multipleChoices' empty multipleChoices = multipleChoices' empty
-- | 300 with headers -- | 300 with headers
multipleChoices' :: forall m b. MonadAff m => Body b => Headers -> b -> m Response multipleChoices' :: forall m b. MonadAff m => Body b => ResponseHeaders -> b -> m Response
multipleChoices' = response' Status.multipleChoices multipleChoices' = response' Status.multipleChoices
-- | 301 -- | 301
@ -390,7 +328,7 @@ movedPermanently :: forall m b. MonadAff m => Body b => b -> m Response
movedPermanently = movedPermanently' empty movedPermanently = movedPermanently' empty
-- | 301 with headers -- | 301 with headers
movedPermanently' :: forall m b. MonadAff m => Body b => Headers -> b -> m Response movedPermanently' :: forall m b. MonadAff m => Body b => ResponseHeaders -> b -> m Response
movedPermanently' = response' Status.movedPermanently movedPermanently' = response' Status.movedPermanently
-- | 302 -- | 302
@ -398,7 +336,7 @@ found :: forall m b. MonadAff m => Body b => b -> m Response
found = found' empty found = found' empty
-- | 302 with headers -- | 302 with headers
found' :: forall m b. MonadAff m => Body b => Headers -> b -> m Response found' :: forall m b. MonadAff m => Body b => ResponseHeaders -> b -> m Response
found' = response' Status.found found' = response' Status.found
-- | 303 -- | 303
@ -406,7 +344,7 @@ seeOther :: forall m b. MonadAff m => Body b => b -> m Response
seeOther = seeOther' empty seeOther = seeOther' empty
-- | 303 with headers -- | 303 with headers
seeOther' :: forall m b. MonadAff m => Body b => Headers -> b -> m Response seeOther' :: forall m b. MonadAff m => Body b => ResponseHeaders -> b -> m Response
seeOther' = response' Status.seeOther seeOther' = response' Status.seeOther
-- | 304 -- | 304
@ -414,7 +352,7 @@ notModified :: forall m. MonadAff m => m Response
notModified = notModified' empty notModified = notModified' empty
-- | 304 with headers -- | 304 with headers
notModified' :: forall m. MonadAff m => Headers -> m Response notModified' :: forall m. MonadAff m => ResponseHeaders -> m Response
notModified' = emptyResponse' Status.notModified notModified' = emptyResponse' Status.notModified
-- | 305 -- | 305
@ -422,7 +360,7 @@ useProxy :: forall m b. MonadAff m => Body b => b -> m Response
useProxy = useProxy' empty useProxy = useProxy' empty
-- | 305 with headers -- | 305 with headers
useProxy' :: forall m b. MonadAff m => Body b => Headers -> b -> m Response useProxy' :: forall m b. MonadAff m => Body b => ResponseHeaders -> b -> m Response
useProxy' = response' Status.useProxy useProxy' = response' Status.useProxy
-- | 307 -- | 307
@ -430,7 +368,7 @@ temporaryRedirect :: forall m b. MonadAff m => Body b => b -> m Response
temporaryRedirect = temporaryRedirect' empty temporaryRedirect = temporaryRedirect' empty
-- | 307 with headers -- | 307 with headers
temporaryRedirect' :: forall m b. MonadAff m => Body b => Headers -> b -> m Response temporaryRedirect' :: forall m b. MonadAff m => Body b => ResponseHeaders -> b -> m Response
temporaryRedirect' = response' Status.temporaryRedirect temporaryRedirect' = response' Status.temporaryRedirect
-- | 308 -- | 308
@ -438,7 +376,7 @@ permanentRedirect :: forall m b. MonadAff m => Body b => b -> m Response
permanentRedirect = permanentRedirect' empty permanentRedirect = permanentRedirect' empty
-- | 308 with headers -- | 308 with headers
permanentRedirect' :: forall m b. MonadAff m => Body b => Headers -> b -> m Response permanentRedirect' :: forall m b. MonadAff m => Body b => ResponseHeaders -> b -> m Response
permanentRedirect' = response' Status.permanentRedirect permanentRedirect' = response' Status.permanentRedirect
--------- ---------
@ -449,7 +387,7 @@ badRequest :: forall m b. MonadAff m => Body b => b -> m Response
badRequest = badRequest' empty badRequest = badRequest' empty
-- | 400 with headers -- | 400 with headers
badRequest' :: forall m b. MonadAff m => Body b => Headers -> b -> m Response badRequest' :: forall m b. MonadAff m => Body b => ResponseHeaders -> b -> m Response
badRequest' = response' Status.badRequest badRequest' = response' Status.badRequest
-- | 401 -- | 401
@ -457,7 +395,7 @@ unauthorized :: forall m. MonadAff m => m Response
unauthorized = unauthorized' empty unauthorized = unauthorized' empty
-- | 401 with headers -- | 401 with headers
unauthorized' :: forall m. MonadAff m => Headers -> m Response unauthorized' :: forall m. MonadAff m => ResponseHeaders -> m Response
unauthorized' = emptyResponse' Status.unauthorized unauthorized' = emptyResponse' Status.unauthorized
-- | 402 -- | 402
@ -465,7 +403,7 @@ paymentRequired :: forall m. MonadAff m => m Response
paymentRequired = paymentRequired' empty paymentRequired = paymentRequired' empty
-- | 402 with headers -- | 402 with headers
paymentRequired' :: forall m. MonadAff m => Headers -> m Response paymentRequired' :: forall m. MonadAff m => ResponseHeaders -> m Response
paymentRequired' = emptyResponse' Status.paymentRequired paymentRequired' = emptyResponse' Status.paymentRequired
-- | 403 -- | 403
@ -473,7 +411,7 @@ forbidden :: forall m. MonadAff m => m Response
forbidden = forbidden' empty forbidden = forbidden' empty
-- | 403 with headers -- | 403 with headers
forbidden' :: forall m. MonadAff m => Headers -> m Response forbidden' :: forall m. MonadAff m => ResponseHeaders -> m Response
forbidden' = emptyResponse' Status.forbidden forbidden' = emptyResponse' Status.forbidden
-- | 404 -- | 404
@ -481,7 +419,7 @@ notFound :: forall m. MonadAff m => m Response
notFound = notFound' empty notFound = notFound' empty
-- | 404 with headers -- | 404 with headers
notFound' :: forall m. MonadAff m => Headers -> m Response notFound' :: forall m. MonadAff m => ResponseHeaders -> m Response
notFound' = emptyResponse' Status.notFound notFound' = emptyResponse' Status.notFound
-- | 405 -- | 405
@ -489,7 +427,7 @@ methodNotAllowed :: forall m. MonadAff m => m Response
methodNotAllowed = methodNotAllowed' empty methodNotAllowed = methodNotAllowed' empty
-- | 405 with headers -- | 405 with headers
methodNotAllowed' :: forall m. MonadAff m => Headers -> m Response methodNotAllowed' :: forall m. MonadAff m => ResponseHeaders -> m Response
methodNotAllowed' = emptyResponse' Status.methodNotAllowed methodNotAllowed' = emptyResponse' Status.methodNotAllowed
-- | 406 -- | 406
@ -497,7 +435,7 @@ notAcceptable :: forall m. MonadAff m => m Response
notAcceptable = notAcceptable' empty notAcceptable = notAcceptable' empty
-- | 406 with headers -- | 406 with headers
notAcceptable' :: forall m. MonadAff m => Headers -> m Response notAcceptable' :: forall m. MonadAff m => ResponseHeaders -> m Response
notAcceptable' = emptyResponse' Status.notAcceptable notAcceptable' = emptyResponse' Status.notAcceptable
-- | 407 -- | 407
@ -505,7 +443,7 @@ proxyAuthenticationRequired :: forall m. MonadAff m => m Response
proxyAuthenticationRequired = proxyAuthenticationRequired' empty proxyAuthenticationRequired = proxyAuthenticationRequired' empty
-- | 407 with headers -- | 407 with headers
proxyAuthenticationRequired' :: forall m. MonadAff m => Headers -> m Response proxyAuthenticationRequired' :: forall m. MonadAff m => ResponseHeaders -> m Response
proxyAuthenticationRequired' = emptyResponse' Status.proxyAuthenticationRequired proxyAuthenticationRequired' = emptyResponse' Status.proxyAuthenticationRequired
-- | 408 -- | 408
@ -513,7 +451,7 @@ requestTimeout :: forall m. MonadAff m => m Response
requestTimeout = requestTimeout' empty requestTimeout = requestTimeout' empty
-- | 408 with headers -- | 408 with headers
requestTimeout' :: forall m. MonadAff m => Headers -> m Response requestTimeout' :: forall m. MonadAff m => ResponseHeaders -> m Response
requestTimeout' = emptyResponse' Status.requestTimeout requestTimeout' = emptyResponse' Status.requestTimeout
-- | 409 -- | 409
@ -521,7 +459,7 @@ conflict :: forall m b. MonadAff m => Body b => b -> m Response
conflict = conflict' empty conflict = conflict' empty
-- | 409 with headers -- | 409 with headers
conflict' :: forall m b. MonadAff m => Body b => Headers -> b -> m Response conflict' :: forall m b. MonadAff m => Body b => ResponseHeaders -> b -> m Response
conflict' = response' Status.conflict conflict' = response' Status.conflict
-- | 410 -- | 410
@ -529,7 +467,7 @@ gone :: forall m. MonadAff m => m Response
gone = gone' empty gone = gone' empty
-- | 410 with headers -- | 410 with headers
gone' :: forall m. MonadAff m => Headers -> m Response gone' :: forall m. MonadAff m => ResponseHeaders -> m Response
gone' = emptyResponse' Status.gone gone' = emptyResponse' Status.gone
-- | 411 -- | 411
@ -537,7 +475,7 @@ lengthRequired :: forall m. MonadAff m => m Response
lengthRequired = lengthRequired' empty lengthRequired = lengthRequired' empty
-- | 411 with headers -- | 411 with headers
lengthRequired' :: forall m. MonadAff m => Headers -> m Response lengthRequired' :: forall m. MonadAff m => ResponseHeaders -> m Response
lengthRequired' = emptyResponse' Status.lengthRequired lengthRequired' = emptyResponse' Status.lengthRequired
-- | 412 -- | 412
@ -545,7 +483,7 @@ preconditionFailed :: forall m. MonadAff m => m Response
preconditionFailed = preconditionFailed' empty preconditionFailed = preconditionFailed' empty
-- | 412 with headers -- | 412 with headers
preconditionFailed' :: forall m. MonadAff m => Headers -> m Response preconditionFailed' :: forall m. MonadAff m => ResponseHeaders -> m Response
preconditionFailed' = emptyResponse' Status.preconditionFailed preconditionFailed' = emptyResponse' Status.preconditionFailed
-- | 413 -- | 413
@ -553,7 +491,7 @@ payloadTooLarge :: forall m. MonadAff m => m Response
payloadTooLarge = payloadTooLarge' empty payloadTooLarge = payloadTooLarge' empty
-- | 413 with headers -- | 413 with headers
payloadTooLarge' :: forall m. MonadAff m => Headers -> m Response payloadTooLarge' :: forall m. MonadAff m => ResponseHeaders -> m Response
payloadTooLarge' = emptyResponse' Status.payloadTooLarge payloadTooLarge' = emptyResponse' Status.payloadTooLarge
-- | 414 -- | 414
@ -561,7 +499,7 @@ uRITooLong :: forall m. MonadAff m => m Response
uRITooLong = uRITooLong' empty uRITooLong = uRITooLong' empty
-- | 414 with headers -- | 414 with headers
uRITooLong' :: forall m. MonadAff m => Headers -> m Response uRITooLong' :: forall m. MonadAff m => ResponseHeaders -> m Response
uRITooLong' = emptyResponse' Status.uRITooLong uRITooLong' = emptyResponse' Status.uRITooLong
-- | 415 -- | 415
@ -569,7 +507,7 @@ unsupportedMediaType :: forall m. MonadAff m => m Response
unsupportedMediaType = unsupportedMediaType' empty unsupportedMediaType = unsupportedMediaType' empty
-- | 415 with headers -- | 415 with headers
unsupportedMediaType' :: forall m. MonadAff m => Headers -> m Response unsupportedMediaType' :: forall m. MonadAff m => ResponseHeaders -> m Response
unsupportedMediaType' = emptyResponse' Status.unsupportedMediaType unsupportedMediaType' = emptyResponse' Status.unsupportedMediaType
-- | 416 -- | 416
@ -577,7 +515,7 @@ rangeNotSatisfiable :: forall m. MonadAff m => m Response
rangeNotSatisfiable = rangeNotSatisfiable' empty rangeNotSatisfiable = rangeNotSatisfiable' empty
-- | 416 with headers -- | 416 with headers
rangeNotSatisfiable' :: forall m. MonadAff m => Headers -> m Response rangeNotSatisfiable' :: forall m. MonadAff m => ResponseHeaders -> m Response
rangeNotSatisfiable' = emptyResponse' Status.rangeNotSatisfiable rangeNotSatisfiable' = emptyResponse' Status.rangeNotSatisfiable
-- | 417 -- | 417
@ -585,7 +523,7 @@ expectationFailed :: forall m. MonadAff m => m Response
expectationFailed = expectationFailed' empty expectationFailed = expectationFailed' empty
-- | 417 with headers -- | 417 with headers
expectationFailed' :: forall m. MonadAff m => Headers -> m Response expectationFailed' :: forall m. MonadAff m => ResponseHeaders -> m Response
expectationFailed' = emptyResponse' Status.expectationFailed expectationFailed' = emptyResponse' Status.expectationFailed
-- | 418 -- | 418
@ -593,7 +531,7 @@ imATeapot :: forall m. MonadAff m => m Response
imATeapot = imATeapot' empty imATeapot = imATeapot' empty
-- | 418 with headers -- | 418 with headers
imATeapot' :: forall m. MonadAff m => Headers -> m Response imATeapot' :: forall m. MonadAff m => ResponseHeaders -> m Response
imATeapot' = emptyResponse' Status.imATeapot imATeapot' = emptyResponse' Status.imATeapot
-- | 421 -- | 421
@ -601,7 +539,7 @@ misdirectedRequest :: forall m. MonadAff m => m Response
misdirectedRequest = misdirectedRequest' empty misdirectedRequest = misdirectedRequest' empty
-- | 421 with headers -- | 421 with headers
misdirectedRequest' :: forall m. MonadAff m => Headers -> m Response misdirectedRequest' :: forall m. MonadAff m => ResponseHeaders -> m Response
misdirectedRequest' = emptyResponse' Status.misdirectedRequest misdirectedRequest' = emptyResponse' Status.misdirectedRequest
-- | 422 -- | 422
@ -609,7 +547,7 @@ unprocessableEntity :: forall m. MonadAff m => m Response
unprocessableEntity = unprocessableEntity' empty unprocessableEntity = unprocessableEntity' empty
-- | 422 with headers -- | 422 with headers
unprocessableEntity' :: forall m. MonadAff m => Headers -> m Response unprocessableEntity' :: forall m. MonadAff m => ResponseHeaders -> m Response
unprocessableEntity' = emptyResponse' Status.unprocessableEntity unprocessableEntity' = emptyResponse' Status.unprocessableEntity
-- | 423 -- | 423
@ -617,7 +555,7 @@ locked :: forall m. MonadAff m => m Response
locked = locked' empty locked = locked' empty
-- | 423 with headers -- | 423 with headers
locked' :: forall m. MonadAff m => Headers -> m Response locked' :: forall m. MonadAff m => ResponseHeaders -> m Response
locked' = emptyResponse' Status.locked locked' = emptyResponse' Status.locked
-- | 424 -- | 424
@ -625,7 +563,7 @@ failedDependency :: forall m. MonadAff m => m Response
failedDependency = failedDependency' empty failedDependency = failedDependency' empty
-- | 424 with headers -- | 424 with headers
failedDependency' :: forall m. MonadAff m => Headers -> m Response failedDependency' :: forall m. MonadAff m => ResponseHeaders -> m Response
failedDependency' = emptyResponse' Status.failedDependency failedDependency' = emptyResponse' Status.failedDependency
-- | 426 -- | 426
@ -633,7 +571,7 @@ upgradeRequired :: forall m. MonadAff m => m Response
upgradeRequired = upgradeRequired' empty upgradeRequired = upgradeRequired' empty
-- | 426 with headers -- | 426 with headers
upgradeRequired' :: forall m. MonadAff m => Headers -> m Response upgradeRequired' :: forall m. MonadAff m => ResponseHeaders -> m Response
upgradeRequired' = emptyResponse' Status.upgradeRequired upgradeRequired' = emptyResponse' Status.upgradeRequired
-- | 428 -- | 428
@ -641,7 +579,7 @@ preconditionRequired :: forall m. MonadAff m => m Response
preconditionRequired = preconditionRequired' empty preconditionRequired = preconditionRequired' empty
-- | 428 with headers -- | 428 with headers
preconditionRequired' :: forall m. MonadAff m => Headers -> m Response preconditionRequired' :: forall m. MonadAff m => ResponseHeaders -> m Response
preconditionRequired' = emptyResponse' Status.preconditionRequired preconditionRequired' = emptyResponse' Status.preconditionRequired
-- | 429 -- | 429
@ -649,7 +587,7 @@ tooManyRequests :: forall m. MonadAff m => m Response
tooManyRequests = tooManyRequests' empty tooManyRequests = tooManyRequests' empty
-- | 429 with headers -- | 429 with headers
tooManyRequests' :: forall m. MonadAff m => Headers -> m Response tooManyRequests' :: forall m. MonadAff m => ResponseHeaders -> m Response
tooManyRequests' = emptyResponse' Status.tooManyRequests tooManyRequests' = emptyResponse' Status.tooManyRequests
-- | 431 -- | 431
@ -657,7 +595,7 @@ requestHeaderFieldsTooLarge :: forall m. MonadAff m => m Response
requestHeaderFieldsTooLarge = requestHeaderFieldsTooLarge' empty requestHeaderFieldsTooLarge = requestHeaderFieldsTooLarge' empty
-- | 431 with headers -- | 431 with headers
requestHeaderFieldsTooLarge' :: forall m. MonadAff m => Headers -> m Response requestHeaderFieldsTooLarge' :: forall m. MonadAff m => ResponseHeaders -> m Response
requestHeaderFieldsTooLarge' = emptyResponse' Status.requestHeaderFieldsTooLarge requestHeaderFieldsTooLarge' = emptyResponse' Status.requestHeaderFieldsTooLarge
-- | 451 -- | 451
@ -665,7 +603,7 @@ unavailableForLegalReasons :: forall m. MonadAff m => m Response
unavailableForLegalReasons = unavailableForLegalReasons' empty unavailableForLegalReasons = unavailableForLegalReasons' empty
-- | 451 with headers -- | 451 with headers
unavailableForLegalReasons' :: forall m. MonadAff m => Headers -> m Response unavailableForLegalReasons' :: forall m. MonadAff m => ResponseHeaders -> m Response
unavailableForLegalReasons' = emptyResponse' Status.unavailableForLegalReasons unavailableForLegalReasons' = emptyResponse' Status.unavailableForLegalReasons
--------- ---------
@ -680,7 +618,7 @@ internalServerError' ::
forall m b. forall m b.
MonadAff m => MonadAff m =>
Body b => Body b =>
Headers -> ResponseHeaders ->
b -> b ->
m Response m Response
internalServerError' = response' Status.internalServerError internalServerError' = response' Status.internalServerError
@ -690,7 +628,7 @@ notImplemented :: forall m. MonadAff m => m Response
notImplemented = notImplemented' empty notImplemented = notImplemented' empty
-- | 501 with headers -- | 501 with headers
notImplemented' :: forall m. MonadAff m => Headers -> m Response notImplemented' :: forall m. MonadAff m => ResponseHeaders -> m Response
notImplemented' = emptyResponse' Status.notImplemented notImplemented' = emptyResponse' Status.notImplemented
-- | 502 -- | 502
@ -698,7 +636,7 @@ badGateway :: forall m. MonadAff m => m Response
badGateway = badGateway' empty badGateway = badGateway' empty
-- | 502 with headers -- | 502 with headers
badGateway' :: forall m. MonadAff m => Headers -> m Response badGateway' :: forall m. MonadAff m => ResponseHeaders -> m Response
badGateway' = emptyResponse' Status.badGateway badGateway' = emptyResponse' Status.badGateway
-- | 503 -- | 503
@ -706,7 +644,7 @@ serviceUnavailable :: forall m. MonadAff m => m Response
serviceUnavailable = serviceUnavailable' empty serviceUnavailable = serviceUnavailable' empty
-- | 503 with headers -- | 503 with headers
serviceUnavailable' :: forall m. MonadAff m => Headers -> m Response serviceUnavailable' :: forall m. MonadAff m => ResponseHeaders -> m Response
serviceUnavailable' = emptyResponse' Status.serviceUnavailable serviceUnavailable' = emptyResponse' Status.serviceUnavailable
-- | 504 -- | 504
@ -714,7 +652,7 @@ gatewayTimeout :: forall m. MonadAff m => m Response
gatewayTimeout = gatewayTimeout' empty gatewayTimeout = gatewayTimeout' empty
-- | 504 with headers -- | 504 with headers
gatewayTimeout' :: forall m. MonadAff m => Headers -> m Response gatewayTimeout' :: forall m. MonadAff m => ResponseHeaders -> m Response
gatewayTimeout' = emptyResponse' Status.gatewayTimeout gatewayTimeout' = emptyResponse' Status.gatewayTimeout
-- | 505 -- | 505
@ -722,7 +660,7 @@ hTTPVersionNotSupported :: forall m. MonadAff m => m Response
hTTPVersionNotSupported = hTTPVersionNotSupported' empty hTTPVersionNotSupported = hTTPVersionNotSupported' empty
-- | 505 with headers -- | 505 with headers
hTTPVersionNotSupported' :: forall m. MonadAff m => Headers -> m Response hTTPVersionNotSupported' :: forall m. MonadAff m => ResponseHeaders -> m Response
hTTPVersionNotSupported' = emptyResponse' Status.hTTPVersionNotSupported hTTPVersionNotSupported' = emptyResponse' Status.hTTPVersionNotSupported
-- | 506 -- | 506
@ -730,7 +668,7 @@ variantAlsoNegotiates :: forall m. MonadAff m => m Response
variantAlsoNegotiates = variantAlsoNegotiates' empty variantAlsoNegotiates = variantAlsoNegotiates' empty
-- | 506 with headers -- | 506 with headers
variantAlsoNegotiates' :: forall m. MonadAff m => Headers -> m Response variantAlsoNegotiates' :: forall m. MonadAff m => ResponseHeaders -> m Response
variantAlsoNegotiates' = emptyResponse' Status.variantAlsoNegotiates variantAlsoNegotiates' = emptyResponse' Status.variantAlsoNegotiates
-- | 507 -- | 507
@ -738,7 +676,7 @@ insufficientStorage :: forall m. MonadAff m => m Response
insufficientStorage = insufficientStorage' empty insufficientStorage = insufficientStorage' empty
-- | 507 with headers -- | 507 with headers
insufficientStorage' :: forall m. MonadAff m => Headers -> m Response insufficientStorage' :: forall m. MonadAff m => ResponseHeaders -> m Response
insufficientStorage' = emptyResponse' Status.insufficientStorage insufficientStorage' = emptyResponse' Status.insufficientStorage
-- | 508 -- | 508
@ -746,7 +684,7 @@ loopDetected :: forall m. MonadAff m => m Response
loopDetected = loopDetected' empty loopDetected = loopDetected' empty
-- | 508 with headers -- | 508 with headers
loopDetected' :: forall m. MonadAff m => Headers -> m Response loopDetected' :: forall m. MonadAff m => ResponseHeaders -> m Response
loopDetected' = emptyResponse' Status.loopDetected loopDetected' = emptyResponse' Status.loopDetected
-- | 510 -- | 510
@ -754,7 +692,7 @@ notExtended :: forall m. MonadAff m => m Response
notExtended = notExtended' empty notExtended = notExtended' empty
-- | 510 with headers -- | 510 with headers
notExtended' :: forall m. MonadAff m => Headers -> m Response notExtended' :: forall m. MonadAff m => ResponseHeaders -> m Response
notExtended' = emptyResponse' Status.notExtended notExtended' = emptyResponse' Status.notExtended
-- | 511 -- | 511
@ -762,5 +700,5 @@ networkAuthenticationRequired :: forall m. MonadAff m => m Response
networkAuthenticationRequired = networkAuthenticationRequired' empty networkAuthenticationRequired = networkAuthenticationRequired' empty
-- | 511 with headers -- | 511 with headers
networkAuthenticationRequired' :: forall m. MonadAff m => Headers -> m Response networkAuthenticationRequired' :: forall m. MonadAff m => ResponseHeaders -> m Response
networkAuthenticationRequired' = emptyResponse' Status.networkAuthenticationRequired networkAuthenticationRequired' = emptyResponse' Status.networkAuthenticationRequired