Skip to content

Commit

Permalink
WIP
Browse files Browse the repository at this point in the history
  • Loading branch information
theophile-scrive committed Aug 9, 2024
1 parent 9e0d8d2 commit d10fc87
Show file tree
Hide file tree
Showing 10 changed files with 388 additions and 247 deletions.
1 change: 1 addition & 0 deletions servant-client-core/servant-client-core.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -91,6 +91,7 @@ library
Servant.Client.Core.Reexport
Servant.Client.Core.Request
Servant.Client.Core.Response
Servant.Client.Core.ResponseUnrender
Servant.Client.Core.RunClient
Servant.Client.Free
Servant.Client.Generic
Expand Down
72 changes: 32 additions & 40 deletions servant-client-core/src/Servant/Client/Core/HasClient.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE ApplicativeDo #-}
{-# OPTIONS_GHC -Wno-missing-methods #-}
{-# LANGUAGE EmptyCase #-}
module Servant.Client.Core.HasClient (
clientIn,
HasClient (..),
Expand All @@ -9,17 +9,19 @@ module Servant.Client.Core.HasClient (
(//),
(/:),
foldMapUnion,
matchUnion
matchUnion,
fromSomeClientResponse
) where

import Prelude ()
import Prelude.Compat

import Control.Arrow
(left, (+++))
import qualified Data.Text as Text
import Control.Monad
(unless)
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Lazy as BSL
import Data.Either
(partitionEithers)
import Data.Constraint (Dict(..))
Expand All @@ -43,13 +45,11 @@ import Data.SOP.Constraint
import Data.SOP.NP
(NP (..), cpure_NP)
import Data.SOP.NS
(NS (S))
(NS (..))
import Data.String
(fromString)
import Data.Text
(Text, pack)
import Data.Proxy
(Proxy (Proxy))
import GHC.TypeLits
(KnownNat, KnownSymbol, TypeError, symbolVal)
import Network.HTTP.Types
Expand All @@ -71,7 +71,7 @@ import Servant.API.Generic
(GenericMode(..), ToServant, ToServantApi
, GenericServant, toServant, fromServant)
import Servant.API.ContentTypes
(contentTypes, AllMime (allMime), AllMimeUnrender (allMimeUnrender), AcceptHeader)
(contentTypes, AllMime (allMime), AllMimeUnrender (allMimeUnrender))
import Servant.API.QueryString (ToDeepQuery(..), generateDeepParam)
import Servant.API.Status
(statusFromNat)
Expand All @@ -87,9 +87,12 @@ import Servant.Client.Core.BasicAuth
import Servant.Client.Core.ClientError
import Servant.Client.Core.Request
import Servant.Client.Core.Response
import Servant.Client.Core.ResponseUnrender
import qualified Servant.Client.Core.Response as Response
import Servant.Client.Core.RunClient
import Servant.API.MultiVerb
import Servant.API.MultiVerb
import qualified Network.HTTP.Media as M
import Data.Typeable

-- * Accessing APIs as a Client

Expand Down Expand Up @@ -325,7 +328,7 @@ data ClientParseError = ClientParseError MediaType String | ClientStatusMismatch
deriving (Eq, Show)

class UnrenderResponse (cts :: [Type]) (a :: Type) where
unrenderResponse :: Seq.Seq H.Header -> BL.ByteString -> Proxy cts
unrenderResponse :: Seq.Seq H.Header -> BSL.ByteString -> Proxy cts
-> [Either (MediaType, String) a]

instance {-# OVERLAPPABLE #-} AllMimeUnrender cts a => UnrenderResponse cts a where
Expand Down Expand Up @@ -367,15 +370,13 @@ instance {-# OVERLAPPING #-}

method = reflectMethod $ Proxy @method
acceptStatus = statuses (Proxy @as)
response <- runRequestAcceptStatus (Just acceptStatus) request {requestMethod = method, requestAccept = accept}
response@Response{responseBody=body, responseStatusCode=status, responseHeaders=headers}
<- runRequestAcceptStatus (Just acceptStatus) (request {requestMethod = method, requestAccept = accept})
responseContentType <- checkContentTypeHeader response
unless (any (matches responseContentType) accept) $ do
throwClientError $ UnsupportedContentType responseContentType response

let status = responseStatusCode response
body = responseBody response
headers = responseHeaders response
res = tryParsers status $ mimeUnrenders (Proxy @contentTypes) headers body
let res = tryParsers status $ mimeUnrenders (Proxy @contentTypes) headers body
case res of
Left errors -> throwClientError $ DecodeFailure (T.pack (show errors)) response
Right x -> return x
Expand All @@ -399,7 +400,7 @@ instance {-# OVERLAPPING #-}
All (UnrenderResponse cts) xs =>
Proxy cts ->
Seq.Seq H.Header ->
BL.ByteString ->
BSL.ByteString ->
NP ([] :.: Either (MediaType, String)) xs
mimeUnrenders ctp headers body = cpure_NP
(Proxy @(UnrenderResponse cts))
Expand All @@ -416,10 +417,10 @@ instance {-# OVERLAPPABLE #-}

hoistClientMonad _ _ f ma = f ma

clientWithRoute _pm Proxy req = withStreamingRequest req' $ \gres -> do
let mimeUnrender' = mimeUnrender (Proxy :: Proxy ct) :: BL.ByteString -> Either String chunk
clientWithRoute _pm Proxy req = withStreamingRequest req' $ \Response{responseBody=body} -> do
let mimeUnrender' = mimeUnrender (Proxy :: Proxy ct) :: BSL.ByteString -> Either String chunk
framingUnrender' = framingUnrender (Proxy :: Proxy framing) mimeUnrender'
fromSourceIO $ framingUnrender' $ responseBody gres
fromSourceIO $ framingUnrender' body
where
req' = req
{ requestAccept = fromList [contentType (Proxy :: Proxy ct)]
Expand All @@ -436,13 +437,14 @@ instance {-# OVERLAPPING #-}

hoistClientMonad _ _ f ma = f ma

clientWithRoute _pm Proxy req = withStreamingRequest req' $ \gres -> do
let mimeUnrender' = mimeUnrender (Proxy :: Proxy ct) :: BL.ByteString -> Either String chunk
clientWithRoute _pm Proxy req = withStreamingRequest req' $
\Response{responseBody=body, responseHeaders=headers} -> do
let mimeUnrender' = mimeUnrender (Proxy :: Proxy ct) :: BSL.ByteString -> Either String chunk
framingUnrender' = framingUnrender (Proxy :: Proxy framing) mimeUnrender'
val <- fromSourceIO $ framingUnrender' $ responseBody gres
val <- fromSourceIO $ framingUnrender' body
return $ Headers
{ getResponse = val
, getHeadersHList = buildHeadersTo . toList $ responseHeaders gres
, getHeadersHList = buildHeadersTo $ toList headers
}

where
Expand Down Expand Up @@ -760,7 +762,7 @@ instance

sourceIO = framingRender
framingP
(mimeRender ctypeP :: chunk -> BL.ByteString)
(mimeRender ctypeP :: chunk -> BSL.ByteString)
(toSourceIO body)

-- | Make the querying function append @path@ to the request path.
Expand Down Expand Up @@ -975,19 +977,9 @@ x // f = f x
(/:) :: (a -> b -> c) -> b -> a -> c
(/:) = flip

class IsResponseList cs as where
responseListRender :: AcceptHeader -> Union (ResponseTypes as) -> Maybe InternalResponse
responseListUnrender :: M.MediaType -> InternalResponse -> UnrenderResult (Union (ResponseTypes as))

responseListStatuses :: [Status]

instance IsResponseList cs '[] where
responseListRender _ x = case x of {}
responseListUnrender _ _ = empty
responseListStatuses = []

instance
( IsResponseList cs as,
( ResponseListUnrender cs as,
AllMime cs,
ReflectMethod method,
AsUnion as r,
Expand All @@ -998,7 +990,7 @@ instance
type Client m (MultiVerb method cs as r) = m r

clientWithRoute _ _ req = do
response <-
response@Response{responseBody=body} <-
runRequestAcceptStatus
(Just (responseListStatuses @cs @as))
req
Expand All @@ -1012,9 +1004,9 @@ instance

-- FUTUREWORK: support streaming
let sresp =
if LBS.null (responseBody response)
then SomeResponse response {responseBody = ()}
else SomeResponse response
if BSL.null body
then SomeClientResponse $ response {Response.responseBody = ()}
else SomeClientResponse response
case responseListUnrender @cs @as c sresp of
StatusMismatch -> throwClientError (DecodeFailure "Status mismatch" response)
UnrenderError e -> throwClientError (DecodeFailure (Text.pack e) response)
Expand Down Expand Up @@ -1064,11 +1056,11 @@ checkContentTypeHeader response =

decodedAs :: forall ct a m. (MimeUnrender ct a, RunClient m)
=> Response -> Proxy ct -> m a
decodedAs response ct = do
decodedAs response@Response{responseBody=body} ct = do
responseContentType <- checkContentTypeHeader response
unless (any (matches responseContentType) accept) $
throwClientError $ UnsupportedContentType responseContentType response
case mimeUnrender ct $ responseBody response of
case mimeUnrender ct body of
Left err -> throwClientError $ DecodeFailure (T.pack err) response
Right val -> return val
where
Expand Down
9 changes: 7 additions & 2 deletions servant-client-core/src/Servant/Client/Core/Response.hs
Original file line number Diff line number Diff line change
@@ -1,17 +1,17 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NamedFieldPuns #-}

module Servant.Client.Core.Response (
Response,
StreamingResponse,
ResponseF (..),
responseToInternalResponse,
) where

import Prelude ()
Expand All @@ -31,6 +31,7 @@ import Network.HTTP.Types

import Servant.API.Stream
(SourceIO)
import Servant.Types.ResponseList

data ResponseF a = Response
{ responseStatusCode :: Status
Expand All @@ -51,3 +52,7 @@ instance NFData a => NFData (ResponseF a) where

type Response = ResponseF LBS.ByteString
type StreamingResponse = ResponseF (SourceIO BS.ByteString)

responseToInternalResponse :: ResponseF a -> InternalResponse a
responseToInternalResponse Response{responseStatusCode, responseHeaders,responseBody} =
InternalResponse responseStatusCode responseHeaders responseBody
134 changes: 134 additions & 0 deletions servant-client-core/src/Servant/Client/Core/ResponseUnrender.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,134 @@
{-# LANGUAGE ApplicativeDo #-}
module Servant.Client.Core.ResponseUnrender where

import Control.Applicative
import Control.Monad
import Data.Kind (Type)
import Data.SOP
import Data.Typeable
import GHC.TypeLits
import Network.HTTP.Types.Status (Status)
import qualified Data.ByteString.Lazy as BSL
import qualified Network.HTTP.Media as M

import Servant.API.ContentTypes
import Servant.API.MultiVerb
import Servant.API.Status
import Servant.API.UVerb.Union (Union)
import Servant.Client.Core.Response (ResponseF(..))
import qualified Servant.Client.Core.Response as Response
import Servant.API.Stream (SourceIO)
import Data.ByteString (ByteString)

data SomeClientResponse = forall a. Typeable a => SomeClientResponse (ResponseF a)

fromSomeClientResponse
:: forall a m. (Alternative m, Typeable a)
=> SomeClientResponse
-> m (ResponseF a)
fromSomeClientResponse (SomeClientResponse Response {..}) = do
body <- maybe empty pure $ cast @_ @a responseBody
pure $
Response
{ responseBody = body,
..
}


class ResponseUnrender cs a where
type ResponseBody a :: Type
type ResponseStatus a :: Nat
responseUnrender
:: M.MediaType
-> ResponseF (ResponseBody a)
-> UnrenderResult (ResponseType a)

--
-- FIXME: Move this to the client in its own module
class (Typeable as) => ResponseListUnrender cs as where
responseListUnrender
:: M.MediaType
-> SomeClientResponse
-> UnrenderResult (Union (ResponseTypes as))

responseListStatuses :: [Status]

instance ResponseListUnrender cs '[] where
responseListUnrender _ _ = StatusMismatch
responseListStatuses = []

instance
( Typeable a,
Typeable (ResponseBody a),
ResponseUnrender cs a,
ResponseListUnrender cs as,
KnownStatus (ResponseStatus a)
) =>
ResponseListUnrender cs (a ': as)
where
responseListUnrender c output =
Z . I <$> (responseUnrender @cs @a c =<< fromSomeClientResponse output)
<|> S <$> responseListUnrender @cs @as c output

responseListStatuses = statusVal (Proxy @(ResponseStatus a)) : responseListStatuses @cs @as

instance
( KnownStatus s,
MimeUnrender ct a
) =>
ResponseUnrender cs (RespondAs (ct :: Type) s desc a)
where
type ResponseStatus (RespondAs ct s desc a) = s
type ResponseBody (RespondAs ct s desc a) = BSL.ByteString

responseUnrender _ output = do
guard (responseStatusCode output == statusVal (Proxy @s))
either UnrenderError UnrenderSuccess $
mimeUnrender (Proxy @ct) (Response.responseBody output)

instance (KnownStatus s) => ResponseUnrender cs (RespondAs '() s desc ()) where
type ResponseStatus (RespondAs '() s desc ()) = s
type ResponseBody (RespondAs '() s desc ()) = ()

responseUnrender _ output =
guard (responseStatusCode output == statusVal (Proxy @s))

instance
(KnownStatus s)
=> ResponseUnrender cs (RespondStreaming s desc framing ct)
where
type ResponseStatus (RespondStreaming s desc framing ct) = s
type ResponseBody (RespondStreaming s desc framing ct) = SourceIO ByteString

responseUnrender _ resp = do
guard (Response.responseStatusCode resp == statusVal (Proxy @s))
pure $ Response.responseBody resp

instance
(AllMimeUnrender cs a, KnownStatus s)
=> ResponseUnrender cs (Respond s desc a) where
type ResponseStatus (Respond s desc a) = s
type ResponseBody (Respond s desc a) = BSL.ByteString

responseUnrender c output = do
guard (responseStatusCode output == statusVal (Proxy @s))
let results = allMimeUnrender (Proxy @cs)
case lookup c results of
Nothing -> empty
Just f -> either UnrenderError UnrenderSuccess (f (responseBody output))

instance
( AsHeaders xs (ResponseType r) a,
ServantHeaders hs xs,
ResponseUnrender cs r
) =>
ResponseUnrender cs (WithHeaders hs a r)
where
type ResponseStatus (WithHeaders hs a r) = ResponseStatus r
type ResponseBody (WithHeaders hs a r) = ResponseBody r

responseUnrender c output = do
x <- responseUnrender @cs @r c output
case extractHeaders @hs (responseHeaders output) of
Nothing -> UnrenderError "Failed to parse headers"
Just hs -> pure $ fromHeaders @xs (hs, x)
3 changes: 2 additions & 1 deletion servant-server/servant-server.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -103,8 +103,9 @@ library
Servant.Server.Internal.DelayedIO
Servant.Server.Internal.ErrorFormatter
Servant.Server.Internal.Handler
Servant.Server.Internal.Router
Servant.Server.Internal.ResponseRender
Servant.Server.Internal.RouteResult
Servant.Server.Internal.Router
Servant.Server.Internal.RoutingApplication
Servant.Server.Internal.ServerError
Servant.Server.StaticFiles
Expand Down
Loading

0 comments on commit d10fc87

Please sign in to comment.