Skip to content

Commit 9497f8d

Browse files
committed
Merge #137: Merge train
Approved-by: rudymatela Auto-deploy: false
2 parents 4873ebe + 6ce0638 commit 9497f8d

File tree

6 files changed

+1259
-221
lines changed

6 files changed

+1259
-221
lines changed

src/Git.hs

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -50,6 +50,8 @@ module Git
5050
runGitReadOnly,
5151
tag,
5252
tag',
53+
toBaseBranch,
54+
toRemoteBranch,
5355
tryIntegrate,
5456
)
5557
where
@@ -90,6 +92,12 @@ newtype RemoteBranch = RemoteBranch Text deriving newtype (Show, Eq)
9092
localBranch :: RemoteBranch -> Branch
9193
localBranch (RemoteBranch name) = Branch name
9294

95+
toRemoteBranch :: Branch -> RemoteBranch
96+
toRemoteBranch (Branch name) = RemoteBranch name
97+
98+
toBaseBranch :: Branch -> BaseBranch
99+
toBaseBranch (Branch name) = BaseBranch name
100+
93101
-- | A commit hash is stored as its hexadecimal representation.
94102
newtype Sha = Sha Text deriving newtype (Show, Eq)
95103

src/Logic.hs

Lines changed: 170 additions & 46 deletions
Original file line numberDiff line numberDiff line change
@@ -36,14 +36,14 @@ where
3636
import Control.Concurrent.STM.TBQueue (TBQueue, newTBQueue, readTBQueue, writeTBQueue)
3737
import Control.Concurrent.STM.TMVar (TMVar, newTMVarIO, readTMVar, swapTMVar)
3838
import Control.Exception (assert)
39-
import Control.Monad (foldM, unless, void, when)
39+
import Control.Monad (foldM, unless, void, when, (>=>))
4040
import Control.Monad.Free (Free (..), foldFree, hoistFree, liftF)
4141
import Control.Monad.STM (atomically)
4242
import Data.Bifunctor (first)
4343
import Data.Either.Extra (maybeToEither)
4444
import Data.Functor.Sum (Sum (InL, InR))
4545
import Data.IntSet (IntSet)
46-
import Data.Maybe (fromJust, isJust, listToMaybe)
46+
import Data.Maybe (fromJust, isJust, listToMaybe, fromMaybe)
4747
import Data.Text (Text)
4848
import Data.Text.Lazy (toStrict)
4949
import GHC.Natural (Natural)
@@ -79,6 +79,7 @@ data ActionFree a
7979
-- This is a record type, but the names are currently only used for documentation.
8080
{ _mergeCommitMessage :: Text
8181
, _integrationCandidate :: (PullRequestId, Branch, Sha)
82+
, _train :: [PullRequestId]
8283
, _alwaysAddMergeCommit :: Bool
8384
, _cont :: Either IntegrationFailure Sha -> a
8485
}
@@ -97,6 +98,7 @@ data ActionFree a
9798
data PRCloseCause =
9899
User -- ^ The user closed the PR.
99100
| StopIntegration -- ^ We close and reopen the PR internally to stop its integration if it is approved.
101+
deriving Show
100102

101103
type Action = Free ActionFree
102104

@@ -118,8 +120,8 @@ doGit = hoistFree (InR . InL)
118120
doGithub :: GithubOperation a -> Operation a
119121
doGithub = hoistFree (InR . InR)
120122

121-
tryIntegrate :: Text -> (PullRequestId, Branch, Sha) -> Bool -> Action (Either IntegrationFailure Sha)
122-
tryIntegrate mergeMessage candidate alwaysAddMergeCommit = liftF $ TryIntegrate mergeMessage candidate alwaysAddMergeCommit id
123+
tryIntegrate :: Text -> (PullRequestId, Branch, Sha) -> [PullRequestId] -> Bool -> Action (Either IntegrationFailure Sha)
124+
tryIntegrate mergeMessage candidate train alwaysAddMergeCommit = liftF $ TryIntegrate mergeMessage candidate train alwaysAddMergeCommit id
123125

