indirect: Better behavior when a file in direct mode is not owned by the user running the conversion.
This commit is contained in:
parent
c923c981b9
commit
c45f5fbdb3
4 changed files with 30 additions and 4 deletions
|
@ -13,6 +13,7 @@
|
||||||
module Annex.Exception (
|
module Annex.Exception (
|
||||||
bracketIO,
|
bracketIO,
|
||||||
tryAnnex,
|
tryAnnex,
|
||||||
|
tryAnnexIO,
|
||||||
throwAnnex,
|
throwAnnex,
|
||||||
catchAnnex,
|
catchAnnex,
|
||||||
) where
|
) where
|
||||||
|
@ -30,6 +31,10 @@ bracketIO setup cleanup = M.bracket (liftIO setup) (liftIO . cleanup)
|
||||||
tryAnnex :: Annex a -> Annex (Either SomeException a)
|
tryAnnex :: Annex a -> Annex (Either SomeException a)
|
||||||
tryAnnex = M.try
|
tryAnnex = M.try
|
||||||
|
|
||||||
|
{- try in the Annex monad, but only catching IO exceptions -}
|
||||||
|
tryAnnexIO :: Annex a -> Annex (Either IOException a)
|
||||||
|
tryAnnexIO = M.try
|
||||||
|
|
||||||
{- throw in the Annex monad -}
|
{- throw in the Annex monad -}
|
||||||
throwAnnex :: Exception e => e -> Annex a
|
throwAnnex :: Exception e => e -> Annex a
|
||||||
throwAnnex = M.throw
|
throwAnnex = M.throw
|
||||||
|
|
|
@ -8,6 +8,7 @@
|
||||||
module Command.Indirect where
|
module Command.Indirect where
|
||||||
|
|
||||||
import System.PosixCompat.Files
|
import System.PosixCompat.Files
|
||||||
|
import Control.Exception.Extensible
|
||||||
|
|
||||||
import Common.Annex
|
import Common.Annex
|
||||||
import Command
|
import Command
|
||||||
|
@ -22,7 +23,9 @@ import Annex.Content
|
||||||
import Annex.CatFile
|
import Annex.CatFile
|
||||||
import Annex.Version
|
import Annex.Version
|
||||||
import Annex.Perms
|
import Annex.Perms
|
||||||
|
import Annex.Exception
|
||||||
import Init
|
import Init
|
||||||
|
import qualified Command.Add
|
||||||
|
|
||||||
def :: [Command]
|
def :: [Command]
|
||||||
def = [notBareRepo $ noDaemonRunning $
|
def = [notBareRepo $ noDaemonRunning $
|
||||||
|
@ -87,11 +90,20 @@ perform = do
|
||||||
thawContentDir =<< calcRepo (gitAnnexLocation k)
|
thawContentDir =<< calcRepo (gitAnnexLocation k)
|
||||||
cleandirect k -- clean before content directory gets frozen
|
cleandirect k -- clean before content directory gets frozen
|
||||||
whenM (liftIO $ not . isSymbolicLink <$> getSymbolicLinkStatus f) $ do
|
whenM (liftIO $ not . isSymbolicLink <$> getSymbolicLinkStatus f) $ do
|
||||||
moveAnnex k f
|
v <-tryAnnexIO (moveAnnex k f)
|
||||||
l <- inRepo $ gitAnnexLink f k
|
case v of
|
||||||
liftIO $ createSymbolicLink l f
|
Right _ -> do
|
||||||
|
l <- inRepo $ gitAnnexLink f k
|
||||||
|
liftIO $ createSymbolicLink l f
|
||||||
|
Left e -> catchAnnex (Command.Add.undo f k e)
|
||||||
|
warnlocked
|
||||||
showEndOk
|
showEndOk
|
||||||
|
|
||||||
|
warnlocked :: SomeException -> Annex ()
|
||||||
|
warnlocked e = do
|
||||||
|
warning $ show e
|
||||||
|
warning "leaving this file as-is; correct this problem and run git annex add on it"
|
||||||
|
|
||||||
cleandirect k = do
|
cleandirect k = do
|
||||||
liftIO . nukeFile =<< calcRepo (gitAnnexInodeCache k)
|
liftIO . nukeFile =<< calcRepo (gitAnnexInodeCache k)
|
||||||
liftIO . nukeFile =<< calcRepo (gitAnnexMapping k)
|
liftIO . nukeFile =<< calcRepo (gitAnnexMapping k)
|
||||||
|
|
2
debian/changelog
vendored
2
debian/changelog
vendored
|
@ -13,6 +13,8 @@ git-annex (4.20130921) UNRELEASED; urgency=low
|
||||||
* assistant: Clear the list of failed transfers when doing a full transfer
|
* assistant: Clear the list of failed transfers when doing a full transfer
|
||||||
scan. This prevents repeated retries to download files that are not
|
scan. This prevents repeated retries to download files that are not
|
||||||
available, or are not referenced by the current git tree.
|
available, or are not referenced by the current git tree.
|
||||||
|
* indirect: Better behavior when a file in direct mode is not owned by
|
||||||
|
the user running the conversion.
|
||||||
|
|
||||||
-- Joey Hess <joeyh@debian.org> Sun, 22 Sep 2013 19:42:29 -0400
|
-- Joey Hess <joeyh@debian.org> Sun, 22 Sep 2013 19:42:29 -0400
|
||||||
|
|
||||||
|
|
|
@ -69,3 +69,10 @@ index 7835988..ed8ea6c 100644
|
||||||
"""]]
|
"""]]
|
||||||
|
|
||||||
Any update on this? Why is `-a` used here? -- [[anarcat]]
|
Any update on this? Why is `-a` used here? -- [[anarcat]]
|
||||||
|
|
||||||
|
> -a is not really the problem. You certianly do usually want
|
||||||
|
> to commit your changes before converting to direct mode.
|
||||||
|
>
|
||||||
|
> [[done]]; now when this happens it catches the exception and
|
||||||
|
> leaves the file in direct mode, which is the same as it being
|
||||||
|
> unlocked. --[[Joey]]
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue