snap-core-1.0.3.2: Snap: A Haskell Web Framework (core interfaces and types)

Safe HaskellNone
LanguageHaskell2010

Snap.Types.Headers

Contents

Description

An opaque data type for HTTP headers. Intended to be imported qualified, i.e:

import           Snap.Types.Headers (Headers)
import qualified Snap.Types.Headers as H

foo :: Headers
foo = H.empty

Synopsis

Headers type

data Headers Source #

A key-value map that represents a collection of HTTP header fields. Keys are case-insensitive.

Headers creation

empty :: Headers Source #

An empty collection of HTTP header fields.

Example:

ghci> H.empty
H {unH = []}

Predicates

null :: Headers -> Bool Source #

Is a given collection of HTTP header fields empty?

Example:

ghci> :set -XOverloadedStrings
ghci> H.null H.empty
True
ghci> H.null $ H.fromList [("Host", "localhost")]
False

member :: CI ByteString -> Headers -> Bool Source #

Does this collection of HTTP header fields contain a given field?

Example:

ghci> :set -XOverloadedStrings
ghci> H.member "host" $ H.fromList [("Host", "localhost")]
True
ghci> H.member "Accept" $ H.fromList [("Host", "localhost")]
False

Lookup

lookup :: CI ByteString -> Headers -> Maybe ByteString Source #

Look up the value of a given HTTP header field.

Example:

ghci> :set -XOverloadedStrings
ghci> H.lookup "host" $ H.fromList [("Host", "localhost")]
Just "localhost"
ghci> H.lookup "Accept" $ H.fromList [("Host", "localhost")]
Nothing

lookupWithDefault :: ByteString -> CI ByteString -> Headers -> ByteString Source #

Look up the value of a given HTTP header field or return the provided default value when that header field is not present.

Example:

ghci> :set -XOverloadedStrings
ghci> let hdrs = H.fromList [("Host", "localhost")]
ghci> H.lookupWithDefault "host" "127.0.0.1" $ hdrs
"localhost"
ghci> H.lookupWithDefault "Accept" "text/plain" $ hdrs
"text/plain"

Adding/setting headers

insert :: CI ByteString -> ByteString -> Headers -> Headers Source #

Insert a key-value pair into the headers map. If the key already exists in the map, the values are catenated with ", ".

Example:

ghci> :set -XOverloadedStrings
ghci> let hdrs = H.insert "Accept" "text/plain" $ H.empty
ghci> hdrs
H {unH = [("accept","text/plain")]}
ghci> H.insert "Accept" "text/html" $ hdrs
H {unH = [("accept","text/plain,text/html")]}

unsafeInsert :: ByteString -> ByteString -> Headers -> Headers Source #

Insert a key-value pair into the headers map, without checking whether the header already exists. The key must be already case-folded, or none of the lookups will work!

Example:

ghci> :set -XOverloadedStrings
ghci> let hdrs = H.unsafeInsert "accept" "text/plain" $ H.empty
ghci> hdrs
H {unH = [("accept","text/plain")]}
ghci> let hdrs' = H.unsafeInsert "accept" "text/html" $ hdrs
ghci> hdrs'
H {unH = [("accept","text/html"), ("accept","text/plain")]}
ghci> H.lookup "accept" hdrs'
Just "text/html"

set :: CI ByteString -> ByteString -> Headers -> Headers Source #

Set the value of a HTTP header field to a given value, replacing the old value.

Example:

ghci> :set -XOverloadedStrings
ghci> H.set "accept" "text/plain" $ H.empty
H {unH = [("accept","text/plain")]}
ghci> H.set "accept" "text/html" $ H.fromList [("Accept", "text/plain")]
H {unH = [("accept","text/html")]}

Deleting

delete :: CI ByteString -> Headers -> Headers Source #

Delete all key-value pairs associated with the given key from the headers map.

Example:

ghci> :set -XOverloadedStrings
ghci> H.delete "accept" $ H.fromList [("Accept", "text/plain")]
H {unH = []}

Traversal

foldl' :: (a -> CI ByteString -> ByteString -> a) -> a -> Headers -> a Source #

Strict left fold over all key-value pairs in the headers map.

Example:

ghci> :set -XOverloadedStrings
ghci> import Data.Monoid
ghci> let hdrs = H.fromList [("Accept", "text/plain"), ("Accept", "text/html")]
ghci> let f (cntr, acc) _ val = (cntr+1, val <> ";" <> acc)
ghci> H.foldl' f (0, "") hdrs
(2,"text/html;text/plain;")

foldr :: (CI ByteString -> ByteString -> a -> a) -> a -> Headers -> a Source #

Right fold over all key-value pairs in the headers map.

Example:

ghci> :set -XOverloadedStrings
ghci> import Data.Monoid
ghci> let hdrs = H.fromList [("Accept", "text/plain"), ("Accept", "text/html")]
ghci> let f _ val (cntr, acc) = (cntr+1, val <> ";" <> acc)
ghci> H.foldr f (0, "") hdrs
(2,"text/plain;text/html;")

foldedFoldl' :: (a -> ByteString -> ByteString -> a) -> a -> Headers -> a Source #

Same as foldl', but the key parameter is of type ByteString instead of CI ByteString. The key is case-folded (lowercase).

foldedFoldr :: (ByteString -> ByteString -> a -> a) -> a -> Headers -> a Source #

Same as foldr, but the key parameter is of type ByteString instead of CI ByteString. The key is case-folded (lowercase).

Lists

toList :: Headers -> [(CI ByteString, ByteString)] Source #

Convert a Headers value to a list of key-value pairs.

Example:

ghci> :set -XOverloadedStrings
ghci> let l = [("Accept", "text/plain"), ("Accept", "text/html")]
ghci> H.toList . H.fromList $ l
[("accept","text/plain"),("accept","text/html")]

fromList :: [(CI ByteString, ByteString)] -> Headers Source #

Build a Headers value from a list of key-value pairs.

Example:

ghci> :set -XOverloadedStrings
ghci> H.fromList [("Accept", "text/plain"), ("Accept", "text/html")]
H {unH = [("accept","text/plain"),("accept","text/html")]}

unsafeFromCaseFoldedList :: [(ByteString, ByteString)] -> Headers Source #

Like fromList, but the keys are assumed to be already case-folded (in lowercase).

unsafeToCaseFoldedList :: Headers -> [(ByteString, ByteString)] Source #

Like toList, but does not convert the keys to CI ByteString, so key comparisons will be case-sensitive.