1
1
mirror of https://github.com/github/semantic.git synced 2024-11-29 02:44:36 +03:00
semantic/test/AlignmentSpec.hs

115 lines
5.9 KiB
Haskell
Raw Normal View History

2016-02-28 22:05:19 +03:00
module AlignmentSpec where
import Test.Hspec
import Test.Hspec.QuickCheck
import Test.QuickCheck hiding (Fixed)
import Data.Text.Arbitrary ()
import Alignment
import ArbitraryTerm (arbitraryLeaf)
import Control.Arrow
import Control.Comonad.Cofree
import Control.Monad.Free hiding (unfold)
import Data.Adjoined
import Data.Bifunctor.Join
import Data.Bifunctor.These
2016-03-03 19:39:23 +03:00
import Data.Copointed
import Data.Functor.Both as Both
import Diff
import qualified Data.Maybe as Maybe
2015-12-30 18:26:40 +03:00
import Data.Functor.Identity
2015-12-23 01:22:07 +03:00
import Line
2016-03-03 22:59:33 +03:00
import Patch
2016-03-01 03:39:04 +03:00
import Prelude hiding (fst, snd)
import qualified Prelude
import Range
import Source hiding ((++), fromList)
import qualified Source
import SplitDiff
import Syntax
spec :: Spec
spec = parallel $ do
describe "splitDiffByLines" $ do
prop "preserves line counts in equal sources" $
2015-12-22 23:55:59 +03:00
\ 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
prop "produces the maximum line count in inequal sources" $
2016-02-29 05:43:47 +03:00
\ 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)
2016-03-03 19:39:23 +03:00
describe "splitAbstractedTerm" $ do
prop "preserves line count" $
\ source -> let range = totalRange source in
2016-03-15 17:58:54 +03:00
splitAbstractedTerm (:<) (Identity source) (Identity (Info range mempty)) (Leaf source) `shouldBe` (Identity . lineMap (fmap (((:< Leaf source) . (`Info` mempty) &&& 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 [
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))) ]
describe "alignDiff" $ do
2016-03-24 20:44:57 +03:00
it "aligns identical branches on a single line" $
alignDiff (both (Source.fromList "[ foo ]") (Source.fromList "[ foo ]")) (pure (info 0 7) `branch` [ pure (info 2 5) `leaf` "foo" ]) `shouldBe`
[ Join (These (info 0 7 `branch` [ info 2 5 `leaf` "foo" ])
(info 0 7 `branch` [ info 2 5 `leaf` "foo" ])) ]
2016-03-24 20:44:57 +03:00
it "aligns identical branches spanning multiple lines" $
alignDiff (both (Source.fromList "[\nfoo\n]") (Source.fromList "[\nfoo\n]")) (pure (info 0 7) `branch` [ pure (info 2 5) `leaf` "foo" ]) `shouldBe`
[ Join (These (info 0 2 `branch` [])
(info 0 2 `branch` []))
, Join (These (info 2 6 `branch` [ info 2 5 `leaf` "foo" ])
(info 2 6 `branch` [ info 2 5 `leaf` "foo" ]))
, Join (These (info 6 7 `branch` [])
(info 6 7 `branch` []))
]
2016-03-24 20:44:57 +03:00
it "aligns reformatted branches" $
alignDiff (both (Source.fromList "[ foo ]") (Source.fromList "[\nfoo\n]")) (pure (info 0 7) `branch` [ pure (info 2 5) `leaf` "foo" ]) `shouldBe`
2016-03-22 07:17:20 +03:00
[ Join (These (info 0 7 `branch` [ info 2 5 `leaf` "foo" ])
(info 0 2 `branch` []))
, Join (That (info 2 6 `branch` [ info 2 5 `leaf` "foo" ]))
, Join (That (info 6 7 `branch` []))
]
2016-03-24 20:44:57 +03:00
it "aligns nodes following reformatted branches" $
alignDiff (both (Source.fromList "[ foo ]\nbar\n") (Source.fromList "[\nfoo\n]\nbar\n")) (pure (info 0 12) `branch` [ pure (info 0 7) `branch` [ pure (info 2 5) `leaf` "foo" ], pure (info 8 11) `leaf` "bar" ]) `shouldBe`
2016-03-22 07:17:20 +03:00
[ Join (These (info 0 8 `branch` [ info 0 7 `branch` [ info 2 5 `leaf` "foo" ] ])
(info 0 2 `branch` [ info 0 2 `branch` [] ]))
, Join (That (info 2 6 `branch` [ info 2 6 `branch` [ info 2 5 `leaf` "foo" ] ]))
, Join (That (info 6 8 `branch` [ info 6 7 `branch` [] ]))
, Join (These (info 8 12 `branch` [ info 8 11 `leaf` "bar" ])
(info 8 12 `branch` [ info 8 11 `leaf` "bar" ]))
, Join (These (info 12 12 `branch` [])
(info 12 12 `branch` []))
]
where
isOnSingleLine (a, _, _) = filter (/= '\n') (toString a) == toString a
2016-03-08 00:33:30 +03:00
combineIntoLeaves (leaves, start) char = (leaves ++ [ Free $ Annotated (Info <$> pure (Range start $ start + 1) <*> mempty) (Leaf [ char ]) ], start + 1)
leafWithRangesInSources sources ranges = Free $ Annotated (Info <$> ranges <*> pure mempty) (Leaf $ runBothWith (++) (toString <$> sources))
2015-12-23 00:52:20 +03:00
2016-03-08 00:33:30 +03:00
leafWithRangeInSource source range = Info range mempty :< Leaf source
patchWithBoth (Insert ()) = Insert . snd
patchWithBoth (Delete ()) = Delete . fst
patchWithBoth (Replace () ()) = runBothWith Replace
2016-03-22 01:54:09 +03:00
branch :: annotation -> [Free (Annotated String annotation) patch] -> Free (Annotated String annotation) patch
branch annotation = Free . Annotated annotation . Indexed
leaf :: annotation -> String -> Free (Annotated String annotation) patch
leaf info = Free . Annotated info . Leaf
2016-03-22 01:54:09 +03:00
info :: Int -> Int -> Info
info = ((`Info` mempty) .) . Range