1
1
mirror of https://github.com/github/semantic.git synced 2024-12-21 13:51:44 +03:00
semantic/test/Data/RandomWalkSimilarity/Spec.hs
2016-06-27 15:37:32 -04:00

37 lines
1.6 KiB
Haskell

{-# LANGUAGE DataKinds #-}
module Data.RandomWalkSimilarity.Spec where
import Data.DList as DList hiding (toList)
import Data.Functor.Both
import Data.RandomWalkSimilarity
import Data.RandomWalkSimilarity.Arbitrary ()
import Diff
import Patch
import Prologue
import Syntax
import Term
import Term.Arbitrary
import Test.Hspec
import Test.Hspec.QuickCheck
import Test.QuickCheck
spec :: Spec
spec = parallel $ do
describe "pqGrams" $ do
prop "produces grams with stems of the specified length" . forAll (arbitrary `suchThat` (\ (_, p, q) -> p > 0 && q > 0)) $
\ (term, p, q) -> pqGrams p q identity (toTerm term :: Term Text Text) `shouldSatisfy` all ((== p) . length . stem)
prop "produces grams with bases of the specified length" . forAll (arbitrary `suchThat` (\ (_, p, q) -> p > 0 && q > 0)) $
\ (term, p, q) -> pqGrams p q identity (toTerm term :: Term Text Text) `shouldSatisfy` all ((== q) . length . base)
describe "featureVector" $ do
prop "produces a vector of the specified dimension" . forAll (arbitrary `suchThat` ((> 0) . Prologue.snd)) $
\ (grams, d) -> length (featureVector d (fromList (grams :: [Gram Text]))) `shouldBe` d
describe "rws" $ do
prop "produces correct diffs" $
\ as bs -> let termA = cofree ("" :< Indexed (toTerm <$> as))
termB = cofree ("" :< Indexed (toTerm <$> bs))
diff = free (Free (both "" "" :< Indexed (rws ((Just .) . (pure .) . Replace) identity (toTerm <$> as) (toTerm <$> bs) :: [Diff Text Text]))) in
(beforeTerm diff, afterTerm diff) `shouldBe` (Just termA, Just termB)