1
1
mirror of https://github.com/github/semantic.git synced 2024-11-28 10:15:55 +03:00
semantic/test/DiffSummarySpec.hs

105 lines
4.2 KiB
Haskell
Raw Normal View History

{-# LANGUAGE DataKinds #-}
2016-05-17 20:09:14 +03:00
module DiffSummarySpec where
2016-05-16 21:43:53 +03:00
import Prologue
import Data.Record
2016-05-16 21:43:53 +03:00
import Test.Hspec
import Test.Hspec.QuickCheck
2016-05-17 22:59:07 +03:00
import Diff
import Syntax
import Term
2016-05-17 20:09:14 +03:00
import Patch
2016-05-17 22:59:07 +03:00
import Category
2016-05-16 21:43:53 +03:00
import DiffSummary
import Text.PrettyPrint.Leijen.Text (pretty)
import Test.Hspec.QuickCheck
import Diff.Arbitrary
import Data.List (partition)
import Term.Arbitrary
import Interpreter
2016-05-17 20:09:14 +03:00
arrayInfo :: Record '[Category]
arrayInfo = ArrayLiteral .: RNil
2016-05-17 22:59:07 +03:00
literalInfo :: Record '[Category]
literalInfo = StringLiteral .: RNil
2016-05-17 22:59:07 +03:00
testDiff :: Diff Text (Record '[Category])
2016-05-17 22:59:07 +03:00
testDiff = free $ Free (pure arrayInfo :< Indexed [ free $ Pure (Insert (cofree $ literalInfo :< Leaf "a")) ])
2016-05-31 23:15:40 +03:00
testSummary :: DiffSummary DiffInfo
testSummary = DiffSummary { patch = Insert (LeafInfo "string" "a"), parentAnnotations = [] }
2016-05-17 20:09:14 +03:00
2016-05-31 23:15:40 +03:00
replacementSummary :: DiffSummary DiffInfo
replacementSummary = DiffSummary { patch = Replace (LeafInfo "string" "a") (LeafInfo "symbol" "b"), parentAnnotations = [ ArrayLiteral ] }
2016-05-18 17:24:08 +03:00
2016-05-17 20:09:14 +03:00
spec :: Spec
spec = parallel $ do
2016-05-17 22:59:07 +03:00
describe "diffSummary" $ do
it "outputs a diff summary" $ do
diffSummary testDiff `shouldBe` [ DiffSummary { patch = Insert (LeafInfo "string" "a"), parentAnnotations = [ ArrayLiteral ] } ]
prop "equal terms produce identity diffs" $
\ a -> let term = toTerm (a :: ArbitraryTerm Text (Record '[Category])) in
diffSummary (diffTerms wrap (==) diffCost term term) `shouldBe` []
describe "annotatedSummaries" $ do
2016-05-17 20:09:14 +03:00
it "should print adds" $
2016-07-16 00:11:45 +03:00
annotatedSummaries testSummary `shouldBe` ["Added the 'a' string"]
2016-05-18 17:24:08 +03:00
it "prints a replacement" $ do
2016-07-16 00:11:45 +03:00
annotatedSummaries replacementSummary `shouldBe` ["Replaced the 'a' string with the 'b' symbol in the array context"]
describe "DiffInfo" $ do
prop "patches in summaries match the patches in diffs" $
\a -> let
diff = (toDiff (a :: ArbitraryDiff Text (Record '[Category, Cost])))
summaries = diffSummary diff
patches = toList diff
in
case (partition isBranchNode (patch <$> summaries), partition isIndexedOrFixed patches) of
((branchPatches, otherPatches), (branchDiffPatches, otherDiffPatches)) ->
(() <$ branchPatches, () <$ otherPatches) `shouldBe` (() <$ branchDiffPatches, () <$ otherDiffPatches)
prop "generates one LeafInfo for each child in an arbitrary branch patch" $
\a -> let
diff = (toDiff (a :: ArbitraryDiff Text (Record '[Category])))
diffInfoPatches = patch <$> diffSummary diff
syntaxPatches = toList diff
extractLeaves :: DiffInfo -> [DiffInfo]
extractLeaves (BranchInfo children _ _) = join $ extractLeaves <$> children
extractLeaves leaf = [ leaf ]
extractDiffLeaves :: Term Text (Record '[Category]) -> [ Term Text (Record '[Category]) ]
extractDiffLeaves term = case unwrap term of
(Indexed children) -> join $ extractDiffLeaves <$> children
(Fixed children) -> join $ extractDiffLeaves <$> children
Commented children leaf -> join $ extractDiffLeaves <$> children <> maybeToList leaf
_ -> [ term ]
in
case (partition isBranchNode diffInfoPatches, partition isIndexedOrFixed syntaxPatches) of
((branchPatches, _), (diffPatches, _)) ->
let listOfLeaves = foldMap extractLeaves (join $ toList <$> branchPatches)
listOfDiffLeaves = foldMap extractDiffLeaves (join $ toList <$> diffPatches)
in
length listOfLeaves `shouldBe` length listOfDiffLeaves
isIndexedOrFixed :: Patch (Term a annotation) -> Bool
isIndexedOrFixed patch = case unwrap <$> patch of
(Insert syntax) -> isIndexedOrFixed' syntax
(Delete syntax) -> isIndexedOrFixed' syntax
(Replace s1 s2) -> isIndexedOrFixed' s1 || isIndexedOrFixed' s2
2016-07-16 03:32:48 +03:00
isIndexedOrFixed' :: Syntax a f -> Bool
isIndexedOrFixed' syntax = case syntax of
(Indexed _) -> True
(Fixed _) -> True
_ -> False
2016-07-16 03:32:48 +03:00
isBranchInfo :: DiffInfo -> Bool
isBranchInfo info = case info of
(BranchInfo _ _ _) -> True
(LeafInfo _ _) -> False
2016-07-16 03:32:48 +03:00
isBranchNode :: Patch DiffInfo -> Bool
isBranchNode patch = case patch of
(Insert diffInfo) -> isBranchInfo diffInfo
(Delete diffInfo) -> isBranchInfo diffInfo
(Replace i1 i2) -> isBranchInfo i1 || isBranchInfo i2