Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Type and constants for handling HTTP header fields.
At the bottom are also some functions to handle certain header field values.
Synopsis
- type Header = (HeaderName, ByteString)
- type HeaderName = CI ByteString
- type RequestHeaders = [Header]
- type ResponseHeaders = [Header]
- hAccept :: HeaderName
- hAcceptCharset :: HeaderName
- hAcceptEncoding :: HeaderName
- hAcceptLanguage :: HeaderName
- hAcceptRanges :: HeaderName
- hAge :: HeaderName
- hAllow :: HeaderName
- hAuthorization :: HeaderName
- hCacheControl :: HeaderName
- hConnection :: HeaderName
- hContentDisposition :: HeaderName
- hContentEncoding :: HeaderName
- hContentLanguage :: HeaderName
- hContentLength :: HeaderName
- hContentLocation :: HeaderName
- hContentMD5 :: HeaderName
- hContentRange :: HeaderName
- hContentType :: HeaderName
- hCookie :: HeaderName
- hDate :: HeaderName
- hETag :: HeaderName
- hExpect :: HeaderName
- hExpires :: HeaderName
- hFrom :: HeaderName
- hHost :: HeaderName
- hIfMatch :: HeaderName
- hIfModifiedSince :: HeaderName
- hIfNoneMatch :: HeaderName
- hIfRange :: HeaderName
- hIfUnmodifiedSince :: HeaderName
- hLastModified :: HeaderName
- hLocation :: HeaderName
- hMaxForwards :: HeaderName
- hMIMEVersion :: HeaderName
- hOrigin :: HeaderName
- hPragma :: HeaderName
- hPrefer :: HeaderName
- hPreferenceApplied :: HeaderName
- hProxyAuthenticate :: HeaderName
- hProxyAuthorization :: HeaderName
- hRange :: HeaderName
- hReferer :: HeaderName
- hRetryAfter :: HeaderName
- hServer :: HeaderName
- hSetCookie :: HeaderName
- hTE :: HeaderName
- hTrailer :: HeaderName
- hTransferEncoding :: HeaderName
- hUpgrade :: HeaderName
- hUserAgent :: HeaderName
- hVary :: HeaderName
- hVia :: HeaderName
- hWWWAuthenticate :: HeaderName
- hWarning :: HeaderName
- data ByteRange
- renderByteRangeBuilder :: ByteRange -> Builder
- renderByteRange :: ByteRange -> ByteString
- type ByteRanges = [ByteRange]
- renderByteRangesBuilder :: ByteRanges -> Builder
- renderByteRanges :: ByteRanges -> ByteString
- parseByteRanges :: ByteString -> Maybe ByteRanges
HTTP Headers
type Header = (HeaderName, ByteString) Source #
A full HTTP header field with the name and value separated.
E.g. "Content-Length: 28"
parsed into a Header
would turn into ("Content-Length", "28")
type HeaderName = CI ByteString Source #
A case-insensitive name of a header field.
This is the part of the header field before the colon: HeaderName: some value
type RequestHeaders = [Header] Source #
A list of Header
s.
Same type as ResponseHeaders
, but useful to differentiate in type signatures.
type ResponseHeaders = [Header] Source #
A list of Header
s.
Same type as RequestHeaders
, but useful to differentiate in type signatures.
Common headers
The following header constants are provided for convenience, to prevent accidental spelling errors.
hAccept :: HeaderName Source #
Since: 0.7.0
hAcceptCharset :: HeaderName Source #
Since: 0.9
hAcceptEncoding :: HeaderName Source #
Since: 0.9
hAcceptLanguage :: HeaderName Source #
Since: 0.7.0
hAcceptRanges :: HeaderName Source #
Since: 0.9
hAge :: HeaderName Source #
Since: 0.9
hAllow :: HeaderName Source #
Since: 0.9
hAuthorization :: HeaderName Source #
Since: 0.7.0
hCacheControl :: HeaderName Source #
Since: 0.7.0
hConnection :: HeaderName Source #
Since: 0.7.0
hContentDisposition :: HeaderName Source #
Since: 0.10
hContentEncoding :: HeaderName Source #
Since: 0.7.0
hContentLanguage :: HeaderName Source #
Since: 0.9
hContentLength :: HeaderName Source #
Since: 0.7.0
hContentLocation :: HeaderName Source #
Since: 0.9
hContentRange :: HeaderName Source #
Since: 0.9
hContentType :: HeaderName Source #
Since: 0.7.0
hCookie :: HeaderName Source #
Since: 0.7.0
hDate :: HeaderName Source #
Since: 0.7.0
hETag :: HeaderName Source #
Since: 0.9
hExpect :: HeaderName Source #
Since: 0.9
hExpires :: HeaderName Source #
Since: 0.9
hFrom :: HeaderName Source #
Since: 0.9
hHost :: HeaderName Source #
Since: 0.9
hIfMatch :: HeaderName Source #
Since: 0.9
hIfModifiedSince :: HeaderName Source #
Since: 0.7.0
hIfNoneMatch :: HeaderName Source #
Since: 0.9
hIfRange :: HeaderName Source #
Since: 0.7.0
hIfUnmodifiedSince :: HeaderName Source #
Since: 0.9
hLastModified :: HeaderName Source #
Since: 0.7.0
hLocation :: HeaderName Source #
Since: 0.7.1
hMaxForwards :: HeaderName Source #
Since: 0.9
hMIMEVersion :: HeaderName Source #
Since: 0.10
hOrigin :: HeaderName Source #
Since: 0.10
hPragma :: HeaderName Source #
hPrefer :: HeaderName Source #
Since: 0.12.2
hPreferenceApplied :: HeaderName Source #
Since: 0.12.2
hProxyAuthenticate :: HeaderName Source #
Since: 0.9
hProxyAuthorization :: HeaderName Source #
Since: 0.9
hRange :: HeaderName Source #
Since: 0.7.0
hReferer :: HeaderName Source #
Since: 0.7.0
hRetryAfter :: HeaderName Source #
Since: 0.9
hServer :: HeaderName Source #
Since: 0.7.1
hSetCookie :: HeaderName Source #
Since: 0.10
hTE :: HeaderName Source #
Since: 0.9
hTrailer :: HeaderName Source #
Since: 0.9
hTransferEncoding :: HeaderName Source #
Since: 0.9
hUpgrade :: HeaderName Source #
Since: 0.9
hUserAgent :: HeaderName Source #
Since: 0.7.0
hVary :: HeaderName Source #
Since: 0.9
hVia :: HeaderName Source #
Since: 0.9
hWWWAuthenticate :: HeaderName Source #
Since: 0.9
Byte ranges
Convenience functions and types to handle values from Range headers.
https://www.rfc-editor.org/rfc/rfc9110.html#name-byte-ranges
An individual byte range.
Negative indices are not allowed!
Since: 0.6.11
Instances
Data ByteRange Source # | Since: 0.8.4 |
Defined in Network.HTTP.Types.Header gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ByteRange -> c ByteRange # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ByteRange # toConstr :: ByteRange -> Constr # dataTypeOf :: ByteRange -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ByteRange) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteRange) # gmapT :: (forall b. Data b => b -> b) -> ByteRange -> ByteRange # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ByteRange -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ByteRange -> r # gmapQ :: (forall d. Data d => d -> u) -> ByteRange -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ByteRange -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ByteRange -> m ByteRange # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteRange -> m ByteRange # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteRange -> m ByteRange # | |
Generic ByteRange Source # | |
Show ByteRange Source # | Since: 0.8.4 |
Eq ByteRange Source # | Since: 0.8.4 |
Ord ByteRange Source # | Since: 0.8.4 |
Defined in Network.HTTP.Types.Header | |
type Rep ByteRange Source # | Since: 0.12.4 |
Defined in Network.HTTP.Types.Header type Rep ByteRange = D1 ('MetaData "ByteRange" "Network.HTTP.Types.Header" "http-types-0.12.4-8sVzaiF2LjrERDtipkARMD" 'False) (C1 ('MetaCons "ByteRangeFrom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Integer)) :+: (C1 ('MetaCons "ByteRangeFromTo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Integer) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Integer)) :+: C1 ('MetaCons "ByteRangeSuffix" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Integer)))) |
renderByteRangeBuilder :: ByteRange -> Builder Source #
Turns a byte range into a byte string Builder
.
Since: 0.6.11
renderByteRange :: ByteRange -> ByteString Source #
Renders a byte range into a ByteString
.
>>>
renderByteRange (ByteRangeFrom 2048)
"2048-"
Since: 0.6.11
type ByteRanges = [ByteRange] Source #
A list of byte ranges.
Since: 0.6.11
renderByteRangesBuilder :: ByteRanges -> Builder Source #
Turns a list of byte ranges into a byte string Builder
.
Since: 0.6.11
renderByteRanges :: ByteRanges -> ByteString Source #
Renders a list of byte ranges into a ByteString
.
>>>
renderByteRanges [ByteRangeFrom 2048, ByteRangeSuffix 20]
"bytes=2048-,-20"
Since: 0.6.11
parseByteRanges :: ByteString -> Maybe ByteRanges Source #
Parse the value of a Range header into a ByteRanges
.
>>>
parseByteRanges "error"
Nothing>>>
parseByteRanges "bytes=0-499"
Just [ByteRangeFromTo 0 499]>>>
parseByteRanges "bytes=500-999"
Just [ByteRangeFromTo 500 999]>>>
parseByteRanges "bytes=-500"
Just [ByteRangeSuffix 500]>>>
parseByteRanges "bytes=9500-"
Just [ByteRangeFrom 9500]>>>
parseByteRanges "bytes=0-0,-1"
Just [ByteRangeFromTo 0 0,ByteRangeSuffix 1]>>>
parseByteRanges "bytes=500-600,601-999"
Just [ByteRangeFromTo 500 600,ByteRangeFromTo 601 999]>>>
parseByteRanges "bytes=500-700,601-999"
Just [ByteRangeFromTo 500 700,ByteRangeFromTo 601 999]
Since: 0.9.1