servant/src/Servant/API/ContentTypes.hs

187 lines
6.5 KiB
Haskell
Raw Normal View History

{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
2015-01-08 16:24:19 +01:00
module Servant.API.ContentTypes where
import Control.Arrow (left)
import Data.Aeson (FromJSON, ToJSON, eitherDecode,
encode)
import qualified Data.ByteString as BS
import Data.ByteString.Lazy (ByteString)
import Data.String.Conversions (cs)
import qualified Data.Text.Lazy as Text
import qualified Data.Text.Lazy.Encoding as Text
2015-02-18 11:24:56 +01:00
import Data.Typeable
import GHC.Exts (Constraint)
import qualified Network.HTTP.Media as M
2015-01-08 16:24:19 +01:00
-- * Provided content types
2015-01-08 16:24:19 +01:00
data JSON deriving Typeable
data PlainText deriving Typeable
data OctetStream deriving Typeable
-- * Accept class
-- | Instances of 'Accept' represent mimetypes. They are used for matching
-- against the @Accept@ HTTP header of the request, and for setting the
-- @Content-Type@ header of the response
--
-- Example:
--
-- > instance Accept HTML where
-- > contentType _ = "text" // "html"
--
class Accept ctype where
contentType :: Proxy ctype -> M.MediaType
-- | @application/json;charset=utf-8@
instance Accept JSON where
contentType _ = "application" M.// "json" M./: ("charset", "utf-8")
-- | @text/plain;charset=utf-8@
instance Accept PlainText where
contentType _ = "text" M.// "plain" M./: ("charset", "utf-8")
-- | @application/octet-stream@
instance Accept OctetStream where
contentType _ = "application" M.// "octet-stream"
newtype AcceptHeader = AcceptHeader BS.ByteString
deriving (Eq, Show)
-- * Render (serializing)
-- | Instantiate this class to register a way of serializing a type based
-- on the @Accept@ header.
--
-- Example:
--
-- > data MyContentType
-- >
-- > instance Accept MyContentType where
-- > contentType _ = "example" // "prs.me.mine" /: ("charset", "utf-8")
-- >
-- > instance Show a => MimeRender MyContentType where
-- > toByteString _ val = pack ("This is MINE! " ++ show val)
-- >
-- > type MyAPI = "path" :> Get '[MyContentType] Int
class Accept ctype => MimeRender ctype a where
toByteString :: Proxy ctype -> a -> ByteString
class AllCTRender list a where
-- If the Accept header can be matched, returns (Just) a tuple of the
-- Content-Type and response (serialization of @a@ into the appropriate
-- mimetype).
handleAcceptH :: Proxy list -> AcceptHeader -> a -> Maybe (ByteString, ByteString)
instance ( AllMimeRender ctyps a, IsNonEmpty ctyps
) => AllCTRender ctyps a where
handleAcceptH _ (AcceptHeader accept) val = M.mapAcceptMedia lkup accept
where pctyps = Proxy :: Proxy ctyps
2015-02-19 10:29:19 +01:00
amrs = allMimeRender pctyps val
lkup = fmap (\(a,b) -> (a, (cs $ show a, b))) amrs
--------------------------------------------------------------------------
-- * Unrender
class Accept ctype => MimeUnrender ctype a where
2015-02-19 10:29:19 +01:00
fromByteString :: Proxy ctype -> ByteString -> Either String a
2015-02-19 19:18:08 +01:00
class (IsNonEmpty list) => AllCTUnrender list a where
handleCTypeH :: Proxy list
-> ByteString -- Content-Type header
-> ByteString -- Request body
2015-02-19 10:29:19 +01:00
-> Maybe (Either String a)
instance ( AllMimeUnrender ctyps a, IsNonEmpty ctyps
) => AllCTUnrender ctyps a where
2015-02-19 10:29:19 +01:00
handleCTypeH _ ctypeH body = M.mapContentMedia lkup (cs ctypeH)
where lkup = allMimeUnrender (Proxy :: Proxy ctyps) body
--------------------------------------------------------------------------
-- * Utils (Internal)
--------------------------------------------------------------------------
-- Check that all elements of list are instances of MimeRender
--------------------------------------------------------------------------
class AllMimeRender ls a where
2015-02-19 10:29:19 +01:00
allMimeRender :: Proxy ls
-> a -- value to serialize
-> [(M.MediaType, ByteString)] -- content-types/response pairs
instance ( MimeRender ctyp a ) => AllMimeRender '[ctyp] a where
2015-02-19 10:29:19 +01:00
allMimeRender _ a = [(contentType pctyp, toByteString pctyp a)]
where pctyp = Proxy :: Proxy ctyp
instance ( MimeRender ctyp a
2015-02-19 10:29:19 +01:00
, AllMimeRender (ctyp' ': ctyps) a
) => AllMimeRender (ctyp ': ctyp' ': ctyps) a where
2015-02-19 10:29:19 +01:00
allMimeRender _ a = (contentType pctyp, toByteString pctyp a)
:(allMimeRender pctyps a)
where pctyp = Proxy :: Proxy ctyp
2015-02-19 10:29:19 +01:00
pctyps = Proxy :: Proxy (ctyp' ': ctyps)
instance AllMimeRender '[] a where
2015-02-19 10:29:19 +01:00
allMimeRender _ _ = []
--------------------------------------------------------------------------
-- Check that all elements of list are instances of MimeUnrender
--------------------------------------------------------------------------
class AllMimeUnrender ls a where
2015-02-19 10:29:19 +01:00
allMimeUnrender :: Proxy ls -> ByteString -> [(M.MediaType, Either String a)]
2015-02-19 10:29:19 +01:00
instance AllMimeUnrender '[] a where
allMimeUnrender _ _ = []
instance ( MimeUnrender ctyp a
, AllMimeUnrender ctyps a
2015-02-19 10:29:19 +01:00
) => AllMimeUnrender (ctyp ': ctyps) a where
allMimeUnrender _ val = (contentType pctyp, fromByteString pctyp val)
:(allMimeUnrender pctyps val)
where pctyp = Proxy :: Proxy ctyp
pctyps = Proxy :: Proxy ctyps
type family IsNonEmpty (ls::[*]) :: Constraint where
2015-02-19 10:29:19 +01:00
IsNonEmpty (x ': xs) = ()
--------------------------------------------------------------------------
-- * MimeRender Instances
-- | `encode`
instance ToJSON a => MimeRender JSON a where
toByteString _ = encode
-- | `Text.encodeUtf8`
instance MimeRender PlainText Text.Text where
toByteString _ = Text.encodeUtf8
-- | `id`
instance MimeRender OctetStream ByteString where
toByteString _ = id
--------------------------------------------------------------------------
-- * MimeUnrender Instances
-- | `eitherDecode`
instance FromJSON a => MimeUnrender JSON a where
fromByteString _ = eitherDecode
-- | `left show . Text.decodeUtf8'`
instance MimeUnrender PlainText Text.Text where
fromByteString _ = left show . Text.decodeUtf8'
-- | `Right . id`
instance MimeUnrender OctetStream ByteString where
fromByteString _ = Right . id