1
1
mirror of https://github.com/github/semantic.git synced 2024-12-29 18:06:14 +03:00

Test that pqGrams produces grams with stems of length p.

This commit is contained in:
Rob Rix 2016-06-22 11:27:30 -04:00
parent 4cb3261069
commit 7da6fde412

View File

@ -1,18 +1,28 @@
module Data.Gram.Spec where
import Data.DList as DList
import Control.Arrow ((&&&))
import Data.DList as DList hiding (toList)
import Data.Gram
import Data.Gram.Arbitrary ()
import Data.String
import Prologue
import Syntax
import Term
import Term.Arbitrary
import Test.Hspec
import Test.Hspec.QuickCheck
import Test.QuickCheck
import Test.QuickCheck hiding (Fixed)
spec :: Spec
spec = parallel $ do
describe "pqGrams" $
it "exists" pending
let getChildren (_ :< f) = case f of
Leaf _ -> []
Indexed c -> c
Fixed c -> c
Keyed c -> toList c in
prop "produces grams with stems of the specified length" $ forAll (arbitrary `suchThat` ((> 0) . fst . snd)) $
\ (term, (p, q)) -> pqGrams p q (headF &&& getChildren) (toTerm term :: Term String String) `shouldSatisfy` all ((<= p) . length . stem)
describe "featureVector" $ do
prop "produces a vector of the specified dimension" $ forAll (arbitrary `suchThat` ((> 0) . snd)) $