1
1
mirror of https://github.com/github/semantic.git synced 2024-12-23 14:54:16 +03:00
semantic/src/DiffSummary.hs

98 lines
4.6 KiB
Haskell
Raw Normal View History

{-# LANGUAGE DataKinds, TypeFamilies, ScopedTypeVariables #-}
2016-06-07 02:41:07 +03:00
2016-05-17 20:09:14 +03:00
module DiffSummary (DiffSummary(..), diffSummary, DiffInfo(..)) where
2016-04-25 18:46:10 +03:00
2016-06-07 02:41:07 +03:00
import Prologue hiding (fst, snd, intercalate)
2016-04-25 18:46:10 +03:00
import Diff
import Info (Info, category)
2016-04-25 18:46:10 +03:00
import Patch
2016-05-17 22:59:07 +03:00
import Term
2016-04-25 18:46:10 +03:00
import Syntax
2016-05-16 20:19:30 +03:00
import Category
2016-05-03 19:17:38 +03:00
import Data.Functor.Foldable as Foldable
2016-05-18 00:34:27 +03:00
import Data.Functor.Both
import Data.OrderedMap
2016-06-07 02:41:07 +03:00
import Data.Text as Text (intercalate, unpack)
2016-04-25 18:46:10 +03:00
2016-06-08 21:50:33 +03:00
data DiffInfo = DiffInfo { categoryName :: Text, termName :: Text } deriving (Eq, Show)
2016-05-18 17:18:26 +03:00
2016-06-08 21:50:33 +03:00
toTermName :: HasCategory leaf => Term leaf Info -> Text
toTermName term = case runCofree term of
(_ :< Leaf leaf) -> toCategoryName leaf
(_ :< Keyed children) -> mconcat $ keys children
(_ :< Indexed children) -> fromMaybe "EmptyIndexedNode" $ (toCategoryName . category) . extract <$> head children
(_ :< Fixed children) -> fromMaybe "EmptyFixedNode" $ (toCategoryName . category) . extract <$> head children
(_ :< Syntax.FunctionCall i _) -> toTermName i
2016-06-10 22:10:37 +03:00
(_ :< Syntax.Function identifier _ _) -> (maybe "anonymous function" toTermName identifier)
2016-05-24 19:49:16 +03:00
class HasCategory a where
toCategoryName :: a -> Text
2016-05-18 00:34:27 +03:00
2016-05-24 19:49:16 +03:00
instance HasCategory Text where
toCategoryName = identity
2016-05-18 19:01:16 +03:00
instance HasCategory Info where
toCategoryName = toCategoryName . category
2016-05-24 19:49:16 +03:00
instance HasCategory Category where
2016-06-10 22:24:37 +03:00
toCategoryName = \case
Program -> "top level"
2016-06-04 01:37:40 +03:00
Error -> "error"
2016-05-18 00:34:27 +03:00
BinaryOperator -> "binary operator"
2016-05-18 20:37:02 +03:00
DictionaryLiteral -> "dictionary"
2016-05-18 00:34:27 +03:00
Pair -> "pair"
2016-06-09 00:18:30 +03:00
Category.FunctionCall -> "function call"
2016-05-18 20:37:02 +03:00
StringLiteral -> "string"
IntegerLiteral -> "integer"
SymbolLiteral -> "symbol"
ArrayLiteral -> "array"
2016-06-10 22:24:37 +03:00
Category.Function -> "function"
Identifier -> "identifier"
Params -> "params"
ExpressionStatements -> "expression statements"
Other s -> s
2016-05-17 20:09:14 +03:00
2016-05-24 19:49:16 +03:00
instance HasCategory leaf => HasCategory (Term leaf Info) where
toCategoryName = toCategoryName . category . extract
2016-05-24 19:49:16 +03:00
2016-05-17 20:09:14 +03:00
data DiffSummary a = DiffSummary {
patch :: Patch a,
parentAnnotations :: [Category]
2016-05-17 20:09:14 +03:00
} deriving (Eq, Functor)
2016-05-13 18:44:03 +03:00
instance Show (DiffSummary DiffInfo) where
showsPrec _ DiffSummary{..} s = (++s) . unpack $ case patch of
(Insert diffInfo) -> "Added the " <> "'" <> termName diffInfo <> "' " <> categoryName diffInfo <> maybeParentContext parentAnnotations
(Delete diffInfo) -> "Deleted the " <> "'" <> termName diffInfo <> "' " <> categoryName diffInfo <> maybeParentContext parentAnnotations
(Replace t1 t2) ->
"Replaced the " <> "'" <> termName t1 <> "' " <> categoryName t1
<> " with the " <> "'" <> termName t2 <> "' " <> categoryName t2
<> maybeParentContext parentAnnotations
where maybeParentContext parentAnnotations = if null parentAnnotations
then ""
else " in the " <> intercalate "/" (toCategoryName <$> parentAnnotations) <> " context"
2016-04-25 18:46:10 +03:00
2016-05-24 19:49:16 +03:00
diffSummary :: HasCategory leaf => Diff leaf Info -> [DiffSummary DiffInfo]
2016-06-06 21:45:45 +03:00
diffSummary = cata $ \case
(Free (_ :< Leaf _)) -> [] -- Skip leaves since they don't have any changes
(Free (infos :< Indexed children)) -> prependSummary (category $ snd infos) <$> join children
(Free (infos :< Fixed children)) -> prependSummary (category $ snd infos) <$> join children
(Free (infos :< Keyed children)) -> prependSummary (category $ snd infos) <$> join (Prologue.toList children)
(Free (infos :< Syntax.FunctionCall identifier children)) -> prependSummary (category $ snd infos) <$> join (Prologue.toList (identifier : children))
2016-06-10 22:10:37 +03:00
(Free (infos :< Syntax.Function id ps body)) -> prependSummary (category $ snd infos) <$> (fromMaybe [] id) <> (fromMaybe [] ps) <> body
(Pure (Insert term)) -> (\info -> DiffSummary (Insert info) []) <$> termToDiffInfo term
(Pure (Delete term)) -> (\info -> DiffSummary (Delete info) []) <$> termToDiffInfo term
(Pure (Replace t1 t2)) -> (\(info1, info2) -> DiffSummary (Replace info1 info2) []) <$> zip (termToDiffInfo t1) (termToDiffInfo t2)
termToDiffInfo :: HasCategory leaf => Term leaf Info -> [DiffInfo]
termToDiffInfo term = case runCofree term of
(_ :< Leaf _) -> [ DiffInfo (toCategoryName term) (toTermName term) ]
(_ :< Indexed children) -> join $ termToDiffInfo <$> children
(_ :< Fixed children) -> join $ termToDiffInfo <$> children
(_ :< Keyed children) -> join $ termToDiffInfo <$> Prologue.toList children
(info :< Syntax.FunctionCall identifier _) -> [ DiffInfo (toCategoryName info) (toTermName identifier) ]
2016-06-10 22:10:37 +03:00
(info :< Syntax.Function identifier params _) -> [ DiffInfo (toCategoryName info) (maybe "anonymous function" toTermName identifier) ]
2016-05-16 17:54:05 +03:00
prependSummary :: Category -> DiffSummary DiffInfo -> DiffSummary DiffInfo
2016-05-16 17:54:05 +03:00
prependSummary annotation summary = summary { parentAnnotations = annotation : parentAnnotations summary }