1
1
mirror of https://github.com/github/semantic.git synced 2024-12-26 08:25:19 +03:00

The RWS specs don’t need to generate arbitrary vectors.

This commit is contained in:
Rob Rix 2016-08-10 09:38:41 -04:00
parent b6637828fa
commit f05570dd3e

View File

@ -1,11 +1,10 @@
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DataKinds #-}
module Data.RandomWalkSimilarity.Spec where module Data.RandomWalkSimilarity.Spec where
import Category
import Data.RandomWalkSimilarity import Data.RandomWalkSimilarity
import Data.Record import Data.Record
import qualified Data.Vector.Arbitrary as Vector
import Diff import Diff
import Info
import Patch import Patch
import Prologue import Prologue
import Syntax import Syntax
@ -31,10 +30,10 @@ spec = parallel $ do
describe "rws" $ do describe "rws" $ do
let compare a b = if extract a == extract b then Just (pure (Replace a b)) else Nothing let compare a b = if extract a == extract b then Just (pure (Replace a b)) else Nothing
prop "produces correct diffs" . forAll (scale (`div` 4) arbitrary) $ prop "produces correct diffs" . forAll (scale (`div` 4) arbitrary) $
\ (as, bs) -> let tas = toTerm <$> as \ (as, bs) -> let tas = featureVectorDecorator (category . headF) 2 2 15 . toTerm <$> (as :: [ArbitraryTerm Text (Record '[Category])])
tbs = toTerm <$> bs tbs = featureVectorDecorator (category . headF) 2 2 15 . toTerm <$> (bs :: [ArbitraryTerm Text (Record '[Category])])
diff = free (Free (pure (Program .: Vector.singleton 0 .: RNil) :< Indexed (rws compare tas tbs :: [Diff Text (Record '[Category, Vector.Vector Double])]))) in diff = free (Free (pure (pure 0 .: Program .: RNil) :< Indexed (rws compare tas tbs))) in
(beforeTerm diff, afterTerm diff) `shouldBe` (Just (cofree ((Program .: Vector.singleton 0 .: RNil) :< Indexed tas)), Just (cofree ((Program .: Vector.singleton 0 .: RNil) :< Indexed tbs))) (beforeTerm diff, afterTerm diff) `shouldBe` (Just (cofree ((pure 0 .: Program .: RNil) :< Indexed tas)), Just (cofree ((pure 0 .: Program .: RNil) :< Indexed tbs)))
positively :: Int -> Int positively :: Int -> Int
positively = succ . abs positively = succ . abs