0

I'm writing a socket server with runTCPServer from conduit-extra (formerly known as network-conduit). My goal is to interact with my editor using this server --- activate the server from the editor (most likely just by calling external command), use it, and terminate the server when the work is done.

For simplicity, I start with a simple echo server, and let's say I'd like to shut down the whole process when the connection is closed.

So I tried:

{-# LANGUAGE OverloadedStrings #-}
module Main where
import Data.Conduit
import Data.Conduit.Network
import Data.ByteString (ByteString)
import Control.Monad.IO.Class (liftIO)
import System.Exit (exitSuccess)
import Control.Exception

defaultPort :: Int
defaultPort = 4567
main :: IO ()
main = runTCPServer (serverSettings defaultPort "*") $ \ appData ->
        appSource appData $$ conduit =$= appSink appData

conduit :: ConduitM ByteString ByteString IO ()
conduit = do
    msg <- await
    case msg of
         Nothing -> liftIO $ do
             putStrLn "Nothing left"
             exitSuccess
             -- I'd like the server to shut down here
         (Just s) -> do
             yield s
             conduit

But this doesn't work -- the program continues to accept new connections. If I am not mistaken, this is because the thread listening to the connection we're dealing with exits with exitSuccess, but the entire process doesn't. So this is totally understandable, but I haven't been able to find a way to exit the whole process.

How do I terminate a server run by runTCPServer? Is runTCPServer something that's supposed to serve forever?

Yosh
  • 2,512
  • 3
  • 24
  • 30
  • `exit` must be called from the main thread (I'm not sure why, but that's the requirement). You can always run `runTCPServer` in a separate `forkIO`d thread, and have the main thread wait on some `MVar` that the worker thread sets when a termination message arrives. – n. m. could be an AI Jun 19 '16 at 15:17
  • And yes, `runTCPServer` is intended to run forever, see [source](https://hackage.haskell.org/package/streaming-commons-0.1.15.5/docs/src/Data-Streaming-Network.html#runTCPServerWithHandle). – n. m. could be an AI Jun 19 '16 at 15:26
  • @n.m. That seems to be the exact answer (especially `forkIO` and `MVar` part) I was looking for. Would you add a simple example (if you don't mind) and post that as an answer? – Yosh Jun 19 '16 at 15:56
  • Have you tried just `return ()` instead of `exitSuccess`? – NovaDenizen Jun 19 '16 at 16:02
  • @NovaDenizen Yes, and the result is the same. By `return ()` the thread exits, but the main process continues to wait for another connection. – Yosh Jun 19 '16 at 16:06

1 Answers1

2

Here's a simple implementation of the idea described in comments:

main = do
     mv <- newEmptyMVar
     tid <- forkTCPServer (serverSettings defaultPort "*") $ \ appData ->
        appSource appData $$ conduit mv =$= appSink appData
     () <- takeMVar mv -- < -- wait for done signal
     return ()

conduit :: MVar () -> ConduitM ByteString ByteString IO ()
conduit mv = do
    msg <- await
    case msg of
         Nothing -> liftIO $ do
             putStrLn "Nothing left"
             putMVar mv () -- < -- signal that we're done
         (Just s) -> do
             yield s
             conduit mv
n. m. could be an AI
  • 112,515
  • 14
  • 128
  • 243