[export] sqlite export tests

parent 33790065
Pipeline #7336 passed with stages
in 54 minutes and 45 seconds
......@@ -129,6 +129,8 @@ library
Gargantext.API.Node
Gargantext.API.Node.Contact.Types
Gargantext.API.Node.Corpus.Annuaire
Gargantext.API.Node.Corpus.Export.Types
Gargantext.API.Node.Corpus.Export.Utils
Gargantext.API.Node.Corpus.New
Gargantext.API.Node.Corpus.New.Types
Gargantext.API.Node.Corpus.Types
......@@ -325,8 +327,6 @@ library
Gargantext.API.Ngrams.NgramsTree
Gargantext.API.Node.Contact
Gargantext.API.Node.Corpus.Export
Gargantext.API.Node.Corpus.Export.Types
Gargantext.API.Node.Corpus.Export.Utils
Gargantext.API.Node.Corpus.Searx
Gargantext.API.Node.Corpus.Subcorpus
Gargantext.API.Node.Document.Export
......@@ -739,6 +739,7 @@ common testDependencies
, servant-auth-client
, servant-client >= 0.20 && < 0.21
, servant-client-core >= 0.20 && < 0.21
, servant-server >= 0.20.1 && < 0.21
, servant-websockets >= 2.0.0 && < 2.1
, shelly >= 1.9 && < 2
, stm >= 2.5.1.0 && < 2.6
......@@ -841,11 +842,14 @@ test-suite garg-test-hspec
type: exitcode-stdio-1.0
main-is: drivers/hspec/Main.hs
build-depends: process ^>= 1.6.18.0
, servant >= 0.20.1 && < 0.21
, sqlite-simple >= 0.4.19 && < 0.5
other-modules:
Paths_gargantext
Test.API
Test.API.Authentication
Test.API.Errors
Test.API.Export
Test.API.GraphQL
Test.API.Notifications
Test.API.Private
......
......@@ -22,7 +22,6 @@ Node API
-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-}
module Gargantext.API.Node
......
......@@ -42,6 +42,7 @@ import Gargantext.Database.Query.Table.Node.Error (HasNodeError)
import Gargantext.Database.Query.Table.Node.Select (selectNodesWithUsername)
import Gargantext.Prelude
import Paths_gargantext qualified as PG -- cabal magic build module
import Prelude qualified
import System.Directory (removeDirectoryRecursive)
import System.IO.Temp (createTempDirectory, getCanonicalTemporaryDirectory)
......@@ -74,8 +75,7 @@ mkCorpusSQLite :: ( CES.MonadMask m
=> CorpusId
-> Maybe ListId
-> m CorpusSQLite
mkCorpusSQLite cId lId =
CES.bracket setup tearDown $ \(fp, _fname, fpath) -> do
mkCorpusSQLite cId lId = withTempSQLiteDir $ \(fp, _fname, fpath) -> do
corpus <- getNodeWith cId (Proxy @HyperdataCorpus)
......@@ -129,7 +129,12 @@ mkCorpusSQLite cId lId =
bsl <- liftBase $ BSL.readFile fpath
pure $ CorpusSQLite bsl
withTempSQLiteDir :: (CES.MonadMask m, MonadBase IO m)
=> ((FilePath, Prelude.String, FilePath) -> m a)
-> m a
withTempSQLiteDir = CES.bracket setup tearDown
where
setup = do
tmpDir <- liftBase getCanonicalTemporaryDirectory
......@@ -140,4 +145,3 @@ mkCorpusSQLite cId lId =
pure (fp, fname, fpath)
tearDown (fp, _fname, _fpath) = do
liftBase $ removeDirectoryRecursive fp
......@@ -5,6 +5,7 @@ import Prelude
import Test.Hspec
import qualified Test.API.Authentication as Auth
import qualified Test.API.Errors as Errors
import qualified Test.API.Export as Export
import qualified Test.API.GraphQL as GraphQL
import qualified Test.API.Notifications as Notifications
import qualified Test.API.Private as Private
......@@ -17,6 +18,7 @@ tests = describe "Gargantext API" $ do
Private.tests
GraphQL.tests
Errors.tests
Export.tests
UpdateList.tests
Notifications.tests
Worker.tests
{-# LANGUAGE ScopedTypeVariables #-}
module Test.API.Export (tests) where
import Data.ByteString.Lazy qualified as BSL
import Data.Version (showVersion)
import Database.SQLite.Simple qualified as S
-- import Fmt (build)
import Gargantext.API.Node.Corpus.Export.Types (CorpusSQLite(..))
import Gargantext.API.Node.Corpus.Export.Utils (withTempSQLiteDir)
import Gargantext.Core.Types (unNodeId)
import Gargantext.Core.Types.Individu
import Gargantext.Prelude hiding (get)
import Paths_gargantext qualified as PG -- cabal magic build module
import Servant.API.ResponseHeaders (Headers(getResponse))
import Servant.Auth.Client ()
import Servant.Client
import Test.API.Prelude (checkEither)
import Test.API.Routes (get_corpus_sqlite_export)
import Test.API.Setup (withTestDBAndPort, dbEnvSetup, SpecContext (..))
import Test.API.UpdateList (createFortranDocsList)
import Test.Hspec
import Test.Hspec.Wai.Internal (withApplication)
import Test.Utils (withValidLogin)
tests :: Spec
tests = sequential $ aroundAll withTestDBAndPort $ beforeAllWith dbEnvSetup $ do
describe "Export API" $ do
describe "GET /api/v1.0/corpus/cId/sqlite" $ do
it "returns correct SQLite db" $ \ctx -> do
let port = _sctx_port ctx
withApplication (_sctx_app ctx) $ do
withValidLogin port "alice" (GargPassword "alice") $ \clientEnv token -> do
cId <- createFortranDocsList (_sctx_env ctx) port clientEnv token
void $ liftIO $ do
(CorpusSQLite { _cs_bs }) <-
(checkEither $ runClientM (get_corpus_sqlite_export token cId) clientEnv) >>= (pure . getResponse)
withTempSQLiteDir $ \(_fp, _fname, fpath) -> do
BSL.writeFile fpath _cs_bs
S.withConnection fpath $ \conn -> do
[S.Only cId'] <- S.query_ conn "SELECT value FROM info WHERE key = 'corpusId'"
cId' `shouldBe` unNodeId cId
-- [S.Only lId'] <- S.query_ conn "SELECT value FROM info WHERE key = 'listId'"
-- lId' `shouldBe` unNodeId listId
[S.Only version] <- S.query_ conn "SELECT value FROM info WHERE key = 'gargVersion'"
version `shouldBe` showVersion PG.version
[S.Only corpoLen] <- S.query conn "SELECT COUNT(*) FROM corpus WHERE id = ?" (S.Only $ unNodeId cId)
corpoLen `shouldBe` (1 :: Int)
-- [S.Only listLen] <- S.query conn "SELECT COUNT(*) FROM lists WHERE id = ?" (S.Only $ unNodeId listId)
-- listLen `shouldBe` (1 :: Int)
[S.Only docsLen] <- S.query_ conn "SELECT COUNT(*) FROM documents"
docsLen `shouldBe` (2 :: Int)
[S.Only ngramsLen] <- S.query_ conn "SELECT COUNT(*) FROM ngrams"
ngramsLen `shouldBe` (0 :: Int)
......@@ -16,8 +16,7 @@ import Data.Aeson qualified as JSON
import Data.Text qualified as T
import Gargantext.API.Errors
import Gargantext.Core.Types.Individu
import Gargantext.Core.Types (NodeId)
import Gargantext.Core.Types (NodeType(..))
import Gargantext.Core.Types (NodeId, NodeType(..))
import Gargantext.Core.Worker.Env () -- instance HasNodeError
import Gargantext.Database.Action.User
import Gargantext.Database.Admin.Types.Hyperdata.Corpus
......
......@@ -28,6 +28,7 @@ module Test.API.Routes (
, delete_node
, add_form_to_list
, add_tsv_to_list
, get_corpus_sqlite_export
) where
import Data.Text.Encoding qualified as TE
......@@ -37,12 +38,13 @@ import Gargantext.API.Errors
import Gargantext.API.HashedResponse (HashedResponse)
import Gargantext.API.Ngrams.List.Types (WithJsonFile, WithTextFile)
import Gargantext.API.Ngrams.Types ( NgramsTable, NgramsTablePatch, OrderBy, TabType, Versioned, VersionedWithCount )
import Gargantext.API.Node.Corpus.Export.Types (CorpusSQLite)
import Gargantext.API.Routes.Named
import Gargantext.API.Routes.Named.Corpus (CorpusExportAPI(corpusSQLiteEp))
import Gargantext.API.Routes.Named.List (updateListJSONEp, updateListTSVEp)
import Gargantext.API.Routes.Named.Node hiding (treeAPI)
import Gargantext.API.Routes.Named.Private hiding (tableNgramsAPI)
import Gargantext.API.Routes.Named.Publish (PublishAPI(..))
import Gargantext.API.Routes.Named.Publish (PublishRequest(..))
import Gargantext.API.Routes.Named.Publish (PublishAPI(..), PublishRequest(..))
import Gargantext.API.Routes.Named.Table
import Gargantext.API.Routes.Named.Tree (nodeTreeEp)
import Gargantext.API.Types () -- MimeUnrender instances
......@@ -57,6 +59,7 @@ import Gargantext.Database.Query.Table.NodeNode (SourceId(..), TargetId(..))
import Gargantext.Prelude
import Network.HTTP.Types qualified as H
import Network.Wai.Handler.Warp (Port)
import Servant (Headers, Header)
import Servant.API.WebSocket qualified as WS
import Servant.Auth.Client qualified as S
import Servant.Client (ClientM)
......@@ -355,3 +358,22 @@ publish_node (toServantToken -> token) sourceId policy = fmap UnsafeMkNodeId $
& publishAPI
& publishEp
& ($ PublishRequest policy)
get_corpus_sqlite_export :: Token
-> CorpusId
-> ClientM (Headers '[Header "Content-Disposition" Text] CorpusSQLite)
get_corpus_sqlite_export (toServantToken -> token) cId =
clientRoutes & apiWithCustomErrorScheme
& ($ GES_new)
& backendAPI
& backendAPI'
& mkBackEndAPI
& gargAPIVersion
& gargPrivateAPI
& mkPrivateAPI
& ($ token)
& corpusExportAPI
& ($ cId)
& corpusSQLiteEp
& ($ Nothing) -- Maybe ListId
......@@ -23,6 +23,7 @@ module Test.API.UpdateList (
, JobPollHandle(..)
, updateNode
, createDocsList
, createFortranDocsList
) where
import Control.Lens (mapped, over)
......
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