1
1
mirror of https://github.com/github/semantic.git synced 2024-12-20 21:31:48 +03:00
semantic/test/Data/RandomWalkSimilarity/Spec.hs

27 lines
1.1 KiB
Haskell
Raw Normal View History

2016-06-23 16:52:15 +03:00
{-# LANGUAGE DataKinds #-}
module Data.RandomWalkSimilarity.Spec where
import Data.DList as DList hiding (toList)
import Data.RandomWalkSimilarity
import Data.RandomWalkSimilarity.Arbitrary ()
import Data.String
import Prologue
import Term
import Term.Arbitrary
import Test.Hspec
import Test.Hspec.QuickCheck
import Test.QuickCheck hiding (Fixed)
spec :: Spec
spec = parallel $ do
describe "pqGrams" $ do
2016-06-23 17:11:48 +03:00
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 String String) `shouldSatisfy` all ((== p) . length . stem)
2016-06-23 17:11:48 +03:00
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 String String) `shouldSatisfy` all ((== q) . length . base)
describe "featureVector" $ do
2016-06-23 17:11:48 +03:00
prop "produces a vector of the specified dimension" . forAll (arbitrary `suchThat` ((> 0) . snd)) $
\ (grams, d) -> length (featureVector (fromList (grams :: [Gram String])) d) `shouldBe` d