handle case of adding populated drive to just created repo
The just created repo has no master branch commits yet. This is now handled, merging in the master branch from the populated drive.
This commit is contained in:
parent
a3f76fe696
commit
5ae1f75a39
5 changed files with 43 additions and 24 deletions
|
@ -89,7 +89,7 @@ mergeBranch = Git.Merge.mergeNonInteractive . Command.Sync.syncBranch
|
||||||
- when a push fails, which can happen due to a remote not having pushed
|
- when a push fails, which can happen due to a remote not having pushed
|
||||||
- changes to us. That could be because it doesn't have us as a remote, or
|
- changes to us. That could be because it doesn't have us as a remote, or
|
||||||
- because the assistant is not running there, or other reasons. -}
|
- because the assistant is not running there, or other reasons. -}
|
||||||
manualPull :: Git.Ref -> [Remote] -> Annex ()
|
manualPull :: (Maybe Git.Ref) -> [Remote] -> Annex ()
|
||||||
manualPull currentbranch remotes = do
|
manualPull currentbranch remotes = do
|
||||||
forM_ remotes $ \r ->
|
forM_ remotes $ \r ->
|
||||||
inRepo $ Git.Command.runBool "fetch" [Param $ Remote.name r]
|
inRepo $ Git.Command.runBool "fetch" [Param $ Remote.name r]
|
||||||
|
|
|
@ -161,18 +161,21 @@ handleMount st dstatus scanremotes dir = do
|
||||||
debug thisThread ["detected mount of", dir]
|
debug thisThread ["detected mount of", dir]
|
||||||
rs <- remotesUnder st dstatus dir
|
rs <- remotesUnder st dstatus dir
|
||||||
unless (null rs) $ do
|
unless (null rs) $ do
|
||||||
go rs =<< runThreadState st (inRepo Git.Branch.current)
|
|
||||||
where
|
|
||||||
go _ Nothing = noop
|
|
||||||
go rs (Just branch) = do
|
|
||||||
let nonspecial = filter (Git.repoIsLocal . Remote.repo) rs
|
let nonspecial = filter (Git.repoIsLocal . Remote.repo) rs
|
||||||
unless (null nonspecial) $
|
unless (null nonspecial) $ do
|
||||||
void $ alertWhile dstatus (syncMountAlert dir nonspecial) $ do
|
void $ alertWhile dstatus (syncMountAlert dir nonspecial) $ do
|
||||||
debug thisThread ["syncing with", show nonspecial]
|
debug thisThread ["syncing with", show rs]
|
||||||
runThreadState st $ manualPull branch nonspecial
|
sync nonspecial =<< runThreadState st (inRepo Git.Branch.current)
|
||||||
|
addScanRemotes scanremotes nonspecial
|
||||||
|
where
|
||||||
|
sync rs (Just branch) = do
|
||||||
|
runThreadState st $ manualPull (Just branch) rs
|
||||||
now <- getCurrentTime
|
now <- getCurrentTime
|
||||||
pushToRemotes thisThread now st Nothing nonspecial
|
pushToRemotes thisThread now st Nothing rs
|
||||||
addScanRemotes scanremotes rs
|
{- No local branch exists yet, but we can try pulling. -}
|
||||||
|
sync rs Nothing = do
|
||||||
|
runThreadState st $ manualPull Nothing rs
|
||||||
|
return True
|
||||||
|
|
||||||
{- Finds remotes located underneath the mount point.
|
{- Finds remotes located underneath the mount point.
|
||||||
-
|
-
|
||||||
|
|
|
@ -118,5 +118,5 @@ pushToRemotes threadname now st mpushmap remotes = do
|
||||||
|
|
||||||
retry branch g rs = do
|
retry branch g rs = do
|
||||||
debug threadname [ "trying manual pull to resolve failed pushes" ]
|
debug threadname [ "trying manual pull to resolve failed pushes" ]
|
||||||
runThreadState st $ manualPull branch rs
|
runThreadState st $ manualPull (Just branch) rs
|
||||||
go False (Just branch) g rs
|
go False (Just branch) g rs
|
||||||
|
|
|
@ -123,7 +123,7 @@ pullRemote remote branch = do
|
||||||
next $ do
|
next $ do
|
||||||
showOutput
|
showOutput
|
||||||
stopUnless fetch $
|
stopUnless fetch $
|
||||||
next $ mergeRemote remote branch
|
next $ mergeRemote remote (Just branch)
|
||||||
where
|
where
|
||||||
fetch = inRepo $ Git.Command.runBool "fetch"
|
fetch = inRepo $ Git.Command.runBool "fetch"
|
||||||
[Param $ Remote.name remote]
|
[Param $ Remote.name remote]
|
||||||
|
@ -132,11 +132,17 @@ pullRemote remote branch = do
|
||||||
- Which to merge from? Well, the master has whatever latest changes
|
- Which to merge from? Well, the master has whatever latest changes
|
||||||
- were committed, while the synced/master may have changes that some
|
- were committed, while the synced/master may have changes that some
|
||||||
- other remote synced to this remote. So, merge them both. -}
|
- other remote synced to this remote. So, merge them both. -}
|
||||||
mergeRemote :: Remote -> Git.Ref -> CommandCleanup
|
mergeRemote :: Remote -> (Maybe Git.Ref) -> CommandCleanup
|
||||||
mergeRemote remote branch = all id <$> (mapM merge =<< tomerge)
|
mergeRemote remote b = case b of
|
||||||
|
Nothing -> do
|
||||||
|
branch <- inRepo Git.Branch.currentUnsafe
|
||||||
|
all id <$> (mapM merge $ branchlist branch)
|
||||||
|
Just _ -> all id <$> (mapM merge =<< tomerge (branchlist b))
|
||||||
where
|
where
|
||||||
merge = mergeFrom . remoteBranch remote
|
merge = mergeFrom . remoteBranch remote
|
||||||
tomerge = filterM (changed remote) [branch, syncBranch branch]
|
tomerge branches = filterM (changed remote) branches
|
||||||
|
branchlist Nothing = []
|
||||||
|
branchlist (Just branch) = [branch, syncBranch branch]
|
||||||
|
|
||||||
pushRemote :: Remote -> Git.Ref -> CommandStart
|
pushRemote :: Remote -> Git.Ref -> CommandStart
|
||||||
pushRemote remote branch = go =<< needpush
|
pushRemote remote branch = go =<< needpush
|
||||||
|
|
|
@ -23,14 +23,24 @@ import Git.Command
|
||||||
-}
|
-}
|
||||||
current :: Repo -> IO (Maybe Git.Ref)
|
current :: Repo -> IO (Maybe Git.Ref)
|
||||||
current r = do
|
current r = do
|
||||||
branch <- firstLine <$> pipeRead [Param "symbolic-ref", Param "HEAD"] r
|
v <- currentUnsafe r
|
||||||
if null branch
|
case v of
|
||||||
then return Nothing
|
Nothing -> return Nothing
|
||||||
else ifM (null <$> pipeRead [Param "show-ref", Param branch] r)
|
Just branch ->
|
||||||
|
ifM (null <$> pipeRead [Param "show-ref", Param $ show branch] r)
|
||||||
( return Nothing
|
( return Nothing
|
||||||
, return $ Just $ Git.Ref branch
|
, return v
|
||||||
)
|
)
|
||||||
|
|
||||||
|
{- The current branch, which may not really exist yet. -}
|
||||||
|
currentUnsafe :: Repo -> IO (Maybe Git.Ref)
|
||||||
|
currentUnsafe r = parse . firstLine
|
||||||
|
<$> pipeRead [Param "symbolic-ref", Param "HEAD"] r
|
||||||
|
where
|
||||||
|
parse l
|
||||||
|
| null l = Nothing
|
||||||
|
| otherwise = Just $ Git.Ref l
|
||||||
|
|
||||||
{- Checks if the second branch has any commits not present on the first
|
{- Checks if the second branch has any commits not present on the first
|
||||||
- branch. -}
|
- branch. -}
|
||||||
changed :: Branch -> Branch -> Repo -> IO Bool
|
changed :: Branch -> Branch -> Repo -> IO Bool
|
||||||
|
|
Loading…
Reference in a new issue