124126
-- Try to fast-forward the remote target branch (usually master) to the new sha.
125127
-- Before doing so, force-push that SHA to the pull request branch, and after
@@ -161,24 +163,26 @@ getDateTime = liftF $ GetDateTime id
161163
-- Interpreter that translates high-level actions into more low-level ones.
162164
runAction :: ProjectConfiguration -> Action a -> Operation a
163165
runAction config = foldFree $ \case
164-
TryIntegrate message (pr, ref, sha) alwaysAddMergeCommit cont -> do
166+
TryIntegrate message (pr, ref, sha) train alwaysAddMergeCommit cont -> do
165167
doGit $ ensureCloned config
166168

167169
-- Needed for backwards compatibility with existing repositories
168170
-- as we now test at testing/<pr_id> instead of testing.
169171
-- When no repositories have a testing branch, this can safely be removed.
170172
_ <- doGit $ Git.deleteRemoteBranch $ Git.Branch $ Config.testBranch config
171173

174+
let targetBranch = fromMaybe (Git.Branch $ Config.branch config) (trainBranch train)
175+
172176
shaOrFailed <- doGit $ Git.tryIntegrate
173177
message
174178
ref
175179
sha
176-
(Git.RemoteBranch $ Config.branch config)
180+
(Git.toRemoteBranch targetBranch)
177181
(testBranch config pr)
178182
alwaysAddMergeCommit
179183

180184
case shaOrFailed of
181-
Left failure -> pure $ cont $ Left $ IntegrationFailure (BaseBranch $ Config.branch config) failure
185+
Left failure -> pure $ cont $ Left $ IntegrationFailure (Git.toBaseBranch targetBranch) failure
182186
Right integratedSha -> pure $ cont $ Right integratedSha
183187

184188
TryPromote prBranch sha cont -> do
@@ -223,14 +227,20 @@ runAction config = foldFree $ \case
223227
openPrIds <- doGithub GithubApi.getOpenPullRequests
224228
pure $ cont openPrIds
225229

226-
GetLatestVersion sha cont -> doGit $
230+
GetLatestVersion sha cont -> doGit $ do
231+
Git.fetchBranchWithTags $ Branch (Config.branch config)
227232
cont . maybe (Right 0) (\t -> maybeToEither t $ parseVersion t) <$> Git.lastTag sha
228233

229234
GetChangelog prevTag curHead cont -> doGit $
230235
cont <$> Git.shortlog (AsRefSpec prevTag) (AsRefSpec curHead)
231236

232237
GetDateTime cont -> doTime $ cont <$> Time.getDateTime
233238

239+
where
240+
trainBranch :: [PullRequestId] -> Maybe Git.Branch
241+
trainBranch [] = Nothing
242+
trainBranch train = Just $ last [testBranch config pr | pr <- train]
243+
234244
ensureCloned :: ProjectConfiguration -> GitOperation ()
235245
ensureCloned config =
236246
let
@@ -370,9 +380,14 @@ handlePullRequestClosedByUser = handlePullRequestClosed User
370380

371381
handlePullRequestClosed :: PRCloseCause -> PullRequestId -> ProjectState -> Action ProjectState
372382
handlePullRequestClosed closingReason pr state = do
373-
when (pr `elem` Pr.integratedPullRequests state) $
383+
when (pr `elem` Pr.unfailedIntegratedPullRequests state) $
374384
leaveComment pr $ prClosingMessage closingReason
375-
pure $ Pr.deletePullRequest pr state
385+
-- actually delete the pull request
386+
pure . Pr.deletePullRequest pr
387+
$ case Pr.lookupPullRequest pr state of
388+
Just (Pr.PullRequest{Pr.integrationStatus = Promoted}) -> state
389+
-- we unintegrate PRs after it if it has not been promoted to master
390+
_ -> unintegrateAfter pr $ state
376391

377392
handlePullRequestEdited :: PullRequestId -> Text -> BaseBranch -> ProjectState -> Action ProjectState
378393
handlePullRequestEdited prId newTitle newBaseBranch state =
@@ -542,20 +557,42 @@ handleMergeRequested projectConfig prId author state pr approvalType = do
542557
then pure $ Pr.setIntegrationStatus prId IncorrectBaseBranch state''
543558
else pure state''
544559

