daemonize git annex watch
This commit is contained in:
parent
ca9ee21bd7
commit
d5884388b0
5 changed files with 123 additions and 34 deletions
|
@ -12,6 +12,8 @@ module Command.Watch where
|
|||
|
||||
import Common.Annex
|
||||
import Command
|
||||
import Utility.Daemon
|
||||
import Utility.LogFile
|
||||
import Utility.ThreadLock
|
||||
import qualified Annex
|
||||
import qualified Annex.Queue
|
||||
|
@ -23,6 +25,7 @@ import qualified Backend
|
|||
import Annex.Content
|
||||
import Annex.CatFile
|
||||
import Git.Types
|
||||
import Option
|
||||
|
||||
import Control.Concurrent
|
||||
import Control.Concurrent.STM
|
||||
|
@ -47,44 +50,52 @@ data Change = Change
|
|||
deriving (Show)
|
||||
|
||||
def :: [Command]
|
||||
def = [command "watch" paramPaths seek "watch for changes"]
|
||||
def = [withOptions [foregroundOption] $
|
||||
command "watch" paramPaths seek "watch for changes"]
|
||||
|
||||
seek :: [CommandSeek]
|
||||
seek = [withNothing start]
|
||||
seek = [withFlag foregroundOption $ withNothing . start]
|
||||
|
||||
start :: CommandStart
|
||||
start = notBareRepo $ do
|
||||
showStart "watch" "."
|
||||
watch
|
||||
foregroundOption :: Option
|
||||
foregroundOption = Option.flag [] "foreground" "do not daemonize"
|
||||
|
||||
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
|
||||
|
||||
watch :: Annex ()
|
||||
watch :: MVar Annex.AnnexState -> IO ()
|
||||
#if defined linux_HOST_OS
|
||||
watch = do
|
||||
showAction "scanning"
|
||||
withStateMVar $ \st -> liftIO $ withINotify $ \i -> do
|
||||
changechan <- atomically newTChan
|
||||
let hook a = Just $ runHandler st changechan a
|
||||
let hooks = WatchHooks
|
||||
{ addHook = hook onAdd
|
||||
, delHook = hook onDel
|
||||
, addSymlinkHook = hook onAddSymlink
|
||||
, delDirHook = hook onDelDir
|
||||
, errHook = hook onErr
|
||||
}
|
||||
-- The commit thread is started early, so that the user
|
||||
-- can immediately begin adding files and having them
|
||||
-- committed, even while the inotify scan is taking place.
|
||||
_ <- forkIO $ commitThread st changechan
|
||||
-- This does not return until the inotify scan is done.
|
||||
-- That can take some time for large trees.
|
||||
watchDir i "." (ignored . takeFileName) hooks
|
||||
-- Notice any files that were deleted before inotify
|
||||
-- was started.
|
||||
runStateMVar st $
|
||||
inRepo $ Git.Command.run "add" [Param "--update"]
|
||||
putStrLn "(started)"
|
||||
waitForTermination
|
||||
watch st = withINotify $ \i -> do
|
||||
changechan <- atomically newTChan
|
||||
let hook a = Just $ runHandler st changechan a
|
||||
let hooks = WatchHooks
|
||||
{ addHook = hook onAdd
|
||||
, delHook = hook onDel
|
||||
, addSymlinkHook = hook onAddSymlink
|
||||
, delDirHook = hook onDelDir
|
||||
, errHook = hook onErr
|
||||
}
|
||||
-- The commit thread is started early, so that the user
|
||||
-- can immediately begin adding files and having them
|
||||
-- committed, even while the inotify scan is taking place.
|
||||
_ <- forkIO $ commitThread st changechan
|
||||
-- This does not return until the inotify scan is done.
|
||||
-- That can take some time for large trees.
|
||||
watchDir i "." (ignored . takeFileName) hooks
|
||||
runStateMVar st $ showAction "scanning"
|
||||
-- Notice any files that were deleted before inotify
|
||||
-- was started.
|
||||
runStateMVar st $ do
|
||||
inRepo $ Git.Command.run "add" [Param "--update"]
|
||||
showAction "started"
|
||||
waitForTermination
|
||||
#else
|
||||
watch = error "watch mode is so far only available on Linux"
|
||||
#endif
|
||||
|
|
|
@ -23,6 +23,7 @@ module Locations (
|
|||
gitAnnexIndex,
|
||||
gitAnnexIndexLock,
|
||||
gitAnnexIndexDirty,
|
||||
gitAnnexLogFile,
|
||||
gitAnnexSshDir,
|
||||
gitAnnexRemotesDir,
|
||||
isLinkToAnnex,
|
||||
|
@ -145,6 +146,10 @@ gitAnnexIndexLock r = gitAnnexDir r </> "index.lck"
|
|||
gitAnnexIndexDirty :: Git.Repo -> FilePath
|
||||
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 -}
|
||||
gitAnnexSshDir :: Git.Repo -> FilePath
|
||||
gitAnnexSshDir r = addTrailingPathSeparator $ gitAnnexDir r </> "ssh"
|
||||
|
|
39
Utility/Daemon.hs
Normal file
39
Utility/Daemon.hs
Normal 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
31
Utility/LogFile.hs
Normal 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
|
|
@ -173,8 +173,11 @@ 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
|
||||
deleted, copied, and moved files. Run this in the background, and you
|
||||
no longer need to manually run git commands when manipulating your files.
|
||||
deleted, copied, and moved files. With this running as a daemon in the
|
||||
background, you no longer need to manually run git commands when
|
||||
manipulating your files.
|
||||
|
||||
To not daemonize, run with --foreground
|
||||
|
||||
# REPOSITORY SETUP COMMANDS
|
||||
|
||||
|
|
Loading…
Reference in a new issue