1 {-# LANGUAGE OverloadedStrings #-}
2 {-# LANGUAGE TypeApplications #-}
3 module Ngrams.Query (tests) where
7 import Data.Map.Strict (Map)
9 import Gargantext.API.Ngrams
10 import Gargantext.API.Ngrams.Types
11 import Gargantext.Core.Types.Main
12 import Gargantext.Core.Types.Query
13 import Gargantext.Prelude
14 import qualified Data.Map.Strict as Map
15 import qualified Data.Patch.Class as Patch
16 import qualified Data.Validity as Validity
17 import qualified Data.Text as T
19 import Ngrams.Query.PaginationCorpus
21 import Test.Tasty.HUnit
25 tests = testGroup "Ngrams" [unitTests]
27 curryElem :: NgramsElement
28 curryElem = mkNgramsElement "curry" MapTerm Nothing mempty
30 elbaElem :: NgramsElement
31 elbaElem = mkNgramsElement "elba" MapTerm Nothing mempty
33 mockFlatCorpus :: Versioned (Map NgramsTerm NgramsElement)
34 mockFlatCorpus = Versioned 0 $ Map.fromList [
35 ( "haskell", curryElem)
36 , ( "idris", elbaElem)
39 mockQueryFn :: Maybe T.Text -> NgramsTerm -> Bool
40 mockQueryFn searchQuery (NgramsTerm nt) =
41 maybe (const True) T.isInfixOf (T.toLower <$> searchQuery) (T.toLower nt)
44 unitTests = testGroup "Query tests"
46 testCase "Simple query mockFlatCorpus" testFlat01
47 , testCase "Simple query (desc sorting)" testFlat02
49 , testCase "Simple query (listType = MapTerm)" testFlat03
50 , testCase "Simple query (listType = StopTerm)" testFlat04
51 -- -- Full text search
52 , testCase "Simple query (search with match)" testFlat05
54 , testCase "Simple pagination on all terms" test_pagination_allTerms
55 , testCase "Simple pagination on MapTerm" test_pagination01
56 , testCase "Simple pagination on MapTerm (limit < total terms)" test_pagination02
57 , testCase "Simple pagination on MapTerm (offset works)" test_pagination02_offset
58 , testCase "Simple pagination on ListTerm (limit < total terms)" test_pagination03
59 , testCase "Simple pagination on ListTerm (offset works)" test_pagination03_offset
60 , testCase "Simple pagination on CandidateTerm (limit < total terms)" test_pagination04
61 , testCase "paginating QuantumComputing corpus works (MapTerms)" test_paginationQuantum
62 , testCase "paginating QuantumComputing corpus works (CandidateTerm)" test_paginationQuantum_02
64 , testCase "I can apply a patch to term mapTerms to stopTerms (issue #217)" test_217
67 -- Let's test that if we request elements sorted in
68 -- /ascending/ order, we get them.
69 testFlat01 :: Assertion
71 let res = searchTableNgrams mockFlatCorpus searchQuery
72 res @?= VersionedWithCount 0 2 ( NgramsTable [curryElem, elbaElem] )
74 searchQuery = NgramsSearchQuery {
76 , _nsq_offset = Nothing
77 , _nsq_listType = Nothing
78 , _nsq_minSize = Nothing
79 , _nsq_maxSize = Nothing
80 , _nsq_orderBy = Just TermAsc
81 , _nsq_searchQuery = mockQueryFn Nothing
84 -- Let's test that if we request elements sorted in
85 -- /descending/ order, we get them.
86 testFlat02 :: Assertion
88 let res = searchTableNgrams mockFlatCorpus searchQuery
89 res @?= VersionedWithCount 0 2 ( NgramsTable [elbaElem, curryElem] )
91 searchQuery = NgramsSearchQuery {
93 , _nsq_offset = Nothing
94 , _nsq_listType = Nothing
95 , _nsq_minSize = Nothing
96 , _nsq_maxSize = Nothing
97 , _nsq_orderBy = Just TermDesc
98 , _nsq_searchQuery = mockQueryFn Nothing
101 testFlat03 :: Assertion
103 let res = searchTableNgrams mockFlatCorpus searchQuery
104 res @?= VersionedWithCount 0 2 ( NgramsTable [elbaElem, curryElem] )
106 searchQuery = NgramsSearchQuery {
108 , _nsq_offset = Nothing
109 , _nsq_listType = Just MapTerm
110 , _nsq_minSize = Nothing
111 , _nsq_maxSize = Nothing
112 , _nsq_orderBy = Just TermDesc
113 , _nsq_searchQuery = mockQueryFn Nothing
116 -- Here we are searching for all the stop terms, but
117 -- due to the fact we don't have any inside 'mockFlatCorpus',
118 -- we should get no results.
119 testFlat04 :: Assertion
121 let res = searchTableNgrams mockFlatCorpus searchQuery
122 res @?= VersionedWithCount 0 0 ( NgramsTable [] )
124 searchQuery = NgramsSearchQuery {
126 , _nsq_offset = Nothing
127 , _nsq_listType = Just StopTerm
128 , _nsq_minSize = Nothing
129 , _nsq_maxSize = Nothing
130 , _nsq_orderBy = Just TermDesc
131 , _nsq_searchQuery = mockQueryFn Nothing
134 -- For this test, we run a full text search on the word
135 -- \"curry\", and we expect back a result.
136 testFlat05 :: Assertion
138 let res = searchTableNgrams mockFlatCorpus searchQuery
139 res @?= VersionedWithCount 0 1 ( NgramsTable [curryElem] )
141 searchQuery = NgramsSearchQuery {
143 , _nsq_offset = Nothing
144 , _nsq_listType = Nothing
145 , _nsq_minSize = Nothing
146 , _nsq_maxSize = Nothing
147 , _nsq_orderBy = Just TermDesc
148 , _nsq_searchQuery = mockQueryFn (Just "curry")
153 test_pagination_allTerms :: Assertion
154 test_pagination_allTerms = do
155 let res = searchTableNgrams paginationCorpus searchQuery
156 res @?= VersionedWithCount 0 10 ( NgramsTable [ haskellElem
166 searchQuery = NgramsSearchQuery {
168 , _nsq_offset = Nothing
169 , _nsq_listType = Nothing
170 , _nsq_minSize = Nothing
171 , _nsq_maxSize = Nothing
172 , _nsq_orderBy = Nothing
173 , _nsq_searchQuery = mockQueryFn Nothing
176 -- In this test, I'm asking for 5 /map terms/, and as the
177 -- corpus has only 2, that's what I should get back.
178 test_pagination01 :: Assertion
179 test_pagination01 = do
180 let res = searchTableNgrams paginationCorpus searchQuery
181 res @?= VersionedWithCount 0 4 ( NgramsTable [implementationElem, languagesElem, termsElem, proofElem] )
183 searchQuery = NgramsSearchQuery {
185 , _nsq_offset = Nothing
186 , _nsq_listType = Just MapTerm
187 , _nsq_minSize = Nothing
188 , _nsq_maxSize = Nothing
189 , _nsq_orderBy = Just ScoreDesc
190 , _nsq_searchQuery = mockQueryFn Nothing
193 test_pagination02 :: Assertion
194 test_pagination02 = do
195 let res = searchTableNgrams paginationCorpus searchQuery
196 res @?= VersionedWithCount 0 4 ( NgramsTable [implementationElem, languagesElem, termsElem] )
198 searchQuery = NgramsSearchQuery {
200 , _nsq_offset = Nothing
201 , _nsq_listType = Just MapTerm
202 , _nsq_minSize = Nothing
203 , _nsq_maxSize = Nothing
204 , _nsq_orderBy = Just ScoreDesc
205 , _nsq_searchQuery = mockQueryFn Nothing
208 test_pagination02_offset :: Assertion
209 test_pagination02_offset = do
210 let res = searchTableNgrams paginationCorpus searchQuery
211 res @?= VersionedWithCount 0 4 ( NgramsTable [termsElem, proofElem] )
213 searchQuery = NgramsSearchQuery {
215 , _nsq_offset = Just (Offset 2)
216 , _nsq_listType = Just MapTerm
217 , _nsq_minSize = Nothing
218 , _nsq_maxSize = Nothing
219 , _nsq_orderBy = Just ScoreDesc
220 , _nsq_searchQuery = mockQueryFn Nothing
223 test_pagination03 :: Assertion
224 test_pagination03 = do
225 let res = searchTableNgrams paginationCorpus searchQuery
226 res @?= VersionedWithCount 0 4 ( NgramsTable [sideEffectsElem, ooElem, javaElem] )
228 searchQuery = NgramsSearchQuery {
230 , _nsq_offset = Nothing
231 , _nsq_listType = Just StopTerm
232 , _nsq_minSize = Nothing
233 , _nsq_maxSize = Nothing
234 , _nsq_orderBy = Just ScoreDesc
235 , _nsq_searchQuery = mockQueryFn Nothing
238 test_pagination03_offset :: Assertion
239 test_pagination03_offset = do
240 let res = searchTableNgrams paginationCorpus searchQuery
241 res @?= VersionedWithCount 0 4 ( NgramsTable [javaElem, pascalElem] )
243 searchQuery = NgramsSearchQuery {
245 , _nsq_offset = Just (Offset 2)
246 , _nsq_listType = Just StopTerm
247 , _nsq_minSize = Nothing
248 , _nsq_maxSize = Nothing
249 , _nsq_orderBy = Just ScoreDesc
250 , _nsq_searchQuery = mockQueryFn Nothing
253 test_pagination04 :: Assertion
254 test_pagination04 = do
255 let res = searchTableNgrams paginationCorpus searchQuery
256 res @?= VersionedWithCount 0 2 ( NgramsTable [haskellElem] )
258 searchQuery = NgramsSearchQuery {
260 , _nsq_offset = Nothing
261 , _nsq_listType = Just CandidateTerm
262 , _nsq_minSize = Nothing
263 , _nsq_maxSize = Nothing
264 , _nsq_orderBy = Just ScoreDesc
265 , _nsq_searchQuery = mockQueryFn Nothing
268 test_paginationQuantum :: Assertion
269 test_paginationQuantum = do
270 let res = searchTableNgrams quantumComputingCorpus searchQuery
271 let elems = coerce @NgramsTable @[NgramsElement] $ _vc_data res
273 forM_ elems $ \term ->
274 assertBool ("found " <> show (_ne_list term) <> " in: " <> show elems) (_ne_list term == MapTerm)
276 searchQuery = NgramsSearchQuery {
277 _nsq_limit = Limit 10
278 , _nsq_offset = Nothing
279 , _nsq_listType = Just MapTerm
280 , _nsq_minSize = Nothing
281 , _nsq_maxSize = Nothing
282 , _nsq_orderBy = Nothing
283 , _nsq_searchQuery = mockQueryFn Nothing
286 test_paginationQuantum_02 :: Assertion
287 test_paginationQuantum_02 = do
288 let res = searchTableNgrams quantumComputingCorpus searchQuery
289 let elems = coerce @NgramsTable @[NgramsElement] $ _vc_data res
290 assertBool ("found only " <> show (length elems) <> " in: " <> show elems) (length elems == 10)
292 searchQuery = NgramsSearchQuery {
293 _nsq_limit = Limit 10
294 , _nsq_offset = Nothing
295 , _nsq_listType = Just CandidateTerm
296 , _nsq_minSize = Nothing
297 , _nsq_maxSize = Nothing
298 , _nsq_orderBy = Nothing
299 , _nsq_searchQuery = mockQueryFn Nothing
302 issue217Corpus :: NgramsTableMap
303 issue217Corpus = Map.fromList [
304 ( "advantages", NgramsRepoElement 1 MapTerm Nothing Nothing (mSetFromList ["advantage"]))
305 , ( "advantage" , NgramsRepoElement 1 MapTerm (Just "advantages") (Just "advantages") mempty)
308 patched217Corpus :: NgramsTableMap
309 patched217Corpus = Map.fromList [
310 ( "advantages", NgramsRepoElement 1 StopTerm Nothing Nothing (mSetFromList ["advantage"]))
311 , ( "advantage" , NgramsRepoElement 1 StopTerm (Just "advantages") (Just "advantages") mempty)
314 -- In this patch we simulate turning the subtree composed by 'advantages' and 'advantage'
315 -- from map terms to stop terms.
316 patch217 :: NgramsTablePatch
317 patch217 = mkNgramsTablePatch $ Map.fromList [
318 (NgramsTerm "advantages", NgramsPatch
319 { _patch_children = mempty
320 , _patch_list = Patch.Replace MapTerm StopTerm
325 test_217 :: Assertion
327 -- Check the patch is applicable
328 Validity.validationIsValid (Patch.applicable patch217 (Just issue217Corpus)) @?= True
329 Patch.act patch217 (Just issue217Corpus) @?= Just patched217Corpus