560+
-- | Given a pull request id, mark all pull requests that follow from it
561+
-- in the merge train as NotIntegrated
562+
unintegrateAfter :: PullRequestId -> ProjectState -> ProjectState
563+
unintegrateAfter pid state = case Pr.lookupPullRequest pid state of
564+
Nothing -> state -- PR not found. Keep the state as it is.
565+
Just pr -> unintegrateAfter' pr state
566+
where
567+
unintegrateAfter' :: PullRequest -> ProjectState -> ProjectState
568+
unintegrateAfter' pr0 = Pr.updatePullRequests unintegrate
569+
where
570+
unintegrate pr | pr `Pr.approvedAfter` pr0 && Pr.isIntegratedOrSpeculativelyConflicted pr
571+
= pr{Pr.integrationStatus = NotIntegrated}
572+
| otherwise
573+
= pr
574+
575+
-- | If there is an integration candidate, and its integration sha matches that of the build,
576+
-- then update the build status for that pull request. Otherwise do nothing.
545577
handleBuildStatusChanged :: Sha -> BuildStatus -> ProjectState -> Action ProjectState
546-
handleBuildStatusChanged buildSha newStatus = pure . Pr.updatePullRequests setBuildStatus
578+
handleBuildStatusChanged buildSha newStatus state = pure $
579+
compose [ Pr.updatePullRequest pid setBuildStatus
580+
. case newStatus of
581+
BuildFailed _ -> unintegrateAfter pid
582+
_ -> id
583+
| pid <- Pr.filterPullRequestsBy shouldUpdate state
584+
] state
547585
where
548-
setBuildStatus pr = case Pr.integrationStatus pr of
549-
-- If there is an integration candidate, and its integration sha matches that of the build,
550-
-- then update the build status for that pull request. Otherwise do nothing.
551-
Integrated candidateSha oldStatus | candidateSha == buildSha && newStatus `supersedes` oldStatus ->
552-
pr { Pr.integrationStatus = Integrated buildSha newStatus
553-
, Pr.needsFeedback = case newStatus of
554-
BuildStarted _ -> True
555-
BuildFailed _ -> True
556-
_ -> Pr.needsFeedback pr -- unchanged
557-
}
558-
_ -> pr
586+
shouldUpdate pr = case Pr.integrationStatus pr of
587+
Integrated candidateSha oldStatus -> candidateSha == buildSha && newStatus `supersedes` oldStatus
588+
_ -> False
589+
setBuildStatus pr = pr
590+
{ Pr.integrationStatus = Integrated buildSha newStatus
591+
, Pr.needsFeedback = case newStatus of
592+
BuildStarted _ -> True
593+
BuildFailed _ -> True
594+
_ -> Pr.needsFeedback pr -- unchanged
595+
}
559596

560597
-- | Does the first build status supersedes the second?
561598
--
@@ -612,15 +649,21 @@ synchronizeState stateInitial =
612649
-- should find a new candidate. Or after the pull request for which a build is
613650
-- in progress is closed, we should find a new candidate.
614651
proceed :: ProjectState -> Action ProjectState
615-
proceed state = do
616-
state' <- provideFeedback state
617-
case (Pr.integratedPullRequests state', Pr.candidatePullRequests state') of
618-
-- Proceed with an already integrated candidate
619-
(candidate:_, _) -> proceedCandidate candidate state'
620-
-- Found a new candidate, try to integrate it.
621-
(_, pr:_) -> tryIntegratePullRequest pr state'
622-
-- No pull requests eligible, do nothing.
623-
(_, _) -> return state'
652+
proceed = provideFeedback
653+
>=> proceedFirstCandidate
654+
>=> tryIntegrateFirstPullRequest
655+
656+
-- proceeds with the candidate that was approved first
657+
proceedFirstCandidate :: ProjectState -> Action ProjectState
658+
proceedFirstCandidate state = case Pr.unfailedIntegratedPullRequests state of
659+
(candidate:_) -> proceedCandidate candidate state
660+
_ -> pure state
661+
662+
-- try to integrate the pull request that was approved first
663+
tryIntegrateFirstPullRequest :: ProjectState -> Action ProjectState
664+
tryIntegrateFirstPullRequest state = case Pr.candidatePullRequests state of
665+
(pr:_) -> tryIntegratePullRequest pr state
666+
_ -> pure state
624667

