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

33 lines
1.0 KiB
Haskell

module TermSpec where
import ArbitraryTerm
import Data.String
import Data.Functor.Foldable
import Data.Text.Arbitrary ()
import Diff
import Interpreter
import Prologue
import Term.Arbitrary
import Test.Hspec
import Test.Hspec.QuickCheck
import Test.QuickCheck
spec :: Spec
spec = parallel $ do
describe "Term" $ do
prop "equality is reflexive" $
\ a -> toTerm a == toTerm (a :: ArbitraryTerm String ())
describe "ArbitraryTerm" $
prop "generates terms of a specific size" $ forAll ((arbitrary >>= \ n -> (,) n <$> termOfSize n) `suchThat` ((> 0) . fst)) $
\ (n, term) -> cata (succ . sum) (toTerm (term :: ArbitraryTerm String ())) `shouldBe` n
describe "Diff" $ do
prop "equality is reflexive" $
\ a b -> let diff = diffTerms (free . Free) (==) diffCost (toTerm a) (toTerm (b :: ArbitraryTerm String CategorySet)) in
diff == diff
prop "equal terms produce identity diffs" $
\ a -> let term = toTerm (a :: ArbitraryTerm String CategorySet) in
diffCost (diffTerms (free . Free) (==) diffCost term term) == 0