2019-08-27 18:01:28 +00:00
|
|
|
{- git-annex direct mode
|
|
|
|
-
|
|
|
|
- This only contains some remnants needed to convert away from direct mode.
|
2012-12-07 21:28:23 +00:00
|
|
|
-
|
2015-01-21 16:50:09 +00:00
|
|
|
- Copyright 2012-2014 Joey Hess <id@joeyh.name>
|
2012-12-07 21:28:23 +00:00
|
|
|
-
|
2019-03-13 19:48:14 +00:00
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2012-12-07 21:28:23 +00:00
|
|
|
-}
|
|
|
|
|
2019-11-27 20:54:11 +00:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
|
2019-08-27 18:01:28 +00:00
|
|
|
module Upgrade.V5.Direct (
|
|
|
|
switchHEADBack,
|
|
|
|
setIndirect,
|
2019-08-27 17:57:17 +00:00
|
|
|
goodContent,
|
2012-12-07 21:28:23 +00:00
|
|
|
associatedFiles,
|
2013-11-15 18:52:03 +00:00
|
|
|
removeAssociatedFiles,
|
2013-02-15 20:37:57 +00:00
|
|
|
removeInodeCache,
|
2012-12-07 21:28:23 +00:00
|
|
|
) where
|
|
|
|
|
2016-01-20 20:36:33 +00:00
|
|
|
import Annex.Common
|
2012-12-07 21:28:23 +00:00
|
|
|
import qualified Git
|
2019-08-27 18:01:28 +00:00
|
|
|
import qualified Git.Config
|
|
|
|
import qualified Git.Ref
|
|
|
|
import qualified Git.Branch
|
|
|
|
import Git.Types
|
|
|
|
import Config
|
|
|
|
import Annex.Perms
|
2013-02-14 20:17:40 +00:00
|
|
|
import Utility.InodeCache
|
2015-12-09 19:42:16 +00:00
|
|
|
import Annex.InodeSentinal
|
2012-12-07 21:28:23 +00:00
|
|
|
|
2019-08-27 18:01:28 +00:00
|
|
|
setIndirect :: Annex ()
|
|
|
|
setIndirect = do
|
|
|
|
setbare
|
|
|
|
switchHEADBack
|
|
|
|
setConfig (annexConfig "direct") val
|
|
|
|
where
|
|
|
|
val = Git.Config.boolConfig False
|
|
|
|
coreworktree = ConfigKey "core.worktree"
|
|
|
|
indirectworktree = ConfigKey "core.indirect-worktree"
|
|
|
|
setbare = do
|
|
|
|
-- core.worktree is not compatable with
|
|
|
|
-- core.bare; git does not allow both to be set, so
|
|
|
|
-- unset it when enabling direct mode, caching in
|
|
|
|
-- core.indirect-worktree
|
|
|
|
moveconfig indirectworktree coreworktree
|
2019-12-02 14:57:09 +00:00
|
|
|
setConfig Git.Config.coreBare val
|
2019-08-27 18:01:28 +00:00
|
|
|
moveconfig src dest = getConfigMaybe src >>= \case
|
|
|
|
Nothing -> noop
|
|
|
|
Just wt -> do
|
|
|
|
unsetConfig src
|
2019-12-05 18:36:43 +00:00
|
|
|
setConfig dest (fromConfigValue wt)
|
2019-08-27 18:01:28 +00:00
|
|
|
reloadConfig
|
|
|
|
|
|
|
|
{- Converts a directBranch back to the original branch.
|
|
|
|
-
|
|
|
|
- Any other ref is left unchanged.
|
|
|
|
-}
|
|
|
|
fromDirectBranch :: Ref -> Ref
|
|
|
|
fromDirectBranch directhead = case splitc '/' $ fromRef directhead of
|
|
|
|
("refs":"heads":"annex":"direct":rest) ->
|
2020-04-07 17:27:11 +00:00
|
|
|
Ref $ encodeBS' $ "refs/heads/" ++ intercalate "/" rest
|
2019-08-27 18:01:28 +00:00
|
|
|
_ -> directhead
|
|
|
|
|
|
|
|
switchHEADBack :: Annex ()
|
|
|
|
switchHEADBack = maybe noop switch =<< inRepo Git.Branch.currentUnsafe
|
|
|
|
where
|
|
|
|
switch currhead = do
|
|
|
|
let orighead = fromDirectBranch currhead
|
|
|
|
inRepo (Git.Ref.sha currhead) >>= \case
|
|
|
|
Just headsha
|
|
|
|
| orighead /= currhead -> do
|
|
|
|
inRepo $ Git.Branch.update "leaving direct mode" orighead headsha
|
|
|
|
inRepo $ Git.Branch.checkout orighead
|
|
|
|
inRepo $ Git.Branch.delete currhead
|
|
|
|
_ -> inRepo $ Git.Branch.checkout orighead
|
|
|
|
|
2013-01-18 16:20:08 +00:00
|
|
|
{- Absolute FilePaths of Files in the tree that are associated with a key. -}
|
2012-12-07 21:28:23 +00:00
|
|
|
associatedFiles :: Key -> Annex [FilePath]
|
|
|
|
associatedFiles key = do
|
2012-12-12 17:11:59 +00:00
|
|
|
files <- associatedFilesRelative key
|
2019-12-09 17:49:05 +00:00
|
|
|
top <- fromRawFilePath <$> fromRepo Git.repoPath
|
2012-12-12 17:11:59 +00:00
|
|
|
return $ map (top </>) files
|
2012-12-07 21:28:23 +00:00
|
|
|
|
2012-12-12 17:11:59 +00:00
|
|
|
{- List of files in the tree that are associated with a key, relative to
|
|
|
|
- the top of the repo. -}
|
|
|
|
associatedFilesRelative :: Key -> Annex [FilePath]
|
|
|
|
associatedFilesRelative key = do
|
2013-04-04 19:46:33 +00:00
|
|
|
mapping <- calcRepo $ gitAnnexMapping key
|
2016-12-24 18:46:31 +00:00
|
|
|
liftIO $ catchDefaultIO [] $ withFile mapping ReadMode $ \h ->
|
2019-08-27 18:01:28 +00:00
|
|
|
-- Read strictly to ensure the file is closed promptly
|
2014-02-03 14:20:18 +00:00
|
|
|
lines <$> hGetContentsStrict h
|
2012-12-10 19:02:44 +00:00
|
|
|
|
2013-11-15 18:52:03 +00:00
|
|
|
{- Removes the list of associated files. -}
|
|
|
|
removeAssociatedFiles :: Key -> Annex ()
|
|
|
|
removeAssociatedFiles key = do
|
|
|
|
mapping <- calcRepo $ gitAnnexMapping key
|
|
|
|
modifyContent mapping $
|
|
|
|
liftIO $ nukeFile mapping
|
|
|
|
|
2012-12-07 21:28:23 +00:00
|
|
|
{- Checks if a file in the tree, associated with a key, has not been modified.
|
|
|
|
-
|
|
|
|
- To avoid needing to fsck the file's content, which can involve an
|
|
|
|
- expensive checksum, this relies on a cache that contains the file's
|
|
|
|
- expected mtime and inode.
|
|
|
|
-}
|
2012-12-08 21:03:39 +00:00
|
|
|
goodContent :: Key -> FilePath -> Annex Bool
|
2019-12-11 18:12:22 +00:00
|
|
|
goodContent key file =
|
|
|
|
sameInodeCache (toRawFilePath file)
|
|
|
|
=<< recordedInodeCache key
|
2012-12-08 21:03:39 +00:00
|
|
|
|
2013-04-06 20:01:39 +00:00
|
|
|
{- Gets the recorded inode cache for a key.
|
|
|
|
-
|
|
|
|
- A key can be associated with multiple files, so may return more than
|
|
|
|
- one. -}
|
|
|
|
recordedInodeCache :: Key -> Annex [InodeCache]
|
2014-12-30 19:18:38 +00:00
|
|
|
recordedInodeCache key = withInodeCacheFile key $ \f ->
|
|
|
|
liftIO $ catchDefaultIO [] $
|
|
|
|
mapMaybe readInodeCache . lines <$> readFileStrict f
|
2012-12-08 17:13:36 +00:00
|
|
|
|
2013-02-15 20:37:57 +00:00
|
|
|
{- Removes an inode cache. -}
|
|
|
|
removeInodeCache :: Key -> Annex ()
|
2014-12-30 19:18:38 +00:00
|
|
|
removeInodeCache key = withInodeCacheFile key $ \f ->
|
|
|
|
modifyContent f $
|
|
|
|
liftIO $ nukeFile f
|
2013-02-15 20:37:57 +00:00
|
|
|
|
2013-02-14 20:17:40 +00:00
|
|
|
withInodeCacheFile :: Key -> (FilePath -> Annex a) -> Annex a
|
2013-04-04 19:46:33 +00:00
|
|
|
withInodeCacheFile key a = a =<< calcRepo (gitAnnexInodeCache key)
|