| Safe Haskell | Safe | 
|---|---|
| Language | Haskell98 | 
Network.HTTP.Types.Header
Contents
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
 - hContentEncoding :: HeaderName
 - hContentLanguage :: HeaderName
 - hContentLength :: HeaderName
 - hContentLocation :: HeaderName
 - hContentMD5 :: HeaderName
 - hContentRange :: HeaderName
 - hContentType :: 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
 - hOrigin :: HeaderName
 - hPragma :: HeaderName
 - hPrefer :: HeaderName
 - hPreferenceApplied :: HeaderName
 - hProxyAuthenticate :: HeaderName
 - hProxyAuthorization :: HeaderName
 - hRange :: HeaderName
 - hReferer :: HeaderName
 - hRetryAfter :: HeaderName
 - hServer :: HeaderName
 - hTE :: HeaderName
 - hTrailer :: HeaderName
 - hTransferEncoding :: HeaderName
 - hUpgrade :: HeaderName
 - hUserAgent :: HeaderName
 - hVary :: HeaderName
 - hVia :: HeaderName
 - hWWWAuthenticate :: HeaderName
 - hWarning :: HeaderName
 - hContentDisposition :: HeaderName
 - hMIMEVersion :: HeaderName
 - hCookie :: HeaderName
 - hSetCookie :: HeaderName
 - data ByteRange
 - renderByteRangeBuilder :: ByteRange -> Builder
 - renderByteRange :: ByteRange -> ByteString
 - type ByteRanges = [ByteRange]
 - renderByteRangesBuilder :: ByteRanges -> Builder
 - renderByteRanges :: ByteRanges -> ByteString
 - parseByteRanges :: ByteString -> Maybe ByteRanges
 
Types
type Header = (HeaderName, ByteString) Source #
Header
type HeaderName = CI ByteString Source #
Header name
type RequestHeaders = [Header] Source #
Request Headers
type ResponseHeaders = [Header] Source #
Response Headers
Common headers
hAccept :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hAcceptCharset :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hAcceptEncoding :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hAcceptLanguage :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hAcceptRanges :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hAge :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hAllow :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hAuthorization :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hCacheControl :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hConnection :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hContentEncoding :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hContentLanguage :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hContentLength :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hContentLocation :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hContentMD5 :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hContentRange :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hContentType :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hDate :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hETag :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hExpect :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hExpires :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hFrom :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hHost :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hIfMatch :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hIfModifiedSince :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hIfNoneMatch :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hIfRange :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hIfUnmodifiedSince :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hLastModified :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hLocation :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hMaxForwards :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hOrigin :: HeaderName Source #
HTTP Header names according to https://tools.ietf.org/html/rfc6454
hPragma :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hPrefer :: HeaderName Source #
HTTP Header names according to https://tools.ietf.org/html/rfc7240
hPreferenceApplied :: HeaderName Source #
HTTP Header names according to https://tools.ietf.org/html/rfc7240
hProxyAuthenticate :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hProxyAuthorization :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hRange :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hReferer :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hRetryAfter :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hServer :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hTE :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hTrailer :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hTransferEncoding :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hUpgrade :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hUserAgent :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hVary :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hVia :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hWWWAuthenticate :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hWarning :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec14.html
hContentDisposition :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec19.html
hMIMEVersion :: HeaderName Source #
HTTP Header names according to http://www.w3.org/Protocols/rfc2616/rfc2616-sec19.html
hCookie :: HeaderName Source #
HTTP Header names according to https://tools.ietf.org/html/rfc6265#section-4
hSetCookie :: HeaderName Source #
HTTP Header names according to https://tools.ietf.org/html/rfc6265#section-4
Byte ranges
RFC 2616 Byte range (individual).
Negative indices are not allowed!
Constructors
| ByteRangeFrom !Integer | |
| ByteRangeFromTo !Integer !Integer | |
| ByteRangeSuffix !Integer | 
Instances
| Eq ByteRange Source # | |
| Data ByteRange Source # | |
Defined in Network.HTTP.Types.Header Methods 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 :: (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 #  | |
| Ord ByteRange Source # | |
| Show ByteRange Source # | |
type ByteRanges = [ByteRange] Source #
RFC 2616 Byte ranges (set).
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]