2012-12-12 23:20:38 +00:00
|
|
|
{- git-annex direct mode
|
2015-12-09 19:42:16 +00:00
|
|
|
-
|
|
|
|
- This is deprecated, and will be removed when direct mode gets removed
|
|
|
|
- from git-annex.
|
2012-12-12 23:20:38 +00:00
|
|
|
-
|
2015-01-21 16:50:09 +00:00
|
|
|
- Copyright 2012-2014 Joey Hess <id@joeyh.name>
|
2012-12-12 23:20:38 +00:00
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
|
|
|
module Annex.Direct where
|
|
|
|
|
2016-01-20 20:36:33 +00:00
|
|
|
import Annex.Common
|
2013-11-05 20:42:59 +00:00
|
|
|
import qualified Annex
|
2012-12-12 23:20:38 +00:00
|
|
|
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
|
2013-11-05 20:42:59 +00:00
|
|
|
import qualified Git.Config
|
|
|
|
import qualified Git.Ref
|
work around lack of receive.denyCurrentBranch in direct mode
Now that direct mode sets core.bare=true, git's normal prohibition about
pushing into the currently checked out branch doesn't work.
A simple fix for this would be an update hook which blocks the pushes..
but git hooks must be executable, and git-annex needs to be usable on eg,
FAT, which lacks x bits.
Instead, enabling direct mode switches the branch (eg master) to a special
purpose branch (eg annex/direct/master). This branch is not pushed when
syncing; instead any changes that git annex sync commits get written to
master, and it's pushed (along with synced/master) to the remote.
Note that initialization has been changed to always call setDirect,
even if it's just setDirect False for indirect mode. This is needed because
if the user has just cloned a direct mode repo, that nothing has synced
with before, it may have no master branch, and only a annex/direct/master.
Resulting in that branch being checked out locally too. Calling setDirect False
for indirect mode moves back out of this branch, to a new master branch,
and ensures that a manual "git push" doesn't push changes directly to
the annex/direct/master of the remote. (It's possible that the user
makes a commit w/o using git-annex and pushes it, but nothing I can do
about that really.)
This commit was sponsored by Jonathan Harrington.
2013-11-06 01:08:31 +00:00
|
|
|
import qualified Git.Branch
|
2012-12-18 19:04:44 +00:00
|
|
|
import Git.Sha
|
2013-10-17 19:11:21 +00:00
|
|
|
import Git.FilePath
|
2012-12-12 23:20:38 +00:00
|
|
|
import Git.Types
|
2013-11-05 20:42:59 +00:00
|
|
|
import Config
|
2013-09-19 18:48:42 +00:00
|
|
|
import Annex.CatFile
|
2012-12-18 19:04:44 +00:00
|
|
|
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
|
2014-03-03 18:57:16 +00:00
|
|
|
import Annex.VariantFile
|
2014-06-09 22:01:30 +00:00
|
|
|
import Git.Index
|
2016-04-06 19:33:29 +00:00
|
|
|
import Annex.GitOverlay
|
2014-07-10 04:32:23 +00:00
|
|
|
import Annex.LockFile
|
2015-12-09 19:42:16 +00:00
|
|
|
import Annex.InodeSentinal
|
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
|
2013-07-28 19:27:36 +00:00
|
|
|
(l, cleanup) <- inRepo $ Git.LsFiles.stagedOthersDetails [top]
|
2012-12-12 23:20:38 +00:00
|
|
|
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. -}
|
2015-12-07 19:22:01 +00:00
|
|
|
go (file, Just sha, Just _mode) = withTSDelta $ \delta -> do
|
|
|
|
shakey <- catKey sha
|
2012-12-12 23:20:38 +00:00
|
|
|
mstat <- liftIO $ catchMaybeIO $ getSymbolicLinkStatus file
|
2015-01-20 23:35:50 +00:00
|
|
|
mcache <- liftIO $ maybe (pure Nothing) (toInodeCache delta file) mstat
|
2018-12-11 17:46:22 +00:00
|
|
|
filekey <- isAnnexLink file >>= \case
|
|
|
|
Just k -> return (Just k)
|
|
|
|
-- v7 unlocked pointer file
|
|
|
|
Nothing -> liftIO (isPointerFile file)
|
finish fixing windows timezone madness
Rather than calculating the TSDelta once, and caching it, this now
reads the inode sential file's InodeCache file once, and then each time a
new InodeCache is generated, looks at the sentinal file to get the current
delta.
This way, if the time zone changes while git-annex is running, it will
adapt.
This adds some inneffiency, but only on Windows, and only 1 stat per new
file added. The worst innefficiency is that `git annex status` and
`git annex sync` will now (on Windows) stat the inode sentinal file once per
file in the repo.
It would be more efficient to use getCurrentTimeZone, rather than needing
to stat the sentinal file. This should be easy to do, once the time
package gets my bugfix patch.
This commit was sponsored by Jürgen Lüters.
2014-06-12 17:43:16 +00:00
|
|
|
case (shakey, filekey, mstat, mcache) of
|
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, _, _)
|
|
|
|
| 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
|
2015-01-27 21:38:06 +00:00
|
|
|
l <- calcRepo $ gitAnnexLink file key
|
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
|
|
|
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]
|
|
|
|
|
2013-12-01 17:59:39 +00:00
|
|
|
deletegit file = Annex.Queue.addCommand "rm" [Param "-qf"] [file]
|
|
|
|
|
|
|
|
{- Run before a commit to update direct mode bookeeping to reflect the
|
|
|
|
- staged changes being committed. -}
|
|
|
|
preCommitDirect :: Annex Bool
|
|
|
|
preCommitDirect = do
|
|
|
|
(diffs, clean) <- inRepo $ DiffTree.diffIndex Git.Ref.headRef
|
|
|
|
makeabs <- flip fromTopFilePath <$> gitRepo
|
|
|
|
forM_ diffs (go makeabs)
|
|
|
|
liftIO clean
|
|
|
|
where
|
|
|
|
go makeabs diff = do
|
|
|
|
withkey (DiffTree.srcsha diff) (DiffTree.srcmode diff) removeAssociatedFile
|
|
|
|
withkey (DiffTree.dstsha diff) (DiffTree.dstmode diff) addAssociatedFile
|
|
|
|
where
|
2017-11-15 20:55:38 +00:00
|
|
|
withkey sha _mode a = when (sha /= nullSha) $
|
|
|
|
catKey sha >>= \case
|
2013-12-01 17:59:39 +00:00
|
|
|
Nothing -> noop
|
|
|
|
Just key -> void $ a key $
|
|
|
|
makeabs $ DiffTree.file diff
|
2012-12-12 23:20:38 +00:00
|
|
|
|
|
|
|
{- 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
|
2015-01-27 21:38:06 +00:00
|
|
|
l <- calcRepo $ gitAnnexLink file key
|
2013-04-04 19:46:33 +00:00
|
|
|
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
|
2014-06-09 22:01:30 +00:00
|
|
|
- sees present direct mode files as type changed files.
|
|
|
|
-
|
|
|
|
- So, to handle a merge, it's run with the work tree set to a temp
|
|
|
|
- directory, and the merge is staged into a copy of the index.
|
|
|
|
- Then the work tree is updated to reflect the merge, and
|
|
|
|
- finally, the merge is committed and the real index updated.
|
2014-07-09 19:07:53 +00:00
|
|
|
-
|
|
|
|
- A lock file is used to avoid races with any other caller of mergeDirect.
|
|
|
|
-
|
2015-09-22 16:59:56 +00:00
|
|
|
- To avoid other git processes from making changes to the index while our
|
2014-07-09 19:07:53 +00:00
|
|
|
- merge is in progress, the index lock file is used as the temp index
|
|
|
|
- file. This is the same as what git does when updating the index
|
|
|
|
- normally.
|
2012-12-18 19:04:44 +00:00
|
|
|
-}
|
2016-04-22 18:26:44 +00:00
|
|
|
mergeDirect :: Maybe Git.Ref -> Maybe Git.Ref -> Git.Branch -> Annex Bool -> [Git.Merge.MergeConfig] -> Git.Branch.CommitMode -> Annex Bool
|
|
|
|
mergeDirect startbranch oldref branch resolvemerge mergeconfig commitmode = exclusively $ do
|
2015-01-06 21:18:12 +00:00
|
|
|
reali <- liftIO . absPath =<< fromRepo indexFile
|
2018-08-17 20:03:40 +00:00
|
|
|
tmpi <- liftIO . absPath =<< fromRepo (indexFileLock . indexFile)
|
2015-09-22 16:59:56 +00:00
|
|
|
liftIO $ whenM (doesFileExist reali) $
|
|
|
|
copyFile reali tmpi
|
2014-06-09 22:01:30 +00:00
|
|
|
|
|
|
|
d <- fromRepo gitAnnexMergeDir
|
|
|
|
liftIO $ do
|
|
|
|
whenM (doesDirectoryExist d) $
|
|
|
|
removeDirectoryRecursive d
|
|
|
|
createDirectoryIfMissing True d
|
|
|
|
|
|
|
|
withIndexFile tmpi $ do
|
2016-04-22 18:26:44 +00:00
|
|
|
merged <- stageMerge d branch mergeconfig commitmode
|
2015-10-15 18:22:46 +00:00
|
|
|
ok <- if merged
|
2014-06-10 00:10:12 +00:00
|
|
|
then return True
|
|
|
|
else resolvemerge
|
2015-10-15 18:22:46 +00:00
|
|
|
if ok
|
|
|
|
then do
|
|
|
|
mergeDirectCleanup d (fromMaybe Git.Sha.emptyTree oldref)
|
|
|
|
mergeDirectCommit merged startbranch branch commitmode
|
|
|
|
liftIO $ whenM (doesFileExist tmpi) $
|
|
|
|
rename tmpi reali
|
2015-10-15 18:27:14 +00:00
|
|
|
else do
|
|
|
|
liftIO $ nukeFile tmpi
|
|
|
|
liftIO $ removeDirectoryRecursive d
|
2015-10-15 18:22:46 +00:00
|
|
|
return ok
|
2014-07-09 19:07:53 +00:00
|
|
|
where
|
2014-07-10 04:32:23 +00:00
|
|
|
exclusively = withExclusiveLock gitAnnexMergeLock
|
2014-07-09 19:07:53 +00:00
|
|
|
|
2014-06-13 02:00:02 +00:00
|
|
|
{- Stage a merge into the index, avoiding changing HEAD or the current
|
|
|
|
- branch. -}
|
2016-04-22 18:26:44 +00:00
|
|
|
stageMerge :: FilePath -> Git.Branch -> [Git.Merge.MergeConfig] -> Git.Branch.CommitMode -> Annex Bool
|
|
|
|
stageMerge d branch mergeconfig commitmode = do
|
2014-06-13 02:00:02 +00:00
|
|
|
-- XXX A bug in git makes stageMerge unsafe to use if the git repo
|
|
|
|
-- is configured with core.symlinks=false
|
2016-04-22 18:26:44 +00:00
|
|
|
-- Using merge is not ideal though, since it will
|
2014-06-13 02:00:02 +00:00
|
|
|
-- update the current branch immediately, before the work tree
|
|
|
|
-- has been updated, which would leave things in an inconsistent
|
|
|
|
-- state if mergeDirectCleanup is interrupted.
|
|
|
|
-- <http://marc.info/?l=git&m=140262402204212&w=2>
|
|
|
|
merger <- ifM (coreSymlinks <$> Annex.getGitConfig)
|
2016-04-22 18:26:44 +00:00
|
|
|
( return $ \ref -> Git.Merge.stageMerge ref mergeconfig
|
|
|
|
, return $ \ref -> Git.Merge.merge ref mergeconfig commitmode
|
2015-01-06 21:18:12 +00:00
|
|
|
)
|
|
|
|
inRepo $ \g -> do
|
|
|
|
wd <- liftIO $ absPath d
|
|
|
|
gd <- liftIO $ absPath $ Git.localGitDir g
|
|
|
|
merger branch $
|
|
|
|
g { location = Local { gitdir = gd, worktree = Just (addTrailingPathSeparator wd) } }
|
2014-06-09 22:01:30 +00:00
|
|
|
|
|
|
|
{- Commits after a direct mode merge is complete, and after the work
|
|
|
|
- tree has been updated by mergeDirectCleanup.
|
|
|
|
-}
|
2014-07-04 15:36:59 +00:00
|
|
|
mergeDirectCommit :: Bool -> Maybe Git.Ref -> Git.Branch -> Git.Branch.CommitMode -> Annex ()
|
|
|
|
mergeDirectCommit allowff old branch commitmode = do
|
2014-06-09 22:01:30 +00:00
|
|
|
void preCommitDirect
|
2014-06-10 00:10:12 +00:00
|
|
|
d <- fromRepo Git.localGitDir
|
|
|
|
let merge_head = d </> "MERGE_HEAD"
|
|
|
|
let merge_msg = d </> "MERGE_MSG"
|
|
|
|
let merge_mode = d </> "MERGE_MODE"
|
|
|
|
ifM (pure allowff <&&> canff)
|
2016-03-31 16:27:48 +00:00
|
|
|
( inRepo $ Git.Branch.update "merge" Git.Ref.headRef branch -- fast forward
|
2014-06-09 22:01:30 +00:00
|
|
|
, do
|
|
|
|
msg <- liftIO $
|
|
|
|
catchDefaultIO ("merge " ++ fromRef branch) $
|
|
|
|
readFile merge_msg
|
2014-07-04 15:36:59 +00:00
|
|
|
void $ inRepo $ Git.Branch.commit commitmode False msg
|
2014-06-09 22:01:30 +00:00
|
|
|
Git.Ref.headRef [Git.Ref.headRef, branch]
|
|
|
|
)
|
|
|
|
liftIO $ mapM_ nukeFile [merge_head, merge_msg, merge_mode]
|
2014-06-10 00:10:12 +00:00
|
|
|
where
|
|
|
|
canff = maybe (return False) (\o -> inRepo $ Git.Branch.fastForwardable o branch) old
|
2014-06-09 22:01:30 +00:00
|
|
|
|
2014-11-12 19:41:15 +00:00
|
|
|
mergeDirectCleanup :: FilePath -> Git.Ref -> Annex ()
|
2015-10-15 18:27:14 +00:00
|
|
|
mergeDirectCleanup d oldref = updateWorkTree d oldref False
|
2014-11-12 19:41:15 +00:00
|
|
|
|
|
|
|
{- Updates the direct mode work tree to reflect the changes staged in the
|
|
|
|
- index by a git command, that was run in a temporary work tree.
|
|
|
|
-
|
|
|
|
- Uses diff-index to compare the staged changes with provided ref
|
|
|
|
- which should be the tree before the merge, and applies those
|
|
|
|
- changes to the work tree.
|
2013-11-15 17:40:12 +00:00
|
|
|
-
|
|
|
|
- There are really only two types of changes: An old item can be deleted,
|
|
|
|
- or a new item added. Two passes are made, first deleting and then
|
|
|
|
- adding. This is to handle cases where eg, a file is deleted and a
|
2013-12-12 19:16:44 +00:00
|
|
|
- directory is added. (The diff-tree output may list these in the opposite
|
|
|
|
- order, but we cannot add the directory until the file with the
|
|
|
|
- same name is removed.)
|
2012-12-18 19:04:44 +00:00
|
|
|
-}
|
2015-08-04 18:01:59 +00:00
|
|
|
updateWorkTree :: FilePath -> Git.Ref -> Bool -> Annex ()
|
|
|
|
updateWorkTree d oldref force = do
|
2014-06-09 22:01:30 +00:00
|
|
|
(items, cleanup) <- inRepo $ DiffTree.diffIndex oldref
|
2013-10-17 19:11:21 +00:00
|
|
|
makeabs <- flip fromTopFilePath <$> gitRepo
|
2013-11-15 17:40:12 +00:00
|
|
|
let fsitems = zip (map (makeabs . DiffTree.file) items) items
|
|
|
|
forM_ fsitems $
|
2015-12-07 19:22:01 +00:00
|
|
|
go makeabs DiffTree.srcsha moveout moveout_raw
|
2013-11-15 17:40:12 +00:00
|
|
|
forM_ fsitems $
|
2015-12-07 19:22:01 +00:00
|
|
|
go makeabs DiffTree.dstsha movein movein_raw
|
2013-04-03 07:52:41 +00:00
|
|
|
void $ liftIO cleanup
|
2012-12-18 19:04:44 +00:00
|
|
|
where
|
2015-12-07 19:22:01 +00:00
|
|
|
go makeabs getsha a araw (f, item)
|
2013-11-15 17:40:12 +00:00
|
|
|
| getsha item == nullSha = noop
|
|
|
|
| otherwise = void $
|
unify exception handling into Utility.Exception
Removed old extensible-exceptions, only needed for very old ghc.
Made webdav use Utility.Exception, to work after some changes in DAV's
exception handling.
Removed Annex.Exception. Mostly this was trivial, but note that
tryAnnex is replaced with tryNonAsync and catchAnnex replaced with
catchNonAsync. In theory that could be a behavior change, since the former
caught all exceptions, and the latter don't catch async exceptions.
However, in practice, nothing in the Annex monad uses async exceptions.
Grepping for throwTo and killThread only find stuff in the assistant,
which does not seem related.
Command.Add.undo is changed to accept a SomeException, and things
that use it for rollback now catch non-async exceptions, rather than
only IOExceptions.
2014-08-08 01:55:44 +00:00
|
|
|
tryNonAsync . maybe (araw item makeabs f) (\k -> void $ a item makeabs k f)
|
2015-12-07 19:22:01 +00:00
|
|
|
=<< catKey (getsha item)
|
2012-12-18 19:04:44 +00:00
|
|
|
|
2014-03-04 05:58:09 +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. -}
|
2014-03-04 05:58:09 +00:00
|
|
|
moveout_raw _ _ f = liftIO $ do
|
2012-12-18 19:04:44 +00:00
|
|
|
nukeFile f
|
2015-01-09 17:11:56 +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
|
2014-03-03 18:57:16 +00:00
|
|
|
- key, it's left alone.
|
|
|
|
-
|
|
|
|
- If the file is already present, and does not exist in the
|
2014-06-09 22:01:30 +00:00
|
|
|
- oldref, preserve this local file.
|
2014-03-03 18:57:16 +00:00
|
|
|
-
|
|
|
|
- Otherwise, create the symlink and then if possible, replace it
|
|
|
|
- with the content. -}
|
2014-03-04 05:58:09 +00:00
|
|
|
movein item makeabs k f = unlessM (goodContent k f) $ do
|
2015-08-04 18:01:59 +00:00
|
|
|
unless force $ preserveUnannexed item makeabs f oldref
|
2015-01-27 21:38:06 +00:00
|
|
|
l <- calcRepo $ 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. -}
|
2014-03-04 05:58:09 +00:00
|
|
|
movein_raw item makeabs f = do
|
2015-08-04 18:01:59 +00:00
|
|
|
unless force $ preserveUnannexed item makeabs f oldref
|
2014-03-03 18:57:16 +00:00
|
|
|
liftIO $ do
|
2015-01-09 17:11:56 +00:00
|
|
|
createDirectoryIfMissing True $ parentDir f
|
2014-03-03 18:57:16 +00:00
|
|
|
void $ tryIO $ rename (d </> getTopFilePath (DiffTree.file item)) f
|
|
|
|
|
2014-03-04 05:58:09 +00:00
|
|
|
{- If the file that's being moved in is already present in the work
|
2014-06-09 22:01:30 +00:00
|
|
|
- tree, but did not exist in the oldref, preserve this
|
2014-03-04 05:58:09 +00:00
|
|
|
- local, unannexed file (or directory), as "variant-local".
|
|
|
|
-
|
|
|
|
- It's also possible that the file that's being moved in
|
|
|
|
- is in a directory that collides with an exsting, non-annexed
|
|
|
|
- file (not a directory), which should be preserved.
|
|
|
|
-}
|
|
|
|
preserveUnannexed :: DiffTree.DiffTreeItem -> (TopFilePath -> FilePath) -> FilePath -> Ref -> Annex ()
|
2014-06-09 22:01:30 +00:00
|
|
|
preserveUnannexed item makeabs absf oldref = do
|
2014-03-04 05:58:09 +00:00
|
|
|
whenM (liftIO (collidingitem absf) <&&> unannexed absf) $
|
|
|
|
liftIO $ findnewname absf 0
|
|
|
|
checkdirs (DiffTree.file item)
|
|
|
|
where
|
2015-01-09 18:26:52 +00:00
|
|
|
checkdirs from = case upFrom (getTopFilePath from) of
|
|
|
|
Nothing -> noop
|
|
|
|
Just p -> do
|
|
|
|
let d = asTopFilePath p
|
2015-01-09 17:11:56 +00:00
|
|
|
let absd = makeabs d
|
|
|
|
whenM (liftIO (colliding_nondir absd) <&&> unannexed absd) $
|
|
|
|
liftIO $ findnewname absd 0
|
|
|
|
checkdirs d
|
2014-03-04 05:58:09 +00:00
|
|
|
|
|
|
|
collidingitem f = isJust
|
|
|
|
<$> catchMaybeIO (getSymbolicLinkStatus f)
|
|
|
|
colliding_nondir f = maybe False (not . isDirectory)
|
|
|
|
<$> catchMaybeIO (getSymbolicLinkStatus f)
|
2014-03-03 21:09:53 +00:00
|
|
|
|
2014-03-04 05:58:09 +00:00
|
|
|
unannexed f = (isNothing <$> isAnnexLink f)
|
2014-06-09 22:01:30 +00:00
|
|
|
<&&> (isNothing <$> catFileDetails oldref f)
|
2014-03-03 21:09:53 +00:00
|
|
|
|
2014-03-04 05:58:09 +00:00
|
|
|
findnewname :: FilePath -> Int -> IO ()
|
|
|
|
findnewname f n = do
|
|
|
|
let localf = mkVariant f
|
|
|
|
("local" ++ if n > 0 then show n else "")
|
|
|
|
ifM (collidingitem localf)
|
|
|
|
( findnewname f (n+1)
|
|
|
|
, rename f localf
|
|
|
|
`catchIO` const (findnewname f (n+1))
|
|
|
|
)
|
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
|
2014-10-09 18:53:13 +00:00
|
|
|
fromindirect loc = do
|
2013-05-06 16:43:03 +00:00
|
|
|
{- Move content from annex to direct file. -}
|
|
|
|
updateInodeCache k loc
|
2013-05-17 19:59:37 +00:00
|
|
|
void $ addAssociatedFile k f
|
2013-11-15 18:52:03 +00:00
|
|
|
modifyContent loc $ do
|
|
|
|
thawContent loc
|
2014-08-15 17:38:05 +00:00
|
|
|
liftIO (replaceFileFrom loc f)
|
|
|
|
`catchIO` (\_ -> freezeContent loc)
|
2013-07-08 21:29:42 +00:00
|
|
|
fromdirect loc = do
|
|
|
|
replaceFile f $
|
2014-08-27 00:06:43 +00:00
|
|
|
liftIO . void . copyFileExternal CopyAllMetaData loc
|
2013-07-08 21:29:42 +00:00
|
|
|
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) $
|
annex.securehashesonly
Cryptographically secure hashes can be forced to be used in a repository,
by setting annex.securehashesonly. This does not prevent the git repository
from containing files with insecure hashes, but it does prevent the content
of such files from being pulled into .git/annex/objects from another
repository.
We want to make sure that at no point does git-annex accept content into
.git/annex/objects that is hashed with an insecure key. Here's how it
was done:
* .git/annex/objects/xx/yy/KEY/ is kept frozen, so nothing can be
written to it normally
* So every place that writes content must call, thawContent or modifyContent.
We can audit for these, and be sure we've considered all cases.
* The main functions are moveAnnex, and linkToAnnex; these were made to
check annex.securehashesonly, and are the main security boundary
for annex.securehashesonly.
* Most other calls to modifyContent deal with other files in the KEY
directory (inode cache etc). The other ones that mess with the content
are:
- Annex.Direct.toDirectGen, in which content already in the
annex directory is moved to the direct mode file, so not relevant.
- fix and lock, which don't add new content
- Command.ReKey.linkKey, which manually unlocks it to make a
copy.
* All other calls to thawContent appear safe.
Made moveAnnex return a Bool, so checked all callsites and made them
deal with a failure in appropriate ways.
linkToAnnex simply returns LinkAnnexFailed; all callsites already deal
with it failing in appropriate ways.
This commit was sponsored by Riku Voipio.
2017-02-27 17:01:32 +00:00
|
|
|
-- If moveAnnex rejects the content of the key,
|
|
|
|
-- treat that the same as its content having changed.
|
2017-02-28 17:24:26 +00:00
|
|
|
ifM (goodContent k f)
|
|
|
|
( unlessM (moveAnnex k f) $
|
|
|
|
logStatus k InfoMissing
|
|
|
|
, logStatus k InfoMissing
|
|
|
|
)
|
2012-12-18 21:15:16 +00:00
|
|
|
liftIO $ do
|
|
|
|
nukeFile f
|
2015-01-09 17:11:56 +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
|
2013-11-05 20:42:59 +00:00
|
|
|
|
2015-12-15 19:34:28 +00:00
|
|
|
{- Git config settings to enable/disable direct mode. -}
|
2013-11-05 20:42:59 +00:00
|
|
|
setDirect :: Bool -> Annex ()
|
|
|
|
setDirect wantdirect = do
|
work around lack of receive.denyCurrentBranch in direct mode
Now that direct mode sets core.bare=true, git's normal prohibition about
pushing into the currently checked out branch doesn't work.
A simple fix for this would be an update hook which blocks the pushes..
but git hooks must be executable, and git-annex needs to be usable on eg,
FAT, which lacks x bits.
Instead, enabling direct mode switches the branch (eg master) to a special
purpose branch (eg annex/direct/master). This branch is not pushed when
syncing; instead any changes that git annex sync commits get written to
master, and it's pushed (along with synced/master) to the remote.
Note that initialization has been changed to always call setDirect,
even if it's just setDirect False for indirect mode. This is needed because
if the user has just cloned a direct mode repo, that nothing has synced
with before, it may have no master branch, and only a annex/direct/master.
Resulting in that branch being checked out locally too. Calling setDirect False
for indirect mode moves back out of this branch, to a new master branch,
and ensures that a manual "git push" doesn't push changes directly to
the annex/direct/master of the remote. (It's possible that the user
makes a commit w/o using git-annex and pushes it, but nothing I can do
about that really.)
This commit was sponsored by Jonathan Harrington.
2013-11-06 01:08:31 +00:00
|
|
|
if wantdirect
|
|
|
|
then do
|
|
|
|
switchHEAD
|
|
|
|
setbare
|
|
|
|
else do
|
|
|
|
setbare
|
|
|
|
switchHEADBack
|
2013-11-05 20:42:59 +00:00
|
|
|
setConfig (annexConfig "direct") val
|
|
|
|
Annex.changeGitConfig $ \c -> c { annexDirect = wantdirect }
|
|
|
|
where
|
|
|
|
val = Git.Config.boolConfig wantdirect
|
2015-03-02 20:43:44 +00:00
|
|
|
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
|
|
|
|
if wantdirect
|
|
|
|
then moveconfig coreworktree indirectworktree
|
|
|
|
else moveconfig indirectworktree coreworktree
|
|
|
|
setConfig (ConfigKey Git.Config.coreBare) val
|
2017-11-15 20:55:38 +00:00
|
|
|
moveconfig src dest = getConfigMaybe src >>= \case
|
|
|
|
Nothing -> noop
|
|
|
|
Just wt -> do
|
|
|
|
unsetConfig src
|
|
|
|
setConfig dest wt
|
|
|
|
reloadConfig
|
work around lack of receive.denyCurrentBranch in direct mode
Now that direct mode sets core.bare=true, git's normal prohibition about
pushing into the currently checked out branch doesn't work.
A simple fix for this would be an update hook which blocks the pushes..
but git hooks must be executable, and git-annex needs to be usable on eg,
FAT, which lacks x bits.
Instead, enabling direct mode switches the branch (eg master) to a special
purpose branch (eg annex/direct/master). This branch is not pushed when
syncing; instead any changes that git annex sync commits get written to
master, and it's pushed (along with synced/master) to the remote.
Note that initialization has been changed to always call setDirect,
even if it's just setDirect False for indirect mode. This is needed because
if the user has just cloned a direct mode repo, that nothing has synced
with before, it may have no master branch, and only a annex/direct/master.
Resulting in that branch being checked out locally too. Calling setDirect False
for indirect mode moves back out of this branch, to a new master branch,
and ensures that a manual "git push" doesn't push changes directly to
the annex/direct/master of the remote. (It's possible that the user
makes a commit w/o using git-annex and pushes it, but nothing I can do
about that really.)
This commit was sponsored by Jonathan Harrington.
2013-11-06 01:08:31 +00:00
|
|
|
|
|
|
|
{- Since direct mode sets core.bare=true, incoming pushes could change
|
|
|
|
- the currently checked out branch. To avoid this problem, HEAD
|
|
|
|
- is changed to a internal ref that nothing is going to push to.
|
|
|
|
-
|
|
|
|
- For refs/heads/master, use refs/heads/annex/direct/master;
|
|
|
|
- this way things that show HEAD (eg shell prompts) will
|
|
|
|
- hopefully show just "master". -}
|
|
|
|
directBranch :: Ref -> Ref
|
2017-01-31 22:40:42 +00:00
|
|
|
directBranch orighead = case splitc '/' $ fromRef orighead of
|
work around lack of receive.denyCurrentBranch in direct mode
Now that direct mode sets core.bare=true, git's normal prohibition about
pushing into the currently checked out branch doesn't work.
A simple fix for this would be an update hook which blocks the pushes..
but git hooks must be executable, and git-annex needs to be usable on eg,
FAT, which lacks x bits.
Instead, enabling direct mode switches the branch (eg master) to a special
purpose branch (eg annex/direct/master). This branch is not pushed when
syncing; instead any changes that git annex sync commits get written to
master, and it's pushed (along with synced/master) to the remote.
Note that initialization has been changed to always call setDirect,
even if it's just setDirect False for indirect mode. This is needed because
if the user has just cloned a direct mode repo, that nothing has synced
with before, it may have no master branch, and only a annex/direct/master.
Resulting in that branch being checked out locally too. Calling setDirect False
for indirect mode moves back out of this branch, to a new master branch,
and ensures that a manual "git push" doesn't push changes directly to
the annex/direct/master of the remote. (It's possible that the user
makes a commit w/o using git-annex and pushes it, but nothing I can do
about that really.)
This commit was sponsored by Jonathan Harrington.
2013-11-06 01:08:31 +00:00
|
|
|
("refs":"heads":"annex":"direct":_) -> orighead
|
|
|
|
("refs":"heads":rest) ->
|
|
|
|
Ref $ "refs/heads/annex/direct/" ++ intercalate "/" rest
|
2014-02-19 05:09:17 +00:00
|
|
|
_ -> Ref $ "refs/heads/" ++ fromRef (Git.Ref.base orighead)
|
work around lack of receive.denyCurrentBranch in direct mode
Now that direct mode sets core.bare=true, git's normal prohibition about
pushing into the currently checked out branch doesn't work.
A simple fix for this would be an update hook which blocks the pushes..
but git hooks must be executable, and git-annex needs to be usable on eg,
FAT, which lacks x bits.
Instead, enabling direct mode switches the branch (eg master) to a special
purpose branch (eg annex/direct/master). This branch is not pushed when
syncing; instead any changes that git annex sync commits get written to
master, and it's pushed (along with synced/master) to the remote.
Note that initialization has been changed to always call setDirect,
even if it's just setDirect False for indirect mode. This is needed because
if the user has just cloned a direct mode repo, that nothing has synced
with before, it may have no master branch, and only a annex/direct/master.
Resulting in that branch being checked out locally too. Calling setDirect False
for indirect mode moves back out of this branch, to a new master branch,
and ensures that a manual "git push" doesn't push changes directly to
the annex/direct/master of the remote. (It's possible that the user
makes a commit w/o using git-annex and pushes it, but nothing I can do
about that really.)
This commit was sponsored by Jonathan Harrington.
2013-11-06 01:08:31 +00:00
|
|
|
|
|
|
|
{- Converts a directBranch back to the original branch.
|
|
|
|
-
|
|
|
|
- Any other ref is left unchanged.
|
|
|
|
-}
|
|
|
|
fromDirectBranch :: Ref -> Ref
|
2017-01-31 22:40:42 +00:00
|
|
|
fromDirectBranch directhead = case splitc '/' $ fromRef directhead of
|
work around lack of receive.denyCurrentBranch in direct mode
Now that direct mode sets core.bare=true, git's normal prohibition about
pushing into the currently checked out branch doesn't work.
A simple fix for this would be an update hook which blocks the pushes..
but git hooks must be executable, and git-annex needs to be usable on eg,
FAT, which lacks x bits.
Instead, enabling direct mode switches the branch (eg master) to a special
purpose branch (eg annex/direct/master). This branch is not pushed when
syncing; instead any changes that git annex sync commits get written to
master, and it's pushed (along with synced/master) to the remote.
Note that initialization has been changed to always call setDirect,
even if it's just setDirect False for indirect mode. This is needed because
if the user has just cloned a direct mode repo, that nothing has synced
with before, it may have no master branch, and only a annex/direct/master.
Resulting in that branch being checked out locally too. Calling setDirect False
for indirect mode moves back out of this branch, to a new master branch,
and ensures that a manual "git push" doesn't push changes directly to
the annex/direct/master of the remote. (It's possible that the user
makes a commit w/o using git-annex and pushes it, but nothing I can do
about that really.)
This commit was sponsored by Jonathan Harrington.
2013-11-06 01:08:31 +00:00
|
|
|
("refs":"heads":"annex":"direct":rest) ->
|
|
|
|
Ref $ "refs/heads/" ++ intercalate "/" rest
|
|
|
|
_ -> directhead
|
|
|
|
|
|
|
|
switchHEAD :: Annex ()
|
|
|
|
switchHEAD = maybe noop switch =<< inRepo Git.Branch.currentUnsafe
|
|
|
|
where
|
|
|
|
switch orighead = do
|
|
|
|
let newhead = directBranch orighead
|
2016-03-31 16:27:48 +00:00
|
|
|
maybe noop (inRepo . Git.Branch.update "entering direct mode" newhead)
|
work around lack of receive.denyCurrentBranch in direct mode
Now that direct mode sets core.bare=true, git's normal prohibition about
pushing into the currently checked out branch doesn't work.
A simple fix for this would be an update hook which blocks the pushes..
but git hooks must be executable, and git-annex needs to be usable on eg,
FAT, which lacks x bits.
Instead, enabling direct mode switches the branch (eg master) to a special
purpose branch (eg annex/direct/master). This branch is not pushed when
syncing; instead any changes that git annex sync commits get written to
master, and it's pushed (along with synced/master) to the remote.
Note that initialization has been changed to always call setDirect,
even if it's just setDirect False for indirect mode. This is needed because
if the user has just cloned a direct mode repo, that nothing has synced
with before, it may have no master branch, and only a annex/direct/master.
Resulting in that branch being checked out locally too. Calling setDirect False
for indirect mode moves back out of this branch, to a new master branch,
and ensures that a manual "git push" doesn't push changes directly to
the annex/direct/master of the remote. (It's possible that the user
makes a commit w/o using git-annex and pushes it, but nothing I can do
about that really.)
This commit was sponsored by Jonathan Harrington.
2013-11-06 01:08:31 +00:00
|
|
|
=<< inRepo (Git.Ref.sha orighead)
|
|
|
|
inRepo $ Git.Branch.checkout newhead
|
|
|
|
|
|
|
|
switchHEADBack :: Annex ()
|
|
|
|
switchHEADBack = maybe noop switch =<< inRepo Git.Branch.currentUnsafe
|
|
|
|
where
|
|
|
|
switch currhead = do
|
|
|
|
let orighead = fromDirectBranch currhead
|
2017-11-15 20:55:38 +00:00
|
|
|
inRepo (Git.Ref.sha currhead) >>= \case
|
work around lack of receive.denyCurrentBranch in direct mode
Now that direct mode sets core.bare=true, git's normal prohibition about
pushing into the currently checked out branch doesn't work.
A simple fix for this would be an update hook which blocks the pushes..
but git hooks must be executable, and git-annex needs to be usable on eg,
FAT, which lacks x bits.
Instead, enabling direct mode switches the branch (eg master) to a special
purpose branch (eg annex/direct/master). This branch is not pushed when
syncing; instead any changes that git annex sync commits get written to
master, and it's pushed (along with synced/master) to the remote.
Note that initialization has been changed to always call setDirect,
even if it's just setDirect False for indirect mode. This is needed because
if the user has just cloned a direct mode repo, that nothing has synced
with before, it may have no master branch, and only a annex/direct/master.
Resulting in that branch being checked out locally too. Calling setDirect False
for indirect mode moves back out of this branch, to a new master branch,
and ensures that a manual "git push" doesn't push changes directly to
the annex/direct/master of the remote. (It's possible that the user
makes a commit w/o using git-annex and pushes it, but nothing I can do
about that really.)
This commit was sponsored by Jonathan Harrington.
2013-11-06 01:08:31 +00:00
|
|
|
Just headsha
|
|
|
|
| orighead /= currhead -> do
|
2016-03-31 16:27:48 +00:00
|
|
|
inRepo $ Git.Branch.update "leaving direct mode" orighead headsha
|
work around lack of receive.denyCurrentBranch in direct mode
Now that direct mode sets core.bare=true, git's normal prohibition about
pushing into the currently checked out branch doesn't work.
A simple fix for this would be an update hook which blocks the pushes..
but git hooks must be executable, and git-annex needs to be usable on eg,
FAT, which lacks x bits.
Instead, enabling direct mode switches the branch (eg master) to a special
purpose branch (eg annex/direct/master). This branch is not pushed when
syncing; instead any changes that git annex sync commits get written to
master, and it's pushed (along with synced/master) to the remote.
Note that initialization has been changed to always call setDirect,
even if it's just setDirect False for indirect mode. This is needed because
if the user has just cloned a direct mode repo, that nothing has synced
with before, it may have no master branch, and only a annex/direct/master.
Resulting in that branch being checked out locally too. Calling setDirect False
for indirect mode moves back out of this branch, to a new master branch,
and ensures that a manual "git push" doesn't push changes directly to
the annex/direct/master of the remote. (It's possible that the user
makes a commit w/o using git-annex and pushes it, but nothing I can do
about that really.)
This commit was sponsored by Jonathan Harrington.
2013-11-06 01:08:31 +00:00
|
|
|
inRepo $ Git.Branch.checkout orighead
|
|
|
|
inRepo $ Git.Branch.delete currhead
|
|
|
|
_ -> inRepo $ Git.Branch.checkout orighead
|