module Gargoyle
( Gargoyle (..)
, withGargoyle
, gargoyleMain
) where
import Control.Concurrent
import Control.Exception
import Control.Monad
import Network.Socket
import System.Directory
import System.Exit
import System.FilePath
import System.IO
import System.IO.Error
import System.Environment
import System.FileLock
import System.Process
import Debug.Trace
data Gargoyle pid a = Gargoyle
{ _gargoyle_exec :: FilePath
, _gargoyle_init :: FilePath -> IO ()
, _gargoyle_start :: FilePath -> IO pid
, _gargoyle_stop :: pid -> IO ()
, _gargoyle_getInfo :: FilePath -> IO a
}
gControlDir :: FilePath -> FilePath
gControlDir = (</> "control")
gWorkDir :: FilePath -> FilePath
gWorkDir = (</> "work")
gOldWorkDir :: FilePath -> FilePath
gOldWorkDir = (</> "db")
gLockDir :: FilePath -> FilePath
gLockDir = (</> "lock")
checkThreadedRuntime :: IO ()
checkThreadedRuntime = when (not rtsSupportsBoundThreads) $ do
hPutStrLn stderr "Gargoyle requires threaded run-time, aborting"
assert rtsSupportsBoundThreads (return ())
withGargoyle :: Gargoyle pid a
-> FilePath
-> (a -> IO b)
-> IO b
withGargoyle g daemonDir b = do
checkThreadedRuntime
daemonExists <- doesDirectoryExist daemonDir
if daemonExists
then do
let oldWrk = gOldWorkDir daemonDir
wrk = gWorkDir daemonDir
oldWorkDirExists <- doesDirectoryExist oldWrk
workDirExists <- doesDirectoryExist wrk
when (oldWorkDirExists && not workDirExists) $ renameDirectory oldWrk wrk
else do
createDirectory daemonDir
_gargoyle_init g (gWorkDir daemonDir)
s <- socket AF_UNIX Stream defaultProtocol
let acquire = do
connectResult <- try $ connect s $ SockAddrUnix $ gControlDir daemonDir
case connectResult of
Right () -> return ()
Left e
| isDoesNotExistError e -> do
let monProc = (proc (_gargoyle_exec g) [daemonDir])
{ std_in = CreatePipe
, std_out = CreatePipe
, std_err = Inherit }
(Just monIn, Just monOut, Nothing, monHnd) <- createProcess monProc
void $ forkOS $ void $ waitForProcess monHnd
hClose monIn
r <- hGetLine monOut
case r of
"retry" -> do
threadDelay 500000
acquire
"ready" -> acquire
_ -> fail "Unexpected gargoyle message from monitor process"
| otherwise -> throwIO e
bracket_ acquire (shutdown s ShutdownBoth >> close s) $
b =<< _gargoyle_getInfo g (gWorkDir daemonDir)
gargoyleMain :: Gargoyle pid a
-> IO ()
gargoyleMain g = do
checkThreadedRuntime
[daemonDir] <- getArgs >>= \case
x@[_] -> return x
_ -> fail "Gargoyle monitor received unexpected number of arguments"
let lockPath = gLockDir daemonDir
catch (openFile lockPath WriteMode >>= hClose) $ \(e :: IOException) -> if
| isAlreadyInUseError e -> return ()
| isDoesNotExistError e -> throwIO e
| isPermissionError e -> throwIO e
lock <- tryLockFile lockPath Exclusive >>= \case
Just x -> return x
Nothing -> do
putStrLn "retry"
hFlush stdout
exitFailure
controlSocket <- socket AF_UNIX Stream defaultProtocol
let socketPath = gControlDir daemonDir
createSocket = do
result <- try $ bind controlSocket $ SockAddrUnix socketPath
case result of
Right () -> return ()
Left e
| isAlreadyInUseError e
-> do
removePathForcibly socketPath
putStrLn "retry"
hFlush stdout
exitFailure
| otherwise -> throwIO e
bracket createSocket (\_ -> removeFile socketPath) $ \_ -> do
listen controlSocket 128
numClientsVar <- newMVar (0 :: Int)
shutdownVar <- newEmptyMVar
void $ forkOS $ forever $ do
(s, _) <- accept controlSocket
modifyMVar_ numClientsVar $ \n -> do
return $ succ n
forkOS $ do
h <- socketToHandle s ReadMode
catchJust
(\e -> if isEOFError e then Just () else e `traceShow` Nothing)
(hGetChar h >> hPutStrLn stderr "Warning: client sent data over the control socket")
return
mask_ $ do
n <- takeMVar numClientsVar
case pred n of
0 -> do
shutdown controlSocket ShutdownBoth
putMVar shutdownVar ()
n' -> putMVar numClientsVar n'
bracket (_gargoyle_start g (gWorkDir daemonDir)) (_gargoyle_stop g) $ \_ -> do
hSetBuffering stdout LineBuffering
putStrLn "ready"
takeMVar shutdownVar
unlockFile lock