[Haskell-beginners] Simple Haskell daemon

Amy de Buitléir amy at nualeargais.ie
Mon Nov 15 20:18:40 EST 2010


I've written a very simple daemon, and it's working just fine. But I'd 
appreciate it if someone could take a look at it and tell me if any of the code 
I've written is... stupid. (I'm trying to get more comfortable with this monad 
stuff.) Thank you in advance.

Daemon.hs
---------
module Daemon where

import System.Exit
import System.IO.Unsafe
import System.Posix.Signals
import Control.Concurrent

class DaemonState a where
  initialise :: IO a
  work :: a -> IO a
  finalise :: a -> IO ()

termReceived = unsafePerformIO (newMVar False)

handleTERM :: IO ()
handleTERM = swapMVar termReceived True >> return ()

loop :: (DaemonState a) => a -> IO (Maybe a)
loop d = do
  timeToStop <- readMVar termReceived
  if timeToStop
    then finalise d >> return Nothing
    else work d >>= loop

start :: (DaemonState a) => IO (Maybe a)
start = installHandler sigTERM (Catch handleTERM) Nothing >>  initialise >>= 
loop

-----
Here's a simple example of how I use it
-----

Main.hs
-------

module Main where

import Daemon

instance DaemonState Int where

initialise = do
  putStrLn "Starting up"
  return 0

work i = do
  putStrLn (show i)
  return (i+1)

finalise i = do
  putStrLn "Shutting down"
  return ()

main = start :: IO (Maybe Int)




More information about the Beginners mailing list