daemonize git annex watch

This commit is contained in:
Joey Hess 2012-06-11 00:39:09 -04:00
parent ca9ee21bd7
commit d5884388b0
5 changed files with 123 additions and 34 deletions

View file

@ -12,6 +12,8 @@ module Command.Watch where
import Common.Annex import Common.Annex
import Command import Command
import Utility.Daemon
import Utility.LogFile
import Utility.ThreadLock import Utility.ThreadLock
import qualified Annex import qualified Annex
import qualified Annex.Queue import qualified Annex.Queue
@ -23,6 +25,7 @@ import qualified Backend
import Annex.Content import Annex.Content
import Annex.CatFile import Annex.CatFile
import Git.Types import Git.Types
import Option
import Control.Concurrent import Control.Concurrent
import Control.Concurrent.STM import Control.Concurrent.STM
@ -47,44 +50,52 @@ data Change = Change
deriving (Show) deriving (Show)
def :: [Command] def :: [Command]
def = [command "watch" paramPaths seek "watch for changes"] def = [withOptions [foregroundOption] $
command "watch" paramPaths seek "watch for changes"]
seek :: [CommandSeek] seek :: [CommandSeek]
seek = [withNothing start] seek = [withFlag foregroundOption $ withNothing . start]
start :: CommandStart foregroundOption :: Option
start = notBareRepo $ do foregroundOption = Option.flag [] "foreground" "do not daemonize"
showStart "watch" "."
watch start :: Bool -> CommandStart
start foreground = notBareRepo $ withStateMVar $ \st -> do
if foreground
then do
showStart "watch" "."
liftIO $ watch st
else do
logfd <- liftIO . openLog =<< fromRepo gitAnnexLogFile
liftIO $ daemonize logfd False $ watch st
stop stop
watch :: Annex () watch :: MVar Annex.AnnexState -> IO ()
#if defined linux_HOST_OS #if defined linux_HOST_OS
watch = do watch st = withINotify $ \i -> do
showAction "scanning" changechan <- atomically newTChan
withStateMVar $ \st -> liftIO $ withINotify $ \i -> do let hook a = Just $ runHandler st changechan a
changechan <- atomically newTChan let hooks = WatchHooks
let hook a = Just $ runHandler st changechan a { addHook = hook onAdd
let hooks = WatchHooks , delHook = hook onDel
{ addHook = hook onAdd , addSymlinkHook = hook onAddSymlink
, delHook = hook onDel , delDirHook = hook onDelDir
, addSymlinkHook = hook onAddSymlink , errHook = hook onErr
, delDirHook = hook onDelDir }
, errHook = hook onErr -- The commit thread is started early, so that the user
} -- can immediately begin adding files and having them
-- The commit thread is started early, so that the user -- committed, even while the inotify scan is taking place.
-- can immediately begin adding files and having them _ <- forkIO $ commitThread st changechan
-- committed, even while the inotify scan is taking place. -- This does not return until the inotify scan is done.
_ <- forkIO $ commitThread st changechan -- That can take some time for large trees.
-- This does not return until the inotify scan is done. watchDir i "." (ignored . takeFileName) hooks
-- That can take some time for large trees. runStateMVar st $ showAction "scanning"
watchDir i "." (ignored . takeFileName) hooks -- Notice any files that were deleted before inotify
-- Notice any files that were deleted before inotify -- was started.
-- was started. runStateMVar st $ do
runStateMVar st $ inRepo $ Git.Command.run "add" [Param "--update"]
inRepo $ Git.Command.run "add" [Param "--update"] showAction "started"
putStrLn "(started)" waitForTermination
waitForTermination
#else #else
watch = error "watch mode is so far only available on Linux" watch = error "watch mode is so far only available on Linux"
#endif #endif

View file

@ -23,6 +23,7 @@ module Locations (
gitAnnexIndex, gitAnnexIndex,
gitAnnexIndexLock, gitAnnexIndexLock,
gitAnnexIndexDirty, gitAnnexIndexDirty,
gitAnnexLogFile,
gitAnnexSshDir, gitAnnexSshDir,
gitAnnexRemotesDir, gitAnnexRemotesDir,
isLinkToAnnex, isLinkToAnnex,
@ -145,6 +146,10 @@ gitAnnexIndexLock r = gitAnnexDir r </> "index.lck"
gitAnnexIndexDirty :: Git.Repo -> FilePath gitAnnexIndexDirty :: Git.Repo -> FilePath
gitAnnexIndexDirty r = gitAnnexDir r </> "index.dirty" gitAnnexIndexDirty r = gitAnnexDir r </> "index.dirty"
{- Log file for daemon mode. -}
gitAnnexLogFile :: Git.Repo -> FilePath
gitAnnexLogFile r = gitAnnexDir r </> "daemon.log"
{- .git/annex/ssh/ is used for ssh connection caching -} {- .git/annex/ssh/ is used for ssh connection caching -}
gitAnnexSshDir :: Git.Repo -> FilePath gitAnnexSshDir :: Git.Repo -> FilePath
gitAnnexSshDir r = addTrailingPathSeparator $ gitAnnexDir r </> "ssh" gitAnnexSshDir r = addTrailingPathSeparator $ gitAnnexDir r </> "ssh"

39
Utility/Daemon.hs Normal file
View file

@ -0,0 +1,39 @@
{- daemon functions
-
- Copyright 2012 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Utility.Daemon where
import System.Posix
import System.Directory
import System.Exit
import Control.Monad
{- Run an action as a daemon, with all output sent to a file descriptor.
-
- Does not return. -}
daemonize :: Fd -> Bool -> IO () -> IO ()
daemonize logfd changedirectory a = do
_ <- forkProcess child1
end
where
child1 = do
_ <- createSession
_ <- forkProcess child2
end
child2 = do
when changedirectory $
setCurrentDirectory "/"
nullfd <- openFd "/dev/null" ReadOnly Nothing defaultFileFlags
_ <- redir nullfd stdInput
mapM_ (redir logfd) [stdOutput, stdError]
closeFd logfd
a
end
redir newh h = do
closeFd h
dupTo newh h
end = exitImmediately ExitSuccess

31
Utility/LogFile.hs Normal file
View file

@ -0,0 +1,31 @@
{- log files
-
- Copyright 2012 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Utility.LogFile where
import Common
import System.Posix
openLog :: FilePath -> IO Fd
openLog logfile = do
rotateLog logfile 0
openFd logfile WriteOnly (Just stdFileMode)
defaultFileFlags { append = True }
rotateLog :: FilePath -> Int -> IO ()
rotateLog logfile num
| num >= 10 = return ()
| otherwise = whenM (doesFileExist currfile) $ do
rotateLog logfile (num + 1)
renameFile currfile nextfile
where
currfile = filename num
nextfile = filename (num + 1)
filename n
| n == 0 = logfile
| otherwise = logfile ++ "." ++ show n

View file

@ -173,8 +173,11 @@ subdirectories).
Watches for changes to files in the current directory and its subdirectories, Watches for changes to files in the current directory and its subdirectories,
and takes care of automatically adding new files, as well as dealing with and takes care of automatically adding new files, as well as dealing with
deleted, copied, and moved files. Run this in the background, and you deleted, copied, and moved files. With this running as a daemon in the
no longer need to manually run git commands when manipulating your files. background, you no longer need to manually run git commands when
manipulating your files.
To not daemonize, run with --foreground
# REPOSITORY SETUP COMMANDS # REPOSITORY SETUP COMMANDS