2017-05-10 22:11:59 +03:00
|
|
|
|
{-# LANGUAGE DeriveAnyClass, RankNTypes #-}
|
2017-05-10 18:56:06 +03:00
|
|
|
|
module Renderer.TOC
|
|
|
|
|
( toc
|
|
|
|
|
, diffTOC
|
|
|
|
|
, JSONSummary(..)
|
|
|
|
|
, Summarizable(..)
|
2017-05-10 22:55:10 +03:00
|
|
|
|
, isValidSummary
|
2017-05-10 18:57:28 +03:00
|
|
|
|
, Declaration(..)
|
2017-05-10 18:58:08 +03:00
|
|
|
|
, declaration
|
2017-05-10 19:09:43 +03:00
|
|
|
|
, declarationAlgebra
|
2017-05-10 18:57:10 +03:00
|
|
|
|
, Entry(..)
|
2017-05-10 18:56:06 +03:00
|
|
|
|
, tableOfContentsBy
|
2017-05-11 22:36:25 +03:00
|
|
|
|
, dedupe
|
2017-05-10 20:18:47 +03:00
|
|
|
|
, entrySummary
|
2017-05-10 18:56:06 +03:00
|
|
|
|
) where
|
2017-01-23 19:22:51 +03:00
|
|
|
|
|
2017-01-23 22:12:05 +03:00
|
|
|
|
import Category as C
|
|
|
|
|
import Data.Aeson
|
2017-05-11 21:22:39 +03:00
|
|
|
|
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
|
2017-05-11 22:48:27 +03:00
|
|
|
|
import Data.Functor.Listable
|
2017-02-14 03:15:38 +03:00
|
|
|
|
import Data.Text (toLower)
|
2017-05-11 22:48:27 +03:00
|
|
|
|
import Data.Text.Listable
|
2017-05-11 23:33:52 +03:00
|
|
|
|
import Data.These
|
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-05-11 21:22:39 +03:00
|
|
|
|
import Patch
|
2017-01-23 22:12:05 +03:00
|
|
|
|
import Prologue
|
2017-04-04 00:15:58 +03:00
|
|
|
|
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)
|
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-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-05-09 18:16:17 +03:00
|
|
|
|
toJSON (JSONSummary Summarizable{..}) = object [ "changeType" .= summarizableChangeType, "category" .= toCategoryName summarizableCategory, "term" .= summarizableTermName, "span" .= summarizableSourceSpan ]
|
2017-01-23 23:58:20 +03:00
|
|
|
|
toJSON ErrorSummary{..} = object [ "error" .= error, "span" .= errorSpan ]
|
2017-01-23 22:12:05 +03:00
|
|
|
|
|
2017-05-10 22:55:10 +03:00
|
|
|
|
isValidSummary :: JSONSummary -> Bool
|
|
|
|
|
isValidSummary ErrorSummary{} = False
|
|
|
|
|
isValidSummary _ = True
|
2017-01-23 20:16:59 +03:00
|
|
|
|
|
2017-05-08 22:11:12 +03:00
|
|
|
|
data Summarizable
|
|
|
|
|
= Summarizable
|
|
|
|
|
{ summarizableCategory :: Category
|
|
|
|
|
, summarizableTermName :: Text
|
|
|
|
|
, summarizableSourceSpan :: SourceSpan
|
|
|
|
|
, summarizableChangeType :: Text
|
|
|
|
|
}
|
2017-01-24 00:33:07 +03:00
|
|
|
|
deriving (Eq, Show)
|
|
|
|
|
|
2017-05-10 18:57:28 +03:00
|
|
|
|
-- | A declaration’s identifier and type.
|
2017-05-10 19:39:12 +03:00
|
|
|
|
data Declaration
|
2017-05-10 19:40:07 +03:00
|
|
|
|
= MethodDeclaration { declarationIdentifier :: Text }
|
2017-05-10 19:39:12 +03:00
|
|
|
|
| FunctionDeclaration { declarationIdentifier :: Text }
|
2017-05-11 21:17:48 +03:00
|
|
|
|
| ErrorDeclaration { declarationIdentifier :: Text }
|
2017-05-10 22:11:59 +03:00
|
|
|
|
deriving (Eq, Generic, NFData, Show)
|
2017-05-10 18:57:28 +03:00
|
|
|
|
|
2017-05-10 19:01:26 +03:00
|
|
|
|
-- | Produce the annotations of nodes representing declarations.
|
2017-05-11 21:02:25 +03:00
|
|
|
|
declaration :: (HasField fields (Maybe Declaration), HasField fields Category) => TermF (Syntax Text) (Record fields) a -> Maybe (Record fields)
|
2017-05-11 21:13:54 +03:00
|
|
|
|
declaration (annotation :< syntax)
|
2017-05-12 00:02:28 +03:00
|
|
|
|
| S.ParseError{} <- syntax = Just (setCategory annotation C.ParseError)
|
|
|
|
|
| otherwise = annotation <$ (getField annotation :: Maybe Declaration)
|
2017-05-10 18:58:08 +03:00
|
|
|
|
|
|
|
|
|
|
2017-05-10 19:10:46 +03:00
|
|
|
|
-- | Compute 'Declaration's for methods and functions.
|
2017-05-10 19:09:43 +03:00
|
|
|
|
declarationAlgebra :: HasField fields Range => Source -> TermF (Syntax Text) (Record fields) (Term (Syntax Text) (Record fields), Maybe Declaration) -> Maybe Declaration
|
|
|
|
|
declarationAlgebra source r = case tailF r of
|
2017-05-10 19:39:12 +03:00
|
|
|
|
S.Function (identifier, _) _ _ -> Just $ FunctionDeclaration (getSource identifier)
|
|
|
|
|
S.Method _ (identifier, _) Nothing _ _ -> Just $ MethodDeclaration (getSource identifier)
|
2017-05-10 19:09:43 +03:00
|
|
|
|
S.Method _ (identifier, _) (Just (receiver, _)) _ _
|
|
|
|
|
| S.Indexed [receiverParams] <- unwrap receiver
|
2017-05-10 19:39:12 +03:00
|
|
|
|
, S.ParameterDecl (Just ty) _ <- unwrap receiverParams -> Just $ MethodDeclaration ("(" <> getSource ty <> ") " <> getSource identifier)
|
|
|
|
|
| otherwise -> Just $ MethodDeclaration (getSource receiver <> "." <> getSource identifier)
|
2017-05-11 21:17:48 +03:00
|
|
|
|
S.ParseError{} -> Just $ ErrorDeclaration (toText (Source.slice (byteRange (headF r)) source))
|
2017-05-10 19:09:43 +03:00
|
|
|
|
_ -> Nothing
|
|
|
|
|
where getSource = toText . flip Source.slice source . byteRange . extract
|
|
|
|
|
|
|
|
|
|
|
2017-05-10 17:24:43 +03:00
|
|
|
|
-- | An entry in a table of contents.
|
2017-05-10 16:55:05 +03:00
|
|
|
|
data Entry a
|
2017-05-12 00:32:43 +03:00
|
|
|
|
= Unchanged { entryPayload :: a } -- ^ An entry for an unchanged portion of a diff (i.e. a diff node not containing any patches).
|
|
|
|
|
| Changed { entryPayload :: a } -- ^ An entry for a node containing changes.
|
|
|
|
|
| Inserted { entryPayload :: a } -- ^ An entry for a change occurring inside an 'Insert' 'Patch'.
|
|
|
|
|
| Deleted { entryPayload :: a } -- ^ An entry for a change occurring inside a 'Delete' 'Patch'.
|
|
|
|
|
| Replaced { entryPayload :: a } -- ^ An entry for a change occurring on the insertion side of a 'Replace' 'Patch'.
|
2017-05-10 16:55:05 +03:00
|
|
|
|
deriving (Eq, Show)
|
|
|
|
|
|
2017-05-11 22:36:02 +03:00
|
|
|
|
|
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.
|
2017-05-10 17:20:51 +03:00
|
|
|
|
tableOfContentsBy :: Traversable f
|
2017-05-10 18:47:19 +03:00
|
|
|
|
=> (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.
|
2017-05-12 00:08:21 +03:00
|
|
|
|
tableOfContentsBy selector = fromMaybe [] . iter diffAlgebra . fmap (Just . fmap patchEntry . crosswalk (cata termAlgebra))
|
2017-05-10 21:28:10 +03:00
|
|
|
|
where diffAlgebra r = case (selector (first Both.snd r), fold r) of
|
|
|
|
|
(Just a, Nothing) -> Just [Unchanged a]
|
|
|
|
|
(Just a, Just []) -> Just [Changed a]
|
2017-05-10 21:29:28 +03:00
|
|
|
|
(_ , entries) -> entries
|
2017-05-10 17:05:12 +03:00
|
|
|
|
termAlgebra r | Just a <- selector r = [a]
|
2017-05-10 16:55:05 +03:00
|
|
|
|
| otherwise = fold r
|
2017-05-12 00:08:21 +03:00
|
|
|
|
patchEntry = these Deleted Inserted (const Replaced) . unPatch
|
2017-05-10 16:55:05 +03:00
|
|
|
|
|
2017-05-11 22:36:25 +03:00
|
|
|
|
dedupe :: (HasField fields Category, HasField fields (Maybe Declaration)) => [Entry (Record fields)] -> [Entry (Record fields)]
|
|
|
|
|
dedupe = foldl' go []
|
|
|
|
|
where go xs x | (_, _:_) <- find (exactMatch `on` entryPayload) x xs = xs
|
2017-05-11 23:05:56 +03:00
|
|
|
|
| (front, similar : back) <- find (similarMatch `on` entryPayload) x xs =
|
2017-05-11 23:41:17 +03:00
|
|
|
|
front <> (Replaced (entryPayload similar) : back)
|
2017-05-11 22:36:25 +03:00
|
|
|
|
| otherwise = xs <> [x]
|
|
|
|
|
|
|
|
|
|
find p x = List.break (p x)
|
|
|
|
|
exactMatch = (==) `on` getDeclaration
|
|
|
|
|
similarMatch a b = sameCategory a b && similarDeclaration a b
|
|
|
|
|
sameCategory = (==) `on` category
|
|
|
|
|
similarDeclaration = (==) `on` fmap (toLower . declarationIdentifier) . getDeclaration
|
|
|
|
|
getDeclaration :: HasField fields (Maybe Declaration) => Record fields -> Maybe Declaration
|
|
|
|
|
getDeclaration = getField
|
2017-05-11 22:25:12 +03:00
|
|
|
|
|
2017-05-10 20:18:47 +03:00
|
|
|
|
-- | Construct a 'JSONSummary' from an 'Entry'. Returns 'Nothing' for 'Unchanged' patches.
|
|
|
|
|
entrySummary :: (HasField fields Category, HasField fields (Maybe Declaration), HasField fields SourceSpan) => Entry (Record fields) -> Maybe JSONSummary
|
|
|
|
|
entrySummary entry = case entry of
|
|
|
|
|
Unchanged _ -> Nothing
|
|
|
|
|
Changed a -> Just (recordSummary a "modified")
|
2017-05-11 23:37:17 +03:00
|
|
|
|
Deleted a -> Just (recordSummary a "removed")
|
|
|
|
|
Inserted a -> Just (recordSummary a "added")
|
|
|
|
|
Replaced a -> Just (recordSummary a "modified")
|
2017-05-11 21:11:49 +03:00
|
|
|
|
where recordSummary record
|
|
|
|
|
| C.ParseError <- category record = const (ErrorSummary (maybe "" declarationIdentifier (getField record :: Maybe Declaration)) (sourceSpan record))
|
|
|
|
|
| otherwise = JSONSummary . Summarizable (category record) (maybe "" declarationIdentifier (getField record :: Maybe Declaration)) (sourceSpan record)
|
2017-05-10 20:18:47 +03:00
|
|
|
|
|
2017-05-10 22:46:04 +03:00
|
|
|
|
toc :: (HasField fields Category, HasField fields (Maybe Declaration), HasField fields SourceSpan) => Both SourceBlob -> Diff (Syntax Text) (Record fields) -> Summaries
|
2017-05-11 23:59:32 +03:00
|
|
|
|
toc blobs = uncurry Summaries . bimap toMap toMap . List.partition isValidSummary . diffTOC
|
2017-05-10 21:00:58 +03:00
|
|
|
|
where toMap [] = mempty
|
|
|
|
|
toMap as = Map.singleton summaryKey (toJSON <$> as)
|
|
|
|
|
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-11 23:59:32 +03:00
|
|
|
|
diffTOC :: (HasField fields Category, HasField fields (Maybe Declaration), HasField fields SourceSpan) => Diff (Syntax Text) (Record fields) -> [JSONSummary]
|
|
|
|
|
diffTOC = mapMaybe entrySummary . dedupe . tableOfContentsBy declaration
|
2017-01-23 22:12:05 +03:00
|
|
|
|
|
2017-02-18 01:57:29 +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"
|
2017-02-18 01:57:29 +03:00
|
|
|
|
c -> show c
|
2017-05-11 22:48:27 +03:00
|
|
|
|
|
|
|
|
|
instance Listable Declaration where
|
|
|
|
|
tiers
|
|
|
|
|
= cons1 (MethodDeclaration . unListableText)
|
|
|
|
|
\/ cons1 (FunctionDeclaration . unListableText)
|
|
|
|
|
\/ cons1 (ErrorDeclaration . unListableText)
|