625668
-- | Pushes the given integrated PR to be the new master if the build succeeded
626669
proceedCandidate :: PullRequestId -> ProjectState -> Action ProjectState
@@ -656,14 +699,18 @@ tryIntegratePullRequest pr state =
656699
, format "Auto-deploy: {}" [if approvalType == MergeAndDeploy then "true" else "false" :: Text]
657700
]
658701
mergeMessage = Text.unlines mergeMessageLines
702+
-- the takeWhile here is needed in case of reintegrations after failing pushes
703+
train = takeWhile (/= pr) $ Pr.unfailedIntegratedPullRequests state
659704
in do
660-
result <- tryIntegrate mergeMessage candidate $ Pr.alwaysAddMergeCommit approvalType
705+
result <- tryIntegrate mergeMessage candidate train $ Pr.alwaysAddMergeCommit approvalType
661706
case result of
662707
Left (IntegrationFailure targetBranch reason) ->
663708
-- If integrating failed, perform no further actions but do set the
664709
-- state to conflicted.
710+
-- If this is a speculative rebase, we wait before giving feedback.
711+
-- For WrongFixups, we can report issues right away.
665712
pure $ Pr.setIntegrationStatus pr (Conflicted targetBranch reason) $
666-
Pr.setNeedsFeedback pr True state
713+
Pr.setNeedsFeedback pr (null train || reason == WrongFixups) state
667714

668715
Right (Sha sha) -> do
669716
-- If it succeeded, set the build to pending,
@@ -721,12 +768,46 @@ pushCandidate (pullRequestId, pullRequest) newHead state =
721768
-- the integration candidate, so we proceed with the next pull request.
722769
PushOk -> do
723770
cleanupTestBranch pullRequestId
724-
pure $ Pr.setIntegrationStatus pullRequestId Promoted state
771+
pure $ Pr.updatePullRequests (unspeculateConflictsAfter pullRequest)
772+
$ Pr.updatePullRequests (unspeculateFailuresAfter pullRequest)
773+
$ Pr.setIntegrationStatus pullRequestId Promoted state
725774
-- If something was pushed to the target branch while the candidate was
726775
-- being tested, try to integrate again and hope that next time the push
727776
-- succeeds.
728777
PushRejected _why -> tryIntegratePullRequest pullRequestId state
729778

