Commit f9f45da4 authored by Alfredo Di Napoli's avatar Alfredo Di Napoli Committed by Alfredo Di Napoli

test we can search in a docs list for a given query

parent 45eff945
...@@ -58,5 +58,6 @@ ...@@ -58,5 +58,6 @@
}, },
"hash": "" "hash": ""
} }
] ],
"garg_version": "0.0.7.1.16"
} }
...@@ -9,15 +9,18 @@ import Data.Text.Encoding qualified as TE ...@@ -9,15 +9,18 @@ import Data.Text.Encoding qualified as TE
import Fmt (Builder, (+|), (|+)) import Fmt (Builder, (+|), (|+))
import Gargantext.API.Admin.Auth.Types (AuthRequest, AuthResponse, Token) import Gargantext.API.Admin.Auth.Types (AuthRequest, AuthResponse, Token)
import Gargantext.API.Errors import Gargantext.API.Errors
import Gargantext.API.HashedResponse (HashedResponse)
import Gargantext.API.Ngrams.Types ( NgramsTable, NgramsTablePatch, OrderBy, TabType, Versioned, VersionedWithCount ) import Gargantext.API.Ngrams.Types ( NgramsTable, NgramsTablePatch, OrderBy, TabType, Versioned, VersionedWithCount )
import Gargantext.API.Routes.Named import Gargantext.API.Routes.Named
import Gargantext.API.Routes.Named.Node import Gargantext.API.Routes.Named.Node
import Gargantext.API.Routes.Named.Private hiding (tableNgramsAPI) import Gargantext.API.Routes.Named.Private hiding (tableNgramsAPI)
import Gargantext.API.Routes.Named.Table import Gargantext.API.Routes.Named.Table
import Gargantext.API.Types () -- MimeUnrender instances import Gargantext.API.Types () -- MimeUnrender instances
import Gargantext.Core.Text.Corpus.Query (RawQuery)
import Gargantext.Core.Types (ListId, NodeId) import Gargantext.Core.Types (ListId, NodeId)
import Gargantext.Core.Types.Main (ListType) import Gargantext.Core.Types.Main (ListType)
import Gargantext.Core.Types.Query (Limit, MaxSize, MinSize, Offset) import Gargantext.Core.Types.Query (Limit, MaxSize, MinSize, Offset)
import Gargantext.Database.Query.Facet qualified as Facet
import Gargantext.Prelude import Gargantext.Prelude
import Network.HTTP.Types qualified as H import Network.HTTP.Types qualified as H
import Network.Wai.Handler.Warp (Port) import Network.Wai.Handler.Warp (Port)
...@@ -64,7 +67,10 @@ auth_api = clientRoutes & apiWithCustomErrorScheme ...@@ -64,7 +67,10 @@ auth_api = clientRoutes & apiWithCustomErrorScheme
& gargAuthAPI & gargAuthAPI
& authEp & authEp
table_ngrams_get_api :: Token toServantToken :: Token -> S.Token
toServantToken = S.Token . TE.encodeUtf8
get_table_ngrams :: Token
-> NodeId -> NodeId
-> TabType -> TabType
-> ListId -> ListId
...@@ -76,7 +82,7 @@ table_ngrams_get_api :: Token ...@@ -76,7 +82,7 @@ table_ngrams_get_api :: Token
-> Maybe OrderBy -> Maybe OrderBy
-> Maybe Text -> Maybe Text
-> ClientM (VersionedWithCount NgramsTable) -> ClientM (VersionedWithCount NgramsTable)
table_ngrams_get_api (toServantToken -> token) nodeId = get_table_ngrams (toServantToken -> token) nodeId =
clientRoutes & apiWithCustomErrorScheme clientRoutes & apiWithCustomErrorScheme
& ($ GES_new) & ($ GES_new)
& backendAPI & backendAPI
...@@ -93,16 +99,13 @@ table_ngrams_get_api (toServantToken -> token) nodeId = ...@@ -93,16 +99,13 @@ table_ngrams_get_api (toServantToken -> token) nodeId =
& tableNgramsGetAPI & tableNgramsGetAPI
& getNgramsTableEp & getNgramsTableEp
toServantToken :: Token -> S.Token put_table_ngrams :: Token
toServantToken = S.Token . TE.encodeUtf8
table_ngrams_put_api :: Token
-> NodeId -> NodeId
-> TabType -> TabType
-> ListId -> ListId
-> Versioned NgramsTablePatch -> Versioned NgramsTablePatch
-> ClientM (Versioned NgramsTablePatch) -> ClientM (Versioned NgramsTablePatch)
table_ngrams_put_api (toServantToken -> token) nodeId = put_table_ngrams (toServantToken -> token) nodeId =
clientRoutes & apiWithCustomErrorScheme clientRoutes & apiWithCustomErrorScheme
& ($ GES_new) & ($ GES_new)
& backendAPI & backendAPI
...@@ -118,3 +121,28 @@ table_ngrams_put_api (toServantToken -> token) nodeId = ...@@ -118,3 +121,28 @@ table_ngrams_put_api (toServantToken -> token) nodeId =
& tableNgramsAPI & tableNgramsAPI
& tableNgramsPutAPI & tableNgramsPutAPI
& putNgramsTableEp & putNgramsTableEp
get_table :: Token
-> NodeId
-> Maybe TabType
-> Maybe Limit
-> Maybe Offset
-> Maybe Facet.OrderBy
-> Maybe RawQuery
-> Maybe Text
-> ClientM (HashedResponse FacetTableResult)
get_table (toServantToken -> token) nodeId =
clientRoutes & apiWithCustomErrorScheme
& ($ GES_new)
& backendAPI
& backendAPI'
& mkBackEndAPI
& gargAPIVersion
& gargPrivateAPI
& mkPrivateAPI
& ($ token)
& nodeEp
& nodeEndpointAPI
& ($ nodeId)
& tableAPI
& getTableEp
...@@ -35,12 +35,14 @@ import Gargantext.API.Routes.Named ...@@ -35,12 +35,14 @@ import Gargantext.API.Routes.Named
import Gargantext.API.Routes.Named.Corpus import Gargantext.API.Routes.Named.Corpus
import Gargantext.API.Routes.Named.Private import Gargantext.API.Routes.Named.Private
import Gargantext.Core qualified as Lang import Gargantext.Core qualified as Lang
import Gargantext.Core.Text.Corpus.Query (RawQuery(..))
import Gargantext.Core.Text.List.Social import Gargantext.Core.Text.List.Social
import Gargantext.Core.Text.Ngrams import Gargantext.Core.Text.Ngrams
import Gargantext.Core.Types ( CorpusId, ListId, ListType(..), NodeId, _NodeId ) import Gargantext.Core.Types ( CorpusId, ListId, ListType(..), NodeId, _NodeId )
import Gargantext.Core.Types.Individu import Gargantext.Core.Types.Individu
import Gargantext.Database.Action.User import Gargantext.Database.Action.User
import Gargantext.Database.Admin.Types.Hyperdata.Corpus import Gargantext.Database.Admin.Types.Hyperdata.Corpus
import Gargantext.Database.Query.Facet qualified as Facet
import Gargantext.Database.Query.Table.Node import Gargantext.Database.Query.Table.Node
import Gargantext.Database.Query.Tree.Root import Gargantext.Database.Query.Tree.Root
import Gargantext.Prelude hiding (get) import Gargantext.Prelude hiding (get)
...@@ -49,7 +51,7 @@ import Paths_gargantext (getDataFileName) ...@@ -49,7 +51,7 @@ import Paths_gargantext (getDataFileName)
import Servant import Servant
import Servant.Client import Servant.Client
import Servant.Job.Async import Servant.Job.Async
import Test.API.Routes (mkUrl, table_ngrams_get_api, table_ngrams_put_api, toServantToken, clientRoutes) import Test.API.Routes (mkUrl, get_table_ngrams, put_table_ngrams, toServantToken, clientRoutes, get_table)
import Test.API.Setup (withTestDBAndPort, setupEnvironment, createAliceAndBob) import Test.API.Setup (withTestDBAndPort, setupEnvironment, createAliceAndBob)
import Test.Database.Types import Test.Database.Types
import Test.Hspec import Test.Hspec
...@@ -59,6 +61,8 @@ import Test.Hspec.Wai.JSON (json) ...@@ -59,6 +61,8 @@ import Test.Hspec.Wai.JSON (json)
import Test.Types (JobPollHandle(..)) import Test.Types (JobPollHandle(..))
import Test.Utils (getJSON, pollUntilFinished, postJSONUrlEncoded, protectedJSON, withValidLogin) import Test.Utils (getJSON, pollUntilFinished, postJSONUrlEncoded, protectedJSON, withValidLogin)
import Web.FormUrlEncoded import Web.FormUrlEncoded
import Gargantext.API.HashedResponse
import Gargantext.Core.Types (TableResult(..))
newCorpusForUser :: TestEnv -> T.Text -> IO NodeId newCorpusForUser :: TestEnv -> T.Text -> IO NodeId
...@@ -145,7 +149,7 @@ tests = sequential $ aroundAll withTestDBAndPort $ do ...@@ -145,7 +149,7 @@ tests = sequential $ aroundAll withTestDBAndPort $ do
listId <- uploadJSONList port token cId listId <- uploadJSONList port token cId
let checkNgrams expected = do let checkNgrams expected = do
eng <- liftIO $ runClientM (table_ngrams_get_api token cId APINgrams.Terms listId 10 Nothing (Just MapTerm) Nothing Nothing Nothing Nothing) clientEnv eng <- liftIO $ runClientM (get_table_ngrams token cId APINgrams.Terms listId 10 Nothing (Just MapTerm) Nothing Nothing Nothing Nothing) clientEnv
case eng of case eng of
Left err -> fail (show err) Left err -> fail (show err)
Right r -> Right r ->
...@@ -164,7 +168,7 @@ tests = sequential $ aroundAll withTestDBAndPort $ do ...@@ -164,7 +168,7 @@ tests = sequential $ aroundAll withTestDBAndPort $ do
, NgramsReplace { _patch_old = Nothing , NgramsReplace { _patch_old = Nothing
, _patch_new = Just nre } ) , _patch_new = Just nre } )
] ]
_ <- liftIO $ runClientM (table_ngrams_put_api token cId APINgrams.Terms listId (Versioned 1 $ NgramsTablePatch $ fst patch)) clientEnv _ <- liftIO $ runClientM (put_table_ngrams token cId APINgrams.Terms listId (Versioned 1 $ NgramsTablePatch $ fst patch)) clientEnv
-- check that new term is added (with no parent) -- check that new term is added (with no parent)
checkNgrams [ (newTerm, []) checkNgrams [ (newTerm, [])
...@@ -175,7 +179,7 @@ tests = sequential $ aroundAll withTestDBAndPort $ do ...@@ -175,7 +179,7 @@ tests = sequential $ aroundAll withTestDBAndPort $ do
( newTerm ( newTerm
, toNgramsPatch [importedTerm] ) , toNgramsPatch [importedTerm] )
] ]
_ <- liftIO $ runClientM (table_ngrams_put_api token cId APINgrams.Terms listId (Versioned 32 $ NgramsTablePatch $ fst patchChildren)) clientEnv _ <- liftIO $ runClientM (put_table_ngrams token cId APINgrams.Terms listId (Versioned 32 $ NgramsTablePatch $ fst patchChildren)) clientEnv
-- check that new term is parent of old one -- check that new term is parent of old one
checkNgrams [ (newTerm, [importedTerm]) ] checkNgrams [ (newTerm, [importedTerm]) ]
...@@ -248,20 +252,40 @@ tests = sequential $ aroundAll withTestDBAndPort $ do ...@@ -248,20 +252,40 @@ tests = sequential $ aroundAll withTestDBAndPort $ do
describe "POST /api/v1.0/corpus/:id/add/form/async (JSON)" $ do describe "POST /api/v1.0/corpus/:id/add/form/async (JSON)" $ do
it "allows uploading a JSON docs file" $ \((testEnv, port), app) -> do it "allows uploading a JSON docs file" $ \((testEnv, port), app) ->
cId <- newCorpusForUser testEnv "alice"
withApplication app $ do withApplication app $ do
withValidLogin port "alice" (GargPassword "alice") $ \clientEnv token -> do withValidLogin port "alice" (GargPassword "alice") $ \clientEnv token -> do
void $ updateFortranDocsList testEnv port clientEnv token
it "doesn't use trashed documents for score calculation (#385)" $ \((testEnv, port), app) -> do
withApplication app $ do
withValidLogin port "alice" (GargPassword "alice") $ \clientEnv token -> do
(corpusId, _listId) <- updateFortranDocsList testEnv port clientEnv token
liftIO $ do
(HashedResponse _ TableResult{..})
<- checkEither $ runClientM (get_table token corpusId
(Just APINgrams.Docs)
(Just 10)
(Just 0)
(Just Facet.DateDesc)
(Just $ RawQuery "fortran")
Nothing
) clientEnv
length tr_docs `shouldBe` 2
updateFortranDocsList :: TestEnv -> Int -> ClientEnv -> Token -> WaiSession () (NodeId, CorpusId)
updateFortranDocsList testEnv port clientEnv token = do
corpusId <- liftIO $ newCorpusForUser testEnv "alice"
-- Import the docsList with only two documents, both containing a \"fortran\" term. -- Import the docsList with only two documents, both containing a \"fortran\" term.
([corpusId] :: [CorpusId]) <- protectedJSON token "POST" (mkUrl port ("/node/" <> build cId)) [aesonQQ|{"pn_typename":"NodeCorpus","pn_name":"Testing"}|] ([listId] :: [CorpusId]) <- protectedJSON token "POST" (mkUrl port ("/node/" <> build corpusId)) [aesonQQ|{"pn_typename":"NodeCorpus","pn_name":"Testing"}|]
simpleDocs <- liftIO (TIO.readFile =<< getDataFileName "test-data/ngrams/GarganText_DocsList-nodeId-177.json") simpleDocs <- liftIO (TIO.readFile =<< getDataFileName "test-data/ngrams/GarganText_DocsList-nodeId-177.json")
let newWithForm = mkNewWithForm simpleDocs "GarganText_DocsList-nodeId-177.json" let newWithForm = mkNewWithForm simpleDocs "GarganText_DocsList-nodeId-177.json"
(j :: JobPollHandle) <- checkEither $ fmap toJobPollHandle <$> liftIO (runClientM (add_file_async token corpusId newWithForm) clientEnv) (j :: JobPollHandle) <- checkEither $ fmap toJobPollHandle <$> liftIO (runClientM (add_file_async token corpusId newWithForm) clientEnv)
let mkPollUrl jh = "/corpus/" <> fromString (show $ _NodeId corpusId) <> "/add/form/async/" +|_jph_id jh|+ "/poll?limit=1" let mkPollUrl jh = "/corpus/" <> fromString (show $ _NodeId corpusId) <> "/add/form/async/" +|_jph_id jh|+ "/poll?limit=1"
j' <- pollUntilFinished token port mkPollUrl j j' <- pollUntilFinished token port mkPollUrl j
liftIO (_jph_status j' `shouldBe` "IsFinished") liftIO (_jph_status j' `shouldBe` "IsFinished")
pure (corpusId, listId)
toJobPollHandle :: JobStatus 'Safe JobLog -> JobPollHandle toJobPollHandle :: JobStatus 'Safe JobLog -> JobPollHandle
toJobPollHandle = either (\x -> panicTrace $ "toJobPollHandle:" <> T.pack x) identity . JSON.eitherDecode . JSON.encode toJobPollHandle = either (\x -> panicTrace $ "toJobPollHandle:" <> T.pack x) identity . JSON.eitherDecode . JSON.encode
......
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