gRPC-haskell/tests/LowLevelTests.hs

277 lines
9.9 KiB
Haskell
Raw Normal View History

{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedLists #-}
Begin safe low-level Haskell layer (#7) * grpc_server_request_call * basic slice functionality * rename function to emphasize side effects * add docs * ByteBuffer function bindings * replace unsafeCoerce with more specific function, add docs, tests. * add newtypes for Tag and Reserved void pointers * manually fix request_registered_call binding * use nocode keyword to fix Ptr () problems * decouple copying Slice from freeing slice * Add time ops * remove nocode decls * Start Op module, fix c2hs preprocessing order * metadata manipulation operations * metadata free function, test * helper functions for constructing ops of each type * bindings for op creation functions * finish up Op creation functions, implement Op destruction, add docs. * tweak documentation * rework Op creation functions to work with an array of ops, for ease of use with grpc_call_start_batch * forgot to change return types * wrap hook lines, fix types to op creation functions * implement part of the payload test * hideous, but working, end to end test * bindings for connectivity state checks, split test into two threads * various cleanup * rename Core to Unsafe for emphasis, clean up tests more * begin safe low-level facilities * begin completion queue and server stuff * Finish server start/stop, cq start/stop, add tests * facilities for safely executing op batches * reorganize LowLevel modules, begin explicit export list * client functionality, stub payload test, various refactors * tweak cabal file, add test * add more documentation * doc tweaks * begin refactor to improve CompletionQueue safety * export only thread-safe CQ functions, add registered call creation and other CQ utilities * begin refactor to use GRPCIO monad, fix missing push semaphore, fix mem leak in server calls * switch to explicit Either where needed * add crashing tests, continue fleshing out serverHandleNormalCall * fix haddock error, finish first draft of request handling function * reduce GHC warnings * non-registered client request helpers * initial request/response test working * don't pass tags around; generate where needed * server call bracket functions * correct order of semaphore acquisition and shutdown check * simple debug flag logging, simplify Call type * fix various registered method issues (but still not working) * cleanup * delete old code * remove old todo * use MetadataMap synonym pervasively * more comments * update TODOs * tweak safety caveat * docs tweaks * improve haddocks * add casts to eliminate clang warnings, remove unused function * update options to eliminate cabal warnings * remove outdated todo * remove unneeded exports from CompletionQueue * rename to GRPCIOCallError, re-add create/shutdown exports (needed for Server module) * newtypes for hosts and method names * more newtypes * more debug logging * Fix flag name collision * instrument uses of free * more debug * switch to STM for completion queue stuff * reduce warnings * more debugging, create/destroy call tests * refactor, fix failure cleanup for server call creation. More tests passing. * formatting tweaks
2016-05-24 22:34:50 +02:00
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
Begin safe low-level Haskell layer (#7) * grpc_server_request_call * basic slice functionality * rename function to emphasize side effects * add docs * ByteBuffer function bindings * replace unsafeCoerce with more specific function, add docs, tests. * add newtypes for Tag and Reserved void pointers * manually fix request_registered_call binding * use nocode keyword to fix Ptr () problems * decouple copying Slice from freeing slice * Add time ops * remove nocode decls * Start Op module, fix c2hs preprocessing order * metadata manipulation operations * metadata free function, test * helper functions for constructing ops of each type * bindings for op creation functions * finish up Op creation functions, implement Op destruction, add docs. * tweak documentation * rework Op creation functions to work with an array of ops, for ease of use with grpc_call_start_batch * forgot to change return types * wrap hook lines, fix types to op creation functions * implement part of the payload test * hideous, but working, end to end test * bindings for connectivity state checks, split test into two threads * various cleanup * rename Core to Unsafe for emphasis, clean up tests more * begin safe low-level facilities * begin completion queue and server stuff * Finish server start/stop, cq start/stop, add tests * facilities for safely executing op batches * reorganize LowLevel modules, begin explicit export list * client functionality, stub payload test, various refactors * tweak cabal file, add test * add more documentation * doc tweaks * begin refactor to improve CompletionQueue safety * export only thread-safe CQ functions, add registered call creation and other CQ utilities * begin refactor to use GRPCIO monad, fix missing push semaphore, fix mem leak in server calls * switch to explicit Either where needed * add crashing tests, continue fleshing out serverHandleNormalCall * fix haddock error, finish first draft of request handling function * reduce GHC warnings * non-registered client request helpers * initial request/response test working * don't pass tags around; generate where needed * server call bracket functions * correct order of semaphore acquisition and shutdown check * simple debug flag logging, simplify Call type * fix various registered method issues (but still not working) * cleanup * delete old code * remove old todo * use MetadataMap synonym pervasively * more comments * update TODOs * tweak safety caveat * docs tweaks * improve haddocks * add casts to eliminate clang warnings, remove unused function * update options to eliminate cabal warnings * remove outdated todo * remove unneeded exports from CompletionQueue * rename to GRPCIOCallError, re-add create/shutdown exports (needed for Server module) * newtypes for hosts and method names * more newtypes * more debug logging * Fix flag name collision * instrument uses of free * more debug * switch to STM for completion queue stuff * reduce warnings * more debugging, create/destroy call tests * refactor, fix failure cleanup for server call creation. More tests passing. * formatting tweaks
2016-05-24 22:34:50 +02:00
module LowLevelTests (lowLevelTests) where
Begin safe low-level Haskell layer (#7) * grpc_server_request_call * basic slice functionality * rename function to emphasize side effects * add docs * ByteBuffer function bindings * replace unsafeCoerce with more specific function, add docs, tests. * add newtypes for Tag and Reserved void pointers * manually fix request_registered_call binding * use nocode keyword to fix Ptr () problems * decouple copying Slice from freeing slice * Add time ops * remove nocode decls * Start Op module, fix c2hs preprocessing order * metadata manipulation operations * metadata free function, test * helper functions for constructing ops of each type * bindings for op creation functions * finish up Op creation functions, implement Op destruction, add docs. * tweak documentation * rework Op creation functions to work with an array of ops, for ease of use with grpc_call_start_batch * forgot to change return types * wrap hook lines, fix types to op creation functions * implement part of the payload test * hideous, but working, end to end test * bindings for connectivity state checks, split test into two threads * various cleanup * rename Core to Unsafe for emphasis, clean up tests more * begin safe low-level facilities * begin completion queue and server stuff * Finish server start/stop, cq start/stop, add tests * facilities for safely executing op batches * reorganize LowLevel modules, begin explicit export list * client functionality, stub payload test, various refactors * tweak cabal file, add test * add more documentation * doc tweaks * begin refactor to improve CompletionQueue safety * export only thread-safe CQ functions, add registered call creation and other CQ utilities * begin refactor to use GRPCIO monad, fix missing push semaphore, fix mem leak in server calls * switch to explicit Either where needed * add crashing tests, continue fleshing out serverHandleNormalCall * fix haddock error, finish first draft of request handling function * reduce GHC warnings * non-registered client request helpers * initial request/response test working * don't pass tags around; generate where needed * server call bracket functions * correct order of semaphore acquisition and shutdown check * simple debug flag logging, simplify Call type * fix various registered method issues (but still not working) * cleanup * delete old code * remove old todo * use MetadataMap synonym pervasively * more comments * update TODOs * tweak safety caveat * docs tweaks * improve haddocks * add casts to eliminate clang warnings, remove unused function * update options to eliminate cabal warnings * remove outdated todo * remove unneeded exports from CompletionQueue * rename to GRPCIOCallError, re-add create/shutdown exports (needed for Server module) * newtypes for hosts and method names * more newtypes * more debug logging * Fix flag name collision * instrument uses of free * more debug * switch to STM for completion queue stuff * reduce warnings * more debugging, create/destroy call tests * refactor, fix failure cleanup for server call creation. More tests passing. * formatting tweaks
2016-05-24 22:34:50 +02:00
import Control.Concurrent (threadDelay)
import Control.Concurrent.Async
import Control.Monad
import Data.ByteString (ByteString)
import qualified Data.Map as M
2016-05-24 23:39:53 +02:00
import Network.GRPC.LowLevel
import qualified Network.GRPC.LowLevel.Client.Unregistered as U
import qualified Network.GRPC.LowLevel.Server.Unregistered as U
2016-05-24 23:39:53 +02:00
import Test.Tasty
import Test.Tasty.HUnit as HU (Assertion,
assertBool,
assertEqual,
assertFailure,
testCase,
(@?=))
Begin safe low-level Haskell layer (#7) * grpc_server_request_call * basic slice functionality * rename function to emphasize side effects * add docs * ByteBuffer function bindings * replace unsafeCoerce with more specific function, add docs, tests. * add newtypes for Tag and Reserved void pointers * manually fix request_registered_call binding * use nocode keyword to fix Ptr () problems * decouple copying Slice from freeing slice * Add time ops * remove nocode decls * Start Op module, fix c2hs preprocessing order * metadata manipulation operations * metadata free function, test * helper functions for constructing ops of each type * bindings for op creation functions * finish up Op creation functions, implement Op destruction, add docs. * tweak documentation * rework Op creation functions to work with an array of ops, for ease of use with grpc_call_start_batch * forgot to change return types * wrap hook lines, fix types to op creation functions * implement part of the payload test * hideous, but working, end to end test * bindings for connectivity state checks, split test into two threads * various cleanup * rename Core to Unsafe for emphasis, clean up tests more * begin safe low-level facilities * begin completion queue and server stuff * Finish server start/stop, cq start/stop, add tests * facilities for safely executing op batches * reorganize LowLevel modules, begin explicit export list * client functionality, stub payload test, various refactors * tweak cabal file, add test * add more documentation * doc tweaks * begin refactor to improve CompletionQueue safety * export only thread-safe CQ functions, add registered call creation and other CQ utilities * begin refactor to use GRPCIO monad, fix missing push semaphore, fix mem leak in server calls * switch to explicit Either where needed * add crashing tests, continue fleshing out serverHandleNormalCall * fix haddock error, finish first draft of request handling function * reduce GHC warnings * non-registered client request helpers * initial request/response test working * don't pass tags around; generate where needed * server call bracket functions * correct order of semaphore acquisition and shutdown check * simple debug flag logging, simplify Call type * fix various registered method issues (but still not working) * cleanup * delete old code * remove old todo * use MetadataMap synonym pervasively * more comments * update TODOs * tweak safety caveat * docs tweaks * improve haddocks * add casts to eliminate clang warnings, remove unused function * update options to eliminate cabal warnings * remove outdated todo * remove unneeded exports from CompletionQueue * rename to GRPCIOCallError, re-add create/shutdown exports (needed for Server module) * newtypes for hosts and method names * more newtypes * more debug logging * Fix flag name collision * instrument uses of free * more debug * switch to STM for completion queue stuff * reduce warnings * more debugging, create/destroy call tests * refactor, fix failure cleanup for server call creation. More tests passing. * formatting tweaks
2016-05-24 22:34:50 +02:00
lowLevelTests :: TestTree
lowLevelTests = testGroup "Unit tests of low-level Haskell library"
[ testGRPCBracket
, testCompletionQueueCreateDestroy
, testClientCreateDestroy
2016-06-08 17:48:28 +02:00
, testClientCall
, testClientTimeoutNoServer
2016-06-08 17:48:28 +02:00
, testServerCreateDestroy
, testServerCall
, testServerTimeoutNoClient
-- , testWrongEndpoint
, testPayload
, testPayloadUnregistered
, testGoaway
, testSlowServer
]
Begin safe low-level Haskell layer (#7) * grpc_server_request_call * basic slice functionality * rename function to emphasize side effects * add docs * ByteBuffer function bindings * replace unsafeCoerce with more specific function, add docs, tests. * add newtypes for Tag and Reserved void pointers * manually fix request_registered_call binding * use nocode keyword to fix Ptr () problems * decouple copying Slice from freeing slice * Add time ops * remove nocode decls * Start Op module, fix c2hs preprocessing order * metadata manipulation operations * metadata free function, test * helper functions for constructing ops of each type * bindings for op creation functions * finish up Op creation functions, implement Op destruction, add docs. * tweak documentation * rework Op creation functions to work with an array of ops, for ease of use with grpc_call_start_batch * forgot to change return types * wrap hook lines, fix types to op creation functions * implement part of the payload test * hideous, but working, end to end test * bindings for connectivity state checks, split test into two threads * various cleanup * rename Core to Unsafe for emphasis, clean up tests more * begin safe low-level facilities * begin completion queue and server stuff * Finish server start/stop, cq start/stop, add tests * facilities for safely executing op batches * reorganize LowLevel modules, begin explicit export list * client functionality, stub payload test, various refactors * tweak cabal file, add test * add more documentation * doc tweaks * begin refactor to improve CompletionQueue safety * export only thread-safe CQ functions, add registered call creation and other CQ utilities * begin refactor to use GRPCIO monad, fix missing push semaphore, fix mem leak in server calls * switch to explicit Either where needed * add crashing tests, continue fleshing out serverHandleNormalCall * fix haddock error, finish first draft of request handling function * reduce GHC warnings * non-registered client request helpers * initial request/response test working * don't pass tags around; generate where needed * server call bracket functions * correct order of semaphore acquisition and shutdown check * simple debug flag logging, simplify Call type * fix various registered method issues (but still not working) * cleanup * delete old code * remove old todo * use MetadataMap synonym pervasively * more comments * update TODOs * tweak safety caveat * docs tweaks * improve haddocks * add casts to eliminate clang warnings, remove unused function * update options to eliminate cabal warnings * remove outdated todo * remove unneeded exports from CompletionQueue * rename to GRPCIOCallError, re-add create/shutdown exports (needed for Server module) * newtypes for hosts and method names * more newtypes * more debug logging * Fix flag name collision * instrument uses of free * more debug * switch to STM for completion queue stuff * reduce warnings * more debugging, create/destroy call tests * refactor, fix failure cleanup for server call creation. More tests passing. * formatting tweaks
2016-05-24 22:34:50 +02:00
testGRPCBracket :: TestTree
testGRPCBracket =
testCase "Start/stop GRPC" $ withGRPC nop
Begin safe low-level Haskell layer (#7) * grpc_server_request_call * basic slice functionality * rename function to emphasize side effects * add docs * ByteBuffer function bindings * replace unsafeCoerce with more specific function, add docs, tests. * add newtypes for Tag and Reserved void pointers * manually fix request_registered_call binding * use nocode keyword to fix Ptr () problems * decouple copying Slice from freeing slice * Add time ops * remove nocode decls * Start Op module, fix c2hs preprocessing order * metadata manipulation operations * metadata free function, test * helper functions for constructing ops of each type * bindings for op creation functions * finish up Op creation functions, implement Op destruction, add docs. * tweak documentation * rework Op creation functions to work with an array of ops, for ease of use with grpc_call_start_batch * forgot to change return types * wrap hook lines, fix types to op creation functions * implement part of the payload test * hideous, but working, end to end test * bindings for connectivity state checks, split test into two threads * various cleanup * rename Core to Unsafe for emphasis, clean up tests more * begin safe low-level facilities * begin completion queue and server stuff * Finish server start/stop, cq start/stop, add tests * facilities for safely executing op batches * reorganize LowLevel modules, begin explicit export list * client functionality, stub payload test, various refactors * tweak cabal file, add test * add more documentation * doc tweaks * begin refactor to improve CompletionQueue safety * export only thread-safe CQ functions, add registered call creation and other CQ utilities * begin refactor to use GRPCIO monad, fix missing push semaphore, fix mem leak in server calls * switch to explicit Either where needed * add crashing tests, continue fleshing out serverHandleNormalCall * fix haddock error, finish first draft of request handling function * reduce GHC warnings * non-registered client request helpers * initial request/response test working * don't pass tags around; generate where needed * server call bracket functions * correct order of semaphore acquisition and shutdown check * simple debug flag logging, simplify Call type * fix various registered method issues (but still not working) * cleanup * delete old code * remove old todo * use MetadataMap synonym pervasively * more comments * update TODOs * tweak safety caveat * docs tweaks * improve haddocks * add casts to eliminate clang warnings, remove unused function * update options to eliminate cabal warnings * remove outdated todo * remove unneeded exports from CompletionQueue * rename to GRPCIOCallError, re-add create/shutdown exports (needed for Server module) * newtypes for hosts and method names * more newtypes * more debug logging * Fix flag name collision * instrument uses of free * more debug * switch to STM for completion queue stuff * reduce warnings * more debugging, create/destroy call tests * refactor, fix failure cleanup for server call creation. More tests passing. * formatting tweaks
2016-05-24 22:34:50 +02:00
testCompletionQueueCreateDestroy :: TestTree
testCompletionQueueCreateDestroy =
testCase "Create/destroy CQ" $ withGRPC $ \g ->
withCompletionQueue g nop
Begin safe low-level Haskell layer (#7) * grpc_server_request_call * basic slice functionality * rename function to emphasize side effects * add docs * ByteBuffer function bindings * replace unsafeCoerce with more specific function, add docs, tests. * add newtypes for Tag and Reserved void pointers * manually fix request_registered_call binding * use nocode keyword to fix Ptr () problems * decouple copying Slice from freeing slice * Add time ops * remove nocode decls * Start Op module, fix c2hs preprocessing order * metadata manipulation operations * metadata free function, test * helper functions for constructing ops of each type * bindings for op creation functions * finish up Op creation functions, implement Op destruction, add docs. * tweak documentation * rework Op creation functions to work with an array of ops, for ease of use with grpc_call_start_batch * forgot to change return types * wrap hook lines, fix types to op creation functions * implement part of the payload test * hideous, but working, end to end test * bindings for connectivity state checks, split test into two threads * various cleanup * rename Core to Unsafe for emphasis, clean up tests more * begin safe low-level facilities * begin completion queue and server stuff * Finish server start/stop, cq start/stop, add tests * facilities for safely executing op batches * reorganize LowLevel modules, begin explicit export list * client functionality, stub payload test, various refactors * tweak cabal file, add test * add more documentation * doc tweaks * begin refactor to improve CompletionQueue safety * export only thread-safe CQ functions, add registered call creation and other CQ utilities * begin refactor to use GRPCIO monad, fix missing push semaphore, fix mem leak in server calls * switch to explicit Either where needed * add crashing tests, continue fleshing out serverHandleNormalCall * fix haddock error, finish first draft of request handling function * reduce GHC warnings * non-registered client request helpers * initial request/response test working * don't pass tags around; generate where needed * server call bracket functions * correct order of semaphore acquisition and shutdown check * simple debug flag logging, simplify Call type * fix various registered method issues (but still not working) * cleanup * delete old code * remove old todo * use MetadataMap synonym pervasively * more comments * update TODOs * tweak safety caveat * docs tweaks * improve haddocks * add casts to eliminate clang warnings, remove unused function * update options to eliminate cabal warnings * remove outdated todo * remove unneeded exports from CompletionQueue * rename to GRPCIOCallError, re-add create/shutdown exports (needed for Server module) * newtypes for hosts and method names * more newtypes * more debug logging * Fix flag name collision * instrument uses of free * more debug * switch to STM for completion queue stuff * reduce warnings * more debugging, create/destroy call tests * refactor, fix failure cleanup for server call creation. More tests passing. * formatting tweaks
2016-05-24 22:34:50 +02:00
testClientCreateDestroy :: TestTree
testClientCreateDestroy =
clientOnlyTest "start/stop" nop
Begin safe low-level Haskell layer (#7) * grpc_server_request_call * basic slice functionality * rename function to emphasize side effects * add docs * ByteBuffer function bindings * replace unsafeCoerce with more specific function, add docs, tests. * add newtypes for Tag and Reserved void pointers * manually fix request_registered_call binding * use nocode keyword to fix Ptr () problems * decouple copying Slice from freeing slice * Add time ops * remove nocode decls * Start Op module, fix c2hs preprocessing order * metadata manipulation operations * metadata free function, test * helper functions for constructing ops of each type * bindings for op creation functions * finish up Op creation functions, implement Op destruction, add docs. * tweak documentation * rework Op creation functions to work with an array of ops, for ease of use with grpc_call_start_batch * forgot to change return types * wrap hook lines, fix types to op creation functions * implement part of the payload test * hideous, but working, end to end test * bindings for connectivity state checks, split test into two threads * various cleanup * rename Core to Unsafe for emphasis, clean up tests more * begin safe low-level facilities * begin completion queue and server stuff * Finish server start/stop, cq start/stop, add tests * facilities for safely executing op batches * reorganize LowLevel modules, begin explicit export list * client functionality, stub payload test, various refactors * tweak cabal file, add test * add more documentation * doc tweaks * begin refactor to improve CompletionQueue safety * export only thread-safe CQ functions, add registered call creation and other CQ utilities * begin refactor to use GRPCIO monad, fix missing push semaphore, fix mem leak in server calls * switch to explicit Either where needed * add crashing tests, continue fleshing out serverHandleNormalCall * fix haddock error, finish first draft of request handling function * reduce GHC warnings * non-registered client request helpers * initial request/response test working * don't pass tags around; generate where needed * server call bracket functions * correct order of semaphore acquisition and shutdown check * simple debug flag logging, simplify Call type * fix various registered method issues (but still not working) * cleanup * delete old code * remove old todo * use MetadataMap synonym pervasively * more comments * update TODOs * tweak safety caveat * docs tweaks * improve haddocks * add casts to eliminate clang warnings, remove unused function * update options to eliminate cabal warnings * remove outdated todo * remove unneeded exports from CompletionQueue * rename to GRPCIOCallError, re-add create/shutdown exports (needed for Server module) * newtypes for hosts and method names * more newtypes * more debug logging * Fix flag name collision * instrument uses of free * more debug * switch to STM for completion queue stuff * reduce warnings * more debugging, create/destroy call tests * refactor, fix failure cleanup for server call creation. More tests passing. * formatting tweaks
2016-05-24 22:34:50 +02:00
2016-06-08 17:48:28 +02:00
testClientCall :: TestTree
testClientCall =
clientOnlyTest "create/destroy call" $ \c -> do
r <- U.withClientCall c "/foo" 10 $ const $ return $ Right ()
r @?= Right ()
testClientTimeoutNoServer :: TestTree
testClientTimeoutNoServer =
clientOnlyTest "request timeout when server DNE" $ \c -> do
rm <- clientRegisterMethod c "/foo" Normal
r <- clientRequest c rm 1 "Hello" mempty
2016-06-10 00:29:21 +02:00
r @?= Left GRPCIOUnknownError
2016-06-08 17:48:28 +02:00
testServerCreateDestroy :: TestTree
testServerCreateDestroy =
serverOnlyTest "start/stop" [] nop
testServerCall :: TestTree
testServerCall =
serverOnlyTest "create/destroy call" [] $ \s -> do
r <- U.withServerCall s 1 $ const $ return $ Right ()
2016-06-08 17:48:28 +02:00
r @?= Left GRPCIOTimeout
testServerTimeoutNoClient :: TestTree
testServerTimeoutNoClient =
serverOnlyTest "wait timeout when client DNE" [("/foo", Normal)] $ \s -> do
let rm = head (registeredMethods s)
r <- serverHandleNormalCall s rm 1 mempty $ \_ _ ->
return ("", mempty, mempty, StatusDetails "details")
r @?= Left GRPCIOTimeout
-- TODO: fix this test: currently, client seems to hang and server times out,
-- expecting that the client reports an invalid endpoint. Also, investigate
-- intermittent crashes on shorter server timeouts (tried 2, 5 seconds)
testWrongEndpoint :: TestTree
testWrongEndpoint =
csTest "client requests unknown endpoint" client server [("/foo", Normal)]
where
-- TODO: possibly factor out dead-simple client/server construction even
-- further
client c = do
rm <- clientRegisterMethod c "/bar" Normal
r <- clientRequest c rm 1 "Hello!" mempty
r @?= Left (GRPCIOBadStatusCode GrpcStatusDeadlineExceeded
(StatusDetails "Deadline Exceeded"))
server s = do
length (registeredMethods s) @?= 1
let rm = head (registeredMethods s)
r <- serverHandleNormalCall s rm 10 mempty $ \_ _ -> do
return ("reply test", dummyMeta, dummyMeta, StatusDetails "details string")
r @?= Right ()
-- TODO: There seems to be a race here (and in other client/server pairs, of
-- course) about what gets reported when there is a failure. E.g., if one of the
-- Assertions fails in the request processing block for the server, we /may/ get
-- that error reported accurately as a call cancellation on the client, rather
-- than a useful error about the failure on the server. Maybe we'll need to
-- tweak EH behavior / async use.
testPayload :: TestTree
testPayload =
csTest "registered normal request/response" client server [("/foo", Normal)]
where
clientMD = [("foo_key", "foo_val"), ("bar_key", "bar_val")]
client c = do
rm <- clientRegisterMethod c "/foo" Normal
clientRequest c rm 10 "Hello!" clientMD >>= do
checkReqRslt $ \NormalRequestResult{..} -> do
rspCode @?= GrpcStatusOk
rspBody @?= "reply test"
details @?= "details string"
initMD @?= Just dummyMeta
trailMD @?= dummyMeta
server s = do
length (registeredMethods s) @?= 1
let rm = head (registeredMethods s)
r <- serverHandleNormalCall s rm 11 mempty $ \reqBody reqMD -> do
reqBody @?= "Hello!"
checkMD "Server metadata mismatch" clientMD reqMD
return ("reply test", dummyMeta, dummyMeta, StatusDetails "details string")
r @?= Right ()
testPayloadUnregistered :: TestTree
testPayloadUnregistered =
csTest "unregistered normal request/response" client server []
where
client c = do
U.clientRequest c "/foo" 10 "Hello!" mempty >>= do
checkReqRslt $ \NormalRequestResult{..} -> do
rspCode @?= GrpcStatusOk
rspBody @?= "reply test"
details @?= "details string"
server s = do
r <- U.serverHandleNormalCall s 11 mempty $ \body _md meth -> do
body @?= "Hello!"
meth @?= "/foo"
return ("reply test", mempty, "details string")
r @?= Right ()
testGoaway :: TestTree
testGoaway =
csTest "Client handles server shutdown gracefully"
client
server
[("/foo", Normal)]
where
client c = do
rm <- clientRegisterMethod c "/foo" Normal
clientRequest c rm 10 "" mempty
clientRequest c rm 10 "" mempty
lastResult <- clientRequest c rm 1 "" mempty
assertBool "Client handles server shutdown gracefully" $
lastResult == unavailableStatus
||
lastResult == Left GRPCIOTimeout
server s = do
let rm = head (registeredMethods s)
serverHandleNormalCall s rm 11 mempty dummyHandler
serverHandleNormalCall s rm 11 mempty dummyHandler
return ()
testSlowServer :: TestTree
testSlowServer =
csTest "Client handles slow server response" client server [("/foo", Normal)]
where
client c = do
rm <- clientRegisterMethod c "/foo" Normal
result <- clientRequest c rm 1 "" mempty
assertBool "Client gets timeout or deadline exceeded" $
result == Left GRPCIOTimeout
||
result == deadlineExceededStatus
server s = do
let rm = head (registeredMethods s)
serverHandleNormalCall s rm 1 mempty $ \_ _ -> do
threadDelay (2*10^(6 :: Int))
return ("", mempty, mempty, StatusDetails "")
return ()
--------------------------------------------------------------------------------
-- Utilities and helpers
dummyMeta :: M.Map ByteString ByteString
dummyMeta = [("foo","bar")]
dummyHandler :: ByteString -> MetadataMap
-> IO (ByteString, MetadataMap, MetadataMap, StatusDetails)
dummyHandler _ _ = return ("", mempty, mempty, StatusDetails "")
unavailableStatus :: Either GRPCIOError a
unavailableStatus =
Left (GRPCIOBadStatusCode GrpcStatusUnavailable (StatusDetails ""))
deadlineExceededStatus :: Either GRPCIOError a
deadlineExceededStatus =
Left (GRPCIOBadStatusCode GrpcStatusDeadlineExceeded
(StatusDetails "Deadline Exceeded"))
nop :: Monad m => a -> m ()
nop = const (return ())
serverOnlyTest :: TestName
-> [(MethodName, GRPCMethodType)]
-> (Server -> IO ())
-> TestTree
serverOnlyTest nm ms =
testCase ("Server - " ++ nm) . runTestServer . stdTestServer ms
clientOnlyTest :: TestName -> (Client -> IO ()) -> TestTree
clientOnlyTest nm =
testCase ("Client - " ++ nm) . runTestClient . stdTestClient
csTest :: TestName
-> (Client -> IO ())
-> (Server -> IO ())
-> [(MethodName, GRPCMethodType)]
-> TestTree
csTest nm c s ms = csTest' nm (stdTestClient c) (stdTestServer ms s)
csTest' :: TestName -> TestClient -> TestServer -> TestTree
csTest' nm tc ts =
testCase ("Client/Server - " ++ nm)
$ void (s `concurrently` c)
where
-- We use a small delay to give the server a head start
c = threadDelay 100000 >> runTestClient tc
s = runTestServer ts
-- | @checkMD msg expected actual@ fails when keys from @expected@ are not in
-- @actual@, or when values differ for matching keys.
checkMD :: String -> MetadataMap -> MetadataMap -> Assertion
checkMD desc expected actual = do
when (not $ M.null $ expected `diff` actual) $ do
assertEqual desc expected (actual `M.intersection` expected)
where
diff = M.differenceWith $ \a b -> if a == b then Nothing else Just b
checkReqRslt :: Show a => (b -> Assertion) -> Either a b -> Assertion
checkReqRslt = either clientFail
clientFail :: Show a => a -> Assertion
clientFail = assertFailure . ("Client error: " ++). show
data TestClient = TestClient ClientConfig (Client -> IO ())
runTestClient :: TestClient -> IO ()
runTestClient (TestClient conf c) = withGRPC $ \g -> withClient g conf c
stdTestClient :: (Client -> IO ()) -> TestClient
stdTestClient = TestClient stdClientConf
stdClientConf :: ClientConfig
stdClientConf = ClientConfig "localhost" 50051
data TestServer = TestServer ServerConfig (Server -> IO ())
runTestServer :: TestServer -> IO ()
runTestServer (TestServer conf s) = withGRPC $ \g -> withServer g conf s
stdTestServer :: [(MethodName, GRPCMethodType)] -> (Server -> IO ()) -> TestServer
stdTestServer = TestServer . stdServerConf
stdServerConf :: [(MethodName, GRPCMethodType)] -> ServerConfig
stdServerConf = ServerConfig "localhost" 50051