1
1
mirror of https://github.com/github/semantic.git synced 2025-01-03 13:02:37 +03:00

Alternate through both sides of the diff when in diffToDiffSummaries annotateWithCategory function

This commit is contained in:
joshvera 2016-10-03 18:55:04 -04:00
parent ff7e2aa18a
commit e53f83ea6a
2 changed files with 17 additions and 12 deletions

View File

@ -138,13 +138,14 @@ rws compare as bs
insertDiff (i, mappedTerm) into)
into
diffs
-- Given a list of diffs, and unmapped terms in unmappedA, deletes
-- any terms that remain in umappedA.
-- Given a list of diffs, and unmapped terms, deletes any terms that remain in unmappedA.
deleteRemaining diffs (_, unmappedA, _) = foldl' (\into (i, deletion) ->
insertDiff (This i, deletion) into)
diffs
((termIndex &&& deleting . term) <$> unmappedA)
-- Possibly replace terms in a diff.
replaceIfEqual :: Term f (Record fields) -> Term f (Record fields) -> Maybe (Diff f (Record fields))
replaceIfEqual a b
| (category <$> a) == (category <$> b) = hylo wrap runCofree <$> zipTerms a b

View File

@ -25,7 +25,7 @@ import Source
data Identifiable a = Identifiable a | Unidentifiable a
identifiable :: SyntaxTerm leaf fields -> Identifiable (SyntaxTerm leaf fields)
identifiable term = isIdentifiable (unwrap term) $ term
identifiable term = isIdentifiable (unwrap term) term
where isIdentifiable = \case
S.FunctionCall{} -> Identifiable
S.MethodCall{} -> Identifiable
@ -64,12 +64,16 @@ summaryToTexts DiffSummary{..} = runJoin . fmap (show . (<+> maybeParentContext
-- Returns a list of 'DiffSummary' given two source blobs and a diff.
diffToDiffSummaries :: (HasCategory leaf, HasField fields Category, HasField fields Range) => Both (Source Char) -> SyntaxDiff leaf fields -> [DiffSummary DiffInfo]
diffToDiffSummaries sources = para $ \diff ->
let diff' = free (Prologue.fst <$> diff)
annotateWithCategory :: [(Diff leaf (Record fields), [DiffSummary DiffInfo])] -> [DiffSummary DiffInfo]
annotateWithCategory children = maybeToList (prependSummary (Both.snd sources) <$> (afterTerm diff')) <*> (children >>= snd) in
case diff of
let
diff' = free (Prologue.fst <$> diff)
annotateWithCategory :: [DiffSummary DiffInfo] -> [DiffSummary DiffInfo]
annotateWithCategory children = case (beforeTerm diff', afterTerm diff') of
(_, Just diff'') -> prependSummary (Both.snd sources) diff'' <$> children
(Just diff'', _) -> prependSummary (Both.fst sources) diff'' <$> children
(Nothing, Nothing) -> []
in case diff of
-- Skip comments and leaves since they don't have any changes
(Free (_ :< syntax)) -> annotateWithCategory (toList syntax)
(Free (_ :< syntax)) -> annotateWithCategory (toList syntax >>= snd)
(Pure patch) -> [ DiffSummary (mapPatch (termToDiffInfo beforeSource) (termToDiffInfo afterSource) patch) Nothing ]
where
(beforeSource, afterSource) = runJoin sources
@ -124,13 +128,13 @@ toTermName source term = case unwrap term of
Leaf leaf -> toCategoryName leaf
S.Assignment identifier _ -> toTermName' identifier
S.Function identifier _ _ -> toTermName' identifier
S.FunctionCall i args -> toTermName' i <> "(" <> (intercalate ", " (toArgName <$> args)) <> ")"
S.FunctionCall i args -> toTermName' i <> "(" <> intercalate ", " (toArgName <$> args) <> ")"
S.MemberAccess base property -> case (unwrap base, unwrap property) of
(S.FunctionCall{}, S.FunctionCall{}) -> toTermName' base <> "()." <> toTermName' property <> "()"
(S.FunctionCall{}, _) -> toTermName' base <> "()." <> toTermName' property
(_, S.FunctionCall{}) -> toTermName' base <> "." <> toTermName' property <> "()"
(_, _) -> toTermName' base <> "." <> toTermName' property
S.MethodCall targetId methodId methodParams -> toTermName' targetId <> sep <> toTermName' methodId <> "(" <> (intercalate ", " (toArgName <$> methodParams)) <> ")"
S.MethodCall targetId methodId methodParams -> toTermName' targetId <> sep <> toTermName' methodId <> "(" <> intercalate ", " (toArgName <$> methodParams) <> ")"
where sep = case unwrap targetId of
S.FunctionCall{} -> "()."
_ -> "."
@ -207,7 +211,7 @@ prependSummary source term summary =
isBranchInfo :: DiffInfo -> Bool
isBranchInfo info = case info of
(BranchInfo _ _ _) -> True
BranchInfo{} -> True
_ -> False
hasErrorInfo :: DiffInfo -> Bool
@ -290,6 +294,6 @@ instance Arbitrary a => Arbitrary (DiffSummary a) where
shrink = genericShrink
instance P.Pretty DiffInfo where
pretty LeafInfo{..} = squotes (string $ toSL termName) <+> (string $ toSL categoryName)
pretty LeafInfo{..} = squotes (string $ toSL termName) <+> string (toSL categoryName)
pretty BranchInfo{..} = mconcat $ punctuate (string "," P.<> space) (pretty <$> branches)
pretty ErrorInfo{..} = squotes (string $ toSL termName) <+> "at" <+> (string . toSL $ displayStartEndPos errorSpan) <+> "in" <+> (string . toSL $ spanName errorSpan)