mirror of
https://github.com/unclechu/gRPC-haskell.git
synced 2024-11-26 21:19:43 +01:00
Add Test{Client,Server} newtype wrappers
This commit is contained in:
parent
c9d06c9ec7
commit
463000d0bc
1 changed files with 26 additions and 20 deletions
|
@ -1,6 +1,6 @@
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
|
||||||
module LowLevelTests where
|
module LowLevelTests (lowLevelTests) where
|
||||||
|
|
||||||
import Control.Concurrent.Async
|
import Control.Concurrent.Async
|
||||||
import Data.ByteString (ByteString)
|
import Data.ByteString (ByteString)
|
||||||
|
@ -55,8 +55,8 @@ testClientCreateDestroy =
|
||||||
gtc "Client - start/stop" $ \grpc -> do
|
gtc "Client - start/stop" $ \grpc -> do
|
||||||
withClient grpc (ClientConfig "localhost" 50051) nop
|
withClient grpc (ClientConfig "localhost" 50051) nop
|
||||||
|
|
||||||
testPayloadLowLevelServer :: GRPC -> IO ()
|
testPayloadLowLevelServer :: TestServer
|
||||||
testPayloadLowLevelServer grpc = do
|
testPayloadLowLevelServer = TestServer $ \grpc -> do
|
||||||
let conf = (ServerConfig "localhost" 50051 [("/foo", "localhost", Normal)])
|
let conf = (ServerConfig "localhost" 50051 [("/foo", "localhost", Normal)])
|
||||||
withServer grpc conf $ \server -> do
|
withServer grpc conf $ \server -> do
|
||||||
let method = head (registeredMethods server)
|
let method = head (registeredMethods server)
|
||||||
|
@ -68,8 +68,8 @@ testPayloadLowLevelServer grpc = do
|
||||||
Left err -> error $ show err
|
Left err -> error $ show err
|
||||||
Right _ -> return ()
|
Right _ -> return ()
|
||||||
|
|
||||||
testPayloadLowLevelClient :: GRPC -> IO ()
|
testPayloadLowLevelClient :: TestClient
|
||||||
testPayloadLowLevelClient grpc =
|
testPayloadLowLevelClient = TestClient $ \grpc ->
|
||||||
withClient grpc (ClientConfig "localhost" 50051) $ \client -> do
|
withClient grpc (ClientConfig "localhost" 50051) $ \client -> do
|
||||||
method <- clientRegisterMethod client "/foo" "localhost" Normal
|
method <- clientRegisterMethod client "/foo" "localhost" Normal
|
||||||
putStrLn "registered method on client."
|
putStrLn "registered method on client."
|
||||||
|
@ -81,8 +81,8 @@ testPayloadLowLevelClient grpc =
|
||||||
respBody @?= "reply test"
|
respBody @?= "reply test"
|
||||||
respCode @?= GrpcStatusOk
|
respCode @?= GrpcStatusOk
|
||||||
|
|
||||||
testPayloadLowLevelClientUnregistered :: GRPC -> IO ()
|
testPayloadLowLevelClientUnregistered :: TestClient
|
||||||
testPayloadLowLevelClientUnregistered grpc = do
|
testPayloadLowLevelClientUnregistered = TestClient $ \grpc -> do
|
||||||
withClient grpc (ClientConfig "localhost" 50051) $ \client -> do
|
withClient grpc (ClientConfig "localhost" 50051) $ \client -> do
|
||||||
reqResult <- clientRequest client "/foo" "localhost" 10 "Hello!" M.empty
|
reqResult <- clientRequest client "/foo" "localhost" 10 "Hello!" M.empty
|
||||||
case reqResult of
|
case reqResult of
|
||||||
|
@ -93,8 +93,8 @@ testPayloadLowLevelClientUnregistered grpc = do
|
||||||
respCode @?= GrpcStatusOk
|
respCode @?= GrpcStatusOk
|
||||||
details @?= "details string"
|
details @?= "details string"
|
||||||
|
|
||||||
testPayloadLowLevelServerUnregistered :: GRPC -> IO ()
|
testPayloadLowLevelServerUnregistered :: TestServer
|
||||||
testPayloadLowLevelServerUnregistered grpc = do
|
testPayloadLowLevelServerUnregistered = 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 -> return ("reply test", M.empty,
|
||||||
|
@ -166,8 +166,8 @@ assertCqEventComplete e = do
|
||||||
eventCompletionType e HU.@?= OpComplete
|
eventCompletionType e HU.@?= OpComplete
|
||||||
eventSuccess e HU.@?= True
|
eventSuccess e HU.@?= True
|
||||||
|
|
||||||
testPayloadClient :: GRPC -> IO ()
|
testPayloadClient :: TestClient
|
||||||
testPayloadClient _grpc = do
|
testPayloadClient = TestClient $ \_grpc -> do
|
||||||
client <- grpcInsecureChannelCreate "localhost:50051" nullPtr reserved
|
client <- grpcInsecureChannelCreate "localhost:50051" nullPtr reserved
|
||||||
cq <- grpcCompletionQueueCreate reserved
|
cq <- grpcCompletionQueueCreate reserved
|
||||||
withMetadataArrayPtr $ \initialMetadataRecv -> do
|
withMetadataArrayPtr $ \initialMetadataRecv -> do
|
||||||
|
@ -213,8 +213,8 @@ testPayloadClient _grpc = do
|
||||||
grpcCompletionQueueDestroy cq
|
grpcCompletionQueueDestroy cq
|
||||||
grpcChannelDestroy client
|
grpcChannelDestroy client
|
||||||
|
|
||||||
testPayloadServer :: GRPC -> IO ()
|
testPayloadServer :: TestServer
|
||||||
testPayloadServer _grpc = do
|
testPayloadServer = TestServer $ \_grpc -> do
|
||||||
server <- grpcServerCreate nullPtr reserved
|
server <- grpcServerCreate nullPtr reserved
|
||||||
cq <- grpcCompletionQueueCreate reserved
|
cq <- grpcCompletionQueueCreate reserved
|
||||||
grpcServerRegisterCompletionQueue server cq reserved
|
grpcServerRegisterCompletionQueue server cq reserved
|
||||||
|
@ -291,18 +291,24 @@ testPayload =
|
||||||
runClientServer testPayloadClient testPayloadServer
|
runClientServer testPayloadClient testPayloadServer
|
||||||
|
|
||||||
--------------------------------------------------------------------------------
|
--------------------------------------------------------------------------------
|
||||||
-- Utility functions
|
-- Utility types and functions
|
||||||
|
|
||||||
|
nop :: Monad m => a -> m ()
|
||||||
|
nop = const (return ())
|
||||||
|
|
||||||
-- | Boilerplate for naming a GRPC unit test
|
-- | Boilerplate for naming a GRPC unit test
|
||||||
gtc :: TestName -> (GRPC -> IO ()) -> TestTree
|
gtc :: TestName -> (GRPC -> IO ()) -> TestTree
|
||||||
gtc nm = testCase nm . withGRPC
|
gtc nm = testCase nm . withGRPC
|
||||||
|
|
||||||
nop :: Monad m => a -> m ()
|
newtype TestClient = TestClient (GRPC -> IO ())
|
||||||
nop = const (return ())
|
newtype TestServer = TestServer (GRPC -> IO ())
|
||||||
|
|
||||||
runClientServer :: (GRPC -> IO ()) -> (GRPC -> IO ()) -> GRPC -> IO ()
|
-- | Asyncs the given 'TestClient' and 'TestServer' and waits for both to
|
||||||
runClientServer client server grpc = do
|
-- terminate. TODO: We'll probably want to add toplevel timeouts and better
|
||||||
withAsync (server grpc) $ \a1 -> do
|
-- error reporting.
|
||||||
withAsync (client grpc) $ \a2 -> do
|
runClientServer :: TestClient -> TestServer -> GRPC -> IO ()
|
||||||
|
runClientServer (TestClient c) (TestServer s) grpc = do
|
||||||
|
withAsync (s grpc) $ \a1 -> do
|
||||||
|
withAsync (c grpc) $ \a2 -> do
|
||||||
wait a1
|
wait a1
|
||||||
wait a2
|
wait a2
|
||||||
|
|
Loading…
Reference in a new issue