Skip to content

Commit

Permalink
Better server-side handling of metadata and errors
Browse files Browse the repository at this point in the history
  • Loading branch information
edsko committed Jul 10, 2023
1 parent 78f4fbd commit f3b8993
Show file tree
Hide file tree
Showing 15 changed files with 490 additions and 291 deletions.
14 changes: 8 additions & 6 deletions demo-server/Demo/Server/API/Protobuf/Greeter.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@ module Demo.Server.API.Protobuf.Greeter (handlers) where

import Control.Lens ((.~), (^.))
import Control.Monad
import Data.Default
import Data.Function ((&))
import Data.ProtoLens
import Data.ProtoLens.Labels ()
Expand Down Expand Up @@ -41,14 +42,15 @@ sayHello req = return $ defMessage & #message .~ msg

sayHelloStreamReply :: RpcHandler IO
sayHelloStreamReply =
(mkRpcHandler (Proxy @(Protobuf Greeter "sayHelloStreamReply")) go) {
handlerMetadata = \_reqMetadata -> return [
AsciiHeader "initial-md" "initial-md-value"
]
}
mkRpcHandler (Proxy @(Protobuf Greeter "sayHelloStreamReply")) go
where
go :: Call (Protobuf Greeter "sayHelloStreamReply") -> IO ()
go call = do
setResponseMetadata call [AsciiHeader "initial-md" "initial-md-value"]

-- The client expects the metadata well before the first output
_ <- initiateResponse call

req <- recvFinalInput call

let msg :: Text -> Text
Expand All @@ -57,4 +59,4 @@ sayHelloStreamReply =
forM_ ["0", "1", "2"] $ \i ->
sendNextOutput call $ defMessage & #message .~ msg i

sendTrailers call []
sendTrailers call def
1 change: 1 addition & 0 deletions grapesy.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -205,6 +205,7 @@ test-suite test-grapesy
other-modules:
Paths_grapesy
Test.Driver.ClientServer
Test.Driver.Dialogue
Test.Sanity.StreamingType.NonStreaming
Test.Util.ClientServer
Test.Util.SOP
Expand Down
19 changes: 9 additions & 10 deletions src/Network/GRPC/Client/Session.hs
Original file line number Diff line number Diff line change
Expand Up @@ -70,7 +70,7 @@ instance IsRPC rpc => IsSession (ClientSession rpc) where
type Outbound (ClientSession rpc) = ClientOutbound rpc

buildProperTrailers _client = \() ->
return [] -- Request trailers are not supported by gRPC
[] -- Request trailers are not supported by gRPC
parseProperTrailers _client =
processResponseTrailers $ Resp.parseProperTrailers (Proxy @rpc)

Expand Down Expand Up @@ -105,15 +105,14 @@ instance IsRPC rpc => InitiateSession (ClientSession rpc) where
(fmap GRPC.getTrailersOnly . Resp.parseTrailersOnly (Proxy @rpc))
(responseHeaders info)

