daemons-0.3.0: Daemons in Haskell made fun and easy

Safe HaskellSafe
LanguageHaskell98

System.Posix.Daemon

Contents

Description

This module provides a simple interface to creating, checking the status of, and stopping background jobs.

Use runDetached to start a background job. For instance, here is a daemon that peridically hits a webserver:

import Control.Concurrent
import Control.Monad
import Data.Default
import Data.Maybe
import Network.BSD
import Network.HTTP
import Network.URI
import System.Posix.Daemon

main :: IO ()
main = runDetached (Just "diydns.pid") def $ forever $ do
    hostname <- getHostName
    _ <- simpleHTTP
             (Request { rqURI     = fromJust (parseURI "http://foo.com/dns")
                      , rqMethod  = GET
                      , rqHeaders = []
                      , rqBody    = hostname })
    threadDelay (600 * 1000 * 1000)

To check if the above job is running, use isRunning with the same pidfile:

isRunning "diydns.pid"

Finally, to stop the above job (maybe because we're rolling a new version of it), use kill:

kill "diydns.pid"

To stop a job and wait for it to close (and release its pidfile), use killAndWait:

killAndWait "diydns.pid" >> doSomething

As a side note, the code above is a script that the author uses as a sort of homebrew dynamic DNS: the remote address is a CGI script that records the IP addresses of all incoming requests in separate files named after the contents of the requests; the addresses are then viewable with any browser.

Synopsis

Starting

runDetached Source #

Arguments

:: Maybe FilePath

pidfile

-> Redirection

redirection

-> IO ()

program

-> IO () 

Run the given action detached from the current terminal; this creates an entirely new process. This function returns immediately. Uses the double-fork technique to create a well behaved daemon. If pidfile is given, check/write it; if we cannot obtain a lock on the file, another process is already using it, so fail. The redirection parameter controls what to do with the standard channels (stdin, stderr, and stdout).

See: http://www.enderunix.org/docs/eng/daemon.php

Note: All unnecessary fds should be close before calling this. Otherwise, you get an fd leak.

data Redirection Source #

Where should the output (and input) of a daemon be redirected to? (we can't just leave it to the current terminal, because it may be closed, and that would kill the daemon).

When in doubt, just use def, the default value.

DevNull causes the output to be redirected to /dev/null. This is safe and is what you want in most cases.

If you don't want to lose the output (maybe because you're using it for logging), use ToFile, instead.

Constructors

DevNull 
ToFile FilePath 
Instances
Show Redirection Source # 
Instance details

Defined in System.Posix.Daemon

Default Redirection Source # 
Instance details

Defined in System.Posix.Daemon

Methods

def :: Redirection #

Status

isRunning :: FilePath -> IO Bool Source #

Return True if the given file is locked by a process. In our case, returns True when the daemon that created the file is still alive.

Stopping

kill :: FilePath -> IO () Source #

Send sigQUIT to the process recorded in the pidfile. This gives the process a chance to close cleanly.

killAndWait :: FilePath -> IO () Source #

Kill a process and wait for it to release its pidfile

brutalKill :: FilePath -> IO () Source #

Send sigKILL to the process recorded in the pidfile. This immediately kills the process.