servant/servant/src/Servant/API/ResponseHeaders.hs

168 lines
5.7 KiB
Haskell
Raw Normal View History

2015-04-20 19:52:29 +02:00
{-# LANGUAGE CPP #-}
2015-04-13 15:12:33 +02:00
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
2015-05-02 03:21:03 +02:00
{-# LANGUAGE TypeFamilies #-}
2015-04-13 15:12:33 +02:00
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
2015-04-20 19:52:29 +02:00
#if !MIN_VERSION_base(4,8,0)
{-# LANGUAGE OverlappingInstances #-}
#endif
2015-05-02 03:21:03 +02:00
{-# OPTIONS_HADDOCK not-home #-}
2015-04-13 15:12:33 +02:00
-- | 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).
module Servant.API.ResponseHeaders
2015-05-02 03:21:03 +02:00
( Headers(..)
2015-05-02 04:38:53 +02:00
, AddHeader(addHeader)
2015-05-02 03:21:03 +02:00
, BuildHeadersTo(buildHeadersTo)
, GetHeaders(getHeaders)
, HeaderValMap
, HList(..)
2015-04-13 15:12:33 +02:00
) where
2015-05-02 03:21:03 +02:00
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative ((<$>))
#endif
import Data.ByteString.Char8 as BS (pack, unlines, init)
import Data.ByteString.Conversion (ToByteString, toByteString',
FromByteString, fromByteString)
2015-04-13 15:12:33 +02:00
import qualified Data.CaseInsensitive as CI
import Data.Proxy
import GHC.TypeLits (KnownSymbol, symbolVal)
import qualified Network.HTTP.Types.Header as HTTP
import Servant.API.Header (Header (..))
-- | Response Header objects. You should never need to construct one directly.
-- Instead, use 'addHeader'.
data Headers ls a = Headers { getResponse :: a
-- ^ The underlying value of a 'Headers'
2015-05-02 03:21:03 +02:00
, getHeadersHList :: HList ls
-- ^ HList of headers.
} deriving (Functor)
data HList a where
HNil :: HList '[]
HCons :: Header h x -> HList xs -> HList (Header h x ': xs)
type family HeaderValMap (f :: * -> *) (xs :: [*]) where
HeaderValMap f '[] = '[]
HeaderValMap f (Header h x ': xs) = Header h (f x) ': (HeaderValMap f xs)
class BuildHeadersTo hs where
buildHeadersTo :: [HTTP.Header] -> HList hs
-- ^ Note: if there are multiple occurences of a header in the argument,
-- the values are interspersed with commas before deserialization (see
-- <http://www.w3.org/Protocols/rfc2616/rfc2616-sec4.html#sec4.2 RFC2616 Sec 4.2>)
instance
#if MIN_VERSION_base(4,8,0)
{-# OVERLAPPING #-}
#endif
BuildHeadersTo '[] where
buildHeadersTo _ = HNil
instance
#if MIN_VERSION_base(4,8,0)
{-# OVERLAPPABLE #-}
#endif
( FromByteString v, BuildHeadersTo xs, KnownSymbol h, Contains h xs ~ 'False
) => BuildHeadersTo ((Header h v) ': xs) where
buildHeadersTo headers =
let wantedHeader = CI.mk . pack $ symbolVal (Proxy :: Proxy h)
matching = snd <$> filter (\(h, _) -> h == wantedHeader) headers
in case matching of
[] -> MissingHeader `HCons` buildHeadersTo headers
xs -> case fromByteString (BS.init $ BS.unlines xs) of
Nothing -> UndecodableHeader (BS.init $ BS.unlines xs)
`HCons` buildHeadersTo headers
Just h -> Header h `HCons` buildHeadersTo headers
-- * Getting
class GetHeaders ls where
getHeaders :: ls -> [HTTP.Header]
instance
#if MIN_VERSION_base(4,8,0)
{-# OVERLAPPING #-}
#endif
GetHeaders (HList '[]) where
getHeaders _ = []
instance
#if MIN_VERSION_base(4,8,0)
{-# OVERLAPPABLE #-}
#endif
( KnownSymbol h, ToByteString x, GetHeaders (HList xs)
) => GetHeaders (HList (Header h x ': xs)) where
getHeaders (Header val `HCons` rest) = (headerName , toByteString' val):getHeaders rest
where headerName = CI.mk . pack $ symbolVal (Proxy :: Proxy h)
getHeaders (UndecodableHeader h `HCons` rest) = (headerName, h) : getHeaders rest
where headerName = CI.mk . pack $ symbolVal (Proxy :: Proxy h)
instance
#if MIN_VERSION_base(4,8,0)
{-# OVERLAPPING #-}
#endif
GetHeaders (Headers '[] a) where
getHeaders _ = []
instance
#if MIN_VERSION_base(4,8,0)
{-# OVERLAPPABLE #-}
#endif
( KnownSymbol h, GetHeaders (HList rest), ToByteString v
) => GetHeaders (Headers (Header h v ': rest) a) where
getHeaders hs = getHeaders $ getHeadersHList hs
-- * Adding
2015-04-13 15:12:33 +02:00
-- We need all these fundeps to save type inference
class AddHeader h v orig new
| h v orig -> new, new -> h, new -> v, new -> orig where
2015-05-02 03:21:03 +02:00
addHeader :: v -> orig -> new -- ^ N.B.: The same header can't be added multiple times
2015-04-13 15:12:33 +02:00
2015-04-20 19:52:29 +02:00
instance
#if MIN_VERSION_base(4,8,0)
{-# OVERLAPPING #-}
#endif
2015-05-02 03:21:03 +02:00
( KnownSymbol h, ToByteString v, Contains h (fst ': rest) ~ 'False
) => AddHeader h v (Headers (fst ': rest) a) (Headers (Header h v ': fst ': rest) a) where
addHeader a (Headers resp heads) = Headers resp (HCons (Header a) heads)
2015-04-13 15:12:33 +02:00
2015-04-20 19:52:29 +02:00
instance
#if MIN_VERSION_base(4,8,0)
{-# OVERLAPPABLE #-}
#endif
( KnownSymbol h, ToByteString v
2015-04-13 15:12:33 +02:00
, new ~ (Headers '[Header h v] a)
) => AddHeader h v a new where
2015-05-02 03:21:03 +02:00
addHeader a resp = Headers resp (HCons (Header a) HNil)
2015-04-13 15:12:33 +02:00
2015-05-02 03:21:03 +02:00
type family Contains x xs where
Contains x ((Header x a) ': xs) = 'True
Contains x ((Header y a) ': xs) = Contains x xs
Contains x '[] = 'False
2015-04-13 15:12:33 +02:00
-- $setup
-- >>> import Servant.API
-- >>> import Data.Aeson
-- >>> import Data.Text
-- >>> data Book
-- >>> instance ToJSON Book where { toJSON = undefined }