]> gitweb.michael.orlitzky.com - dead/htsn.git/commitdiff
Wrap the entire daemonization process in an exception handler.
authorMichael Orlitzky <michael@orlitzky.com>
Wed, 8 Jan 2014 01:03:45 +0000 (20:03 -0500)
committerMichael Orlitzky <michael@orlitzky.com>
Wed, 8 Jan 2014 01:03:45 +0000 (20:03 -0500)
Automatically create the PID directory if it doesn't exist.

src/Main.hs
src/Unix.hs

index a06bd2338e62a0371fb90215d43a366478719347..3f0974346d38389c20b00fdb8bd4b4d02eeb4860 100644 (file)
@@ -5,7 +5,7 @@ module Main
 where
 
 import Control.Concurrent ( threadDelay )
-import Control.Exception.Base ( bracket )
+import Control.Exception ( bracket, throw )
 import Control.Monad ( when )
 import Data.List ( isPrefixOf )
 import Data.Maybe ( isNothing )
@@ -296,7 +296,7 @@ main = do
 
   -- If we were asked to daemonize, do that; otherwise just run the thing.
   if (daemonize cfg)
-  then full_daemonize cfg run_program
+  then try_daemonize cfg run_program
   else run_program
 
   where
@@ -313,3 +313,16 @@ main = do
       catchIOError (connect_and_parse cfg host) (report_error . show)
       thread_sleep 5 -- Wait 5s before attempting to reconnect.
       round_robin cfg $ (feed_host_idx + 1) `mod` (length hosts)
+
+
+    -- | A exception handler around full_daemonize. If full_daemonize
+    --   doesn't work, we report the error and crash. This is fine; we
+    --   only need the program to be resilient once it actually starts.
+    --
+    try_daemonize :: Configuration -> IO () -> IO ()
+    try_daemonize cfg program =
+      catchIOError
+        (full_daemonize cfg program)
+        (\e -> do
+          report_error (show e)
+          throw e)
index b6990d2a663e3ef31df3d70ad5efa4e503b127c1..17e3960104b75ca88f1d34ab93fe3119a9894574 100644 (file)
@@ -5,7 +5,10 @@ where
 
 import Control.Concurrent ( ThreadId, myThreadId )
 import Control.Exception ( throwTo )
+import Control.Monad ( unless )
+import System.Directory ( createDirectory, doesDirectoryExist )
 import System.Exit ( ExitCode( ExitSuccess ) )
+import System.FilePath ( dropFileName, dropTrailingPathSeparator )
 import System.IO.Error ( catchIOError )
 import System.Posix (
   GroupEntry ( groupID ),
@@ -23,6 +26,7 @@ import System.Posix (
   removeLink,
   setFileCreationMask,
   setGroupID,
+  setOwnerAndGroup,
   setUserID,
   sigTERM )
 import System.Posix.Daemonize ( daemonize )
@@ -31,8 +35,7 @@ import Configuration (
   Configuration( pidfile,
                  run_as_group,
                  run_as_user ))
-import Network.Services.TSN.Logging ( log_info, log_error )
-import Network.Services.TSN.Terminal ( display_error )
+import Network.Services.TSN.Report ( report_error, report_info )
 
 -- | Retrieve the uid associated with the given system user name. We
 --   take a Maybe String as an argument so the user name can be passed
@@ -60,10 +63,9 @@ get_group_id (Just s) = fmap groupID (getGroupEntryForName s)
 --
 graceful_shutdown :: Configuration -> ThreadId -> IO ()
 graceful_shutdown cfg main_thread_id = do
-  log_info "SIGTERM received, removing PID file and shutting down."
+  report_info "SIGTERM received, removing PID file and shutting down."
   catchIOError try_nicely (\e -> do
-                             display_error (show e)
-                             log_error (show e)
+                             report_error (show e)
                              exitImmediately ExitSuccess )
   where
     try_nicely = do
@@ -71,25 +73,55 @@ graceful_shutdown cfg main_thread_id = do
       throwTo main_thread_id ExitSuccess
 
 
+-- | Create the directory in which we intend to store the PID
+--   file. This will *not* create any parent directories. The PID
+--   directory will have its owner/group changed to the user/group
+--   under which we'll be running. No permissions will be set; the
+--   system's umask must allow owner-write.
+--
+--   This is intended to create one level beneath either /var/run or
+--   /run which often do not survive a reboot.
+--
+--   If the directory already exists, it is left alone; that is, we
+--   don't change its owner/group.
+--
+create_pid_directory :: FilePath -- ^ The directory to contain the PID file.
+                     -> UserID   -- ^ Owner of the new directory if created.
+                     -> GroupID  -- ^ Group of the new directory if created.
+                     -> IO ()
+create_pid_directory pid_directory uid gid = do
+  it_exists <- doesDirectoryExist pid_directory
+  unless it_exists $ do
+    report_info $ "Creating PID directory " ++ pid_directory
+    createDirectory pid_directory
+    report_info $ "Changing owner/group of " ++ pid_directory ++
+                    " to " ++ (show uid) ++ "/" ++ (show gid)
+    setOwnerAndGroup pid_directory uid gid
+
 -- | Write a PID file, install a SIGTERM handler, drop privileges, and
 --   finally do the daemonization dance.
 --
 full_daemonize :: Configuration -> IO () -> IO ()
 full_daemonize cfg program = do
+  uid <- get_user_id (run_as_user cfg)
+  gid <- get_group_id (run_as_group cfg)
+
+  -- This will have to be done as root and the result chowned to our
+  -- user/group, so it must happen before daemonizing.
+  let pid_directory = dropTrailingPathSeparator $ dropFileName $ pidfile cfg
+  create_pid_directory pid_directory uid gid
+
   -- The call to 'daemonize' will set the umask to zero, but we want
   -- to retain it. So, we set the umask to zero before 'daemonize'
   -- can, so that we can record the previous umask value (returned by
   -- setFileCreationMask).
   orig_umask <- setFileCreationMask 0
-  -- This is the 'daemonize' from System.Posix.Daemonize. If it
-  -- doesn't work, we report the error and do not much else.
-  catchIOError (daemonize (program' orig_umask))
-                 (\e -> do
-                    display_error (show e)
-                    log_error (show e))
+
+  -- This is the 'daemonize' from System.Posix.Daemonize.
+  daemonize (program' orig_umask uid gid)
   where
     -- We need to do all this stuff *after* we daemonize.
-    program' orig_umask = do
+    program' orig_umask uid gid = do
       -- First we install a signal handler for sigTERM. We need to
       -- pass the thread ID to the signal handler so it knows which
       -- process to "exit."
@@ -98,8 +130,8 @@ full_daemonize cfg program = do
 
       -- Next we drop privileges. Group ID has to go first, otherwise
       -- you ain't root to change groups.
-      get_group_id (run_as_group cfg) >>= setGroupID
-      get_user_id  (run_as_user cfg) >>= setUserID
+      setGroupID gid
+      setUserID uid
 
       -- Now we create the PID file.
       pid <- getProcessID