2015-12-15 19:34:28 +00:00
|
|
|
{- git-annex worktree files
|
|
|
|
-
|
2019-02-05 17:13:09 +00:00
|
|
|
- Copyright 2013-2019 Joey Hess <id@joeyh.name>
|
2015-12-15 19:34:28 +00:00
|
|
|
-
|
2019-03-13 19:48:14 +00:00
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2015-12-15 19:34:28 +00:00
|
|
|
-}
|
|
|
|
|
|
|
|
module Annex.WorkTree where
|
|
|
|
|
2016-01-20 20:36:33 +00:00
|
|
|
import Annex.Common
|
2015-12-15 19:34:28 +00:00
|
|
|
import Annex.Link
|
|
|
|
import Annex.CatFile
|
2015-12-16 18:27:12 +00:00
|
|
|
import Annex.Version
|
2016-10-17 19:19:47 +00:00
|
|
|
import Annex.Content
|
|
|
|
import Annex.ReplaceFile
|
2018-10-19 21:51:25 +00:00
|
|
|
import Annex.CurrentBranch
|
2018-12-11 17:05:03 +00:00
|
|
|
import Annex.InodeSentinal
|
|
|
|
import Utility.InodeCache
|
2015-12-16 18:27:12 +00:00
|
|
|
import Config
|
2016-10-17 19:19:47 +00:00
|
|
|
import Git.FilePath
|
2016-10-17 18:58:33 +00:00
|
|
|
import qualified Git.Ref
|
|
|
|
import qualified Git.LsTree
|
|
|
|
import qualified Git.Types
|
|
|
|
import Database.Types
|
|
|
|
import qualified Database.Keys
|
|
|
|
import qualified Database.Keys.SQL
|
2015-12-15 19:34:28 +00:00
|
|
|
|
2015-12-30 18:23:31 +00:00
|
|
|
{- Looks up the key corresponding to an annexed file in the work tree,
|
2015-12-15 19:34:28 +00:00
|
|
|
- by examining what the file links to.
|
|
|
|
-
|
|
|
|
- An unlocked file will not have a link on disk, so fall back to
|
|
|
|
- looking for a pointer to a key in git.
|
2018-10-19 21:51:25 +00:00
|
|
|
-
|
|
|
|
- When in an adjusted branch that may have hidden the file, looks for a
|
|
|
|
- pointer to a key in the original branch.
|
2015-12-15 19:34:28 +00:00
|
|
|
-}
|
|
|
|
lookupFile :: FilePath -> Annex (Maybe Key)
|
2019-02-05 17:13:09 +00:00
|
|
|
lookupFile = lookupFile' catkeyfile
|
|
|
|
where
|
|
|
|
catkeyfile file =
|
|
|
|
ifM (liftIO $ doesFileExist file)
|
2018-10-19 21:51:25 +00:00
|
|
|
( catKeyFile file
|
|
|
|
, catKeyFileHidden file =<< getCurrentBranch
|
2015-12-16 18:27:12 +00:00
|
|
|
)
|
2019-02-05 17:13:09 +00:00
|
|
|
|
|
|
|
lookupFileNotHidden :: FilePath -> Annex (Maybe Key)
|
|
|
|
lookupFileNotHidden = lookupFile' catkeyfile
|
|
|
|
where
|
|
|
|
catkeyfile file =
|
|
|
|
ifM (liftIO $ doesFileExist file)
|
|
|
|
( catKeyFile file
|
|
|
|
, return Nothing
|
|
|
|
)
|
|
|
|
|
|
|
|
lookupFile' :: (FilePath -> Annex (Maybe Key)) -> FilePath -> Annex (Maybe Key)
|
|
|
|
lookupFile' catkeyfile file = isAnnexLink file >>= \case
|
|
|
|
Just key -> return (Just key)
|
|
|
|
Nothing -> ifM (versionSupportsUnlockedPointers <||> isDirect)
|
|
|
|
( catkeyfile file
|
2017-12-05 19:00:50 +00:00
|
|
|
, return Nothing
|
|
|
|
)
|
2015-12-15 19:34:28 +00:00
|
|
|
|
|
|
|
{- Modifies an action to only act on files that are already annexed,
|
|
|
|
- and passes the key on to it. -}
|
|
|
|
whenAnnexed :: (FilePath -> Key -> Annex (Maybe a)) -> FilePath -> Annex (Maybe a)
|
|
|
|
whenAnnexed a file = ifAnnexed file (a file) (return Nothing)
|
|
|
|
|
|
|
|
ifAnnexed :: FilePath -> (Key -> Annex a) -> Annex a -> Annex a
|
|
|
|
ifAnnexed file yes no = maybe no yes =<< lookupFile file
|
2016-10-17 18:58:33 +00:00
|
|
|
|
|
|
|
{- Find all unlocked files and update the keys database for them.
|
|
|
|
-
|
|
|
|
- This is expensive, and so normally the associated files are updated
|
|
|
|
- incrementally when changes are noticed. So, this only needs to be done
|
2019-07-16 16:36:29 +00:00
|
|
|
- when initializing/upgrading a v6+ mode repository.
|
2016-10-17 19:19:47 +00:00
|
|
|
-
|
|
|
|
- Also, the content for the unlocked file may already be present as
|
2019-08-26 17:46:58 +00:00
|
|
|
- an annex object. If so, make the unlocked file use that content
|
|
|
|
- when replacefiles is True.
|
2016-10-17 18:58:33 +00:00
|
|
|
-}
|
2019-08-26 17:46:58 +00:00
|
|
|
scanUnlockedFiles :: Bool -> Annex ()
|
|
|
|
scanUnlockedFiles replacefiles = whenM (inRepo Git.Ref.headExists) $ do
|
2016-10-17 19:19:47 +00:00
|
|
|
Database.Keys.runWriter $
|
|
|
|
liftIO . Database.Keys.SQL.dropAllAssociatedFiles
|
2019-02-21 21:32:59 +00:00
|
|
|
(l, cleanup) <- inRepo $ Git.LsTree.lsTree Git.LsTree.LsTreeRecursive Git.Ref.headRef
|
2016-10-17 19:19:47 +00:00
|
|
|
forM_ l $ \i ->
|
|
|
|
when (isregfile i) $
|
|
|
|
maybe noop (add i)
|
|
|
|
=<< catKey (Git.LsTree.sha i)
|
|
|
|
liftIO $ void cleanup
|
2016-10-17 18:58:33 +00:00
|
|
|
where
|
2018-05-14 18:22:44 +00:00
|
|
|
isregfile i = case Git.Types.toTreeItemType (Git.LsTree.mode i) of
|
|
|
|
Just Git.Types.TreeFile -> True
|
|
|
|
Just Git.Types.TreeExecutable -> True
|
2016-10-17 18:58:33 +00:00
|
|
|
_ -> False
|
2016-10-17 19:19:47 +00:00
|
|
|
add i k = do
|
|
|
|
let tf = Git.LsTree.file i
|
|
|
|
Database.Keys.runWriter $
|
|
|
|
liftIO . Database.Keys.SQL.addAssociatedFileFast (toIKey k) tf
|
2019-08-26 17:46:58 +00:00
|
|
|
whenM (pure replacefiles <&&> inAnnex k) $ do
|
2016-10-17 19:19:47 +00:00
|
|
|
f <- fromRepo $ fromTopFilePath tf
|
|
|
|
destmode <- liftIO $ catchMaybeIO $ fileMode <$> getFileStatus f
|
2018-12-11 17:05:03 +00:00
|
|
|
ic <- replaceFile f $ \tmp ->
|
2017-12-05 19:00:50 +00:00
|
|
|
linkFromAnnex k tmp destmode >>= \case
|
2018-12-11 17:05:03 +00:00
|
|
|
LinkAnnexOk ->
|
|
|
|
withTSDelta (liftIO . genInodeCache tmp)
|
|
|
|
LinkAnnexNoop -> return Nothing
|
|
|
|
LinkAnnexFailed -> liftIO $ do
|
2016-10-17 19:19:47 +00:00
|
|
|
writePointerFile tmp k destmode
|
2018-12-11 17:05:03 +00:00
|
|
|
return Nothing
|
|
|
|
maybe noop (restagePointerFile (Restage True) f) ic
|