[test] some fixes, more arbitrary moved to instances

parent 2d61da1c
Pipeline #6993 passed with stages
in 73 minutes and 4 seconds
...@@ -34,7 +34,6 @@ Pouillard (who mainly made it). ...@@ -34,7 +34,6 @@ Pouillard (who mainly made it).
module Gargantext.API module Gargantext.API
where where
import Control.Concurrent
import Control.Concurrent.Async qualified as Async import Control.Concurrent.Async qualified as Async
import Data.Cache qualified as InMemory import Data.Cache qualified as InMemory
import Data.List (lookup) import Data.List (lookup)
...@@ -42,13 +41,12 @@ import Data.Set qualified as Set ...@@ -42,13 +41,12 @@ import Data.Set qualified as Set
import Data.Text (pack) import Data.Text (pack)
import Data.Text.Encoding qualified as TE import Data.Text.Encoding qualified as TE
import Data.Text.IO (putStrLn) import Data.Text.IO (putStrLn)
import Data.Validity
import Gargantext.API.Admin.Auth.Types (AuthContext) import Gargantext.API.Admin.Auth.Types (AuthContext)
import Gargantext.API.Admin.EnvTypes (Env, FireWall(..), Mode(..), env_config, env_jwt_settings) import Gargantext.API.Admin.EnvTypes (Env, FireWall(..), Mode(..), env_config, env_jwt_settings)
import Gargantext.API.Admin.Settings (newEnv) import Gargantext.API.Admin.Settings (newEnv)
import Gargantext.API.Middleware (logStdoutDevSanitised) import Gargantext.API.Middleware (logStdoutDevSanitised)
import Gargantext.API.Routes.Named (API) import Gargantext.API.Routes.Named (API)
import Gargantext.API.Routes.Named.EKG import Gargantext.API.Routes.Named.EKG (EkgAPI)
import Gargantext.API.Server.Named (server) import Gargantext.API.Server.Named (server)
import Gargantext.Core.Config (gc_notifications_config, gc_frontend_config) import Gargantext.Core.Config (gc_notifications_config, gc_frontend_config)
import Gargantext.Core.Config.Types (CORSOrigin(..), CORSSettings, MicroServicesProxyStatus(..), NotificationsConfig(..), PortNumber, SettingsFile(..), corsAllowedOrigins, fc_appPort, fc_cors, fc_cookie_settings, microServicesProxyStatus) import Gargantext.Core.Config.Types (CORSOrigin(..), CORSSettings, MicroServicesProxyStatus(..), NotificationsConfig(..), PortNumber, SettingsFile(..), corsAllowedOrigins, fc_appPort, fc_cors, fc_cookie_settings, microServicesProxyStatus)
...@@ -57,12 +55,12 @@ import Gargantext.Core.Notifications (withNotifications) ...@@ -57,12 +55,12 @@ import Gargantext.Core.Notifications (withNotifications)
import Gargantext.Database.Prelude qualified as DB import Gargantext.Database.Prelude qualified as DB
import Gargantext.MicroServices.ReverseProxy (microServicesProxyApp) import Gargantext.MicroServices.ReverseProxy (microServicesProxyApp)
import Gargantext.Prelude hiding (putStrLn, to) import Gargantext.Prelude hiding (putStrLn, to)
import Gargantext.System.Logging import Gargantext.System.Logging (withLoggerHoisted)
import Network.HTTP.Types hiding (Query) import Network.HTTP.Types hiding (Query)
import Network.Wai import Network.Wai (Middleware, Request, requestHeaders)
import Network.Wai.Handler.Warp hiding (defaultSettings) import Network.Wai.Handler.Warp hiding (defaultSettings)
import Network.Wai.Middleware.Cors import Network.Wai.Middleware.Cors
import Network.Wai.Middleware.RequestLogger import Network.Wai.Middleware.RequestLogger (logStdout)
-- import Paths_gargantext (getDataDir) -- import Paths_gargantext (getDataDir)
import Servant hiding (Header) import Servant hiding (Header)
import Servant.Client.Core.BaseUrl (showBaseUrl) import Servant.Client.Core.BaseUrl (showBaseUrl)
......
...@@ -16,17 +16,15 @@ module Gargantext.Core ...@@ -16,17 +16,15 @@ module Gargantext.Core
where where
import Control.Exception.Safe (impureThrow) import Control.Exception.Safe (impureThrow)
import Data.Aeson
import Data.LanguageCodes qualified as ISO639
import Data.Bimap qualified as Bimap
import Data.Bimap (Bimap) import Data.Bimap (Bimap)
import Data.Bimap qualified as Bimap
import Data.LanguageCodes qualified as ISO639
import Data.Morpheus.Types (GQLType) import Data.Morpheus.Types (GQLType)
import Data.Swagger import Data.Swagger (ToSchema(..), defaultSchemaOptions, genericDeclareNamedSchemaUnrestricted)
import Data.Text (pack) import Data.Text (pack)
import Gargantext.Prelude hiding (All) import Gargantext.Prelude hiding (All)
import Servant.API
import Test.QuickCheck
import Prelude (userError) import Prelude (userError)
import Servant.API (FromHttpApiData(..), ToHttpApiData(..), URI)
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | Language of a Text -- | Language of a Text
...@@ -83,8 +81,6 @@ instance FromHttpApiData Lang ...@@ -83,8 +81,6 @@ instance FromHttpApiData Lang
instance ToHttpApiData Lang where instance ToHttpApiData Lang where
toUrlPiece = pack . show toUrlPiece = pack . show
instance Hashable Lang instance Hashable Lang
instance Arbitrary Lang where
arbitrary = arbitraryBoundedEnum
toISO639 :: Lang -> ISO639.ISO639_1 toISO639 :: Lang -> ISO639.ISO639_1
toISO639 DE = ISO639.DE toISO639 DE = ISO639.DE
......
...@@ -41,7 +41,6 @@ import Gargantext.Core.Types.Main ...@@ -41,7 +41,6 @@ import Gargantext.Core.Types.Main
import Gargantext.Core.Utils.Prefix (unPrefix, wellNamedSchema) import Gargantext.Core.Utils.Prefix (unPrefix, wellNamedSchema)
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
import Gargantext.Prelude hiding (Ordering, empty) import Gargantext.Prelude hiding (Ordering, empty)
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
------------------------------------------------------------------------ ------------------------------------------------------------------------
...@@ -185,9 +184,6 @@ $(deriveJSON (unPrefix "tr_") ''TableResult) ...@@ -185,9 +184,6 @@ $(deriveJSON (unPrefix "tr_") ''TableResult)
instance (Typeable a, ToSchema a) => ToSchema (TableResult a) where instance (Typeable a, ToSchema a) => ToSchema (TableResult a) where
declareNamedSchema = wellNamedSchema "tr_" declareNamedSchema = wellNamedSchema "tr_"
instance Arbitrary a => Arbitrary (TableResult a) where
arbitrary = TableResult <$> arbitrary <*> arbitrary
---------------------------------------------------------------------------- ----------------------------------------------------------------------------
data Typed a b = data Typed a b =
Typed { _withType :: a Typed { _withType :: a
......
...@@ -39,8 +39,10 @@ import Gargantext.API.Node.Share.Types (ShareNodeParams(..)) ...@@ -39,8 +39,10 @@ import Gargantext.API.Node.Share.Types (ShareNodeParams(..))
import Gargantext.API.Node.Update.Types qualified as NU import Gargantext.API.Node.Update.Types qualified as NU
import Gargantext.API.Node.Types (NewWithForm, RenameNode(..), WithQuery) import Gargantext.API.Node.Types (NewWithForm, RenameNode(..), WithQuery)
import Gargantext.API.Viz.Types (PhyloData) import Gargantext.API.Viz.Types (PhyloData)
import Gargantext.Core (Lang)
import Gargantext.Core.Notifications.CentralExchange.Types qualified as CET import Gargantext.Core.Notifications.CentralExchange.Types qualified as CET
import Gargantext.Core.Notifications.Dispatcher.Types qualified as DET import Gargantext.Core.Notifications.Dispatcher.Types qualified as DET
import Gargantext.Core.Types (TableResult)
import Gargantext.Core.Types.Individu qualified as Individu import Gargantext.Core.Types.Individu qualified as Individu
import Gargantext.Core.Types.Main (ListType(CandidateTerm, StopTerm, MapTerm)) import Gargantext.Core.Types.Main (ListType(CandidateTerm, StopTerm, MapTerm))
import Gargantext.Core.Viz.Phylo qualified as Phylo import Gargantext.Core.Viz.Phylo qualified as Phylo
...@@ -98,6 +100,8 @@ alphanum :: [Char] ...@@ -98,6 +100,8 @@ alphanum :: [Char]
alphanum = smallLetter <> largeLetter <> digit alphanum = smallLetter <> largeLetter <> digit
instance (Arbitrary a, Generic a) => Arbitrary (TableResult a) where arbitrary = genericArbitrary
instance Arbitrary Individu.User where arbitrary = genericArbitrary instance Arbitrary Individu.User where arbitrary = genericArbitrary
...@@ -211,6 +215,9 @@ instance Arbitrary Phylo.TimeUnit where arbitrary = genericArbitrary ...@@ -211,6 +215,9 @@ instance Arbitrary Phylo.TimeUnit where arbitrary = genericArbitrary
instance Arbitrary PhyloData where arbitrary = genericArbitrary instance Arbitrary PhyloData where arbitrary = genericArbitrary
instance Arbitrary Lang where arbitrary = arbitraryBoundedEnum
instance Arbitrary NU.UpdateNodeParams where arbitrary = genericArbitrary instance Arbitrary NU.UpdateNodeParams where arbitrary = genericArbitrary
instance Arbitrary NU.Method where arbitrary = arbitraryBoundedEnum instance Arbitrary NU.Method where arbitrary = arbitraryBoundedEnum
instance Arbitrary NU.Granularity where arbitrary = arbitraryBoundedEnum instance Arbitrary NU.Granularity where arbitrary = arbitraryBoundedEnum
......
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