Skip to content

Commit

Permalink
Add Proto.API.Trivial module
Browse files Browse the repository at this point in the history
We had a few spots where we were defining a `RawRPC "trivial" "trivial"` RPC
with `NoMetadata`, so just abstracted to deduplicate.
  • Loading branch information
FinleyMcIlwaine committed Aug 28, 2024
1 parent 9710050 commit 346ac83
Show file tree
Hide file tree
Showing 5 changed files with 44 additions and 34 deletions.
1 change: 1 addition & 0 deletions grapesy.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -329,6 +329,7 @@ test-suite test-grapesy

Proto.API.Interop
Proto.API.Ping
Proto.API.Trivial
Proto.Empty
Proto.Messages
Proto.Ping
Expand Down
21 changes: 21 additions & 0 deletions proto/Proto/API/Trivial.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,21 @@
{-# OPTIONS_GHC -Wno-orphans #-}

module Proto.API.Trivial
( -- * Trivial RPC
Trivial
, Trivial'
) where

import Network.GRPC.Common
import Network.GRPC.Spec

{-------------------------------------------------------------------------------
Trivial RPC
-------------------------------------------------------------------------------}

type Trivial = RawRpc "trivial" "trivial"
type Trivial' s = RawRpc "trivial" s

type instance RequestMetadata (Trivial' s) = NoMetadata
type instance ResponseInitialMetadata (Trivial' s) = NoMetadata
type instance ResponseTrailingMetadata (Trivial' s) = NoMetadata
30 changes: 14 additions & 16 deletions test-grapesy/Test/Sanity/Disconnect.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@
-- 1. The handlers dealing with that client (i.e. on that connection) should
-- fail with 'Server.ClientDisonnected'
-- 2. Future calls (after reconnection) succeed
module Test.Sanity.Disconnect where
module Test.Sanity.Disconnect (tests) where

import Control.Concurrent
import Control.Concurrent.Async
Expand All @@ -36,6 +36,7 @@ import Network.GRPC.Common
import Network.GRPC.Server qualified as Server
import Network.GRPC.Server.Binary qualified as Binary
import Network.GRPC.Spec
import Proto.API.Trivial
import Test.Util
import Test.Util.RawTestServer

Expand All @@ -45,6 +46,13 @@ tests = testGroup "Test.Sanity.Disconnect" [
, testCase "server" test_serverDisconnect
]

-- | We want two distinct handlers running at the same time, so we have two
-- trivial RPCs
type RPC1 = Trivial' "rpc1"

-- | See 'RPC1'
type RPC2 = Trivial' "rpc2"

-- | Two separate clients make many concurrent calls, one of them disconnects.
test_clientDisconnect :: Assertion
test_clientDisconnect = do
Expand All @@ -54,9 +62,9 @@ test_clientDisconnect = do
server <-
Server.mkGrpcServer def [
Server.someRpcHandler $
Server.mkRpcHandler @Trivial $ echoHandler (Just disconnectCounter1)
Server.mkRpcHandler @RPC1 $ echoHandler (Just disconnectCounter1)
, Server.someRpcHandler $
Server.mkRpcHandler @Trivial' $ echoHandler (Just disconnectCounter2)
Server.mkRpcHandler @RPC2 $ echoHandler (Just disconnectCounter2)
]

portSignal <- newEmptyMVar
Expand Down Expand Up @@ -85,7 +93,7 @@ test_clientDisconnect = do
return False
]
mapConcurrently_
( Client.withRPC conn def (Proxy @Trivial)
( Client.withRPC conn def (Proxy @RPC1)
. countUntil
)
predicates
Expand All @@ -99,14 +107,14 @@ test_clientDisconnect = do
(result1, result2) <- concurrently
( Client.withConnection def serverAddress $ \conn -> do
sum <$> mapConcurrently
( Client.withRPC conn def (Proxy @Trivial)
( Client.withRPC conn def (Proxy @RPC1)
. countUntil
)
predicates
)
( Client.withConnection def serverAddress $ \conn -> do
sum <$> mapConcurrently
( Client.withRPC conn def (Proxy @Trivial')
( Client.withRPC conn def (Proxy @RPC2)
. countUntil
)
predicates
Expand Down Expand Up @@ -275,13 +283,3 @@ echoHandler disconnectCounter call = trackDisconnects disconnectCounter $ do
-------------------------------------------------------------------------------}

foreign import ccall unsafe "exit" c_exit :: CInt -> IO ()

type Trivial = RawRpc "trivial" "trivial"
type Trivial' = RawRpc "trivial" "trivial'"

type instance RequestMetadata Trivial = NoMetadata
type instance ResponseInitialMetadata Trivial = NoMetadata
type instance ResponseTrailingMetadata Trivial = NoMetadata
type instance RequestMetadata Trivial' = NoMetadata
type instance ResponseInitialMetadata Trivial' = NoMetadata
type instance ResponseTrailingMetadata Trivial' = NoMetadata
14 changes: 7 additions & 7 deletions test-grapesy/Test/Sanity/EndOfStream.hs
Original file line number Diff line number Diff line change
Expand Up @@ -101,7 +101,7 @@ test_recvTrailers = testClientServer $ ClientServerTest {
config = def
, server = [Server.fromMethod nonStreamingHandler]
, client = simpleTestClient $ \conn ->
Client.withRPC conn def (Proxy @Trivial) $ \call -> do
Client.withRPC conn def (Proxy @Poke) $ \call -> do
Client.sendFinalInput call BS.Lazy.empty

resp <- Client.recvNextOutput call
Expand All @@ -123,7 +123,7 @@ test_recvTrailers = testClientServer $ ClientServerTest {
-------------------------------------------------------------------------------}

-- | Receive any string, respond with a single 'mempty'
type Trivial = RawRpc "Test" "trivial"
type Poke = RawRpc "Test" "trivial"

-- | Service that simply absorbs all messages and then returns with 'mempty'
type Absorb = RawRpc "Test" "absorb"
Expand All @@ -132,7 +132,7 @@ type Absorb = RawRpc "Test" "absorb"
-- client with a bunch of 'mempty' messages
type Spam = RawRpc "Test" "spam"

nonStreamingHandler :: ServerHandler' NonStreaming IO Trivial
nonStreamingHandler :: ServerHandler' NonStreaming IO Poke
nonStreamingHandler = Server.mkNonStreaming $ \_inp ->
return BS.Lazy.empty

Expand Down Expand Up @@ -161,13 +161,13 @@ test_recvInput = testClientServer $ ClientServerTest {
config = def
, server = [Server.someRpcHandler handler]
, client = simpleTestClient $ \conn ->
Client.withRPC conn def (Proxy @Trivial) $ \call -> do
Client.withRPC conn def (Proxy @Poke) $ \call -> do
Client.sendFinalInput call BS.Lazy.empty
_resp <- Client.recvFinalOutput call
return ()
}
where
handler :: Server.RpcHandler IO Trivial
handler :: Server.RpcHandler IO Poke
handler = Server.mkRpcHandler $ \call -> do
x <- Server.recvInput call

Expand All @@ -189,13 +189,13 @@ test_recvEndOfInput = testClientServer $ ClientServerTest {
config = def
, server = [Server.someRpcHandler handler]
, client = simpleTestClient $ \conn ->
Client.withRPC conn def (Proxy @Trivial) $ \call -> do
Client.withRPC conn def (Proxy @Poke) $ \call -> do
Client.sendFinalInput call BS.Lazy.empty
_resp <- Client.recvFinalOutput call
return ()
}
where
handler :: Server.RpcHandler IO Trivial
handler :: Server.RpcHandler IO Poke
handler = Server.mkRpcHandler $ \call -> do
resp <- Server.recvNextInput call
assertEqual "resp" BS.Lazy.empty $ resp
Expand Down
12 changes: 1 addition & 11 deletions test-grapesy/Test/Sanity/Exception.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ import Network.GRPC.Client.Binary qualified as Binary
import Network.GRPC.Common
import Network.GRPC.Server qualified as Server
import Network.GRPC.Server.Binary qualified as Binary
import Network.GRPC.Spec
import Proto.API.Trivial
import Test.Driver.ClientServer
import Test.Util.Exception

Expand Down Expand Up @@ -184,13 +184,3 @@ incUntilFinal call = do
-- ticket above.
Server.sendTrailers call NoMetadata
return ()

{-------------------------------------------------------------------------------
Auxiliary
-------------------------------------------------------------------------------}

type Trivial = RawRpc "trivial" "trivial"

type instance RequestMetadata Trivial = NoMetadata
type instance ResponseInitialMetadata Trivial = NoMetadata
type instance ResponseTrailingMetadata Trivial = NoMetadata

0 comments on commit 346ac83

Please sign in to comment.