mirror of
https://github.com/github/semantic.git
synced 2024-12-25 07:55:12 +03:00
Correct the tests.
This commit is contained in:
parent
e6c81e1c22
commit
1a22eaebf6
@ -32,36 +32,36 @@ spec = parallel $ do
|
||||
describe "splitDiffByLines" $ do
|
||||
prop "preserves line counts in equal sources" $
|
||||
\ source ->
|
||||
length (splitDiffByLines (pure source) (Free $ Annotated (pure $ Info (totalRange source) mempty) (Indexed . Prelude.fst $ foldl combineIntoLeaves ([], 0) source))) `shouldBe` length (filter (== '\n') $ toString source) + 1
|
||||
length (splitDiffByLines (pure source) (Free $ Annotated (pure $ Info (totalRange source) mempty 1) (Indexed . Prelude.fst $ foldl combineIntoLeaves ([], 0) source))) `shouldBe` length (filter (== '\n') $ toString source) + 1
|
||||
|
||||
prop "produces the maximum line count in inequal sources" $
|
||||
\ sources ->
|
||||
length (splitDiffByLines sources (Free $ Annotated ((`Info` mempty) . totalRange <$> sources) (Indexed $ leafWithRangesInSources sources <$> runBothWith (zipWith both) (actualLineRanges <$> (totalRange <$> sources) <*> sources)))) `shouldBe` runBothWith max ((+ 1) . length . filter (== '\n') . toString <$> sources)
|
||||
length (splitDiffByLines sources (Free $ Annotated ((\ s -> Info (totalRange s) mempty 0) <$> sources) (Indexed $ leafWithRangesInSources sources <$> runBothWith (zipWith both) (actualLineRanges <$> (totalRange <$> sources) <*> sources)))) `shouldBe` runBothWith max ((+ 1) . length . filter (== '\n') . toString <$> sources)
|
||||
|
||||
describe "splitAbstractedTerm" $ do
|
||||
prop "preserves line count" $
|
||||
\ source -> let range = totalRange source in
|
||||
splitAbstractedTerm (:<) (Identity source) (Identity (Info range mempty)) (Leaf source) `shouldBe` (Identity . lineMap (fmap (((:< Leaf source) . (`Info` mempty) &&& id))) <$> linesInRangeOfSource range source)
|
||||
splitAbstractedTerm (:<) (Identity source) (Identity (Info range mempty 1)) (Leaf source) `shouldBe` (Identity . lineMap (fmap (((:< Leaf source) . (\ r -> Info r mempty 1) &&& id))) <$> linesInRangeOfSource range source)
|
||||
|
||||
let makeTerm = ((Free .) . Annotated) :: Info -> Syntax (Source Char) (SplitDiff (Source Char) Info) -> SplitDiff (Source Char) Info
|
||||
prop "outputs one row for single-line unchanged leaves" $
|
||||
forAll (arbitraryLeaf `suchThat` isOnSingleLine) $
|
||||
\ (source, info@(Info range categories), syntax) -> splitAbstractedTerm makeTerm (pure source) (pure $ Info range categories) syntax `shouldBe` fromList [
|
||||
\ (source, info@(Info range categories size), syntax) -> splitAbstractedTerm makeTerm (pure source) (pure $ Info range categories size) syntax `shouldBe` fromList [
|
||||
both (pure (makeTerm info $ Leaf source, Range 0 (length source))) (pure (makeTerm info $ Leaf source, Range 0 (length source))) ]
|
||||
|
||||
prop "outputs one row for single-line empty unchanged indexed nodes" $
|
||||
forAll (arbitrary `suchThat` (\ a -> filter (/= '\n') (toString a) == toString a)) $
|
||||
\ source -> splitAbstractedTerm makeTerm (pure source) (pure $ Info (totalRange source) mempty) (Indexed []) `shouldBe` fromList [
|
||||
both (pure (makeTerm (Info (totalRange source) mempty) $ Indexed [], Range 0 (length source))) (pure (makeTerm (Info (totalRange source) mempty) $ Indexed [], Range 0 (length source))) ]
|
||||
\ source -> splitAbstractedTerm makeTerm (pure source) (pure $ Info (totalRange source) mempty 1) (Indexed []) `shouldBe` fromList [
|
||||
both (pure (makeTerm (Info (totalRange source) mempty 1) $ Indexed [], Range 0 (length source))) (pure (makeTerm (Info (totalRange source) mempty 1) $ Indexed [], Range 0 (length source))) ]
|
||||
|
||||
where
|
||||
isOnSingleLine (a, _, _) = filter (/= '\n') (toString a) == toString a
|
||||
|
||||
combineIntoLeaves (leaves, start) char = (leaves ++ [ Free $ Annotated (Info <$> pure (Range start $ start + 1) <*> mempty) (Leaf [ char ]) ], start + 1)
|
||||
combineIntoLeaves (leaves, start) char = (leaves ++ [ Free $ Annotated (Info <$> pure (Range start $ start + 1) <*> mempty <*> pure 1) (Leaf [ char ]) ], start + 1)
|
||||
|
||||
leafWithRangesInSources sources ranges = Free $ Annotated (Info <$> ranges <*> pure mempty) (Leaf $ runBothWith (++) (toString <$> sources))
|
||||
leafWithRangesInSources sources ranges = Free $ Annotated (Info <$> ranges <*> pure mempty <*> pure 1) (Leaf $ runBothWith (++) (toString <$> sources))
|
||||
|
||||
leafWithRangeInSource source range = Info range mempty :< Leaf source
|
||||
leafWithRangeInSource source range = Info range mempty 1 :< Leaf source
|
||||
|
||||
patchWithBoth (Insert ()) = Insert . snd
|
||||
patchWithBoth (Delete ()) = Delete . fst
|
||||
|
@ -74,4 +74,4 @@ instance Arbitrary a => Arbitrary (Source a) where
|
||||
|
||||
arbitraryLeaf :: Gen (Source Char, Info, Syntax (Source Char) f)
|
||||
arbitraryLeaf = toTuple <$> arbitrary
|
||||
where toTuple string = (string, Info (Range 0 $ length string) mempty, Leaf string)
|
||||
where toTuple string = (string, Info (Range 0 $ length string) mempty 1, Leaf string)
|
||||
|
@ -1,5 +1,6 @@
|
||||
module InterpreterSpec where
|
||||
|
||||
import Diff
|
||||
import qualified Interpreter as I
|
||||
import Range
|
||||
import Syntax
|
||||
@ -14,8 +15,8 @@ spec :: Spec
|
||||
spec = parallel $ do
|
||||
describe "interpret" $ do
|
||||
it "returns a replacement when comparing two unicode equivalent terms" $
|
||||
I.interpret comparable (Info range mempty :< Leaf "t\776") (Info range2 mempty :< Leaf "\7831") `shouldBe`
|
||||
Pure (Replace (Info range mempty :< Leaf "t\776") (Info range2 mempty :< Leaf "\7831"))
|
||||
I.interpret comparable diffCost (Info range mempty 0 :< Leaf "t\776") (Info range2 mempty 0 :< Leaf "\7831") `shouldBe`
|
||||
Pure (Replace (Info range mempty 0 :< Leaf "t\776") (Info range2 mempty 0 :< Leaf "\7831"))
|
||||
|
||||
where
|
||||
range = Range 0 2
|
||||
|
@ -14,4 +14,4 @@ spec :: Spec
|
||||
spec = parallel $
|
||||
describe "hunks" $
|
||||
it "empty diffs have empty hunks" $
|
||||
hunks (Free . Annotated (pure (Info (Range 0 0) mempty)) $ Leaf "") (Both (SourceBlob (fromList "") "abcde" "path2.txt" (Just defaultPlainBlob), SourceBlob (fromList "") "xyz" "path2.txt" (Just defaultPlainBlob))) `shouldBe` [Hunk {offset = Both (0, 0), changes = [], trailingContext = []}]
|
||||
hunks (Free . Annotated (pure (Info (Range 0 0) mempty 1)) $ Leaf "") (Both (SourceBlob (fromList "") "abcde" "path2.txt" (Just defaultPlainBlob), SourceBlob (fromList "") "xyz" "path2.txt" (Just defaultPlainBlob))) `shouldBe` [Hunk {offset = Both (0, 0), changes = [], trailingContext = []}]
|
||||
|
@ -17,9 +17,9 @@ spec = parallel $ do
|
||||
|
||||
describe "Diff" $ do
|
||||
prop "equality is reflexive" $
|
||||
\ a b -> let diff = interpret comparable (unTerm a) (unTerm (b :: ArbitraryTerm String CategorySet)) in
|
||||
\ a b -> let diff = interpret comparable diffCost (unTerm a) (unTerm (b :: ArbitraryTerm String CategorySet)) in
|
||||
diff == diff
|
||||
|
||||
prop "equal terms produce identity diffs" $
|
||||
\ a -> let term = unTerm (a :: ArbitraryTerm String CategorySet) in
|
||||
diffCost (interpret comparable term term) == 0
|
||||
diffCost (interpret comparable diffCost term term) == 0
|
||||
|
Loading…
Reference in New Issue
Block a user