2017-01-23 20:16:59 +03:00
|
|
|
{-# LANGUAGE ScopedTypeVariables #-}
|
2017-01-26 20:45:36 +03:00
|
|
|
module Renderer.TOC (toc) 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.Functor.Both hiding (fst, snd)
|
2017-01-24 00:59:47 +03:00
|
|
|
import qualified Data.Functor.Both as Both
|
2017-02-14 03:15:38 +03:00
|
|
|
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
|
2017-02-11 00:44:09 +03:00
|
|
|
import Range
|
2017-01-23 22:12:05 +03:00
|
|
|
import qualified Data.List as List
|
|
|
|
import qualified Data.Map as Map hiding (null)
|
|
|
|
import Renderer
|
2017-02-10 01:10:16 +03:00
|
|
|
import Source hiding (null)
|
2017-01-23 22:12:05 +03:00
|
|
|
import Syntax as S
|
|
|
|
import Term
|
2017-01-24 01:26:43 +03:00
|
|
|
import Patch
|
2017-01-23 20:16:59 +03:00
|
|
|
|
2017-01-24 22:16:22 +03:00
|
|
|
data JSONSummary = JSONSummary { info :: Summarizable }
|
2017-01-23 23:58:20 +03:00
|
|
|
| ErrorSummary { error :: Text, errorSpan :: SourceSpan }
|
2017-01-23 22:12:05 +03:00
|
|
|
deriving (Generic, Eq, Show)
|
|
|
|
|
2017-01-24 00:33:07 +03:00
|
|
|
instance ToJSON JSONSummary where
|
2017-01-24 22:16:22 +03:00
|
|
|
toJSON JSONSummary{..} = object $ case info of
|
2017-01-25 01:20:22 +03:00
|
|
|
InSummarizable{..} -> [ "changeType" .= ("modified" :: Text), "category" .= (show parentCategory :: Text), "term" .= parentTermName, "span" .= parentSourceSpan ]
|
|
|
|
Summarizable{..} -> [ "changeType" .= summarizableChangeType, "category" .= (show summarizableCategory :: Text), "term" .= summarizableTermName, "span" .= summarizableSourceSpan ]
|
2017-01-24 22:16:22 +03:00
|
|
|
NotSummarizable -> panic "NotSummarizable should have been pruned"
|
2017-01-23 23:58:20 +03:00
|
|
|
toJSON ErrorSummary{..} = object [ "error" .= error, "span" .= errorSpan ]
|
2017-01-23 22:12:05 +03:00
|
|
|
|
2017-01-24 00:33:07 +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-01-24 01:26:43 +03:00
|
|
|
data DiffInfo = LeafInfo { leafCategory :: Category, termName :: Text, leafSourceSpan :: SourceSpan }
|
2017-01-23 20:16:59 +03:00
|
|
|
| BranchInfo { branches :: [ DiffInfo ], branchCategory :: Category }
|
2017-01-23 23:58:20 +03:00
|
|
|
| ErrorInfo { infoSpan :: SourceSpan, termName :: Text }
|
2017-01-23 20:16:59 +03:00
|
|
|
deriving (Eq, Show)
|
|
|
|
|
|
|
|
data TOCSummary a = TOCSummary {
|
2017-01-25 21:45:56 +03:00
|
|
|
summaryPatch :: Patch a,
|
2017-01-24 22:16:22 +03:00
|
|
|
parentInfo :: Summarizable
|
|
|
|
} deriving (Eq, Functor, Show, Generic)
|
2017-01-23 20:16:59 +03:00
|
|
|
|
2017-01-24 22:16:22 +03:00
|
|
|
data Summarizable = Summarizable { summarizableCategory :: Category, summarizableTermName :: Text, summarizableSourceSpan :: SourceSpan, summarizableChangeType :: Text }
|
|
|
|
| InSummarizable { parentCategory :: Category, parentTermName :: Text, parentSourceSpan :: SourceSpan }
|
|
|
|
| NotSummarizable
|
2017-01-24 00:33:07 +03:00
|
|
|
deriving (Eq, Show)
|
|
|
|
|
2017-01-24 22:16:22 +03:00
|
|
|
data SummarizableTerm a = SummarizableTerm a | NotSummarizableTerm a
|
|
|
|
|
2017-01-23 22:12:05 +03:00
|
|
|
toc :: (DefaultFields fields) => Renderer (Record fields)
|
|
|
|
toc blobs diff = TOCOutput $ Map.fromList [
|
|
|
|
("changes", changes),
|
|
|
|
("errors", errors)
|
|
|
|
]
|
|
|
|
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
|
|
|
|
summaryKey = toSummaryKey (path <$> blobs)
|
|
|
|
summaries = diffTOC blobs diff
|
2017-01-23 20:16:59 +03:00
|
|
|
|
2017-01-24 00:33:07 +03:00
|
|
|
diffTOC :: (StringConv leaf Text, DefaultFields fields) => Both SourceBlob -> SyntaxDiff leaf fields -> [JSONSummary]
|
2017-02-14 04:30:33 +03:00
|
|
|
diffTOC blobs diff = removeDupes (diffToTOCSummaries (source <$> blobs) diff) >>= toJSONSummaries
|
2017-01-23 22:12:05 +03:00
|
|
|
where
|
2017-01-24 20:13:59 +03:00
|
|
|
removeDupes :: [TOCSummary DiffInfo] -> [TOCSummary DiffInfo]
|
2017-02-14 19:27:00 +03:00
|
|
|
removeDupes = foldl' (\xs x -> case (x `anyDuplicateSummary` xs, x `findSimilarSummaryIndex` xs) of
|
2017-02-14 04:18:25 +03:00
|
|
|
(True, Nothing) -> xs
|
|
|
|
(False, Nothing) -> xs <> [x]
|
|
|
|
(_, Just n) ->
|
|
|
|
let
|
2017-02-14 04:30:33 +03:00
|
|
|
(a, existingItem : b) = List.splitAt n xs
|
|
|
|
(Summarizable category name sourceSpan _) = parentInfo existingItem
|
|
|
|
replacement = x { parentInfo = Summarizable category name sourceSpan "modified" }
|
2017-02-14 04:18:25 +03:00
|
|
|
in
|
2017-02-14 04:30:33 +03:00
|
|
|
a <> (replacement : b)
|
2017-02-14 04:18:25 +03:00
|
|
|
) []
|
2017-02-14 19:27:00 +03:00
|
|
|
anyDuplicateSummary a = List.any (\b -> parentInfo a == parentInfo b)
|
2017-02-14 04:18:25 +03:00
|
|
|
findSimilarSummaryIndex summary = List.findIndex (isSimilarSummary summary)
|
|
|
|
isSimilarSummary a b = case (parentInfo a, parentInfo b) of
|
2017-02-14 19:27:00 +03:00
|
|
|
(Summarizable catA nameA _ _, Summarizable catB nameB _ _) -> catA == catB && toLower nameA == toLower nameB
|
2017-02-14 04:18:25 +03:00
|
|
|
(_, _) -> False
|
2017-01-24 20:13:59 +03:00
|
|
|
|
2017-02-10 19:21:24 +03:00
|
|
|
diffToTOCSummaries :: (StringConv leaf Text, DefaultFields fields) => Both Source -> SyntaxDiff leaf fields -> [TOCSummary DiffInfo]
|
2017-01-23 22:12:05 +03:00
|
|
|
diffToTOCSummaries sources = para $ \diff ->
|
|
|
|
let
|
2017-01-24 00:59:47 +03:00
|
|
|
diff' = free (Prologue.fst <$> diff)
|
2017-01-24 22:16:22 +03:00
|
|
|
patch' = mapPatch (termToDiffInfo beforeSource) (termToDiffInfo afterSource)
|
2017-01-23 22:12:05 +03:00
|
|
|
(beforeSource, afterSource) = runJoin sources
|
2017-01-24 22:16:22 +03:00
|
|
|
in case diff of
|
|
|
|
(Free (_ :< syntax)) -> mapToInSummarizable sources diff' (toList syntax >>= snd)
|
|
|
|
(Pure patch) -> toTOCSummaries (patch' patch)
|
|
|
|
|
|
|
|
-- Mark which leaves are summarizable.
|
|
|
|
toTOCSummaries :: Patch DiffInfo -> [TOCSummary DiffInfo]
|
2017-01-24 23:58:17 +03:00
|
|
|
toTOCSummaries patch = case afterOrBefore patch of
|
2017-01-26 23:07:18 +03:00
|
|
|
Just diffInfo -> toTOCSummaries' patch diffInfo
|
2017-01-24 23:58:17 +03:00
|
|
|
Nothing -> panic "No diff"
|
2017-01-24 22:16:22 +03:00
|
|
|
where
|
2017-01-26 23:07:18 +03:00
|
|
|
toTOCSummaries' patch' diffInfo = case diffInfo of
|
|
|
|
ErrorInfo{..} -> pure $ TOCSummary patch' NotSummarizable
|
|
|
|
BranchInfo{..} -> join $ zipWith toTOCSummaries' (flattenPatch patch') branches
|
|
|
|
LeafInfo{..} -> pure . TOCSummary patch' $ case leafCategory of
|
|
|
|
C.Function -> Summarizable leafCategory termName leafSourceSpan (patchType patch')
|
|
|
|
C.Method -> Summarizable leafCategory termName leafSourceSpan (patchType patch')
|
2017-01-24 22:16:22 +03:00
|
|
|
_ -> NotSummarizable
|
|
|
|
|
2017-01-26 23:07:18 +03:00
|
|
|
flattenPatch :: Patch DiffInfo -> [Patch DiffInfo]
|
|
|
|
flattenPatch = \case
|
|
|
|
Replace i1 i2 -> zipWith Replace (toLeafInfos' i1) (toLeafInfos' i2)
|
|
|
|
Insert info -> Insert <$> toLeafInfos' info
|
|
|
|
Delete info -> Delete <$> toLeafInfos' info
|
|
|
|
|
|
|
|
toLeafInfos' :: DiffInfo -> [DiffInfo]
|
|
|
|
toLeafInfos' BranchInfo{..} = branches >>= toLeafInfos'
|
|
|
|
toLeafInfos' leaf = [leaf]
|
|
|
|
|
2017-02-10 19:21:24 +03:00
|
|
|
mapToInSummarizable :: forall leaf fields. DefaultFields fields => Both Source -> SyntaxDiff leaf fields -> [TOCSummary DiffInfo] -> [TOCSummary DiffInfo]
|
2017-01-24 22:16:22 +03:00
|
|
|
mapToInSummarizable sources diff children = case (beforeTerm diff, afterTerm diff) of
|
|
|
|
(_, Just diff') -> mapToInSummarizable' (Both.snd sources) diff' <$> children
|
|
|
|
(Just diff', _) -> mapToInSummarizable' (Both.fst sources) diff' <$> children
|
|
|
|
(Nothing, Nothing) -> []
|
|
|
|
where
|
2017-02-10 19:21:24 +03:00
|
|
|
mapToInSummarizable' :: Source -> SyntaxTerm leaf fields -> TOCSummary DiffInfo -> TOCSummary DiffInfo
|
2017-01-24 22:16:22 +03:00
|
|
|
mapToInSummarizable' source term summary =
|
|
|
|
case (parentInfo summary, summarizable term) of
|
|
|
|
(NotSummarizable, SummarizableTerm _) ->
|
2017-02-13 23:53:20 +03:00
|
|
|
summary { parentInfo = InSummarizable (category (extract term)) (toTermName 0 source term) (Info.sourceSpan (extract term)) }
|
2017-01-24 22:16:22 +03:00
|
|
|
(_, _) -> summary
|
|
|
|
|
|
|
|
summarizable :: ComonadCofree (Syntax t) w => w a -> SummarizableTerm (w a)
|
|
|
|
summarizable term = go (unwrap term) term
|
|
|
|
where go = \case
|
|
|
|
S.Method{} -> SummarizableTerm
|
|
|
|
S.Function{} -> SummarizableTerm
|
|
|
|
_ -> NotSummarizableTerm
|
|
|
|
|
|
|
|
toJSONSummaries :: TOCSummary DiffInfo -> [JSONSummary]
|
2017-01-25 21:45:56 +03:00
|
|
|
toJSONSummaries TOCSummary{..} = case afterOrBefore summaryPatch of
|
2017-01-24 23:58:17 +03:00
|
|
|
Just diffInfo -> toJSONSummaries' diffInfo
|
|
|
|
Nothing -> panic "No diff"
|
2017-01-24 22:16:22 +03:00
|
|
|
where
|
|
|
|
toJSONSummaries' = \case
|
|
|
|
ErrorInfo{..} -> pure $ ErrorSummary termName infoSpan
|
|
|
|
BranchInfo{..} -> branches >>= toJSONSummaries'
|
2017-01-24 22:25:44 +03:00
|
|
|
LeafInfo{..} -> case parentInfo of
|
|
|
|
NotSummarizable -> []
|
|
|
|
_ -> pure $ JSONSummary parentInfo
|
2017-01-23 22:12:05 +03:00
|
|
|
|
2017-02-10 19:21:24 +03:00
|
|
|
termToDiffInfo :: forall leaf fields. (StringConv leaf Text, DefaultFields fields) => Source -> SyntaxTerm leaf fields -> DiffInfo
|
2017-02-10 22:18:55 +03:00
|
|
|
termToDiffInfo source term = case unwrap term of
|
2017-01-23 22:12:05 +03:00
|
|
|
S.Indexed children -> BranchInfo (termToDiffInfo' <$> children) (category $ extract term)
|
|
|
|
S.Fixed children -> BranchInfo (termToDiffInfo' <$> children) (category $ extract term)
|
|
|
|
S.AnonymousFunction _ _ -> LeafInfo C.AnonymousFunction (toTermName' term) (getField $ extract term)
|
|
|
|
S.Commented cs leaf -> BranchInfo (termToDiffInfo' <$> cs <> maybeToList leaf) (category $ extract term)
|
2017-01-26 20:48:03 +03:00
|
|
|
S.ParseError _ -> ErrorInfo (getField $ extract term) (toTermName' term)
|
2017-01-23 22:12:05 +03:00
|
|
|
_ -> toLeafInfo term
|
2017-02-10 00:33:33 +03:00
|
|
|
where
|
2017-02-13 23:53:20 +03:00
|
|
|
toTermName' = toTermName 0 source
|
2017-02-13 23:19:06 +03:00
|
|
|
termToDiffInfo' = termToDiffInfo source
|
2017-02-10 00:33:33 +03:00
|
|
|
toLeafInfo term = LeafInfo (category $ extract term) (toTermName' term) (getField $ extract term)
|
2017-01-23 19:22:51 +03:00
|
|
|
|
2017-02-13 23:53:20 +03:00
|
|
|
toTermName :: forall leaf fields. DefaultFields fields => Int -> Source -> SyntaxTerm leaf fields -> Text
|
|
|
|
toTermName parentOffset parentSource term = case unwrap term of
|
2017-01-26 02:26:03 +03:00
|
|
|
S.Function identifier _ _ _ -> toTermName' identifier
|
2017-02-08 01:53:15 +03:00
|
|
|
S.Method identifier Nothing _ _ _ -> toTermName' identifier
|
|
|
|
S.Method identifier (Just receiver) _ _ _ -> toTermName' receiver <> "." <> toTermName' identifier
|
2017-02-10 00:33:33 +03:00
|
|
|
_ -> toText source
|
2017-01-23 22:12:05 +03:00
|
|
|
where
|
2017-02-13 23:53:20 +03:00
|
|
|
source = Source.slice (offsetRange (range term) (negate parentOffset)) parentSource
|
|
|
|
offset = start (range term)
|
2017-02-10 00:33:33 +03:00
|
|
|
toTermName' :: SyntaxTerm leaf fields -> Text
|
2017-02-13 23:53:20 +03:00
|
|
|
toTermName' = toTermName offset source
|
2017-01-23 22:12:05 +03:00
|
|
|
range = characterRange . extract
|