Copyright | (c) 2009 Henning Thielemann |
---|---|
License | BSD |
Stability | experimental |
Portability | non-portable (not tested) |
Safe Haskell | Safe |
Language | Haskell98 |
Provide the functionality of Network.HTTP.Headers with qualified identifier style.
- class HasHeaders x where
- type T = Header
- data Header :: * = Header HeaderName String
- cons :: Name -> String -> T
- type Name = HeaderName
- data HeaderName :: *
- = HdrCacheControl
- | HdrConnection
- | HdrDate
- | HdrPragma
- | HdrTransferEncoding
- | HdrUpgrade
- | HdrVia
- | HdrAccept
- | HdrAcceptCharset
- | HdrAcceptEncoding
- | HdrAcceptLanguage
- | HdrAuthorization
- | HdrCookie
- | HdrExpect
- | HdrFrom
- | HdrHost
- | HdrIfModifiedSince
- | HdrIfMatch
- | HdrIfNoneMatch
- | HdrIfRange
- | HdrIfUnmodifiedSince
- | HdrMaxForwards
- | HdrProxyAuthorization
- | HdrRange
- | HdrReferer
- | HdrUserAgent
- | HdrAge
- | HdrLocation
- | HdrProxyAuthenticate
- | HdrPublic
- | HdrRetryAfter
- | HdrServer
- | HdrSetCookie
- | HdrTE
- | HdrTrailer
- | HdrVary
- | HdrWarning
- | HdrWWWAuthenticate
- | HdrAllow
- | HdrContentBase
- | HdrContentEncoding
- | HdrContentLanguage
- | HdrContentLength
- | HdrContentLocation
- | HdrContentMD5
- | HdrContentRange
- | HdrContentType
- | HdrETag
- | HdrExpires
- | HdrLastModified
- | HdrContentTransferEncoding
- | HdrCustom String
- consName :: String -> Name
- getName :: T -> Name
- getValue :: T -> String
- setMany :: HasHeaders x => x -> [T] -> x
- getMany :: HasHeaders x => x -> [T]
- modifyMany :: HasHeaders x => ([T] -> [T]) -> x -> x
- insert :: HasHeaders a => Name -> String -> a -> a
- insertMany :: HasHeaders a => [T] -> a -> a
- insertIfMissing :: HasHeaders a => Name -> String -> a -> a
- retrieveMany :: HasHeaders a => Name -> a -> [T]
- replace :: HasHeaders a => Name -> String -> a -> a
- find :: HasHeaders a => Name -> a -> Maybe String
- findMany :: HasHeaders a => Name -> a -> [String]
- lookup :: Name -> [T] -> Maybe String
- parse :: String -> Exceptional String T
- parseManyWarn :: [String] -> [Exceptional String T]
- parseManyStraight :: [String] -> [T]
- dictionary :: Map String Name
- matchName :: Name -> T -> Bool
Documentation
class HasHeaders x where #
HasHeaders
is a type class for types containing HTTP headers, allowing
you to write overloaded header manipulation functions
for both Request
and Response
data types, for instance.
getHeaders :: x -> [Header] #
setHeaders :: x -> [Header] -> x #
HasHeaders (Request a) | |
HasHeaders (Response a) | |
The Header
data type pairs header names & values.
type Name = HeaderName Source #
data HeaderName :: * #
HTTP HeaderName
type, a Haskell data constructor for each
specification-defined header, prefixed with Hdr
and CamelCased,
(i.e., eliding the -
in the process.) Should you require using
a custom header, there's the HdrCustom
constructor which takes
a String
argument.
Encoding HTTP header names differently, as Strings perhaps, is an equally fine choice..no decidedly clear winner, but let's stick with data constructors here.
setMany :: HasHeaders x => x -> [T] -> x Source #
getMany :: HasHeaders x => x -> [T] Source #
modifyMany :: HasHeaders x => ([T] -> [T]) -> x -> x Source #
insert :: HasHeaders a => Name -> String -> a -> a Source #
Inserts a header with the given name and value. Allows duplicate header names.
insertMany :: HasHeaders a => [T] -> a -> a Source #
Inserts multiple headers.
insertIfMissing :: HasHeaders a => Name -> String -> a -> a Source #
Adds the new header only if no previous header shares the same name.
retrieveMany :: HasHeaders a => Name -> a -> [T] Source #
Gets a list of headers with a particular Name
.
replace :: HasHeaders a => Name -> String -> a -> a Source #
Removes old headers with duplicate name.
find :: HasHeaders a => Name -> a -> Maybe String Source #
Lookup presence of specific Name in a list of Headers Returns the value from the first matching header.
lookup :: Name -> [T] -> Maybe String Source #
Deprecated: Call find
using the [Header] instance of HasHeaders
parseManyWarn :: [String] -> [Exceptional String T] Source #
parseManyStraight :: [String] -> [T] Source #