Commit 7b955a56 authored by Alfredo Di Napoli's avatar Alfredo Di Napoli Committed by Alfredo Di Napoli

Add some basic pagination tests

This commit adds some basic tests for the Ngrams pagination,
capitalizing on the refactoring of the `searchTableNgrams` function,
which is now pure and can be tested fairly easily.
parent 92be964e
Pipeline #3980 failed with stage
in 28 minutes and 42 seconds
......@@ -848,6 +848,7 @@ test-suite garg-test
Ngrams.Lang.Occurrences
Ngrams.Metrics
Ngrams.NLP
Ngrams.Query
Parsers.Date
Parsers.Types
Parsers.WOS
......@@ -882,6 +883,7 @@ test-suite garg-test
build-depends:
QuickCheck
, base
, containers
, duckling
, extra
, gargantext
......@@ -889,6 +891,8 @@ test-suite garg-test
, hspec
, parsec
, quickcheck-instances
, tasty
, tasty-hunit
, text
, time
, unordered-containers
......
......@@ -504,6 +504,7 @@ tests:
- -with-rtsopts=-N
dependencies:
- base
- containers
- gargantext
- gargantext-prelude
- hspec
......@@ -512,6 +513,8 @@ tests:
- time
- parsec
- duckling
- tasty
- tasty-hunit
- text
- unordered-containers
jobqueue-test:
......
......@@ -17,6 +17,7 @@ import qualified Core.Utils as Utils
--import qualified Ngrams.Lang as Lang
import qualified Ngrams.Lang.Occurrences as Occ
import qualified Ngrams.NLP as NLP
import qualified Ngrams.Query as NgramsQuery
import qualified Ngrams.Metrics as Metrics
import qualified Parsers.Date as PD
-- import qualified Graph.Distance as GD
......@@ -35,3 +36,4 @@ main = do
-- GD.test
Crypto.test
NLP.main
NgramsQuery.main
{-# LANGUAGE OverloadedStrings #-}
module Ngrams.Query where
import Gargantext.Prelude
import Gargantext.API.Ngrams
import Gargantext.API.Ngrams.Types
import Data.Monoid
import qualified Data.Text as T
import qualified Data.Map.Strict as Map
import Data.Map.Strict (Map)
import Gargantext.Core.Types.Query
import Gargantext.Core.Types.Main
import Test.Tasty
import Test.Tasty.HUnit
main :: IO ()
main = defaultMain tests
tests :: TestTree
tests = testGroup "Ngrams" [unitTests]
curryElem :: NgramsElement
curryElem = mkNgramsElement "curry" MapTerm Nothing mempty
elbaElem :: NgramsElement
elbaElem = mkNgramsElement "elba" MapTerm Nothing mempty
mockFlatCorpus :: Versioned (Map NgramsTerm NgramsElement)
mockFlatCorpus = Versioned 0 $ Map.fromList [
( "haskell", curryElem)
, ( "idris", elbaElem)
]
mockQueryFn :: Maybe T.Text -> NgramsTerm -> Bool
mockQueryFn searchQuery (NgramsTerm nt) =
maybe (const True) T.isInfixOf (T.toLower <$> searchQuery) (T.toLower nt)
unitTests :: TestTree
unitTests = testGroup "Query tests"
[ -- Sorting
testCase "Simple query mockFlatCorpus" testFlat01
, testCase "Simple query (desc sorting)" testFlat02
-- Filtering
, testCase "Simple query (listType = MapTerm)" testFlat03
, testCase "Simple query (listType = StopTerm)" testFlat04
-- Full text search
, testCase "Simple query (search with match)" testFlat05
]
-- Let's test that if we request elements sorted in
-- /ascending/ order, we get them.
testFlat01 :: Assertion
testFlat01 = do
let res = searchTableNgrams mockFlatCorpus searchQuery
res @?= VersionedWithCount 0 2 ( NgramsTable [curryElem, elbaElem] )
where
searchQuery = NgramsSearchQuery {
_nsq_limit = Limit 5
, _nsq_offset = Nothing
, _nsq_listType = Nothing
, _nsq_minSize = Nothing
, _nsq_maxSize = Nothing
, _nsq_orderBy = Just TermAsc
, _nsq_searchQuery = mockQueryFn Nothing
}
-- Let's test that if we request elements sorted in
-- /descending/ order, we get them.
testFlat02 :: Assertion
testFlat02 = do
let res = searchTableNgrams mockFlatCorpus searchQuery
res @?= VersionedWithCount 0 2 ( NgramsTable [elbaElem, curryElem] )
where
searchQuery = NgramsSearchQuery {
_nsq_limit = Limit 5
, _nsq_offset = Nothing
, _nsq_listType = Nothing
, _nsq_minSize = Nothing
, _nsq_maxSize = Nothing
, _nsq_orderBy = Just TermDesc
, _nsq_searchQuery = mockQueryFn Nothing
}
testFlat03 :: Assertion
testFlat03 = do
let res = searchTableNgrams mockFlatCorpus searchQuery
res @?= VersionedWithCount 0 2 ( NgramsTable [elbaElem, curryElem] )
where
searchQuery = NgramsSearchQuery {
_nsq_limit = Limit 5
, _nsq_offset = Nothing
, _nsq_listType = Just MapTerm
, _nsq_minSize = Nothing
, _nsq_maxSize = Nothing
, _nsq_orderBy = Just TermDesc
, _nsq_searchQuery = mockQueryFn Nothing
}
-- Here we are searching for all the stop terms, but
-- due to the fact we don't have any inside 'mockFlatCorpus',
-- we should get no results.
testFlat04 :: Assertion
testFlat04 = do
let res = searchTableNgrams mockFlatCorpus searchQuery
res @?= VersionedWithCount 0 0 ( NgramsTable [] )
where
searchQuery = NgramsSearchQuery {
_nsq_limit = Limit 5
, _nsq_offset = Nothing
, _nsq_listType = Just StopTerm
, _nsq_minSize = Nothing
, _nsq_maxSize = Nothing
, _nsq_orderBy = Just TermDesc
, _nsq_searchQuery = mockQueryFn Nothing
}
-- For this test, we run a full text search on the word
-- \"curry\", and we expect back a result.
testFlat05 :: Assertion
testFlat05 = do
let res = searchTableNgrams mockFlatCorpus searchQuery
res @?= VersionedWithCount 0 1 ( NgramsTable [curryElem] )
where
searchQuery = NgramsSearchQuery {
_nsq_limit = Limit 5
, _nsq_offset = Nothing
, _nsq_listType = Nothing
, _nsq_minSize = Nothing
, _nsq_maxSize = Nothing
, _nsq_orderBy = Just TermDesc
, _nsq_searchQuery = mockQueryFn (Just "curry")
}
......@@ -28,6 +28,7 @@ module Gargantext.API.Ngrams
, TableNgramsApiGet
, TableNgramsApiPut
, searchTableNgrams
, getTableNgrams
, getTableNgramsCorpus
, setListNgrams
......@@ -532,14 +533,13 @@ searchTableNgrams :: Versioned (Map NgramsTerm NgramsElement)
searchTableNgrams versionedTableMap NgramsSearchQuery{..} =
-- lIds <- selectNodesWithUsername NodeList userMaster
let
ngramsType = ngramsTypeFromTabType _nsq_tabType
offset' = getOffset $ maybe 0 identity _nsq_offset
listType' = maybe (const True) (==) _nsq_listType
minSize' = maybe (const True) (<=) (getMinSize <$> _nsq_minSize)
maxSize' = maybe (const True) (>=) (getMaxSize <$> _nsq_maxSize)
rootOf tableMap ne = maybe ne (\r -> fromMaybe (panic "getTableNgrams: invalid root")
(tableMap ^. at r)
rootOf tblMap ne = maybe ne (\r -> fromMaybe (panic "getTableNgrams: invalid root")
(tblMap ^. at r)
)
(ne ^. ne_root)
......@@ -560,23 +560,23 @@ searchTableNgrams versionedTableMap NgramsSearchQuery{..} =
---------------------------------------
-- | Filter the given `tableMap` with the search criteria.
filteredNodes :: Map NgramsTerm NgramsElement -> Set NgramsElement
filteredNodes tableMap = roots
filteredNodes tblMap = roots
where
list = Set.fromList $ Map.elems tableMap
list = Set.fromList $ Map.elems tblMap
selected_nodes = list & Set.filter selected_node
roots = Set.map (rootOf tableMap) selected_nodes
roots = Set.map (rootOf tblMap) selected_nodes
-- | For each input root, extends its occurrence count with
-- the information found in the subitems.
withInners :: Map NgramsTerm NgramsElement -> Set NgramsElement -> Set NgramsElement
withInners tableMap roots = Set.map addSubitemsOccurrences roots
withInners tblMap roots = Set.map addSubitemsOccurrences roots
where
addSubitemsOccurrences :: NgramsElement -> NgramsElement
addSubitemsOccurrences e =
e { _ne_occurrences = foldl' alterOccurrences (e ^. ne_occurrences) (e ^. ne_children) }
alterOccurrences :: Set ContextId -> NgramsTerm -> Set ContextId
alterOccurrences occs t = case Map.lookup t tableMap of
alterOccurrences occs t = case Map.lookup t tblMap of
Nothing -> occs
Just e' -> occs <> e' ^. ne_occurrences
......@@ -589,8 +589,6 @@ searchTableNgrams versionedTableMap NgramsSearchQuery{..} =
---------------------------------------
scoresNeeded = needsScores _nsq_orderBy
tableMap = versionedTableMap ^. v_data
filteredData = filteredNodes tableMap
......@@ -603,15 +601,15 @@ searchTableNgrams versionedTableMap NgramsSearchQuery{..} =
getTableNgrams :: forall env err m.
(HasNodeStory env err m, HasNodeError err, CmdCommon env)
=> NodeType
-> NodeId
=> NodeId
-> ListId
-> TabType
-> NgramsSearchQuery
-> m (VersionedWithCount NgramsTable)
getTableNgrams nodeType nodeId tabType searchQuery = do
getTableNgrams nodeId listId tabType searchQuery = do
let ngramsType = ngramsTypeFromTabType tabType
versionedInput <- getNgramsTable' nodeType nodeId ngramsType
searchTableNgrams versionedInput searchQuery
versionedInput <- getNgramsTable' nodeId listId ngramsType
pure $ searchTableNgrams versionedInput searchQuery
-- | Helper function to get the ngrams table with scores.
......@@ -734,12 +732,11 @@ getTableNgramsCorpus :: (HasNodeStory env err m, HasNodeError err, CmdCommon env
-> Maybe Text -- full text search
-> m (VersionedWithCount NgramsTable)
getTableNgramsCorpus nId tabType listId limit_ offset listType minSize maxSize orderBy mt =
getTableNgrams NodeCorpus nId tabType searchQuery
getTableNgrams nId listId tabType searchQuery
where
searchQueryFn (NgramsTerm nt) = maybe (const True) isInfixOf (toLower <$> mt) (toLower nt)
searchQuery = NgramsSearchQuery {
_nsq_listId = listId
, _nsq_limit = limit_
_nsq_limit = limit_
, _nsq_offset = offset
, _nsq_listType = listType
, _nsq_minSize = minSize
......@@ -781,8 +778,7 @@ getTableNgramsDoc dId tabType listId limit_ offset listType minSize maxSize orde
ngs <- selectNgramsByDoc (ns <> [listId]) dId ngramsType
let searchQueryFn (NgramsTerm nt) = flip Set.member (Set.fromList ngs) nt
searchQuery = NgramsSearchQuery {
_nsq_listId = listId
, _nsq_limit = limit_
_nsq_limit = limit_
, _nsq_offset = offset
, _nsq_listType = listType
, _nsq_minSize = minSize
......@@ -790,7 +786,7 @@ getTableNgramsDoc dId tabType listId limit_ offset listType minSize maxSize orde
, _nsq_orderBy = orderBy
, _nsq_searchQuery = searchQueryFn
}
getTableNgrams NodeDocument dId tabType searchQuery
getTableNgrams dId listId tabType searchQuery
apiNgramsTableCorpus :: NodeId -> ServerT TableNgramsApi (GargM Env GargError)
......
......@@ -40,7 +40,7 @@ import Database.PostgreSQL.Simple.FromField (FromField, fromField, fromJSONField
import Database.PostgreSQL.Simple.ToField (ToField, toJSONField, toField)
import GHC.Generics (Generic)
import Gargantext.Core.Text (size)
import Gargantext.Core.Types (ListType(..), ListId, NodeId, NodeType, TODO)
import Gargantext.Core.Types (ListType(..), ListId, NodeId, TODO)
import Gargantext.Core.Types.Query (Limit, Offset, MaxSize, MinSize)
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixUntagged, unPrefixSwagger, wellNamedSchema)
import Gargantext.Database.Admin.Types.Node (ContextId)
......@@ -296,9 +296,8 @@ instance Arbitrary OrderBy
-- | A query on a 'NgramsTable'.
data NgramsSearchQuery m = NgramsSearchQuery
{ _nsq_listId :: !ListId
, _nsq_limit :: !Limit
data NgramsSearchQuery = NgramsSearchQuery
{ _nsq_limit :: !Limit
, _nsq_offset :: !(Maybe Offset)
, _nsq_listType :: !(Maybe ListType)
, _nsq_minSize :: !(Maybe MinSize)
......
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