[refactor] some import refactorings

parent 57be61f7
Pipeline #7038 failed with stages
in 70 minutes and 53 seconds
...@@ -147,6 +147,7 @@ library ...@@ -147,6 +147,7 @@ library
Gargantext.API.Node.Update Gargantext.API.Node.Update
Gargantext.API.Node.Update.Types Gargantext.API.Node.Update.Types
Gargantext.API.Prelude Gargantext.API.Prelude
Gargantext.API.Public.Types
Gargantext.API.Routes Gargantext.API.Routes
Gargantext.API.Routes.Named Gargantext.API.Routes.Named
Gargantext.API.Routes.Named.Annuaire Gargantext.API.Routes.Named.Annuaire
...@@ -170,6 +171,7 @@ library ...@@ -170,6 +171,7 @@ library
Gargantext.API.Routes.Named.Tree Gargantext.API.Routes.Named.Tree
Gargantext.API.Routes.Named.Viz Gargantext.API.Routes.Named.Viz
Gargantext.API.Routes.Types Gargantext.API.Routes.Types
Gargantext.API.Search.Types
Gargantext.API.Types Gargantext.API.Types
Gargantext.API.Viz.Types Gargantext.API.Viz.Types
Gargantext.API.Worker Gargantext.API.Worker
...@@ -332,9 +334,7 @@ library ...@@ -332,9 +334,7 @@ library
Gargantext.API.Node.DocumentsFromWriteNodes Gargantext.API.Node.DocumentsFromWriteNodes
Gargantext.API.Node.FrameCalcUpload Gargantext.API.Node.FrameCalcUpload
Gargantext.API.Node.New Gargantext.API.Node.New
Gargantext.API.Public.Types
Gargantext.API.Search Gargantext.API.Search
Gargantext.API.Search.Types
Gargantext.API.Server.Named Gargantext.API.Server.Named
Gargantext.API.Server.Named.EKG Gargantext.API.Server.Named.EKG
Gargantext.API.Server.Named.Ngrams Gargantext.API.Server.Named.Ngrams
......
...@@ -51,8 +51,9 @@ import Data.UUID.V4 (nextRandom) ...@@ -51,8 +51,9 @@ import Data.UUID.V4 (nextRandom)
import Gargantext.API.Admin.Auth.Types import Gargantext.API.Admin.Auth.Types
import Gargantext.API.Admin.EnvTypes (Env) import Gargantext.API.Admin.EnvTypes (Env)
import Gargantext.API.Auth.PolicyCheck import Gargantext.API.Auth.PolicyCheck
import Gargantext.API.Errors import Gargantext.API.Errors (BackendInternalError(..), HasAuthenticationError, _AuthenticationError)
import Gargantext.API.Prelude (authenticationError, HasServerError, GargServerC, _ServerError, GargM, IsGargServer) import Gargantext.API.Prelude (authenticationError, HasServerError, GargServerC, _ServerError, GargM, IsGargServer)
import Gargantext.API.Routes.Named qualified as Named
import Gargantext.API.Worker (serveWorkerAPI) import Gargantext.API.Worker (serveWorkerAPI)
import Gargantext.Core.Config (HasJWTSettings(..)) import Gargantext.Core.Config (HasJWTSettings(..))
import Gargantext.Core.Mail (MailModel(..), mail) import Gargantext.Core.Mail (MailModel(..), mail)
...@@ -69,11 +70,9 @@ import Gargantext.Database.Schema.Node (NodePoly(_node_id)) ...@@ -69,11 +70,9 @@ import Gargantext.Database.Schema.Node (NodePoly(_node_id))
import Gargantext.Prelude hiding (Handler, reverse, to) import Gargantext.Prelude hiding (Handler, reverse, to)
import Gargantext.Prelude.Crypto.Auth qualified as Auth import Gargantext.Prelude.Crypto.Auth qualified as Auth
import Gargantext.Prelude.Crypto.Pass.User (gargPass) import Gargantext.Prelude.Crypto.Pass.User (gargPass)
import Servant import Servant (HasServer, ServerT, NamedRoutes, errBody, hoistServer, err404)
import Servant.API.Generic () import Servant.Auth.Server (makeJWT)
import Servant.Auth.Server import Servant.Server.Generic (AsServerT)
import Servant.Server.Generic
import qualified Gargantext.API.Routes.Named as Named
--------------------------------------------------- ---------------------------------------------------
......
...@@ -47,7 +47,7 @@ import Gargantext.Core.Types.Individu (Username, GargPassword(..), arbitraryUser ...@@ -47,7 +47,7 @@ import Gargantext.Core.Types.Individu (Username, GargPassword(..), arbitraryUser
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger) import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
import Gargantext.Database.Admin.Types.Node (NodeId(..), ListId, DocId, UserId (..)) import Gargantext.Database.Admin.Types.Node (NodeId(..), ListId, DocId, UserId (..))
import Gargantext.Prelude hiding (reverse) import Gargantext.Prelude hiding (reverse)
import Servant.Auth.Server import Servant.Auth.Server (CookieSettings, JWTSettings, ToJWT, FromJWT)
import Test.QuickCheck (elements) import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary) import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
......
-- | {-|
Module : Gargantext.API.Admin.EnvTypes
Description : Env definitions in which the Gargantext app is run
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeFamilies #-}
...@@ -25,15 +35,13 @@ module Gargantext.API.Admin.EnvTypes ( ...@@ -25,15 +35,13 @@ module Gargantext.API.Admin.EnvTypes (
, DevJobHandle(..) , DevJobHandle(..)
) where ) where
import Control.Lens hiding (Level, (:<), (.=)) import Control.Lens (to, view)
import Control.Monad.Except
import Control.Monad.Reader
import Data.List ((\\)) import Data.List ((\\))
import Data.Pool (Pool) import Data.Pool (Pool)
import Data.Text qualified as T import Data.Text qualified as T
import Database.PostgreSQL.Simple (Connection) import Database.PostgreSQL.Simple (Connection)
import Gargantext.API.Admin.Orchestrator.Types import Gargantext.API.Admin.Orchestrator.Types (JobLog, noJobLog)
import Gargantext.API.Errors.Types import Gargantext.API.Errors.Types (BackendInternalError)
import Gargantext.API.Prelude (GargM, IsGargServer) import Gargantext.API.Prelude (GargM, IsGargServer)
import Gargantext.Core.Notifications.CentralExchange qualified as CE import Gargantext.Core.Notifications.CentralExchange qualified as CE
import Gargantext.Core.Notifications.CentralExchange.Types qualified as CET import Gargantext.Core.Notifications.CentralExchange.Types qualified as CET
...@@ -51,6 +59,7 @@ import Network.HTTP.Client (Manager) ...@@ -51,6 +59,7 @@ import Network.HTTP.Client (Manager)
import Servant.Auth.Server (JWTSettings) import Servant.Auth.Server (JWTSettings)
import System.Log.FastLogger qualified as FL import System.Log.FastLogger qualified as FL
data Mode = Dev | Mock | Prod data Mode = Dev | Mock | Prod
deriving (Show, Read, Generic) deriving (Show, Read, Generic)
......
{-|
Module : Gargantext.API.Admin.Orchestrator.Types
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# OPTIONS_GHC -fno-warn-orphans #-} {-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
...@@ -5,17 +17,12 @@ ...@@ -5,17 +17,12 @@
module Gargantext.API.Admin.Orchestrator.Types module Gargantext.API.Admin.Orchestrator.Types
where where
import Control.Lens hiding (elements) import Data.Aeson (genericParseJSON, genericToJSON)
import Data.Aeson
import Data.Morpheus.Types ( GQLType, typeOptions ) import Data.Morpheus.Types ( GQLType, typeOptions )
import Data.Proxy import Data.Swagger (ToParamSchema, ToSchema, declareNamedSchema, defaultSchemaOptions, genericDeclareNamedSchemaUnrestricted)
import Data.Swagger hiding (URL, url, port)
import GHC.Generics hiding (to)
import Gargantext.API.GraphQL.UnPrefix qualified as GQLU import Gargantext.API.GraphQL.UnPrefix qualified as GQLU
import Gargantext.Core.Types (TODO(..)) import Gargantext.Core.Types (TODO(..))
import Gargantext.Prelude import Gargantext.Prelude
import Servant
import Servant.Job.Async
import Servant.Job.Types import Servant.Job.Types
import Servant.Job.Utils (jsonOptions) import Servant.Job.Utils (jsonOptions)
import Test.QuickCheck (elements) import Test.QuickCheck (elements)
...@@ -51,24 +58,6 @@ instance ToSchema ExternalAPIs where ...@@ -51,24 +58,6 @@ instance ToSchema ExternalAPIs where
instance ToSchema URL where instance ToSchema URL where
declareNamedSchema _ = declareNamedSchema (Proxy :: Proxy TODO) declareNamedSchema _ = declareNamedSchema (Proxy :: Proxy TODO)
data ScraperInput = ScraperInput
{ _scin_spider :: !Text
, _scin_query :: !(Maybe Text)
, _scin_user :: !Text
, _scin_corpus :: !Int
, _scin_report_every :: !(Maybe Int)
, _scin_limit :: !(Maybe Int)
, _scin_local_file :: !(Maybe Text)
, _scin_count_only :: !(Maybe Bool)
}
deriving Generic
makeLenses ''ScraperInput
instance FromJSON ScraperInput where
parseJSON = genericParseJSON $ jsonOptions "_scin_"
-- Proposal to replace the Corpus.API.Query type which seems to generically named.
data ScraperEvent = ScraperEvent data ScraperEvent = ScraperEvent
{ _scev_message :: !(Maybe Text) { _scev_message :: !(Maybe Text)
...@@ -117,19 +106,9 @@ instance ToSchema JobLog -- TODO _scst_ prefix ...@@ -117,19 +106,9 @@ instance ToSchema JobLog -- TODO _scst_ prefix
instance GQLType JobLog where instance GQLType JobLog where
typeOptions _ = GQLU.unPrefix "_scst_" typeOptions _ = GQLU.unPrefix "_scst_"
instance ToSchema ScraperInput -- TODO _scin_ prefix
instance ToParamSchema Offset -- where instance ToParamSchema Offset -- where
-- toParamSchema = panic "TODO" -- toParamSchema = panic "TODO"
instance ToParamSchema Limit -- where instance ToParamSchema Limit -- where
-- toParamSchema = panic "TODO" -- toParamSchema = panic "TODO"
type ScrapersEnv = JobEnv JobLog JobLog
type ScraperAPI = AsyncJobsAPI JobLog ScraperInput JobLog
------------------------------------------------------------------------
data AsyncJobs event ctI input output mode = AsyncJobs
{ asyncJobsAPI' :: mode :- AsyncJobsAPI' 'Unsafe 'Safe ctI '[JSON] Maybe event input output }
deriving Generic
...@@ -16,7 +16,7 @@ TODO-SECURITY: Critical ...@@ -16,7 +16,7 @@ TODO-SECURITY: Critical
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
module Gargantext.API.Admin.Settings module Gargantext.API.Admin.Settings
where where
import Codec.Serialise (Serialise(), serialise) import Codec.Serialise (Serialise(), serialise)
...@@ -24,15 +24,15 @@ import Data.ByteString.Lazy qualified as L ...@@ -24,15 +24,15 @@ import Data.ByteString.Lazy qualified as L
import Data.Pool (Pool) import Data.Pool (Pool)
import Data.Pool qualified as Pool import Data.Pool qualified as Pool
import Database.PostgreSQL.Simple (Connection, connect, close, ConnectInfo) import Database.PostgreSQL.Simple (Connection, connect, close, ConnectInfo)
import Gargantext.API.Admin.EnvTypes import Gargantext.API.Admin.EnvTypes (Env(..))
import Gargantext.API.Errors.Types import Gargantext.API.Errors.Types (BackendInternalError)
import Gargantext.API.Prelude import Gargantext.API.Prelude (GargM)
import Gargantext.Core.Notifications.Dispatcher qualified as D import Gargantext.Core.Notifications.Dispatcher qualified as D
import Gargantext.Core.Config (GargConfig(..)) import Gargantext.Core.Config (GargConfig(..))
import Gargantext.Core.Config.Types (jwtSettings) import Gargantext.Core.Config.Types (jwtSettings)
import Gargantext.Core.NodeStory import Gargantext.Core.NodeStory (fromDBNodeStoryEnv)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.System.Logging import Gargantext.System.Logging (Logger)
import Network.HTTP.Client.TLS (newTlsManager) import Network.HTTP.Client.TLS (newTlsManager)
import System.Directory (renameFile) import System.Directory (renameFile)
import System.IO (hClose) import System.IO (hClose)
......
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.API.Admin.Settings.TOML where
import Control.Lens hiding ((.=))
import Data.Text qualified as T
import Gargantext.API.Admin.Settings.CORS
import Gargantext.API.Admin.Settings.MicroServices
import Gargantext.Core.Worker.TOML
import Gargantext.Prelude (panicTrace)
import Gargantext.System.Logging
import Prelude
import Toml
import Servant.Client.Core.BaseUrl
-- | Compatibility bridge until we fix #304 (move to Toml)
data GargTomlSettings = GargTomlSettings
{ _gargCorsSettings :: !CORSSettings
, _gargMicroServicesSettings :: !MicroServicesSettings
, _gargWorkerSettings :: !WorkerSettings
}
makeLenses ''GargTomlSettings
settingsCodec :: TomlCodec GargTomlSettings
settingsCodec = GargTomlSettings
<$> (Toml.table corsSettingsCodec "cors" .= _gargCorsSettings)
<*> (Toml.table microServicesSettingsCodec "microservices.proxy" .= _gargMicroServicesSettings)
<*> (Toml.table workerSettingsCodec "worker" .= _gargWorkerSettings)
-- | Extends the 'allowed-origins' in the CORSettings with the URLs embellished
-- with the proxy port.
addProxyToAllowedOrigins :: GargTomlSettings -> GargTomlSettings
addProxyToAllowedOrigins stgs =
stgs & over gargCorsSettings (addProxies $ stgs ^. gargMicroServicesSettings . msProxyPort)
where
addProxies :: Int -> CORSSettings -> CORSSettings
addProxies port cors =
let origins = _corsAllowedOrigins cors
mkUrl (CORSOrigin bh) = CORSOrigin $ bh { baseUrlPort = port }
in cors { _corsAllowedOrigins = origins <> Prelude.map mkUrl origins }
-- | Loads the 'CORSSettings' from the 'toml' file.
loadGargTomlSettings :: FilePath -> IO GargTomlSettings
loadGargTomlSettings tomlFile = do
tomlRes <- Toml.decodeFileEither settingsCodec tomlFile
case tomlRes of
Left errs -> do
withLogger () $ \ioLogger -> do
logMsg ioLogger ERROR $ T.unpack $ "Error, gargantext-settings.toml parsing failed: " <> Toml.prettyTomlDecodeErrors errs
panicTrace "Please fix the errors in your gargantext-settings.toml file."
Right settings0 -> case settings0 ^. gargCorsSettings . corsUseOriginsForHosts of
True -> pure $ addProxyToAllowedOrigins $
settings0 & over (gargCorsSettings . corsAllowedHosts)
(\_ -> (settings0 ^. gargCorsSettings . corsAllowedOrigins))
False -> pure $ addProxyToAllowedOrigins settings0
{-|
Module : Gargantext.API.Auth.PolicyCheck
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE LambdaCase #-} {-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeFamilies #-}
......
...@@ -16,19 +16,15 @@ Portability : POSIX ...@@ -16,19 +16,15 @@ Portability : POSIX
module Gargantext.API.Context module Gargantext.API.Context
where where
import Prelude
import Data.Aeson (FromJSON, ToJSON)
import Servant
import Gargantext.API.Admin.Auth (withNamedAccess) import Gargantext.API.Admin.Auth (withNamedAccess)
import Gargantext.API.Admin.Auth.Types (PathId(..), AuthenticatedUser) import Gargantext.API.Admin.Auth.Types (PathId(..), AuthenticatedUser)
import Gargantext.API.Prelude import Gargantext.API.Prelude (IsGargServer)
import Gargantext.Database.Admin.Types.Node import Gargantext.API.Routes.Named.Context qualified as Named
import Gargantext.Database.Admin.Types.Node (ContextId, contextId2NodeId)
import Gargantext.Database.Prelude (JSONB) import Gargantext.Database.Prelude (JSONB)
import Gargantext.Database.Query.Table.Context import Gargantext.Database.Query.Table.Context (getContextWith)
import Gargantext.Prelude
import Servant.Server.Generic (AsServerT) import Servant.Server.Generic (AsServerT)
import Gargantext.API.Routes.Named.Context qualified as Named
------------------------------------------------------------------- -------------------------------------------------------------------
-- TODO use Context instead of Node -- TODO use Context instead of Node
......
{-|
Module : Gargantext.API.Count.Types
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
module Gargantext.API.Count.Types ( module Gargantext.API.Count.Types (
Scraper(..) Scraper(..)
, QueryBool(..) , QueryBool(..)
......
{-|
Module : Gargantext.API.EKG
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# OPTIONS_GHC -fno-warn-orphans #-} {-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}
module Gargantext.API.EKG where module Gargantext.API.EKG where
import Data.HashMap.Strict as HM import Data.HashMap.Strict as HM
import Data.Text as T import Data.Text as T
import Data.Text.IO as T import Data.Text.IO as T
import Data.Time.Clock.POSIX (getPOSIXTime) import Data.Time.Clock.POSIX (getPOSIXTime)
import Network.Wai import Network.Wai (Middleware)
import Protolude import Protolude
import Servant import Servant
import Servant.Auth import Servant.Auth (Auth)
import Servant.Ekg import Servant.Ekg (HasEndpoint, getEndpoint, enumerateEndpoints, monitorEndpoints)
import System.Metrics import System.Metrics
import qualified System.Metrics.Json as J import System.Metrics.Json qualified as J
-- Mimics https://github.com/tibbe/ekg/blob/master/System/Remote/Snap.hs#L98 -- Mimics https://github.com/tibbe/ekg/blob/master/System/Remote/Snap.hs#L98
type EkgAPI = type EkgAPI =
......
...@@ -21,13 +21,13 @@ module Gargantext.API.Errors ( ...@@ -21,13 +21,13 @@ module Gargantext.API.Errors (
import Prelude import Prelude
import Control.Exception.Safe import Control.Exception.Safe (displayException)
import Data.Aeson qualified as JSON import Data.Aeson qualified as JSON
import Data.Text qualified as T import Data.Text qualified as T
import Data.Text.Lazy qualified as TL import Data.Text.Lazy qualified as TL
import Data.Text.Lazy.Encoding qualified as TE import Data.Text.Lazy.Encoding qualified as TE
import Data.Validity ( prettyValidation ) import Data.Validity ( prettyValidation )
import Gargantext.API.Admin.Auth.Types import Gargantext.API.Admin.Auth.Types (AuthenticationError(..))
import Gargantext.API.Errors.Class as Class import Gargantext.API.Errors.Class as Class
import Gargantext.API.Errors.TH (deriveHttpStatusCode) import Gargantext.API.Errors.TH (deriveHttpStatusCode)
import Gargantext.API.Errors.Types as Types import Gargantext.API.Errors.Types as Types
...@@ -35,7 +35,7 @@ import Gargantext.Database.Query.Table.Node.Error hiding (nodeError) ...@@ -35,7 +35,7 @@ import Gargantext.Database.Query.Table.Node.Error hiding (nodeError)
import Gargantext.Database.Query.Tree hiding (treeError) import Gargantext.Database.Query.Tree hiding (treeError)
import Gargantext.Utils.Jobs.Monad (JobError(..)) import Gargantext.Utils.Jobs.Monad (JobError(..))
import Network.HTTP.Types.Status qualified as HTTP import Network.HTTP.Types.Status qualified as HTTP
import Servant.Server import Servant.Server (ServerError(..), err404, err500)
$(deriveHttpStatusCode ''BackendErrorCode) $(deriveHttpStatusCode ''BackendErrorCode)
......
{-|
Module : Gargantext.API.Errors.Class
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
module Gargantext.API.Errors.Class where module Gargantext.API.Errors.Class where
import Control.Lens import Control.Lens (Prism')
import Gargantext.API.Admin.Auth.Types (AuthenticationError) import Gargantext.API.Admin.Auth.Types (AuthenticationError)
class HasAuthenticationError e where class HasAuthenticationError e where
_AuthenticationError :: Prism' e AuthenticationError _AuthenticationError :: Prism' e AuthenticationError
{-|
Module : Gargantext.API.Errors.TH
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE LambdaCase #-} {-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
......
...@@ -39,7 +39,7 @@ import Gargantext.API.GraphQL.TreeFirstLevel qualified as GQLTree ...@@ -39,7 +39,7 @@ import Gargantext.API.GraphQL.TreeFirstLevel qualified as GQLTree
import Gargantext.API.GraphQL.User qualified as GQLUser import Gargantext.API.GraphQL.User qualified as GQLUser
import Gargantext.API.GraphQL.UserInfo qualified as GQLUserInfo import Gargantext.API.GraphQL.UserInfo qualified as GQLUserInfo
import Gargantext.API.Prelude (GargM) import Gargantext.API.Prelude (GargM)
import Gargantext.API.Types import Gargantext.API.Types (HTML)
import Gargantext.Core.Config (HasJWTSettings) import Gargantext.Core.Config (HasJWTSettings)
import Gargantext.Core.NLP (HasNLPServer) import Gargantext.Core.NLP (HasNLPServer)
import Gargantext.Database.Prelude (CmdCommon) import Gargantext.Database.Prelude (CmdCommon)
...@@ -47,7 +47,7 @@ import Gargantext.Prelude hiding (ByteString) ...@@ -47,7 +47,7 @@ import Gargantext.Prelude hiding (ByteString)
import Servant import Servant
import Servant.Auth qualified as SA import Servant.Auth qualified as SA
import Servant.Auth.Server qualified as SAS import Servant.Auth.Server qualified as SAS
import Servant.Server.Generic import Servant.Server.Generic (AsServerT)
-- | Represents possible GraphQL queries. -- | Represents possible GraphQL queries.
......
{-|
Module : Gargantext.API.GraphQL.Annuaire
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE DuplicateRecordFields #-}
module Gargantext.API.GraphQL.Annuaire where module Gargantext.API.GraphQL.Annuaire where
import Control.Lens import Control.Lens (Traversal', _Just, ix)
import Data.Morpheus.Types ( GQLType ) import Data.Morpheus.Types ( GQLType )
import Data.Proxy
import Gargantext.Database.Admin.Types.Hyperdata.Contact import Gargantext.Database.Admin.Types.Hyperdata.Contact
( HyperdataContact ( HyperdataContact
, ContactWho , ContactWho
...@@ -17,7 +27,7 @@ import Gargantext.Database.Prelude (CmdCommon) ...@@ -17,7 +27,7 @@ import Gargantext.Database.Prelude (CmdCommon)
import Gargantext.Database.Query.Table.Context (getContextWith) import Gargantext.Database.Query.Table.Context (getContextWith)
import Gargantext.Database.Schema.Node (node_hyperdata) import Gargantext.Database.Schema.Node (node_hyperdata)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.API.GraphQL.Types import Gargantext.API.GraphQL.Types (GqlM)
data AnnuaireContact = AnnuaireContact data AnnuaireContact = AnnuaireContact
{ ac_title :: !(Maybe Text) { ac_title :: !(Maybe Text)
......
{-|
Module : Gargantext.API.GraphQL.IMT
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE DerivingStrategies #-}
......
{-|
Module : Gargantext.API.GraphQL.NLP
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE DerivingStrategies #-}
...@@ -11,13 +22,13 @@ module Gargantext.API.GraphQL.NLP ...@@ -11,13 +22,13 @@ module Gargantext.API.GraphQL.NLP
where where
import Control.Lens (view) import Control.Lens (view)
import Data.Map.Strict qualified as Map
import Data.Morpheus.Types (GQLType) import Data.Morpheus.Types (GQLType)
import Gargantext.API.GraphQL.Types import Gargantext.API.GraphQL.Types
import Gargantext.Core (Lang(..), NLPServerConfig(..), PosTagAlgo) -- , allLangs) import Gargantext.Core (Lang(..), NLPServerConfig(..), PosTagAlgo) -- , allLangs)
import Gargantext.Core.NLP (HasNLPServer(..)) import Gargantext.Core.NLP (HasNLPServer(..))
import Gargantext.Prelude import Gargantext.Prelude
import Protolude import Protolude qualified
import qualified Data.Map.Strict as Map
newtype LanguagesArgs newtype LanguagesArgs
= LanguagesArgs () = LanguagesArgs ()
......
{-|
Module : Gargantext.API.GraphQL.PolicyCheck
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
module Gargantext.API.GraphQL.PolicyCheck where module Gargantext.API.GraphQL.PolicyCheck where
......
...@@ -15,17 +15,17 @@ Portability : POSIX ...@@ -15,17 +15,17 @@ Portability : POSIX
module Gargantext.API.GraphQL.User where module Gargantext.API.GraphQL.User where
import Data.Morpheus.Types ( GQLType ) import Data.Morpheus.Types ( GQLType )
import Gargantext.API.Admin.Auth.Types import Gargantext.API.Admin.Auth.Types (AuthenticatedUser)
import Gargantext.API.Auth.PolicyCheck import Gargantext.API.Auth.PolicyCheck (AccessPolicyManager, nodeReadChecks)
import Gargantext.API.GraphQL.PolicyCheck import Gargantext.API.GraphQL.PolicyCheck (withPolicy)
import Gargantext.API.GraphQL.Types import Gargantext.API.GraphQL.Types (GqlM, GqlM')
import Gargantext.Core.Types (NodeId(..), UserId)
import Gargantext.Core.Types.Individu qualified as Individu import Gargantext.Core.Types.Individu qualified as Individu
import Gargantext.Database.Admin.Types.Hyperdata (HyperdataUser(..)) import Gargantext.Database.Admin.Types.Hyperdata (HyperdataUser(..))
import Gargantext.Database.Prelude (CmdCommon) import Gargantext.Database.Prelude (CmdCommon)
import Gargantext.Database.Query.Table.User qualified as DBUser import Gargantext.Database.Query.Table.User qualified as DBUser
import Gargantext.Database.Schema.User (UserLight(..)) import Gargantext.Database.Schema.User (UserLight(..))
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Core.Types
data User m = User data User m = User
{ u_email :: Text { u_email :: Text
......
...@@ -40,12 +40,14 @@ import Gargantext.Database.Admin.Types.Hyperdata.Contact ...@@ -40,12 +40,14 @@ import Gargantext.Database.Admin.Types.Hyperdata.Contact
, ct_phone , ct_phone
, hc_who , hc_who
, hc_where) , hc_where)
import Gargantext.API.Admin.Auth.Types hiding (Valid)
import Gargantext.API.Auth.PolicyCheck import Gargantext.API.Admin.Auth.Types (AuthenticatedUser)
import Gargantext.API.GraphQL.PolicyCheck import Gargantext.API.Auth.PolicyCheck (AccessPolicyManager, userMe)
import Gargantext.API.GraphQL.Types import Gargantext.API.GraphQL.PolicyCheck (withPolicy)
import Gargantext.API.GraphQL.Types (GqlM, GqlM')
import Gargantext.API.GraphQL.Utils (AuthStatus(Invalid, Valid), authUser) import Gargantext.API.GraphQL.Utils (AuthStatus(Invalid, Valid), authUser)
import Gargantext.Core.Config (HasJWTSettings) import Gargantext.Core.Config (HasJWTSettings)
import Gargantext.Core.Types (UserId(..))
import Gargantext.Core.Types.Individu qualified as Individu import Gargantext.Core.Types.Individu qualified as Individu
import Gargantext.Database.Prelude (CmdCommon) import Gargantext.Database.Prelude (CmdCommon)
import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata) import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata)
...@@ -53,7 +55,6 @@ import Gargantext.Database.Query.Table.User (getUsersWithHyperdata, getUsersWith ...@@ -53,7 +55,6 @@ import Gargantext.Database.Query.Table.User (getUsersWithHyperdata, getUsersWith
import Gargantext.Database.Schema.Node (node_id, node_hyperdata, NodePoly (Node, _node_id)) import Gargantext.Database.Schema.Node (node_id, node_hyperdata, NodePoly (Node, _node_id))
import Gargantext.Database.Schema.User (UserLight(..)) import Gargantext.Database.Schema.User (UserLight(..))
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Core.Types
data UserInfo = UserInfo data UserInfo = UserInfo
{ ui_id :: Int { ui_id :: Int
......
...@@ -12,7 +12,7 @@ Portability : POSIX ...@@ -12,7 +12,7 @@ Portability : POSIX
module Gargantext.API.HashedResponse where module Gargantext.API.HashedResponse where
import Data.Aeson import Data.Aeson
import Data.Swagger import Data.Swagger (ToSchema)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Prelude.Crypto.Hash qualified as Crypto (hash) import Gargantext.Prelude.Crypto.Hash qualified as Crypto (hash)
......
...@@ -26,7 +26,7 @@ import Control.Lens (over, _Just) ...@@ -26,7 +26,7 @@ import Control.Lens (over, _Just)
import Data.Text qualified as T import Data.Text qualified as T
import Gargantext.API.Admin.Orchestrator.Types import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Utils.Jobs.Error import Gargantext.Utils.Jobs.Error (ToHumanFriendlyError, mkHumanFriendly)
newtype RemainingSteps = RemainingSteps { _RemainingSteps :: Int } newtype RemainingSteps = RemainingSteps { _RemainingSteps :: Int }
deriving (Show, Eq, Num) deriving (Show, Eq, Num)
......
...@@ -10,7 +10,7 @@ Portability : POSIX ...@@ -10,7 +10,7 @@ Portability : POSIX
module Gargantext.API.Members where module Gargantext.API.Members where
import Gargantext.API.Prelude import Gargantext.API.Prelude (IsGargServer)
import Gargantext.API.Routes.Named.Private qualified as Named import Gargantext.API.Routes.Named.Private qualified as Named
import Gargantext.Database.Action.Share (membersOf) import Gargantext.Database.Action.Share (membersOf)
import Gargantext.Database.Admin.Types.Node (NodeType(NodeTeam)) import Gargantext.Database.Admin.Types.Node (NodeType(NodeTeam))
......
...@@ -16,21 +16,20 @@ Metrics API ...@@ -16,21 +16,20 @@ Metrics API
module Gargantext.API.Metrics module Gargantext.API.Metrics
where where
import Control.Lens
import Data.HashMap.Strict qualified as HashMap import Data.HashMap.Strict qualified as HashMap
import Data.Time (UTCTime) import Data.Time (UTCTime)
import Data.Vector (Vector) import Data.Vector (Vector)
import Gargantext.API.HashedResponse import Gargantext.API.HashedResponse (HashedResponse, constructHashedResponse, hash)
import Gargantext.API.Ngrams.NgramsTree import Gargantext.API.Ngrams.NgramsTree (NgramsTree)
import Gargantext.API.Ngrams.Types import Gargantext.API.Ngrams.Types (QueryParamR, TabType, ngramsTypeFromTabType, unNgramsTerm)
import Gargantext.API.Prelude (IsGargServer) import Gargantext.API.Prelude (IsGargServer)
import Gargantext.API.Routes.Named.Metrics qualified as Named import Gargantext.API.Routes.Named.Metrics qualified as Named
import Gargantext.Core.NodeStory (HasNodeStory) import Gargantext.Core.NodeStory (HasNodeStory)
import Gargantext.Core.Text.Metrics (Scored(..), {-normalizeGlobal,-} normalizeLocal) import Gargantext.Core.Text.Metrics (Scored(..), {-normalizeGlobal,-} normalizeLocal)
import Gargantext.Core.Types (CorpusId, ListId, ListType(..)) import Gargantext.Core.Types (CorpusId, ListId, ListType(..))
import Gargantext.Core.Types.Query (Limit) import Gargantext.Core.Types.Query (Limit)
import Gargantext.Core.Viz.Chart import Gargantext.Core.Viz.Chart (chartData, histoData, treeData)
import Gargantext.Core.Viz.Types import Gargantext.Core.Viz.Types (Histo)
import Gargantext.Database.Action.Metrics qualified as Metrics import Gargantext.Database.Action.Metrics qualified as Metrics
import Gargantext.Database.Admin.Types.Hyperdata (HyperdataList(..), hl_chart, hl_pie, hl_scatter, hl_tree) import Gargantext.Database.Admin.Types.Hyperdata (HyperdataList(..), hl_chart, hl_pie, hl_scatter, hl_tree)
import Gargantext.Database.Admin.Types.Metrics (ChartMetrics(..), Metric(..), Metrics(..)) import Gargantext.Database.Admin.Types.Metrics (ChartMetrics(..), Metric(..), Metrics(..))
......
{-|
Module : Gargantext.API.Middleware
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE ViewPatterns #-} {-# LANGUAGE ViewPatterns #-}
{-| Edit 'sensitiveKeywords' to extend the list of redacted fields. -} {-| Edit 'sensitiveKeywords' to extend the list of redacted fields. -}
...@@ -5,8 +17,8 @@ module Gargantext.API.Middleware ( ...@@ -5,8 +17,8 @@ module Gargantext.API.Middleware (
logStdoutDevSanitised logStdoutDevSanitised
) where ) where
import Control.Lens import Control.Lens (Traversal', at, over)
import Control.Monad.Logger import Control.Monad.Logger (LogStr, toLogStr)
import Data.Aeson qualified as A import Data.Aeson qualified as A
import Data.Aeson.Lens qualified as L import Data.Aeson.Lens qualified as L
import Data.ByteString (ByteString) import Data.ByteString (ByteString)
...@@ -16,15 +28,15 @@ import Data.ByteString.Char8 qualified as C8 ...@@ -16,15 +28,15 @@ import Data.ByteString.Char8 qualified as C8
import Data.ByteString.Lazy qualified as B import Data.ByteString.Lazy qualified as B
import Data.CaseInsensitive qualified as CI import Data.CaseInsensitive qualified as CI
import Data.List qualified as L import Data.List qualified as L
import Data.String import Data.String (fromString)
import Data.Text qualified as T import Data.Text qualified as T
import Data.Text.Encoding qualified as TE import Data.Text.Encoding qualified as TE
import Network.HTTP.Types import Network.HTTP.Types (QueryItem, Status(..))
import Network.HTTP.Types.Header import Network.HTTP.Types.Header (Header, hAuthorization, hCookie, hSetCookie)
import Network.Wai import Network.Wai (Middleware, queryString, requestMethod, rawPathInfo)
import Network.Wai.Middleware.RequestLogger import Network.Wai.Middleware.RequestLogger
import Prelude import Prelude
import System.Console.ANSI import System.Console.ANSI (Color(..), setSGRCode, SGR(..), ConsoleLayer(..), ColorIntensity(..))
-- | Like 'logStdoutDev' from \"wai-extra\", but redacts (or omits altogether) payloads which might have -- | Like 'logStdoutDev' from \"wai-extra\", but redacts (or omits altogether) payloads which might have
-- sensitive information -- sensitive information
......
...@@ -29,7 +29,7 @@ import Data.Vector qualified as Vec ...@@ -29,7 +29,7 @@ import Data.Vector qualified as Vec
import Gargantext.API.Admin.EnvTypes (Env) import Gargantext.API.Admin.EnvTypes (Env)
import Gargantext.API.Errors.Types (BackendInternalError(InternalServerError)) import Gargantext.API.Errors.Types (BackendInternalError(InternalServerError))
import Gargantext.API.Ngrams (setListNgrams) import Gargantext.API.Ngrams (setListNgrams)
import Gargantext.API.Ngrams.List.Types import Gargantext.API.Ngrams.List.Types (_wjf_data, _wtf_data)
import Gargantext.API.Ngrams.Prelude (getNgramsList) import Gargantext.API.Ngrams.Prelude (getNgramsList)
import Gargantext.API.Ngrams.Types import Gargantext.API.Ngrams.Types
import Gargantext.API.Prelude (GargM, serverError, HasServerError) import Gargantext.API.Prelude (GargM, serverError, HasServerError)
......
...@@ -13,20 +13,17 @@ Portability : POSIX ...@@ -13,20 +13,17 @@ Portability : POSIX
module Gargantext.API.Ngrams.List.Types where module Gargantext.API.Ngrams.List.Types where
--import Control.Lens hiding (elements, Indexed)
import Data.Aeson import Data.Aeson
import qualified Data.ByteString.Lazy as BSL import Data.ByteString.Lazy qualified as BSL
import Data.Swagger (ToSchema, declareNamedSchema, genericDeclareNamedSchema) import Data.Swagger (ToSchema, declareNamedSchema, genericDeclareNamedSchema)
import Data.Text import Data.Text
import qualified Data.Text.Encoding as E import Data.Text.Encoding qualified as E
import Servant.Job.Utils (jsonOptions)
import Web.FormUrlEncoded (FromForm(..), ToForm, parseUnique)
import Protolude
import Gargantext.API.Ngrams.Types (NgramsList) import Gargantext.API.Ngrams.Types (NgramsList)
import Gargantext.API.Node.Corpus.New.Types (FileType(..)) import Gargantext.API.Node.Corpus.New.Types (FileType(..))
import Gargantext.Core.Utils.Prefix (unPrefixSwagger) import Gargantext.Core.Utils.Prefix (unPrefixSwagger)
import Protolude
import Servant.Job.Utils (jsonOptions)
import Web.FormUrlEncoded (FromForm(..), ToForm, parseUnique)
......
...@@ -20,20 +20,19 @@ module Gargantext.API.Prelude ...@@ -20,20 +20,19 @@ module Gargantext.API.Prelude
where where
import Control.Lens ((#)) import Control.Lens ((#))
import Data.Aeson.Types
import Gargantext.API.Admin.Auth.Types (AuthenticationError) import Gargantext.API.Admin.Auth.Types (AuthenticationError)
import Gargantext.API.Errors.Class import Gargantext.API.Errors.Class (HasAuthenticationError, _AuthenticationError)
import Gargantext.Core.Notifications.CentralExchange.Types (HasCentralExchangeNotification) import Gargantext.Core.Notifications.CentralExchange.Types (HasCentralExchangeNotification)
import Gargantext.Core.Config (HasConfig) import Gargantext.Core.Config (HasConfig)
import Gargantext.Core.Mail.Types (HasMail) import Gargantext.Core.Mail.Types (HasMail)
import Gargantext.Core.NLP (HasNLPServer) import Gargantext.Core.NLP (HasNLPServer)
import Gargantext.Core.NodeStory import Gargantext.Core.NodeStory (HasNodeStory, HasNodeStoryEnv)
import Gargantext.Core.Types import Gargantext.Core.Types (HasValidationError)
import Gargantext.Database.Prelude (CmdM, CmdRandom, HasConnectionPool) import Gargantext.Database.Prelude (CmdM, CmdRandom, HasConnectionPool)
import Gargantext.Database.Query.Table.Node.Error (HasNodeError(..)) import Gargantext.Database.Query.Table.Node.Error (HasNodeError(..))
import Gargantext.Database.Query.Tree import Gargantext.Database.Query.Tree (HasTreeError)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.System.Logging import Gargantext.System.Logging (MonadLogger)
import Gargantext.Utils.Jobs.Monad (MonadJobStatus(..), JobHandle) import Gargantext.Utils.Jobs.Monad (MonadJobStatus(..), JobHandle)
import Servant import Servant
import Servant.Job.Core (HasServerError(..), serverError) import Servant.Job.Core (HasServerError(..), serverError)
......
{-|
Module : Gargantext.API.Public.Types
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
module Gargantext.API.Public.Types ( module Gargantext.API.Public.Types (
PublicData(..) PublicData(..)
, defaultPublicData
) where ) where
import Data.Aeson import Data.Aeson
import Data.Swagger import Data.Swagger (ToSchema)
import Data.Text (Text) import Data.Text (Text)
import GHC.Generics import GHC.Generics (Generic)
import Gargantext.Utils.Aeson qualified as GUA import Gargantext.Utils.Aeson qualified as GUA
import Prelude
import Test.QuickCheck
data PublicData = PublicData data PublicData = PublicData
{ title :: Text { title :: Text
...@@ -31,16 +38,3 @@ instance ToJSON PublicData where ...@@ -31,16 +38,3 @@ instance ToJSON PublicData where
toJSON = genericToJSON (defaultOptions { sumEncoding = GUA.defaultTaggedObject }) toJSON = genericToJSON (defaultOptions { sumEncoding = GUA.defaultTaggedObject })
instance ToSchema PublicData instance ToSchema PublicData
instance Arbitrary PublicData where
arbitrary = elements
$ replicate 6 defaultPublicData
defaultPublicData :: PublicData
defaultPublicData =
PublicData { title = "Title"
, abstract = foldl (<>) "" $ replicate 100 "abstract "
, img = "images/Gargantextuel-212x300.jpg"
, url = "https://.."
, date = "YY/MM/DD"
, database = "database"
, author = "Author" }
...@@ -17,18 +17,16 @@ Portability : POSIX ...@@ -17,18 +17,16 @@ Portability : POSIX
module Gargantext.API.Routes module Gargantext.API.Routes
where where
import Data.Validity
import Gargantext.API.Admin.EnvTypes (Env) import Gargantext.API.Admin.EnvTypes (Env)
import Gargantext.API.Errors.Types import Gargantext.API.Errors.Types (BackendInternalError)
import Gargantext.API.Prelude import Gargantext.API.Prelude (GargServer, GargM)
import Gargantext.API.Routes.Named.Annuaire qualified as Named import Gargantext.API.Routes.Named.Annuaire qualified as Named
import Gargantext.API.Routes.Named.Corpus qualified as Named import Gargantext.API.Routes.Named.Corpus qualified as Named
import Gargantext.API.Worker (serveWorkerAPI) import Gargantext.API.Worker (serveWorkerAPI)
import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Core.Worker.Jobs.Types qualified as Jobs import Gargantext.Core.Worker.Jobs.Types qualified as Jobs
import Gargantext.Prelude import Gargantext.Prelude
import Servant import Servant (Get, JSON)
import Servant.Auth.Swagger ()
import Servant.Server.Generic (AsServerT) import Servant.Server.Generic (AsServerT)
---------------------------------------------------------------------- ----------------------------------------------------------------------
......
...@@ -18,20 +18,20 @@ module Gargantext.API.Routes.Named ( ...@@ -18,20 +18,20 @@ module Gargantext.API.Routes.Named (
) where ) where
import Data.Text (Text) import Data.Text (Text)
import GHC.Generics import GHC.Generics (Generic)
import Gargantext.API.Admin.Auth.Types import Gargantext.API.Admin.Auth.Types
import Gargantext.API.Admin.FrontEnd (FrontEndAPI) import Gargantext.API.Admin.FrontEnd (FrontEndAPI)
import Gargantext.API.GraphQL import Gargantext.API.GraphQL (GraphQLAPI)
import Gargantext.API.Routes.Named.Private import Gargantext.API.Routes.Named.Private (GargPrivateAPI)
import Gargantext.API.Routes.Named.Public import Gargantext.API.Routes.Named.Public (GargPublicAPI)
import Gargantext.API.Routes.Types import Gargantext.API.Routes.Types (WithCustomErrorScheme)
import Gargantext.API.Worker (WorkerAPI) import Gargantext.API.Worker (WorkerAPI)
import Gargantext.Core.Notifications.Dispatcher.WebSocket qualified as Dispatcher import Gargantext.Core.Notifications.Dispatcher.WebSocket qualified as Dispatcher
import Servant.API ((:>), (:-), JSON, ReqBody, Post, Get, QueryParam) import Servant.API ((:>), (:-), JSON, ReqBody, Post, Get, QueryParam)
import Servant.API.Description (Summary) import Servant.API.Description (Summary)
import Servant.API.NamedRoutes import Servant.API.NamedRoutes (NamedRoutes)
import Servant.Auth.Swagger () import Servant.Auth.Swagger () -- toSwagger instance
import Servant.Swagger.UI import Servant.Swagger.UI (SwaggerSchemaUI)
newtype API mode = API newtype API mode = API
......
...@@ -28,24 +28,24 @@ module Gargantext.API.Routes.Named.Node ( ...@@ -28,24 +28,24 @@ module Gargantext.API.Routes.Named.Node (
, UpdateNodeParams(..) , UpdateNodeParams(..)
) where ) where
import GHC.Generics import GHC.Generics (Generic)
import Gargantext.API.Auth.PolicyCheck ( PolicyChecked ) import Gargantext.API.Auth.PolicyCheck ( PolicyChecked )
import Gargantext.API.Ngrams.Types (TabType(..)) import Gargantext.API.Ngrams.Types (TabType(..))
import Gargantext.API.Node.New.Types ( PostNode(..) ) import Gargantext.API.Node.New.Types ( PostNode(..) )
import Gargantext.API.Node.Types ( RenameNode(..), NodesToScore(..), NodesToCategory(..) ) import Gargantext.API.Node.Types ( RenameNode(..), NodesToScore(..), NodesToCategory(..) )
import Gargantext.API.Node.Update.Types ( UpdateNodeParams(..), Charts(..), Granularity(..), Method(..) ) import Gargantext.API.Node.Update.Types ( UpdateNodeParams(..), Charts(..), Granularity(..), Method(..) )
import Gargantext.API.Routes.Named.Document import Gargantext.API.Routes.Named.Document (DocumentsFromWriteNodesAPI, DocumentUploadAPI)
import Gargantext.API.Routes.Named.File import Gargantext.API.Routes.Named.File (FileAsyncAPI, FileAPI)
import Gargantext.API.Routes.Named.FrameCalc import Gargantext.API.Routes.Named.FrameCalc (FrameCalcAPI)
import Gargantext.API.Routes.Named.Metrics import Gargantext.API.Routes.Named.Metrics (ChartAPI, PieAPI, ScatterAPI, TreeAPI)
import Gargantext.API.Routes.Named.Publish (PublishAPI) import Gargantext.API.Routes.Named.Publish (PublishAPI)
import Gargantext.API.Routes.Named.Search import Gargantext.API.Routes.Named.Search (SearchAPI, SearchResult)
import Gargantext.API.Routes.Named.Share as Share import Gargantext.API.Routes.Named.Share (ShareNode, UnshareNode)
import Gargantext.API.Routes.Named.Table import Gargantext.API.Routes.Named.Table (TableAPI, TableNgramsAPI)
import Gargantext.API.Routes.Named.Viz import Gargantext.API.Routes.Named.Viz (PhyloAPI)
import Gargantext.API.Worker (WorkerAPI) import Gargantext.API.Worker (WorkerAPI)
import Gargantext.Core.Types import Gargantext.Core.Types
import Gargantext.Core.Types.Query import Gargantext.Core.Types.Query (Limit, Offset)
import Gargantext.Database.Admin.Types.Hyperdata.User ( HyperdataUser ) import Gargantext.Database.Admin.Types.Hyperdata.User ( HyperdataUser )
import Gargantext.Database.Query.Facet.Types ( FacetDoc, OrderBy(..) ) import Gargantext.Database.Query.Facet.Types ( FacetDoc, OrderBy(..) )
import Prelude import Prelude
...@@ -82,7 +82,7 @@ data NodeAPI a mode = NodeAPI ...@@ -82,7 +82,7 @@ data NodeAPI a mode = NodeAPI
, scoreAPI :: mode :- "score" :> NamedRoutes ScoreAPI , scoreAPI :: mode :- "score" :> NamedRoutes ScoreAPI
, searchAPI :: mode :- "search" :> NamedRoutes (SearchAPI SearchResult) , searchAPI :: mode :- "search" :> NamedRoutes (SearchAPI SearchResult)
, shareAPI :: mode :- "share" :> NamedRoutes ShareNode , shareAPI :: mode :- "share" :> NamedRoutes ShareNode
, unshareEp :: mode :- "unshare" :> NamedRoutes Share.UnshareNode , unshareEp :: mode :- "unshare" :> NamedRoutes UnshareNode
, publishAPI :: mode :- "publish" :> (PolicyChecked (NamedRoutes PublishAPI)) , publishAPI :: mode :- "publish" :> (PolicyChecked (NamedRoutes PublishAPI))
---- Pairing utilities ---- Pairing utilities
, pairWithEp :: mode :- "pairwith" :> NamedRoutes PairWith , pairWithEp :: mode :- "pairwith" :> NamedRoutes PairWith
......
...@@ -26,23 +26,23 @@ module Gargantext.API.Routes.Named.Private ( ...@@ -26,23 +26,23 @@ module Gargantext.API.Routes.Named.Private (
import Data.Text (Text) import Data.Text (Text)
import GHC.Generics import GHC.Generics (Generic)
import Gargantext.API.Admin.Auth.Types import Gargantext.API.Admin.Auth.Types (AuthenticatedUser)
import Gargantext.API.Auth.PolicyCheck import Gargantext.API.Auth.PolicyCheck (PolicyChecked)
import Gargantext.API.Routes.Named.Contact import Gargantext.API.Routes.Named.Contact (ContactAPI)
import Gargantext.API.Routes.Named.Context import Gargantext.API.Routes.Named.Context (ContextAPI)
import Gargantext.API.Routes.Named.Corpus import Gargantext.API.Routes.Named.Corpus (AddWithForm, AddWithQuery, CorpusExportAPI, MakeSubcorpusAPI)
import Gargantext.API.Routes.Named.Count import Gargantext.API.Routes.Named.Count (CountAPI, Query)
import Gargantext.API.Routes.Named.Document import Gargantext.API.Routes.Named.Document (DocumentExportAPI)
import Gargantext.API.Routes.Named.List qualified as List import Gargantext.API.Routes.Named.List (GETAPI, JSONAPI, TSVAPI)
import Gargantext.API.Routes.Named.Node import Gargantext.API.Routes.Named.Node (NodeAPI, NodesAPI, NodeNodeAPI, Roots)
import Gargantext.API.Routes.Named.Share import Gargantext.API.Routes.Named.Share (ShareURL)
import Gargantext.API.Routes.Named.Table import Gargantext.API.Routes.Named.Table (TableNgramsAPI)
import Gargantext.API.Routes.Named.Tree import Gargantext.API.Routes.Named.Tree (NodeTreeAPI, TreeFlatAPI)
import Gargantext.API.Routes.Named.Viz import Gargantext.API.Routes.Named.Viz (GraphAPI, PhyloExportAPI)
import Gargantext.Database.Admin.Types.Hyperdata.Any import Gargantext.Database.Admin.Types.Hyperdata.Any (HyperdataAny)
import Gargantext.Database.Admin.Types.Hyperdata.Corpus import Gargantext.Database.Admin.Types.Hyperdata.Corpus (HyperdataAnnuaire, HyperdataCorpus)
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node (ContextId, CorpusId, DocId, NodeId)
import Servant.API import Servant.API
import Servant.Auth qualified as SA import Servant.Auth qualified as SA
...@@ -97,9 +97,9 @@ data GargPrivateAPI' mode = GargPrivateAPI' ...@@ -97,9 +97,9 @@ data GargPrivateAPI' mode = GargPrivateAPI'
, addWithFormAPI :: mode :- NamedRoutes AddWithForm , addWithFormAPI :: mode :- NamedRoutes AddWithForm
, addWithQueryEp :: mode :- NamedRoutes AddWithQuery , addWithQueryEp :: mode :- NamedRoutes AddWithQuery
, makeSubcorpusAPI :: mode :- NamedRoutes MakeSubcorpusAPI , makeSubcorpusAPI :: mode :- NamedRoutes MakeSubcorpusAPI
, listGetAPI :: mode :- NamedRoutes List.GETAPI , listGetAPI :: mode :- NamedRoutes GETAPI
, listJsonAPI :: mode :- NamedRoutes List.JSONAPI , listJsonAPI :: mode :- NamedRoutes JSONAPI
, listTsvAPI :: mode :- NamedRoutes List.TSVAPI , listTsvAPI :: mode :- NamedRoutes TSVAPI
, shareUrlAPI :: mode :- "shareurl" :> NamedRoutes ShareURL , shareUrlAPI :: mode :- "shareurl" :> NamedRoutes ShareURL
} deriving Generic } deriving Generic
......
{-|
Module : Gargantext.API.Routes.Named.Publish
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
module Gargantext.API.Routes.Named.Publish ( module Gargantext.API.Routes.Named.Publish (
...@@ -6,12 +16,11 @@ module Gargantext.API.Routes.Named.Publish ( ...@@ -6,12 +16,11 @@ module Gargantext.API.Routes.Named.Publish (
) where ) where
import Data.Aeson as JS import Data.Aeson as JS
import Data.Swagger import Data.Swagger (ToSchema)
import Gargantext.Database.Query.Table.NodeNode (NodePublishPolicy) import Gargantext.Database.Query.Table.NodeNode (NodePublishPolicy)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Prelude import Prelude
import Servant import Servant
import Test.QuickCheck
newtype PublishRequest = PublishRequest newtype PublishRequest = PublishRequest
{ pubrq_policy :: NodePublishPolicy { pubrq_policy :: NodePublishPolicy
...@@ -28,9 +37,6 @@ instance FromJSON PublishRequest where ...@@ -28,9 +37,6 @@ instance FromJSON PublishRequest where
pubrq_policy <- o JS..: "policy" pubrq_policy <- o JS..: "policy"
pure $ PublishRequest{..} pure $ PublishRequest{..}
instance Arbitrary PublishRequest where
arbitrary = PublishRequest <$> arbitraryBoundedEnum
newtype PublishAPI mode = PublishAPI newtype PublishAPI mode = PublishAPI
{ publishEp :: mode :- Summary "Publish a Corpus Node" { publishEp :: mode :- Summary "Publish a Corpus Node"
:> ReqBody '[JSON] PublishRequest :> ReqBody '[JSON] PublishRequest
......
...@@ -12,10 +12,10 @@ module Gargantext.API.Routes.Named.Search ( ...@@ -12,10 +12,10 @@ module Gargantext.API.Routes.Named.Search (
) where ) where
import GHC.Generics import GHC.Generics (Generic)
import Gargantext.API.Search.Types ( SearchQuery(..), SearchType(..), SearchResult(..), SearchResultTypes(..) ) import Gargantext.API.Search.Types ( SearchQuery(..), SearchType(..), SearchResult(..), SearchResultTypes(..) )
import Gargantext.Core.Types.Query (Limit, Offset) import Gargantext.Core.Types.Query (Limit, Offset)
import Gargantext.Database.Query.Facet import Gargantext.Database.Query.Facet (OrderBy)
import Servant import Servant
......
...@@ -13,12 +13,12 @@ module Gargantext.API.Routes.Named.Share ( ...@@ -13,12 +13,12 @@ module Gargantext.API.Routes.Named.Share (
, ShareNodeParams(..) , ShareNodeParams(..)
) where ) where
import Data.Aeson import Data.Aeson (FromJSON(..), ToJSON(..), withText)
import Data.Swagger import Data.Swagger (ToSchema, declareNamedSchema)
import Data.Text qualified as T import Data.Text qualified as T
import GHC.Generics import GHC.Generics (Generic)
import Gargantext.API.Node.Share.Types ( ShareNodeParams (..) ) import Gargantext.API.Node.Share.Types ( ShareNodeParams (..) )
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node (NodeId, NodeType)
import Network.URI (parseURI) import Network.URI (parseURI)
import Prelude import Prelude
import Servant import Servant
......
...@@ -17,15 +17,15 @@ module Gargantext.API.Routes.Named.Table ( ...@@ -17,15 +17,15 @@ module Gargantext.API.Routes.Named.Table (
) where ) where
import Data.Text (Text) import Data.Text (Text)
import GHC.Generics import GHC.Generics (Generic)
import Gargantext.API.HashedResponse import Gargantext.API.HashedResponse (HashedResponse)
import Gargantext.API.Ngrams.Types (TabType(..), UpdateTableNgramsCharts, Version, QueryParamR, Versioned, VersionedWithCount, NgramsTable, NgramsTablePatch) import Gargantext.API.Ngrams.Types (TabType(..), UpdateTableNgramsCharts, Version, QueryParamR, Versioned, VersionedWithCount, NgramsTable, NgramsTablePatch)
import Gargantext.API.Ngrams.Types qualified as Ngrams import Gargantext.API.Ngrams.Types qualified as Ngrams
import Gargantext.API.Worker (WorkerAPI) import Gargantext.API.Worker (WorkerAPI)
import Gargantext.API.Table.Types ( TableQuery(..), FacetTableResult ) import Gargantext.API.Table.Types ( TableQuery(..), FacetTableResult )
import Gargantext.Core.Text.Corpus.Query (RawQuery) import Gargantext.Core.Text.Corpus.Query (RawQuery)
import Gargantext.Core.Types.Main (ListType) import Gargantext.Core.Types.Main (ListType)
import Gargantext.Core.Types.Query import Gargantext.Core.Types.Query (Limit, MinSize, MaxSize, Offset)
import Gargantext.Database.Admin.Types.Node (ListId) import Gargantext.Database.Admin.Types.Node (ListId)
import Gargantext.Database.Query.Facet.Types qualified as Facet import Gargantext.Database.Query.Facet.Types qualified as Facet
import Prelude import Prelude
......
...@@ -7,9 +7,9 @@ module Gargantext.API.Routes.Named.Tree ( ...@@ -7,9 +7,9 @@ module Gargantext.API.Routes.Named.Tree (
) where ) where
import Data.Text (Text) import Data.Text (Text)
import GHC.Generics import GHC.Generics (Generic)
import Gargantext.Core.Types.Main import Gargantext.Core.Types.Main
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node (NodeType)
import Servant import Servant
data NodeTreeAPI mode = NodeTreeAPI data NodeTreeAPI mode = NodeTreeAPI
......
...@@ -18,11 +18,11 @@ module Gargantext.API.Routes.Named.Viz ( ...@@ -18,11 +18,11 @@ module Gargantext.API.Routes.Named.Viz (
import Data.Aeson ( Value ) import Data.Aeson ( Value )
import Data.Text (Text) import Data.Text (Text)
import GHC.Generics import GHC.Generics (Generic)
import Gargantext.API.Viz.Types (PhyloData(..)) import Gargantext.API.Viz.Types (PhyloData(..))
import Gargantext.API.Worker (WorkerAPI) import Gargantext.API.Worker (WorkerAPI)
import Gargantext.Core.Types import Gargantext.Core.Types (ListId, NodeId)
import Gargantext.Core.Viz.Graph.Types import Gargantext.Core.Viz.Graph.Types (Graph, GraphLegendAPI, GraphVersions(..), HyperdataGraphAPI)
import Gargantext.Core.Viz.LegacyPhylo (Level) import Gargantext.Core.Viz.LegacyPhylo (Level)
import Gargantext.Core.Viz.Phylo.Legacy.LegacyMain (MinSizeBranch) import Gargantext.Core.Viz.Phylo.Legacy.LegacyMain (MinSizeBranch)
import Servant import Servant
......
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeApplications #-}
module Gargantext.API.Routes.Types where module Gargantext.API.Routes.Types where
import Control.Lens import Control.Lens ((&), (%~), traversed)
import Data.ByteString (ByteString) import Data.ByteString (ByteString)
import Data.CaseInsensitive qualified as CI import Data.CaseInsensitive qualified as CI
import Data.List qualified as L import Data.List qualified as L
import Data.Proxy import Data.Proxy (Proxy(..))
import Data.Set qualified as Set import Data.Set qualified as Set
import Gargantext.API.Errors import Gargantext.API.Errors (GargErrorScheme(..), renderGargErrorScheme)
import Network.Wai hiding (responseHeaders) import Network.HTTP.Types (HeaderName)
import Network.Wai (requestHeaders)
import Prelude import Prelude
import Servant.API.Routes import Servant.API.Routes (HasRoutes, getRoutes, mkHeaderRep, responseHeaders)
import Servant.API.Routes.Internal.Response (unResponses) import Servant.API.Routes.Internal.Response (unResponses)
import Servant.API.Routes.Route import Servant.API.Routes.Route (routeResponse)
import Servant.Client hiding (responseHeaders) import Servant.Client (HasClient, Client, clientWithRoute, hoistClientMonad)
import Servant.Client.Core.Request (addHeader) import Servant.Client.Core.Request (addHeader)
import Servant.Ekg import Servant.Ekg (HasEndpoint, enumerateEndpoints, getEndpoint)
import Servant.Server import Servant.Server (HasServer, ServerT, hoistServerWithContext, route)
import Servant.Server.Internal.Delayed import Servant.Server.Internal.Delayed (addHeaderCheck)
import Servant.Server.Internal.DelayedIO import Servant.Server.Internal.DelayedIO (DelayedIO, withRequest)
import Network.HTTP.Types (HeaderName)
data WithCustomErrorScheme a data WithCustomErrorScheme a
......
...@@ -22,14 +22,14 @@ module Gargantext.API.Search ...@@ -22,14 +22,14 @@ module Gargantext.API.Search
import Data.Text qualified as T import Data.Text qualified as T
import Gargantext.API.Prelude (IsGargServer) import Gargantext.API.Prelude (IsGargServer)
import Gargantext.API.Routes.Named.Search qualified as Named import Gargantext.API.Routes.Named.Search qualified as Named
import Gargantext.API.Search.Types import Gargantext.API.Search.Types (SearchQuery(..), SearchResult(..), SearchResultTypes(..), SearchType(..))
import Gargantext.Core.Text.Corpus.Query (RawQuery (..), parseQuery) import Gargantext.Core.Text.Corpus.Query (RawQuery (..), parseQuery)
import Gargantext.Core.Types.Search import Gargantext.Core.Types.Search (toRow)
import Gargantext.Database.Action.Flow.Pairing (isPairedWith) import Gargantext.Database.Action.Flow.Pairing (isPairedWith)
import Gargantext.Database.Action.Search import Gargantext.Database.Action.Search (searchInCorpus, searchInCorpusWithContacts)
import Gargantext.Database.Admin.Types.Node hiding (DEBUG) import Gargantext.Database.Admin.Types.Node (NodeId, NodeType(..))
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.System.Logging import Gargantext.System.Logging (logLocM, LogLevel(..))
import Servant.Server.Generic (AsServerT) import Servant.Server.Generic (AsServerT)
----------------------------------------------------------------------- -----------------------------------------------------------------------
......
module Gargantext.API.Search.Types where module Gargantext.API.Search.Types where
import GHC.Generics import Data.Aeson (defaultOptions, genericParseJSON, genericToJSON, sumEncoding, SumEncoding(..))
import Data.Aeson hiding (defaultTaggedObject) import Data.Swagger (ToSchema, declareNamedSchema, genericDeclareNamedSchema)
import Data.Swagger hiding (fieldLabelModifier, Contact)
import Gargantext.Core.Text.Corpus.Query (RawQuery (..)) import Gargantext.Core.Text.Corpus.Query (RawQuery (..))
import Gargantext.Core.Types.Search import Gargantext.Core.Types.Search (Row)
import Gargantext.Core.Utils.Prefix (unPrefixSwagger) import Gargantext.Core.Utils.Prefix (unPrefixSwagger)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Utils.Aeson (defaultTaggedObject) import Gargantext.Utils.Aeson (defaultTaggedObject)
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary
----------------------------------------------------------------------- -----------------------------------------------------------------------
----------------------------------------------------------------------- -----------------------------------------------------------------------
...@@ -23,8 +20,6 @@ instance FromJSON SearchType where ...@@ -23,8 +20,6 @@ instance FromJSON SearchType where
instance ToJSON SearchType where instance ToJSON SearchType where
toJSON = genericToJSON (defaultOptions { sumEncoding = ObjectWithSingleField }) toJSON = genericToJSON (defaultOptions { sumEncoding = ObjectWithSingleField })
instance ToSchema SearchType instance ToSchema SearchType
instance Arbitrary SearchType where
arbitrary = elements [SearchDoc, SearchContact]
----------------------------------------------------------------------- -----------------------------------------------------------------------
data SearchQuery = data SearchQuery =
...@@ -42,9 +37,6 @@ instance ToSchema SearchQuery ...@@ -42,9 +37,6 @@ instance ToSchema SearchQuery
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "") declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "")
-} -}
instance Arbitrary SearchQuery where
arbitrary = elements [SearchQuery (RawQuery "electrodes") SearchDoc]
-- arbitrary = elements [SearchQuery "electrodes" 1 ] --SearchDoc]
----------------------------------------------------------------------- -----------------------------------------------------------------------
data SearchResult = data SearchResult =
SearchResult { result :: !SearchResultTypes} SearchResult { result :: !SearchResultTypes}
...@@ -62,9 +54,6 @@ instance ToSchema SearchResult ...@@ -62,9 +54,6 @@ instance ToSchema SearchResult
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "") declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "")
-} -}
instance Arbitrary SearchResult where
arbitrary = SearchResult <$> arbitrary
data SearchResultTypes = data SearchResultTypes =
SearchResultDoc { docs :: ![Row] } SearchResultDoc { docs :: ![Row] }
...@@ -76,13 +65,6 @@ instance FromJSON SearchResultTypes where ...@@ -76,13 +65,6 @@ instance FromJSON SearchResultTypes where
instance ToJSON SearchResultTypes where instance ToJSON SearchResultTypes where
toJSON = genericToJSON (defaultOptions { sumEncoding = defaultTaggedObject }) toJSON = genericToJSON (defaultOptions { sumEncoding = defaultTaggedObject })
instance Arbitrary SearchResultTypes where
arbitrary = do
srd <- SearchResultDoc <$> arbitrary
src <- SearchResultContact <$> arbitrary
srn <- pure $ SearchNoResult "No result because.."
elements [srd, src, srn]
instance ToSchema SearchResultTypes where instance ToSchema SearchResultTypes where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "") declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "")
......
...@@ -29,7 +29,7 @@ import Gargantext.Prelude hiding (Handler, catch) ...@@ -29,7 +29,7 @@ import Gargantext.Prelude hiding (Handler, catch)
import Gargantext.System.Logging (logLocM, LogLevel(..)) import Gargantext.System.Logging (logLocM, LogLevel(..))
import Paths_gargantext qualified as PG -- cabal magic build module import Paths_gargantext qualified as PG -- cabal magic build module
import Servant import Servant
import Servant.Server.Generic import Servant.Server.Generic (AsServer, AsServerT)
import Servant.Swagger.UI (swaggerSchemaUIServer) import Servant.Swagger.UI (swaggerSchemaUIServer)
serverGargAPI :: Env -> BackEndAPI (AsServerT (GargM Env BackendInternalError)) serverGargAPI :: Env -> BackEndAPI (AsServerT (GargM Env BackendInternalError))
......
...@@ -3,20 +3,21 @@ ...@@ -3,20 +3,21 @@
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-} {-# OPTIONS_GHC -fno-warn-orphans #-}
module Gargantext.API.Server.Named.EKG where module Gargantext.API.Server.Named.EKG where
import Data.HashMap.Strict as HM import Data.HashMap.Strict as HM
import Data.Text as T import Data.Text as T
import Data.Text.IO as T import Data.Text.IO as T
import Data.Time.Clock.POSIX (getPOSIXTime) import Data.Time.Clock.POSIX (getPOSIXTime)
import Gargantext.API.Routes.Named.EKG import Gargantext.API.Routes.Named.EKG (EkgAPI(..))
import Network.Wai import Network.Wai (Middleware)
import Protolude import Protolude
import Servant import Servant
import Servant.Auth import Servant.Auth (Auth)
import Servant.Ekg import Servant.Ekg (HasEndpoint, enumerateEndpoints, getEndpoint, monitorEndpoints)
import Servant.Server.Generic import Servant.Server.Generic (AsServer)
import System.Metrics import System.Metrics (Store, newStore, registerCounter, registerGcMetrics, sampleAll)
import System.Metrics.Json qualified as J import System.Metrics.Json qualified as J
......
...@@ -11,16 +11,16 @@ import Data.Map.Strict qualified as Map ...@@ -11,16 +11,16 @@ import Data.Map.Strict qualified as Map
import Data.Set qualified as Set import Data.Set qualified as Set
import Gargantext.API.Admin.Auth (withNamedAccess) import Gargantext.API.Admin.Auth (withNamedAccess)
import Gargantext.API.Admin.Auth.Types (AuthenticatedUser, PathId (..)) import Gargantext.API.Admin.Auth.Types (AuthenticatedUser, PathId (..))
import Gargantext.API.Admin.EnvTypes import Gargantext.API.Admin.EnvTypes (Env)
import Gargantext.API.Errors.Types (BackendInternalError) import Gargantext.API.Errors.Types (BackendInternalError)
import Gargantext.API.Metrics qualified as Metrics import Gargantext.API.Metrics qualified as Metrics
import Gargantext.API.Ngrams import Gargantext.API.Ngrams
import Gargantext.API.Ngrams.Types import Gargantext.API.Ngrams.Types
import Gargantext.API.Prelude import Gargantext.API.Prelude (GargM)
import Gargantext.API.Routes.Named.Table qualified as Named import Gargantext.API.Routes.Named.Table qualified as Named
import Gargantext.API.Worker (serveWorkerAPI) import Gargantext.API.Worker (serveWorkerAPI)
import Gargantext.Core.NodeStory.Types (HasNodeStory) import Gargantext.Core.NodeStory.Types (HasNodeStory)
import Gargantext.Core.Types hiding (Terms) import Gargantext.Core.Types (DocId, ListId, ListType(..), NodeId, NodeType(..))
import Gargantext.Core.Types.Query (Limit(..), Offset(..)) import Gargantext.Core.Types.Query (Limit(..), Offset(..))
import Gargantext.Core.Worker.Jobs.Types qualified as Jobs import Gargantext.Core.Worker.Jobs.Types qualified as Jobs
import Gargantext.Database.Admin.Config (userMaster) import Gargantext.Database.Admin.Config (userMaster)
...@@ -30,7 +30,7 @@ import Gargantext.Database.Query.Table.Node.Error (HasNodeError) ...@@ -30,7 +30,7 @@ import Gargantext.Database.Query.Table.Node.Error (HasNodeError)
import Gargantext.Database.Query.Table.Node.Select ( selectNodesWithUsername ) import Gargantext.Database.Query.Table.Node.Select ( selectNodesWithUsername )
import Gargantext.Database.Schema.Node (node_id, node_parent_id, node_user_id) import Gargantext.Database.Schema.Node (node_id, node_parent_id, node_user_id)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Utils.Jobs.Monad import Gargantext.Utils.Jobs.Monad (JobHandle, MonadJobStatus(..), markFailedNoErr)
import Servant.Server.Generic (AsServerT) import Servant.Server.Generic (AsServerT)
......
{-# OPTIONS_GHC -Wno-deprecations #-} {-# OPTIONS_GHC -Wno-deprecations #-}
module Gargantext.API.Server.Named.Private where module Gargantext.API.Server.Named.Private where
import Gargantext.API.Admin.Auth.Types (AuthenticatedUser(..)) import Gargantext.API.Admin.Auth.Types (AuthenticatedUser(..))
import Gargantext.API.Admin.EnvTypes (Env) import Gargantext.API.Admin.EnvTypes (Env)
import Gargantext.API.Context import Gargantext.API.Context (contextAPI)
import Gargantext.API.Count qualified as Count import Gargantext.API.Count qualified as Count
import Gargantext.API.Errors.Types import Gargantext.API.Errors.Types (BackendInternalError)
import Gargantext.API.Members (members) import Gargantext.API.Members (members)
import Gargantext.API.Ngrams.List qualified as List import Gargantext.API.Ngrams.List qualified as List
import Gargantext.API.Node import Gargantext.API.Node (annuaireNodeAPI, corpusNodeAPI, nodeAPI, nodeNodeAPI, nodesAPI, roots)
import Gargantext.API.Node qualified as Tree import Gargantext.API.Node qualified as Tree
import Gargantext.API.Node.Contact as Contact import Gargantext.API.Node.Contact as Contact
import Gargantext.API.Node.Corpus.Export qualified as CorpusExport import Gargantext.API.Node.Corpus.Export qualified as CorpusExport
...@@ -16,15 +17,14 @@ import Gargantext.API.Node.Corpus.Subcorpus qualified as Subcorpus ...@@ -16,15 +17,14 @@ import Gargantext.API.Node.Corpus.Subcorpus qualified as Subcorpus
import Gargantext.API.Node.Document.Export (documentExportAPI) import Gargantext.API.Node.Document.Export (documentExportAPI)
import Gargantext.API.Node.Phylo.Export qualified as PhyloExport import Gargantext.API.Node.Phylo.Export qualified as PhyloExport
import Gargantext.API.Node.ShareURL ( shareURL ) import Gargantext.API.Node.ShareURL ( shareURL )
import Gargantext.API.Prelude import Gargantext.API.Prelude (GargM)
import Gargantext.API.Routes (addCorpusWithForm, addCorpusWithQuery) import Gargantext.API.Routes (addCorpusWithForm, addCorpusWithQuery)
import Gargantext.API.Routes.Named.Private qualified as Named import Gargantext.API.Routes.Named.Private qualified as Named
import Gargantext.API.Server.Named.Ngrams import Gargantext.API.Server.Named.Ngrams (apiNgramsTableDoc)
import Gargantext.API.Server.Named.Viz qualified as Viz import Gargantext.API.Server.Named.Viz qualified as Viz
import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Database.Admin.Types.Hyperdata import Gargantext.Database.Admin.Types.Hyperdata (HyperdataAny)
import Gargantext.Prelude import Gargantext.Prelude
import Servant.Auth.Swagger ()
import Servant.Server.Generic (AsServerT) import Servant.Server.Generic (AsServerT)
--------------------------------------------------------------------- ---------------------------------------------------------------------
......
...@@ -9,7 +9,9 @@ import Data.Map.Strict qualified as Map ...@@ -9,7 +9,9 @@ import Data.Map.Strict qualified as Map
import Data.Set qualified as Set import Data.Set qualified as Set
import Gargantext.API.Node.File (fileApi) import Gargantext.API.Node.File (fileApi)
import Gargantext.API.Prelude (serverError, IsGargServer) import Gargantext.API.Prelude (serverError, IsGargServer)
import Gargantext.API.Public.Types import Gargantext.API.Public.Types (PublicData(..))
import Gargantext.API.Routes.Named.File qualified as Named
import Gargantext.API.Routes.Named.Public qualified as Named
import Gargantext.Core.Utils.DateUtils (utc2year) import Gargantext.Core.Utils.DateUtils (utc2year)
import Gargantext.Database.Admin.Types.Hyperdata.Corpus ( hc_fields ) import Gargantext.Database.Admin.Types.Hyperdata.Corpus ( hc_fields )
import Gargantext.Database.Admin.Types.Hyperdata.CorpusField import Gargantext.Database.Admin.Types.Hyperdata.CorpusField
...@@ -22,8 +24,6 @@ import Gargantext.Database.Schema.Node ( NodePoly(..), node_date, node_hyperdata ...@@ -22,8 +24,6 @@ import Gargantext.Database.Schema.Node ( NodePoly(..), node_date, node_hyperdata
import Gargantext.Prelude import Gargantext.Prelude
import Servant import Servant
import Servant.Server.Generic (AsServerT) import Servant.Server.Generic (AsServerT)
import qualified Gargantext.API.Routes.Named.File as Named
import qualified Gargantext.API.Routes.Named.Public as Named
serverPublicGargAPI :: IsGargServer env err m => Text -> Named.GargPublicAPI (AsServerT m) serverPublicGargAPI :: IsGargServer env err m => Text -> Named.GargPublicAPI (AsServerT m)
serverPublicGargAPI baseUrl = serverPublicGargAPI baseUrl =
......
...@@ -4,15 +4,14 @@ module Gargantext.API.Server.Named.Viz ( ...@@ -4,15 +4,14 @@ module Gargantext.API.Server.Named.Viz (
) where ) where
import Gargantext.API.Admin.Auth (withNamedAccess) import Gargantext.API.Admin.Auth (withNamedAccess)
import Gargantext.API.Admin.Auth.Types import Gargantext.API.Admin.Auth.Types (AuthenticatedUser, PathId(..))
import Gargantext.API.Admin.EnvTypes (Env) import Gargantext.API.Admin.EnvTypes (Env)
import Gargantext.API.Errors.Types ( BackendInternalError ) import Gargantext.API.Errors.Types ( BackendInternalError )
import Gargantext.API.Prelude (GargM) import Gargantext.API.Prelude (GargM)
import Gargantext.API.Routes.Named.Viz qualified as Named import Gargantext.API.Routes.Named.Viz qualified as Named
import Gargantext.Core.Viz.Graph.API import Gargantext.Core.Viz.Graph.API
import Gargantext.Core.Viz.Graph.GEXF ()
-- (cooc2graph) -- (cooc2graph)
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node (NodeId, UserId)
import Gargantext.Prelude import Gargantext.Prelude
import Servant.Server.Generic (AsServerT) import Servant.Server.Generic (AsServerT)
......
...@@ -14,15 +14,14 @@ Portability : POSIX ...@@ -14,15 +14,14 @@ Portability : POSIX
--------------------------------------------------------------------- ---------------------------------------------------------------------
module Gargantext.API.Swagger where module Gargantext.API.Swagger where
--------------------------------------------------------------------- ---------------------------------------------------------------------
import Control.Lens import Control.Lens ((?~))
import Data.Swagger import Data.Swagger
import Data.Version (showVersion) import Data.Version (showVersion)
import Servant
import Servant.Swagger
import qualified Paths_gargantext as PG -- cabal magic build module
import Gargantext.API.Routes.Named qualified as Named import Gargantext.API.Routes.Named qualified as Named
import Gargantext.Prelude import Gargantext.Prelude
import Paths_gargantext qualified as PG -- cabal magic build module
import Servant
import Servant.Swagger (toSwagger, subOperations)
backendApiProxy :: Proxy (ToServantApi Named.BackEndAPI) backendApiProxy :: Proxy (ToServantApi Named.BackEndAPI)
backendApiProxy = Proxy backendApiProxy = Proxy
......
...@@ -30,23 +30,23 @@ module Gargantext.API.Table ...@@ -30,23 +30,23 @@ module Gargantext.API.Table
where where
import Data.Text qualified as T import Data.Text qualified as T
import Gargantext.API.HashedResponse import Gargantext.API.HashedResponse (HashedResponse(..), constructHashedResponse)
import Gargantext.API.Ngrams.Types (TabType(..)) import Gargantext.API.Ngrams.Types (TabType(..))
import Gargantext.API.Prelude (IsGargServer) import Gargantext.API.Prelude (IsGargServer)
import Gargantext.API.Routes.Named.Table qualified as Named import Gargantext.API.Routes.Named.Table qualified as Named
import Gargantext.API.Table.Types import Gargantext.API.Table.Types (FacetTableResult, TableQuery(..))
import Gargantext.Core.Text.Corpus.Query (RawQuery, parseQuery, getRawQuery) import Gargantext.Core.Text.Corpus.Query (RawQuery, parseQuery, getRawQuery)
import Gargantext.Core.Types (TableResult(..)) import Gargantext.Core.Types (TableResult(..))
import Gargantext.Core.Types.Query (Offset, Limit) import Gargantext.Core.Types.Query (Offset, Limit)
import Gargantext.Database.Action.Learn (FavOrTrash(..), moreLike) import Gargantext.Database.Action.Learn (FavOrTrash(..), moreLike)
import Gargantext.Database.Action.Search import Gargantext.Database.Action.Search (searchCountInCorpus, searchInCorpus)
import Gargantext.Database.Admin.Types.Node hiding (ERROR, DEBUG) import Gargantext.Database.Admin.Types.Node (ContactId, CorpusId, NodeId)
import Gargantext.Database.Prelude (CmdM, DbCmd', DBCmd) import Gargantext.Database.Prelude (CmdM, DbCmd', DBCmd)
import Gargantext.Database.Query.Facet (FacetDoc , runViewDocuments, runCountDocuments, OrderBy(..), runViewAuthorsDoc) import Gargantext.Database.Query.Facet (FacetDoc , runViewDocuments, runCountDocuments, OrderBy(..), runViewAuthorsDoc)
import Gargantext.Database.Query.Table.Node.Error (HasNodeError) import Gargantext.Database.Query.Table.Node.Error (HasNodeError)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.System.Logging import Gargantext.System.Logging
import Servant.Server.Generic import Servant.Server.Generic (AsServerT)
tableApi :: IsGargServer env err m => NodeId -> Named.TableAPI (AsServerT m) tableApi :: IsGargServer env err m => NodeId -> Named.TableAPI (AsServerT m)
tableApi id' = Named.TableAPI tableApi id' = Named.TableAPI
......
...@@ -12,8 +12,6 @@ import Gargantext.Core.Types.Query (Offset, Limit) ...@@ -12,8 +12,6 @@ import Gargantext.Core.Types.Query (Offset, Limit)
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger) import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
import Gargantext.Database.Query.Facet (FacetDoc , OrderBy(..)) import Gargantext.Database.Query.Facet (FacetDoc , OrderBy(..))
import Gargantext.Prelude import Gargantext.Prelude
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
data TableQuery = TableQuery data TableQuery = TableQuery
{ tq_offset :: Offset { tq_offset :: Offset
...@@ -29,12 +27,3 @@ $(deriveJSON (unPrefix "tq_") ''TableQuery) ...@@ -29,12 +27,3 @@ $(deriveJSON (unPrefix "tq_") ''TableQuery)
instance ToSchema TableQuery where instance ToSchema TableQuery where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "tq_") declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "tq_")
instance Arbitrary TableQuery where
arbitrary = elements [TableQuery { tq_offset = 0
, tq_limit = 10
, tq_orderBy = DateAsc
, tq_view = Docs
, tq_query = "electrodes" }]
...@@ -25,10 +25,10 @@ module Gargantext.API.ThrowAll ( ...@@ -25,10 +25,10 @@ module Gargantext.API.ThrowAll (
import Control.Lens ((#)) import Control.Lens ((#))
import Data.ByteString.Char8 qualified as C8 import Data.ByteString.Char8 qualified as C8
import Gargantext.API.Admin.Auth.Types import Gargantext.API.Admin.Auth.Types (AuthenticatedUser(..))
import Gargantext.API.Admin.EnvTypes (Env) import Gargantext.API.Admin.EnvTypes (Env)
import Gargantext.API.Errors.Types import Gargantext.API.Errors.Types (BackendInternalError)
import Gargantext.API.Prelude import Gargantext.API.Prelude (GargM, _ServerError)
import Gargantext.API.Routes.Named.Private qualified as Named import Gargantext.API.Routes.Named.Private qualified as Named
import Gargantext.API.Server.Named.Private qualified as Named import Gargantext.API.Server.Named.Private qualified as Named
import Gargantext.Database.Admin.Types.Node (UserId (..)) import Gargantext.Database.Admin.Types.Node (UserId (..))
...@@ -36,7 +36,6 @@ import Gargantext.Prelude hiding (Handler) ...@@ -36,7 +36,6 @@ import Gargantext.Prelude hiding (Handler)
import Network.HTTP.Types.Status (Status(..)) import Network.HTTP.Types.Status (Status(..))
import Network.Wai (responseLBS) import Network.Wai (responseLBS)
import Servant import Servant
import Servant.API.Generic ()
import Servant.Auth.Server (AuthResult(..)) import Servant.Auth.Server (AuthResult(..))
import Servant.Server.Generic (AsServerT) import Servant.Server.Generic (AsServerT)
......
...@@ -38,10 +38,15 @@ import Gargantext.API.Node.New.Types (PostNode(..)) ...@@ -38,10 +38,15 @@ import Gargantext.API.Node.New.Types (PostNode(..))
import Gargantext.API.Node.Share.Types (ShareNodeParams(..)) 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.Public.Types (PublicData(..))
import Gargantext.API.Routes.Named.Publish (PublishRequest(..))
import Gargantext.API.Search.Types (SearchQuery(..), SearchResult(..), SearchResultTypes(..), SearchType(..))
import Gargantext.API.Table.Types (TableQuery(..))
import Gargantext.API.Viz.Types (PhyloData) import Gargantext.API.Viz.Types (PhyloData)
import Gargantext.Core (Lang) 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.Text.Corpus.Query (RawQuery(..))
import Gargantext.Core.Types (TableResult) 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))
...@@ -49,6 +54,7 @@ import Gargantext.Core.Viz.Phylo qualified as Phylo ...@@ -49,6 +54,7 @@ import Gargantext.Core.Viz.Phylo qualified as Phylo
import Gargantext.Core.Worker.Jobs.Types (Job(..)) import Gargantext.Core.Worker.Jobs.Types (Job(..))
import Gargantext.Database.Admin.Types.Hyperdata qualified as Hyperdata import Gargantext.Database.Admin.Types.Hyperdata qualified as Hyperdata
import Gargantext.Database.Admin.Types.Node (NodeId(..), UserId(..), NodeType(..)) import Gargantext.Database.Admin.Types.Node (NodeId(..), UserId(..), NodeType(..))
import Gargantext.Database.Query.Facet (OrderBy(..))
import Gargantext.Prelude hiding (replace, Location) import Gargantext.Prelude hiding (replace, Location)
import Servant.Job.Core qualified as SJ import Servant.Job.Core qualified as SJ
import Servant.Job.Types qualified as SJ import Servant.Job.Types qualified as SJ
...@@ -129,6 +135,40 @@ instance Arbitrary Datafield where arbitrary = genericArbitrary ...@@ -129,6 +135,40 @@ instance Arbitrary Datafield where arbitrary = genericArbitrary
instance Arbitrary WithQuery where arbitrary = genericArbitrary instance Arbitrary WithQuery where arbitrary = genericArbitrary
instance Arbitrary PublicData where
arbitrary = elements
$ replicate 6 defaultPublicData
defaultPublicData :: PublicData
defaultPublicData =
PublicData { title = "Title"
, abstract = foldl (<>) "" $ replicate 100 "abstract "
, img = "images/Gargantextuel-212x300.jpg"
, url = "https://.."
, date = "YY/MM/DD"
, database = "database"
, author = "Author" }
instance Arbitrary PublishRequest where
arbitrary = PublishRequest <$> arbitraryBoundedEnum
instance Arbitrary SearchQuery where
arbitrary = elements [SearchQuery (RawQuery "electrodes") SearchDoc]
-- arbitrary = elements [SearchQuery "electrodes" 1 ] --SearchDoc]
instance Arbitrary SearchResult where
arbitrary = SearchResult <$> arbitrary
instance Arbitrary SearchResultTypes where
arbitrary = do
srd <- SearchResultDoc <$> arbitrary
src <- SearchResultContact <$> arbitrary
srn <- pure $ SearchNoResult "No result because.."
elements [srd, src, srn]
instance Arbitrary SearchType where
arbitrary = elements [SearchDoc, SearchContact]
-- The endpoint does nothing currently, but if it will, we need to provide some valid _wf_data -- The endpoint does nothing currently, but if it will, we need to provide some valid _wf_data
instance Arbitrary AnnuaireWithForm where arbitrary = genericArbitrary instance Arbitrary AnnuaireWithForm where arbitrary = genericArbitrary
...@@ -150,6 +190,19 @@ instance Arbitrary ShareNodeParams where ...@@ -150,6 +190,19 @@ instance Arbitrary ShareNodeParams where
, SharePublicParams (UnsafeMkNodeId 1) , SharePublicParams (UnsafeMkNodeId 1)
] ]
instance Arbitrary TableQuery where
arbitrary = elements [TableQuery { tq_offset = 0
, tq_limit = 10
, tq_orderBy = DateAsc
, tq_view = Docs
, tq_query = "electrodes" }]
-- phylo -- phylo
instance Arbitrary Phylo.PhyloSubConfigAPI where arbitrary = genericArbitrary instance Arbitrary Phylo.PhyloSubConfigAPI where arbitrary = genericArbitrary
......
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