2016-07-27 00:21:35 +02:00
|
|
|
{-# LANGUAGE DataKinds #-}
|
|
|
|
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
|
|
|
{-# LANGUAGE LambdaCase #-}
|
|
|
|
{-# LANGUAGE OverloadedLists #-}
|
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
{-# LANGUAGE PatternSynonyms #-}
|
|
|
|
{-# LANGUAGE RecordWildCards #-}
|
|
|
|
{-# LANGUAGE ScopedTypeVariables #-}
|
|
|
|
{-# LANGUAGE TupleSections #-}
|
|
|
|
{-# LANGUAGE ViewPatterns #-}
|
|
|
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
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-13 22:51:53 +02:00
|
|
|
module 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
|
|
|
|
2016-06-08 18:50:57 +02:00
|
|
|
import Control.Concurrent (threadDelay)
|
2016-05-24 23:34:23 +02:00
|
|
|
import Control.Concurrent.Async
|
2016-05-26 00:41:37 +02:00
|
|
|
import Control.Monad
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
import Control.Monad.Managed
|
2016-06-22 22:07:38 +02:00
|
|
|
import Data.ByteString (ByteString,
|
|
|
|
isPrefixOf,
|
|
|
|
isSuffixOf)
|
2016-08-17 18:55:06 +02:00
|
|
|
import Data.List (find)
|
2016-08-01 21:38:35 +02:00
|
|
|
import qualified Data.Map.Strict as M
|
|
|
|
import qualified Data.Set as S
|
|
|
|
import GHC.Exts (fromList, toList)
|
2016-05-24 23:39:53 +02:00
|
|
|
import Network.GRPC.LowLevel
|
2016-07-29 22:18:08 +02:00
|
|
|
import Network.GRPC.LowLevel.GRPC (threadDelaySecs)
|
2016-06-22 19:41:14 +02:00
|
|
|
import qualified Network.GRPC.LowLevel.Call.Unregistered as U
|
2016-06-08 21:38:01 +02:00
|
|
|
import qualified Network.GRPC.LowLevel.Client.Unregistered as U
|
|
|
|
import qualified Network.GRPC.LowLevel.Server.Unregistered as U
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
import qualified Pipes as P
|
2016-05-24 23:39:53 +02:00
|
|
|
import Test.Tasty
|
2016-06-08 18:50:57 +02:00
|
|
|
import Test.Tasty.HUnit as HU (Assertion,
|
2016-06-13 16:25:32 +02:00
|
|
|
assertBool,
|
2016-06-08 18:50:57 +02:00
|
|
|
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"
|
2016-06-08 20:12:07 +02:00
|
|
|
[ testGRPCBracket
|
|
|
|
, testCompletionQueueCreateDestroy
|
|
|
|
, testClientCreateDestroy
|
2016-06-08 17:48:28 +02:00
|
|
|
, testClientCall
|
2016-06-08 20:12:07 +02:00
|
|
|
, testClientTimeoutNoServer
|
2016-06-08 17:48:28 +02:00
|
|
|
, testServerCreateDestroy
|
2016-06-16 17:23:54 +02:00
|
|
|
, testMixRegisteredUnregistered
|
2016-06-08 20:12:07 +02:00
|
|
|
, testPayload
|
2016-08-17 18:55:06 +02:00
|
|
|
, testSSL
|
|
|
|
, testAuthMetadataTransfer
|
|
|
|
, testServerAuthProcessorCancel
|
2016-06-08 20:12:07 +02:00
|
|
|
, testPayloadUnregistered
|
2016-06-13 22:51:53 +02:00
|
|
|
, testServerCancel
|
2016-06-13 16:25:32 +02:00
|
|
|
, testGoaway
|
|
|
|
, testSlowServer
|
2016-06-16 21:45:55 +02:00
|
|
|
, testServerCallExpirationCheck
|
2016-06-22 22:07:38 +02:00
|
|
|
, testCustomUserAgent
|
|
|
|
, testClientCompression
|
|
|
|
, testClientServerCompression
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
, testClientStreaming
|
2016-07-14 18:53:28 +02:00
|
|
|
, testClientStreamingUnregistered
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
, testServerStreaming
|
2016-07-14 18:53:28 +02:00
|
|
|
, testServerStreamingUnregistered
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
, testBiDiStreaming
|
2016-07-14 18:53:28 +02:00
|
|
|
, testBiDiStreamingUnregistered
|
2016-06-08 20:12:07 +02:00
|
|
|
]
|
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
|
2016-06-08 20:12:07 +02:00
|
|
|
testGRPCBracket =
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
testCase "Start/stop GRPC" $ runManaged $ void mgdGRPC
|
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 =
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
testCase "Create/destroy CQ" $ runManaged $ do
|
|
|
|
g <- mgdGRPC
|
|
|
|
liftIO (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 =
|
2016-06-08 20:12:07 +02:00
|
|
|
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 20:12:07 +02:00
|
|
|
testClientTimeoutNoServer :: TestTree
|
|
|
|
testClientTimeoutNoServer =
|
|
|
|
clientOnlyTest "request timeout when server DNE" $ \c -> do
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
rm <- clientRegisterMethodNormal c "/foo"
|
2016-06-08 21:38:01 +02:00
|
|
|
r <- clientRequest c rm 1 "Hello" mempty
|
2016-06-22 19:41:14 +02:00
|
|
|
r @?= Left GRPCIOTimeout
|
2016-06-08 20:12:07 +02:00
|
|
|
|
2016-06-08 17:48:28 +02:00
|
|
|
testServerCreateDestroy :: TestTree
|
|
|
|
testServerCreateDestroy =
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
serverOnlyTest "start/stop" (["/foo"],[],[],[]) nop
|
2016-06-08 17:48:28 +02:00
|
|
|
|
2016-06-16 17:23:54 +02:00
|
|
|
testMixRegisteredUnregistered :: TestTree
|
|
|
|
testMixRegisteredUnregistered =
|
|
|
|
csTest "server uses unregistered calls to handle unknown endpoints"
|
|
|
|
client
|
|
|
|
server
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
(["/foo"],[],[],[])
|
2016-06-16 17:23:54 +02:00
|
|
|
where
|
|
|
|
client c = do
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
rm1 <- clientRegisterMethodNormal c "/foo"
|
|
|
|
rm2 <- clientRegisterMethodNormal c "/bar"
|
2016-06-16 17:23:54 +02:00
|
|
|
clientRequest c rm1 1 "Hello" mempty >>= do
|
|
|
|
checkReqRslt $ \NormalRequestResult{..} -> do
|
|
|
|
rspBody @?= "reply test"
|
2016-06-23 23:34:36 +02:00
|
|
|
initMD @?= dummyMeta
|
2016-06-16 17:23:54 +02:00
|
|
|
trailMD @?= dummyMeta
|
|
|
|
clientRequest c rm2 1 "bad endpoint" mempty >>= do
|
|
|
|
checkReqRslt $ \NormalRequestResult{..} -> do
|
|
|
|
rspBody @?= ""
|
|
|
|
return ()
|
|
|
|
server s = do
|
|
|
|
concurrently regThread unregThread
|
|
|
|
return ()
|
|
|
|
where regThread = do
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
let rm = head (normalMethods s)
|
2016-07-27 00:21:35 +02:00
|
|
|
_r <- serverHandleNormalCall s rm dummyMeta $ \c -> do
|
2016-07-15 01:33:56 +02:00
|
|
|
payload c @?= "Hello"
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
return ("reply test", dummyMeta, StatusOk, "")
|
2016-06-16 17:23:54 +02:00
|
|
|
return ()
|
|
|
|
unregThread = do
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
U.serverHandleNormalCall s mempty $ \call _ -> do
|
2016-06-22 19:41:14 +02:00
|
|
|
U.callMethod call @?= "/bar"
|
2016-06-16 17:23:54 +02:00
|
|
|
return ("", mempty, StatusOk,
|
|
|
|
StatusDetails "Wrong endpoint")
|
|
|
|
return ()
|
2016-06-08 20:12:07 +02:00
|
|
|
|
|
|
|
-- 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 =
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
csTest "registered normal request/response" client server (["/foo"],[],[],[])
|
2016-06-08 20:12:07 +02:00
|
|
|
where
|
2016-08-01 21:38:35 +02:00
|
|
|
clientMD = [ ("foo_key", "foo_val")
|
|
|
|
, ("bar_key", "bar_val")
|
|
|
|
, ("bar_key", "bar_repeated_val")]
|
2016-06-08 20:12:07 +02:00
|
|
|
client c = do
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
rm <- clientRegisterMethodNormal c "/foo"
|
2016-06-08 21:38:01 +02:00
|
|
|
clientRequest c rm 10 "Hello!" clientMD >>= do
|
2016-06-08 20:12:07 +02:00
|
|
|
checkReqRslt $ \NormalRequestResult{..} -> do
|
2016-06-16 17:23:54 +02:00
|
|
|
rspCode @?= StatusOk
|
2016-06-08 20:12:07 +02:00
|
|
|
rspBody @?= "reply test"
|
|
|
|
details @?= "details string"
|
2016-06-23 23:34:36 +02:00
|
|
|
initMD @?= dummyMeta
|
2016-06-08 20:12:07 +02:00
|
|
|
trailMD @?= dummyMeta
|
|
|
|
server s = do
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
let rm = head (normalMethods s)
|
2016-07-15 01:33:56 +02:00
|
|
|
r <- serverHandleNormalCall s rm dummyMeta $ \c -> do
|
|
|
|
payload c @?= "Hello!"
|
|
|
|
checkMD "Server metadata mismatch" clientMD (metadata c)
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
return ("reply test", dummyMeta, StatusOk, "details string")
|
2016-06-13 22:51:53 +02:00
|
|
|
r @?= Right ()
|
|
|
|
|
2016-08-17 18:55:06 +02:00
|
|
|
testSSL :: TestTree
|
|
|
|
testSSL =
|
|
|
|
csTest' "request/response using SSL" client server
|
|
|
|
where
|
|
|
|
clientConf = stdClientConf
|
|
|
|
{clientSSLConfig = Just (ClientSSLConfig
|
|
|
|
(Just "tests/ssl/localhost.crt")
|
|
|
|
Nothing
|
|
|
|
Nothing)
|
|
|
|
}
|
|
|
|
client = TestClient clientConf $ \c -> do
|
|
|
|
rm <- clientRegisterMethodNormal c "/foo"
|
|
|
|
clientRequest c rm 10 "hi" mempty >>= do
|
|
|
|
checkReqRslt $ \NormalRequestResult{..} -> do
|
|
|
|
rspCode @?= StatusOk
|
|
|
|
rspBody @?= "reply test"
|
|
|
|
|
|
|
|
serverConf = defServerConf
|
|
|
|
{sslConfig = Just (ServerSSLConfig
|
|
|
|
Nothing
|
|
|
|
"tests/ssl/localhost.key"
|
|
|
|
"tests/ssl/localhost.crt"
|
|
|
|
SslDontRequestClientCertificate
|
|
|
|
Nothing)
|
|
|
|
}
|
|
|
|
server = TestServer serverConf $ \s -> do
|
|
|
|
r <- U.serverHandleNormalCall s mempty $ \U.ServerCall{..} body -> do
|
|
|
|
body @?= "hi"
|
|
|
|
return ("reply test", mempty, StatusOk, "")
|
|
|
|
r @?= Right ()
|
|
|
|
|
|
|
|
-- NOTE: With auth plugin tests, if an auth plugin decides someone isn't
|
|
|
|
-- authenticated, then the call never happens from the perspective of
|
|
|
|
-- the server, so the server will continue to block waiting for a call. So, if
|
|
|
|
-- these tests hang forever, it's because auth failed and the server is still
|
|
|
|
-- waiting for a successfully authenticated call to come in.
|
|
|
|
|
|
|
|
testServerAuthProcessorCancel :: TestTree
|
|
|
|
testServerAuthProcessorCancel =
|
|
|
|
csTest' "request rejection by auth processor" client server
|
|
|
|
where
|
|
|
|
clientConf = stdClientConf
|
|
|
|
{clientSSLConfig = Just (ClientSSLConfig
|
|
|
|
(Just "tests/ssl/localhost.crt")
|
|
|
|
Nothing
|
|
|
|
Nothing)
|
|
|
|
}
|
|
|
|
client = TestClient clientConf $ \c -> do
|
|
|
|
rm <- clientRegisterMethodNormal c "/foo"
|
|
|
|
r <- clientRequest c rm 10 "hi" mempty
|
|
|
|
-- TODO: using checkReqRslt on this first result causes the test to hang!
|
|
|
|
r @?= Left (GRPCIOBadStatusCode StatusUnauthenticated "denied!")
|
|
|
|
clientRequest c rm 10 "hi" [("foo","bar")] >>= do
|
|
|
|
checkReqRslt $ \NormalRequestResult{..} -> do
|
|
|
|
rspCode @?= StatusOk
|
|
|
|
rspBody @?= "reply test"
|
|
|
|
|
|
|
|
serverProcessor = Just $ \_ m -> do
|
|
|
|
let (status, details) = if M.member "foo" (unMap m)
|
|
|
|
then (StatusOk, "")
|
|
|
|
else (StatusUnauthenticated, "denied!")
|
|
|
|
return $ AuthProcessorResult mempty mempty status details
|
|
|
|
|
|
|
|
serverConf = defServerConf
|
|
|
|
{sslConfig = Just (ServerSSLConfig
|
|
|
|
Nothing
|
|
|
|
"tests/ssl/localhost.key"
|
|
|
|
"tests/ssl/localhost.crt"
|
|
|
|
SslDontRequestClientCertificate
|
|
|
|
serverProcessor)
|
|
|
|
}
|
|
|
|
server = TestServer serverConf $ \s -> do
|
|
|
|
r <- U.serverHandleNormalCall s mempty $ \U.ServerCall{..} body -> do
|
|
|
|
checkMD "Handler only sees requests with good metadata"
|
|
|
|
[("foo","bar")]
|
|
|
|
metadata
|
|
|
|
return ("reply test", mempty, StatusOk, "")
|
|
|
|
r @?= Right ()
|
|
|
|
|
|
|
|
testAuthMetadataTransfer :: TestTree
|
|
|
|
testAuthMetadataTransfer =
|
|
|
|
csTest' "Auth metadata changes sent from client to server" client server
|
|
|
|
where
|
|
|
|
plugin :: ClientMetadataCreate
|
|
|
|
plugin authMetaCtx = do
|
|
|
|
let authCtx = (channelAuthContext authMetaCtx)
|
|
|
|
|
|
|
|
addAuthProperty authCtx (AuthProperty "foo1" "bar1")
|
|
|
|
newProps <- getAuthProperties authCtx
|
|
|
|
let addedProp = find ((== "foo1") . authPropName) newProps
|
|
|
|
addedProp @?= Just (AuthProperty "foo1" "bar1")
|
|
|
|
return $ ClientMetadataCreateResult [("foo","bar")] StatusOk ""
|
|
|
|
clientConf = stdClientConf
|
|
|
|
{clientSSLConfig = Just (ClientSSLConfig
|
|
|
|
(Just "tests/ssl/localhost.crt")
|
|
|
|
Nothing
|
|
|
|
(Just plugin))
|
|
|
|
}
|
|
|
|
client = TestClient clientConf $ \c -> do
|
|
|
|
rm <- clientRegisterMethodNormal c "/foo"
|
|
|
|
clientRequest c rm 10 "hi" mempty >>= do
|
|
|
|
checkReqRslt $ \NormalRequestResult{..} -> do
|
|
|
|
rspCode @?= StatusOk
|
|
|
|
rspBody @?= "reply test"
|
|
|
|
|
|
|
|
serverProcessor :: Maybe ProcessMeta
|
|
|
|
serverProcessor = Just $ \authCtx m -> do
|
|
|
|
let expected = fromList [("foo","bar")]
|
|
|
|
|
|
|
|
props <- getAuthProperties authCtx
|
|
|
|
let clientProp = find ((== "foo1") . authPropName) props
|
|
|
|
assertBool "server plugin doesn't see auth properties set by client"
|
|
|
|
(clientProp == Nothing)
|
|
|
|
checkMD "server plugin sees metadata added by client plugin" expected m
|
|
|
|
return $ AuthProcessorResult mempty mempty StatusOk ""
|
|
|
|
|
|
|
|
serverConf = defServerConf
|
|
|
|
{sslConfig = Just (ServerSSLConfig
|
|
|
|
Nothing
|
|
|
|
"tests/ssl/localhost.key"
|
|
|
|
"tests/ssl/localhost.crt"
|
|
|
|
SslDontRequestClientCertificate
|
|
|
|
serverProcessor)
|
|
|
|
}
|
|
|
|
server = TestServer serverConf $ \s -> do
|
|
|
|
r <- U.serverHandleNormalCall s mempty $ \U.ServerCall{..} body -> do
|
|
|
|
body @?= "hi"
|
|
|
|
return ("reply test", mempty, StatusOk, "")
|
|
|
|
r @?= Right ()
|
|
|
|
|
|
|
|
-- TODO: auth metadata doesn't propagate from parent calls to child calls.
|
|
|
|
-- Once we implement our own system for doing so, update this test and add it
|
|
|
|
-- to the tests list.
|
|
|
|
testAuthMetadataPropagate :: TestTree
|
|
|
|
testAuthMetadataPropagate = testCase "auth metadata inherited by children" $ do
|
|
|
|
c <- async client
|
|
|
|
s1 <- async server
|
|
|
|
s2 <- async server2
|
|
|
|
wait c
|
|
|
|
wait s1
|
|
|
|
wait s2
|
|
|
|
return ()
|
|
|
|
where
|
|
|
|
clientPlugin _ =
|
|
|
|
return $ ClientMetadataCreateResult [("foo","bar")] StatusOk ""
|
|
|
|
clientConf = stdClientConf
|
|
|
|
{clientSSLConfig = Just (ClientSSLConfig
|
|
|
|
(Just "tests/ssl/localhost.crt")
|
|
|
|
Nothing
|
|
|
|
(Just clientPlugin))
|
|
|
|
}
|
|
|
|
client = do
|
|
|
|
threadDelaySecs 3
|
|
|
|
withGRPC $ \g -> withClient g clientConf $ \c -> do
|
|
|
|
rm <- clientRegisterMethodNormal c "/foo"
|
|
|
|
clientRequest c rm 10 "hi" mempty >>= do
|
|
|
|
checkReqRslt $ \NormalRequestResult{..} -> do
|
|
|
|
rspCode @?= StatusOk
|
|
|
|
rspBody @?= "reply test"
|
|
|
|
|
|
|
|
server1ServerPlugin _ctx md = do
|
|
|
|
checkMD "server1 sees client's auth metadata." [("foo","bar")] md
|
|
|
|
-- TODO: add response meta to check, and consume meta to see what happens.
|
|
|
|
return $ AuthProcessorResult mempty mempty StatusOk ""
|
|
|
|
|
|
|
|
server1ServerConf = defServerConf
|
|
|
|
{sslConfig = Just (ServerSSLConfig
|
|
|
|
Nothing
|
|
|
|
"tests/ssl/localhost.key"
|
|
|
|
"tests/ssl/localhost.crt"
|
|
|
|
SslDontRequestClientCertificate
|
|
|
|
(Just server1ServerPlugin)),
|
|
|
|
methodsToRegisterNormal = ["/foo"]
|
|
|
|
}
|
|
|
|
|
|
|
|
server1ClientPlugin _ =
|
|
|
|
return $ ClientMetadataCreateResult [("foo1","bar1")] StatusOk ""
|
|
|
|
|
|
|
|
server1ClientConf = stdClientConf
|
|
|
|
{clientSSLConfig = Just (ClientSSLConfig
|
|
|
|
(Just "tests/ssl/localhost.crt")
|
|
|
|
Nothing
|
|
|
|
(Just server1ClientPlugin)),
|
|
|
|
serverPort = 50052
|
|
|
|
}
|
|
|
|
|
|
|
|
server = do
|
|
|
|
threadDelaySecs 2
|
|
|
|
withGRPC $ \g -> withServer g server1ServerConf $ \s ->
|
|
|
|
withClient g server1ClientConf $ \c -> do
|
|
|
|
let rm = head (normalMethods s)
|
|
|
|
serverHandleNormalCall s rm mempty $ \call -> do
|
|
|
|
rmc <- clientRegisterMethodNormal c "/foo"
|
|
|
|
res <- clientRequestParent c (Just call) rmc 10 "hi" mempty
|
|
|
|
case res of
|
|
|
|
Left _ ->
|
|
|
|
error "got bad result from server2"
|
|
|
|
Right (NormalRequestResult{..}) ->
|
|
|
|
return (rspBody, mempty, StatusOk, "")
|
|
|
|
|
|
|
|
server2ServerPlugin _ctx md = do
|
|
|
|
print md
|
|
|
|
checkMD "server2 sees server1's auth metadata." [("foo1","bar1")] md
|
|
|
|
--TODO: this assert fails
|
|
|
|
checkMD "server2 sees client's auth metadata." [("foo","bar")] md
|
|
|
|
return $ AuthProcessorResult mempty mempty StatusOk ""
|
|
|
|
|
|
|
|
server2ServerConf = defServerConf
|
|
|
|
{sslConfig = Just (ServerSSLConfig
|
|
|
|
Nothing
|
|
|
|
"tests/ssl/localhost.key"
|
|
|
|
"tests/ssl/localhost.crt"
|
|
|
|
SslDontRequestClientCertificate
|
|
|
|
(Just server2ServerPlugin)),
|
|
|
|
methodsToRegisterNormal = ["/foo"],
|
|
|
|
port = 50052
|
|
|
|
}
|
|
|
|
|
|
|
|
server2 = withGRPC $ \g -> withServer g server2ServerConf $ \s -> do
|
|
|
|
let rm = head (normalMethods s)
|
|
|
|
serverHandleNormalCall s rm mempty $ \call -> do
|
|
|
|
return ("server2 reply", mempty, StatusOk, "")
|
|
|
|
|
2016-06-13 22:51:53 +02:00
|
|
|
testServerCancel :: TestTree
|
|
|
|
testServerCancel =
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
csTest "server cancel call" client server (["/foo"],[],[],[])
|
2016-06-13 22:51:53 +02:00
|
|
|
where
|
|
|
|
client c = do
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
rm <- clientRegisterMethodNormal c "/foo"
|
2016-08-05 18:29:20 +02:00
|
|
|
Left (GRPCIOBadStatusCode s _) <- clientRequest c rm 10 "" mempty
|
|
|
|
s @?= StatusCancelled
|
2016-06-13 22:51:53 +02:00
|
|
|
server s = do
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
let rm = head (normalMethods s)
|
2016-07-15 01:33:56 +02:00
|
|
|
r <- serverHandleNormalCall s rm mempty $ \c -> do
|
2016-06-16 17:23:54 +02:00
|
|
|
serverCallCancel c StatusCancelled ""
|
2016-06-22 19:41:14 +02:00
|
|
|
return (mempty, mempty, StatusCancelled, "")
|
2016-06-08 20:12:07 +02:00
|
|
|
r @?= Right ()
|
|
|
|
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
testServerStreaming :: TestTree
|
|
|
|
testServerStreaming =
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
csTest "server streaming" client server ([],[],["/feed"],[])
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
where
|
|
|
|
clientInitMD = [("client","initmd")]
|
|
|
|
serverInitMD = [("server","initmd")]
|
|
|
|
clientPay = "FEED ME!"
|
|
|
|
pays = ["ONE", "TWO", "THREE", "FOUR"] :: [ByteString]
|
|
|
|
|
|
|
|
client c = do
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
rm <- clientRegisterMethodServerStreaming c "/feed"
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
eea <- clientReader c rm 10 clientPay clientInitMD $ \initMD recv -> do
|
2016-08-10 23:14:41 +02:00
|
|
|
checkMD "Server initial metadata mismatch" serverInitMD initMD
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
forM_ pays $ \p -> recv `is` Right (Just p)
|
|
|
|
recv `is` Right Nothing
|
|
|
|
eea @?= Right (dummyMeta, StatusOk, "dtls")
|
|
|
|
|
|
|
|
server s = do
|
|
|
|
let rm = head (sstreamingMethods s)
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
r <- serverWriter s rm serverInitMD $ \sc send -> do
|
2016-08-10 23:14:41 +02:00
|
|
|
checkMD "Server request metadata mismatch" clientInitMD (metadata sc)
|
|
|
|
payload sc @?= clientPay
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
forM_ pays $ \p -> send p `is` Right ()
|
|
|
|
return (dummyMeta, StatusOk, "dtls")
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
r @?= Right ()
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
|
2016-07-14 18:53:28 +02:00
|
|
|
-- TODO: these unregistered streaming tests are basically the same as the
|
|
|
|
-- registered ones. Reduce duplication.
|
|
|
|
-- TODO: Once client-side unregistered streaming functions are added, switch
|
|
|
|
-- to using them in these tests.
|
|
|
|
testServerStreamingUnregistered :: TestTree
|
|
|
|
testServerStreamingUnregistered =
|
|
|
|
csTest "unregistered server streaming" client server ([],[],[],[])
|
|
|
|
where
|
|
|
|
clientInitMD = [("client","initmd")]
|
|
|
|
serverInitMD = [("server","initmd")]
|
|
|
|
clientPay = "FEED ME!"
|
|
|
|
pays = ["ONE", "TWO", "THREE", "FOUR"] :: [ByteString]
|
|
|
|
|
|
|
|
client c = do
|
|
|
|
rm <- clientRegisterMethodServerStreaming c "/feed"
|
|
|
|
eea <- clientReader c rm 10 clientPay clientInitMD $ \initMD recv -> do
|
2016-08-10 23:14:41 +02:00
|
|
|
checkMD "Server initial metadata mismatch" serverInitMD initMD
|
2016-07-14 18:53:28 +02:00
|
|
|
forM_ pays $ \p -> recv `is` Right (Just p)
|
|
|
|
recv `is` Right Nothing
|
|
|
|
eea @?= Right (dummyMeta, StatusOk, "dtls")
|
|
|
|
|
|
|
|
server s = U.withServerCallAsync s $ \call -> do
|
|
|
|
r <- U.serverWriter s call serverInitMD $ \sc send -> do
|
2016-08-10 23:14:41 +02:00
|
|
|
checkMD "Server request metadata mismatch" clientInitMD (metadata sc)
|
|
|
|
payload sc @?= clientPay
|
2016-07-14 18:53:28 +02:00
|
|
|
forM_ pays $ \p -> send p `is` Right ()
|
|
|
|
return (dummyMeta, StatusOk, "dtls")
|
|
|
|
r @?= Right ()
|
|
|
|
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
testClientStreaming :: TestTree
|
|
|
|
testClientStreaming =
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
csTest "client streaming" client server ([],["/slurp"],[],[])
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
where
|
|
|
|
clientInitMD = [("a","b")]
|
|
|
|
serverInitMD = [("x","y")]
|
|
|
|
trailMD = dummyMeta
|
|
|
|
serverRsp = "serverReader reply"
|
|
|
|
serverDtls = "deets"
|
|
|
|
serverStatus = StatusOk
|
|
|
|
pays = ["P_ONE", "P_TWO", "P_THREE"] :: [ByteString]
|
|
|
|
|
|
|
|
client c = do
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
rm <- clientRegisterMethodClientStreaming c "/slurp"
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
eea <- clientWriter c rm 10 clientInitMD $ \send -> do
|
|
|
|
-- liftIO $ checkMD "Server initial metadata mismatch" serverInitMD initMD
|
|
|
|
forM_ pays $ \p -> send p `is` Right ()
|
|
|
|
eea @?= Right (Just serverRsp, serverInitMD, trailMD, serverStatus, serverDtls)
|
|
|
|
|
|
|
|
server s = do
|
|
|
|
let rm = head (cstreamingMethods s)
|
|
|
|
eea <- serverReader s rm serverInitMD $ \sc recv -> do
|
2016-08-10 23:14:41 +02:00
|
|
|
checkMD "Client request metadata mismatch" clientInitMD (metadata sc)
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
forM_ pays $ \p -> recv `is` Right (Just p)
|
|
|
|
recv `is` Right Nothing
|
|
|
|
return (Just serverRsp, trailMD, serverStatus, serverDtls)
|
|
|
|
eea @?= Right ()
|
|
|
|
|
2016-07-14 18:53:28 +02:00
|
|
|
testClientStreamingUnregistered :: TestTree
|
|
|
|
testClientStreamingUnregistered =
|
|
|
|
csTest "unregistered client streaming" client server ([],[],[],[])
|
|
|
|
where
|
|
|
|
clientInitMD = [("a","b")]
|
|
|
|
serverInitMD = [("x","y")]
|
|
|
|
trailMD = dummyMeta
|
|
|
|
serverRsp = "serverReader reply"
|
|
|
|
serverDtls = "deets"
|
|
|
|
serverStatus = StatusOk
|
|
|
|
pays = ["P_ONE", "P_TWO", "P_THREE"] :: [ByteString]
|
|
|
|
|
|
|
|
client c = do
|
|
|
|
rm <- clientRegisterMethodClientStreaming c "/slurp"
|
|
|
|
eea <- clientWriter c rm 10 clientInitMD $ \send -> do
|
|
|
|
-- liftIO $ checkMD "Server initial metadata mismatch" serverInitMD initMD
|
|
|
|
forM_ pays $ \p -> send p `is` Right ()
|
|
|
|
eea @?= Right (Just serverRsp, serverInitMD, trailMD, serverStatus, serverDtls)
|
|
|
|
|
|
|
|
server s = U.withServerCallAsync s $ \call -> do
|
|
|
|
eea <- U.serverReader s call serverInitMD $ \sc recv -> do
|
2016-08-10 23:14:41 +02:00
|
|
|
checkMD "Client request metadata mismatch" clientInitMD (metadata sc)
|
2016-07-14 18:53:28 +02:00
|
|
|
forM_ pays $ \p -> recv `is` Right (Just p)
|
|
|
|
recv `is` Right Nothing
|
|
|
|
return (Just serverRsp, trailMD, serverStatus, serverDtls)
|
|
|
|
eea @?= Right ()
|
|
|
|
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
testBiDiStreaming :: TestTree
|
|
|
|
testBiDiStreaming =
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
csTest "bidirectional streaming" client server ([],[],[],["/bidi"])
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
where
|
|
|
|
clientInitMD = [("bidi-streaming","client")]
|
|
|
|
serverInitMD = [("bidi-streaming","server")]
|
|
|
|
trailMD = dummyMeta
|
|
|
|
serverStatus = StatusOk
|
|
|
|
serverDtls = "deets"
|
|
|
|
|
|
|
|
client c = do
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
rm <- clientRegisterMethodBiDiStreaming c "/bidi"
|
2016-08-15 19:55:40 +02:00
|
|
|
eea <- clientRW c rm 10 clientInitMD $ \getMD recv send writesDone -> do
|
|
|
|
either clientFail (checkMD "Server rsp metadata mismatch" serverInitMD) =<< getMD
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
send "cw0" `is` Right ()
|
|
|
|
recv `is` Right (Just "sw0")
|
|
|
|
send "cw1" `is` Right ()
|
|
|
|
recv `is` Right (Just "sw1")
|
|
|
|
recv `is` Right (Just "sw2")
|
2016-08-09 18:30:47 +02:00
|
|
|
writesDone `is` Right ()
|
|
|
|
recv `is` Right Nothing
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
eea @?= Right (trailMD, serverStatus, serverDtls)
|
|
|
|
|
|
|
|
server s = do
|
|
|
|
let rm = head (bidiStreamingMethods s)
|
|
|
|
eea <- serverRW s rm serverInitMD $ \sc recv send -> do
|
2016-08-10 23:14:41 +02:00
|
|
|
checkMD "Client request metadata mismatch" clientInitMD (metadata sc)
|
2016-07-14 18:53:28 +02:00
|
|
|
recv `is` Right (Just "cw0")
|
|
|
|
send "sw0" `is` Right ()
|
|
|
|
recv `is` Right (Just "cw1")
|
|
|
|
send "sw1" `is` Right ()
|
|
|
|
send "sw2" `is` Right ()
|
|
|
|
recv `is` Right Nothing
|
|
|
|
return (trailMD, serverStatus, serverDtls)
|
|
|
|
eea @?= Right ()
|
|
|
|
|
|
|
|
testBiDiStreamingUnregistered :: TestTree
|
|
|
|
testBiDiStreamingUnregistered =
|
|
|
|
csTest "unregistered bidirectional streaming" client server ([],[],[],[])
|
|
|
|
where
|
|
|
|
clientInitMD = [("bidi-streaming","client")]
|
|
|
|
serverInitMD = [("bidi-streaming","server")]
|
|
|
|
trailMD = dummyMeta
|
|
|
|
serverStatus = StatusOk
|
|
|
|
serverDtls = "deets"
|
|
|
|
|
|
|
|
client c = do
|
|
|
|
rm <- clientRegisterMethodBiDiStreaming c "/bidi"
|
2016-08-15 19:55:40 +02:00
|
|
|
eea <- clientRW c rm 10 clientInitMD $ \getMD recv send writesDone -> do
|
|
|
|
either clientFail (checkMD "Server rsp metadata mismatch" serverInitMD) =<< getMD
|
2016-07-14 18:53:28 +02:00
|
|
|
send "cw0" `is` Right ()
|
|
|
|
recv `is` Right (Just "sw0")
|
|
|
|
send "cw1" `is` Right ()
|
|
|
|
recv `is` Right (Just "sw1")
|
|
|
|
recv `is` Right (Just "sw2")
|
2016-08-09 18:30:47 +02:00
|
|
|
writesDone `is` Right ()
|
|
|
|
recv `is` Right Nothing
|
2016-07-14 18:53:28 +02:00
|
|
|
eea @?= Right (trailMD, serverStatus, serverDtls)
|
|
|
|
|
|
|
|
server s = U.withServerCallAsync s $ \call -> do
|
|
|
|
eea <- U.serverRW s call serverInitMD $ \sc recv send -> do
|
2016-08-09 18:30:47 +02:00
|
|
|
checkMD "Client request metadata mismatch" clientInitMD (metadata sc)
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
recv `is` Right (Just "cw0")
|
|
|
|
send "sw0" `is` Right ()
|
|
|
|
recv `is` Right (Just "cw1")
|
|
|
|
send "sw1" `is` Right ()
|
|
|
|
send "sw2" `is` Right ()
|
|
|
|
recv `is` Right Nothing
|
|
|
|
return (trailMD, serverStatus, serverDtls)
|
|
|
|
eea @?= Right ()
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Unregistered tests
|
|
|
|
|
|
|
|
testClientCall :: TestTree
|
|
|
|
testClientCall =
|
|
|
|
clientOnlyTest "create/destroy call" $ \c -> do
|
|
|
|
r <- U.withClientCall c "/foo" 10 $ const $ return $ Right ()
|
|
|
|
r @?= Right ()
|
|
|
|
|
|
|
|
testServerCall :: TestTree
|
|
|
|
testServerCall =
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
serverOnlyTest "create/destroy call" ([],[],[],[]) $ \s -> do
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
r <- U.withServerCall s $ const $ return $ Right ()
|
|
|
|
r @?= Left GRPCIOTimeout
|
|
|
|
|
2016-06-08 20:12:07 +02:00
|
|
|
testPayloadUnregistered :: TestTree
|
|
|
|
testPayloadUnregistered =
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
csTest "unregistered normal request/response" client server ([],[],[],[])
|
2016-06-08 20:12:07 +02:00
|
|
|
where
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
client c =
|
2016-06-08 21:38:01 +02:00
|
|
|
U.clientRequest c "/foo" 10 "Hello!" mempty >>= do
|
2016-06-08 20:12:07 +02:00
|
|
|
checkReqRslt $ \NormalRequestResult{..} -> do
|
2016-06-16 17:23:54 +02:00
|
|
|
rspCode @?= StatusOk
|
2016-06-08 20:12:07 +02:00
|
|
|
rspBody @?= "reply test"
|
|
|
|
details @?= "details string"
|
|
|
|
server s = do
|
2016-06-22 19:41:14 +02:00
|
|
|
r <- U.serverHandleNormalCall s mempty $ \U.ServerCall{..} body -> do
|
2016-06-08 20:12:07 +02:00
|
|
|
body @?= "Hello!"
|
2016-06-22 19:41:14 +02:00
|
|
|
callMethod @?= "/foo"
|
2016-06-16 17:23:54 +02:00
|
|
|
return ("reply test", mempty, StatusOk, "details string")
|
2016-06-08 20:12:07 +02:00
|
|
|
r @?= Right ()
|
2016-05-24 23:34:23 +02:00
|
|
|
|
2016-06-13 16:25:32 +02:00
|
|
|
testGoaway :: TestTree
|
|
|
|
testGoaway =
|
|
|
|
csTest "Client handles server shutdown gracefully"
|
|
|
|
client
|
|
|
|
server
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
(["/foo"],[],[],[])
|
2016-06-13 16:25:32 +02:00
|
|
|
where
|
|
|
|
client c = do
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
rm <- clientRegisterMethodNormal c "/foo"
|
2016-06-13 16:25:32 +02:00
|
|
|
clientRequest c rm 10 "" mempty
|
|
|
|
clientRequest c rm 10 "" mempty
|
2016-12-20 22:57:38 +01:00
|
|
|
eer <- clientRequest c rm 1 "" mempty
|
|
|
|
assertBool "Client handles server shutdown gracefully" $ case eer of
|
|
|
|
Left (GRPCIOBadStatusCode StatusUnavailable _) -> True
|
|
|
|
Left (GRPCIOBadStatusCode StatusDeadlineExceeded "Deadline Exceeded") -> True
|
|
|
|
Left GRPCIOTimeout -> True
|
|
|
|
_ -> False
|
|
|
|
|
2016-06-13 16:25:32 +02:00
|
|
|
server s = do
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
let rm = head (normalMethods s)
|
2016-06-22 19:41:14 +02:00
|
|
|
serverHandleNormalCall s rm mempty dummyHandler
|
|
|
|
serverHandleNormalCall s rm mempty dummyHandler
|
2016-06-13 16:25:32 +02:00
|
|
|
return ()
|
|
|
|
|
|
|
|
testSlowServer :: TestTree
|
|
|
|
testSlowServer =
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
csTest "Client handles slow server response" client server (["/foo"],[],[],[])
|
2016-06-13 16:25:32 +02:00
|
|
|
where
|
|
|
|
client c = do
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
rm <- clientRegisterMethodNormal c "/foo"
|
2016-06-13 16:25:32 +02:00
|
|
|
result <- clientRequest c rm 1 "" mempty
|
2016-12-20 22:57:38 +01:00
|
|
|
result @?= Left (GRPCIOBadStatusCode StatusDeadlineExceeded "Deadline Exceeded")
|
2016-06-13 16:25:32 +02:00
|
|
|
server s = do
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
let rm = head (normalMethods s)
|
2016-07-15 01:33:56 +02:00
|
|
|
serverHandleNormalCall s rm mempty $ \_ -> do
|
2016-06-13 16:25:32 +02:00
|
|
|
threadDelay (2*10^(6 :: Int))
|
2016-06-22 22:07:38 +02:00
|
|
|
return dummyResp
|
2016-06-13 16:25:32 +02:00
|
|
|
return ()
|
|
|
|
|
2016-06-16 21:45:55 +02:00
|
|
|
testServerCallExpirationCheck :: TestTree
|
|
|
|
testServerCallExpirationCheck =
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
csTest "Check for call expiration" client server (["/foo"],[],[],[])
|
2016-06-16 21:45:55 +02:00
|
|
|
where
|
|
|
|
client c = do
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
rm <- clientRegisterMethodNormal c "/foo"
|
2016-07-27 00:21:35 +02:00
|
|
|
void $ clientRequest c rm 3 "" mempty
|
2016-06-16 21:45:55 +02:00
|
|
|
server s = do
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
let rm = head (normalMethods s)
|
2016-07-15 01:33:56 +02:00
|
|
|
serverHandleNormalCall s rm mempty $ \c -> do
|
2016-06-16 21:45:55 +02:00
|
|
|
exp1 <- serverCallIsExpired c
|
|
|
|
assertBool "Call isn't expired when handler starts" $ not exp1
|
|
|
|
threadDelaySecs 1
|
|
|
|
exp2 <- serverCallIsExpired c
|
|
|
|
assertBool "Call isn't expired after 1 second" $ not exp2
|
|
|
|
threadDelaySecs 3
|
|
|
|
exp3 <- serverCallIsExpired c
|
|
|
|
assertBool "Call is expired after 4 seconds" exp3
|
2016-06-22 22:07:38 +02:00
|
|
|
return dummyResp
|
|
|
|
return ()
|
|
|
|
|
|
|
|
testCustomUserAgent :: TestTree
|
|
|
|
testCustomUserAgent =
|
|
|
|
csTest' "Server sees custom user agent prefix/suffix" client server
|
|
|
|
where
|
|
|
|
clientArgs = [UserAgentPrefix "prefix!", UserAgentSuffix "suffix!"]
|
|
|
|
client =
|
2016-08-17 18:55:06 +02:00
|
|
|
TestClient (ClientConfig "localhost" 50051 clientArgs Nothing) $
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
\c -> do rm <- clientRegisterMethodNormal c "/foo"
|
2016-07-27 00:21:35 +02:00
|
|
|
void $ clientRequest c rm 4 "" mempty
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
server = TestServer (serverConf (["/foo"],[],[],[])) $ \s -> do
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
let rm = head (normalMethods s)
|
2016-07-15 01:33:56 +02:00
|
|
|
serverHandleNormalCall s rm mempty $ \c -> do
|
2016-08-01 21:38:35 +02:00
|
|
|
ua <- case toList $ (unMap $ metadata c) M.! "user-agent" of
|
|
|
|
[] -> fail "user-agent missing from metadata."
|
|
|
|
[ua] -> return ua
|
|
|
|
_ -> fail "multiple user-agent keys."
|
2016-06-22 22:07:38 +02:00
|
|
|
assertBool "User agent prefix is present" $ isPrefixOf "prefix!" ua
|
|
|
|
assertBool "User agent suffix is present" $ isSuffixOf "suffix!" ua
|
|
|
|
return dummyResp
|
|
|
|
return ()
|
|
|
|
|
|
|
|
testClientCompression :: TestTree
|
|
|
|
testClientCompression =
|
|
|
|
csTest' "client-only compression: no errors" client server
|
|
|
|
where
|
|
|
|
client =
|
|
|
|
TestClient (ClientConfig
|
|
|
|
"localhost"
|
|
|
|
50051
|
2016-08-17 18:55:06 +02:00
|
|
|
[CompressionAlgArg GrpcCompressDeflate]
|
|
|
|
Nothing) $ \c -> do
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
rm <- clientRegisterMethodNormal c "/foo"
|
2016-07-27 00:21:35 +02:00
|
|
|
void $ clientRequest c rm 1 "hello" mempty
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
server = TestServer (serverConf (["/foo"],[],[],[])) $ \s -> do
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
let rm = head (normalMethods s)
|
2016-07-15 01:33:56 +02:00
|
|
|
serverHandleNormalCall s rm mempty $ \c -> do
|
|
|
|
payload c @?= "hello"
|
2016-06-22 22:07:38 +02:00
|
|
|
return dummyResp
|
|
|
|
return ()
|
|
|
|
|
|
|
|
testClientServerCompression :: TestTree
|
|
|
|
testClientServerCompression =
|
|
|
|
csTest' "client/server compression: no errors" client server
|
|
|
|
where
|
|
|
|
cconf = ClientConfig "localhost"
|
|
|
|
50051
|
|
|
|
[CompressionAlgArg GrpcCompressDeflate]
|
2016-08-17 18:55:06 +02:00
|
|
|
Nothing
|
2016-06-22 22:07:38 +02:00
|
|
|
client = TestClient cconf $ \c -> do
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
rm <- clientRegisterMethodNormal c "/foo"
|
2016-06-22 22:07:38 +02:00
|
|
|
clientRequest c rm 1 "hello" mempty >>= do
|
|
|
|
checkReqRslt $ \NormalRequestResult{..} -> do
|
|
|
|
rspCode @?= StatusOk
|
|
|
|
rspBody @?= "hello"
|
|
|
|
details @?= ""
|
2016-06-23 23:34:36 +02:00
|
|
|
initMD @?= dummyMeta
|
2016-06-22 22:07:38 +02:00
|
|
|
trailMD @?= dummyMeta
|
|
|
|
return ()
|
|
|
|
sconf = ServerConfig "localhost"
|
|
|
|
50051
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
["/foo"] [] [] []
|
2016-06-22 22:07:38 +02:00
|
|
|
[CompressionAlgArg GrpcCompressDeflate]
|
2016-08-17 18:55:06 +02:00
|
|
|
Nothing
|
2016-06-22 22:07:38 +02:00
|
|
|
server = TestServer sconf $ \s -> do
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
let rm = head (normalMethods s)
|
2016-07-15 01:33:56 +02:00
|
|
|
serverHandleNormalCall s rm dummyMeta $ \sc -> do
|
2016-08-05 18:29:20 +02:00
|
|
|
payload sc @?= "hello"
|
|
|
|
return ("hello", dummyMeta, StatusOk, StatusDetails "")
|
|
|
|
return ()
|
|
|
|
|
|
|
|
testClientServerCompressionLvl :: TestTree
|
|
|
|
testClientServerCompressionLvl =
|
|
|
|
csTest' "client/server compression: no errors" client server
|
|
|
|
where
|
|
|
|
cconf = ClientConfig "localhost"
|
|
|
|
50051
|
|
|
|
[CompressionLevelArg GrpcCompressLevelHigh]
|
2016-08-17 18:55:06 +02:00
|
|
|
Nothing
|
2016-08-05 18:29:20 +02:00
|
|
|
client = TestClient cconf $ \c -> do
|
|
|
|
rm <- clientRegisterMethodNormal c "/foo"
|
|
|
|
clientRequest c rm 1 "hello" mempty >>= do
|
|
|
|
checkReqRslt $ \NormalRequestResult{..} -> do
|
|
|
|
rspCode @?= StatusOk
|
|
|
|
rspBody @?= "hello"
|
|
|
|
details @?= ""
|
|
|
|
initMD @?= dummyMeta
|
|
|
|
trailMD @?= dummyMeta
|
|
|
|
return ()
|
|
|
|
sconf = ServerConfig "localhost"
|
|
|
|
50051
|
|
|
|
["/foo"] [] [] []
|
|
|
|
[CompressionLevelArg GrpcCompressLevelLow]
|
2016-08-17 18:55:06 +02:00
|
|
|
Nothing
|
2016-08-05 18:29:20 +02:00
|
|
|
server = TestServer sconf $ \s -> do
|
|
|
|
let rm = head (normalMethods s)
|
|
|
|
serverHandleNormalCall s rm dummyMeta $ \sc -> do
|
2016-07-15 01:33:56 +02:00
|
|
|
payload sc @?= "hello"
|
2016-06-22 22:07:38 +02:00
|
|
|
return ("hello", dummyMeta, StatusOk, StatusDetails "")
|
2016-06-16 21:45:55 +02:00
|
|
|
return ()
|
|
|
|
|
2016-05-25 19:34:03 +02:00
|
|
|
--------------------------------------------------------------------------------
|
2016-05-25 19:49:38 +02:00
|
|
|
-- Utilities and helpers
|
|
|
|
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
is :: (Eq a, Show a, MonadIO m) => m a -> a -> m ()
|
|
|
|
is act x = act >>= liftIO . (@?= x)
|
|
|
|
|
2016-08-01 21:38:35 +02:00
|
|
|
dummyMeta :: MetadataMap
|
2016-06-08 20:12:07 +02:00
|
|
|
dummyMeta = [("foo","bar")]
|
2016-05-25 19:48:37 +02:00
|
|
|
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
dummyResp :: (ByteString, MetadataMap, StatusCode, StatusDetails)
|
2016-06-22 22:07:38 +02:00
|
|
|
dummyResp = ("", mempty, StatusOk, StatusDetails "")
|
|
|
|
|
2016-07-15 01:33:56 +02:00
|
|
|
dummyHandler :: ServerCall a
|
2016-06-16 17:23:54 +02:00
|
|
|
-> IO (ByteString, MetadataMap, StatusCode, StatusDetails)
|
2016-07-15 01:33:56 +02:00
|
|
|
dummyHandler _ = return dummyResp
|
2016-06-13 16:25:32 +02:00
|
|
|
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
dummyResult' :: StatusDetails
|
|
|
|
-> IO (ByteString, MetadataMap, StatusCode, StatusDetails)
|
|
|
|
dummyResult' = return . (mempty, mempty, StatusOk, )
|
2016-06-13 16:25:32 +02:00
|
|
|
|
2016-05-25 19:48:37 +02:00
|
|
|
nop :: Monad m => a -> m ()
|
|
|
|
nop = const (return ())
|
2016-05-25 19:34:03 +02:00
|
|
|
|
2016-06-08 20:12:07 +02:00
|
|
|
serverOnlyTest :: TestName
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
-> ([MethodName],[MethodName],[MethodName],[MethodName])
|
2016-06-08 20:12:07 +02:00
|
|
|
-> (Server -> IO ())
|
|
|
|
-> TestTree
|
|
|
|
serverOnlyTest nm ms =
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
testCase ("Server - " ++ nm) . runTestServer . TestServer (serverConf ms)
|
2016-06-08 20:12:07 +02:00
|
|
|
|
|
|
|
clientOnlyTest :: TestName -> (Client -> IO ()) -> TestTree
|
|
|
|
clientOnlyTest nm =
|
|
|
|
testCase ("Client - " ++ nm) . runTestClient . stdTestClient
|
|
|
|
|
|
|
|
csTest :: TestName
|
|
|
|
-> (Client -> IO ())
|
|
|
|
-> (Server -> IO ())
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
-> ([MethodName],[MethodName],[MethodName],[MethodName])
|
2016-06-08 20:12:07 +02:00
|
|
|
-> TestTree
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
csTest nm c s ms =
|
|
|
|
csTest' nm (stdTestClient c) (TestServer (serverConf ms) s)
|
2016-06-08 20:12:07 +02:00
|
|
|
|
|
|
|
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
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
checkMD desc expected actual =
|
2016-08-01 21:38:35 +02:00
|
|
|
assertEqual desc expected' (actual' `S.intersection` expected')
|
2016-06-08 20:12:07 +02:00
|
|
|
where
|
2016-08-01 21:38:35 +02:00
|
|
|
expected' = fromList . toList $ expected
|
|
|
|
actual' = fromList . toList $ actual
|
2016-06-08 20:12:07 +02:00
|
|
|
|
|
|
|
checkReqRslt :: Show a => (b -> Assertion) -> Either a b -> Assertion
|
|
|
|
checkReqRslt = either clientFail
|
|
|
|
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
-- | The consumer which asserts that the next value it consumes is equal to the
|
|
|
|
-- given value; string parameter used as in 'assertEqual'.
|
|
|
|
assertConsumeEq :: (Eq a, Show a) => String -> a -> P.Consumer a IO ()
|
|
|
|
assertConsumeEq s v = P.lift . assertEqual s v =<< P.await
|
|
|
|
|
2016-06-08 20:12:07 +02:00
|
|
|
clientFail :: Show a => a -> Assertion
|
|
|
|
clientFail = assertFailure . ("Client error: " ++). show
|
|
|
|
|
|
|
|
data TestClient = TestClient ClientConfig (Client -> IO ())
|
|
|
|
|
|
|
|
runTestClient :: TestClient -> IO ()
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
runTestClient (TestClient conf f) =
|
|
|
|
runManaged $ mgdGRPC >>= mgdClient conf >>= liftIO . f
|
2016-06-08 20:12:07 +02:00
|
|
|
|
|
|
|
stdTestClient :: (Client -> IO ()) -> TestClient
|
|
|
|
stdTestClient = TestClient stdClientConf
|
|
|
|
|
|
|
|
stdClientConf :: ClientConfig
|
2016-08-17 18:55:06 +02:00
|
|
|
stdClientConf = ClientConfig "localhost" 50051 [] Nothing
|
2016-06-08 20:12:07 +02:00
|
|
|
|
|
|
|
data TestServer = TestServer ServerConfig (Server -> IO ())
|
|
|
|
|
|
|
|
runTestServer :: TestServer -> IO ()
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
runTestServer (TestServer conf f) =
|
|
|
|
runManaged $ mgdGRPC >>= mgdServer conf >>= liftIO . f
|
2016-06-08 20:12:07 +02:00
|
|
|
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
defServerConf :: ServerConfig
|
2016-08-17 18:55:06 +02:00
|
|
|
defServerConf = ServerConfig "localhost" 50051 [] [] [] [] [] Nothing
|
2016-06-08 20:12:07 +02:00
|
|
|
|
Joel/highlevelv2 (#40)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* begin high-level server interface
* update to datakind representation
* clean up
* move method type info to type level, parametrize ServerCall by payload
* convert for writer handler
* start switching over to Message-based handlers
* begin work on highlevel example
* comment out old code
* parametrize StreamSend
* parametrize StreamRecv
* conversion for ServerReaderHandler
* finish handler conversions
* Add high level version and payload checking to echo-client
* Decouple server CQs from call-bound CQs (registered methods); use more consistent naming conventions
* Decouple server/call-bound CQs for unregistered methods; refactor U.serverRequestCall; misc cleanup
* Make convertRecv total; formatting wibbles
2016-07-12 20:28:21 +02:00
|
|
|
serverConf :: ([MethodName],[MethodName],[MethodName],[MethodName])
|
|
|
|
-> ServerConfig
|
|
|
|
serverConf (ns, cs, ss, bs) =
|
|
|
|
defServerConf {methodsToRegisterNormal = ns,
|
|
|
|
methodsToRegisterClientStreaming = cs,
|
|
|
|
methodsToRegisterServerStreaming = ss,
|
|
|
|
methodsToRegisterBiDiStreaming = bs}
|
2016-06-16 21:45:55 +02:00
|
|
|
|
Preliminary streaming mode support (client streaming, server streaming, bidirectional) (#37)
* Tweak runOps param order, inline common op sequences, clean up serverHandleNormalCall
* More ops sequence inlining for clarity, experimenting with Managed
* Checkpoint: preliminary support for all streaming modes; much cleanup/refactoring and api design still needed
* Use mempty for default StatusDetails; tweak bad status matching mechanism
* Preliminary user-facing, server-streaming, low-level api and test
* renaming wibbles
* Preliminary user-facing, client-streaming, low-level api and test
* Move sendMsgs comb to Network.GRPC.LowLevel.Op; misc cleanup/DCR
* Modify bidi streaming to omit request payload
* Add transformers dep
* Preliminary user-facing low-level bidirectional streaming api and test
* Fix missing peek import
* Remove TimeoutSeconds params on streaming mode functions
* Fix serverHandleNormalCall rebase wart
* Fix rebase warts; minor hlint fixes and wibbles
* Post-rebase tweaks to optional payload use in serverRequestCall (i.e., now respects payloadHandling again)
* Cleanup/refactor serverRequestCall
* Fix comment
* Change ServerRWHandler type so that handler does not have to invoke a finalizer
* Change ServerReaderHandler type so that handler does not have to invoke a finalizer
* Simplify serverWriter interface and ServerWriterHandler structure
* Simplify serverRW (get rid of exec param), improve bidi streaming tests
* Use ExceptT in serverRW impl
* Change ServerRWHandler type to pass recv/send operations.
* Renaming
* Define ClientRWHandler, pass recv/send ops
* wibbles
* Use ExceptT in clientRW impl
* Add DataKinded phantom typing to RegisteredMethod; misc cleanup
* Simplify sendMsgs interface; add SingleSend type and related helpers
* Rename SingleSend to SendSingle, use ExceptT to clean up {client,server}Writer and sendMsgs
* More ExceptT cleanup in clientWriter
* Factor out reusable bits of clientWriter
* Shrink ServerReaderHandler
* Delete stale comments
* Use common machinery for all streaming modes; make handler types more consistent
* wibbles
2016-07-06 15:59:38 +02:00
|
|
|
mgdGRPC :: Managed GRPC
|
|
|
|
mgdGRPC = managed withGRPC
|
|
|
|
|
|
|
|
mgdClient :: ClientConfig -> GRPC -> Managed Client
|
|
|
|
mgdClient conf g = managed $ withClient g conf
|
|
|
|
|
|
|
|
mgdServer :: ServerConfig -> GRPC -> Managed Server
|
|
|
|
mgdServer conf g = managed $ withServer g conf
|