Shut down server when serverLoop thread is killed. (#71)

Previously, killing the thread running serverLoop
would not actually shut down the server, leading
to file descriptor leaks and perhaps worse effects.
This commit is contained in:
j6carey 2019-01-07 15:53:10 -08:00 committed by GitHub
parent 28288a17b7
commit bc457cc4e3
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23

View File

@ -9,12 +9,15 @@
module Network.GRPC.HighLevel.Server.Unregistered where module Network.GRPC.HighLevel.Server.Unregistered where
import Control.Arrow import Control.Arrow
import Control.Concurrent.Async (async, wait) import Control.Concurrent.MVar (newEmptyMVar,
putMVar,
takeMVar)
import qualified Control.Exception as CE import qualified Control.Exception as CE
import Control.Monad import Control.Monad
import Data.Foldable (find) import Data.Foldable (find)
import Network.GRPC.HighLevel.Server import Network.GRPC.HighLevel.Server
import Network.GRPC.LowLevel import Network.GRPC.LowLevel
import Network.GRPC.LowLevel.Server (forkServer)
import qualified Network.GRPC.LowLevel.Call.Unregistered as U import qualified Network.GRPC.LowLevel.Call.Unregistered as U
import qualified Network.GRPC.LowLevel.Server.Unregistered as U import qualified Network.GRPC.LowLevel.Server.Unregistered as U
import Proto3.Suite.Class import Proto3.Suite.Class
@ -66,11 +69,35 @@ dispatchLoop s logger md hN hC hS hB =
where herr (e :: CE.SomeException) = GRPCIOHandlerException (show e) where herr (e :: CE.SomeException) = GRPCIOHandlerException (show e)
serverLoop :: ServerOptions -> IO () serverLoop :: ServerOptions -> IO ()
serverLoop ServerOptions{..} = do serverLoop ServerOptions{..} =
-- We run the loop in a new thread so that we can kill the serverLoop thread. -- In the GRPC library, "doc/core/epoll-polling-engine.md" seems
-- Without this fork, we block on a foreign call, which can't be interrupted. -- to indicate that the thread which actually awakens from sleep
tid <- async $ withGRPC $ \grpc -> -- on file descriptor events may differ from the one which seeks
-- to "pluck" the resulting event.
--
-- Thus it seems possible that "dispatchLoop" may be waiting on
-- a condition variable when the "serverLoop" thread is killed.
--
-- Note that "pthread_cond_timedwait" never returns EINTR; see:
-- <https://pubs.opengroup.org/onlinepubs/7908799/xsh/pthread_cond_wait.html>
--
-- Therefore to awaken "dispatchLoop" we must initiate a GRPC
-- shutdown; it would not suffice to kill its Haskell thread.
-- (Presumably a GRPC shutdown broadcasts on relvant condition
-- variables; regardless, we do see it awaken "dispatchLoop".)
--
-- The "withServer" cleanup code will initiate a GRPC shutdown.
-- We arrange to trigger it by leaving the "serverLoop" thread
-- in an interruptible sleep ("takeMVar") while "dispatchLoop"
-- runs in its own thread.
withGRPC $ \grpc ->
withServer grpc config $ \server -> do withServer grpc config $ \server -> do
-- Killing the "serverLoop" thread triggers the "withServer"
-- cleanup code, which initiates a shutdown, which in turn
-- kills the "dispatchLoop" thread and any other thread we
-- may have started with "forkServer".
done <- newEmptyMVar
launched <- forkServer server $
dispatchLoop server dispatchLoop server
optLogger optLogger
optInitialMetadata optInitialMetadata
@ -78,7 +105,9 @@ serverLoop ServerOptions{..} = do
optClientStreamHandlers optClientStreamHandlers
optServerStreamHandlers optServerStreamHandlers
optBiDiStreamHandlers optBiDiStreamHandlers
wait tid `CE.finally` putMVar done ()
when launched $
takeMVar done
where where
config = ServerConfig config = ServerConfig
{ host = optServerHost { host = optServerHost