Commit 0f018d7c authored by Alfredo Di Napoli's avatar Alfredo Di Napoli

Fix remaining tests

In particular:

* In ngrams search tests where we were comparing the total number of
  results returned, we need to account only for the roots, because the
  total number we would be returning from the pagination would be
  higher, as it would include children, in some cases;
* In the `AcyclipTableMap` generator, the roots we generate need to be
  so (i.e. `_ne_root` and `_ne_parent` must be `Nothing`).
parent ab4d30db
Pipeline #7886 passed with stages
in 52 minutes and 5 seconds
...@@ -17,13 +17,12 @@ add get ...@@ -17,13 +17,12 @@ add get
{-# LANGUAGE BangPatterns #-} {-# LANGUAGE BangPatterns #-}
{-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE IncoherentInstances #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.API.Ngrams module Gargantext.API.Ngrams
( (
......
...@@ -768,7 +768,7 @@ genCorpusWithMatchingElement = do ...@@ -768,7 +768,7 @@ genCorpusWithMatchingElement = do
depth <- choose (1, 5) depth <- choose (1, 5)
let mkEntry = do let mkEntry = do
trm <- arbitrary trm <- arbitrary
el <- over ne_children (breakLoop trm) <$> (resize depth arbitrary) el <- over ne_children (breakLoop trm) . makeItRoot <$> (resize depth arbitrary)
pure (trm, el { _ne_ngrams = trm }) pure (trm, el { _ne_ngrams = trm })
-- Let's build the map first, so that duplicates will be overwritten. -- Let's build the map first, so that duplicates will be overwritten.
fullMap <- (Map.fromList <$> vectorOf depth mkEntry) `suchThat` (\x -> isRight (buildForest x)) -- exclude loops fullMap <- (Map.fromList <$> vectorOf depth mkEntry) `suchThat` (\x -> isRight (buildForest x)) -- exclude loops
...@@ -778,6 +778,10 @@ genCorpusWithMatchingElement = do ...@@ -778,6 +778,10 @@ genCorpusWithMatchingElement = do
breakLoop :: NgramsTerm -> MSet NgramsTerm -> MSet NgramsTerm breakLoop :: NgramsTerm -> MSet NgramsTerm -> MSet NgramsTerm
breakLoop t = mSetFromSet . Set.delete t . mSetToSet breakLoop t = mSetFromSet . Set.delete t . mSetToSet
makeItRoot :: NgramsElement -> NgramsElement
makeItRoot ne = ne & ne_root .~ Nothing
& ne_parent .~ Nothing
instance Arbitrary AcyclicTableMap where instance Arbitrary AcyclicTableMap where
arbitrary = genCorpusWithMatchingElement arbitrary = genCorpusWithMatchingElement
shrink = shrinkTree shrink = shrinkTree
......
...@@ -236,7 +236,7 @@ testForestSearchProp :: Property ...@@ -236,7 +236,7 @@ testForestSearchProp :: Property
testForestSearchProp = forAll arbitrary $ \(AcyclicTableMap ngramsTable el) -> do testForestSearchProp = forAll arbitrary $ \(AcyclicTableMap ngramsTable el) -> do
case searchTableNgrams (Versioned 0 ngramsTable) (searchQuery el) of case searchTableNgrams (Versioned 0 ngramsTable) (searchQuery el) of
Left (BFE_loop_detected err) -> fail (T.unpack $ renderLoop err) Left (BFE_loop_detected err) -> fail (T.unpack $ renderLoop err)
Right res -> res ^. vc_data `shouldSatisfy` (elem (_ne_ngrams el) . map _ne_ngrams . getNgramsTable) Right res -> res ^. vc_data `shouldSatisfy` (any (containsTerm (_ne_ngrams el)) . getNgramsTable)
where where
searchQuery term = NgramsSearchQuery { searchQuery term = NgramsSearchQuery {
_nsq_limit = Limit 5 _nsq_limit = Limit 5
...@@ -397,7 +397,7 @@ test_paginationQuantum = do ...@@ -397,7 +397,7 @@ test_paginationQuantum = do
Left err -> fail (show err) Left err -> fail (show err)
Right res -> do Right res -> do
let elems = coerce @NgramsTable @[NgramsElement] $ _vc_data res let elems = coerce @NgramsTable @[NgramsElement] $ _vc_data res
length elems @?= 10 countRoots elems @?= 10
forM_ elems $ \term -> forM_ elems $ \term ->
assertBool ("found " <> show (_ne_list term) <> " in: " <> show elems) (_ne_list term == MapTerm) assertBool ("found " <> show (_ne_list term) <> " in: " <> show elems) (_ne_list term == MapTerm)
where where
...@@ -411,13 +411,20 @@ test_paginationQuantum = do ...@@ -411,13 +411,20 @@ test_paginationQuantum = do
, _nsq_searchQuery = mockQueryFn Nothing , _nsq_searchQuery = mockQueryFn Nothing
} }
countRoots :: [NgramsElement] -> Int
countRoots [] = 0
countRoots (x:xs) =
if isNothing (_ne_root x) || isNothing (_ne_parent x)
then 1 + countRoots xs
else countRoots xs
test_paginationQuantum_02 :: Assertion test_paginationQuantum_02 :: Assertion
test_paginationQuantum_02 = do test_paginationQuantum_02 = do
case searchTableNgrams quantumComputingCorpus searchQuery of case searchTableNgrams quantumComputingCorpus searchQuery of
Left err -> fail (show err) Left err -> fail (show err)
Right res -> do Right res -> do
let elems = coerce @NgramsTable @[NgramsElement] $ _vc_data res let elems = coerce @NgramsTable @[NgramsElement] $ _vc_data res
assertBool ("found only " <> show (length elems) <> " in: " <> show elems) (length elems == 10) assertBool ("found only " <> show (length elems) <> " in: " <> show elems) (countRoots elems == 10)
where where
searchQuery = NgramsSearchQuery { searchQuery = NgramsSearchQuery {
_nsq_limit = Limit 10 _nsq_limit = Limit 10
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment