watch subcommand

So far this only handles auto-annexing new files that are created inside
the repository while it's running. To make this really useful,
it needs to at least:

- notice deleted files and stage the deletion
  (tricky; there's a race with add..)
- notice renamed files, auto-fix the symlink, and stage the new file location
- periodically auto-commit staged changes
- honor .gitignore, not adding files it excludes

Also nice to have would be:

- Somehow sync remotes, possibly using a push sync like dvcs-autosync
  does, so they are immediately updated.
- Somehow get content that is unavilable. This is problimatic with inotify,
  since we only get an event once the user has tried (and failed) to read
  from the file. Perhaps instead, automatically copy content that is added
  out to remotes, with the goal of all repos eventually getting a copy,
  if df allows.
- Drop files that have not been used lately, or meet some other criteria
  (as long as there's a copy elsewhere).
- Perhaps automatically dropunused files that have been deleted,
  although I cannot see a way to do that, since by the time the inotify
  deletion event arrives, the file is deleted, and we cannot see what
  its symlink pointed to! Alternatievely, perhaps automatically
  do an expensive unused/dropunused cleanup process.

Some of this probably needs the currently stateless threads to maintain
a common state.
This commit is contained in:
Joey Hess 2012-04-12 17:29:43 -04:00
parent 6464a576cd
commit d5ffd2d99d
2 changed files with 57 additions and 0 deletions

55
Command/Watch.hs Normal file
View file

@ -0,0 +1,55 @@
{- git-annex command
-
- Copyright 2012 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Command.Watch where
import Common.Annex
import Command
import qualified Annex
import CmdLine
import Utility.Inotify
import Control.Exception as E
import qualified Command.Add as Add
import System.INotify
def :: [Command]
def = [command "watch" paramPaths seek "watch for changes"]
seek :: [CommandSeek]
seek = [withNothing start]
start :: CommandStart
start = notBareRepo $ do
showStart "watch" "."
showAction "scanning"
state <- Annex.getState id
next $ next $ liftIO $ withINotify $ \i -> do
watchDir i notgit (Just $ run state onAdd) Nothing "."
putStrLn "(started)"
waitForTermination
return True
where
notgit dir = takeFileName dir /= ".git"
{- Inotify events are run in separate threads, and so each is a
- self-contained Annex monad. Exceptions by the handlers are ignored,
- otherwise a whole watcher thread could be crashed. -}
run :: Annex.AnnexState -> (FilePath -> Annex a) -> FilePath -> IO ()
run startstate a f = do
r <- E.try go :: IO (Either E.SomeException ())
case r of
Left e -> putStrLn (show e)
_ -> return ()
where
go = Annex.eval startstate $ do
_ <- a f
_ <- shutdown True
return ()
onAdd :: FilePath -> Annex Bool
onAdd file = doCommand $ Add.start file

View file

@ -56,6 +56,7 @@ import qualified Command.AddUrl
import qualified Command.Map
import qualified Command.Upgrade
import qualified Command.Version
import qualified Command.Watch
cmds :: [Command]
cmds = concat
@ -95,6 +96,7 @@ cmds = concat
, Command.Map.def
, Command.Upgrade.def
, Command.Version.def
, Command.Watch.def
]
options :: [Option]