]> Git — Sourcephile - gargantext.git/blob - src-test/Ngrams/Query.hs
Add test case to reproduce #217
[gargantext.git] / src-test / Ngrams / Query.hs
1 {-# LANGUAGE OverloadedStrings #-}
2 {-# LANGUAGE TypeApplications #-}
3 module Ngrams.Query where
4
5 import Control.Monad
6 import Data.Coerce
7 import Data.Map.Strict (Map)
8 import Data.Monoid
9 import Gargantext.API.Ngrams.Types (mSetFromList)
10 import Gargantext.API.Ngrams
11 import Gargantext.API.Ngrams.Types
12 import Gargantext.Core.Types.Main
13 import Gargantext.Core.Types.Query
14 import Gargantext.Prelude
15 import qualified Data.Map.Strict as Map
16 import qualified Data.Patch.Class as Patch
17 import qualified Data.Validity as Validity
18 import qualified Data.Text as T
19
20 import Ngrams.Query.PaginationCorpus
21 import Test.Tasty
22 import Test.Tasty.HUnit
23
24
25 main :: IO ()
26 main = defaultMain tests
27
28 tests :: TestTree
29 tests = testGroup "Ngrams" [unitTests]
30
31 curryElem :: NgramsElement
32 curryElem = mkNgramsElement "curry" MapTerm Nothing mempty
33
34 elbaElem :: NgramsElement
35 elbaElem = mkNgramsElement "elba" MapTerm Nothing mempty
36
37 mockFlatCorpus :: Versioned (Map NgramsTerm NgramsElement)
38 mockFlatCorpus = Versioned 0 $ Map.fromList [
39 ( "haskell", curryElem)
40 , ( "idris", elbaElem)
41 ]
42
43 mockQueryFn :: Maybe T.Text -> NgramsTerm -> Bool
44 mockQueryFn searchQuery (NgramsTerm nt) =
45 maybe (const True) T.isInfixOf (T.toLower <$> searchQuery) (T.toLower nt)
46
47 unitTests :: TestTree
48 unitTests = testGroup "Query tests"
49 [ -- Sorting
50 testCase "Simple query mockFlatCorpus" testFlat01
51 , testCase "Simple query (desc sorting)" testFlat02
52 -- -- Filtering
53 , testCase "Simple query (listType = MapTerm)" testFlat03
54 , testCase "Simple query (listType = StopTerm)" testFlat04
55 -- -- Full text search
56 , testCase "Simple query (search with match)" testFlat05
57 -- -- Pagination
58 , testCase "Simple pagination on all terms" test_pagination_allTerms
59 , testCase "Simple pagination on MapTerm" test_pagination01
60 , testCase "Simple pagination on MapTerm (limit < total terms)" test_pagination02
61 , testCase "Simple pagination on MapTerm (offset works)" test_pagination02_offset
62 , testCase "Simple pagination on ListTerm (limit < total terms)" test_pagination03
63 , testCase "Simple pagination on ListTerm (offset works)" test_pagination03_offset
64 , testCase "Simple pagination on CandidateTerm (limit < total terms)" test_pagination04
65 , testCase "paginating QuantumComputing corpus works (MapTerms)" test_paginationQuantum
66 , testCase "paginating QuantumComputing corpus works (CandidateTerm)" test_paginationQuantum_02
67 -- -- Patching
68 , testCase "I can apply a patch to term mapTerms to stopTerms (issue #217)" test_217
69 ]
70
71 -- Let's test that if we request elements sorted in
72 -- /ascending/ order, we get them.
73 testFlat01 :: Assertion
74 testFlat01 = do
75 let res = searchTableNgrams mockFlatCorpus searchQuery
76 res @?= VersionedWithCount 0 2 ( NgramsTable [curryElem, elbaElem] )
77 where
78 searchQuery = NgramsSearchQuery {
79 _nsq_limit = Limit 5
80 , _nsq_offset = Nothing
81 , _nsq_listType = Nothing
82 , _nsq_minSize = Nothing
83 , _nsq_maxSize = Nothing
84 , _nsq_orderBy = Just TermAsc
85 , _nsq_searchQuery = mockQueryFn Nothing
86 }
87
88 -- Let's test that if we request elements sorted in
89 -- /descending/ order, we get them.
90 testFlat02 :: Assertion
91 testFlat02 = do
92 let res = searchTableNgrams mockFlatCorpus searchQuery
93 res @?= VersionedWithCount 0 2 ( NgramsTable [elbaElem, curryElem] )
94 where
95 searchQuery = NgramsSearchQuery {
96 _nsq_limit = Limit 5
97 , _nsq_offset = Nothing
98 , _nsq_listType = Nothing
99 , _nsq_minSize = Nothing
100 , _nsq_maxSize = Nothing
101 , _nsq_orderBy = Just TermDesc
102 , _nsq_searchQuery = mockQueryFn Nothing
103 }
104
105 testFlat03 :: Assertion
106 testFlat03 = do
107 let res = searchTableNgrams mockFlatCorpus searchQuery
108 res @?= VersionedWithCount 0 2 ( NgramsTable [elbaElem, curryElem] )
109 where
110 searchQuery = NgramsSearchQuery {
111 _nsq_limit = Limit 5
112 , _nsq_offset = Nothing
113 , _nsq_listType = Just MapTerm
114 , _nsq_minSize = Nothing
115 , _nsq_maxSize = Nothing
116 , _nsq_orderBy = Just TermDesc
117 , _nsq_searchQuery = mockQueryFn Nothing
118 }
119
120 -- Here we are searching for all the stop terms, but
121 -- due to the fact we don't have any inside 'mockFlatCorpus',
122 -- we should get no results.
123 testFlat04 :: Assertion
124 testFlat04 = do
125 let res = searchTableNgrams mockFlatCorpus searchQuery
126 res @?= VersionedWithCount 0 0 ( NgramsTable [] )
127 where
128 searchQuery = NgramsSearchQuery {
129 _nsq_limit = Limit 5
130 , _nsq_offset = Nothing
131 , _nsq_listType = Just StopTerm
132 , _nsq_minSize = Nothing
133 , _nsq_maxSize = Nothing
134 , _nsq_orderBy = Just TermDesc
135 , _nsq_searchQuery = mockQueryFn Nothing
136 }
137
138 -- For this test, we run a full text search on the word
139 -- \"curry\", and we expect back a result.
140 testFlat05 :: Assertion
141 testFlat05 = do
142 let res = searchTableNgrams mockFlatCorpus searchQuery
143 res @?= VersionedWithCount 0 1 ( NgramsTable [curryElem] )
144 where
145 searchQuery = NgramsSearchQuery {
146 _nsq_limit = Limit 5
147 , _nsq_offset = Nothing
148 , _nsq_listType = Nothing
149 , _nsq_minSize = Nothing
150 , _nsq_maxSize = Nothing
151 , _nsq_orderBy = Just TermDesc
152 , _nsq_searchQuery = mockQueryFn (Just "curry")
153 }
154
155 -- Pagination tests
156
157 test_pagination_allTerms :: Assertion
158 test_pagination_allTerms = do
159 let res = searchTableNgrams paginationCorpus searchQuery
160 res @?= VersionedWithCount 0 10 ( NgramsTable [ haskellElem
161 , sideEffectsElem
162 , concHaskellElem
163 , implementationElem
164 , ooElem
165 , languagesElem
166 , javaElem
167 , termsElem
168 ] )
169 where
170 searchQuery = NgramsSearchQuery {
171 _nsq_limit = Limit 8
172 , _nsq_offset = Nothing
173 , _nsq_listType = Nothing
174 , _nsq_minSize = Nothing
175 , _nsq_maxSize = Nothing
176 , _nsq_orderBy = Nothing
177 , _nsq_searchQuery = mockQueryFn Nothing
178 }
179
180 -- In this test, I'm asking for 5 /map terms/, and as the
181 -- corpus has only 2, that's what I should get back.
182 test_pagination01 :: Assertion
183 test_pagination01 = do
184 let res = searchTableNgrams paginationCorpus searchQuery
185 res @?= VersionedWithCount 0 4 ( NgramsTable [implementationElem, languagesElem, termsElem, proofElem] )
186 where
187 searchQuery = NgramsSearchQuery {
188 _nsq_limit = Limit 5
189 , _nsq_offset = Nothing
190 , _nsq_listType = Just MapTerm
191 , _nsq_minSize = Nothing
192 , _nsq_maxSize = Nothing
193 , _nsq_orderBy = Just ScoreDesc
194 , _nsq_searchQuery = mockQueryFn Nothing
195 }
196
197 test_pagination02 :: Assertion
198 test_pagination02 = do
199 let res = searchTableNgrams paginationCorpus searchQuery
200 res @?= VersionedWithCount 0 4 ( NgramsTable [implementationElem, languagesElem, termsElem] )
201 where
202 searchQuery = NgramsSearchQuery {
203 _nsq_limit = Limit 3
204 , _nsq_offset = Nothing
205 , _nsq_listType = Just MapTerm
206 , _nsq_minSize = Nothing
207 , _nsq_maxSize = Nothing
208 , _nsq_orderBy = Just ScoreDesc
209 , _nsq_searchQuery = mockQueryFn Nothing
210 }
211
212 test_pagination02_offset :: Assertion
213 test_pagination02_offset = do
214 let res = searchTableNgrams paginationCorpus searchQuery
215 res @?= VersionedWithCount 0 4 ( NgramsTable [termsElem, proofElem] )
216 where
217 searchQuery = NgramsSearchQuery {
218 _nsq_limit = Limit 2
219 , _nsq_offset = Just (Offset 2)
220 , _nsq_listType = Just MapTerm
221 , _nsq_minSize = Nothing
222 , _nsq_maxSize = Nothing
223 , _nsq_orderBy = Just ScoreDesc
224 , _nsq_searchQuery = mockQueryFn Nothing
225 }
226
227 test_pagination03 :: Assertion
228 test_pagination03 = do
229 let res = searchTableNgrams paginationCorpus searchQuery
230 res @?= VersionedWithCount 0 4 ( NgramsTable [sideEffectsElem, ooElem, javaElem] )
231 where
232 searchQuery = NgramsSearchQuery {
233 _nsq_limit = Limit 3
234 , _nsq_offset = Nothing
235 , _nsq_listType = Just StopTerm
236 , _nsq_minSize = Nothing
237 , _nsq_maxSize = Nothing
238 , _nsq_orderBy = Just ScoreDesc
239 , _nsq_searchQuery = mockQueryFn Nothing
240 }
241
242 test_pagination03_offset :: Assertion
243 test_pagination03_offset = do
244 let res = searchTableNgrams paginationCorpus searchQuery
245 res @?= VersionedWithCount 0 4 ( NgramsTable [javaElem, pascalElem] )
246 where
247 searchQuery = NgramsSearchQuery {
248 _nsq_limit = Limit 2
249 , _nsq_offset = Just (Offset 2)
250 , _nsq_listType = Just StopTerm
251 , _nsq_minSize = Nothing
252 , _nsq_maxSize = Nothing
253 , _nsq_orderBy = Just ScoreDesc
254 , _nsq_searchQuery = mockQueryFn Nothing
255 }
256
257 test_pagination04 :: Assertion
258 test_pagination04 = do
259 let res = searchTableNgrams paginationCorpus searchQuery
260 res @?= VersionedWithCount 0 2 ( NgramsTable [haskellElem] )
261 where
262 searchQuery = NgramsSearchQuery {
263 _nsq_limit = Limit 1
264 , _nsq_offset = Nothing
265 , _nsq_listType = Just CandidateTerm
266 , _nsq_minSize = Nothing
267 , _nsq_maxSize = Nothing
268 , _nsq_orderBy = Just ScoreDesc
269 , _nsq_searchQuery = mockQueryFn Nothing
270 }
271
272 test_paginationQuantum :: Assertion
273 test_paginationQuantum = do
274 let res = searchTableNgrams quantumComputingCorpus searchQuery
275 let elems = coerce @NgramsTable @[NgramsElement] $ _vc_data res
276 length elems @?= 10
277 forM_ elems $ \term ->
278 assertBool ("found " <> show (_ne_list term) <> " in: " <> show elems) (_ne_list term == MapTerm)
279 where
280 searchQuery = NgramsSearchQuery {
281 _nsq_limit = Limit 10
282 , _nsq_offset = Nothing
283 , _nsq_listType = Just MapTerm
284 , _nsq_minSize = Nothing
285 , _nsq_maxSize = Nothing
286 , _nsq_orderBy = Nothing
287 , _nsq_searchQuery = mockQueryFn Nothing
288 }
289
290 test_paginationQuantum_02 :: Assertion
291 test_paginationQuantum_02 = do
292 let res = searchTableNgrams quantumComputingCorpus searchQuery
293 let elems = coerce @NgramsTable @[NgramsElement] $ _vc_data res
294 assertBool ("found only " <> show (length elems) <> " in: " <> show elems) (length elems == 10)
295 where
296 searchQuery = NgramsSearchQuery {
297 _nsq_limit = Limit 10
298 , _nsq_offset = Nothing
299 , _nsq_listType = Just CandidateTerm
300 , _nsq_minSize = Nothing
301 , _nsq_maxSize = Nothing
302 , _nsq_orderBy = Nothing
303 , _nsq_searchQuery = mockQueryFn Nothing
304 }
305
306 issue217Corpus :: NgramsTableMap
307 issue217Corpus = Map.fromList [
308 ( "advantages", NgramsRepoElement 1 MapTerm Nothing Nothing (mSetFromList ["advantage"]))
309 , ( "advantage" , NgramsRepoElement 1 MapTerm (Just "advantages") (Just "advantages") mempty)
310 ]
311
312 patched217Corpus :: NgramsTableMap
313 patched217Corpus = Map.fromList [
314 ( "advantages", NgramsRepoElement 1 StopTerm Nothing Nothing (mSetFromList ["advantage"]))
315 , ( "advantage" , NgramsRepoElement 1 StopTerm (Just "advantages") (Just "advantages") mempty)
316 ]
317
318 -- In this patch we simulate turning the subtree composed by 'advantages' and 'advantage'
319 -- from map terms to stop terms.
320 patch217 :: NgramsTablePatch
321 patch217 = mkNgramsTablePatch $ Map.fromList [
322 (NgramsTerm "advantages", NgramsPatch
323 { _patch_children = mempty
324 , _patch_list = Patch.Replace MapTerm StopTerm
325 }
326 )
327 ]
328
329 test_217 :: Assertion
330 test_217 = do
331 -- Check the patch is applicable
332 Validity.validationIsValid (Patch.applicable patch217 (Just issue217Corpus)) @?= True
333 Patch.act patch217 (Just issue217Corpus) @?= Just patched217Corpus