aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorLibravatar Alexander Foremny <aforemny@posteo.de>2024-03-26 07:10:05 +0100
committerLibravatar Alexander Foremny <aforemny@posteo.de>2024-03-26 07:24:02 +0100
commit22fd4b079dcf02a72fbd26c9d6733b5ec250ea53 (patch)
tree88d24d2b9e6e49e7af3671b718b457fe8971ed6e
parent1290402724684a47b5f36f1158b7fbc7b5406a09 (diff)
Previously, we tracked re-opening of issues by advancing the commit hash for scrambles that do not witness an issue. Advancing the commit hash for scrambles not witnessing an issue is obviously incorrect. To see that, consider a top/earlier commit that creates a new file with an issue in it. None of the bottom/later scrambles witness the issue. Hence, it would have been logged as being created in the bottom-most/latest commit instead of the top-most/earliest commit.
-rw-r--r--app/History/IssueEvents.hs137
-rw-r--r--app/History/Issues.hs4
-rw-r--r--app/History/Plan.hs4
-rw-r--r--app/History/Scramble.hs6
4 files changed, 90 insertions, 61 deletions
diff --git a/app/History/IssueEvents.hs b/app/History/IssueEvents.hs
index fc5feff..86cba7c 100644
--- a/app/History/IssueEvents.hs
+++ b/app/History/IssueEvents.hs
@@ -13,8 +13,8 @@ import Data.Maybe (fromMaybe)
import Data.Ord (comparing)
import Data.Proxy (Proxy)
import GHC.Generics (Generic)
-import History.Plan (Id, Planable, Proto, assume, propagate, protoOf)
-import History.Scramble (Scramble (..), getScramble)
+import History.Plan (Id, Planable, Proto, assume, postprocess, propagate, protoOf)
+import History.Scramble (Scramble (..), getScrambleOf)
import Issue (Issue (..))
import IssueEvent (IssueEvent (..))
import IssueEvent qualified as E
@@ -22,7 +22,7 @@ import IssueEvent qualified as E
data IssueEvents = IssueEvents
{ commitHash :: Backend.CommitHash,
issueEvents :: [E.IssueEvent],
- filesSeen :: [FilePath]
+ filesSeen :: M.Map FilePath Backend.CommitHash
}
deriving (Show, Generic, Binary)
@@ -30,7 +30,7 @@ instance Planable IssueEvents where
type Id IssueEvents = Backend.CommitHash
type Proto IssueEvents = Scramble
protoOf :: Proxy IssueEvents -> Backend.CommitHash -> IO Scramble
- protoOf _ = getScramble
+ protoOf _ = getScrambleOf
assume :: Scramble -> IssueEvents
assume Scramble {..} =
@@ -39,7 +39,11 @@ instance Planable IssueEvents where
[ IssueCreated commitHash issue
| issue <- M.elems issues
],
- filesSeen = filesChanged,
+ filesSeen =
+ M.unions
+ [ M.singleton issue.file commitHash
+ | issue <- M.elems issues
+ ],
..
}
@@ -50,6 +54,37 @@ instance Planable IssueEvents where
IssueEvents
propagate = propagateIssueEvents
+ postprocess :: [Backend.CommitHash] -> IssueEvents -> IssueEvents
+ postprocess log issueEvents =
+ issueEvents
+ { issueEvents =
+ sortOn logOrder . concatMap dropLastDeleted . groupPerIssue $
+ issueEvents.issueEvents
+ }
+ where
+ dropLastDeleted xs =
+ case NE.last xs of
+ IssueDeleted _ _ -> NE.init xs
+ _ -> NE.toList xs
+
+ groupPerIssue =
+ map (NE.sortBy (comparing logOrder))
+ . NE.groupBy (sym `on` issue)
+ . sortOn ((.id) . issue)
+
+ logOrder = fromMaybe (-1) . (`elemIndex` log) . commitHash
+
+ sym :: Issue -> Issue -> Bool
+ sym = (==) `on` (.id)
+
+ commitHash (IssueChanged commitHash _ _) = commitHash
+ commitHash (IssueCreated commitHash _) = commitHash
+ commitHash (IssueDeleted commitHash _) = commitHash
+
+ issue (IssueChanged _ _ issue) = issue
+ issue (IssueCreated _ issue) = issue
+ issue (IssueDeleted _ issue) = issue
+
-- | Propagates issue events from a top commit to a consecutive bottom commit.
--
-- Because we are building the history of issue events backwards, we use *top* and *bottom* to refer to the later and earlier commit within the Git history, respectively. We use *earlier* and *later* to refer to the top and bottom commits within the application of this function. In particular, top commits are processed earlier, and bottom commits are processed later.
@@ -60,23 +95,9 @@ instance Planable IssueEvents where
--
-- Because we are building the history from top/earlier to bottom/later commits, we have to assume that at any top/earlier commit, the issues present have been created in that commit. This function advances the issue's original commit as we learn about bottom/later commits from scrambles.
--
--- A scramble *advances* an issue's original commit if contains it or does not witness it. In particular, a scramble does NOT advance an issue's original commit, if it *just witnesses* it (ie. witnesses it, but does not contain it). To understand this, consider the following scenarios (A) and (B). Suppose the top/ earlier commit is `commit-c`, and the bottom/ later commit is `commit-a`. Between them, the commit `commit-b` is intermediary. Suppose for scenario (A) that `issue-1` is created in `commit-a`, deleted in `commit-b` and re-opened in `commit-c`. Suppose for scenario (B) that `issue-1` is originally created in `commit-c`. Then, at `commit-b` the following holds true:
---
--- - The issue `issue-1` has been created in `commit-c`, because it is present.
--- - The issue `issue-1 is not present in `commit-b`.
--- - The scramble of `commit-b` can witness `issue-1` in both scenarios (A), (B) even though it does not contain it.
+-- Suppose an issue `1` is present since a top commit `b`, and we encounter a scramble that witnesses the issue at commit `a`. Has issue `1` originally been created in commit `b`, or has it been closed in commit `a` and re-opened in commit `b`? Answering that question depends on later information, ie. whether issue `1` is created in a later commit. In the first case, it would be correct to simply not advance the original commit of issue `a`. In the second case, it would be correct to create an event that the issue has been deleted. Not advancing the original commit of issue `a` leaves us no information to answer the question later. Thus, we create an event that the issue has been deleted.
--
--- Thus, we cannot decide at `commit-b` whether `issue-1` has been initially created in the top/ earlier commit `commit-c`, or whether is has been re-opened in `commit-c`. We need the information of presence in `commit-a` to decide this.
---
--- The most confusing edge case it the re-opening of issues. Suppose `issue-1` has been created in `commit-a`, deleted in `commit-b` and re-opened in `commit-c`. Contrast this with the scenario that `issue-1` has initially been created in `commit-c`. Observe the following as we propagate events from `commmit-c` to `commit-a`:
---
--- - At `commit-c`: `issue-1` is present in both scenarios, thus it is initially tracked as "created" in `commit-c`.
--- - At `commit-b`: `issue-1` is NOT present in both scenarios. Note that the scramble can witness `issue-1` in either cases.
--- - At `commit-a`: `issue-1` is present in the first scenario, but not in the second.
---
--- So, in the case `issue-1` has been re-opened, we cannot track its deletion at `commit-b`, because whether it was re-opened or originally created at `commit-b` depends on whether `issue-1` is present in the bottom `commit-a`, that we process only later. Thus, the scramble of commit `commit-b` cannot safely advance the issue's original commit, and we use this information to track re-opening of commits at later commits.
---
--- Note that in the whole process, issue change events and issue deletion events can never be bottom-most/latest events, as they would depend on information not yet known, ie. the first commit can neither change nor delete an issue.
+-- This is incorrect for issues that have not been re-opened. Finally, those issues will have a chain of issue events that end in a deletion event, and we post-process issue events to remove precisely those.
propagateIssueEvents :: [Backend.CommitHash] -> IssueEvents -> Scramble -> IssueEvents
propagateIssueEvents log topIssueEvents bottomScramble =
IssueEvents
@@ -86,76 +107,82 @@ propagateIssueEvents log topIssueEvents bottomScramble =
let issueEventsPerIssue =
groupPerIssue topIssueEvents.issueEvents
in concat
- [ -- CASE 1. The issue is present in the top/earlier history and bottom/later scramble. We can safely advance the issue's original commit.
+ [ -- CASE 1. The issue is present in the top/earlier history and bottom/later scramble. We advance the issue's original commit, and track any change if there was any.
concat
[ NE.init issueEvents ++ case NE.last issueEvents of
- (IssueCreated commitHash issue) ->
- if commitHash /= topCommitHash
- then
- [ IssueCreated commitHash issue,
- IssueDeleted topCommitHash issue {closed = True},
- IssueCreated bottomCommitHash bottomIssue
+ IssueCreated commitHash _ ->
+ concat
+ [ if topIssue `neq` bottomIssue
+ then
+ [ IssueChanged commitHash bottomIssue topIssue
+ ]
+ else [],
+ [ IssueCreated bottomCommitHash bottomIssue
]
- else
- concat
- [ if topIssue `neq` bottomIssue
- then [IssueChanged commitHash bottomIssue issue]
- else [],
- [IssueCreated bottomCommitHash bottomIssue]
- ]
- _ -> error "bottom issues can only be created"
+ ]
+ issueEvent@(IssueDeleted _ _) ->
+ [ issueEvent,
+ IssueCreated bottomCommitHash bottomIssue
+ ]
+ issueEvent -> [issueEvent]
| issueEvents <- issueEventsPerIssue,
let topIssue = issue (NE.last issueEvents),
bottomIssue <- bottomIssues,
bottomIssue `sym` topIssue
],
concat
- [ -- CASE 2. The issue is present in the top/earlier history, not contained in the bottom/later scramble, but witnessed by the bottom/later scramble. We cannot safely advance the issue's original commit.
+ [ -- CASE 2. The issue is present in the top/earlier history, not contained in the bottom/later scramble, but witnessed by the bottom/later scramble. We track a deletion, because we don't know whether or not the issue has been re-opened (see above).
NE.init issueEvents ++ case NE.last issueEvents of
- (IssueCreated commitHash issue) -> [IssueCreated commitHash issue]
- _ -> error "bottom issues can only be created"
+ issueEvent@(IssueCreated _ issue) ->
+ [ issueEvent,
+ IssueDeleted bottomCommitHash issue {closed = True}
+ ]
+ issueEvent -> [issueEvent]
| issueEvents <- issueEventsPerIssue,
let topIssue = issue (NE.last issueEvents),
all (`nsym` topIssue) bottomIssues,
topIssue.file `elem` bottomScramble.filesChanged
],
concat
- [ -- CASE 3. The issue is present in the top/earlier history, but not witnessed by the bottom/later scramble. It is safe to advance the issue's commit hash.
+ [ -- CASE 3. The issue is present in the top/earlier history, but not witnessed by the bottom/later scramble. We keep the issue event unchanged.
NE.init issueEvents ++ case NE.last issueEvents of
- (IssueCreated _ issue) -> [IssueCreated bottomCommitHash issue]
- _ -> error "bottom issues can only be created"
+ issueEvent -> [issueEvent]
| issueEvents <- issueEventsPerIssue,
let topIssue = issue (NE.last issueEvents),
all (`nsym` topIssue) bottomIssues,
not (topIssue.file `elem` bottomScramble.filesChanged)
],
concat
- [ -- CASE 4. The issue it not present in the top/earlier history, but contained in the bottom scramble. It had to be deleted by the top/ earlier commit.
- ( if bottomIssue.file `elem` topIssueEvents.filesSeen
- then
- [ IssueDeleted topIssueEvents.commitHash bottomIssue {closed = True},
- IssueCreated bottomCommitHash bottomIssue
- ]
- else
- [ IssueCreated bottomCommitHash bottomIssue
- ]
- )
+ [ -- CASE 4. The issue it not present in the top/earlier history, but contained in the bottom scramble. If we have seen the issue's file earlier, this means the issue had to be deleted at the earlier commit. If the file has not been seen earlier, we plainly track the issue's creation.
+ concat
+ [ case M.lookup bottomIssue.file topIssueEvents.filesSeen of
+ Nothing -> []
+ Just seenCommitHash ->
+ [IssueDeleted seenCommitHash bottomIssue {closed = True}],
+ [IssueCreated bottomCommitHash bottomIssue]
+ ]
| bottomIssue <- bottomIssues,
all ((`nsym` bottomIssue) . issue . NE.last) issueEventsPerIssue
]
],
- filesSeen = nub (topIssueEvents.filesSeen ++ bottomScramble.filesChanged)
+ filesSeen =
+ M.union
+ ( M.unions
+ [ M.singleton file bottomScramble.commitHash
+ | file <- bottomScramble.filesChanged
+ ]
+ )
+ topIssueEvents.filesSeen
}
where
groupPerIssue =
map (NE.sortBy (comparing logOrder))
. NE.groupBy (sym `on` issue)
. sortOn ((.id) . issue)
+
logOrder = fromMaybe (-1) . (`elemIndex` log) . commitHash
- topCommitHash = topIssueEvents.commitHash
bottomCommitHash = bottomScramble.commitHash
-
bottomIssues = M.elems bottomScramble.issues
neq, sym, nsym :: Issue -> Issue -> Bool
diff --git a/app/History/Issues.hs b/app/History/Issues.hs
index 09f51dd..49bb893 100644
--- a/app/History/Issues.hs
+++ b/app/History/Issues.hs
@@ -12,7 +12,7 @@ import Data.Proxy (Proxy)
import Data.Text qualified as T
import GHC.Generics (Generic)
import History.Plan (Id, Planable, Proto, assume, propagate, protoOf)
-import History.Scramble (Scramble (..), getScramble)
+import History.Scramble (Scramble (..), getScrambleOf)
import Issue qualified as I
data Issues = Issues
@@ -26,7 +26,7 @@ instance Planable Issues where
type Id Issues = Backend.CommitHash
type Proto Issues = Scramble
protoOf :: Proxy Issues -> Backend.CommitHash -> IO Scramble
- protoOf _ = getScramble
+ protoOf _ = getScrambleOf
assume :: Scramble -> Issues
assume (Scramble {..}) = Issues {filesSeen = filesChanged, ..}
diff --git a/app/History/Plan.hs b/app/History/Plan.hs
index 3dec391..d7984c6 100644
--- a/app/History/Plan.hs
+++ b/app/History/Plan.hs
@@ -41,6 +41,8 @@ class Planable output where
protoOf :: Proxy output -> Id output -> IO (Proto output)
assume :: Proto output -> output
propagate :: [Id output] -> output -> Proto output -> output
+ postprocess :: [Id output] -> output -> output
+ postprocess _ = id
data Plan output = Plan (NE.NonEmpty (Id output)) [Task output]
@@ -102,7 +104,7 @@ realise plan@(Plan ids tasks) = do
output <- atomically $ do
maybe retry pure . M.lookup id . (.outputs) =<< readTVar stateT
killThread tid
- pure output
+ pure (postprocess (NE.toList ids) output)
step ::
(Ord (Id output), Planable output) =>
diff --git a/app/History/Scramble.hs b/app/History/Scramble.hs
index ca4f4f8..017523a 100644
--- a/app/History/Scramble.hs
+++ b/app/History/Scramble.hs
@@ -1,6 +1,6 @@
module History.Scramble
( Scramble (..),
- getScramble,
+ getScrambleOf,
getIssuesOfFile,
fromComment,
)
@@ -35,8 +35,8 @@ data Scramble = Scramble
}
deriving (Show, Binary, Generic)
-getScramble :: Backend.CommitHash -> IO Scramble
-getScramble commitHash = do
+getScrambleOf :: Backend.CommitHash -> IO Scramble
+getScrambleOf commitHash = do
filesChanged <- Backend.getChangedFilesOf commitHash
issues <- concat <$> mapM (getIssuesOfFile commitHash) filesChanged
pure $