2012-06-22 21:01:08 +00:00
|
|
|
{- git-annex assistant git merge thread
|
|
|
|
-
|
|
|
|
- Copyright 2012 Joey Hess <joey@kitenet.net>
|
2012-06-23 05:20:40 +00:00
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
2012-06-22 21:01:08 +00:00
|
|
|
-}
|
|
|
|
|
2012-08-26 18:14:12 +00:00
|
|
|
module Assistant.Threads.Merger where
|
2012-06-22 21:01:08 +00:00
|
|
|
|
2012-07-20 23:29:59 +00:00
|
|
|
import Assistant.Common
|
2012-06-22 21:01:08 +00:00
|
|
|
import Assistant.ThreadedMonad
|
2012-09-18 01:05:50 +00:00
|
|
|
import Assistant.DaemonStatus
|
|
|
|
import Assistant.TransferQueue
|
2012-06-22 21:01:08 +00:00
|
|
|
import Utility.DirWatcher
|
|
|
|
import Utility.Types.DirWatcher
|
2012-09-16 22:53:13 +00:00
|
|
|
import qualified Annex.Branch
|
2012-06-22 21:01:08 +00:00
|
|
|
import qualified Git
|
2012-06-23 14:29:46 +00:00
|
|
|
import qualified Git.Merge
|
2012-06-22 21:01:08 +00:00
|
|
|
import qualified Git.Branch
|
|
|
|
|
2012-07-20 23:29:59 +00:00
|
|
|
thisThread :: ThreadName
|
|
|
|
thisThread = "Merger"
|
|
|
|
|
2012-09-18 01:05:50 +00:00
|
|
|
{- This thread watches for changes to .git/refs/, and handles incoming
|
|
|
|
- pushes. -}
|
|
|
|
mergeThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> NamedThread
|
|
|
|
mergeThread st dstatus transferqueue = thread $ do
|
2012-10-12 05:17:45 +00:00
|
|
|
g <- runThreadState st gitRepo
|
2012-09-17 03:09:08 +00:00
|
|
|
let dir = Git.localGitDir g </> "refs"
|
2012-06-22 21:01:08 +00:00
|
|
|
createDirectoryIfMissing True dir
|
run current branch merge in annex monad
I was seeing some interesting crashes after the previous commit,
when making file changes slightly faster than the assistant could keep up.
error: Ref refs/heads/master is at 7074f8e0a11110c532d06746e334f2fec6af6ab4 but expected 95ea86008d72a40d97a81cfc8fb47a0da92166bd
fatal: cannot lock HEAD ref
Committer crashed: git commit [Param "--allow-empty-message",Param "-m",Param "",Param "--allow-empty",Param "--quiet"] failed
Pusher crashed: thread blocked indefinitely in an STM transaction
Clearly the the merger ended up running at the same time as the committer,
and with both modifying HEAD the committer crashed. I fixed that by
making the Merger run its merge inside the annex monad, which avoids
it running concurrently with other git operations. Also by making
the committer not crash if git fails.
What I don't understand is why the pusher then crashed with a STM deadlock.
That must be in either the DaemonStatusHandle or the FailedPushMap,
and the latter is only used by the pusher. Did the committer's crash somehow
break STM?
The BlockedIndefinitelyOnSTM exception is described as:
-- |The thread is waiting to retry an STM transaction, but there are no
-- other references to any @TVar@s involved, so it can't ever continue.
If the Committer had a reference to a TVar and crashed, I can sort of see
this leading to that exception..
The crash was quite easy to reproduce after the previous commit, but
after making the above change, I have yet to see it again. Here's hoping.
2012-09-18 01:32:30 +00:00
|
|
|
let hook a = Just $ runHandler st dstatus transferqueue a
|
2012-06-22 21:01:08 +00:00
|
|
|
let hooks = mkWatchHooks
|
|
|
|
{ addHook = hook onAdd
|
|
|
|
, errHook = hook onErr
|
|
|
|
}
|
2012-06-28 17:37:03 +00:00
|
|
|
void $ watchDir dir (const False) hooks id
|
2012-07-20 23:29:59 +00:00
|
|
|
debug thisThread ["watching", dir]
|
2012-09-06 18:56:04 +00:00
|
|
|
where
|
|
|
|
thread = NamedThread thisThread
|
2012-06-22 21:01:08 +00:00
|
|
|
|
run current branch merge in annex monad
I was seeing some interesting crashes after the previous commit,
when making file changes slightly faster than the assistant could keep up.
error: Ref refs/heads/master is at 7074f8e0a11110c532d06746e334f2fec6af6ab4 but expected 95ea86008d72a40d97a81cfc8fb47a0da92166bd
fatal: cannot lock HEAD ref
Committer crashed: git commit [Param "--allow-empty-message",Param "-m",Param "",Param "--allow-empty",Param "--quiet"] failed
Pusher crashed: thread blocked indefinitely in an STM transaction
Clearly the the merger ended up running at the same time as the committer,
and with both modifying HEAD the committer crashed. I fixed that by
making the Merger run its merge inside the annex monad, which avoids
it running concurrently with other git operations. Also by making
the committer not crash if git fails.
What I don't understand is why the pusher then crashed with a STM deadlock.
That must be in either the DaemonStatusHandle or the FailedPushMap,
and the latter is only used by the pusher. Did the committer's crash somehow
break STM?
The BlockedIndefinitelyOnSTM exception is described as:
-- |The thread is waiting to retry an STM transaction, but there are no
-- other references to any @TVar@s involved, so it can't ever continue.
If the Committer had a reference to a TVar and crashed, I can sort of see
this leading to that exception..
The crash was quite easy to reproduce after the previous commit, but
after making the above change, I have yet to see it again. Here's hoping.
2012-09-18 01:32:30 +00:00
|
|
|
type Handler = ThreadState -> DaemonStatusHandle -> TransferQueue -> FilePath -> Maybe FileStatus -> IO ()
|
2012-06-22 21:01:08 +00:00
|
|
|
|
|
|
|
{- Runs an action handler.
|
|
|
|
-
|
|
|
|
- Exceptions are ignored, otherwise a whole thread could be crashed.
|
|
|
|
-}
|
run current branch merge in annex monad
I was seeing some interesting crashes after the previous commit,
when making file changes slightly faster than the assistant could keep up.
error: Ref refs/heads/master is at 7074f8e0a11110c532d06746e334f2fec6af6ab4 but expected 95ea86008d72a40d97a81cfc8fb47a0da92166bd
fatal: cannot lock HEAD ref
Committer crashed: git commit [Param "--allow-empty-message",Param "-m",Param "",Param "--allow-empty",Param "--quiet"] failed
Pusher crashed: thread blocked indefinitely in an STM transaction
Clearly the the merger ended up running at the same time as the committer,
and with both modifying HEAD the committer crashed. I fixed that by
making the Merger run its merge inside the annex monad, which avoids
it running concurrently with other git operations. Also by making
the committer not crash if git fails.
What I don't understand is why the pusher then crashed with a STM deadlock.
That must be in either the DaemonStatusHandle or the FailedPushMap,
and the latter is only used by the pusher. Did the committer's crash somehow
break STM?
The BlockedIndefinitelyOnSTM exception is described as:
-- |The thread is waiting to retry an STM transaction, but there are no
-- other references to any @TVar@s involved, so it can't ever continue.
If the Committer had a reference to a TVar and crashed, I can sort of see
this leading to that exception..
The crash was quite easy to reproduce after the previous commit, but
after making the above change, I have yet to see it again. Here's hoping.
2012-09-18 01:32:30 +00:00
|
|
|
runHandler :: ThreadState -> DaemonStatusHandle -> TransferQueue -> Handler -> FilePath -> Maybe FileStatus -> IO ()
|
|
|
|
runHandler st dstatus transferqueue handler file filestatus = void $
|
2012-06-22 21:01:08 +00:00
|
|
|
either print (const noop) =<< tryIO go
|
|
|
|
where
|
run current branch merge in annex monad
I was seeing some interesting crashes after the previous commit,
when making file changes slightly faster than the assistant could keep up.
error: Ref refs/heads/master is at 7074f8e0a11110c532d06746e334f2fec6af6ab4 but expected 95ea86008d72a40d97a81cfc8fb47a0da92166bd
fatal: cannot lock HEAD ref
Committer crashed: git commit [Param "--allow-empty-message",Param "-m",Param "",Param "--allow-empty",Param "--quiet"] failed
Pusher crashed: thread blocked indefinitely in an STM transaction
Clearly the the merger ended up running at the same time as the committer,
and with both modifying HEAD the committer crashed. I fixed that by
making the Merger run its merge inside the annex monad, which avoids
it running concurrently with other git operations. Also by making
the committer not crash if git fails.
What I don't understand is why the pusher then crashed with a STM deadlock.
That must be in either the DaemonStatusHandle or the FailedPushMap,
and the latter is only used by the pusher. Did the committer's crash somehow
break STM?
The BlockedIndefinitelyOnSTM exception is described as:
-- |The thread is waiting to retry an STM transaction, but there are no
-- other references to any @TVar@s involved, so it can't ever continue.
If the Committer had a reference to a TVar and crashed, I can sort of see
this leading to that exception..
The crash was quite easy to reproduce after the previous commit, but
after making the above change, I have yet to see it again. Here's hoping.
2012-09-18 01:32:30 +00:00
|
|
|
go = handler st dstatus transferqueue file filestatus
|
2012-06-22 21:01:08 +00:00
|
|
|
|
|
|
|
{- Called when there's an error with inotify. -}
|
|
|
|
onErr :: Handler
|
run current branch merge in annex monad
I was seeing some interesting crashes after the previous commit,
when making file changes slightly faster than the assistant could keep up.
error: Ref refs/heads/master is at 7074f8e0a11110c532d06746e334f2fec6af6ab4 but expected 95ea86008d72a40d97a81cfc8fb47a0da92166bd
fatal: cannot lock HEAD ref
Committer crashed: git commit [Param "--allow-empty-message",Param "-m",Param "",Param "--allow-empty",Param "--quiet"] failed
Pusher crashed: thread blocked indefinitely in an STM transaction
Clearly the the merger ended up running at the same time as the committer,
and with both modifying HEAD the committer crashed. I fixed that by
making the Merger run its merge inside the annex monad, which avoids
it running concurrently with other git operations. Also by making
the committer not crash if git fails.
What I don't understand is why the pusher then crashed with a STM deadlock.
That must be in either the DaemonStatusHandle or the FailedPushMap,
and the latter is only used by the pusher. Did the committer's crash somehow
break STM?
The BlockedIndefinitelyOnSTM exception is described as:
-- |The thread is waiting to retry an STM transaction, but there are no
-- other references to any @TVar@s involved, so it can't ever continue.
If the Committer had a reference to a TVar and crashed, I can sort of see
this leading to that exception..
The crash was quite easy to reproduce after the previous commit, but
after making the above change, I have yet to see it again. Here's hoping.
2012-09-18 01:32:30 +00:00
|
|
|
onErr _ _ _ msg _ = error msg
|
2012-06-22 21:01:08 +00:00
|
|
|
|
|
|
|
{- Called when a new branch ref is written.
|
|
|
|
-
|
|
|
|
- This relies on git's atomic method of updating branch ref files,
|
|
|
|
- which is to first write the new file to .lock, and then rename it
|
|
|
|
- over the old file. So, ignore .lock files, and the rename ensures
|
|
|
|
- the watcher sees a new file being added on each update.
|
|
|
|
-
|
|
|
|
- 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.
|
|
|
|
-}
|
|
|
|
onAdd :: Handler
|
run current branch merge in annex monad
I was seeing some interesting crashes after the previous commit,
when making file changes slightly faster than the assistant could keep up.
error: Ref refs/heads/master is at 7074f8e0a11110c532d06746e334f2fec6af6ab4 but expected 95ea86008d72a40d97a81cfc8fb47a0da92166bd
fatal: cannot lock HEAD ref
Committer crashed: git commit [Param "--allow-empty-message",Param "-m",Param "",Param "--allow-empty",Param "--quiet"] failed
Pusher crashed: thread blocked indefinitely in an STM transaction
Clearly the the merger ended up running at the same time as the committer,
and with both modifying HEAD the committer crashed. I fixed that by
making the Merger run its merge inside the annex monad, which avoids
it running concurrently with other git operations. Also by making
the committer not crash if git fails.
What I don't understand is why the pusher then crashed with a STM deadlock.
That must be in either the DaemonStatusHandle or the FailedPushMap,
and the latter is only used by the pusher. Did the committer's crash somehow
break STM?
The BlockedIndefinitelyOnSTM exception is described as:
-- |The thread is waiting to retry an STM transaction, but there are no
-- other references to any @TVar@s involved, so it can't ever continue.
If the Committer had a reference to a TVar and crashed, I can sort of see
this leading to that exception..
The crash was quite easy to reproduce after the previous commit, but
after making the above change, I have yet to see it again. Here's hoping.
2012-09-18 01:32:30 +00:00
|
|
|
onAdd st dstatus transferqueue file _
|
2012-06-22 21:01:08 +00:00
|
|
|
| ".lock" `isSuffixOf` file = noop
|
2012-09-18 01:05:50 +00:00
|
|
|
| isAnnexBranch file = runThreadState st $
|
|
|
|
whenM Annex.Branch.forceUpdate $
|
|
|
|
queueDeferredDownloads Later transferqueue dstatus
|
run current branch merge in annex monad
I was seeing some interesting crashes after the previous commit,
when making file changes slightly faster than the assistant could keep up.
error: Ref refs/heads/master is at 7074f8e0a11110c532d06746e334f2fec6af6ab4 but expected 95ea86008d72a40d97a81cfc8fb47a0da92166bd
fatal: cannot lock HEAD ref
Committer crashed: git commit [Param "--allow-empty-message",Param "-m",Param "",Param "--allow-empty",Param "--quiet"] failed
Pusher crashed: thread blocked indefinitely in an STM transaction
Clearly the the merger ended up running at the same time as the committer,
and with both modifying HEAD the committer crashed. I fixed that by
making the Merger run its merge inside the annex monad, which avoids
it running concurrently with other git operations. Also by making
the committer not crash if git fails.
What I don't understand is why the pusher then crashed with a STM deadlock.
That must be in either the DaemonStatusHandle or the FailedPushMap,
and the latter is only used by the pusher. Did the committer's crash somehow
break STM?
The BlockedIndefinitelyOnSTM exception is described as:
-- |The thread is waiting to retry an STM transaction, but there are no
-- other references to any @TVar@s involved, so it can't ever continue.
If the Committer had a reference to a TVar and crashed, I can sort of see
this leading to that exception..
The crash was quite easy to reproduce after the previous commit, but
after making the above change, I have yet to see it again. Here's hoping.
2012-09-18 01:32:30 +00:00
|
|
|
| "/synced/" `isInfixOf` file = runThreadState st $ do
|
|
|
|
mergecurrent =<< inRepo Git.Branch.current
|
2012-09-16 22:53:13 +00:00
|
|
|
| otherwise = noop
|
|
|
|
where
|
|
|
|
changedbranch = fileToBranch file
|
2012-09-18 01:05:50 +00:00
|
|
|
mergecurrent (Just current)
|
2012-09-16 22:53:13 +00:00
|
|
|
| equivBranches changedbranch current = do
|
|
|
|
liftIO $ debug thisThread
|
|
|
|
[ "merging"
|
|
|
|
, show changedbranch
|
|
|
|
, "into"
|
|
|
|
, show current
|
|
|
|
]
|
run current branch merge in annex monad
I was seeing some interesting crashes after the previous commit,
when making file changes slightly faster than the assistant could keep up.
error: Ref refs/heads/master is at 7074f8e0a11110c532d06746e334f2fec6af6ab4 but expected 95ea86008d72a40d97a81cfc8fb47a0da92166bd
fatal: cannot lock HEAD ref
Committer crashed: git commit [Param "--allow-empty-message",Param "-m",Param "",Param "--allow-empty",Param "--quiet"] failed
Pusher crashed: thread blocked indefinitely in an STM transaction
Clearly the the merger ended up running at the same time as the committer,
and with both modifying HEAD the committer crashed. I fixed that by
making the Merger run its merge inside the annex monad, which avoids
it running concurrently with other git operations. Also by making
the committer not crash if git fails.
What I don't understand is why the pusher then crashed with a STM deadlock.
That must be in either the DaemonStatusHandle or the FailedPushMap,
and the latter is only used by the pusher. Did the committer's crash somehow
break STM?
The BlockedIndefinitelyOnSTM exception is described as:
-- |The thread is waiting to retry an STM transaction, but there are no
-- other references to any @TVar@s involved, so it can't ever continue.
If the Committer had a reference to a TVar and crashed, I can sort of see
this leading to that exception..
The crash was quite easy to reproduce after the previous commit, but
after making the above change, I have yet to see it again. Here's hoping.
2012-09-18 01:32:30 +00:00
|
|
|
void $ inRepo $
|
|
|
|
Git.Merge.mergeNonInteractive changedbranch
|
2012-09-18 01:05:50 +00:00
|
|
|
mergecurrent _ = noop
|
2012-09-16 22:53:13 +00:00
|
|
|
|
|
|
|
equivBranches :: Git.Ref -> Git.Ref -> Bool
|
|
|
|
equivBranches x y = base x == base y
|
|
|
|
where
|
|
|
|
base = takeFileName . show
|
2012-06-22 21:01:08 +00:00
|
|
|
|
2012-09-16 22:53:13 +00:00
|
|
|
isAnnexBranch :: FilePath -> Bool
|
|
|
|
isAnnexBranch f = n `isSuffixOf` f
|
|
|
|
where
|
|
|
|
n = "/" ++ show Annex.Branch.name
|
|
|
|
|
|
|
|
fileToBranch :: FilePath -> Git.Ref
|
2012-09-17 03:09:08 +00:00
|
|
|
fileToBranch f = Git.Ref $ "refs" </> base
|
2012-09-16 22:53:13 +00:00
|
|
|
where
|
2012-09-17 03:09:08 +00:00
|
|
|
base = Prelude.last $ split "/refs/" f
|