fix crashes when run in a git repo that has been initted but has no master branch yet

This commit is contained in:
Joey Hess 2012-08-05 15:45:47 -04:00
parent 7478872a09
commit 34fc0d358e
4 changed files with 36 additions and 27 deletions

View file

@ -22,8 +22,8 @@ import Utility.ThreadScheduler
import Utility.Mounts import Utility.Mounts
import Remote.List import Remote.List
import qualified Types.Remote as Remote import qualified Types.Remote as Remote
import qualified Command.Sync
import Assistant.Threads.Merger import Assistant.Threads.Merger
import qualified Git.Branch
import Control.Concurrent import Control.Concurrent
import qualified Control.Exception as E import qualified Control.Exception as E
@ -161,7 +161,10 @@ 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
branch <- runThreadState st $ Command.Sync.currentBranch 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) $
void $ alertWhile dstatus (syncMountAlert dir nonspecial) $ do void $ alertWhile dstatus (syncMountAlert dir nonspecial) $ do

View file

@ -17,6 +17,7 @@ import Assistant.DaemonStatus
import qualified Command.Sync import qualified Command.Sync
import Utility.ThreadScheduler import Utility.ThreadScheduler
import Utility.Parallel import Utility.Parallel
import qualified Git.Branch
import Data.Time.Clock import Data.Time.Clock
import qualified Data.Map as M import qualified Data.Map as M
@ -84,10 +85,11 @@ shouldPush _now commits
pushToRemotes :: ThreadName -> UTCTime -> ThreadState -> (Maybe FailedPushMap) -> [Remote] -> IO Bool pushToRemotes :: ThreadName -> UTCTime -> ThreadState -> (Maybe FailedPushMap) -> [Remote] -> IO Bool
pushToRemotes threadname now st mpushmap remotes = do pushToRemotes threadname now st mpushmap remotes = do
(g, branch) <- runThreadState st $ (g, branch) <- runThreadState st $
(,) <$> fromRepo id <*> Command.Sync.currentBranch (,) <$> fromRepo id <*> inRepo Git.Branch.current
go True branch g remotes go True branch g remotes
where where
go shouldretry branch g rs = do go _ Nothing _ _ = return True -- no branch, so nothing to do
go shouldretry (Just branch) g rs = do
debug threadname debug threadname
[ "pushing to" [ "pushing to"
, show rs , show rs
@ -117,4 +119,4 @@ 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 branch rs
go False branch g rs go False (Just branch) g rs

View file

@ -6,8 +6,6 @@
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
{-# LANGUAGE BangPatterns #-}
module Command.Sync where module Command.Sync where
import Common.Annex import Common.Annex
@ -39,7 +37,7 @@ def = [command "sync" (paramOptional (paramRepeating paramRemote))
-- syncing involves several operations, any of which can independently fail -- syncing involves several operations, any of which can independently fail
seek :: CommandSeek seek :: CommandSeek
seek rs = do seek rs = do
branch <- currentBranch branch <- fromMaybe nobranch <$> inRepo Git.Branch.current
remotes <- syncRemotes rs remotes <- syncRemotes rs
return $ concat return $ concat
[ [ commit ] [ [ commit ]
@ -49,11 +47,6 @@ seek rs = do
, [ pushLocal branch ] , [ pushLocal branch ]
, [ pushRemote remote branch | remote <- remotes ] , [ pushRemote remote branch | remote <- remotes ]
] ]
currentBranch :: Annex Git.Ref
currentBranch = do
!branch <- fromMaybe nobranch <$> inRepo Git.Branch.current
return branch
where where
nobranch = error "no branch is checked out" nobranch = error "no branch is checked out"

View file

@ -5,6 +5,8 @@
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
{-# LANGUAGE BangPatterns #-}
module Git.Branch where module Git.Branch where
import Common import Common
@ -12,13 +14,22 @@ import Git
import Git.Sha import Git.Sha
import Git.Command import Git.Command
{- The currently checked out branch. -} {- The currently checked out branch.
-
- In a just initialized git repo before the first commit,
- symbolic-ref will show the master branch, even though that
- branch is not created yet. So, this also looks at show-ref HEAD
- to double-check.
-}
current :: Repo -> IO (Maybe Git.Ref) current :: Repo -> IO (Maybe Git.Ref)
current r = parse <$> pipeRead [Param "symbolic-ref", Param "HEAD"] r current r = do
where branch <- firstLine <$> pipeRead [Param "symbolic-ref", Param "HEAD"] r
parse v if null branch
| null v = Nothing then return Nothing
| otherwise = Just $ Git.Ref $ firstLine v else ifM (null <$> pipeRead [Param "show-ref", Param branch] r)
( return Nothing
, return $ Just $ Git.Ref branch
)
{- 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. -}