How to daemonize a threaded Haskell program?

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

Quoth Bas van Dijk
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.
type ProcessID = CInt type Fd = CInt foreign import ccall "fork" c_fork :: IO CInt foreign import ccall "_exit" _exit :: CInt -> IO () fork :: IO Int -> IO ProcessID fork fn = do pid <- c_fork if pid == 0 then do fn >>= _exit . fromIntegral return 0 -- unused, I reckon else if pid > 0 then return pid else throwErrno "fork" System.PosixProcess (exitImmediately) is supposed to be "_exit". I would not care to hazard a guess as to whether this will work reliably for you. If you figure out how to use your own custom C main() function, I'd be interested to know. I use separate C programs that exec my Haskell programs. My current GHC can't compile -via-C, but if you can compile a minimal "main" module to C that way, it probably calls hs_main() or something like that? and you could add your own xx_main() to the stack. Donn Cave, donn@avvanta.com

On 5 March 2011 21:43, Donn Cave
Quoth Bas van Dijk
, ... 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.
type ProcessID = CInt type Fd = CInt
foreign import ccall "fork" c_fork :: IO CInt foreign import ccall "_exit" _exit :: CInt -> IO ()
fork :: IO Int -> IO ProcessID fork fn = do pid <- c_fork if pid == 0 then do fn >>= _exit . fromIntegral return 0 -- unused, I reckon else if pid > 0 then return pid else throwErrno "fork"
System.PosixProcess (exitImmediately) is supposed to be "_exit".
I would not care to hazard a guess as to whether this will work reliably for you.
Thanks, I thought about this too, however I consider myself too unfamiliar with the RTS to know if this is safe. Bas

On Sat, Mar 05, 2011 at 08:51:59PM +0100, Bas van Dijk wrote:
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:
Hi, Did you alternatively though about daemonizing in your haskell program normally without using +RTS -N, and exec'ing yourself (using executeFile) with the extra cmdline +RTS -N options, and also --no-daemon option to avoid re-daemon/exec'ing ? I think that would be simpler than your current approch. -- Vincent

On 5 March 2011 21:51, Vincent Hanquez
On Sat, Mar 05, 2011 at 08:51:59PM +0100, Bas van Dijk wrote:
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:
Hi,
Did you alternatively though about daemonizing in your haskell program normally without using +RTS -N, and exec'ing yourself (using executeFile) with the extra cmdline +RTS -N options, and also --no-daemon option to avoid re-daemon/exec'ing ?
I think that would be simpler than your current approch.
What a nice idea! I actually looked for a unix command line tool that could do this but did not think further about doing it myself. Thanks, Bas P.S. So is there a tool that daemonizes another program? Sounds like a job for a neat little Haskell program...

On Mar 5, 2011, at 5:59 PM, Bas van Dijk wrote:
On 5 March 2011 21:51, Vincent Hanquez
wrote: On Sat, Mar 05, 2011 at 08:51:59PM +0100, Bas van Dijk wrote:
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].
Have you looked at direct-daemonize[1]? I'm not sure if it will do the job, but it's certainly worth mentioning. Cheers, Sterl

On Sat, Mar 5, 2011 at 11:59 PM, Bas van Dijk
So is there a tool that daemonizes another program? Sounds like a job for a neat little Haskell program...
There are a few I'm aware of:
* http://software.clapper.org/daemonize/
* http://cr.yp.to/daemontools.html (warning, DJ Bernstein code :) )
G
--
Gregory Collins

Hi Bas If you want to use your own C main(), that's documented here: http://www.haskell.org/ghc/docs/7.0-latest/html/users_guide/ffi-ghc.html#usi...

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.
For reference, Upstart, the new PID 1 on Ubuntu and friends, has a horrible
hack[1] built in specifically to keep track of processes that "helpfully"
daemonize themselves, so that it can offer additional services like
restarting crashed services or notifying the owner of a problem.
As has been pointed out elsewhere on thread, there are plenty of standalone
programs that implement daemonization if you end up not using service
management software to do it for you. It's also trivial to implement a
Haskell program that would do this for you, since that standalone program
would not need threads or the complications that they bring to forking.
Or if you really must, make daemonization a startup option of your real
server, but please please please have a flag to turn that behavior off, so
that your service isn't a nightmare to manage for us poor sysadmins :-).
- Dave
[1]: if you care, the hack in question is ptrace(): if you declare to
Upstart that your service daemonizes itself, it will boot your binary,
ptrace() it, and track the process across two fork/clone syscalls, then
un-ptrace() and use the second child as the "real" service process. Please
don't make binaries where daemonization can't be turned off. Machine
management software should not have to use debugging facilities to correctly
monitor your program.
On Sat, Mar 5, 2011 at 11:51 AM, Bas van Dijk
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
#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-Posi... [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

Sterling, Gregory, Brandon and David thanks for your suggestions.
On 6 March 2011 05:38, David Anderson
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.
Agreed, I already noticed that debugging is a bit harder since I have no stdout and stderr anymore.
For reference, Upstart, the new PID 1 on Ubuntu and friends, has a horrible hack[1] built in specifically to keep track of processes that "helpfully" daemonize themselves, so that it can offer additional services like restarting crashed services or notifying the owner of a problem. As has been pointed out elsewhere on thread, there are plenty of standalone programs that implement daemonization if you end up not using service management software to do it for you.
I plan to run the daemon on a Ubuntu server. Do you know if Upstart is able to daemonize a process? Regards, Bas

On Mon, Mar 7, 2011 at 12:39 AM, Bas van Dijk
Sterling, Gregory, Brandon and David thanks for your suggestions.
On 6 March 2011 05:38, David Anderson
wrote: 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.
Agreed, I already noticed that debugging is a bit harder since I have no stdout and stderr anymore.
For reference, Upstart, the new PID 1 on Ubuntu and friends, has a horrible hack[1] built in specifically to keep track of processes that "helpfully" daemonize themselves, so that it can offer additional services like restarting crashed services or notifying the owner of a problem. As has been pointed out elsewhere on thread, there are plenty of standalone programs that implement daemonization if you end up not using service management software to do it for you.
I plan to run the daemon on a Ubuntu server. Do you know if Upstart is able to daemonize a process?
It's perfectly simple. In fact, it's the default assumption of Upstart that your program doesn't daemonize, and that Upstart should help it. You have to specify if your program violates that assumption. Here's a sample file. It specifies a service that; should run whenever the main runlevels are entered (i.e. basic system init like mounting filesystems is done, but no other guarantee); stops when the system leaves those runlevels; runs a binary that does not fork or daemonize; respawns the service if the process should die for any reason; can be manually stopped and restarted by the admin if he feels like it. $ cat /etc/init/demo.conf description "Demo service that doesn't daemonize by itself" start on runlevel [2345] stop on runlevel [!2345] respawn exec /path/to/binary $ sudo start demo demo start/running, process 27469 $ sudo stop demo demo stop/waiting $ sudo status demo demo stop/waiting $ Hope this helps. The upstart configuration format is a little sparsely documented, when I wrote scripts for it, I used the existing files in /etc/init as a rough guide. - Dave
Regards,
Bas
participants (7)
-
Bas van Dijk
-
Brandon Moore
-
David Anderson
-
Donn Cave
-
Gregory Collins
-
Sterling Clover
-
Vincent Hanquez