{-# LANGUAGE FlexibleInstances #-}
module Dormouse.Client.Payload
( HasMediaType(..)
, EmptyPayload
, RequestPayload(..)
, ResponsePayload(..)
, JsonPayload
, UrlFormPayload
, HtmlPayload
, RawRequestPayload(..)
, json
, urlForm
, noPayload
, html
) where
import Control.Exception.Safe (MonadThrow, throw)
import Control.Monad.IO.Class
import Data.Aeson (FromJSON, ToJSON, encode, eitherDecodeStrict)
import qualified Data.CaseInsensitive as CI
import Data.Proxy
import qualified Data.Text as T
import qualified Data.Text.Encoding as TE
import Data.Word (Word8, Word64)
import Dormouse.Client.Data
import Dormouse.Client.Types
import Dormouse.Client.Exception (DecodingException(..))
import Dormouse.Client.Headers
import Dormouse.Client.Headers.MediaType
import qualified Dormouse.Client.Headers.MediaType as MTH
import qualified Data.ByteString.Lazy as LB
import qualified Data.Map.Strict as Map
import qualified Web.FormUrlEncoded as W
import qualified Streamly.Data.Fold as Fold
import qualified Streamly.External.ByteString as SEB
import qualified Streamly.External.ByteString.Lazy as SEBL
import qualified Streamly.Data.Stream as Stream
class HasMediaType tag where
mediaType :: Proxy tag -> Maybe MediaType
data RawRequestPayload
= DefinedContentLength Word64 (Stream.Stream IO Word8)
| ChunkedTransfer (Stream.Stream IO Word8)
class HasMediaType contentTag => RequestPayload body contentTag where
serialiseRequest :: Proxy contentTag -> HttpRequest url method body contentTag acceptTag -> HttpRequest url method RawRequestPayload contentTag acceptTag
class HasMediaType tag => ResponsePayload body tag where
deserialiseRequest :: Proxy tag -> HttpResponse (Stream.Stream IO Word8) -> IO (HttpResponse body)
data JsonPayload = JsonPayload
instance HasMediaType JsonPayload where
mediaType :: Proxy JsonPayload -> Maybe MediaType
mediaType Proxy JsonPayload
_ = MediaType -> Maybe MediaType
forall a. a -> Maybe a
Just MediaType
applicationJson
instance (ToJSON body) => RequestPayload body JsonPayload where
serialiseRequest :: forall url (method :: Symbol) acceptTag.
Proxy JsonPayload
-> HttpRequest url method body JsonPayload acceptTag
-> HttpRequest url method RawRequestPayload JsonPayload acceptTag
serialiseRequest Proxy JsonPayload
_ HttpRequest url method body JsonPayload acceptTag
r =
let b :: body
b = HttpRequest url method body JsonPayload acceptTag -> body
forall url (method :: Symbol) body contentTag acceptTag.
HttpRequest url method body contentTag acceptTag -> body
requestBody HttpRequest url method body JsonPayload acceptTag
r
lbs :: ByteString
lbs = body -> ByteString
forall a. ToJSON a => a -> ByteString
encode body
b
in HttpRequest url method body JsonPayload acceptTag
r { requestBody = DefinedContentLength (fromIntegral . LB.length $ lbs) (Stream.unfold SEBL.reader lbs) }
instance (FromJSON body) => ResponsePayload body JsonPayload where
deserialiseRequest :: Proxy JsonPayload
-> HttpResponse (Stream IO Word8) -> IO (HttpResponse body)
deserialiseRequest Proxy JsonPayload
_ HttpResponse (Stream IO Word8)
resp = do
let stream :: Stream IO Word8
stream = HttpResponse (Stream IO Word8) -> Stream IO Word8
forall body. HttpResponse body -> body
responseBody HttpResponse (Stream IO Word8)
resp
ByteString
bs <- Fold IO Word8 ByteString -> Stream IO Word8 -> IO ByteString
forall (m :: * -> *) a b.
Monad m =>
Fold m a b -> Stream m a -> m b
Stream.fold Fold IO Word8 ByteString
forall (m :: * -> *). MonadIO m => Fold m Word8 ByteString
SEB.write Stream IO Word8
stream
body
body <- (String -> IO body)
-> (body -> IO body) -> Either String body -> IO body
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (DecodingException -> IO body
forall (m :: * -> *) e a.
(HasCallStack, MonadThrow m, Exception e) =>
e -> m a
throw (DecodingException -> IO body)
-> (String -> DecodingException) -> String -> IO body
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> DecodingException
DecodingException (Text -> DecodingException)
-> (String -> Text) -> String -> DecodingException
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack) body -> IO body
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String body -> IO body)
-> (ByteString -> Either String body) -> ByteString -> IO body
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either String body
forall a. FromJSON a => ByteString -> Either String a
eitherDecodeStrict (ByteString -> IO body) -> ByteString -> IO body
forall a b. (a -> b) -> a -> b
$ ByteString
bs
HttpResponse body -> IO (HttpResponse body)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (HttpResponse body -> IO (HttpResponse body))
-> HttpResponse body -> IO (HttpResponse body)
forall a b. (a -> b) -> a -> b
$ HttpResponse (Stream IO Word8)
resp { responseBody = body }
json :: Proxy JsonPayload
json :: Proxy JsonPayload
json = Proxy JsonPayload
forall {k} (t :: k). Proxy t
Proxy :: Proxy JsonPayload
data UrlFormPayload = UrlFormPayload
instance HasMediaType UrlFormPayload where
mediaType :: Proxy UrlFormPayload -> Maybe MediaType
mediaType Proxy UrlFormPayload
_ = MediaType -> Maybe MediaType
forall a. a -> Maybe a
Just MediaType
applicationXWWWFormUrlEncoded
instance (W.ToForm body) => RequestPayload body UrlFormPayload where
serialiseRequest :: forall url (method :: Symbol) acceptTag.
Proxy UrlFormPayload
-> HttpRequest url method body UrlFormPayload acceptTag
-> HttpRequest
url method RawRequestPayload UrlFormPayload acceptTag
serialiseRequest Proxy UrlFormPayload
_ HttpRequest url method body UrlFormPayload acceptTag
r =
let b :: body
b = HttpRequest url method body UrlFormPayload acceptTag -> body
forall url (method :: Symbol) body contentTag acceptTag.
HttpRequest url method body contentTag acceptTag -> body
requestBody HttpRequest url method body UrlFormPayload acceptTag
r
lbs :: ByteString
lbs = body -> ByteString
forall a. ToForm a => a -> ByteString
W.urlEncodeAsForm body
b
in HttpRequest url method body UrlFormPayload acceptTag
r { requestBody = DefinedContentLength (fromIntegral . LB.length $ lbs) (Stream.unfold SEBL.reader lbs) }
instance (W.FromForm body) => ResponsePayload body UrlFormPayload where
deserialiseRequest :: Proxy UrlFormPayload
-> HttpResponse (Stream IO Word8) -> IO (HttpResponse body)
deserialiseRequest Proxy UrlFormPayload
_ HttpResponse (Stream IO Word8)
resp = do
let stream :: Stream IO Word8
stream = HttpResponse (Stream IO Word8) -> Stream IO Word8
forall body. HttpResponse body -> body
responseBody HttpResponse (Stream IO Word8)
resp
ByteString
bs <- Fold IO Word8 ByteString -> Stream IO Word8 -> IO ByteString
forall (m :: * -> *) a b.
Monad m =>
Fold m a b -> Stream m a -> m b
Stream.fold Fold IO Word8 ByteString
forall (m :: * -> *). MonadIO m => Fold m Word8 ByteString
SEB.write (Stream IO Word8 -> IO ByteString)
-> Stream IO Word8 -> IO ByteString
forall a b. (a -> b) -> a -> b
$ Stream IO Word8
stream
body
body <- (Text -> IO body)
-> (body -> IO body) -> Either Text body -> IO body
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (DecodingException -> IO body
forall (m :: * -> *) e a.
(HasCallStack, MonadThrow m, Exception e) =>
e -> m a
throw (DecodingException -> IO body)
-> (Text -> DecodingException) -> Text -> IO body
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> DecodingException
DecodingException) body -> IO body
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either Text body -> IO body)
-> (ByteString -> Either Text body) -> ByteString -> IO body
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either Text body
forall a. FromForm a => ByteString -> Either Text a
W.urlDecodeAsForm (ByteString -> IO body) -> ByteString -> IO body
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
LB.fromStrict ByteString
bs
HttpResponse body -> IO (HttpResponse body)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (HttpResponse body -> IO (HttpResponse body))
-> HttpResponse body -> IO (HttpResponse body)
forall a b. (a -> b) -> a -> b
$ HttpResponse (Stream IO Word8)
resp { responseBody = body }
urlForm :: Proxy UrlFormPayload
urlForm :: Proxy UrlFormPayload
urlForm = Proxy UrlFormPayload
forall {k} (t :: k). Proxy t
Proxy :: Proxy UrlFormPayload
data EmptyPayload = EmptyPayload
instance HasMediaType EmptyPayload where
mediaType :: Proxy EmptyPayload -> Maybe MediaType
mediaType Proxy EmptyPayload
_ = Maybe MediaType
forall a. Maybe a
Nothing
instance RequestPayload Empty EmptyPayload where
serialiseRequest :: forall url (method :: Symbol) acceptTag.
Proxy EmptyPayload
-> HttpRequest url method Empty EmptyPayload acceptTag
-> HttpRequest url method RawRequestPayload EmptyPayload acceptTag
serialiseRequest Proxy EmptyPayload
_ HttpRequest url method Empty EmptyPayload acceptTag
r = HttpRequest url method Empty EmptyPayload acceptTag
r { requestBody = DefinedContentLength 0 Stream.nil }
instance ResponsePayload Empty EmptyPayload where
deserialiseRequest :: Proxy EmptyPayload
-> HttpResponse (Stream IO Word8) -> IO (HttpResponse Empty)
deserialiseRequest Proxy EmptyPayload
_ HttpResponse (Stream IO Word8)
resp = do
let stream :: Stream IO Word8
stream = HttpResponse (Stream IO Word8) -> Stream IO Word8
forall body. HttpResponse body -> body
responseBody HttpResponse (Stream IO Word8)
resp
Empty
body <- Empty
Empty Empty -> IO () -> IO Empty
forall a b. a -> IO b -> IO a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Fold IO Word8 () -> Stream IO Word8 -> IO ()
forall (m :: * -> *) a b.
Monad m =>
Fold m a b -> Stream m a -> m b
Stream.fold Fold IO Word8 ()
forall (m :: * -> *) a. Monad m => Fold m a ()
Fold.drain Stream IO Word8
stream
HttpResponse Empty -> IO (HttpResponse Empty)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (HttpResponse Empty -> IO (HttpResponse Empty))
-> HttpResponse Empty -> IO (HttpResponse Empty)
forall a b. (a -> b) -> a -> b
$ HttpResponse (Stream IO Word8)
resp { responseBody = body }
noPayload :: Proxy EmptyPayload
noPayload :: Proxy EmptyPayload
noPayload = Proxy EmptyPayload
forall {k} (t :: k). Proxy t
Proxy :: Proxy EmptyPayload
decodeTextContent :: (MonadThrow m, MonadIO m) => HttpResponse (Stream.Stream m Word8) -> m (HttpResponse T.Text)
decodeTextContent :: forall (m :: * -> *).
(MonadThrow m, MonadIO m) =>
HttpResponse (Stream m Word8) -> m (HttpResponse Text)
decodeTextContent HttpResponse (Stream m Word8)
resp = do
let contentTypeHV :: Maybe ByteString
contentTypeHV = HeaderName -> HttpResponse (Stream m Word8) -> Maybe ByteString
forall a. HasHeaders a => HeaderName -> a -> Maybe ByteString
getHeaderValue HeaderName
"Content-Type" HttpResponse (Stream m Word8)
resp
Maybe MediaType
mediaType' <- (ByteString -> m MediaType)
-> Maybe ByteString -> m (Maybe MediaType)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Maybe a -> f (Maybe b)
traverse ByteString -> m MediaType
forall (m :: * -> *). MonadThrow m => ByteString -> m MediaType
MTH.parseMediaType Maybe ByteString
contentTypeHV
let maybeCharset :: Maybe ByteString
maybeCharset = Maybe MediaType
mediaType' Maybe MediaType
-> (MediaType -> Maybe ByteString) -> Maybe ByteString
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= HeaderName -> Map HeaderName ByteString -> Maybe ByteString
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup HeaderName
"charset" (Map HeaderName ByteString -> Maybe ByteString)
-> (MediaType -> Map HeaderName ByteString)
-> MediaType
-> Maybe ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MediaType -> Map HeaderName ByteString
MTH.parameters
let stream :: Stream m Word8
stream = HttpResponse (Stream m Word8) -> Stream m Word8
forall body. HttpResponse body -> body
responseBody HttpResponse (Stream m Word8)
resp
ByteString
bs <- Fold m Word8 ByteString -> Stream m Word8 -> m ByteString
forall (m :: * -> *) a b.
Monad m =>
Fold m a b -> Stream m a -> m b
Stream.fold Fold m Word8 ByteString
forall (m :: * -> *). MonadIO m => Fold m Word8 ByteString
SEB.write (Stream m Word8 -> m ByteString) -> Stream m Word8 -> m ByteString
forall a b. (a -> b) -> a -> b
$ Stream m Word8
stream
HttpResponse Text -> m (HttpResponse Text)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (HttpResponse Text -> m (HttpResponse Text))
-> HttpResponse Text -> m (HttpResponse Text)
forall a b. (a -> b) -> a -> b
$ HttpResponse (Stream m Word8)
resp { responseBody = decodeContent maybeCharset bs }
where
decodeContent :: Maybe a -> ByteString -> Text
decodeContent Maybe a
maybeCharset ByteString
bs' =
case (a -> CI a) -> Maybe a -> Maybe (CI a)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> CI a
forall s. FoldCase s => s -> CI s
CI.mk Maybe a
maybeCharset of
Just(CI a
"utf8") -> ByteString -> Text
TE.decodeUtf8 ByteString
bs'
Just(CI a
"iso-8859-1") -> ByteString -> Text
TE.decodeLatin1 ByteString
bs'
Maybe (CI a)
_ -> ByteString -> Text
TE.decodeUtf8 ByteString
bs'
data HtmlPayload = HtmlPayload
instance HasMediaType HtmlPayload where
mediaType :: Proxy HtmlPayload -> Maybe MediaType
mediaType Proxy HtmlPayload
_ = MediaType -> Maybe MediaType
forall a. a -> Maybe a
Just MediaType
textHtml
instance RequestPayload T.Text HtmlPayload where
serialiseRequest :: forall url (method :: Symbol) acceptTag.
Proxy HtmlPayload
-> HttpRequest url method Text HtmlPayload acceptTag
-> HttpRequest url method RawRequestPayload HtmlPayload acceptTag
serialiseRequest Proxy HtmlPayload
_ HttpRequest url method Text HtmlPayload acceptTag
r =
let b :: Text
b = HttpRequest url method Text HtmlPayload acceptTag -> Text
forall url (method :: Symbol) body contentTag acceptTag.
HttpRequest url method body contentTag acceptTag -> body
requestBody HttpRequest url method Text HtmlPayload acceptTag
r
lbs :: ByteString
lbs = ByteString -> ByteString
LB.fromStrict (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
TE.encodeUtf8 Text
b
in HttpRequest url method Text HtmlPayload acceptTag
r { requestBody = DefinedContentLength (fromIntegral . LB.length $ lbs) (Stream.unfold SEBL.reader lbs) }
instance ResponsePayload T.Text HtmlPayload where
deserialiseRequest :: Proxy HtmlPayload
-> HttpResponse (Stream IO Word8) -> IO (HttpResponse Text)
deserialiseRequest Proxy HtmlPayload
_ HttpResponse (Stream IO Word8)
resp = HttpResponse (Stream IO Word8) -> IO (HttpResponse Text)
forall (m :: * -> *).
(MonadThrow m, MonadIO m) =>
HttpResponse (Stream m Word8) -> m (HttpResponse Text)
decodeTextContent HttpResponse (Stream IO Word8)
resp
html :: Proxy HtmlPayload
html :: Proxy HtmlPayload
html = Proxy HtmlPayload
forall {k} (t :: k). Proxy t
Proxy :: Proxy HtmlPayload