Improve call-related code (#14)

* projections from CallDetails

* refactor Call, refactor clientRegisteredRequest, handle null error

* split ServerCall into separate reg/unreg types

* pass method name to unreg call handler, finish destroyServerUnregCall
This commit is contained in:
Connor Clark 2016-06-02 08:46:20 -07:00
parent e039adc2b7
commit 091bf4a457
11 changed files with 324 additions and 201 deletions

View file

@ -359,3 +359,15 @@ grpc_call* grpc_channel_create_registered_call_(
propagation_mask, completion_queue, registered_call_handle, propagation_mask, completion_queue, registered_call_handle,
*deadline, reserved); *deadline, reserved);
} }
char* call_details_get_method(grpc_call_details* details){
return details->method;
}
char* call_details_get_host(grpc_call_details* details){
return details->host;
}
gpr_timespec* call_details_get_deadline(grpc_call_details* details){
return &(details->deadline);
}

View file

@ -123,4 +123,10 @@ grpc_call* grpc_channel_create_registered_call_(
grpc_completion_queue *completion_queue, void *registered_call_handle, grpc_completion_queue *completion_queue, void *registered_call_handle,
gpr_timespec *deadline, void *reserved); gpr_timespec *deadline, void *reserved);
char* call_details_get_method(grpc_call_details* details);
char* call_details_get_host(grpc_call_details* details);
gpr_timespec* call_details_get_deadline(grpc_call_details* details);
#endif //GRPC_HASKELL #endif //GRPC_HASKELL

View file

@ -21,22 +21,24 @@ GRPC
-- * Calls -- * Calls
, GRPCMethodType(..) , GRPCMethodType(..)
, RegisteredMethod , RegisteredMethod
, Call
, NormalRequestResult(..) , NormalRequestResult(..)
-- * Server -- * Server
, ServerConfig(..) , ServerConfig(..)
, Server , Server
, ServerRegCall
, ServerUnregCall
, registeredMethods , registeredMethods
, withServer , withServer
, serverHandleNormalRegisteredCall , serverHandleNormalRegisteredCall
, serverHandleNormalCall , serverHandleNormalCall
, withServerCall , withServerUnregCall
, withServerRegisteredCall , withServerRegisteredCall
-- * Client -- * Client
, ClientConfig(..) , ClientConfig(..)
, Client , Client
, ClientCall
, withClient , withClient
, clientRegisterMethod , clientRegisterMethod
, clientRegisteredRequest , clientRegisteredRequest
@ -44,7 +46,9 @@ GRPC
, withClientCall , withClientCall
-- * Ops -- * Ops
, runOps , runClientOps
, runServerRegOps
, runServerUnregOps
, Op(..) , Op(..)
, OpRecvResult(..) , OpRecvResult(..)
, StatusDetails(..) , StatusDetails(..)

View file

