git-annex/Annex/WorkTree.hs

118 lines
3.8 KiB
Haskell
Raw Normal View History

2015-12-15 19:34:28 +00:00
{- git-annex worktree files
-
- Copyright 2013-2020 Joey Hess <id@joeyh.name>
2015-12-15 19:34:28 +00:00
-
- Licensed under the GNU AGPL version 3 or higher.
2015-12-15 19:34:28 +00:00
-}
module Annex.WorkTree where
import Annex.Common
2015-12-15 19:34:28 +00:00
import Annex.Link
import Annex.CatFile
import Annex.Content
import Annex.ReplaceFile
import Annex.CurrentBranch
import Annex.InodeSentinal
import Utility.InodeCache
import Git.FilePath
2016-10-17 18:58:33 +00:00
import qualified Git.Ref
import qualified Git.LsTree
import qualified Git.Types
import qualified Database.Keys
import qualified Database.Keys.SQL
import Config
import qualified Utility.RawFilePath as R
2015-12-15 19:34:28 +00:00
import Control.Concurrent
{- 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.
-
- 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
-}
2020-07-10 18:17:35 +00:00
lookupKey :: RawFilePath -> Annex (Maybe Key)
lookupKey = lookupKey' catkeyfile
where
catkeyfile file =
ifM (liftIO $ doesFileExist $ fromRawFilePath file)
( catKeyFile file
, catKeyFileHidden file =<< getCurrentBranch
)
2020-07-10 18:17:35 +00:00
lookupKeyNotHidden :: RawFilePath -> Annex (Maybe Key)
lookupKeyNotHidden = lookupKey' catkeyfile
where
catkeyfile file =
ifM (liftIO $ doesFileExist $ fromRawFilePath file)
( catKeyFile file
, return Nothing
)
2020-07-10 18:17:35 +00:00
lookupKey' :: (RawFilePath -> Annex (Maybe Key)) -> RawFilePath -> Annex (Maybe Key)
lookupKey' catkeyfile file = isAnnexLink file >>= \case
Just key -> return (Just key)
Nothing -> catkeyfile file
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 :: (RawFilePath -> Key -> Annex (Maybe a)) -> RawFilePath -> Annex (Maybe a)
2015-12-15 19:34:28 +00:00
whenAnnexed a file = ifAnnexed file (a file) (return Nothing)
ifAnnexed :: RawFilePath -> (Key -> Annex a) -> Annex a -> Annex a
2020-07-10 18:17:35 +00:00
ifAnnexed file yes no = maybe no yes =<< lookupKey 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
- when initializing/upgrading a v6+ mode repository.
-
- Also, the content for the unlocked file may already be present as
- an annex object. If so, populate the pointer file with it.
- But if worktree file does not have a pointer file's content, it is left
- as-is.
2016-10-17 18:58:33 +00:00
-}
scanUnlockedFiles :: Annex ()
scanUnlockedFiles = whenM (inRepo Git.Ref.headExists <&&> not <$> isBareRepo) $ do
dropold <- liftIO $ newMVar $
Database.Keys.runWriter $
liftIO . Database.Keys.SQL.dropAllAssociatedFiles
(l, cleanup) <- inRepo $ Git.LsTree.lsTree Git.LsTree.LsTreeRecursive Git.Ref.headRef
forM_ l $ \i ->
when (isregfile i) $
maybe noop (add dropold i)
=<< catKey (Git.LsTree.sha i)
liftIO $ void cleanup
2016-10-17 18:58:33 +00:00
where
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
add dropold i k = do
join $ fromMaybe noop <$> liftIO (tryTakeMVar dropold)
let tf = Git.LsTree.file i
Database.Keys.runWriter $
liftIO . Database.Keys.SQL.addAssociatedFileFast k tf
whenM (inAnnex k) $ do
f <- fromRepo $ fromTopFilePath tf
liftIO (isPointerFile f) >>= \case
Just k' | k' == k -> do
destmode <- liftIO $ catchMaybeIO $
fileMode <$> R.getFileStatus f
ic <- replaceWorkTreeFile (fromRawFilePath f) $ \tmp -> do
let tmp' = toRawFilePath tmp
linkFromAnnex k tmp destmode >>= \case
LinkAnnexOk ->
withTSDelta (liftIO . genInodeCache tmp')
LinkAnnexNoop -> return Nothing
LinkAnnexFailed -> liftIO $ do
writePointerFile tmp' k destmode
return Nothing
maybe noop (restagePointerFile (Restage True) f) ic
_ -> noop