2015-12-17 21:08:47 +03:00
module SplitSpec where
import Test.Hspec
import Split
import qualified Data.Set as Set
import Diff
import Range
import Test.Hspec.QuickCheck
import Test.QuickCheck hiding ( Fixed )
import Control.Comonad.Cofree
import Control.Monad.Free hiding ( unfold )
2015-12-21 21:00:46 +03:00
import qualified Data.Maybe as Maybe
2015-12-17 21:08:47 +03:00
import Patch
import Syntax
2015-12-21 17:58:20 +03:00
instance Arbitrary a => Arbitrary ( Row a ) where
2015-12-17 21:08:47 +03:00
arbitrary = oneof [
Row <$> arbitrary <*> arbitrary ]
instance Arbitrary HTML where
arbitrary = oneof [
Text <$> arbitrary ,
Span <$> arbitrary <*> arbitrary ,
const Break <$> ( arbitrary :: Gen () ) ]
2015-12-21 17:58:20 +03:00
instance Arbitrary a => Arbitrary ( Line a ) where
2015-12-17 21:08:47 +03:00
arbitrary = oneof [
Line <$> arbitrary <*> arbitrary ,
const EmptyLine <$> ( arbitrary :: Gen () ) ]
spec :: Spec
spec = do
describe " annotatedToRows " $ do
it " outputs one row for single-line unchanged leaves " $
2015-12-22 03:44:07 +03:00
annotatedToRows ( unchanged " a " " leaf " ( Leaf " " ) ) " a " " a " ` shouldBe ` [ Row ( Line False [ span " a " ] ) ( Line False [ span " a " ] ) ]
2015-12-17 21:08:47 +03:00
it " outputs one row for single-line empty unchanged indexed nodes " $
2015-12-22 03:44:07 +03:00
annotatedToRows ( unchanged " [] " " branch " ( Indexed [] ) ) " [] " " [] " ` shouldBe ` [ Row ( Line False [ Ul ( Just " category-branch " ) [ Text " [] " ] ] ) ( Line False [ Ul ( Just " category-branch " ) [ Text " [] " ] ] ) ]
2015-12-17 21:08:47 +03:00
it " outputs one row for single-line non-empty unchanged indexed nodes " $
annotatedToRows ( unchanged " [ a, b ] " " branch " ( Indexed [
Free . offsetAnnotated 2 2 $ unchanged " a " " leaf " ( Leaf " " ) ,
Free . offsetAnnotated 5 5 $ unchanged " b " " leaf " ( Leaf " " )
2015-12-22 03:44:07 +03:00
] ) ) " [ a, b ] " " [ a, b ] " ` shouldBe ` [ Row ( Line False [ Ul ( Just " category-branch " ) [ Text " [ " , span " a " , Text " , " , span " b " , Text " ] " ] ] ) ( Line False [ Ul ( Just " category-branch " ) [ Text " [ " , span " a " , Text " , " , span " b " , Text " ] " ] ] ) ]
2015-12-17 21:08:47 +03:00
it " outputs one row for single-line non-empty formatted indexed nodes " $
annotatedToRows ( formatted " [ a, b ] " " [ a, b ] " " branch " ( Indexed [
Free . offsetAnnotated 2 2 $ unchanged " a " " leaf " ( Leaf " " ) ,
Free . offsetAnnotated 5 6 $ unchanged " b " " leaf " ( Leaf " " )
2015-12-22 03:44:07 +03:00
] ) ) " [ a, b ] " " [ a, b ] " ` shouldBe ` [ Row ( Line False [ Ul ( Just " category-branch " ) [ Text " [ " , span " a " , Text " , " , span " b " , Text " ] " ] ] ) ( Line False [ Ul ( Just " category-branch " ) [ Text " [ " , span " a " , Text " , " , span " b " , Text " ] " ] ] ) ]
2015-12-17 21:08:47 +03:00
it " outputs two rows for two-line non-empty unchanged indexed nodes " $
annotatedToRows ( unchanged " [ a, \ n b ] " " branch " ( Indexed [
Free . offsetAnnotated 2 2 $ unchanged " a " " leaf " ( Leaf " " ) ,
Free . offsetAnnotated 5 5 $ unchanged " b " " leaf " ( Leaf " " )
] ) ) " [ a, \ n b ] " " [ a, \ n b ] " ` shouldBe `
2015-12-22 03:44:07 +03:00
[
2015-12-17 21:08:47 +03:00
Row ( Line False [ Ul ( Just " category-branch " ) [ Text " [ " , span " a " , Text " , " , Break ] ] )
( Line False [ Ul ( Just " category-branch " ) [ Text " [ " , span " a " , Text " , " , Break ] ] ) ,
Row ( Line False [ Ul ( Just " category-branch " ) [ span " b " , Text " ] " ] ] )
( Line False [ Ul ( Just " category-branch " ) [ span " b " , Text " ] " ] ] )
2015-12-22 03:44:07 +03:00
]
2015-12-17 21:08:47 +03:00
it " outputs two rows for two-line non-empty formatted indexed nodes " $
annotatedToRows ( formatted " [ a, \ n b ] " " [ \ n a, \ n b ] " " branch " ( Indexed [
Free . offsetAnnotated 2 2 $ unchanged " a " " leaf " ( Leaf " " ) ,
Free . offsetAnnotated 5 5 $ unchanged " b " " leaf " ( Leaf " " )
] ) ) " [ a, \ n b ] " " [ \ n a, \ n b ] " ` shouldBe `
2015-12-22 03:44:07 +03:00
[
2015-12-17 21:08:47 +03:00
Row ( Line False [ Ul ( Just " category-branch " ) [ Text " [ " , span " a " , Text " , " , Break ] ] )
( Line False [ Ul ( Just " category-branch " ) [ Text " [ " , Break ] ] ) ,
Row EmptyLine
( Line False [ Ul ( Just " category-branch " ) [ span " a " , Text " , " , Break ] ] ) ,
Row ( Line False [ Ul ( Just " category-branch " ) [ span " b " , Text " ] " ] ] )
( Line False [ Ul ( Just " category-branch " ) [ span " b " , Text " ] " ] ] )
2015-12-22 03:44:07 +03:00
]
2015-12-17 21:08:47 +03:00
it " " $
let ( sourceA , sourceB ) = ( " [ \ n a \ n , \ n b] " , " [a,b] " ) in
annotatedToRows ( formatted sourceA sourceB " branch " ( Indexed [
Free . offsetAnnotated 2 1 $ unchanged " a " " leaf " ( Leaf " " ) ,
Free . offsetAnnotated 6 3 $ unchanged " b " " leaf " ( Leaf " " )
] ) ) sourceA sourceB ` shouldBe `
2015-12-22 03:44:07 +03:00
[
2015-12-17 21:08:47 +03:00
Row ( Line False [ Ul ( Just " category-branch " ) [ Text " [ " , Break ] ] )
( Line False [ Ul ( Just " category-branch " ) [ Text " [ " , span " a " , Text " , " , span " b " , Text " ] " ] ] ) ,
Row ( Line False [ Ul ( Just " category-branch " ) [ span " a " , Break ] ] )
EmptyLine ,
Row ( Line False [ Ul ( Just " category-branch " ) [ Text " , " , Break ] ] )
EmptyLine ,
Row ( Line False [ Ul ( Just " category-branch " ) [ span " b " , Text " ] " ] ] )
EmptyLine
2015-12-22 03:44:07 +03:00
]
2015-12-17 21:08:47 +03:00
it " should split multi-line deletions across multiple rows " $
let ( sourceA , sourceB ) = ( " /* \ n */ \ n a " , " a " ) in
annotatedToRows ( formatted sourceA sourceB " branch " ( Indexed [
2015-12-21 21:01:46 +03:00
Pure . Delete $ ( Info ( Range 0 5 ) ( Set . fromList [ " leaf " ] ) :< Leaf " " ) ,
2015-12-17 21:08:47 +03:00
Free . offsetAnnotated 6 0 $ unchanged " a " " leaf " ( Leaf " " )
] ) ) sourceA sourceB ` shouldBe `
2015-12-22 03:44:07 +03:00
[
2015-12-17 21:08:47 +03:00
Row ( Line True [ Ul ( Just " category-branch " ) [ Div ( Just " delete " ) [ span " /* " , Break ] ] ] ) EmptyLine ,
Row ( Line True [ Ul ( Just " category-branch " ) [ Div ( Just " delete " ) [ span " */ " ] , Break ] ] ) EmptyLine ,
Row ( Line False [ Ul ( Just " category-branch " ) [ span " a " ] ] ) ( Line False [ Ul ( Just " category-branch " ) [ span " a " ] ] )
2015-12-22 03:44:07 +03:00
]
2015-12-17 21:08:47 +03:00
describe " unicode " $
it " equivalent precomposed and decomposed characters are not equal " $
let ( sourceA , sourceB ) = ( " t \ 776 " , " \ 7831 " )
2015-12-21 21:01:46 +03:00
syntax = Leaf . Pure $ Replace ( info sourceA " leaf " :< Leaf " " ) ( info sourceB " leaf " :< Leaf " " )
2015-12-17 21:08:47 +03:00
in
annotatedToRows ( formatted sourceA sourceB " leaf " syntax ) sourceA sourceB ` shouldBe `
2015-12-22 03:44:07 +03:00
[ Row ( Line False [ span " t \ 776 " ] ) ( Line False [ span " \ 7831 " ] ) ]
2015-12-17 21:08:47 +03:00
2015-12-21 20:57:50 +03:00
describe " adjoinRowsBy " $ do
2015-12-17 21:08:47 +03:00
prop " is identity on top of no rows " $
2015-12-21 20:57:50 +03:00
\ a -> adjoinRowsBy openElement [] a == [ a ]
2015-12-17 21:08:47 +03:00
2015-12-18 21:04:52 +03:00
prop " appends onto open rows " $
2015-12-21 21:01:46 +03:00
forAll ( ( arbitrary ` suchThat ` isOpen ) >>= \ a -> ( , ) a <$> ( arbitrary ` suchThat ` isOpen ) ) $
2015-12-18 21:04:52 +03:00
\ ( a @ ( Row ( Line ac1 as1 ) ( Line bc1 bs1 ) ) , b @ ( Row ( Line ac2 as2 ) ( Line bc2 bs2 ) ) ) ->
2015-12-21 20:57:50 +03:00
adjoinRowsBy openElement [ a ] b ` shouldBe ` [ Row ( Line ( ac1 || ac2 ) $ as1 ++ as2 ) ( Line ( bc1 || bc2 ) $ bs1 ++ bs2 ) ]
2015-12-18 20:11:01 +03:00
2015-12-18 21:19:40 +03:00
prop " does not append onto closed rows " $
2015-12-21 21:01:46 +03:00
forAll ( ( arbitrary ` suchThat ` isClosed ) >>= \ a -> ( , ) a <$> ( arbitrary ` suchThat ` isClosed ) ) $
2015-12-21 20:57:50 +03:00
\ ( a , b ) -> adjoinRowsBy openElement [ a ] b ` shouldBe ` [ b , a ]
2015-12-18 21:19:40 +03:00
2015-12-18 21:27:03 +03:00
prop " does not promote elements through empty lines onto closed lines " $
2015-12-21 21:01:46 +03:00
forAll ( ( arbitrary ` suchThat ` isClosed ) >>= \ a -> ( , ) a <$> ( arbitrary ` suchThat ` isClosed ) ) $
2015-12-21 20:57:50 +03:00
\ ( a , b ) -> adjoinRowsBy openElement [ Row EmptyLine EmptyLine , a ] b ` shouldBe ` [ b , Row EmptyLine EmptyLine , a ]
2015-12-18 21:27:03 +03:00
2015-12-18 21:58:02 +03:00
prop " promotes elements through empty lines onto open lines " $
2015-12-21 21:01:46 +03:00
forAll ( ( arbitrary ` suchThat ` isOpen ) >>= \ a -> ( , ) a <$> ( arbitrary ` suchThat ` isOpen ) ) $
2015-12-21 20:57:50 +03:00
\ ( a , b ) -> adjoinRowsBy openElement [ Row EmptyLine EmptyLine , a ] b ` shouldBe ` Row EmptyLine EmptyLine : adjoinRowsBy openElement [ a ] b
2015-12-18 21:58:02 +03:00
2015-12-17 21:08:47 +03:00
describe " termToLines " $ do
it " splits multi-line terms into multiple lines " $
2015-12-21 21:01:46 +03:00
termToLines ( Info ( Range 0 5 ) ( Set . singleton " leaf " ) :< Leaf " " ) " /* \ n */ "
2015-12-17 21:08:47 +03:00
` shouldBe `
( [
Line True [ span " /* " , Break ] ,
Line True [ span " */ " ]
] , Range 0 5 )
2015-12-22 03:54:40 +03:00
describe " splitTermByLines " $ do
it " splits multi-line terms into multiple lines " $
2015-12-22 04:02:17 +03:00
splitTermByLines ( Info ( Range 0 5 ) mempty :< Leaf " " ) " /* \ n */ "
2015-12-22 03:54:40 +03:00
` shouldBe `
( [
2015-12-22 04:02:17 +03:00
Line True [ Info ( Range 0 3 ) mempty :< Leaf " " ] ,
Line True [ Info ( Range 3 5 ) mempty :< Leaf " " ]
2015-12-22 03:54:40 +03:00
] , Range 0 5 )
2015-12-21 18:01:00 +03:00
describe " openLineBy " $ do
2015-12-17 21:08:47 +03:00
it " should produce the earliest non-empty line in a list, if open " $
2015-12-21 18:01:00 +03:00
openLineBy openElement [
2015-12-17 21:08:47 +03:00
Line True [ Div ( Just " delete " ) [ span " */ " ] ] ,
Line True [ Div ( Just " delete " ) [ span " * Debugging " , Break ] ] ,
Line True [ Div ( Just " delete " ) [ span " /* " , Break ] ]
] ` shouldBe ` ( Just $ Line True [ Div ( Just " delete " ) [ span " */ " ] ] )
2015-12-22 04:04:05 +03:00
it " should produce the earliest non-empty line in a list, if open " $
openLineBy ( openTerm " \ n " ) [
Line True [ Info ( Range 1 2 ) mempty :< Leaf " " ] ,
Line True [ Info ( Range 0 1 ) mempty :< Leaf " " ]
] ` shouldBe ` ( Just $ Line True [ Info ( Range 1 2 ) mempty :< Leaf " " ] )
2015-12-17 21:08:47 +03:00
it " should return Nothing if the earliest non-empty line is closed " $
2015-12-21 18:01:00 +03:00
openLineBy openElement [
2015-12-17 21:08:47 +03:00
Line True [ Div ( Just " delete " ) [ span " * Debugging " , Break ] ]
] ` shouldBe ` Nothing
2015-12-22 04:04:05 +03:00
it " should return Nothing if the earliest non-empty line is closed " $
openLineBy ( openTerm " \ n " ) [
Line True [ Info ( Range 0 1 ) mempty :< Leaf " " ]
] ` shouldBe ` Nothing
2015-12-22 04:06:19 +03:00
describe " openTerm " $ do
2015-12-22 04:08:05 +03:00
it " returns Just the term if its substring does not end with a newline " $
let term = Info ( Range 0 2 ) mempty :< Leaf " " in openTerm " " term ` shouldBe ` Just term
2015-12-22 04:07:53 +03:00
it " returns Nothing for terms whose substring ends with a newline " $
2015-12-22 04:06:19 +03:00
openTerm " \ n " ( Info ( Range 0 2 ) mempty :< Leaf " " ) ` shouldBe ` Nothing
2015-12-17 21:08:47 +03:00
where
rightRowText text = rightRow [ Text text ]
rightRow xs = Row EmptyLine ( Line False xs )
leftRowText text = leftRow [ Text text ]
leftRow xs = Row ( Line False xs ) EmptyLine
rowText a b = Row ( Line False [ Text a ] ) ( Line False [ Text b ] )
info source category = Info ( totalRange source ) ( Set . fromList [ category ] )
2015-12-21 21:01:38 +03:00
unchanged source = formatted source source
2015-12-17 21:08:47 +03:00
formatted source1 source2 category = Annotated ( info source1 category , info source2 category )
offsetInfo by ( Info ( Range start end ) categories ) = Info ( Range ( start + by ) ( end + by ) ) categories
offsetAnnotated by1 by2 ( Annotated ( left , right ) syntax ) = Annotated ( offsetInfo by1 left , offsetInfo by2 right ) syntax
span = Span ( Just " category-leaf " )
2015-12-21 21:03:08 +03:00
isOpen ( Row a b ) = Maybe . isJust ( openLineBy openElement [ a ] ) && Maybe . isJust ( openLineBy openElement [ b ] )
isClosed ( Row a @ ( Line _ _ ) b @ ( Line _ _ ) ) = Maybe . isNothing ( openLineBy openElement [ a ] ) && Maybe . isNothing ( openLineBy openElement [ b ] )
2015-12-18 21:19:05 +03:00
isClosed ( Row _ _ ) = False