Commit 7ce34b7c authored by Alfredo Di Napoli's avatar Alfredo Di Napoli

Setup test for simple TSV upload

parent fd4b99ec
Pipeline #7473 passed with stages
in 48 minutes and 35 seconds
{-# LANGUAGE BangPatterns #-} {-# LANGUAGE BangPatterns #-}
{-# LANGUAGE TypeApplications #-} {-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
module Test.API.Private.List ( module Test.API.Private.List (
tests tests
) where ) where
import Data.Aeson.QQ
import Data.Text.IO qualified as TIO
import Gargantext.API.Ngrams.List.Types
import Gargantext.API.Ngrams.Types qualified as APINgrams
import Gargantext.API.Node.Corpus.New.Types qualified as FType
import Gargantext.Core.Config
import Gargantext.Core.Types
import Gargantext.Core.Types.Individu import Gargantext.Core.Types.Individu
import Gargantext.Prelude import Gargantext.Prelude
import Paths_gargantext
import Servant.Client.Streaming
import Test.API.Prelude (newCorpusForUser, checkEither)
import Test.API.Routes
import Test.API.Setup import Test.API.Setup
import Test.Database.Types
import Test.Hspec (Spec, it, aroundAll, describe, sequential) import Test.Hspec (Spec, it, aroundAll, describe, sequential)
import Test.Hspec.Expectations
import Test.Hspec.Wai.Internal (withApplication) import Test.Hspec.Wai.Internal (withApplication)
import Test.Utils import Test.Utils
import Fmt
tests :: Spec tests :: Spec
tests = sequential $ aroundAll withTestDBAndPort $ do tests = sequential $ aroundAll withTestDBAndPort $ do
...@@ -23,7 +39,21 @@ tests = sequential $ aroundAll withTestDBAndPort $ do ...@@ -23,7 +39,21 @@ tests = sequential $ aroundAll withTestDBAndPort $ do
describe "Importing terms as TSV" $ do describe "Importing terms as TSV" $ do
it "should work for the simplest case" $ \(SpecContext _testEnv serverPort app _) -> do it "[#381] should work" $ \(SpecContext testEnv port app _) -> do
cId <- newCorpusForUser testEnv "alice"
let log_cfg = (test_config testEnv) ^. gc_logging
withApplication app $ do withApplication app $ do
withValidLogin serverPort "alice" (GargPassword "alice") $ \_clientEnv _token -> do withValidLogin port "alice" (GargPassword "alice") $ \clientEnv token -> do
pure () ([listId] :: [NodeId]) <- protectedJSON token "POST" (mkUrl port ("/node/" <> build cId)) [aesonQQ|{"pn_typename":"NodeList","pn_name":"Testing"}|]
-- Upload the CSV doc
simpleNgrams <- liftIO (TIO.readFile =<< getDataFileName "test-data/ngrams/simple.tsv")
let params = WithTextFile { _wtf_filetype = FType.TSV
, _wtf_data = simpleNgrams
, _wtf_name = "simple.tsv" }
ji <- checkEither $ liftIO $ runClientM (add_tsv_to_list token listId params) clientEnv
_ <- pollUntilWorkFinished log_cfg port ji
-- Now check that we can retrieve the ngrams
liftIO $ do
eRes <- runClientM (get_table_ngrams token cId APINgrams.Terms listId 50 Nothing (Just MapTerm) Nothing Nothing Nothing Nothing) clientEnv
eRes `shouldSatisfy` isRight
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