aboutsummaryrefslogtreecommitdiffstats
path: root/app/History/IssueEvents.hs
blob: 176d660386720fdc303d2dbe89d129a2b3237d9a (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
module History.IssueEvents
  ( IssueEvents (..),
  )
where

import Data.Binary (Binary)
import Data.Function (on)
import Data.List
import Data.List.NonEmpty qualified as NE
import Data.Map qualified as M
import Data.Maybe (fromMaybe)
import Data.Ord (comparing)
import Data.Proxy (Proxy)
import GHC.Generics (Generic)
import Git qualified
import History.Plan (Id, Planable, Proto, assume, propagate, protoOf)
import History.Scramble (Scramble (..), getIssuesOfFile)
import Issue (Issue (..))
import IssueEvent (IssueEvent (..))
import IssueEvent qualified as E

data IssueEvents = IssueEvents
  { commitHash :: Git.CommitHash,
    issueEvents :: [E.IssueEvent]
  }
  deriving (Show, Generic, Binary)

instance Planable IssueEvents where
  type Id IssueEvents = Git.CommitHash
  type Proto IssueEvents = Scramble
  protoOf :: Proxy IssueEvents -> Git.CommitHash -> IO Scramble
  protoOf _ commitHash@Git.WorkingTree = do
    filesChanged <- Git.getFilesOf commitHash
    issues <- concat <$> mapM (getIssuesOfFile commitHash) filesChanged
    pure $
      Scramble
        { issues =
            M.unions
              [ M.singleton issue.id issue | issue <- issues
              ],
          ..
        }
  protoOf _ commitHash@(Git.Commit _) = do
    filesChanged <- Git.getChangedFilesOf commitHash
    issues <- concat <$> mapM (getIssuesOfFile commitHash) filesChanged
    pure $
      Scramble
        { issues =
            M.unions
              [ M.singleton issue.id issue | issue <- issues
              ],
          ..
        }

  assume :: Scramble -> IssueEvents
  assume Scramble {..} =
    IssueEvents
      { issueEvents =
          [ IssueCreated commitHash issue
            | issue <- M.elems issues
          ],
        ..
      }

  propagate ::
    [Git.CommitHash] ->
    IssueEvents ->
    Scramble ->
    IssueEvents
  propagate = propagateIssueEvents

-- | 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.
--
-- For the top/earlier commit, issue events are known. For the bottom/later commit, only the scramble is known.
--
-- The scramble is said to *witness* an issue, if its changed files contain the issue's file. Thus, in addition to the issues a scramble contains, it witnesses the issues that have been deleted in the scramble's commit.
--
-- 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.
--
-- 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.
propagateIssueEvents :: [Git.CommitHash] -> IssueEvents -> Scramble -> IssueEvents
propagateIssueEvents log topIssueEvents bottomScramble =
  IssueEvents
    { commitHash = bottomScramble.commitHash,
      issueEvents =
        sortOn logOrder $
          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.
                  concat
                    [ NE.init issueEvents ++ case NE.last issueEvents of
                        (IssueCreated commitHash issue) ->
                          if commitHash /= topCommitHash
                            then
                              [ IssueCreated commitHash issue,
                                IssueDeleted topCommitHash issue,
                                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"
                      | 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.
                      NE.init issueEvents ++ case NE.last issueEvents of
                        (IssueCreated commitHash issue) -> [IssueCreated commitHash issue]
                        _ -> error "bottom issues can only be created"
                      | 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.
                      NE.init issueEvents ++ case NE.last issueEvents of
                        (IssueCreated _ issue) -> [IssueCreated bottomCommitHash issue]
                        _ -> error "bottom issues can only be created"
                      | 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.
                      [ IssueDeleted topIssueEvents.commitHash bottomIssue,
                        IssueCreated bottomCommitHash bottomIssue
                      ]
                      | bottomIssue <- bottomIssues,
                        all ((`nsym` bottomIssue) . issue . NE.last) issueEventsPerIssue
                    ]
                ]
    }
  where
    groupPerIssue =
      map (NE.sortBy (comparing logOrder)) . NE.groupBy (sym `on` issue) . sortOn ((.id) . issue)

    topCommitHash = topIssueEvents.commitHash
    bottomCommitHash = bottomScramble.commitHash

    bottomIssues = M.elems bottomScramble.issues

    neq, sym, nsym :: Issue -> Issue -> Bool
    sym = (==) `on` (.id)
    nsym = (/=) `on` (.id)
    neq = (/=) `on` (.rawTextHash)

    commitHash (IssueChanged commitHash _ _) = commitHash
    commitHash (IssueCreated commitHash _) = commitHash
    commitHash (IssueDeleted commitHash _) = commitHash

    issue (IssueChanged _ _ issue) = issue
    issue (IssueCreated _ issue) = issue
    issue (IssueDeleted _ issue) = issue

    logOrder = fromMaybe (-1) . (`elemIndex` log) . commitHash