2016-08-05 02:19:03 +03:00
|
|
|
{-# LANGUAGE DataKinds #-}
|
2017-11-27 21:48:43 +03:00
|
|
|
module Diffing.Algorithm.RWS.Spec where
|
2016-06-23 00:59:28 +03:00
|
|
|
|
2018-03-08 04:01:47 +03:00
|
|
|
import Data.Abstract.FreeVariables
|
2017-11-27 22:32:13 +03:00
|
|
|
import Analysis.Decorator
|
2017-06-15 16:46:51 +03:00
|
|
|
import Data.Array.IArray
|
2017-02-24 00:13:42 +03:00
|
|
|
import Data.Bifunctor
|
2017-09-27 19:41:41 +03:00
|
|
|
import Data.Diff
|
2017-09-26 16:48:59 +03:00
|
|
|
import Data.Functor.Listable (ListableSyntax)
|
2016-08-05 02:19:03 +03:00
|
|
|
import Data.Record
|
2017-09-26 16:44:42 +03:00
|
|
|
import qualified Data.Syntax as Syntax
|
2017-09-27 19:37:37 +03:00
|
|
|
import Data.Term
|
2017-02-23 22:17:52 +03:00
|
|
|
import Data.These
|
2017-09-26 16:44:42 +03:00
|
|
|
import Data.Union
|
2017-11-27 21:36:00 +03:00
|
|
|
import Diffing.Algorithm
|
2017-11-27 19:51:39 +03:00
|
|
|
import Diffing.Algorithm.RWS
|
2017-11-27 19:45:08 +03:00
|
|
|
import Diffing.Interpreter
|
2016-06-23 00:59:28 +03:00
|
|
|
import Test.Hspec
|
2017-01-08 07:27:01 +03:00
|
|
|
import Test.Hspec.LeanCheck
|
2016-06-23 00:59:28 +03:00
|
|
|
|
|
|
|
spec :: Spec
|
|
|
|
spec = parallel $ do
|
2016-08-10 18:32:42 +03:00
|
|
|
let positively = succ . abs
|
2016-08-09 23:23:38 +03:00
|
|
|
describe "pqGramDecorator" $ do
|
2016-08-10 16:05:12 +03:00
|
|
|
prop "produces grams with stems of the specified length" $
|
2017-09-26 16:48:59 +03:00
|
|
|
\ (term, p, q) -> pqGramDecorator constructorNameAndConstantFields (positively p) (positively q) (term :: Term ListableSyntax (Record '[])) `shouldSatisfy` all ((== positively p) . length . stem . rhead)
|
2016-06-23 00:59:28 +03:00
|
|
|
|
2016-08-10 16:05:12 +03:00
|
|
|
prop "produces grams with bases of the specified width" $
|
2017-09-26 16:48:59 +03:00
|
|
|
\ (term, p, q) -> pqGramDecorator constructorNameAndConstantFields (positively p) (positively q) (term :: Term ListableSyntax (Record '[])) `shouldSatisfy` all ((== positively q) . length . base . rhead)
|
2016-06-23 00:59:28 +03:00
|
|
|
|
2016-06-27 22:37:32 +03:00
|
|
|
describe "rws" $ do
|
2017-01-08 07:27:01 +03:00
|
|
|
prop "produces correct diffs" $
|
2017-09-26 16:48:59 +03:00
|
|
|
\ (as, bs) -> let tas = decorate <$> (as :: [Term ListableSyntax (Record '[])])
|
|
|
|
tbs = decorate <$> (bs :: [Term ListableSyntax (Record '[])])
|
2017-09-26 16:44:42 +03:00
|
|
|
wrap = termIn Nil . inj
|
2017-10-03 22:10:11 +03:00
|
|
|
diff = merge (Nil, Nil) (inj (stripDiff . diffThese <$> rws comparableTerms (equalTerms comparableTerms) tas tbs)) in
|
2017-09-26 16:44:42 +03:00
|
|
|
(beforeTerm diff, afterTerm diff) `shouldBe` (Just (wrap (stripTerm <$> tas)), Just (wrap (stripTerm <$> tbs)))
|
2016-08-11 18:53:51 +03:00
|
|
|
|
2016-08-12 18:59:09 +03:00
|
|
|
it "produces unbiased insertions within branches" $
|
2018-03-08 04:01:47 +03:00
|
|
|
let (a, b) = (decorate (termIn Nil (inj [ termIn Nil (inj (Syntax.Identifier (name "a"))) ])), decorate (termIn Nil (inj [ termIn Nil (inj (Syntax.Identifier (name "b"))) ]))) in
|
2017-10-03 22:10:11 +03:00
|
|
|
fmap (bimap stripTerm stripTerm) (rws comparableTerms (equalTerms comparableTerms) [ b ] [ a, b ]) `shouldBe` fmap (bimap stripTerm stripTerm) [ That a, These b b ]
|
2017-02-24 00:13:42 +03:00
|
|
|
|
2017-09-26 16:44:42 +03:00
|
|
|
where decorate = defaultFeatureVectorDecorator constructorNameAndConstantFields
|
2017-02-24 00:13:42 +03:00
|
|
|
|
|
|
|
diffThese = these deleting inserting replacing
|