2016-07-13 21:32:53 +03:00
|
|
|
{-# LANGUAGE DataKinds #-}
|
2016-05-17 20:09:14 +03:00
|
|
|
module DiffSummarySpec where
|
2016-05-16 21:43:53 +03:00
|
|
|
|
2016-05-26 20:40:54 +03:00
|
|
|
import Prologue
|
2016-06-17 20:33:50 +03:00
|
|
|
import Data.Record
|
2016-05-16 21:43:53 +03:00
|
|
|
import Test.Hspec
|
2016-05-17 22:59:07 +03:00
|
|
|
import Diff
|
|
|
|
import Info
|
|
|
|
import Syntax
|
2016-05-17 20:09:14 +03:00
|
|
|
import Patch
|
2016-05-17 22:59:07 +03:00
|
|
|
import Range
|
|
|
|
import Category
|
2016-05-16 21:43:53 +03:00
|
|
|
import DiffSummary
|
2016-07-13 21:32:53 +03:00
|
|
|
import Text.PrettyPrint.Leijen.Text (pretty)
|
|
|
|
import Test.Hspec.QuickCheck
|
|
|
|
import Interpreter
|
2016-07-14 18:52:40 +03:00
|
|
|
import Diff.Arbitrary
|
2016-07-13 21:32:53 +03:00
|
|
|
import Text.Megaparsec.Text
|
|
|
|
import Text.Megaparsec
|
2016-05-17 20:09:14 +03:00
|
|
|
|
2016-05-17 22:59:07 +03:00
|
|
|
arrayInfo :: Info
|
2016-06-17 20:33:50 +03:00
|
|
|
arrayInfo = rangeAt 0 .: ArrayLiteral .: 2 .: 0 .: RNil
|
2016-05-17 22:59:07 +03:00
|
|
|
|
|
|
|
literalInfo :: Info
|
2016-06-17 20:33:50 +03:00
|
|
|
literalInfo = rangeAt 1 .: StringLiteral .: 1 .: 0 .: RNil
|
2016-05-17 22:59:07 +03:00
|
|
|
|
2016-06-10 23:42:11 +03:00
|
|
|
testDiff :: Diff Text Info
|
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
|
2016-06-10 23:42:11 +03:00
|
|
|
testSummary = DiffSummary { patch = Insert (DiffInfo "string" "a"), parentAnnotations = [] }
|
2016-05-17 20:09:14 +03:00
|
|
|
|
2016-05-31 23:15:40 +03:00
|
|
|
replacementSummary :: DiffSummary DiffInfo
|
2016-06-10 23:42:11 +03:00
|
|
|
replacementSummary = DiffSummary { patch = Replace (DiffInfo "string" "a") (DiffInfo "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
|
2016-06-10 23:42:11 +03:00
|
|
|
diffSummary testDiff `shouldBe` [ DiffSummary { patch = Insert (DiffInfo "string" "a"), parentAnnotations = [ ArrayLiteral ] } ]
|
2016-05-17 20:09:14 +03:00
|
|
|
describe "show" $ do
|
|
|
|
it "should print adds" $
|
2016-07-13 18:58:43 +03:00
|
|
|
show (pretty testSummary) `shouldBe` ("Added the 'a' string" :: Text)
|
2016-05-18 17:24:08 +03:00
|
|
|
it "prints a replacement" $ do
|
2016-07-13 18:58:43 +03:00
|
|
|
show (pretty replacementSummary) `shouldBe` ("Replaced the 'a' string with the 'b' symbol in the array context" :: Text)
|
2016-07-13 21:32:53 +03:00
|
|
|
prop "diff summaries of arbitrary diffs are identical" $
|
2016-07-14 18:52:40 +03:00
|
|
|
\a -> let
|
|
|
|
diff = (toDiff (a :: ArbitraryDiff Text (Record '[Category])))
|
|
|
|
summaries = diffSummary diff in
|
|
|
|
((() <$) . patch <$> summaries) `shouldBe` ((() <$) <$> toList diff)
|
2016-07-13 21:32:53 +03:00
|
|
|
|
|
|
|
parsePrettyDiff :: Text -> Maybe [DiffSummary DiffInfo]
|
|
|
|
parsePrettyDiff string = parseMaybe diffParser string
|
|
|
|
|
2016-07-14 18:52:40 +03:00
|
|
|
parsePatch :: Parsec Text (Patch DiffInfo)
|
|
|
|
parsePatch = (\x y z a -> case x of
|
|
|
|
"Added" -> Insert (DiffInfo (toS z) (toS a))
|
|
|
|
"Deleted" -> Delete (DiffInfo(toS z) (toS a))) <$> (string "Added" <|> string "Deleted") <*> (space *> string "the" <* space) <*> between (char '\'') (char '\'') (many printChar) <*> (space *> many printChar)
|
2016-07-13 21:32:53 +03:00
|
|
|
|
2016-07-14 18:52:40 +03:00
|
|
|
diffParser :: Parsec Text [(DiffSummary DiffInfo)]
|
|
|
|
diffParser = (DiffSummary <$> parsePatch <*> pure []) `sepBy` newline
|