git-annex/Assistant/Threads/Merger.hs

116 lines
3.3 KiB
Haskell
Raw Normal View History

{- git-annex assistant git merge thread
-
- Copyright 2012-2017 Joey Hess <id@joeyh.name>
2012-06-23 05:20:40 +00:00
-
- Licensed under the GNU AGPL version 3 or higher.
-}
2012-08-26 18:14:12 +00:00
module Assistant.Threads.Merger where
import Assistant.Common
import Assistant.TransferQueue
import Assistant.BranchChange
import Assistant.Sync
import Utility.DirWatcher
import Utility.DirWatcher.Types
import Annex.CurrentBranch
import qualified Annex
import qualified Annex.Branch
import qualified Git
import qualified Git.Branch
import qualified Git.Ref
import qualified Command.Sync
{- This thread watches for changes to .git/refs/, and handles incoming
- pushes. -}
2012-10-29 15:40:22 +00:00
mergeThread :: NamedThread
mergeThread = namedThread "Merger" $ do
2012-10-29 15:40:22 +00:00
g <- liftAnnex gitRepo
let gitd = fromRawFilePath (Git.localGitDir g)
let dir = gitd </> "refs"
liftIO $ createDirectoryUnder gitd dir
2012-10-29 15:40:22 +00:00
let hook a = Just <$> asIO2 (runHandler a)
changehook <- hook onChange
2012-10-29 15:40:22 +00:00
errhook <- hook onErr
let hooks = mkWatchHooks
{ addHook = changehook
, modifyHook = changehook
2012-10-29 15:40:22 +00:00
, errHook = errhook
}
void $ liftIO $ watchDir dir (const False) True hooks id
2012-10-29 15:40:22 +00:00
debug ["watching", dir]
2012-10-29 15:40:22 +00:00
type Handler = FilePath -> Assistant ()
{- Runs an action handler.
-
- Exceptions are ignored, otherwise a whole thread could be crashed.
-}
2012-10-29 15:40:22 +00:00
runHandler :: Handler -> FilePath -> Maybe FileStatus -> Assistant ()
runHandler handler file _filestatus =
either (liftIO . print) (const noop) =<< tryIO <~> handler file
{- Called when there's an error with inotify. -}
onErr :: Handler
2013-10-03 02:59:07 +00:00
onErr = error
{- Called when a new branch ref is written, or a branch ref is modified.
-
- At startup, synthetic add events fire, causing this to run, but that's
- ok; it ensures that any changes pushed since the last time the assistant
- ran are merged in.
-}
onChange :: Handler
onChange file
| ".lock" `isSuffixOf` file = noop
| isAnnexBranch file = do
2012-10-29 23:20:54 +00:00
branchChanged
diverged <- Annex.Branch.refsWereMerged
<$> liftAnnex Annex.Branch.forceUpdate
when diverged $ do
updateExportTreeFromLogAll
queueDeferredDownloads "retrying deferred download" Later
| otherwise = mergecurrent
2012-10-29 15:40:22 +00:00
where
changedbranch = fileToBranch file
mergecurrent =
mergecurrent' =<< liftAnnex getCurrentBranch
mergecurrent' currbranch@(Just b, _)
| changedbranch `isRelatedTo` b =
whenM (liftAnnex $ inRepo $ Git.Branch.changed b changedbranch) $ do
debug
[ "merging", Git.fromRef changedbranch
, "into", Git.fromRef b
]
void $ liftAnnex $ do
cmode <- annexCommitMode <$> Annex.getGitConfig
Command.Sync.merge
currbranch Command.Sync.mergeConfig
def
cmode
changedbranch
mergecurrent' _ = noop
{- Is the first branch a synced branch or remote tracking branch related
- to the second branch, which should be merged into it? -}
isRelatedTo :: Git.Ref -> Git.Ref -> Bool
isRelatedTo x y
| basex /= takeDirectory basex ++ "/" ++ basey = False
| "/synced/" `isInfixOf` Git.fromRef x = True
| "refs/remotes/" `isPrefixOf` Git.fromRef x = True
| otherwise = False
2012-10-31 06:34:03 +00:00
where
basex = Git.fromRef $ Git.Ref.base x
basey = Git.fromRef $ Git.Ref.base y
isAnnexBranch :: FilePath -> Bool
isAnnexBranch f = n `isSuffixOf` f
2012-10-31 06:34:03 +00:00
where
n = '/' : Git.fromRef Annex.Branch.name
fileToBranch :: FilePath -> Git.Ref
fileToBranch f = Git.Ref $ encodeBS' $ "refs" </> base
2012-10-31 06:34:03 +00:00
where
base = Prelude.last $ split "/refs/" f