mirror of
https://github.com/github/semantic.git
synced 2024-12-21 22:01:46 +03:00
Define a function to compute the table of contents for a diff given some relevance predicate.
This commit is contained in:
parent
bf2a12cbf4
commit
0534c3303d
@ -1,8 +1,9 @@
|
||||
{-# LANGUAGE RankNTypes #-}
|
||||
module Renderer.TOC (toc, diffTOC, JSONSummary(..), Summarizable(..), isErrorSummary) where
|
||||
|
||||
import Category as C
|
||||
import Data.Aeson
|
||||
import Data.Align (sequenceL)
|
||||
import Data.Align (crosswalk, sequenceL)
|
||||
import Data.Functor.Both hiding (fst, snd)
|
||||
import qualified Data.Functor.Both as Both
|
||||
import Data.Text (toLower)
|
||||
@ -52,6 +53,21 @@ data Summarizable
|
||||
}
|
||||
deriving (Eq, Show)
|
||||
|
||||
data Entry a
|
||||
= Unchanged a
|
||||
| Changed (Either a (Patch a))
|
||||
deriving (Eq, Show)
|
||||
|
||||
tableOfContentsBy :: Traversable f => (forall b. TermF f (Record fields) b -> Bool) -> Diff f (Record fields) -> [Entry (Record fields)]
|
||||
tableOfContentsBy isRelevant = fromMaybe [] . iter alg . fmap (Just . fmap (Changed . Right) . crosswalk (cata termAlgebra))
|
||||
where alg r | isRelevant (first Both.snd r)
|
||||
, annotation <- Both.snd (headF r) = Just (maybe [Unchanged annotation] (wrapList annotation) (fold r))
|
||||
| otherwise = fold r
|
||||
wrapList a es | null es = [Changed (Left a)]
|
||||
| otherwise = es
|
||||
termAlgebra r | isRelevant r = [headF r]
|
||||
| otherwise = fold r
|
||||
|
||||
toc :: HasDefaultFields fields => Both SourceBlob -> Diff (Syntax Text) (Record fields) -> Summaries
|
||||
toc blobs diff = Summaries changes errors
|
||||
where
|
||||
|
Loading…
Reference in New Issue
Block a user