Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides facilities for adding headers to a response.
>>>
let headerVal = addHeader "some-url" 5 :: Headers '[Header "Location" String] Int
The value is added to the header specified by the type (Location
in the
example above).
- data Headers ls a = Headers {
- getResponse :: a
- getHeadersHList :: HList ls
- data ResponseHeader (sym :: Symbol) a
- class AddHeader h v orig new | h v orig -> new, new -> h, new -> v, new -> orig
- addHeader :: AddHeader h v orig new => v -> orig -> new
- noHeader :: AddHeader h v orig new => orig -> new
- class BuildHeadersTo hs where
- class GetHeaders ls where
- type family HeaderValMap (f :: * -> *) (xs :: [*]) where ...
- data HList a where
Documentation
Response Header objects. You should never need to construct one directly.
Instead, use addOptionalHeader
.
Headers | |
|
data ResponseHeader (sym :: Symbol) a Source #
Functor (ResponseHeader sym) Source # | |
Eq a => Eq (ResponseHeader sym a) Source # | |
Show a => Show (ResponseHeader sym a) Source # | |
class AddHeader h v orig new | h v orig -> new, new -> h, new -> v, new -> orig Source #
addOptionalHeader
addHeader :: AddHeader h v orig new => v -> orig -> new Source #
addHeader
adds a header to a response. Note that it changes the type of
the value in the following ways:
- A simple value is wrapped in "Headers '[hdr]":
>>>
let example1 = addHeader 5 "hi" :: Headers '[Header "someheader" Int] String;
>>>
getHeaders example1
[("someheader","5")]
- A value that already has a header has its new header *prepended* to the existing list:
>>>
let example1 = addHeader 5 "hi" :: Headers '[Header "someheader" Int] String;
>>>
let example2 = addHeader True example1 :: Headers '[Header "1st" Bool, Header "someheader" Int] String
>>>
getHeaders example2
[("1st","true"),("someheader","5")]
Note that while in your handlers type annotations are not required, since the type can be inferred from the API type, in other cases you may find yourself needing to add annotations.
noHeader :: AddHeader h v orig new => orig -> new Source #
Deliberately do not add a header to a value.
>>>
let example1 = noHeader "hi" :: Headers '[Header "someheader" Int] String
>>>
getHeaders example1
[]
class BuildHeadersTo hs where Source #
buildHeadersTo :: [Header] -> HList hs Source #
Note: if there are multiple occurences of a header in the argument, the values are interspersed with commas before deserialization (see RFC2616 Sec 4.2)
BuildHeadersTo ([] *) Source # | |
(FromHttpApiData v, BuildHeadersTo xs, KnownSymbol h) => BuildHeadersTo ((:) * (Header * h v) xs) Source # | |
class GetHeaders ls where Source #
getHeaders :: ls -> [Header] Source #
GetHeadersFromHList hs => GetHeaders (HList hs) Source # | |
GetHeaders' hs => GetHeaders (Headers hs a) Source # | |
type family HeaderValMap (f :: * -> *) (xs :: [*]) where ... Source #
HeaderValMap f '[] = '[] | |
HeaderValMap f (Header h x ': xs) = Header h (f x) ': HeaderValMap f xs |