2012-12-12 23:20:38 +00:00
|
|
|
{- git-annex direct mode
|
|
|
|
-
|
|
|
|
- Copyright 2012 Joey Hess <joey@kitenet.net>
|
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
|
|
|
module Annex.Direct where
|
|
|
|
|
|
|
|
import Common.Annex
|
|
|
|
import qualified Git
|
|
|
|
import qualified Git.LsFiles
|
2012-12-18 19:04:44 +00:00
|
|
|
import qualified Git.Merge
|
|
|
|
import qualified Git.DiffTree as DiffTree
|
|
|
|
import Git.Sha
|
2012-12-12 23:20:38 +00:00
|
|
|
import Git.Types
|
|
|
|
import Annex.CatFile
|
2012-12-18 19:04:44 +00:00
|
|
|
import Utility.FileMode
|
|
|
|
import qualified Annex.Queue
|
2012-12-12 23:20:38 +00:00
|
|
|
import Logs.Location
|
|
|
|
import Backend
|
|
|
|
import Types.KeySource
|
|
|
|
import Annex.Content
|
|
|
|
import Annex.Content.Direct
|
fully support core.symlinks=false in all relevant symlink handling code
Refactored annex link code into nice clean new library.
Audited and dealt with calls to createSymbolicLink.
Remaining calls are all safe, because:
Annex/Link.hs: ( liftIO $ createSymbolicLink linktarget file
only when core.symlinks=true
Assistant/WebApp/Configurators/Local.hs: createSymbolicLink link link
test if symlinks can be made
Command/Fix.hs: liftIO $ createSymbolicLink link file
command only works in indirect mode
Command/FromKey.hs: liftIO $ createSymbolicLink link file
command only works in indirect mode
Command/Indirect.hs: liftIO $ createSymbolicLink l f
refuses to run if core.symlinks=false
Init.hs: createSymbolicLink f f2
test if symlinks can be made
Remote/Directory.hs: go [file] = catchBoolIO $ createSymbolicLink file f >> return True
fast key linking; catches failure to make symlink and falls back to copy
Remote/Git.hs: liftIO $ catchBoolIO $ createSymbolicLink loc file >> return True
ditto
Upgrade/V1.hs: liftIO $ createSymbolicLink link f
v1 repos could not be on a filesystem w/o symlinks
Audited and dealt with calls to readSymbolicLink.
Remaining calls are all safe, because:
Annex/Link.hs: ( liftIO $ catchMaybeIO $ readSymbolicLink file
only when core.symlinks=true
Assistant/Threads/Watcher.hs: ifM ((==) (Just link) <$> liftIO (catchMaybeIO $ readSymbolicLink file))
code that fixes real symlinks when inotify sees them
It's ok to not fix psdueo-symlinks.
Assistant/Threads/Watcher.hs: mlink <- liftIO (catchMaybeIO $ readSymbolicLink file)
ditto
Command/Fix.hs: stopUnless ((/=) (Just link) <$> liftIO (catchMaybeIO $ readSymbolicLink file)) $ do
command only works in indirect mode
Upgrade/V1.hs: getsymlink = takeFileName <$> readSymbolicLink file
v1 repos could not be on a filesystem w/o symlinks
Audited and dealt with calls to isSymbolicLink.
(Typically used with getSymbolicLinkStatus, but that is just used because
getFileStatus is not as robust; it also works on pseudolinks.)
Remaining calls are all safe, because:
Assistant/Threads/SanityChecker.hs: | isSymbolicLink s -> addsymlink file ms
only handles staging of symlinks that were somehow not staged
(might need to be updated to support pseudolinks, but this is
only a belt-and-suspenders check anyway, and I've never seen the code run)
Command/Add.hs: if isSymbolicLink s || not (isRegularFile s)
avoids adding symlinks to the annex, so not relevant
Command/Indirect.hs: | isSymbolicLink s -> void $ flip whenAnnexed f $
only allowed on systems that support symlinks
Command/Indirect.hs: whenM (liftIO $ not . isSymbolicLink <$> getSymbolicLinkStatus f) $ do
ditto
Seek.hs:notSymlink f = liftIO $ not . isSymbolicLink <$> getSymbolicLinkStatus f
used to find unlocked files, only relevant in indirect mode
Utility/FSEvents.hs: | Files.isSymbolicLink s = runhook addSymlinkHook $ Just s
Utility/FSEvents.hs: | Files.isSymbolicLink s ->
Utility/INotify.hs: | Files.isSymbolicLink s ->
Utility/INotify.hs: checkfiletype Files.isSymbolicLink addSymlinkHook f
Utility/Kqueue.hs: | Files.isSymbolicLink s = callhook addSymlinkHook (Just s) change
all above are lower-level, not relevant
Audited and dealt with calls to isSymLink.
Remaining calls are all safe, because:
Annex/Direct.hs: | isSymLink (getmode item) =
This is looking at git diff-tree objects, not files on disk
Command/Unused.hs: | isSymLink (LsTree.mode l) = do
This is looking at git ls-tree, not file on disk
Utility/FileMode.hs:isSymLink :: FileMode -> Bool
Utility/FileMode.hs:isSymLink = checkMode symbolicLinkMode
low-level
Done!!
2013-02-17 19:05:55 +00:00
|
|
|
import Annex.Link
|
2013-02-14 20:17:40 +00:00
|
|
|
import Utility.InodeCache
|
2013-01-14 15:56:37 +00:00
|
|
|
import Utility.CopyFile
|
2013-04-30 23:33:43 +00:00
|
|
|
import Annex.Perms
|
2013-05-17 19:59:37 +00:00
|
|
|
import Annex.ReplaceFile
|
2013-05-25 19:11:54 +00:00
|
|
|
import Annex.Exception
|
2012-12-12 23:20:38 +00:00
|
|
|
|
|
|
|
{- Uses git ls-files to find files that need to be committed, and stages
|
|
|
|
- them into the index. Returns True if some changes were staged. -}
|
|
|
|
stageDirect :: Annex Bool
|
|
|
|
stageDirect = do
|
|
|
|
Annex.Queue.flush
|
|
|
|
top <- fromRepo Git.repoPath
|
|
|
|
(l, cleanup) <- inRepo $ Git.LsFiles.stagedDetails [top]
|
|
|
|
forM_ l go
|
|
|
|
void $ liftIO cleanup
|
|
|
|
staged <- Annex.Queue.size
|
|
|
|
Annex.Queue.flush
|
|
|
|
return $ staged /= 0
|
|
|
|
where
|
|
|
|
{- Determine what kind of modified or deleted file this is, as
|
|
|
|
- efficiently as we can, by getting any key that's associated
|
|
|
|
- with it in git, as well as its stat info. -}
|
|
|
|
go (file, Just sha) = do
|
sync: Bug fix, avoid adding to the annex the dummy symlinks used on crippled filesystems.
The root of the problem is that toInodeCache sees a non-symlink, and so
goes on and generates a new inode cache for the dummy symlink.
Any place that toInodeCache, or sameFileStatus, or genInodeCache are called
may need to deal with this case. Although many of them are ok. For example,
prepSendAnnex calls sameInodeCache, which calls genInodeCache.. but if
the file content is not present, the InodeCache generated for its standin
file is appropriately not the same, and so it returns Nothing.
I've audited some, but have to say I'm not happy with this; it should be
handled at the type level somehow, or a toInodeCache wrapper be used that
is aware of dummy symlinks.
(The Watcher already dealt with it, via the guardSymlinkStandin function.)
2013-04-23 21:13:09 +00:00
|
|
|
shakey <- catKey sha
|
2012-12-12 23:20:38 +00:00
|
|
|
mstat <- liftIO $ catchMaybeIO $ getSymbolicLinkStatus file
|
sync: Bug fix, avoid adding to the annex the dummy symlinks used on crippled filesystems.
The root of the problem is that toInodeCache sees a non-symlink, and so
goes on and generates a new inode cache for the dummy symlink.
Any place that toInodeCache, or sameFileStatus, or genInodeCache are called
may need to deal with this case. Although many of them are ok. For example,
prepSendAnnex calls sameInodeCache, which calls genInodeCache.. but if
the file content is not present, the InodeCache generated for its standin
file is appropriately not the same, and so it returns Nothing.
I've audited some, but have to say I'm not happy with this; it should be
handled at the type level somehow, or a toInodeCache wrapper be used that
is aware of dummy symlinks.
(The Watcher already dealt with it, via the guardSymlinkStandin function.)
2013-04-23 21:13:09 +00:00
|
|
|
filekey <- isAnnexLink file
|
|
|
|
case (shakey, filekey, mstat, toInodeCache =<< mstat) of
|
|
|
|
(_, Just key, _, _)
|
|
|
|
| shakey == filekey -> noop
|
|
|
|
{- A changed symlink. -}
|
|
|
|
| otherwise -> stageannexlink file key
|
|
|
|
(Just key, _, _, Just cache) -> do
|
2012-12-12 23:20:38 +00:00
|
|
|
{- All direct mode files will show as
|
|
|
|
- modified, so compare the cache to see if
|
|
|
|
- it really was. -}
|
2013-02-14 20:17:40 +00:00
|
|
|
oldcache <- recordedInodeCache key
|
2013-03-11 06:57:48 +00:00
|
|
|
case oldcache of
|
2013-04-06 20:01:39 +00:00
|
|
|
[] -> modifiedannexed file key cache
|
|
|
|
_ -> unlessM (elemInodeCaches cache oldcache) $
|
2013-03-11 06:57:48 +00:00
|
|
|
modifiedannexed file key cache
|
sync: Bug fix, avoid adding to the annex the dummy symlinks used on crippled filesystems.
The root of the problem is that toInodeCache sees a non-symlink, and so
goes on and generates a new inode cache for the dummy symlink.
Any place that toInodeCache, or sameFileStatus, or genInodeCache are called
may need to deal with this case. Although many of them are ok. For example,
prepSendAnnex calls sameInodeCache, which calls genInodeCache.. but if
the file content is not present, the InodeCache generated for its standin
file is appropriately not the same, and so it returns Nothing.
I've audited some, but have to say I'm not happy with this; it should be
handled at the type level somehow, or a toInodeCache wrapper be used that
is aware of dummy symlinks.
(The Watcher already dealt with it, via the guardSymlinkStandin function.)
2013-04-23 21:13:09 +00:00
|
|
|
(Just key, _, Nothing, _) -> deletedannexed file key
|
|
|
|
(Nothing, _, Nothing, _) -> deletegit file
|
|
|
|
(_, _, Just _, _) -> addgit file
|
2013-01-06 21:24:22 +00:00
|
|
|
go _ = noop
|
2012-12-12 23:20:38 +00:00
|
|
|
|
|
|
|
modifiedannexed file oldkey cache = do
|
|
|
|
void $ removeAssociatedFile oldkey file
|
|
|
|
void $ addDirect file cache
|
|
|
|
|
|
|
|
deletedannexed file key = do
|
|
|
|
void $ removeAssociatedFile key file
|
|
|
|
deletegit file
|
|
|
|
|
sync: Bug fix, avoid adding to the annex the dummy symlinks used on crippled filesystems.
The root of the problem is that toInodeCache sees a non-symlink, and so
goes on and generates a new inode cache for the dummy symlink.
Any place that toInodeCache, or sameFileStatus, or genInodeCache are called
may need to deal with this case. Although many of them are ok. For example,
prepSendAnnex calls sameInodeCache, which calls genInodeCache.. but if
the file content is not present, the InodeCache generated for its standin
file is appropriately not the same, and so it returns Nothing.
I've audited some, but have to say I'm not happy with this; it should be
handled at the type level somehow, or a toInodeCache wrapper be used that
is aware of dummy symlinks.
(The Watcher already dealt with it, via the guardSymlinkStandin function.)
2013-04-23 21:13:09 +00:00
|
|
|
stageannexlink file key = do
|
|
|
|
l <- inRepo $ gitAnnexLink file key
|
|
|
|
stageSymlink file =<< hashSymlink l
|
|
|
|
void $ addAssociatedFile key file
|
|
|
|
|
2012-12-12 23:20:38 +00:00
|
|
|
addgit file = Annex.Queue.addCommand "add" [Param "-f"] [file]
|
|
|
|
|
|
|
|
deletegit file = Annex.Queue.addCommand "rm" [Param "-f"] [file]
|
|
|
|
|
|
|
|
{- Adds a file to the annex in direct mode. Can fail, if the file is
|
|
|
|
- modified or deleted while it's being added. -}
|
2013-02-14 20:17:40 +00:00
|
|
|
addDirect :: FilePath -> InodeCache -> Annex Bool
|
2012-12-12 23:20:38 +00:00
|
|
|
addDirect file cache = do
|
|
|
|
showStart "add" file
|
|
|
|
let source = KeySource
|
|
|
|
{ keyFilename = file
|
|
|
|
, contentLocation = file
|
2013-02-14 20:54:36 +00:00
|
|
|
, inodeCache = Just cache
|
2012-12-12 23:20:38 +00:00
|
|
|
}
|
|
|
|
got =<< genKey source =<< chooseBackend file
|
|
|
|
where
|
|
|
|
got Nothing = do
|
|
|
|
showEndFail
|
|
|
|
return False
|
2013-04-06 20:01:39 +00:00
|
|
|
got (Just (key, _)) = ifM (sameInodeCache file [cache])
|
2012-12-12 23:20:38 +00:00
|
|
|
( do
|
2013-04-04 19:46:33 +00:00
|
|
|
l <- inRepo $ gitAnnexLink file key
|
|
|
|
stageSymlink file =<< hashSymlink l
|
2013-04-06 20:01:39 +00:00
|
|
|
addInodeCache key cache
|
2012-12-12 23:20:38 +00:00
|
|
|
void $ addAssociatedFile key file
|
|
|
|
logStatus key InfoPresent
|
|
|
|
showEndOk
|
|
|
|
return True
|
|
|
|
, do
|
|
|
|
showEndFail
|
|
|
|
return False
|
|
|
|
)
|
2012-12-18 19:04:44 +00:00
|
|
|
|
|
|
|
{- In direct mode, git merge would usually refuse to do anything, since it
|
|
|
|
- sees present direct mode files as type changed files. To avoid this,
|
|
|
|
- merge is run with the work tree set to a temp directory.
|
|
|
|
-
|
|
|
|
- This should only be used once any changes to the real working tree have
|
|
|
|
- already been committed, because it overwrites files in the working tree.
|
|
|
|
-}
|
|
|
|
mergeDirect :: FilePath -> Git.Ref -> Git.Repo -> IO Bool
|
|
|
|
mergeDirect d branch g = do
|
|
|
|
createDirectoryIfMissing True d
|
|
|
|
let g' = g { location = Local { gitdir = Git.localGitDir g, worktree = Just d } }
|
|
|
|
Git.Merge.mergeNonInteractive branch g'
|
|
|
|
|
|
|
|
{- Cleans up after a direct mode merge. The merge must have been committed,
|
|
|
|
- and the commit sha passed in, along with the old sha of the tree
|
|
|
|
- before the merge. Uses git diff-tree to find files that changed between
|
|
|
|
- the two shas, and applies those changes to the work tree.
|
|
|
|
-}
|
|
|
|
mergeDirectCleanup :: FilePath -> Git.Ref -> Git.Ref -> Annex ()
|
|
|
|
mergeDirectCleanup d oldsha newsha = do
|
|
|
|
(items, cleanup) <- inRepo $ DiffTree.diffTreeRecursive oldsha newsha
|
|
|
|
forM_ items updated
|
2013-04-03 07:52:41 +00:00
|
|
|
void $ liftIO cleanup
|
2012-12-18 19:04:44 +00:00
|
|
|
liftIO $ removeDirectoryRecursive d
|
|
|
|
where
|
|
|
|
updated item = do
|
2013-05-25 19:11:54 +00:00
|
|
|
void $ tryAnnex $
|
|
|
|
go DiffTree.srcsha DiffTree.srcmode moveout moveout_raw
|
|
|
|
void $ tryAnnex $
|
|
|
|
go DiffTree.dstsha DiffTree.dstmode movein movein_raw
|
2012-12-18 19:04:44 +00:00
|
|
|
where
|
|
|
|
go getsha getmode a araw
|
|
|
|
| getsha item == nullSha = noop
|
|
|
|
| isSymLink (getmode item) =
|
|
|
|
maybe (araw f) (\k -> void $ a k f)
|
|
|
|
=<< catKey (getsha item)
|
|
|
|
| otherwise = araw f
|
|
|
|
f = DiffTree.file item
|
|
|
|
|
2013-02-18 06:39:40 +00:00
|
|
|
moveout = removeDirect
|
2012-12-18 19:04:44 +00:00
|
|
|
|
|
|
|
{- Files deleted by the merge are removed from the work tree.
|
|
|
|
- Empty work tree directories are removed, per git behavior. -}
|
|
|
|
moveout_raw f = liftIO $ do
|
|
|
|
nukeFile f
|
2013-02-14 18:10:36 +00:00
|
|
|
void $ tryIO $ removeDirectory $ parentDir f
|
2012-12-18 19:04:44 +00:00
|
|
|
|
2013-05-20 17:37:52 +00:00
|
|
|
{- If the file is already present, with the right content for the
|
|
|
|
- key, it's left alone. Otherwise, create the symlink and then
|
|
|
|
- if possible, replace it with the content. -}
|
|
|
|
movein k f = unlessM (goodContent k f) $ do
|
2013-04-04 19:46:33 +00:00
|
|
|
l <- inRepo $ gitAnnexLink f k
|
2013-04-02 17:13:42 +00:00
|
|
|
replaceFile f $ makeAnnexLink l
|
2012-12-18 21:15:16 +00:00
|
|
|
toDirect k f
|
2012-12-18 19:04:44 +00:00
|
|
|
|
|
|
|
{- Any new, modified, or renamed files were written to the temp
|
|
|
|
- directory by the merge, and are moved to the real work tree. -}
|
|
|
|
movein_raw f = liftIO $ do
|
|
|
|
createDirectoryIfMissing True $ parentDir f
|
2013-02-14 18:10:36 +00:00
|
|
|
void $ tryIO $ rename (d </> f) f
|
2012-12-18 19:04:44 +00:00
|
|
|
|
2012-12-18 21:15:16 +00:00
|
|
|
{- If possible, converts a symlink in the working tree into a direct
|
2013-05-23 00:58:27 +00:00
|
|
|
- mode file. If the content is not available, leaves the symlink
|
|
|
|
- unchanged. -}
|
2012-12-18 21:15:16 +00:00
|
|
|
toDirect :: Key -> FilePath -> Annex ()
|
2013-02-18 06:39:40 +00:00
|
|
|
toDirect k f = fromMaybe noop =<< toDirectGen k f
|
2012-12-18 21:15:16 +00:00
|
|
|
|
|
|
|
toDirectGen :: Key -> FilePath -> Annex (Maybe (Annex ()))
|
|
|
|
toDirectGen k f = do
|
2013-04-04 19:46:33 +00:00
|
|
|
loc <- calcRepo $ gitAnnexLocation k
|
2013-05-06 16:43:03 +00:00
|
|
|
ifM (liftIO $ doesFileExist loc)
|
2013-05-23 00:58:27 +00:00
|
|
|
( return $ Just $ fromindirect loc
|
|
|
|
, do
|
|
|
|
{- Copy content from another direct file. -}
|
|
|
|
absf <- liftIO $ absPath f
|
2013-07-08 21:29:42 +00:00
|
|
|
dlocs <- filterM (goodContent k) =<<
|
|
|
|
filterM (\l -> isNothing <$> getAnnexLinkTarget l) =<<
|
|
|
|
(filter (/= absf) <$> addAssociatedFile k f)
|
|
|
|
case dlocs of
|
|
|
|
[] -> return Nothing
|
|
|
|
(dloc:_) -> return $ Just $ fromdirect dloc
|
2013-05-06 16:43:03 +00:00
|
|
|
)
|
|
|
|
where
|
2013-05-23 00:58:27 +00:00
|
|
|
fromindirect loc = do
|
2013-05-06 16:43:03 +00:00
|
|
|
{- Move content from annex to direct file. -}
|
|
|
|
thawContentDir loc
|
|
|
|
updateInodeCache k loc
|
2013-05-17 19:59:37 +00:00
|
|
|
void $ addAssociatedFile k f
|
2013-05-06 16:43:03 +00:00
|
|
|
thawContent loc
|
|
|
|
replaceFile f $ liftIO . moveFile loc
|
2013-07-08 21:29:42 +00:00
|
|
|
fromdirect loc = do
|
|
|
|
replaceFile f $
|
|
|
|
liftIO . void . copyFileExternal loc
|
|
|
|
updateInodeCache k f
|
2012-12-18 21:15:16 +00:00
|
|
|
|
2013-05-20 20:28:33 +00:00
|
|
|
{- Removes a direct mode file, while retaining its content in the annex
|
|
|
|
- (unless its content has already been changed). -}
|
2012-12-18 21:15:16 +00:00
|
|
|
removeDirect :: Key -> FilePath -> Annex ()
|
|
|
|
removeDirect k f = do
|
2013-05-20 20:28:33 +00:00
|
|
|
void $ removeAssociatedFileUnchecked k f
|
|
|
|
unlessM (inAnnex k) $
|
|
|
|
ifM (goodContent k f)
|
|
|
|
( moveAnnex k f
|
|
|
|
, logStatus k InfoMissing
|
|
|
|
)
|
2012-12-18 21:15:16 +00:00
|
|
|
liftIO $ do
|
|
|
|
nukeFile f
|
2013-02-14 18:10:36 +00:00
|
|
|
void $ tryIO $ removeDirectory $ parentDir f
|
2012-12-25 19:48:15 +00:00
|
|
|
|
|
|
|
{- Called when a direct mode file has been changed. Its old content may be
|
|
|
|
- lost. -}
|
|
|
|
changedDirect :: Key -> FilePath -> Annex ()
|
|
|
|
changedDirect oldk f = do
|
|
|
|
locs <- removeAssociatedFile oldk f
|
|
|
|
whenM (pure (null locs) <&&> not <$> inAnnex oldk) $
|
|
|
|
logStatus oldk InfoMissing
|