
Hello,
I like to turn my Haskell program into a unix daemon. One of the steps
in "daemonizing" a process is to fork it then exit the parent and
continue with the child. All this is nicely abstracted in
hdaemonize[1] which internally calls forkProcess[2].
I would also like to use multiple simultaneous threads in my program.
Unfortunately forkProcess is not supported when running with +RTS -N
so I can't use hdaemonize.
I understand why it's problematic to fork a process which is in the
middle of running multiple simultaneous threads. However, in the case
of a daemon the fork happens in the beginning of the program. So if I
can manage to create a program that first daemonizes my process then
starts the Haskell program, all is good.
My current plan is to have a custom Haskell main function which is
exported using the FFI:
---------------------------------------------------------------------
{-# LANGUAGE ForeignFunctionInterface #-}
module MyMain where
import Control.Monad ( forM_ )
import Control.Concurrent ( threadDelay )
-- from hsyslog:
import System.Posix.Syslog ( Priority(Debug), syslog )
foreign export ccall myMain :: IO ()
myMain :: IO ()
myMain = forM_ [1..10 :: Int] $ \n -> do
syslog Debug $ "test " ++ show n
threadDelay 1000000
---------------------------------------------------------------------
Then create a C program that first daemonizes my process (using the
'daemon'[3] function from unistd) then start up my custom Haskell main
function:
---------------------------------------------------------------------
#include