1 {-# LANGUAGE OverloadedStrings #-}
2 {-# LANGUAGE TypeApplications #-}
3 module Ngrams.Query where
6 import Gargantext.Prelude
7 import Gargantext.API.Ngrams
8 import Gargantext.API.Ngrams.Types
11 import qualified Data.Text as T
12 import qualified Data.Map.Strict as Map
13 import Data.Map.Strict (Map)
14 import Gargantext.Core.Types.Query
15 import Gargantext.Core.Types.Main
17 import Ngrams.Query.PaginationCorpus
19 import Test.Tasty.HUnit
23 main = defaultMain tests
26 tests = testGroup "Ngrams" [unitTests]
28 curryElem :: NgramsElement
29 curryElem = mkNgramsElement "curry" MapTerm Nothing mempty
31 elbaElem :: NgramsElement
32 elbaElem = mkNgramsElement "elba" MapTerm Nothing mempty
34 mockFlatCorpus :: Versioned (Map NgramsTerm NgramsElement)
35 mockFlatCorpus = Versioned 0 $ Map.fromList [
36 ( "haskell", curryElem)
37 , ( "idris", elbaElem)
40 mockQueryFn :: Maybe T.Text -> NgramsTerm -> Bool
41 mockQueryFn searchQuery (NgramsTerm nt) =
42 maybe (const True) T.isInfixOf (T.toLower <$> searchQuery) (T.toLower nt)
45 unitTests = testGroup "Query tests"
47 testCase "Simple query mockFlatCorpus" testFlat01
48 , testCase "Simple query (desc sorting)" testFlat02
50 , testCase "Simple query (listType = MapTerm)" testFlat03
51 , testCase "Simple query (listType = StopTerm)" testFlat04
52 -- -- Full text search
53 , testCase "Simple query (search with match)" testFlat05
55 , testCase "Simple pagination on all terms" test_pagination_allTerms
56 , testCase "Simple pagination on MapTerm" test_pagination01
57 , testCase "Simple pagination on MapTerm (limit < total terms)" test_pagination02
58 , testCase "Simple pagination on MapTerm (offset works)" test_pagination02_offset
59 , testCase "Simple pagination on ListTerm (limit < total terms)" test_pagination03
60 , testCase "Simple pagination on ListTerm (offset works)" test_pagination03_offset
61 , testCase "Simple pagination on CandidateTerm (limit < total terms)" test_pagination04
62 , testCase "paginating QuantumComputing corpus works (MapTerms)" test_paginationQuantum
63 , testCase "paginating QuantumComputing corpus works (CandidateTerm)" test_paginationQuantum_02
66 -- Let's test that if we request elements sorted in
67 -- /ascending/ order, we get them.
68 testFlat01 :: Assertion
70 let res = searchTableNgrams mockFlatCorpus searchQuery
71 res @?= VersionedWithCount 0 2 ( NgramsTable [curryElem, elbaElem] )
73 searchQuery = NgramsSearchQuery {
75 , _nsq_offset = Nothing
76 , _nsq_listType = Nothing
77 , _nsq_minSize = Nothing
78 , _nsq_maxSize = Nothing
79 , _nsq_orderBy = Just TermAsc
80 , _nsq_searchQuery = mockQueryFn Nothing
83 -- Let's test that if we request elements sorted in
84 -- /descending/ order, we get them.
85 testFlat02 :: Assertion
87 let res = searchTableNgrams mockFlatCorpus searchQuery
88 res @?= VersionedWithCount 0 2 ( NgramsTable [elbaElem, curryElem] )
90 searchQuery = NgramsSearchQuery {
92 , _nsq_offset = Nothing
93 , _nsq_listType = Nothing
94 , _nsq_minSize = Nothing
95 , _nsq_maxSize = Nothing
96 , _nsq_orderBy = Just TermDesc
97 , _nsq_searchQuery = mockQueryFn Nothing
100 testFlat03 :: Assertion
102 let res = searchTableNgrams mockFlatCorpus searchQuery
103 res @?= VersionedWithCount 0 2 ( NgramsTable [elbaElem, curryElem] )
105 searchQuery = NgramsSearchQuery {
107 , _nsq_offset = Nothing
108 , _nsq_listType = Just MapTerm
109 , _nsq_minSize = Nothing
110 , _nsq_maxSize = Nothing
111 , _nsq_orderBy = Just TermDesc
112 , _nsq_searchQuery = mockQueryFn Nothing
115 -- Here we are searching for all the stop terms, but
116 -- due to the fact we don't have any inside 'mockFlatCorpus',
117 -- we should get no results.
118 testFlat04 :: Assertion
120 let res = searchTableNgrams mockFlatCorpus searchQuery
121 res @?= VersionedWithCount 0 0 ( NgramsTable [] )
123 searchQuery = NgramsSearchQuery {
125 , _nsq_offset = Nothing
126 , _nsq_listType = Just StopTerm
127 , _nsq_minSize = Nothing
128 , _nsq_maxSize = Nothing
129 , _nsq_orderBy = Just TermDesc
130 , _nsq_searchQuery = mockQueryFn Nothing
133 -- For this test, we run a full text search on the word
134 -- \"curry\", and we expect back a result.
135 testFlat05 :: Assertion
137 let res = searchTableNgrams mockFlatCorpus searchQuery
138 res @?= VersionedWithCount 0 1 ( NgramsTable [curryElem] )
140 searchQuery = NgramsSearchQuery {
142 , _nsq_offset = Nothing
143 , _nsq_listType = Nothing
144 , _nsq_minSize = Nothing
145 , _nsq_maxSize = Nothing
146 , _nsq_orderBy = Just TermDesc
147 , _nsq_searchQuery = mockQueryFn (Just "curry")
152 test_pagination_allTerms :: Assertion
153 test_pagination_allTerms = do
154 let res = searchTableNgrams paginationCorpus searchQuery
155 res @?= VersionedWithCount 0 10 ( NgramsTable [ haskellElem
165 searchQuery = NgramsSearchQuery {
167 , _nsq_offset = Nothing
168 , _nsq_listType = Nothing
169 , _nsq_minSize = Nothing
170 , _nsq_maxSize = Nothing
171 , _nsq_orderBy = Nothing
172 , _nsq_searchQuery = mockQueryFn Nothing
175 -- In this test, I'm asking for 5 /map terms/, and as the
176 -- corpus has only 2, that's what I should get back.
177 test_pagination01 :: Assertion
178 test_pagination01 = do
179 let res = searchTableNgrams paginationCorpus searchQuery
180 res @?= VersionedWithCount 0 4 ( NgramsTable [implementationElem, languagesElem, termsElem, proofElem] )
182 searchQuery = NgramsSearchQuery {
184 , _nsq_offset = Nothing
185 , _nsq_listType = Just MapTerm
186 , _nsq_minSize = Nothing
187 , _nsq_maxSize = Nothing
188 , _nsq_orderBy = Just ScoreDesc
189 , _nsq_searchQuery = mockQueryFn Nothing
192 test_pagination02 :: Assertion
193 test_pagination02 = do
194 let res = searchTableNgrams paginationCorpus searchQuery
195 res @?= VersionedWithCount 0 4 ( NgramsTable [implementationElem, languagesElem, termsElem] )
197 searchQuery = NgramsSearchQuery {
199 , _nsq_offset = Nothing
200 , _nsq_listType = Just MapTerm
201 , _nsq_minSize = Nothing
202 , _nsq_maxSize = Nothing
203 , _nsq_orderBy = Just ScoreDesc
204 , _nsq_searchQuery = mockQueryFn Nothing
207 test_pagination02_offset :: Assertion
208 test_pagination02_offset = do
209 let res = searchTableNgrams paginationCorpus searchQuery
210 res @?= VersionedWithCount 0 4 ( NgramsTable [termsElem, proofElem] )
212 searchQuery = NgramsSearchQuery {
214 , _nsq_offset = Just (Offset 2)
215 , _nsq_listType = Just MapTerm
216 , _nsq_minSize = Nothing
217 , _nsq_maxSize = Nothing
218 , _nsq_orderBy = Just ScoreDesc
219 , _nsq_searchQuery = mockQueryFn Nothing
222 test_pagination03 :: Assertion
223 test_pagination03 = do
224 let res = searchTableNgrams paginationCorpus searchQuery
225 res @?= VersionedWithCount 0 4 ( NgramsTable [sideEffectsElem, ooElem, javaElem] )
227 searchQuery = NgramsSearchQuery {
229 , _nsq_offset = Nothing
230 , _nsq_listType = Just StopTerm
231 , _nsq_minSize = Nothing
232 , _nsq_maxSize = Nothing
233 , _nsq_orderBy = Just ScoreDesc
234 , _nsq_searchQuery = mockQueryFn Nothing
237 test_pagination03_offset :: Assertion
238 test_pagination03_offset = do
239 let res = searchTableNgrams paginationCorpus searchQuery
240 res @?= VersionedWithCount 0 4 ( NgramsTable [javaElem, pascalElem] )
242 searchQuery = NgramsSearchQuery {
244 , _nsq_offset = Just (Offset 2)
245 , _nsq_listType = Just StopTerm
246 , _nsq_minSize = Nothing
247 , _nsq_maxSize = Nothing
248 , _nsq_orderBy = Just ScoreDesc
249 , _nsq_searchQuery = mockQueryFn Nothing
252 test_pagination04 :: Assertion
253 test_pagination04 = do
254 let res = searchTableNgrams paginationCorpus searchQuery
255 res @?= VersionedWithCount 0 2 ( NgramsTable [haskellElem] )
257 searchQuery = NgramsSearchQuery {
259 , _nsq_offset = Nothing
260 , _nsq_listType = Just CandidateTerm
261 , _nsq_minSize = Nothing
262 , _nsq_maxSize = Nothing
263 , _nsq_orderBy = Just ScoreDesc
264 , _nsq_searchQuery = mockQueryFn Nothing
267 test_paginationQuantum :: Assertion
268 test_paginationQuantum = do
269 let res = searchTableNgrams quantumComputingCorpus searchQuery
270 let elems = coerce @NgramsTable @[NgramsElement] $ _vc_data res
272 forM_ elems $ \term ->
273 assertBool ("found " <> show (_ne_list term) <> " in: " <> show elems) (_ne_list term == MapTerm)
275 searchQuery = NgramsSearchQuery {
276 _nsq_limit = Limit 10
277 , _nsq_offset = Nothing
278 , _nsq_listType = Just MapTerm
279 , _nsq_minSize = Nothing
280 , _nsq_maxSize = Nothing
281 , _nsq_orderBy = Nothing
282 , _nsq_searchQuery = mockQueryFn Nothing
285 test_paginationQuantum_02 :: Assertion
286 test_paginationQuantum_02 = do
287 let res = searchTableNgrams quantumComputingCorpus searchQuery
288 let elems = coerce @NgramsTable @[NgramsElement] $ _vc_data res
289 assertBool ("found only " <> show (length elems) <> " in: " <> show elems) (length elems == 10)
291 searchQuery = NgramsSearchQuery {
292 _nsq_limit = Limit 10
293 , _nsq_offset = Nothing
294 , _nsq_listType = Just CandidateTerm
295 , _nsq_minSize = Nothing
296 , _nsq_maxSize = Nothing
297 , _nsq_orderBy = Nothing
298 , _nsq_searchQuery = mockQueryFn Nothing