@ -4,9 +4,10 @@
module Network.GRPC.LowLevel.Call where module Network.GRPC.LowLevel.Call where
import Control.Monad import Control.Monad
import Data.ByteString (ByteString)
import Data.String (IsString) import Data.String (IsString)
import Foreign.Marshal.Alloc (free) import Foreign.Marshal.Alloc (free)
import Foreign.Ptr (Ptr, castPtr) import Foreign.Ptr (Ptr, nullPtr)
import Foreign.Storable (peek) import Foreign.Storable (peek)
import qualified Network.GRPC.Unsafe as C import qualified Network.GRPC.Unsafe as C
@ -14,7 +15,7 @@ import qualified Network.GRPC.Unsafe.Time as C
import qualified Network.GRPC.Unsafe.Metadata as C import qualified Network.GRPC.Unsafe.Metadata as C
import qualified Network.GRPC.Unsafe.ByteBuffer as C import qualified Network.GRPC.Unsafe.ByteBuffer as C
import Network.GRPC.LowLevel.GRPC (grpcDebug) import Network.GRPC.LowLevel.GRPC (grpcDebug, MetadataMap)
-- | Models the four types of RPC call supported by gRPC. We currently only -- | Models the four types of RPC call supported by gRPC. We currently only
-- support the first alternative, and only in a preliminary fashion. -- support the first alternative, and only in a preliminary fashion.
@ -38,78 +39,141 @@ data RegisteredMethod = RegisteredMethod {methodType :: GRPCMethodType,
methodHost :: Host, methodHost :: Host,
methodHandle :: C.CallHandle} methodHandle :: C.CallHandle}
-- | Represents one GRPC call (i.e. request). This type is used on both the -- | Represents one GRPC call (i.e. request) on the client.
-- client and server. Contains pointers to all the necessary C state needed to
-- send and respond to a call.
-- This is used to associate send/receive 'Op's with a request. -- This is used to associate send/receive 'Op's with a request.
-- There are separate functions for creating these depending on whether the data ClientCall = ClientCall {internalClientCall :: C.Call}
-- method is registered and whether the call is on the client or server side.
data Call = ClientCall {internalCall :: C.Call}
| ServerCall
{internalCall :: C.Call,
requestMetadataRecv :: (Ptr C.MetadataArray),
optionalPayload :: Maybe (Ptr C.ByteBuffer),
parentPtr :: Maybe (Ptr C.Call),
callDetails :: Maybe (C.CallDetails),
-- ^ used on the server for non-registered calls
--, to identify the endpoint being used.
callDeadline :: Maybe C.CTimeSpecPtr
}
debugCall :: Call -> IO () -- | Represents one registered GRPC call on the server.
-- Contains pointers to all the C state needed to respond to a registered call.
data ServerRegCall = ServerRegCall
{internalServerRegCall :: C.Call,
requestMetadataRecvReg :: Ptr C.MetadataArray,
optionalPayload :: Ptr C.ByteBuffer,
parentPtrReg :: Maybe (Ptr C.Call),
callDeadline :: C.CTimeSpecPtr
}
serverRegCallGetMetadata :: ServerRegCall -> IO MetadataMap
serverRegCallGetMetadata ServerRegCall{..} = do
marray <- peek requestMetadataRecvReg
C.getAllMetadataArray marray
-- | Extract the client request body from the given registered call, if present.
-- TODO: the reason this returns @Maybe ByteString@ is because the gRPC library
-- calls the underlying out parameter "optional_payload". I am not sure exactly
-- in what cases it won't be present.
serverRegCallGetPayload :: ServerRegCall -> IO (Maybe ByteString)
serverRegCallGetPayload ServerRegCall{..} = do
bb@(C.ByteBuffer rawPtr) <- peek optionalPayload
if rawPtr == nullPtr
then return Nothing
else Just <$> C.copyByteBufferToByteString bb
-- | Represents one unregistered GRPC call on the server.
-- Contains pointers to all the C state needed to respond to an unregistered
-- call.
data ServerUnregCall = ServerUnregCall
{internalServerUnregCall :: C.Call,
requestMetadataRecvUnreg :: Ptr C.MetadataArray,
parentPtrUnreg :: Maybe (Ptr C.Call),
callDetails :: C.CallDetails}
serverUnregCallGetMetadata :: ServerUnregCall -> IO MetadataMap
serverUnregCallGetMetadata ServerUnregCall{..} = do
marray <- peek requestMetadataRecvUnreg
C.getAllMetadataArray marray
serverUnregCallGetMethodName :: ServerUnregCall -> IO MethodName
serverUnregCallGetMethodName ServerUnregCall{..} =
MethodName <$> C.callDetailsGetMethod callDetails
debugClientCall :: ClientCall -> IO ()
{-# INLINE debugClientCall #-}
#ifdef DEBUG #ifdef DEBUG
debugCall (ClientCall (C.Call ptr)) = debugClientCall (ClientCall (C.Call ptr)) =
grpcDebug $ "debugCall: client call: " ++ (show ptr) grpcDebug $ "debugCall: client call: " ++ (show ptr)
debugCall call@(ServerCall (C.Call ptr) _ _ _ _ _) = do
grpcDebug $ "debugCall: server call: " ++ (show ptr)
grpcDebug $ "debugCall: metadata ptr: " ++ show (requestMetadataRecv call)
metadataArr <- peek (requestMetadataRecv call)
metadata <- C.getAllMetadataArray metadataArr
grpcDebug $ "debugCall: metadata received: " ++ (show metadata)
forM_ (optionalPayload call) $ \payloadPtr -> do
grpcDebug $ "debugCall: payload ptr: " ++ show payloadPtr
payload <- peek payloadPtr
bs <- C.copyByteBufferToByteString payload
grpcDebug $ "debugCall: payload contents: " ++ show bs
forM_ (parentPtr call) $ \parentPtr' -> do
grpcDebug $ "debugCall: parent ptr: " ++ show parentPtr'
(C.Call parent) <- peek parentPtr'
grpcDebug $ "debugCall: parent: " ++ show parent
forM_ (callDetails call) $ \(C.CallDetails callDetailsPtr) -> do
grpcDebug $ "debugCall: callDetails ptr: " ++ show callDetailsPtr
--TODO: need functions for getting data out of call_details.
forM_ (callDeadline call) $ \timespecptr -> do
grpcDebug $ "debugCall: deadline ptr: " ++ show timespecptr
timespec <- peek timespecptr
grpcDebug $ "debugCall: deadline: " ++ show (C.timeSpec timespec)
#else #else
{-# INLINE debugCall #-} debugClientCall = const $ return ()
debugCall = const $ return ()
#endif #endif
-- | Destroys a 'Call'. debugServerRegCall :: ServerRegCall -> IO ()
destroyCall :: Call -> IO () #ifdef DEBUG
destroyCall ClientCall{..} = do debugServerRegCall call@(ServerRegCall (C.Call ptr) _ _ _ _) = do
grpcDebug "Destroying client-side call object." grpcDebug $ "debugServerRegCall: server call: " ++ (show ptr)
C.grpcCallDestroy internalCall grpcDebug $ "debugServerRegCall: metadata ptr: "
destroyCall call@ServerCall{..} = do ++ show (requestMetadataRecvReg call)
grpcDebug "destroyCall: entered." metadataArr <- peek (requestMetadataRecvReg call)
debugCall call metadata <- C.getAllMetadataArray metadataArr
grpcDebug $ "Destroying server-side call object: " ++ show internalCall grpcDebug $ "debugServerRegCall: metadata received: " ++ (show metadata)
C.grpcCallDestroy internalCall grpcDebug $ "debugServerRegCall: payload ptr: " ++ show (optionalPayload call)
grpcDebug $ "destroying metadata array: " ++ show requestMetadataRecv payload <- peek (optionalPayload call)
C.metadataArrayDestroy requestMetadataRecv bs <- C.copyByteBufferToByteString payload
grpcDebug $ "destroying optional payload" ++ show optionalPayload grpcDebug $ "debugServerRegCall: payload contents: " ++ show bs
forM_ optionalPayload C.destroyReceivingByteBuffer forM_ (parentPtrReg call) $ \parentPtr' -> do
grpcDebug $ "freeing parentPtr: " ++ show parentPtr grpcDebug $ "debugServerRegCall: parent ptr: " ++ show parentPtr'
forM_ parentPtr free (C.Call parent) <- peek parentPtr'
grpcDebug $ "destroying call details" ++ show callDetails grpcDebug $ "debugServerRegCall: parent: " ++ show parent
forM_ callDetails C.destroyCallDetails grpcDebug $ "debugServerRegCall: deadline ptr: " ++ show (callDeadline call)
grpcDebug $ "destroying deadline." ++ show callDeadline timespec <- peek (callDeadline call)
forM_ callDeadline C.timespecDestroy grpcDebug $ "debugServerRegCall: deadline: " ++ show (C.timeSpec timespec)
#else
{-# INLINE debugServerRegCall #-}
debugServerRegCall = const $ return ()
#endif
_nowarn_unused :: a debugServerUnregCall :: ServerUnregCall -> IO ()
_nowarn_unused = #ifdef DEBUG
castPtr `undefined` debugServerUnregCall call@(ServerUnregCall (C.Call ptr) _ _ _) = do
(peek :: Ptr Int -> IO Int) `undefined` grpcDebug $ "debugServerUnregCall: server call: " ++ (show ptr)
() grpcDebug $ "debugServerUnregCall: metadata ptr: "
++ show (requestMetadataRecvUnreg call)
metadataArr <- peek (requestMetadataRecvUnreg call)
metadata <- C.getAllMetadataArray metadataArr
grpcDebug $ "debugServerUnregCall: metadata received: " ++ (show metadata)
forM_ (parentPtrUnreg call) $ \parentPtr' -> do
grpcDebug $ "debugServerRegCall: parent ptr: " ++ show parentPtr'
(C.Call parent) <- peek parentPtr'
grpcDebug $ "debugServerRegCall: parent: " ++ show parent
grpcDebug $ "debugServerUnregCall: callDetails ptr: "
++ show (callDetails call)
--TODO: need functions for getting data out of call_details.
#else
{-# INLINE debugServerUnregCall #-}
debugServerUnregCall = const $ return ()
#endif
destroyClientCall :: ClientCall -> IO ()
destroyClientCall ClientCall{..} = do
grpcDebug "Destroying client-side call object."
C.grpcCallDestroy internalClientCall
destroyServerRegCall :: ServerRegCall -> IO ()
destroyServerRegCall call@ServerRegCall{..} = do
grpcDebug "destroyServerRegCall: entered."
debugServerRegCall call
grpcDebug $ "Destroying server-side call object: "
++ show internalServerRegCall
C.grpcCallDestroy internalServerRegCall
grpcDebug $ "destroying metadata array: " ++ show requestMetadataRecvReg
C.metadataArrayDestroy requestMetadataRecvReg
grpcDebug $ "destroying optional payload" ++ show optionalPayload
C.destroyReceivingByteBuffer optionalPayload
grpcDebug $ "freeing parentPtr: " ++ show parentPtrReg
forM_ parentPtrReg free
grpcDebug $ "destroying deadline." ++ show callDeadline
C.timespecDestroy callDeadline
destroyServerUnregCall :: ServerUnregCall -> IO ()
destroyServerUnregCall call@ServerUnregCall{..} = do
grpcDebug "destroyServerUnregCall: entered."
debugServerUnregCall call
grpcDebug $ "Destroying server-side call object: "
++ show internalServerUnregCall
C.grpcCallDestroy internalServerUnregCall
grpcDebug $ "destroying metadata array: " ++ show requestMetadataRecvUnreg
C.metadataArrayDestroy requestMetadataRecvUnreg
grpcDebug $ "freeing parentPtrUnreg: " ++ show parentPtrUnreg
forM_ parentPtrUnreg free
grpcDebug $ "destroying call details: " ++ show callDetails
C.destroyCallDetails callDetails

View file

@ -3,6 +3,7 @@
module Network.GRPC.LowLevel.Client where module Network.GRPC.LowLevel.Client where
import Control.Exception (bracket, finally) import Control.Exception (bracket, finally)
import Control.Monad (join)
import Data.ByteString (ByteString) import Data.ByteString (ByteString)
import Foreign.Ptr (nullPtr) import Foreign.Ptr (nullPtr)
import qualified Network.GRPC.Unsafe as C import qualified Network.GRPC.Unsafe as C
@ -63,7 +64,7 @@ clientRegisterMethod _ _ _ _ = error "Streaming methods not yet implemented."
-- Returns 'Left' if the CQ is shutting down or if the job to create a call -- Returns 'Left' if the CQ is shutting down or if the job to create a call
-- timed out. -- timed out.
clientCreateRegisteredCall :: Client -> RegisteredMethod -> TimeoutSeconds clientCreateRegisteredCall :: Client -> RegisteredMethod -> TimeoutSeconds
-> IO (Either GRPCIOError Call) -> IO (Either GRPCIOError ClientCall)
clientCreateRegisteredCall Client{..} RegisteredMethod{..} timeout = do clientCreateRegisteredCall Client{..} RegisteredMethod{..} timeout = do
let parentCall = C.Call nullPtr --Unsure what this does. null is safe, though. let parentCall = C.Call nullPtr --Unsure what this does. null is safe, though.
C.withDeadlineSeconds timeout $ \deadline -> do C.withDeadlineSeconds timeout $ \deadline -> do
@ -74,7 +75,7 @@ clientCreateRegisteredCall Client{..} RegisteredMethod{..} timeout = do
-- by switching to ExceptT IO. -- by switching to ExceptT IO.
-- | Handles safe creation and cleanup of a client call -- | Handles safe creation and cleanup of a client call
withClientRegisteredCall :: Client -> RegisteredMethod -> TimeoutSeconds withClientRegisteredCall :: Client -> RegisteredMethod -> TimeoutSeconds
-> (Call -> (ClientCall
-> IO (Either GRPCIOError a)) -> IO (Either GRPCIOError a))
-> IO (Either GRPCIOError a) -> IO (Either GRPCIOError a)
withClientRegisteredCall client regmethod timeout f = do withClientRegisteredCall client regmethod timeout f = do
@ -83,7 +84,7 @@ withClientRegisteredCall client regmethod timeout f = do
Left x -> return $ Left x Left x -> return $ Left x
Right call -> f call `finally` logDestroy call Right call -> f call `finally` logDestroy call
where logDestroy c = grpcDebug "withClientRegisteredCall: destroying." where logDestroy c = grpcDebug "withClientRegisteredCall: destroying."
>> destroyCall c >> destroyClientCall c
-- | Create a call on the client for an endpoint without using the -- | Create a call on the client for an endpoint without using the
-- method registration machinery. In practice, we'll probably only use the -- method registration machinery. In practice, we'll probably only use the
@ -94,7 +95,7 @@ clientCreateCall :: Client
-> Host -> Host
-- ^ The host. -- ^ The host.
-> TimeoutSeconds -> TimeoutSeconds
-> IO (Either GRPCIOError Call) -> IO (Either GRPCIOError ClientCall)
clientCreateCall Client{..} method host timeout = do clientCreateCall Client{..} method host timeout = do
let parentCall = C.Call nullPtr let parentCall = C.Call nullPtr
C.withDeadlineSeconds timeout $ \deadline -> do C.withDeadlineSeconds timeout $ \deadline -> do
@ -102,7 +103,7 @@ clientCreateCall Client{..} method host timeout = do
clientCQ method host deadline clientCQ method host deadline
withClientCall :: Client -> MethodName -> Host -> TimeoutSeconds withClientCall :: Client -> MethodName -> Host -> TimeoutSeconds
-> (Call -> IO (Either GRPCIOError a)) -> (ClientCall -> IO (Either GRPCIOError a))
-> IO (Either GRPCIOError a) -> IO (Either GRPCIOError a)
withClientCall client method host timeout f = do withClientCall client method host timeout f = do
createResult <- clientCreateCall client method host timeout createResult <- clientCreateCall client method host timeout
@ -110,7 +111,7 @@ withClientCall client method host timeout f = do
Left x -> return $ Left x Left x -> return $ Left x
Right call -> f call `finally` logDestroy call Right call -> f call `finally` logDestroy call
where logDestroy c = grpcDebug "withClientCall: destroying." where logDestroy c = grpcDebug "withClientCall: destroying."
>> destroyCall c >> destroyClientCall c
data NormalRequestResult = NormalRequestResult data NormalRequestResult = NormalRequestResult
ByteString ByteString
@ -121,26 +122,25 @@ data NormalRequestResult = NormalRequestResult
deriving (Show, Eq) deriving (Show, Eq)
-- | Function for assembling call result when the 'MethodType' is 'Normal'. -- | Function for assembling call result when the 'MethodType' is 'Normal'.
compileNormalRequestResults :: [OpRecvResult] -> NormalRequestResult compileNormalRequestResults :: [OpRecvResult]
-> Either GRPCIOError NormalRequestResult
compileNormalRequestResults compileNormalRequestResults
--TODO: consider using more precise type instead of match.
-- Whether we do so depends on whether this layer of abstraction is supposed
-- to be a safe interface to the gRPC C core library, or something that makes
-- core use cases easy.
[OpRecvInitialMetadataResult m, [OpRecvInitialMetadataResult m,
OpRecvMessageResult body, OpRecvMessageResult (Just body),
OpRecvStatusOnClientResult m2 status details] OpRecvStatusOnClientResult m2 status details]
= NormalRequestResult body (Just m) m2 status (StatusDetails details) = Right $ NormalRequestResult body (Just m) m2 status
(StatusDetails details)
-- TODO: it seems registered request responses on the server -- TODO: it seems registered request responses on the server
-- don't send initial metadata. Hence the 'Maybe'. Investigate. -- don't send initial metadata. Hence the 'Maybe'. Investigate.
compileNormalRequestResults compileNormalRequestResults
[OpRecvMessageResult body, [OpRecvMessageResult (Just body),
OpRecvStatusOnClientResult m2 status details] OpRecvStatusOnClientResult m2 status details]
= NormalRequestResult body Nothing m2 status (StatusDetails details) = Right $ NormalRequestResult body Nothing m2 status (StatusDetails details)
compileNormalRequestResults _ = compileNormalRequestResults x =
--TODO: impossible case should be enforced by more precise types. case extractStatus x of
error "non-normal request input to compileNormalRequestResults." Nothing -> Left GRPCIOUnknownError
Just (OpRecvStatusOnClientResult _ status details) ->
Left (GRPCIOBadStatusCode status (StatusDetails details))
-- | Make a request of the given method with the given body. Returns the -- | Make a request of the given method with the given body. Returns the
-- server's response. TODO: This is preliminary until we figure out how many -- server's response. TODO: This is preliminary until we figure out how many
@ -162,37 +162,28 @@ clientRegisteredRequest :: Client
-> IO (Either GRPCIOError NormalRequestResult) -> IO (Either GRPCIOError NormalRequestResult)
clientRegisteredRequest client@(Client{..}) rm@(RegisteredMethod{..}) clientRegisteredRequest client@(Client{..}) rm@(RegisteredMethod{..})
timeLimit body meta = timeLimit body meta =
case methodType of fmap join $ case methodType of
Normal -> withClientRegisteredCall client rm timeLimit $ \call -> do Normal -> withClientRegisteredCall client rm timeLimit $ \call -> do
grpcDebug "clientRegisteredRequest: created call." grpcDebug "clientRegisteredRequest: created call."
debugCall call debugClientCall call
--TODO: doing one op at a time to debug. Some were hanging. -- NOTE: sendOps and recvOps *must* be in separate batches or
let op1 = [OpSendInitialMetadata meta] -- the client hangs when the server can't be reached.
res1 <- runOps call clientCQ op1 timeLimit let sendOps = [OpSendInitialMetadata meta
grpcDebug $ "finished res1: " ++ show res1 , OpSendMessage body
let op2 = [OpSendMessage body] , OpSendCloseFromClient]
res2 <- runOps call clientCQ op2 timeLimit sendRes <- runClientOps call clientCQ sendOps timeLimit
grpcDebug $ "finished res2: " ++ show res2 case sendRes of
let op3 = [OpSendCloseFromClient] Left x -> do grpcDebug "clientRegisteredRequest: batch error."
res3 <- runOps call clientCQ op3 timeLimit return $ Left x
grpcDebug $ "finished res3: " ++ show res3 Right rs -> do
let op4 = [OpRecvMessage] let recvOps = [OpRecvMessage, OpRecvStatusOnClient]
res4 <- runOps call clientCQ op4 timeLimit recvRes <- runClientOps call clientCQ recvOps timeLimit
grpcDebug $ "finished res4: " ++ show res4 case recvRes of
let op5 = [OpRecvStatusOnClient] Left x -> do
res5 <- runOps call clientCQ op5 timeLimit grpcDebug "clientRegisteredRequest: batch error."
grpcDebug $ "finished res5: " ++ show res5 return $ Left x
let results = do Right rs' -> do
r1 <- res1 return $ Right $ compileNormalRequestResults (rs ++ rs')
r2 <- res2
r3 <- res3
r4 <- res4
r5 <- res5
return $ r1 ++ r2 ++ r3 ++ r4 ++ r5
case results of
Left x -> return $ Left x
Right rs -> return $
Right $ compileNormalRequestResults rs
_ -> error "Streaming methods not yet implemented." _ -> error "Streaming methods not yet implemented."
-- | Makes a normal (non-streaming) request without needing to register a method -- | Makes a normal (non-streaming) request without needing to register a method
@ -210,16 +201,16 @@ clientRequest :: Client
-- ^ Request metadata. -- ^ Request metadata.
-> IO (Either GRPCIOError NormalRequestResult) -> IO (Either GRPCIOError NormalRequestResult)
clientRequest client@(Client{..}) (MethodName method) (Host host) clientRequest client@(Client{..}) (MethodName method) (Host host)
timeLimit body meta = do timeLimit body meta =
fmap join $
withClientCall client (MethodName method) (Host host) timeLimit $ \call -> do withClientCall client (MethodName method) (Host host) timeLimit $ \call -> do
let ops = clientNormalRequestOps body meta let ops = clientNormalRequestOps body meta
results <- runOps call clientCQ ops timeLimit results <- runClientOps call clientCQ ops timeLimit
grpcDebug "clientRequest: ops ran." grpcDebug "clientRequest: ops ran."
case results of case results of
Left x -> return $ Left x Left x -> return $ Left x
Right rs -> return $ Right $ compileNormalRequestResults rs Right rs -> return $ Right $ compileNormalRequestResults rs
clientNormalRequestOps :: ByteString -> MetadataMap -> [Op] clientNormalRequestOps :: ByteString -> MetadataMap -> [Op]
clientNormalRequestOps body metadata = clientNormalRequestOps body metadata =
[OpSendInitialMetadata metadata, [OpSendInitialMetadata metadata,

View file

@ -224,7 +224,8 @@ shutdownCompletionQueue (CompletionQueue{..}) = do
channelCreateRegisteredCall :: C.Channel -> C.Call -> C.PropagationMask channelCreateRegisteredCall :: C.Channel -> C.Call -> C.PropagationMask
-> CompletionQueue -> C.CallHandle -> CompletionQueue -> C.CallHandle
-> C.CTimeSpecPtr -> IO (Either GRPCIOError Call) -> C.CTimeSpecPtr
-> IO (Either GRPCIOError ClientCall)
channelCreateRegisteredCall channelCreateRegisteredCall
chan parent mask cq@CompletionQueue{..} handle deadline = chan parent mask cq@CompletionQueue{..} handle deadline =
withPermission Push cq $ do withPermission Push cq $ do
@ -238,7 +239,7 @@ channelCreateRegisteredCall
channelCreateCall :: C.Channel -> C.Call -> C.PropagationMask -> CompletionQueue channelCreateCall :: C.Channel -> C.Call -> C.PropagationMask -> CompletionQueue
-> MethodName -> Host -> C.CTimeSpecPtr -> MethodName -> Host -> C.CTimeSpecPtr
-> IO (Either GRPCIOError Call) -> IO (Either GRPCIOError ClientCall)
channelCreateCall channelCreateCall
chan parent mask cq@CompletionQueue{..} (MethodName methodName) (Host host) chan parent mask cq@CompletionQueue{..} (MethodName methodName) (Host host)
deadline = deadline =
@ -250,7 +251,7 @@ channelCreateCall
-- | Create the call object to handle a registered call. -- | Create the call object to handle a registered call.
serverRequestRegisteredCall :: C.Server -> CompletionQueue -> TimeoutSeconds serverRequestRegisteredCall :: C.Server -> CompletionQueue -> TimeoutSeconds
-> RegisteredMethod -> RegisteredMethod
-> IO (Either GRPCIOError Call) -> IO (Either GRPCIOError ServerRegCall)
serverRequestRegisteredCall serverRequestRegisteredCall
server cq@CompletionQueue{..} timeLimit RegisteredMethod{..} = server cq@CompletionQueue{..} timeLimit RegisteredMethod{..} =
withPermission Push cq $ do withPermission Push cq $ do
@ -280,9 +281,8 @@ serverRequestRegisteredCall
return $ Left x return $ Left x
Right () -> do Right () -> do
rawCall <- peek callPtr rawCall <- peek callPtr
let assembledCall = ServerCall rawCall metadataArrayPtr let assembledCall = ServerRegCall rawCall metadataArrayPtr
(Just bbPtr) Nothing Nothing bbPtr Nothing deadline
(Just deadline)
return $ Right assembledCall return $ Right assembledCall
-- TODO: see TODO for failureCleanup in serverRequestCall. -- TODO: see TODO for failureCleanup in serverRequestCall.
where failureCleanup deadline callPtr metadataArrayPtr bbPtr = forkIO $ do where failureCleanup deadline callPtr metadataArrayPtr bbPtr = forkIO $ do
@ -294,7 +294,7 @@ serverRequestRegisteredCall
free bbPtr free bbPtr
serverRequestCall :: C.Server -> CompletionQueue -> TimeoutSeconds serverRequestCall :: C.Server -> CompletionQueue -> TimeoutSeconds
-> IO (Either GRPCIOError Call) -> IO (Either GRPCIOError ServerUnregCall)
serverRequestCall server cq@CompletionQueue{..} timeLimit = serverRequestCall server cq@CompletionQueue{..} timeLimit =
withPermission Push cq $ do withPermission Push cq $ do
callPtr <- malloc callPtr <- malloc
@ -321,12 +321,10 @@ serverRequestCall server cq@CompletionQueue{..} timeLimit =
return $ Left x return $ Left x
Right () -> do Right () -> do
rawCall <- peek callPtr rawCall <- peek callPtr
let call = ServerCall rawCall let call = ServerUnregCall rawCall
metadataArrayPtr metadataArrayPtr
Nothing Nothing
Nothing callDetails
(Just callDetails)
Nothing
return $ Right call return $ Right call
--TODO: the gRPC library appears to hold onto these pointers for a random --TODO: the gRPC library appears to hold onto these pointers for a random

View file

@ -10,12 +10,20 @@ import Control.Monad.Except (ExceptT(..), runExceptT, throwError,
MonadError) MonadError)
-} -}
import Control.Exception import Control.Exception
import qualified Data.ByteString as B
import qualified Data.Map as M
import Data.String (IsString)
import qualified Network.GRPC.Unsafe as C import qualified Network.GRPC.Unsafe as C
import qualified Network.GRPC.Unsafe.Op as C
#ifdef DEBUG #ifdef DEBUG
import GHC.Conc (myThreadId) import GHC.Conc (myThreadId)
#endif #endif
type MetadataMap = M.Map B.ByteString B.ByteString
newtype StatusDetails = StatusDetails B.ByteString deriving (Show, Eq, IsString)
-- | Functions as a proof that the gRPC core has been started. The gRPC core -- | Functions as a proof that the gRPC core has been started. The gRPC core
-- must be initialized to create any gRPC state, so this is a requirement for -- must be initialized to create any gRPC state, so this is a requirement for
-- the server and client create/start functions. -- the server and client create/start functions.
@ -39,6 +47,7 @@ data GRPCIOError = GRPCIOCallError C.CallError
-- ^ Thrown if a 'CompletionQueue' fails to shut down in a -- ^ Thrown if a 'CompletionQueue' fails to shut down in a
-- reasonable amount of time. -- reasonable amount of time.
| GRPCIOUnknownError | GRPCIOUnknownError
| GRPCIOBadStatusCode C.StatusCode StatusDetails
deriving (Show, Eq) deriving (Show, Eq)
throwIfCallError :: C.CallError -> Either GRPCIOError () throwIfCallError :: C.CallError -> Either GRPCIOError ()

View file

@ -14,7 +14,7 @@ import Foreign.Marshal.Alloc (free, malloc,
mallocBytes) mallocBytes)
import Foreign.Ptr (Ptr, nullPtr) import Foreign.Ptr (Ptr, nullPtr)
import Foreign.Storable (peek, poke) import Foreign.Storable (peek, poke)
import qualified Network.GRPC.Unsafe as C () import qualified Network.GRPC.Unsafe as C (Call)
import qualified Network.GRPC.Unsafe.ByteBuffer as C import qualified Network.GRPC.Unsafe.ByteBuffer as C
import qualified Network.GRPC.Unsafe.Metadata as C import qualified Network.GRPC.Unsafe.Metadata as C
import qualified Network.GRPC.Unsafe.Op as C import qualified Network.GRPC.Unsafe.Op as C
@ -23,10 +23,6 @@ import Network.GRPC.LowLevel.Call
import Network.GRPC.LowLevel.CompletionQueue import Network.GRPC.LowLevel.CompletionQueue
import Network.GRPC.LowLevel.GRPC import Network.GRPC.LowLevel.GRPC
type MetadataMap = M.Map B.ByteString B.ByteString
newtype StatusDetails = StatusDetails B.ByteString deriving (Show, Eq, IsString)
-- | Sum describing all possible send and receive operations that can be batched -- | Sum describing all possible send and receive operations that can be batched
-- and executed by gRPC. Usually these are processed in a handful of -- and executed by gRPC. Usually these are processed in a handful of
-- combinations depending on the 'MethodType' of the call being run. -- combinations depending on the 'MethodType' of the call being run.
@ -146,7 +142,9 @@ withOpArray n = bracket (C.opArrayCreate n)
-- | Container holding GC-managed results for 'Op's which receive data. -- | Container holding GC-managed results for 'Op's which receive data.
data OpRecvResult = data OpRecvResult =
OpRecvInitialMetadataResult MetadataMap OpRecvInitialMetadataResult MetadataMap
| OpRecvMessageResult B.ByteString | OpRecvMessageResult (Maybe B.ByteString)
-- ^ If the client or server dies, we might not receive a response body, in
-- which case this will be 'Nothing'.
| OpRecvStatusOnClientResult MetadataMap C.StatusCode B.ByteString | OpRecvStatusOnClientResult MetadataMap C.StatusCode B.ByteString
| OpRecvCloseOnServerResult Bool -- ^ True if call was cancelled. | OpRecvCloseOnServerResult Bool -- ^ True if call was cancelled.
deriving (Eq, Show) deriving (Eq, Show)
@ -162,11 +160,12 @@ resultFromOpContext (OpRecvInitialMetadataContext pmetadata) = do
return $ Just $ OpRecvInitialMetadataResult metadataMap return $ Just $ OpRecvInitialMetadataResult metadataMap
resultFromOpContext (OpRecvMessageContext pbb) = do resultFromOpContext (OpRecvMessageContext pbb) = do
grpcDebug "resultFromOpContext: OpRecvMessageContext" grpcDebug "resultFromOpContext: OpRecvMessageContext"
bb <- peek pbb bb@(C.ByteBuffer bbptr) <- peek pbb
grpcDebug "resultFromOpContext: bytebuffer peeked." if bbptr == nullPtr
bs <- C.copyByteBufferToByteString bb then return $ Just $ OpRecvMessageResult Nothing
grpcDebug "resultFromOpContext: bb copied." else do bs <- C.copyByteBufferToByteString bb
return $ Just $ OpRecvMessageResult bs grpcDebug "resultFromOpContext: bb copied."
return $ Just $ OpRecvMessageResult (Just bs)
resultFromOpContext (OpRecvStatusOnClientContext pmetadata pcode pstr) = do resultFromOpContext (OpRecvStatusOnClientContext pmetadata pcode pstr) = do
grpcDebug "resultFromOpContext: OpRecvStatusOnClientContext" grpcDebug "resultFromOpContext: OpRecvStatusOnClientContext"
metadata <- peek pmetadata metadata <- peek pmetadata
@ -186,23 +185,18 @@ resultFromOpContext _ = do
--TODO: the list of 'Op's type is less specific than it could be. There are only --TODO: the list of 'Op's type is less specific than it could be. There are only
-- a few different sequences of 'Op's we will see in practice. Once we figure -- a few different sequences of 'Op's we will see in practice. Once we figure
-- out what those are, we should create a more specific sum type. This will also -- out what those are, we should create a more specific sum type. However, since
-- allow us to make a more specific sum type to replace @[OpRecvResult]@, too. -- ops can fail, the list of 'OpRecvResult' returned by 'runOps' can vary in
-- their contents and are perhaps less amenable to simplification.
-- In the meantime, from looking at the core tests, it looks like it is safe to
-- say that we always get a GRPC_CALL_ERROR_TOO_MANY_OPERATIONS error if we use
-- the same 'Op' twice in the same batch, so we might want to change the list to
-- a set. I don't think order matters within a batch. Need to check.
-- | For a given call, run the given 'Op's on the given completion queue with runOps :: C.Call
-- the given tag. Blocks until the ops are complete or the given number of
-- seconds have elapsed.
runOps :: Call
-- ^ 'Call' that this batch is associated with. One call can be
-- associated with many batches.
-> CompletionQueue -> CompletionQueue
-- ^ Queue on which our tag will be placed once our ops are done
-- running.
-> [Op] -> [Op]
-> TimeoutSeconds -> TimeoutSeconds
-- ^ How long to block waiting for the tag to appear on the queue.
-- If we time out, the result of this action will be
-- @CallBatchError BatchTimeout@.
-> IO (Either GRPCIOError [OpRecvResult]) -> IO (Either GRPCIOError [OpRecvResult])
runOps call cq ops timeLimit = runOps call cq ops timeLimit =
let l = length ops in let l = length ops in
@ -212,7 +206,7 @@ runOps call cq ops timeLimit =
grpcDebug $ "runOps: allocated op contexts: " ++ show contexts grpcDebug $ "runOps: allocated op contexts: " ++ show contexts
sequence_ $ zipWith (setOpArray opArray) [0..l-1] contexts sequence_ $ zipWith (setOpArray opArray) [0..l-1] contexts
tag <- newTag cq tag <- newTag cq
callError <- startBatch cq (internalCall call) opArray l tag callError <- startBatch cq call opArray l tag
grpcDebug $ "runOps: called start_batch. callError: " grpcDebug $ "runOps: called start_batch. callError: "
++ (show callError) ++ (show callError)
case callError of case callError of
@ -226,5 +220,44 @@ runOps call cq ops timeLimit =
fmap (Right . catMaybes) $ mapM resultFromOpContext contexts fmap (Right . catMaybes) $ mapM resultFromOpContext contexts
Left err -> return $ Left err Left err -> return $ Left err
_nowarn_unused :: a -- | For a given call, run the given 'Op's on the given completion queue with
_nowarn_unused = undefined nullPtr -- the given tag. Blocks until the ops are complete or the given number of
-- seconds have elapsed.
-- TODO: now that 'ServerRegCall' and 'ServerUnregCall' are separate types, we
-- could try to limit the input 'Op's more appropriately. E.g., we don't use
-- an 'OpRecvInitialMetadata' when receiving a registered call, because gRPC
-- handles that for us.
runServerRegOps :: ServerRegCall
-- ^ 'Call' that this batch is associated with. One call can be
-- associated with many batches.
-> CompletionQueue
-- ^ Queue on which our tag will be placed once our ops are done
-- running.
-> [Op]
-- ^ The list of 'Op's to execute.
-> TimeoutSeconds
-- ^ How long to block waiting for the tag to appear on the
--queue. If we time out, the result of this action will be
-- @CallBatchError BatchTimeout@.
-> IO (Either GRPCIOError [OpRecvResult])
runServerRegOps = runOps . internalServerRegCall
runServerUnregOps :: ServerUnregCall
-> CompletionQueue
-> [Op]
-> TimeoutSeconds
-> IO (Either GRPCIOError [OpRecvResult])
runServerUnregOps = runOps . internalServerUnregCall
-- | Like 'runServerOps', but for client-side calls.
runClientOps :: ClientCall
-> CompletionQueue
-> [Op]
-> TimeoutSeconds
-> IO (Either GRPCIOError [OpRecvResult])
runClientOps = runOps . internalClientCall
extractStatus :: [OpRecvResult] -> Maybe OpRecvResult
extractStatus [] = Nothing
extractStatus (res@(OpRecvStatusOnClientResult _ _ _):_) = Just res
extractStatus (_:xs) = extractStatus xs

View file

@ -6,9 +6,7 @@ import Control.Concurrent (threadDelay)
import Control.Exception (bracket, finally) import Control.Exception (bracket, finally)
import Control.Monad import Control.Monad
import Data.ByteString (ByteString) import Data.ByteString (ByteString)
import qualified Data.Map as M
import Foreign.Ptr (nullPtr) import Foreign.Ptr (nullPtr)
import Foreign.Storable (peek)
import qualified Network.GRPC.Unsafe as C import qualified Network.GRPC.Unsafe as C
import qualified Network.GRPC.Unsafe.Op as C import qualified Network.GRPC.Unsafe.Op as C
@ -25,9 +23,6 @@ import Network.GRPC.LowLevel.CompletionQueue (CompletionQueue,
import Network.GRPC.LowLevel.GRPC import Network.GRPC.LowLevel.GRPC
import Network.GRPC.LowLevel.Op import Network.GRPC.LowLevel.Op
import qualified Network.GRPC.Unsafe.ByteBuffer as C
import qualified Network.GRPC.Unsafe.Metadata as C
-- | Wraps various gRPC state needed to run a server. -- | Wraps various gRPC state needed to run a server.
data Server = Server {internalServer :: C.Server, serverCQ :: CompletionQueue, data Server = Server {internalServer :: C.Server, serverCQ :: CompletionQueue,
registeredMethods :: [RegisteredMethod]} registeredMethods :: [RegisteredMethod]}
@ -123,12 +118,12 @@ serverRegisterMethod _ _ _ _ = error "Streaming methods not implemented yet."
-- | Create a 'Call' with which to wait for the invocation of a registered -- | Create a 'Call' with which to wait for the invocation of a registered
-- method. -- method.
serverCreateRegisteredCall :: Server -> RegisteredMethod -> TimeoutSeconds serverCreateRegisteredCall :: Server -> RegisteredMethod -> TimeoutSeconds
-> IO (Either GRPCIOError Call) -> IO (Either GRPCIOError ServerRegCall)
serverCreateRegisteredCall Server{..} rm timeLimit = serverCreateRegisteredCall Server{..} rm timeLimit =
serverRequestRegisteredCall internalServer serverCQ timeLimit rm serverRequestRegisteredCall internalServer serverCQ timeLimit rm
withServerRegisteredCall :: Server -> RegisteredMethod -> TimeoutSeconds withServerRegisteredCall :: Server -> RegisteredMethod -> TimeoutSeconds
-> (Call -> (ServerRegCall
-> IO (Either GRPCIOError a)) -> IO (Either GRPCIOError a))
-> IO (Either GRPCIOError a) -> IO (Either GRPCIOError a)
withServerRegisteredCall server regmethod timeout f = do withServerRegisteredCall server regmethod timeout f = do
@ -137,23 +132,23 @@ withServerRegisteredCall server regmethod timeout f = do
Left x -> return $ Left x Left x -> return $ Left x
Right call -> f call `finally` logDestroy call Right call -> f call `finally` logDestroy call
where logDestroy c = grpcDebug "withServerRegisteredCall: destroying." where logDestroy c = grpcDebug "withServerRegisteredCall: destroying."
>> destroyCall c >> destroyServerRegCall c
serverCreateCall :: Server -> TimeoutSeconds serverCreateUnregCall :: Server -> TimeoutSeconds
-> IO (Either GRPCIOError Call) -> IO (Either GRPCIOError ServerUnregCall)
serverCreateCall Server{..} timeLimit = serverCreateUnregCall Server{..} timeLimit =
serverRequestCall internalServer serverCQ timeLimit serverRequestCall internalServer serverCQ timeLimit
withServerCall :: Server -> TimeoutSeconds withServerUnregCall :: Server -> TimeoutSeconds
-> (Call -> IO (Either GRPCIOError a)) -> (ServerUnregCall -> IO (Either GRPCIOError a))
-> IO (Either GRPCIOError a) -> IO (Either GRPCIOError a)
withServerCall server timeout f = do withServerUnregCall server timeout f = do
createResult <- serverCreateCall server timeout createResult <- serverCreateUnregCall server timeout
case createResult of case createResult of
Left x -> return $ Left x Left x -> return $ Left x
Right call -> f call `finally` logDestroy call Right call -> f call `finally` logDestroy call
where logDestroy c = grpcDebug "withServerCall: destroying." where logDestroy c = grpcDebug "withServerCall: destroying."
>> destroyCall c >> destroyServerUnregCall c
-- | Sequence of 'Op's needed to receive a normal (non-streaming) call. -- | Sequence of 'Op's needed to receive a normal (non-streaming) call.
serverOpsGetNormalCall :: MetadataMap -> [Op] serverOpsGetNormalCall :: MetadataMap -> [Op]
@ -211,19 +206,19 @@ serverHandleNormalRegisteredCall s@Server{..} rm timeLimit srvMetadata f = do
-- anyway. -- anyway.
withServerRegisteredCall s rm timeLimit $ \call -> do withServerRegisteredCall s rm timeLimit $ \call -> do
grpcDebug "serverHandleNormalRegisteredCall: starting batch." grpcDebug "serverHandleNormalRegisteredCall: starting batch."
debugCall call debugServerRegCall call
case optionalPayload call of payload <- serverRegCallGetPayload call
Nothing -> error "Impossible: not a registered call." --TODO: better types case payload of
Just payloadPtr -> do --TODO: what should we do with an empty payload? Have the handler take
payload <- peek payloadPtr -- @Maybe ByteString@? Need to figure out when/why payload would be empty.
requestBody <- C.copyByteBufferToByteString payload Nothing -> error "serverHandleNormalRegisteredCall: payload empty."
metadataArray <- peek $ requestMetadataRecv call Just requestBody -> do
metadata <- C.getAllMetadataArray metadataArray requestMeta <- serverRegCallGetMetadata call
(respBody, initMeta, trailingMeta, details) <- f requestBody metadata (respBody, initMeta, trailingMeta, details) <- f requestBody requestMeta
let status = C.GrpcStatusOk let status = C.GrpcStatusOk
let respOps = serverOpsSendNormalRegisteredResponse let respOps = serverOpsSendNormalRegisteredResponse
respBody initMeta trailingMeta status details respBody initMeta trailingMeta status details
respOpsResults <- runOps call serverCQ respOps timeLimit respOpsResults <- runServerRegOps call serverCQ respOps timeLimit
grpcDebug "serverHandleNormalRegisteredCall: finished response ops." grpcDebug "serverHandleNormalRegisteredCall: finished response ops."
case respOpsResults of case respOpsResults of
Left x -> return $ Left x Left x -> return $ Left x
@ -235,25 +230,28 @@ serverHandleNormalRegisteredCall s@Server{..} rm timeLimit srvMetadata f = do
serverHandleNormalCall :: Server -> TimeoutSeconds serverHandleNormalCall :: Server -> TimeoutSeconds
-> MetadataMap -> MetadataMap
-- ^ Initial server metadata. -- ^ Initial server metadata.
-> (ByteString -> MetadataMap -> (ByteString -> MetadataMap -> MethodName
-> IO (ByteString, MetadataMap, StatusDetails)) -> IO (ByteString, MetadataMap, StatusDetails))
-- ^ Handler function takes a request body and -- ^ Handler function takes a request body and
-- metadata and returns a response body and metadata. -- metadata and returns a response body and metadata.
-> IO (Either GRPCIOError ()) -> IO (Either GRPCIOError ())
serverHandleNormalCall s@Server{..} timeLimit srvMetadata f = do serverHandleNormalCall s@Server{..} timeLimit srvMetadata f = do
withServerCall s timeLimit $ \call -> do withServerUnregCall s timeLimit $ \call -> do
grpcDebug "serverHandleNormalCall: starting batch." grpcDebug "serverHandleNormalCall: starting batch."
let recvOps = serverOpsGetNormalCall srvMetadata let recvOps = serverOpsGetNormalCall srvMetadata
opResults <- runOps call serverCQ recvOps timeLimit opResults <- runServerUnregOps call serverCQ recvOps timeLimit
case opResults of case opResults of
Left x -> return $ Left x Left x -> do grpcDebug "serverHandleNormalCall: ops failed; aborting"
Right [OpRecvMessageResult body] -> do return $ Left x
--TODO: we need to get client metadata Right [OpRecvMessageResult (Just body)] -> do
(respBody, respMetadata, details) <- f body M.empty requestMeta <- serverUnregCallGetMetadata call
grpcDebug $ "got client metadata: " ++ show requestMeta
methodName <- serverUnregCallGetMethodName call
(respBody, respMetadata, details) <- f body requestMeta methodName
let status = C.GrpcStatusOk let status = C.GrpcStatusOk
let respOps = serverOpsSendNormalResponse let respOps = serverOpsSendNormalResponse
respBody respMetadata status details respBody respMetadata status details
respOpsResults <- runOps call serverCQ respOps timeLimit respOpsResults <- runServerUnregOps call serverCQ respOps timeLimit
case respOpsResults of case respOpsResults of
Left x -> do grpcDebug "serverHandleNormalCall: resp failed." Left x -> do grpcDebug "serverHandleNormalCall: resp failed."
return $ Left x return $ Left x

View file

@ -263,3 +263,9 @@ castPeek p = peek (castPtr p)
`MetadataArray', id `Ptr ByteBuffer', `CompletionQueue', `MetadataArray', id `Ptr ByteBuffer', `CompletionQueue',
`CompletionQueue',unTag `Tag'} `CompletionQueue',unTag `Tag'}
-> `CallError'#} -> `CallError'#}
{#fun call_details_get_method as ^ {`CallDetails'} -> `String'#}
{#fun call_details_get_host as ^ {`CallDetails'} -> `String'#}
{#fun call_details_get_deadline as ^ {`CallDetails'} -> `CTimeSpec' peek* #}

View file

@ -84,8 +84,10 @@ payloadLowLevelServerUnregistered :: TestServer
payloadLowLevelServerUnregistered = TestServer $ \grpc -> do payloadLowLevelServerUnregistered = TestServer $ \grpc -> do
withServer grpc (ServerConfig "localhost" 50051 []) $ \server -> do withServer grpc (ServerConfig "localhost" 50051 []) $ \server -> do
result <- serverHandleNormalCall server 11 M.empty $ result <- serverHandleNormalCall server 11 M.empty $
\_reqBody _reqMeta -> return ("reply test", M.empty, \reqBody _reqMeta reqMethod -> do
StatusDetails "details string") reqBody @?= "Hello!"
reqMethod @?= "/foo"
return ("reply test", M.empty, StatusDetails "details string")
case result of case result of
Left x -> error $ show x Left x -> error $ show x
Right _ -> return () Right _ -> return ()
@ -115,7 +117,7 @@ testServerUnregisteredAwaitNoClient =
let conf = ServerConfig "localhost" 50051 [] let conf = ServerConfig "localhost" 50051 []
withServer grpc conf $ \server -> do withServer grpc conf $ \server -> do
result <- serverHandleNormalCall server 10 M.empty $ result <- serverHandleNormalCall server 10 M.empty $
\_ _ -> return ("", M.empty, StatusDetails "") \_ _ _ -> return ("", M.empty, StatusDetails "")
case result of case result of
Left err -> error $ show err Left err -> error $ show err
Right _ -> return () Right _ -> return ()
@ -135,7 +137,7 @@ testWithServerCall =
grpcTest "Server - Create/destroy call" $ \grpc -> do grpcTest "Server - Create/destroy call" $ \grpc -> do
let conf = ServerConfig "localhost" 50051 [] let conf = ServerConfig "localhost" 50051 []
withServer grpc conf $ \server -> do withServer grpc conf $ \server -> do
result <- withServerCall server 1 $ const $ return $ Right () result <- withServerUnregCall server 1 $ const $ return $ Right ()
result @?= Left GRPCIOTimeout result @?= Left GRPCIOTimeout
testWithClientCall :: TestTree testWithClientCall :: TestTree