{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_HADDOCK not-home #-}
module Servant.API.ContentTypes
(
JSON
, PlainText
, FormUrlEncoded
, OctetStream
, Accept(..)
, MimeRender(..)
, MimeUnrender(..)
, NoContent(..)
, AcceptHeader(..)
, AllCTRender(..)
, AllCTUnrender(..)
, AllMime(..)
, AllMimeRender(..)
, AllMimeUnrender(..)
, eitherDecodeLenient
, canHandleAcceptH
) where
import Control.Arrow
(left)
import Control.Monad.Compat
import Data.Aeson
(FromJSON (..), ToJSON (..), encode)
import Data.Aeson.Parser
(value)
import Data.Aeson.Types
(parseEither)
import Data.Attoparsec.ByteString.Char8
(endOfInput, parseOnly, skipSpace, (<?>))
import qualified Data.ByteString as BS
import Data.ByteString.Lazy
(ByteString, fromStrict, toStrict)
import qualified Data.ByteString.Lazy.Char8 as BC
import qualified Data.List.NonEmpty as NE
import Data.Maybe
(isJust)
import Data.String.Conversions
(cs)
import qualified Data.Text as TextS
import qualified Data.Text.Encoding as TextS
import qualified Data.Text.Lazy as TextL
import qualified Data.Text.Lazy.Encoding as TextL
import Data.Typeable
import GHC.Generics
(Generic)
import qualified GHC.TypeLits as TL
import qualified Network.HTTP.Media as M
import Prelude ()
import Prelude.Compat
import Web.FormUrlEncoded
(FromForm, ToForm, urlDecodeAsForm, urlEncodeAsForm)
data JSON deriving Typeable
data PlainText deriving Typeable
data FormUrlEncoded deriving Typeable
data OctetStream deriving Typeable
class Accept ctype where
contentType :: Proxy ctype -> M.MediaType
contentType = NE.head . contentTypes
contentTypes :: Proxy ctype -> NE.NonEmpty M.MediaType
contentTypes = (NE.:| []) . contentType
{-# MINIMAL contentType | contentTypes #-}
instance Accept JSON where
contentTypes _ =
"application" M.// "json" M./: ("charset", "utf-8") NE.:|
[ "application" M.// "json" ]
instance Accept FormUrlEncoded where
contentType _ = "application" M.// "x-www-form-urlencoded"
instance Accept PlainText where
contentType _ = "text" M.// "plain" M./: ("charset", "utf-8")
instance Accept OctetStream where
contentType _ = "application" M.// "octet-stream"
newtype AcceptHeader = AcceptHeader BS.ByteString
deriving (Eq, Show, Read, Typeable, Generic)
class Accept ctype => MimeRender ctype a where
mimeRender :: Proxy ctype -> a -> ByteString
class (AllMime list) => AllCTRender (list :: [*]) a where
handleAcceptH :: Proxy list -> AcceptHeader -> a -> Maybe (ByteString, ByteString)
instance {-# OVERLAPPABLE #-}
(Accept ct, AllMime cts, AllMimeRender (ct ': cts) a) => AllCTRender (ct ': cts) a where
handleAcceptH _ (AcceptHeader accept) val = M.mapAcceptMedia lkup accept
where pctyps = Proxy :: Proxy (ct ': cts)
amrs = allMimeRender pctyps val
lkup = fmap (\(a,b) -> (a, (fromStrict $ M.renderHeader a, b))) amrs
instance TL.TypeError ('TL.Text "No instance for (), use NoContent instead.")
=> AllCTRender '[] () where
handleAcceptH _ _ _ = error "unreachable"
class Accept ctype => MimeUnrender ctype a where
mimeUnrender :: Proxy ctype -> ByteString -> Either String a
mimeUnrender p = mimeUnrenderWithType p (contentType p)
mimeUnrenderWithType :: Proxy ctype -> M.MediaType -> ByteString -> Either String a
mimeUnrenderWithType p _ = mimeUnrender p
{-# MINIMAL mimeUnrender | mimeUnrenderWithType #-}
class AllCTUnrender (list :: [*]) a where
canHandleCTypeH
:: Proxy list
-> ByteString
-> Maybe (ByteString -> Either String a)
handleCTypeH :: Proxy list
-> ByteString
-> ByteString
-> Maybe (Either String a)
handleCTypeH p ctypeH body = ($ body) `fmap` canHandleCTypeH p ctypeH
instance ( AllMimeUnrender ctyps a ) => AllCTUnrender ctyps a where
canHandleCTypeH p ctypeH =
M.mapContentMedia (allMimeUnrender p) (cs ctypeH)
class AllMime (list :: [*]) where
allMime :: Proxy list -> [M.MediaType]
instance AllMime '[] where
allMime _ = []
instance (Accept ctyp, AllMime ctyps) => AllMime (ctyp ': ctyps) where
allMime _ = NE.toList (contentTypes pctyp) ++ allMime pctyps
where
pctyp = Proxy :: Proxy ctyp
pctyps = Proxy :: Proxy ctyps
canHandleAcceptH :: AllMime list => Proxy list -> AcceptHeader -> Bool
canHandleAcceptH p (AcceptHeader h ) = isJust $ M.matchAccept (allMime p) h
class (AllMime list) => AllMimeRender (list :: [*]) a where
allMimeRender :: Proxy list
-> a
-> [(M.MediaType, ByteString)]
instance {-# OVERLAPPABLE #-} ( MimeRender ctyp a ) => AllMimeRender '[ctyp] a where
allMimeRender _ a = map (, bs) $ NE.toList $ contentTypes pctyp
where
bs = mimeRender pctyp a
pctyp = Proxy :: Proxy ctyp
instance {-# OVERLAPPABLE #-}
( MimeRender ctyp a
, AllMimeRender (ctyp' ': ctyps) a
) => AllMimeRender (ctyp ': ctyp' ': ctyps) a where
allMimeRender _ a =
map (, bs) (NE.toList $ contentTypes pctyp)
++ allMimeRender pctyps a
where
bs = mimeRender pctyp a
pctyp = Proxy :: Proxy ctyp
pctyps = Proxy :: Proxy (ctyp' ': ctyps)
instance {-# OVERLAPPING #-} ( Accept ctyp ) => AllMimeRender '[ctyp] NoContent where
allMimeRender _ _ = map (, "") $ NE.toList $ contentTypes pctyp
where
pctyp = Proxy :: Proxy ctyp
instance {-# OVERLAPPING #-}
( AllMime (ctyp ': ctyp' ': ctyps)
) => AllMimeRender (ctyp ': ctyp' ': ctyps) NoContent where
allMimeRender p _ = zip (allMime p) (repeat "")
class (AllMime list) => AllMimeUnrender (list :: [*]) a where
allMimeUnrender :: Proxy list
-> [(M.MediaType, ByteString -> Either String a)]
instance AllMimeUnrender '[] a where
allMimeUnrender _ = []
instance ( MimeUnrender ctyp a
, AllMimeUnrender ctyps a
) => AllMimeUnrender (ctyp ': ctyps) a where
allMimeUnrender _ =
map mk (NE.toList $ contentTypes pctyp)
++ allMimeUnrender pctyps
where
mk ct = (ct, mimeUnrenderWithType pctyp ct)
pctyp = Proxy :: Proxy ctyp
pctyps = Proxy :: Proxy ctyps
instance {-# OVERLAPPABLE #-}
ToJSON a => MimeRender JSON a where
mimeRender _ = encode
instance {-# OVERLAPPABLE #-}
ToForm a => MimeRender FormUrlEncoded a where
mimeRender _ = urlEncodeAsForm
instance MimeRender PlainText TextL.Text where
mimeRender _ = TextL.encodeUtf8
instance MimeRender PlainText TextS.Text where
mimeRender _ = fromStrict . TextS.encodeUtf8
instance MimeRender PlainText String where
mimeRender _ = BC.pack
instance MimeRender OctetStream ByteString where
mimeRender _ = id
instance MimeRender OctetStream BS.ByteString where
mimeRender _ = fromStrict
data NoContent = NoContent
deriving (Show, Eq, Read, Generic)
eitherDecodeLenient :: FromJSON a => ByteString -> Either String a
eitherDecodeLenient input =
parseOnly parser (cs input) >>= parseEither parseJSON
where
parser = skipSpace
*> Data.Aeson.Parser.value
<* skipSpace
<* (endOfInput <?> "trailing junk after valid JSON")
instance FromJSON a => MimeUnrender JSON a where
mimeUnrender _ = eitherDecodeLenient
instance FromForm a => MimeUnrender FormUrlEncoded a where
mimeUnrender _ = left TextS.unpack . urlDecodeAsForm
instance MimeUnrender PlainText TextL.Text where
mimeUnrender _ = left show . TextL.decodeUtf8'
instance MimeUnrender PlainText TextS.Text where
mimeUnrender _ = left show . TextS.decodeUtf8' . toStrict
instance MimeUnrender PlainText String where
mimeUnrender _ = Right . BC.unpack
instance MimeUnrender OctetStream ByteString where
mimeUnrender _ = Right . id
instance MimeUnrender OctetStream BS.ByteString where
mimeUnrender _ = Right . toStrict