779+
-- | When a pull request has been promoted to master this means that any
780+
-- conflicts (failed rebases) built on top of it are not speculative anymore:
781+
-- they are real conflicts on top of the (new) master.
782+
--
783+
-- This function updates the conflicted bases for all pull requests that come
784+
-- after the given PR and sets them to need feedback.
785+
unspeculateConflictsAfter :: PullRequest -> PullRequest -> PullRequest
786+
unspeculateConflictsAfter promotedPullRequest pr
787+
| Pr.PullRequest{ Pr.integrationStatus = Conflicted specBase reason
788+
, Pr.baseBranch = realBase
789+
} <- pr
790+
, specBase /= realBase && pr `Pr.approvedAfter` promotedPullRequest
791+
= pr { Pr.integrationStatus = Conflicted realBase reason
792+
, Pr.needsFeedback = True
793+
}
794+
| otherwise
795+
= pr
796+
797+
-- | When a pull request has been promoted to master this means that any build
798+
-- failures build on top of it are not speculative anymore: they are real build
799+
-- failures on top of the (new) master.
800+
--
801+
-- This function simply sets them to be sent feedback again this time the build
802+
-- failure will be reported as a real definitive failure.
803+
unspeculateFailuresAfter :: PullRequest -> PullRequest -> PullRequest
804+
unspeculateFailuresAfter promotedPullRequest pr
805+
| Pr.PullRequest{Pr.integrationStatus = Integrated _ (BuildFailed _)} <- pr
806+
, pr `Pr.approvedAfter` promotedPullRequest
807+
= pr{Pr.needsFeedback = True}
808+
| otherwise
809+
= pr
810+
730811
-- Keep doing a proceed step until the state doesn't change any more. For this
731812
-- to work properly, it is essential that "proceed" does not have any side
732813
-- effects if it does not change the state.
@@ -749,8 +830,14 @@ describeStatus prId pr state = case Pr.classifyPullRequest pr of
749830
0 -> format "Pull request approved for {} by @{}, rebasing now." [approvalCommand, approvedBy]
750831
1 -> format "Pull request approved for {} by @{}, waiting for rebase behind one pull request." [approvalCommand, approvedBy]
751832
n -> format "Pull request approved for {} by @{}, waiting for rebase behind {} pull requests." (approvalCommand, approvedBy, n)
752-
PrStatusBuildPending -> let Sha sha = fromJust $ getIntegrationSha pr
753-
in Text.concat ["Rebased as ", sha, ", waiting for CI …"]
833+
PrStatusBuildPending -> let Sha sha = fromJust $ Pr.integrationSha pr
834+
train = takeWhile (/= prId) $ Pr.unfailedIntegratedPullRequests state
835+
in case train of
836+
[] -> Text.concat ["Rebased as ", sha, ", waiting for CI …"]
837+
(_:_) -> Text.concat [ "Speculatively rebased as ", sha
838+
, " behind ", prettyPullRequestIds train
839+
, ", waiting for CI …"
840+
]
754841
PrStatusBuildStarted url -> Text.concat ["[CI job](", url, ") started."]
755842
PrStatusIntegrated -> "The build succeeded."
756843
PrStatusIncorrectBaseBranch -> "Merge rejected: the target branch must be the integration branch."
@@ -769,16 +856,22 @@ describeStatus prId pr state = case Pr.classifyPullRequest pr of
769856
, " "
770857
, prBranchName
771858
]
772-
PrStatusFailedBuild url -> case url of
773-
Just url' -> format "The build failed: {}\nIf this is the result of a flaky test, close and reopen the PR, then tag me again.\nOtherwise, push a new commit and tag me again." [url']
774-
-- This should probably never happen
775-
Nothing -> "The build failed, but GitHub did not provide an URL to the build failure."
776-
where
777-
getIntegrationSha :: PullRequest -> Maybe Sha
778-
getIntegrationSha pullRequest =
779-
case Pr.integrationStatus pullRequest of
780-
Integrated sha _ -> Just sha
781-
_ -> Nothing
859+
-- The following is not actually shown to the user
860+
-- as it is never set with needsFeedback=True,
861+
-- but here in case we decide to show it.
862+
PrStatusSpeculativeConflict -> "Failed to speculatively rebase. \
863+
\ I will retry rebasing automatically when the queue clears."
864+
PrStatusFailedBuild url -> case Pr.unfailedIntegratedPullRequestsBefore pr state of
865+
[] -> case url of
866+
Just url' -> format "The build failed: {}\n\
867+
\If this is the result of a flaky test, \
868+
\close and reopen the PR, then tag me again.\n\
869+
\Otherwise, push a new commit and tag me again." [url']
870+
-- This should probably never happen
871+
Nothing -> "The build failed, but GitHub did not provide an URL to the build failure."
872+
trainBefore -> format "Speculative build failed. \
873+
\ I will automatically retry after getting build results for {}."
874+
[prettyPullRequestIds trainBefore]
782875

783876
-- Leave a comment with the feedback from 'describeStatus' and set the
784877
-- 'needsFeedback' flag to 'False'.
@@ -829,3 +922,34 @@ pullRequestIdToText (PullRequestId prid) = Text.pack $ show prid
829922

830923
testBranch :: ProjectConfiguration -> PullRequestId -> Git.Branch
831924
testBranch config pullRequestId = Git.Branch $ Config.testBranch config <> "/" <> pullRequestIdToText pullRequestId
925+
926+
-- | Textual rendering of a list of 'PullRequestId's
927+
--
928+
-- >>> prettyPullRequestIds [PullRequestId 12, PullRequestId 60, PullRequestId 1337]
929+
-- "#12, #60 and #1337"
930+
prettyPullRequestIds :: [PullRequestId] -> Text
931+
prettyPullRequestIds = commaAnd . map prettyPullRequestId
932+
where
933+
prettyPullRequestId (PullRequestId n) = "#" <> Text.pack (show n)
934+
935+
-- | Pretty printing of a list of Text with comma and and.
936+
--
937+
-- >>> commaAnd ["a", "b", "c" :: Text]
938+
-- "a, b and c"
939+
commaAnd :: [Text] -> Text
940+
commaAnd [] = "none"
941+
commaAnd ss = case init ss of
942+
[] -> last ss
943+
is -> Text.intercalate ", " is <> " and " <> last ss
944+
945+
-- | Fold a list of unary functions by composition
946+
--
947+
-- Writing
948+
--
949+
-- > compose [f,g,h]
950+
--
951+
-- translates to
952+
--
953+
-- > f . g . h
954+
compose :: [a -> a] -> a -> a
955+
compose = foldr (.) id

0 commit comments

Comments
 (0)