mirror of
https://github.com/github/semantic.git
synced 2025-01-06 23:46:21 +03:00
Match on Category instead of name and rework determiner logic
This commit is contained in:
parent
cd2fe4a681
commit
489ed112a0
@ -3,7 +3,7 @@
|
|||||||
|
|
||||||
module DiffSummary (diffSummaries, DiffSummary(..), DiffInfo(..), diffToDiffSummaries, isBranchInfo, isErrorSummary, JSONSummary(..)) where
|
module DiffSummary (diffSummaries, DiffSummary(..), DiffInfo(..), diffToDiffSummaries, isBranchInfo, isErrorSummary, JSONSummary(..)) where
|
||||||
|
|
||||||
import Prologue hiding (intercalate)
|
import Prologue hiding (intercalate, null, isPrefixOf)
|
||||||
import Diff
|
import Diff
|
||||||
import Patch
|
import Patch
|
||||||
import Term
|
import Term
|
||||||
@ -13,7 +13,7 @@ import Syntax as S
|
|||||||
import Category as C
|
import Category as C
|
||||||
import Data.Functor.Both hiding (fst, snd)
|
import Data.Functor.Both hiding (fst, snd)
|
||||||
import qualified Data.Functor.Both as Both
|
import qualified Data.Functor.Both as Both
|
||||||
import Data.Text (intercalate)
|
import Data.Text (intercalate, null, isPrefixOf)
|
||||||
import qualified Data.Text as Text (head)
|
import qualified Data.Text as Text (head)
|
||||||
import Test.QuickCheck hiding (Fixed)
|
import Test.QuickCheck hiding (Fixed)
|
||||||
import Patch.Arbitrary()
|
import Patch.Arbitrary()
|
||||||
@ -76,8 +76,8 @@ isErrorSummary :: JSONSummary summary span -> Bool
|
|||||||
isErrorSummary ErrorSummary{} = True
|
isErrorSummary ErrorSummary{} = True
|
||||||
isErrorSummary _ = False
|
isErrorSummary _ = False
|
||||||
|
|
||||||
data DiffInfo = LeafInfo { categoryName :: Text, termName :: Text, sourceSpan :: SourceSpan }
|
data DiffInfo = LeafInfo { leafCategory :: Category, termName :: Text, sourceSpan :: SourceSpan }
|
||||||
| BranchInfo { branches :: [ DiffInfo ], categoryName :: Text, branchType :: Branch }
|
| BranchInfo { branches :: [ DiffInfo ], branchCategory :: Category, branchType :: Branch }
|
||||||
| ErrorInfo { errorSpan :: SourceSpan, termName :: Text }
|
| ErrorInfo { errorSpan :: SourceSpan, termName :: Text }
|
||||||
| HideInfo -- Hide/Strip from summary output entirely.
|
| HideInfo -- Hide/Strip from summary output entirely.
|
||||||
deriving (Eq, Show)
|
deriving (Eq, Show)
|
||||||
@ -142,55 +142,40 @@ prefixWithPatch patch constructor = prefixWithThe (patchToPrefix patch)
|
|||||||
(Insert _) -> "Added"
|
(Insert _) -> "Added"
|
||||||
(Delete _) -> "Deleted"
|
(Delete _) -> "Deleted"
|
||||||
|
|
||||||
-- Optional determiner (e.g. "the") to tie together summary statements.
|
|
||||||
determiner :: DiffInfo -> Doc
|
|
||||||
determiner = \case
|
|
||||||
LeafInfo "number" _ _ -> ""
|
|
||||||
LeafInfo "integer" _ _ -> ""
|
|
||||||
LeafInfo "boolean" _ _ -> ""
|
|
||||||
LeafInfo "begin statement" _ _ -> "a"
|
|
||||||
LeafInfo "select statement" _ _ -> "a"
|
|
||||||
LeafInfo "else block" _ _ -> "an"
|
|
||||||
LeafInfo "ensure block" _ _ -> "an"
|
|
||||||
LeafInfo "when block" _ _ -> "a"
|
|
||||||
LeafInfo "anonymous function" _ _ -> "an"
|
|
||||||
LeafInfo "break statement" _ _ -> "a"
|
|
||||||
LeafInfo "continue statement" _ _ -> "a"
|
|
||||||
LeafInfo "yield statement" "" _ -> "a"
|
|
||||||
LeafInfo "return statement" "" _ -> "a"
|
|
||||||
LeafInfo "BEGIN block" _ _ -> "a"
|
|
||||||
LeafInfo "END block" _ _ -> "an"
|
|
||||||
LeafInfo{..} -> "the"
|
|
||||||
info -> panic $ "Expected a leaf info but got a: " <> show info
|
|
||||||
|
|
||||||
toLeafInfos :: DiffInfo -> [JSONSummary Doc SourceSpan]
|
toLeafInfos :: DiffInfo -> [JSONSummary Doc SourceSpan]
|
||||||
toLeafInfos err@ErrorInfo{..} = pure $ ErrorSummary (pretty err) errorSpan
|
toLeafInfos err@ErrorInfo{..} = pure $ ErrorSummary (pretty err) errorSpan
|
||||||
toLeafInfos BranchInfo{..} = branches >>= toLeafInfos
|
toLeafInfos BranchInfo{..} = branches >>= toLeafInfos
|
||||||
toLeafInfos HideInfo = []
|
toLeafInfos HideInfo = []
|
||||||
toLeafInfos leaf = pure . flip JSONSummary (sourceSpan leaf) $ leafSummary leaf
|
toLeafInfos LeafInfo{..} = pure $ JSONSummary (summary leafCategory termName) sourceSpan
|
||||||
where
|
where
|
||||||
leafSummary leaf = determiner leaf <+> case leaf of
|
summary :: Category -> Text -> Doc
|
||||||
LeafInfo "number" termName _ -> squotes $ toDoc termName
|
summary category termName = case category of
|
||||||
LeafInfo "integer" termName _ -> squotes $ toDoc termName
|
C.NumberLiteral -> squotes $ toDoc termName
|
||||||
LeafInfo "boolean" termName _ -> squotes $ toDoc termName
|
C.IntegerLiteral -> squotes $ toDoc termName
|
||||||
LeafInfo "anonymous function" termName _ -> toDoc termName <+> "function"
|
C.Boolean -> squotes $ toDoc termName
|
||||||
LeafInfo cName@"begin statement" _ _ -> toDoc cName
|
C.StringLiteral -> termAndCategoryName
|
||||||
LeafInfo cName@"select statement" _ _ -> toDoc cName
|
C.Export -> termAndCategoryName
|
||||||
LeafInfo cName@"else block" _ _ -> toDoc cName
|
C.Import -> termAndCategoryName
|
||||||
LeafInfo cName@"ensure block" _ _ -> toDoc cName
|
C.Subshell -> termAndCategoryName
|
||||||
LeafInfo cName@"when block" _ _ -> toDoc cName
|
C.AnonymousFunction -> "an" <+> toDoc termName <+> "function"
|
||||||
LeafInfo cName@"string" termName _ -> toDoc termName <+> toDoc cName
|
C.Begin -> categoryName'
|
||||||
LeafInfo cName@"export statement" termName _ -> toDoc termName <+> toDoc cName
|
C.Select -> categoryName'
|
||||||
LeafInfo cName@"import statement" termName _ -> toDoc termName <+> toDoc cName
|
C.Else -> categoryName'
|
||||||
LeafInfo cName@"subshell command" termName _ -> toDoc termName <+> toDoc cName
|
C.Ensure -> categoryName'
|
||||||
LeafInfo cName@"break statement" _ _ -> toDoc cName
|
C.Break -> categoryName'
|
||||||
LeafInfo cName@"continue statement" _ _ -> toDoc cName
|
C.Continue -> categoryName'
|
||||||
LeafInfo cName@"yield statement" "" _ -> toDoc cName
|
C.BeginBlock -> categoryName'
|
||||||
LeafInfo cName@"return statement" "" _ -> toDoc cName
|
C.EndBlock -> categoryName'
|
||||||
LeafInfo cName@"BEGIN block" _ _ -> toDoc cName
|
C.Yield | null termName -> categoryName'
|
||||||
LeafInfo cName@"END block" _ _ -> toDoc cName
|
C.Return | null termName -> categoryName'
|
||||||
LeafInfo{..} -> squotes (toDoc termName) <+> toDoc categoryName
|
_ -> "the" <+> squotes (toDoc termName) <+> toDoc categoryName
|
||||||
node -> panic $ "Expected a leaf info but got a: " <> show node
|
where
|
||||||
|
termAndCategoryName = "the" <+> toDoc termName <+> toDoc categoryName
|
||||||
|
categoryName = toCategoryName category
|
||||||
|
categoryName' = case categoryName of
|
||||||
|
name | startsWithVowel name -> "an" <+> toDoc name
|
||||||
|
| otherwise -> "a" <+> toDoc name
|
||||||
|
startsWithVowel text = getAny $ foldMap (Any . flip isPrefixOf text) ["a","e","i","o","u","A","E","I","O","U"]
|
||||||
|
|
||||||
-- Returns a text representing a specific term given a source and a term.
|
-- Returns a text representing a specific term given a source and a term.
|
||||||
toTermName :: forall leaf fields. (HasCategory leaf, DefaultFields fields) => Source Char -> SyntaxTerm leaf fields -> Text
|
toTermName :: forall leaf fields. (HasCategory leaf, DefaultFields fields) => Source Char -> SyntaxTerm leaf fields -> Text
|
||||||
@ -311,16 +296,16 @@ toDoc = string . toS
|
|||||||
|
|
||||||
termToDiffInfo :: (HasCategory leaf, DefaultFields fields) => Source Char -> SyntaxTerm leaf fields -> DiffInfo
|
termToDiffInfo :: (HasCategory leaf, DefaultFields fields) => Source Char -> SyntaxTerm leaf fields -> DiffInfo
|
||||||
termToDiffInfo blob term = case unwrap term of
|
termToDiffInfo blob term = case unwrap term of
|
||||||
S.Indexed children -> BranchInfo (termToDiffInfo' <$> children) (toCategoryName term) BIndexed
|
S.Indexed children -> BranchInfo (termToDiffInfo' <$> children) (category $ extract term) BIndexed
|
||||||
S.Fixed children -> BranchInfo (termToDiffInfo' <$> children) (toCategoryName term) BFixed
|
S.Fixed children -> BranchInfo (termToDiffInfo' <$> children) (category $ extract term) BFixed
|
||||||
S.AnonymousFunction _ _ -> LeafInfo "anonymous function" (toTermName' term) (getField $ extract term)
|
S.AnonymousFunction _ _ -> LeafInfo C.AnonymousFunction (toTermName' term) (getField $ extract term)
|
||||||
S.Comment _ -> HideInfo
|
S.Comment _ -> HideInfo
|
||||||
S.Commented cs leaf -> BranchInfo (termToDiffInfo' <$> cs <> maybeToList leaf) (toCategoryName term) BCommented
|
S.Commented cs leaf -> BranchInfo (termToDiffInfo' <$> cs <> maybeToList leaf) (category $ extract term) BCommented
|
||||||
S.Error _ -> ErrorInfo (getField $ extract term) (toTermName' term)
|
S.Error _ -> ErrorInfo (getField $ extract term) (toTermName' term)
|
||||||
_ -> toLeafInfo term
|
_ -> toLeafInfo term
|
||||||
where toTermName' = toTermName blob
|
where toTermName' = toTermName blob
|
||||||
termToDiffInfo' = termToDiffInfo blob
|
termToDiffInfo' = termToDiffInfo blob
|
||||||
toLeafInfo term = LeafInfo (toCategoryName term) (toTermName' term) (getField $ extract term)
|
toLeafInfo term = LeafInfo (category $ extract term) (toTermName' term) (getField $ extract term)
|
||||||
|
|
||||||
-- | Append a parentAnnotation to the current DiffSummary instance.
|
-- | Append a parentAnnotation to the current DiffSummary instance.
|
||||||
-- | For a DiffSummary without a parentAnnotation, we append a parentAnnotation with the first identifiable term.
|
-- | For a DiffSummary without a parentAnnotation, we append a parentAnnotation with the first identifiable term.
|
||||||
@ -458,7 +443,7 @@ instance Arbitrary a => Arbitrary (DiffSummary a) where
|
|||||||
shrink = genericShrink
|
shrink = genericShrink
|
||||||
|
|
||||||
instance P.Pretty DiffInfo where
|
instance P.Pretty DiffInfo where
|
||||||
pretty LeafInfo{..} = squotes (string $ toSL termName) <+> string (toSL categoryName)
|
pretty LeafInfo{..} = squotes (string $ toSL termName) <+> string (toSL (toCategoryName leafCategory))
|
||||||
pretty BranchInfo{..} = mconcat $ punctuate (string "," P.<> space) (pretty <$> branches)
|
pretty BranchInfo{..} = mconcat $ punctuate (string "," P.<> space) (pretty <$> branches)
|
||||||
pretty ErrorInfo{..} = squotes (string $ toSL termName) <+> "at" <+> (string . toSL $ displayStartEndPos errorSpan)
|
pretty ErrorInfo{..} = squotes (string $ toSL termName) <+> "at" <+> (string . toSL $ displayStartEndPos errorSpan)
|
||||||
pretty HideInfo = ""
|
pretty HideInfo = ""
|
||||||
|
Loading…
Reference in New Issue
Block a user