{-# LANGUAGE CPP #-}
+import Control.Exception
import Control.Monad
import Data.List
import Data.Maybe
import System.Directory
import System.Environment
import System.Exit
+import System.FilePath
import System.IO
import System.Log.Handler.Simple
import System.Log.Logger
import System.Posix.Files
+import System.Posix.IO
+import System.Posix.Process
import System.Posix.Types
import System.Posix.User
gid <- getGroupID opts
lsdir <- getLocalStateDir opts
+ -- Create our localstatedir *before* dropping privileges.
createLocalStateDir lsdir uid gid
setGroupID gid
setUserID uid
- setupLogger opts
- env <- setupEnv lsdir portNum
+ -- Now that we have our localstatedir. Let's acquire a lock
+ -- on the lockfile. Then create other files.
+ withSystemLock (lsdir </> "lock") $
+ withPidFile (lsdir </> "pid") $
+ do setupLogger opts
+ env <- setupEnv lsdir portNum
- rebuildIndexIfRequested env opts
+ rebuildIndexIfRequested env opts
- infoM logger ("Listening to " ++ show portNum ++ "/tcp...")
- runHttpd (envLucuConf env) (resTree env) [fallbackPageEntity env]
+ infoM logger ("Listening to " ++ show portNum ++ "/tcp...")
+ runHttpd (envLucuConf env) (resTree env) [fallbackPageEntity env]
resTree :: Environment -> ResTree
_ -> False) opts
when rebuild
$ rebuildIndex (envStorage env)
+
+withSystemLock :: FilePath -> IO a -> IO a
+withSystemLock lockfile = bracket lock' unlock' . const
+ where
+ lock' :: IO Fd
+ lock' = do fd <- openFd
+ lockfile
+ ReadWrite
+ (Just 420) -- 0644, -rw-r--r--
+ defaultFileFlags
+ setLock fd (WriteLock, AbsoluteSeek, 0, 0)
+ return fd
+
+ unlock' :: Fd -> IO ()
+ unlock' = closeFd
+
+withPidFile :: FilePath -> IO a -> IO a
+withPidFile lockfile = bracket mkPid' (const delPid') . const
+ where
+ mkPid' :: IO ()
+ mkPid' = withFile lockfile WriteMode $ \ h ->
+ do pid <- getProcessID
+ hPutStrLn h (show pid)
+
+ delPid' :: IO ()
+ delPid' = removeFile lockfile