git-annex/Command/Watch.hs

277 lines
7.9 KiB
Haskell
Raw Normal View History

{- git-annex command
-
- Copyright 2012 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-}
module Command.Watch where
import Common.Annex
import Command
2012-06-04 23:43:29 +00:00
import Utility.ThreadLock
import qualified Annex
import qualified Annex.Queue
import qualified Command.Add
import qualified Git.Command
import qualified Git.UpdateIndex
import qualified Backend
import Annex.Content
import Control.Concurrent
import Control.Concurrent.STM
import Data.Time.Clock
#if defined linux_HOST_OS
import Utility.Inotify
import System.INotify
#endif
2012-06-10 22:29:05 +00:00
type ChangeChan = TChan Change
type Handler = FilePath -> Annex (Maybe Change)
data Change = Change
{ changeTime :: UTCTime
, changeFile :: FilePath
, changeDesc :: String
}
deriving (Show)
def :: [Command]
def = [command "watch" paramPaths seek "watch for changes"]
seek :: [CommandSeek]
seek = [withNothing start]
start :: CommandStart
start = notBareRepo $ do
showStart "watch" "."
2012-06-10 21:40:35 +00:00
watch
stop
watch :: Annex ()
#if defined linux_HOST_OS
watch = do
showAction "scanning"
2012-06-10 21:40:35 +00:00
withStateMVar $ \st -> liftIO $ withINotify $ \i -> do
changechan <- atomically newTChan
2012-06-10 22:29:05 +00:00
let hook a = Just $ runHandler st changechan a
2012-06-07 03:20:09 +00:00
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.
2012-06-07 03:20:09 +00:00
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
#else
2012-06-10 21:40:35 +00:00
watch = error "watch mode is so far only available on Linux"
#endif
2012-06-07 03:30:38 +00:00
ignored :: FilePath -> Bool
ignored ".git" = True
ignored ".gitignore" = True
ignored ".gitattributes" = True
ignored _ = False
2012-06-10 17:23:10 +00:00
{- Stores the Annex state in a MVar, so that threaded actions can access
- it.
-
2012-06-10 17:23:10 +00:00
- Once the action is finished, retrieves the state from the MVar.
-}
2012-06-10 17:23:10 +00:00
withStateMVar :: (MVar Annex.AnnexState -> Annex a) -> Annex a
withStateMVar a = do
state <- Annex.getState id
mvar <- liftIO $ newMVar state
r <- a mvar
newstate <- liftIO $ takeMVar mvar
Annex.changeState (const newstate)
return r
{- Runs an Annex action, using the state from the MVar. -}
runStateMVar :: MVar Annex.AnnexState -> Annex () -> IO ()
runStateMVar mvar a = do
startstate <- takeMVar mvar
2012-06-10 17:23:10 +00:00
!newstate <- Annex.exec startstate a
putMVar mvar newstate
2012-06-10 22:29:05 +00:00
{- Runs an action handler, inside the Annex monad.
2012-06-10 17:23:10 +00:00
-
- Exceptions are ignored, otherwise a whole watcher thread could be crashed.
-}
2012-06-10 22:29:05 +00:00
runHandler :: MVar Annex.AnnexState -> ChangeChan -> Handler -> FilePath -> IO ()
runHandler st changechan hook file = handle =<< tryIO (runStateMVar st go)
where
2012-06-10 22:29:05 +00:00
go = maybe noop (signalChange changechan) =<< hook file
2012-06-10 17:23:10 +00:00
handle (Right ()) = return ()
handle (Left e) = putStrLn $ show e
2012-06-10 22:29:05 +00:00
{- Handlers call this when they made a change that needs to get committed. -}
madeChange :: FilePath -> String -> Annex (Maybe Change)
madeChange file desc = liftIO $
Just <$> (Change <$> getCurrentTime <*> pure file <*> pure desc)
{- Adding a file is tricky; the file has to be replaced with a symlink
- but this is race prone, as the symlink could be changed immediately
- after creation. To avoid that race, git add is not used to stage the
2012-06-10 22:29:05 +00:00
- symlink.
-
- Inotify will notice the new symlink, so this Handler does not stage it
- or return a Change, leaving that to onAddSymlink.
-}
onAdd :: Handler
onAdd file = do
showStart "add" file
2012-06-10 22:29:05 +00:00
handle =<< Command.Add.ingest file
return Nothing
where
2012-06-10 22:29:05 +00:00
handle Nothing = showEndFail
handle (Just key) = do
Command.Add.link file key True
showEndOk
{- A symlink might be an arbitrary symlink, which is just added.
- Or, if it is a git-annex symlink, ensure it points to the content
- before adding it.
-}
2012-06-10 22:29:05 +00:00
onAddSymlink :: Handler
onAddSymlink file = go =<< Backend.lookupFile file
where
2012-06-10 22:29:05 +00:00
go Nothing = do
addlink =<< liftIO (readSymbolicLink file)
madeChange file "add"
go (Just (key, _)) = do
link <- calcGitLink file key
ifM ((==) link <$> liftIO (readSymbolicLink file))
2012-06-10 22:29:05 +00:00
( do
addlink link
madeChange file "add"
, do
liftIO $ removeFile file
liftIO $ createSymbolicLink link file
addlink link
2012-06-10 22:29:05 +00:00
madeChange file "fix"
)
addlink link = stageSymlink file link
2012-06-10 22:29:05 +00:00
onDel :: Handler
onDel file = do
Annex.Queue.addUpdateIndex =<<
inRepo (Git.UpdateIndex.unstageFile file)
madeChange file "rm"
{- A directory has been deleted, or moved, so tell git to remove anything
- that was inside it from its cache. Since it could reappear at any time,
- use --cached to only delete it from the index.
-
- Note: This could use unstageFile, but would need to run another git
- command to get the recursive list of files in the directory, so rm is
- just as good. -}
2012-06-10 22:29:05 +00:00
onDelDir :: Handler
onDelDir dir = do
Annex.Queue.addCommand "rm"
[Params "--quiet -r --cached --ignore-unmatch --"] [dir]
madeChange dir "rmdir"
2012-06-07 03:20:09 +00:00
{- Called when there's an error with inotify. -}
2012-06-10 22:29:05 +00:00
onErr :: Handler
onErr msg = do
warning msg
return Nothing
{- Adds a symlink to the index, without ever accessing the actual symlink
- on disk. -}
stageSymlink :: FilePath -> String -> Annex ()
stageSymlink file linktext =
Annex.Queue.addUpdateIndex =<<
inRepo (Git.UpdateIndex.stageSymlink file linktext)
{- Signals that a change has been made, that needs to get committed. -}
2012-06-10 22:29:05 +00:00
signalChange :: ChangeChan -> Change -> Annex ()
signalChange chan change = do
liftIO $ atomically $ writeTChan chan change
-- Just in case the commit thread is not flushing
-- the queue fast enough.
Annex.Queue.flushWhenFull
2012-06-10 22:29:05 +00:00
{- Gets all unhandled changes.
- Blocks until at least one change is made. -}
2012-06-10 22:29:05 +00:00
getChanges :: ChangeChan -> IO [Change]
getChanges chan = atomically $ do
c <- readTChan chan
go [c]
where
go l = do
v <- tryReadTChan chan
case v of
Nothing -> return l
Just c -> go (c:l)
{- Puts unhandled changes back into the channel.
- Note: Original order is not preserved. -}
2012-06-10 22:29:05 +00:00
refillChanges :: ChangeChan -> [Change] -> IO ()
refillChanges chan cs = atomically $ mapM_ (writeTChan chan) cs
2012-06-10 22:29:05 +00:00
{- This thread makes git commits at appropriate times. -}
commitThread :: MVar Annex.AnnexState -> ChangeChan -> IO ()
commitThread st changechan = forever $ do
-- First, a simple rate limiter.
threadDelay oneSecond
-- Next, wait until at least one change has been made.
cs <- getChanges changechan
-- Now see if now's a good time to commit.
time <- getCurrentTime
if shouldCommit time cs
2012-06-10 22:29:05 +00:00
then void $ tryIO $ runStateMVar st $ commitStaged
else refillChanges changechan cs
where
oneSecond = 1000000 -- microseconds
2012-06-10 22:29:05 +00:00
commitStaged :: Annex ()
commitStaged = do
Annex.Queue.flush
inRepo $ Git.Command.run "commit"
[ Param "--allow-empty-message"
, Param "-m", Param ""
-- Empty commits may be made if tree changes cancel
-- each other out, etc
, Param "--allow-empty"
-- Avoid running the usual git-annex pre-commit hook;
-- watch does the same symlink fixing, and we don't want
-- to deal with unlocked files in these commits.
, Param "--quiet"
]
{- Decide if now is a good time to make a commit.
- Note that the list of change times has an undefined order.
-
- Current strategy: If there have been 10 commits within the past second,
- a batch activity is taking place, so wait for later.
-}
2012-06-10 22:29:05 +00:00
shouldCommit :: UTCTime -> [Change] -> Bool
shouldCommit now changes
| len == 0 = False
| len > 4096 = True -- avoid bloating queue too much
2012-06-10 22:29:05 +00:00
| length (filter thisSecond changes) < 10 = True
| otherwise = False -- batch activity
where
2012-06-10 22:29:05 +00:00
len = length changes
thisSecond c = now `diffUTCTime` changeTime c <= 1