module System.Daemon (
ensureDaemonRunning, ensureDaemonWithHandlerRunning,
runClient, runClientWithHandler,
DaemonOptions(..), PidFile(..), HostName, Port,
runInForeground, bindPort, getSocket
) where
import Control.Concurrent ( threadDelay )
import qualified Control.Exception as CE
import Control.Monad ( when )
import Control.Pipe.C3 ( commandSender, commandReceiver )
import Control.Pipe.Socket ( Handler, runSocketServer, runSocketClient )
import Data.Default ( Default(..) )
import Data.Serialize ( Serialize )
import Data.String ( IsString(..) )
import Network.Socket ( Socket, SockAddr(..), Family(..), SocketType(..)
, SocketOption(..), setSocketOption
, socket, sClose, connect, bindSocket, listen
, AddrInfo(..), getAddrInfo, addrAddress, defaultHints
, defaultProtocol, iNADDR_ANY, maxListenQueue )
import System.Directory ( getHomeDirectory )
import System.FilePath ( (</>), (<.>) )
import System.Posix.Daemon ( runDetached, isRunning )
import Text.Printf ( printf )
type Port = Int
type HostName = String
data DaemonOptions = DaemonOptions
{ daemonPort :: Port
, daemonPidFile :: PidFile
, printOnDaemonStarted :: Bool
} deriving ( Show )
instance Default DaemonOptions where
def = DaemonOptions { daemonPort = 5000
, daemonPidFile = InHome
, printOnDaemonStarted = True
}
data PidFile = InHome
| PidFile FilePath
deriving ( Show )
instance IsString PidFile where
fromString = PidFile
ensureDaemonRunning :: (Serialize a, Serialize b)
=> String
-> DaemonOptions
-> (a -> IO b)
-> IO ()
ensureDaemonRunning name options executeCommand = do
ensureDaemonWithHandlerRunning name options (commandReceiver executeCommand)
ensureDaemonWithHandlerRunning :: String
-> DaemonOptions
-> Handler ()
-> IO ()
ensureDaemonWithHandlerRunning name options handler = do
home <- getHomeDirectory
let pidfile = case daemonPidFile options of
InHome -> home </> ("." ++ name) <.> "pid"
PidFile path -> path
running <- isRunning pidfile
when (not running) $ do
runDetached (Just pidfile) def
(runInForeground (daemonPort options) handler)
when (printOnDaemonStarted options)
(printf "Daemon started on port %d\n" (daemonPort options))
threadDelay (1 * 1000 * 1000)
runInForeground :: Port -> Handler () -> IO ()
runInForeground port handler = do
CE.bracket
(bindPort port)
sClose
(\lsocket ->
runSocketServer lsocket handler)
runClient :: (Serialize a, Serialize b)
=> HostName
-> Port
-> a
-> IO (Maybe b)
runClient hostname port comm =
runClientWithHandler hostname port (commandSender comm)
runClientWithHandler :: HostName
-> Port
-> Handler a
-> IO a
runClientWithHandler hostname port handler = do
CE.bracket
(getSocket hostname port)
sClose
(\s -> runSocketClient s handler)
bindPort :: Port -> IO Socket
bindPort port = do
CE.bracketOnError
(socket AF_INET Stream defaultProtocol)
sClose
(\s -> do
setSocketOption s ReuseAddr 1
bindSocket s (SockAddrInet (fromIntegral port) iNADDR_ANY)
listen s maxListenQueue
return s)
getSocket :: HostName -> Port -> IO Socket
getSocket hostname port = do
addrInfos <- getAddrInfo (Just (defaultHints { addrFamily = AF_INET }))
(Just hostname)
(Just $ show port)
CE.bracketOnError
(socket AF_INET Stream defaultProtocol)
sClose
(\s -> do
connect s (addrAddress $ head addrInfos)
return s)