
Amy,
Here's a small suggestion:
If the start and loop functions always returns Nothing, I think it may
be cleaner to
simply make them return ().
Patrick
On Tue, Nov 16, 2010 at 3:28 PM, Amy de Buitléir
Chaddaï Fouché
writes: To use a typeclass there is pretty strange and doesn't have much advantage, it would be much easier and nicer to just write start to take some functions as parameters...
Doh! Yes, I kind of overlooked the obvious there. Thank you so much! Here's my new version, in case anyone Googles this.
----- Daemon.hs ----- module Daemon where
import System.Exit import System.IO.Unsafe import System.Posix.Signals import Control.Concurrent
termReceived = unsafePerformIO (newMVar False)
handleTERM :: IO () handleTERM = swapMVar termReceived True >> return ()
loop :: (a -> IO a) -> (a -> IO ()) -> a -> IO (Maybe a) loop work finalise d = do timeToStop <- readMVar termReceived if timeToStop then finalise d >> return Nothing else work d >>= loop work finalise
start -- | This function will be invoked when the daemon starts. :: IO a -- | This function will be invoked in the main loop. -> (a -> IO a) -- | This function will be invoked when the daemon shuts down. -> (a -> IO ()) -- | The result will always be Nothing. -> IO (Maybe a) start initialise work finalise = installHandler sigTERM (Catch handleTERM) Nothing >> initialise >>= loop work finalise
----- CountingExample.hs -----
module CountingExample where
import Daemon
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 initialise work finalise
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- ===================== Patrick LeBoutillier Rosemère, Québec, Canada