1
1
mirror of https://github.com/github/semantic.git synced 2024-11-29 02:44:36 +03:00
semantic/test/DiffSpec.hs
2017-05-11 09:30:15 -04:00

39 lines
1.2 KiB
Haskell

{-# LANGUAGE DataKinds #-}
module DiffSpec where
import Category
import Data.Bifunctor.Join
import Data.Functor.Listable
import RWS
import Data.String
import Diff
import Info
import Interpreter
import Patch
import Prologue
import SpecHelpers
import Term
import Test.Hspec
import Test.Hspec.LeanCheck
spec :: Spec
spec = parallel $ do
let decorate = defaultFeatureVectorDecorator (category . headF)
prop "equality is reflexive" $
\ a -> let diff = unListableDiff a :: SyntaxDiff String '[Category] in
diff `shouldBe` diff
prop "equal terms produce identity diffs" $
\ a -> let term = decorate (unListableF a :: SyntaxTerm String '[Category]) in
diffCost (diffTerms term term) `shouldBe` 0
describe "beforeTerm" $ do
prop "recovers the before term" $
\ a b -> let diff = stripDiff $ diffTerms (decorate (unListableF a)) (decorate (unListableF b :: SyntaxTerm String '[Category])) in
beforeTerm diff `shouldBe` Just (unListableF a)
describe "afterTerm" $ do
prop "recovers the after term" $
\ a b -> let diff = stripDiff $ diffTerms (decorate (unListableF a)) (decorate (unListableF b :: SyntaxTerm String '[Category])) in
afterTerm diff `shouldBe` Just (unListableF b)