1
1
mirror of https://github.com/github/semantic.git synced 2024-12-26 08:25:19 +03:00
semantic/src/Renderer/TOC.hs

170 lines
7.5 KiB
Haskell
Raw Normal View History

{-# LANGUAGE RankNTypes #-}
2017-05-10 18:56:06 +03:00
module Renderer.TOC
( toc
, diffTOC
, JSONSummary(..)
, Summarizable(..)
, isErrorSummary
, tableOfContentsBy
) where
2017-01-23 19:22:51 +03:00
2017-01-23 22:12:05 +03:00
import Category as C
import Data.Aeson
import Data.Align (crosswalk)
2017-01-23 22:12:05 +03:00
import Data.Functor.Both hiding (fst, snd)
2017-01-24 00:59:47 +03:00
import qualified Data.Functor.Both as Both
import Data.Text (toLower)
2017-01-23 19:22:51 +03:00
import Data.Record
2017-01-23 22:12:05 +03:00
import Diff
2017-01-23 19:22:51 +03:00
import Info
2017-01-23 22:12:05 +03:00
import Prologue
import Renderer.Summary (Summaries(..))
2017-01-23 22:12:05 +03:00
import qualified Data.List as List
import qualified Data.Map as Map hiding (null)
import Source hiding (null)
2017-01-23 22:12:05 +03:00
import Syntax as S
import Term
import Patch
2017-01-23 20:16:59 +03:00
data JSONSummary = JSONSummary { info :: Summarizable }
| ErrorSummary { error :: Text, errorSpan :: SourceSpan }
2017-01-23 22:12:05 +03:00
deriving (Generic, Eq, Show)
instance ToJSON JSONSummary where
2017-05-09 18:16:17 +03:00
toJSON (JSONSummary Summarizable{..}) = object [ "changeType" .= summarizableChangeType, "category" .= toCategoryName summarizableCategory, "term" .= summarizableTermName, "span" .= summarizableSourceSpan ]
toJSON ErrorSummary{..} = object [ "error" .= error, "span" .= errorSpan ]
2017-01-23 22:12:05 +03:00
isErrorSummary :: JSONSummary -> Bool
2017-01-23 22:12:05 +03:00
isErrorSummary ErrorSummary{} = True
isErrorSummary _ = False
2017-01-23 20:16:59 +03:00
2017-05-09 18:02:15 +03:00
data DiffInfo = DiffInfo
2017-05-09 18:08:18 +03:00
{ infoCategory :: Maybe Category
2017-05-09 18:02:15 +03:00
, infoName :: Text
, infoSpan :: SourceSpan
}
2017-05-08 23:00:29 +03:00
deriving (Eq, Show)
2017-01-23 20:16:59 +03:00
2017-05-09 18:13:17 +03:00
data TOCSummary a = TOCSummary
{ summaryPatch :: Patch a
, parentInfo :: Maybe Summarizable
}
2017-05-09 17:07:21 +03:00
deriving (Eq, Functor, Show, Generic)
2017-01-23 20:16:59 +03:00
data Summarizable
= Summarizable
{ summarizableCategory :: Category
, summarizableTermName :: Text
, summarizableSourceSpan :: SourceSpan
, summarizableChangeType :: Text
}
deriving (Eq, Show)
2017-05-10 17:24:43 +03:00
-- | An entry in a table of contents.
data Entry a
= Unchanged a -- ^ An entry for an unchanged portion of a diff (i.e. a diff node not containing any patches).
| Changed a -- ^ An entry for a node containing changes.
| Patched (Patch a) -- ^ An entry for a change occurring inside a 'Patch'.
deriving (Eq, Show)
2017-05-10 17:21:00 +03:00
-- | Compute a table of contents for a diff characterized by a function mapping relevant nodes onto values in Maybe.
tableOfContentsBy :: Traversable f
=> (forall b. TermF f annotation b -> Maybe a) -- ^ A function mapping relevant nodes onto values in Maybe.
-> Diff f annotation -- ^ The diff to compute the table of contents for.
-> [Entry a] -- ^ A list of entries for relevant changed and unchanged nodes in the diff.
tableOfContentsBy selector = fromMaybe [] . iter diffAlgebra . fmap (Just . fmap Patched . crosswalk (cata termAlgebra))
where diffAlgebra r | Just a <- selector (first Both.snd r) = Just (maybe [Unchanged a] (maybe [Changed a] (uncurry (:)) . uncons) (fold r))
2017-05-10 17:00:20 +03:00
| otherwise = fold r
termAlgebra r | Just a <- selector r = [a]
| otherwise = fold r
toc :: HasDefaultFields fields => Both SourceBlob -> Diff (Syntax Text) (Record fields) -> Summaries
toc blobs diff = Summaries changes errors
2017-01-23 22:12:05 +03:00
where
changes = if null changes' then mempty else Map.singleton summaryKey (toJSON <$> changes')
errors = if null errors' then mempty else Map.singleton summaryKey (toJSON <$> errors')
(errors', changes') = List.partition isErrorSummary summaries
summaries = diffTOC blobs diff
2017-01-23 20:16:59 +03:00
summaryKey = toS $ case runJoin (path <$> blobs) of
(before, after) | null before -> after
| null after -> before
| before == after -> after
| otherwise -> before <> " -> " <> after
2017-03-31 23:48:06 +03:00
2017-05-08 18:36:45 +03:00
diffTOC :: HasDefaultFields fields => Both SourceBlob -> Diff (Syntax Text) (Record fields) -> [JSONSummary]
diffTOC blobs = removeDupes . diffToTOCSummaries >=> toJSONSummaries
2017-01-23 22:12:05 +03:00
where
2017-01-24 20:13:59 +03:00
removeDupes :: [TOCSummary DiffInfo] -> [TOCSummary DiffInfo]
removeDupes = foldl' go []
where
go xs x | (_, _ : _) <- find exactMatch x xs = xs
2017-05-09 17:06:14 +03:00
| (front, TOCSummary _ (Just info) : back) <- find similarMatch x xs =
front <> (x { parentInfo = Just (info { summarizableChangeType = "modified" }) } : back)
| otherwise = xs <> [x]
find p x = List.break (p x)
exactMatch a b = parentInfo a == parentInfo b
similarMatch a b = case (parentInfo a, parentInfo b) of
2017-05-08 18:31:30 +03:00
(Just (Summarizable catA nameA _ _), Just (Summarizable catB nameB _ _)) -> catA == catB && toLower nameA == toLower nameB
(_, _) -> False
2017-01-24 20:13:59 +03:00
diffToTOCSummaries = para $ \diff -> case diff of
Free (Join (_, annotation) :< syntax)
| Just identifier <- identifierFor diffSource diffUnwrap syntax ->
foldMap (fmap (contextualize (Summarizable (category annotation) identifier (sourceSpan annotation) "modified")) . snd) syntax
| otherwise -> foldMap snd syntax
Pure patch -> fmap summarize (sequenceA (runBothWith mapPatch (toInfo . source <$> blobs) patch))
2017-05-09 18:08:18 +03:00
summarize patch = TOCSummary patch (infoCategory >>= summarizable)
2017-05-09 18:02:15 +03:00
where DiffInfo{..} = afterOrBefore patch
2017-05-09 18:08:18 +03:00
summarizable category = Summarizable category infoName infoSpan (patchType patch) <$ find (category ==) [C.Function, C.Method, C.SingletonMethod]
2017-05-09 00:39:21 +03:00
contextualize info summary = summary { parentInfo = Just (fromMaybe info (parentInfo summary)) }
2017-05-09 19:44:02 +03:00
diffSource diff = case runFree diff of
Free (Join (_, a) :< r) -> termFSource (source (Both.snd blobs)) (a :< r)
Pure a -> termFSource (source (Both.snd blobs)) (runCofree (afterOrBefore a))
toInfo :: HasDefaultFields fields => Source -> Term (Syntax Text) (Record fields) -> [DiffInfo]
toInfo source = para $ \ (annotation :< syntax) -> let termName = fromMaybe (textFor source (byteRange annotation)) (identifierFor (termFSource source . runCofree) (Just . tailF . runCofree) syntax) in case syntax of
S.ParseError{} -> [DiffInfo Nothing termName (sourceSpan annotation)]
S.Indexed{} -> foldMap snd syntax
S.Fixed{} -> foldMap snd syntax
S.Commented{} -> foldMap snd syntax
S.AnonymousFunction{} -> [DiffInfo (Just C.AnonymousFunction) termName (sourceSpan annotation)]
_ -> [DiffInfo (Just (category annotation)) termName (sourceSpan annotation)]
identifierFor :: (a -> Text) -> (a -> Maybe (Syntax Text a)) -> Syntax Text (a, b) -> Maybe Text
identifierFor getSource unwrap syntax = case syntax of
S.Function (identifier, _) _ _ -> Just $ getSource identifier
S.Method _ (identifier, _) Nothing _ _ -> Just $ getSource identifier
S.Method _ (identifier, _) (Just (receiver, _)) _ _
| Just (S.Indexed [receiverParams]) <- unwrap receiver
, Just (S.ParameterDecl (Just ty) _) <- unwrap receiverParams -> Just $ "(" <> getSource ty <> ") " <> getSource identifier
| otherwise -> Just $ getSource receiver <> "." <> getSource identifier
_ -> Nothing
diffUnwrap :: Diff f (Record fields) -> Maybe (f (Diff f (Record fields)))
diffUnwrap diff = case runFree diff of
Free (_ :< syntax) -> Just syntax
_ -> Nothing
termFSource :: HasField fields Range => Source -> TermF f (Record fields) a -> Text
termFSource source = toText . flip Source.slice source . byteRange . headF
textFor :: Source -> Range -> Text
textFor source = toText . flip Source.slice source
toJSONSummaries :: TOCSummary DiffInfo -> [JSONSummary]
2017-05-09 18:02:15 +03:00
toJSONSummaries TOCSummary{..} = case infoCategory of
2017-05-09 18:08:18 +03:00
Nothing -> [ErrorSummary infoName infoSpan]
2017-05-09 18:02:15 +03:00
_ -> maybe [] (pure . JSONSummary) parentInfo
where DiffInfo{..} = afterOrBefore summaryPatch
2017-01-23 22:12:05 +03:00
-- The user-facing category name
toCategoryName :: Category -> Text
2017-03-28 22:32:45 +03:00
toCategoryName category = case category of
2017-02-23 07:05:20 +03:00
C.SingletonMethod -> "Method"
c -> show c