1
1
mirror of https://github.com/github/semantic.git synced 2024-11-24 08:54:07 +03:00
semantic/test/InterpreterSpec.hs

40 lines
1.7 KiB
Haskell
Raw Normal View History

{-# LANGUAGE DataKinds #-}
module InterpreterSpec where
2017-09-27 19:41:41 +03:00
import Data.Diff
2017-06-01 18:10:47 +03:00
import Data.Functor.Both
2017-01-19 23:53:16 +03:00
import Data.Functor.Foldable hiding (Nil)
import Data.Functor.Listable
import Data.Record
import qualified Data.Syntax as Syntax
2017-09-27 19:37:37 +03:00
import Data.Term
import Data.Union
import Interpreter
import Test.Hspec (Spec, describe, it, parallel)
import Test.Hspec.Expectations.Pretty
import Test.Hspec.LeanCheck
spec :: Spec
spec = parallel $ do
describe "interpret" $ do
it "returns a replacement when comparing two unicode equivalent terms" $
let termA = termIn Nil (inj (Syntax.Identifier "t\776"))
termB = termIn Nil (inj (Syntax.Identifier "\7831")) in
diffTerms termA termB `shouldBe` replacing termA (termB :: Term ListableSyntax (Record '[]))
prop "produces correct diffs" $
\ a b -> let diff = diffTerms a b :: Diff ListableSyntax (Record '[]) (Record '[]) in
2017-09-14 02:34:27 +03:00
(beforeTerm diff, afterTerm diff) `shouldBe` (Just a, Just b)
prop "constructs zero-cost diffs of equal terms" $
\ a -> let diff = diffTerms a a :: Diff ListableSyntax (Record '[]) (Record '[]) in
diffCost diff `shouldBe` 0
it "produces unbiased insertions within branches" $
let term s = termIn Nil (inj [ termIn Nil (inj (Syntax.Identifier s)) ]) :: Term ListableSyntax (Record '[])
wrap = termIn Nil . inj in
2017-09-28 17:40:23 +03:00
diffTerms (wrap [ term "b" ]) (wrap [ term "a", term "b" ]) `shouldBe` merge (Nil, Nil) (inj [ inserting (term "a"), merging (term "b") ])
prop "compares nodes against context" $
\ a b -> diffTerms a (termIn Nil (inj (Syntax.Context (pure b) a))) `shouldBe` insertF (In Nil (inj (Syntax.Context (pure (inserting b)) (merging (a :: Term ListableSyntax (Record '[]))))))