I humbly recommend doing such daemonizations from outside your program. Programs that daemonize on startup make it very difficult to monitor them by direct means, instead forcing you to rely on PID files and other mechanisms which may not always be available or fresh.
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 <unistd.h>
#include "HsFFI.h"
#include "MyMain_stub.h"
extern void __stginit_Main ( void );
int main(int argc, char *argv[])
{
int r;
r = daemon(0,0);
if (r < 0)
{
return r;
}
hs_init(&argc, &argv);
hs_add_root(__stginit_Main);
myMain();
hs_exit();
return 0;
}
---------------------------------------------------------------------
My question is: how can I combine these two into a single program?
I very much prefer to do this using Cabal since my actual program
contains lots of dependencies.
Thanks,
Bas
[1] http://hackage.haskell.org/package/hdaemonize
[2] http://hackage.haskell.org/packages/archive/unix/latest/doc/html/System-Posix-Process.html#v:forkProcess
[3] http://www.kernel.org/doc/man-pages/online/pages/man3/daemon.3.html
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe