[test] some test refactorings

parent 8b0f558b
Pipeline #4599 failed with stages
in 27 seconds
......@@ -151,7 +151,7 @@ source-repository-package
source-repository-package
type: git
location: ssh://git@gitlab.iscpif.fr:20022/gargantext/crawlers/epo.git
tag: 4918c32679edaba87d05bed88ea1c3024813946d
tag: 10e2303c01079715e98a39c36f1034d50c08f50f
allow-older: *
allow-newer: *
......
......@@ -484,7 +484,7 @@ library
, process ^>= 1.6.13.2
, product-profunctors ^>= 0.11.0.3
, profunctors ^>= 5.6.2
, protolude ^>= 0.3.0
, protolude ^>= 0.3.3
, pureMD5 ^>= 2.1.4
, quickcheck-instances ^>= 0.3.25.2
, rake ^>= 0.0.1
......@@ -890,6 +890,7 @@ test-suite garg-test-tasty
Database.Operations
Graph.Clustering
Graph.Distance
Instances
Ngrams.Lang
Ngrams.Lang.En
Ngrams.Lang.Fr
......@@ -945,6 +946,7 @@ test-suite garg-test-tasty
, containers ^>= 0.6.5.1
, crawlerArxiv
, duckling ^>= 0.2.0.0
, epo
, extra ^>= 1.7.9
, gargantext
, gargantext-prelude
......@@ -961,6 +963,7 @@ test-suite garg-test-tasty
, patches-map ^>= 0.1.0.1
, postgres-options >= 0.2 && < 0.3
, postgresql-simple >= 0.6.4 && < 0.7
, protolude ^>= 0.3.3
, quickcheck-instances ^>= 0.3.25.2
, raw-strings-qq
, recover-rtti >= 0.4 && < 0.5
......
......@@ -12,12 +12,13 @@ New corpus means either:
- new data in existing corpus
-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ViewPatterns #-}
module Gargantext.API.Node.Corpus.New
where
module Gargantext.API.Node.Corpus.New where
import Conduit
import Control.Lens hiding (elements, Empty)
......@@ -36,7 +37,6 @@ import Servant.Job.Utils (jsonOptions)
-- import Servant.Multipart
import Data.Text.Encoding qualified as TE
-- import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary
import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs)
import Gargantext.API.Admin.Types (HasSettings)
......@@ -126,8 +126,6 @@ api uid (Query q _ as) = do
-- TODO use this route for Client implementation
data ApiInfo = ApiInfo { api_info :: [API.ExternalAPIs]}
deriving (Generic)
instance Arbitrary ApiInfo where
arbitrary = ApiInfo <$> arbitrary
deriveJSON (unPrefix "") 'ApiInfo
......@@ -174,15 +172,9 @@ instance ToJSON WithQuery where
instance ToSchema WithQuery where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_wq_")
instance Arbitrary WithQuery where
arbitrary = WithQuery <$> arbitrary
<*> arbitrary
<*> arbitrary
<*> arbitrary
<*> arbitrary
<*> arbitrary
<*> arbitrary
<*> arbitrary
------------------------------------------------------------------------
instance ToSchema EPO.AuthKey where
declareNamedSchema = genericDeclareNamedSchema defaultSchemaOptions
------------------------------------------------------------------------
......
{-|
Module : Graph.Clustering
Module : Core.Text
Description : Basic tests to avoid quick regression
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......
{-|
Module : Core.Text.Corpus.Query
Description : Gargantext tests
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
......
{-|
Module : Gargantext.Core.Text.Examples
Module : Core.Text.Examples
Description : Minimal Examples to test behavior of the functions.
Copyright : (c) CNRS, 2017 - present
License : AGPL + CECILL v3
......
{-|
Module : Gargantext.Core.Text.Flow
Module : Core.Text.Flow
Description : Server API
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......
{-|
Module : Database.Operations
Description : Gargantext tests
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
......
{-|
Module : Ngrams.Lang
Module : Ngrams.Lang.En
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......
{-|
Module : Ngrams.Lang
Module : Ngrams.Lang.Fr
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......
{-|
Module : Ngrams.Query
Description : Gargantext tests
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
module Ngrams.Query (tests) where
......
{-|
Module : Ngrams.Query.PaginationCorpus
Description : Gargantext tests
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE ScopedTypeVariables #-}
module Ngrams.Query.PaginationCorpus where
......
{-|
Module : Offline.JSON
Description : Gargantext tests
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
......@@ -6,18 +16,19 @@
module Offline.JSON (tests) where
import Data.Aeson
import Data.ByteString qualified as B
import Data.ByteString.Lazy.Char8 qualified as C8
import Data.Either
import Gargantext.API.Node.Corpus.New
import Gargantext.API.Node.Corpus.Types
import Gargantext.Core.Types.Phylo
import Gargantext.Core.Viz.Phylo.API
import Instances ()
import Prelude
import Test.Tasty
import Test.Tasty.HUnit
import Test.Tasty.QuickCheck
import Text.RawString.QQ
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy.Char8 as C8
import Paths_gargantext
......
......@@ -6,9 +6,6 @@ License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
......
{-|
Module : WOS
Module : Parsers.WOS
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......
{-|
Module : Utils
Description : Test utils
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE ScopedTypeVariables #-}
module Utils where
......
{-|
Module : Utils.Jobs
Description : Gargantext tests
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NumericUnderscores #-}
module Utils.Jobs (test) where
import Control.Concurrent
......
{-|
Module : Main
Description : Gargantext tests
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
module Main where
......
......@@ -34,6 +34,7 @@ main = do
cryptoSpec <- testSpec "Crypto" Crypto.test
nlpSpec <- testSpec "NLP" NLP.test
jobsSpec <- testSpec "Jobs" Jobs.test
dbSpec <- testSpec "DB" DB.tests
defaultMain $ testGroup "Gargantext"
[ utilSpec
......@@ -45,4 +46,5 @@ main = do
, NgramsQuery.tests
, CorpusQuery.tests
, JSON.tests
, dbSpec
]
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