buildRequestInfo _ start = do
return RequestInfo {
requestMethod = rawMethod resourceHeaders
, requestPath = rawPath resourceHeaders
, requestHeaders = Req.buildHeaders (Proxy @rpc) $
case start of
FlowStartRegular headers -> outHeaders headers
FlowStartTrailersOnly headers -> headers
}
buildRequestInfo _ start = RequestInfo {
requestMethod = rawMethod resourceHeaders
, requestPath = rawPath resourceHeaders
, requestHeaders = Req.buildHeaders (Proxy @rpc) $
case start of
FlowStartRegular headers -> outHeaders headers
FlowStartTrailersOnly headers -> headers
}
where
resourceHeaders :: RawResourceHeaders
resourceHeaders = buildResourceHeaders $ ResourceHeaders {
Expand Down
100 changes: 52 additions & 48 deletions src/Network/GRPC/Server.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,11 +9,12 @@ module Network.GRPC.Server (
, Call -- opaque
, RpcHandler -- opaque
, Handler.mkRpcHandler
, Handler.handlerMetadata

-- * Ongoing calls
-- * Open (ongoing) call
, recvInput
, sendOutput
, getRequestMetadata
, setResponseMetadata

-- ** Protocol specific wrappers
, recvFinalInput
Expand All @@ -22,14 +23,19 @@ module Network.GRPC.Server (
, sendNextOutput
, sendTrailers

-- ** Low-level API
, recvInputSTM
, sendOutputSTM
, initiateResponse
, sendTrailersOnly

-- * Common serialization formats
, Protobuf
) where

import Control.Exception
import Control.Tracer
import Data.Text qualified as Text
import Network.HTTP.Types qualified as HTTP
import Network.HTTP2.Server qualified as HTTP2

import Network.GRPC.Common.Exceptions
Expand All @@ -43,8 +49,6 @@ import Network.GRPC.Server.Handler qualified as Handler
import Network.GRPC.Spec
import Network.GRPC.Spec.PseudoHeaders
import Network.GRPC.Spec.RPC.Protobuf (Protobuf)
import Network.GRPC.Util.Session.Server qualified as Server
import Network.GRPC.Spec.Response qualified as Resp

{-------------------------------------------------------------------------------
Server proper
Expand All @@ -66,49 +70,15 @@ handleRequest handlers conn = do
-- TODO: Proper "Apache style" logging (in addition to the debug logging)
traceWith tracer $ Context.NewRequest path

RpcHandler{
handlerMetadata
, handlerRun
} <- getHandler handlers path
mCall :: Either SomeException (Call rpc) <-
try $ acceptCall conn handlerMetadata

case mCall of
Right call -> do
-- TODO: Timeouts
--
-- Wait-for-ready semantics makes this more complicated, maybe.
-- See example in the grpc-repo (python/wait_for_ready).

mErr :: Either SomeException () <- try $ handlerRun call
case mErr of
Right () -> return ()
Left err -> do
-- TODO: We need to think hard about error handling.
--
-- o It should be possible to throw a specific gRPC non-OK status
-- (i.e., we should catch GrpcException and treat it special)
-- o We need to think about how streaming works with trailers, if
-- streaming goes wrong halfway
-- o We need to consider security concerns here, too
-- (exceptions can leak sensitive data)
--
-- gRPC error responses must make use of the gRPC Trailers-Only case
-- according to the spec.
putStrLn $ "Uncaught exception: " ++ show err
putStrLn "(TODO: We need a proper handler here.)"
Left err -> do
traceWith tracer $ Context.AcceptCallFailed err
Server.respond (Connection.connectionToClient conn) $
HTTP2.responseNoBody
HTTP.ok200 -- gRPC uses HTTP 200 even when there are gRPC errors
(Resp.buildTrailersOnly $ TrailersOnly $ ProperTrailers {
trailerGrpcStatus = GrpcError GrpcUnknown
-- TODO: Potential security concern here
-- (showing the exception)?
, trailerGrpcMessage = Just $ Text.pack $ show err
, trailerMetadata = []
})
RpcHandler handler <- getHandler handlers path
call <- acceptCall conn

-- TODO: Timeouts
--
-- Wait-for-ready semantics makes this more complicated, maybe.
-- See example in the grpc-repo (python/wait_for_ready).

handle (forwardException call) $ handler call
where
path :: Path
path = Connection.path conn
Expand All @@ -119,6 +89,40 @@ handleRequest handlers conn = do
$ Context.params
$ Connection.context conn

-- | Forward exception to the client
--
-- If the handler throws an exception, attempt to forward it to the client so
-- that it is notified something went wrong. This is a best-effort only:
--
-- * The nature of the exception might mean that we we cannot send anything to
-- the client at all.
-- * It is possible the exception was thrown /after/ the handler already send
-- the trailers to the client.
--
-- We therefore catch and suppress all exceptions here.
forwardException :: Call rpc -> SomeException -> IO ()
forwardException call err =
handle ignoreExceptions $
sendTrailers call trailers
where
trailers :: ProperTrailers
trailers
| Just (err' :: GrpcException) <- fromException err
= grpcExceptionToTrailers err'

-- TODO: There might be a security concern here (server-side exceptions
-- could potentially leak some sensitive data).
| otherwise
= ProperTrailers {
trailerGrpcStatus = GrpcError GrpcUnknown
, trailerGrpcMessage = Just $ Text.pack $ show err
, trailerMetadata = []
}

-- See discussion above.
ignoreExceptions :: SomeException -> IO ()
ignoreExceptions _ = return ()

{-------------------------------------------------------------------------------
Get handler for the request
-------------------------------------------------------------------------------}
Expand Down
Loading

0 comments on commit f3b8993

Please sign in to comment.