Commit 70edc60b authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

Merge branch '467-dev-api-refactorings-merge' into 'dev'

Resolve "API refactorings"

See merge request !412
parents d19839d8 62984bf8
Pipeline #7679 passed with stages
in 47 minutes and 35 seconds
...@@ -14,8 +14,8 @@ import Data.Aeson.Encode.Pretty ...@@ -14,8 +14,8 @@ import Data.Aeson.Encode.Pretty
import Data.ByteString qualified as B import Data.ByteString qualified as B
import Data.ByteString.Lazy qualified as BL import Data.ByteString.Lazy qualified as BL
import Gargantext.API.Routes.Named import Gargantext.API.Routes.Named
import Gargantext.Prelude
import Options.Applicative import Options.Applicative
import Prelude
import Servant.API import Servant.API
import Servant.API.Routes import Servant.API.Routes
import Servant.API.WebSocket qualified as WS (WebSocketPending) import Servant.API.WebSocket qualified as WS (WebSocketPending)
...@@ -52,6 +52,6 @@ instance HasRoutes Raw where ...@@ -52,6 +52,6 @@ instance HasRoutes Raw where
routesCLI :: CLIRoutes -> IO () routesCLI :: CLIRoutes -> IO ()
routesCLI = \case routesCLI = \case
CLIR_list CLIR_list
-> printRoutes @(NamedRoutes API) -> printRoutesSorted @(NamedRoutes API)
(CLIR_export filePath) (CLIR_export filePath)
-> B.writeFile filePath . BL.toStrict $ encodePretty (getRoutes @(NamedRoutes API)) -> B.writeFile filePath . BL.toStrict $ encodePretty (getRoutes @(NamedRoutes API))
...@@ -16,7 +16,7 @@ fi ...@@ -16,7 +16,7 @@ fi
# with the `sha256sum` result calculated on the `cabal.project` and # with the `sha256sum` result calculated on the `cabal.project` and
# `cabal.project.freeze`. This ensures the files stay deterministic so that CI # `cabal.project.freeze`. This ensures the files stay deterministic so that CI
# cache can kick in. # cache can kick in.
expected_cabal_project_hash="7d021a8e3d0b68421e26bdfe4e1da82f6ea26b6c420fc984b3c30c14bc5fea98" expected_cabal_project_hash="c7e0466c8d4c1ca88b4f3d62d022bd29329d44afc48fffbcfacf0f65293acba8"
expected_cabal_project_freeze_hash="553b98aadb35506a305bd740cdd71f5fadc1e6d55d10f91cf39daa6735a63d78" expected_cabal_project_freeze_hash="553b98aadb35506a305bd740cdd71f5fadc1e6d55d10f91cf39daa6735a63d78"
......
...@@ -146,7 +146,7 @@ source-repository-package ...@@ -146,7 +146,7 @@ source-repository-package
source-repository-package source-repository-package
type: git type: git
location: https://github.com/fpringle/servant-routes.git location: https://github.com/fpringle/servant-routes.git
tag: 7694f62af6bc1596d754b42af16da131ac403b3a tag: c3c558d9278ef239a474f1e1b69afc461be60d01
source-repository-package source-repository-package
type: git type: git
......
...@@ -120,7 +120,6 @@ library ...@@ -120,7 +120,6 @@ library
Gargantext.API.Admin.Orchestrator.Types Gargantext.API.Admin.Orchestrator.Types
Gargantext.API.Admin.Settings Gargantext.API.Admin.Settings
Gargantext.API.Auth.PolicyCheck Gargantext.API.Auth.PolicyCheck
Gargantext.API.Count.Types
Gargantext.API.Dev Gargantext.API.Dev
Gargantext.API.Errors Gargantext.API.Errors
Gargantext.API.Errors.Class Gargantext.API.Errors.Class
...@@ -166,7 +165,6 @@ library ...@@ -166,7 +165,6 @@ library
Gargantext.API.Routes.Named.Contact Gargantext.API.Routes.Named.Contact
Gargantext.API.Routes.Named.Context Gargantext.API.Routes.Named.Context
Gargantext.API.Routes.Named.Corpus Gargantext.API.Routes.Named.Corpus
Gargantext.API.Routes.Named.Count
Gargantext.API.Routes.Named.Document Gargantext.API.Routes.Named.Document
Gargantext.API.Routes.Named.EKG Gargantext.API.Routes.Named.EKG
Gargantext.API.Routes.Named.File Gargantext.API.Routes.Named.File
...@@ -335,7 +333,6 @@ library ...@@ -335,7 +333,6 @@ library
Gargantext.API.Admin.Auth Gargantext.API.Admin.Auth
Gargantext.API.Admin.FrontEnd Gargantext.API.Admin.FrontEnd
Gargantext.API.Context Gargantext.API.Context
Gargantext.API.Count
Gargantext.API.EKG Gargantext.API.EKG
Gargantext.API.GraphQL Gargantext.API.GraphQL
Gargantext.API.GraphQL.Annuaire Gargantext.API.GraphQL.Annuaire
...@@ -707,7 +704,6 @@ executable gargantext ...@@ -707,7 +704,6 @@ executable gargantext
, gargantext , gargantext
, gargantext-prelude , gargantext-prelude
, haskell-bee , haskell-bee
, lens >= 5.2.2 && < 5.3
, MonadRandom ^>= 0.6 , MonadRandom ^>= 0.6
, optparse-applicative , optparse-applicative
, postgresql-simple >= 0.6.4 && <= 0.7.0.0 , postgresql-simple >= 0.6.4 && <= 0.7.0.0
......
{-|
Module : Gargantext.API.Count
Description : Server API
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Count API part of Gargantext.
-}
{-# OPTIONS_GHC -fno-warn-deprecations #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DeriveAnyClass #-}
module Gargantext.API.Count (
countAPI
) where
import Gargantext.API.Count.Types
import Gargantext.API.Routes.Named.Count qualified as Named
import Gargantext.Prelude
import Servant.Server.Generic (AsServerT)
-----------------------------------------------------------------------
-- TODO-ACCESS: CanCount
-- TODO-EVENTS: No events as this is a read only query.
-----------------------------------------------------------------------
countAPI :: Query -> Named.CountAPI (AsServerT m)
countAPI _ = Named.CountAPI undefined
{-|
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 #-}
module Gargantext.API.Count.Types (
Scraper(..)
, QueryBool(..)
, Query(..)
, Message(..)
, Code
, Error
, Errors
, Counts(..)
, Count(..)
-- * functions
, scrapers
) where
import Data.Swagger ( ToSchema(..), genericDeclareNamedSchema )
import Data.Text (pack)
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
import Gargantext.Prelude
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary (Arbitrary(..))
-----------------------------------------------------------------------
data Scraper = Pubmed | Hal | IsTex | Isidore
deriving (Eq, Show, Generic, Enum, Bounded)
scrapers :: [Scraper]
scrapers = [minBound..maxBound]
instance FromJSON Scraper
instance ToJSON Scraper
instance Arbitrary Scraper where
arbitrary = elements scrapers
instance ToSchema Scraper
-----------------------------------------------------------------------
data QueryBool = QueryBool Text
deriving (Eq, Show, Generic)
queries :: [QueryBool]
queries = [QueryBool (pack "(X OR X') AND (Y OR Y') NOT (Z OR Z')")]
--queries = [QueryBool (pack "(X + X') * (Y + Y') - (Z + Z')")]
instance Arbitrary QueryBool where
arbitrary = elements queries
instance FromJSON QueryBool
instance ToJSON QueryBool
instance ToSchema QueryBool
-----------------------------------------------------------------------
data Query = Query { query_query :: QueryBool
, query_name :: Maybe [Scraper]
}
deriving (Eq, Show, Generic)
instance FromJSON Query
instance ToJSON Query
instance Arbitrary Query where
arbitrary = elements [ Query q (Just n)
| q <- queries
, n <- take 10 $ permutations scrapers
]
instance ToSchema Query where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "query_")
-----------------------------------------------------------------------
type Code = Integer
type Error = Text
type Errors = [Error]
-----------------------------------------------------------------------
data Message = Message Code Errors
deriving (Eq, Show, Generic)
toMessage :: [(Code, Errors)] -> [Message]
toMessage = map (\(c,err) -> Message c err)
messages :: [Message]
messages = toMessage $ [ (400, ["Ill formed query "])
, (300, ["API connexion error "])
, (300, ["Internal Gargantext Error "])
] <> take 10 ( repeat (200, [""]))
instance Arbitrary Message where
arbitrary = elements messages
instance ToSchema Message
-----------------------------------------------------------------------
data Counts = Counts { results :: [Either Message Count]
} deriving (Eq, Show, Generic)
instance Arbitrary Counts where
arbitrary = elements [Counts [ Right (Count Pubmed (Just 20 ))
, Right (Count IsTex (Just 150))
, Right (Count Hal (Just 150))
]
]
instance ToSchema Counts
-----------------------------------------------------------------------
data Count = Count { count_name :: Scraper
, count_count :: Maybe Int
}
deriving (Eq, Show, Generic)
instance ToSchema Count where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "count_")
--instance Arbitrary Count where
-- arbitrary = Count <$> arbitrary <*> arbitrary <*> arbitrary
--
-- JSON instances
--
instance FromJSON Message
instance ToJSON Message
$(deriveJSON (unPrefix "count_") ''Count)
instance FromJSON Counts
instance ToJSON Counts
...@@ -61,11 +61,14 @@ import Servant.Server.Generic (AsServerT) ...@@ -61,11 +61,14 @@ import Servant.Server.Generic (AsServerT)
getAPI :: Named.GETAPI (AsServerT (GargM Env BackendInternalError)) getAPI :: Named.GETAPI (AsServerT (GargM Env BackendInternalError))
getAPI = Named.GETAPI $ \listId -> Named.ListEndpoints getAPI = Named.GETAPI
{
getListEp = \listId -> Named.ListEndpoints
{ listJSONEp = getJson listId { listJSONEp = getJson listId
, listJSONZipEp = getJsonZip listId , listJSONZipEp = getJsonZip listId
, listTSVEp = getTsv listId , listTSVEp = getTsv listId
} }
}
-- --
-- JSON API -- JSON API
......
...@@ -32,7 +32,7 @@ import Gargantext.API.Admin.Auth.Types (PathId(..), AuthenticatedUser (..), auth ...@@ -32,7 +32,7 @@ import Gargantext.API.Admin.Auth.Types (PathId(..), AuthenticatedUser (..), auth
import Gargantext.API.Admin.EnvTypes (Env) import Gargantext.API.Admin.EnvTypes (Env)
import Gargantext.API.Auth.PolicyCheck ( nodeReadChecks, nodeWriteChecks, moveChecks, AccessPolicyManager, publishChecks ) import Gargantext.API.Auth.PolicyCheck ( nodeReadChecks, nodeWriteChecks, moveChecks, AccessPolicyManager, publishChecks )
import Gargantext.API.Errors.Types (BackendInternalError) import Gargantext.API.Errors.Types (BackendInternalError)
import Gargantext.API.Metrics import Gargantext.API.Metrics (chartApi, pieApi, scatterApi, treeApi, updateChart)
import Gargantext.API.Ngrams.Types (TabType(..)) import Gargantext.API.Ngrams.Types (TabType(..))
import Gargantext.API.Node.DocumentUpload qualified as DocumentUpload import Gargantext.API.Node.DocumentUpload qualified as DocumentUpload
import Gargantext.API.Node.DocumentsFromWriteNodes qualified as DFWN import Gargantext.API.Node.DocumentsFromWriteNodes qualified as DFWN
...@@ -40,7 +40,7 @@ import Gargantext.API.Node.File ( fileApi, fileAsyncApi ) ...@@ -40,7 +40,7 @@ import Gargantext.API.Node.File ( fileApi, fileAsyncApi )
import Gargantext.API.Node.FrameCalcUpload qualified as FrameCalcUpload import Gargantext.API.Node.FrameCalcUpload qualified as FrameCalcUpload
import Gargantext.API.Node.New ( postNode, postNodeAsyncAPI ) import Gargantext.API.Node.New ( postNode, postNodeAsyncAPI )
import Gargantext.API.Node.Share qualified as Share import Gargantext.API.Node.Share qualified as Share
import Gargantext.API.Node.Types import Gargantext.API.Node.Types (NodesToCategory(..), NodesToScore(..), RenameNode(..))
import Gargantext.API.Node.Update qualified as Update import Gargantext.API.Node.Update qualified as Update
import Gargantext.API.Prelude ( GargM, GargServer, IsGargServer ) import Gargantext.API.Prelude ( GargM, GargServer, IsGargServer )
import Gargantext.API.Routes.Named.File qualified as Named import Gargantext.API.Routes.Named.File qualified as Named
...@@ -61,14 +61,14 @@ import Gargantext.Database.Action.Delete qualified as Action (deleteNode) ...@@ -61,14 +61,14 @@ import Gargantext.Database.Action.Delete qualified as Action (deleteNode)
import Gargantext.Database.Action.Flow.Pairing (pairing) import Gargantext.Database.Action.Flow.Pairing (pairing)
import Gargantext.Database.Admin.Types.Hyperdata (HyperdataAny, HyperdataCorpus, HyperdataAnnuaire) import Gargantext.Database.Admin.Types.Hyperdata (HyperdataAny, HyperdataCorpus, HyperdataAnnuaire)
import Gargantext.Database.Admin.Types.Hyperdata.Prelude ( HyperdataC ) import Gargantext.Database.Admin.Types.Hyperdata.Prelude ( HyperdataC )
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node (CorpusId, NodeId, ParentId, RootId, UserId)
import Gargantext.Database.Prelude import Gargantext.Database.Prelude (DBCmdExtra, JSONB, runDBTx, runDBQuery)
import Gargantext.Database.Query.Table.Node import Gargantext.Database.Query.Table.Node (defaultList, deleteNodes, getNodeWith, getNodesWithParentId)
import Gargantext.Database.Query.Table.Node.Children (getChildren) import Gargantext.Database.Query.Table.Node.Children (getChildren)
import Gargantext.Database.Query.Table.Node.Error (HasNodeError) import Gargantext.Database.Query.Table.Node.Error (HasNodeError)
import Gargantext.Database.Query.Table.Node.Update (Update(..), update)
import Gargantext.Database.Query.Table.Node.Update qualified as U (update, Update(..), publish)
import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata) import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata)
import Gargantext.Database.Query.Table.Node.Update qualified as U (update, Update(..), publish)
import Gargantext.Database.Query.Table.Node.Update (Update(..), update)
import Gargantext.Database.Query.Table.NodeContext (nodeContextsCategory, nodeContextsScore) import Gargantext.Database.Query.Table.NodeContext (nodeContextsCategory, nodeContextsScore)
import Gargantext.Database.Query.Table.NodeNode import Gargantext.Database.Query.Table.NodeNode
import Gargantext.Database.Query.Tree (tree, tree_flat, TreeMode(..)) import Gargantext.Database.Query.Tree (tree, tree_flat, TreeMode(..))
...@@ -249,11 +249,11 @@ genericNodeAPI' :: forall a proxy. ( HyperdataC a ) ...@@ -249,11 +249,11 @@ genericNodeAPI' :: forall a proxy. ( HyperdataC a )
-> Named.NodeAPI a (AsServerT (GargM Env BackendInternalError)) -> Named.NodeAPI a (AsServerT (GargM Env BackendInternalError))
genericNodeAPI' _ authenticatedUser targetNode = Named.NodeAPI genericNodeAPI' _ authenticatedUser targetNode = Named.NodeAPI
{ nodeNodeAPI = withNamedPolicyT authenticatedUser (nodeReadChecks targetNode) $ { nodeNodeAPI = withNamedPolicyT authenticatedUser (nodeReadChecks targetNode) $
Named.NodeNodeAPI $ runDBQuery (getNodeWith targetNode (Proxy :: Proxy a)) Named.NodeNodeAPI { getNodeEp = runDBQuery $ getNodeWith targetNode (Proxy :: Proxy a) }
, renameAPI = withNamedPolicyT authenticatedUser (nodeWriteChecks targetNode) $ , renameAPI = withNamedPolicyT authenticatedUser (nodeWriteChecks targetNode) $
Named.RenameAPI $ rename loggedInUserId targetNode Named.RenameAPI { renameEp = rename loggedInUserId targetNode }
, postNodeAPI = withNamedPolicyT authenticatedUser (nodeWriteChecks targetNode) $ , postNodeAPI = withNamedPolicyT authenticatedUser (nodeWriteChecks targetNode) $
Named.PostNodeAPI $ postNode authenticatedUser targetNode Named.PostNodeAPI { postWithParentEp = postNode authenticatedUser targetNode }
, postNodeAsyncAPI = withNamedPolicyT authenticatedUser (nodeWriteChecks targetNode) $ , postNodeAsyncAPI = withNamedPolicyT authenticatedUser (nodeWriteChecks targetNode) $
postNodeAsyncAPI authenticatedUser targetNode postNodeAsyncAPI authenticatedUser targetNode
, frameCalcUploadAPI = FrameCalcUpload.api authenticatedUser targetNode , frameCalcUploadAPI = FrameCalcUpload.api authenticatedUser targetNode
...@@ -262,30 +262,29 @@ genericNodeAPI' _ authenticatedUser targetNode = Named.NodeAPI ...@@ -262,30 +262,29 @@ genericNodeAPI' _ authenticatedUser targetNode = Named.NodeAPI
Update.api targetNode Update.api targetNode
, deleteEp = withPolicy authenticatedUser (nodeWriteChecks targetNode) $ , deleteEp = withPolicy authenticatedUser (nodeWriteChecks targetNode) $
Action.deleteNode userRootId targetNode Action.deleteNode userRootId targetNode
, childrenAPI = Named.ChildrenAPI $ \mb_nty mb_off mb_lim -> , childrenAPI = Named.ChildrenAPI { summaryChildrenEp = \nt o l -> runDBQuery $ getChildren targetNode (Proxy :: Proxy a) nt o l }
runDBQuery $ getChildren targetNode (Proxy :: Proxy a) mb_nty mb_off mb_lim
, tableAPI = tableApi targetNode , tableAPI = tableApi targetNode
, tableNgramsAPI = apiNgramsTableCorpus targetNode , tableNgramsAPI = apiNgramsTableCorpus targetNode
, catAPI = Named.CatAPI $ catApi targetNode , catAPI = Named.CatAPI { categoriseEp = catApi targetNode }
, scoreAPI = Named.ScoreAPI $ scoreApi targetNode , scoreAPI = Named.ScoreAPI { scoreNodesEp = scoreApi targetNode }
, searchAPI = Search.api targetNode , searchAPI = Search.api targetNode
, shareAPI = Named.ShareNode $ Share.api userRootId targetNode , shareAPI = Named.ShareNode { shareNodeEp = Share.api userRootId targetNode }
, unshareEp = Share.unShare targetNode , unshareEp = Share.unShare targetNode
, publishAPI = withNamedPolicyT authenticatedUser (publishChecks targetNode) $ , publishAPI = withNamedPolicyT authenticatedUser (publishChecks targetNode) $
Named.PublishAPI $ \Named.PublishRequest{pubrq_policy} -> runDBTx $ U.publish loggedInUserId targetNode pubrq_policy Named.PublishAPI { publishEp = \Named.PublishRequest{pubrq_policy} -> runDBTx $ U.publish loggedInUserId targetNode pubrq_policy }
---- Pairing utilities ---- Pairing utilities
, pairWithEp = pairWith targetNode , pairWithEp = pairWith targetNode
, pairsEp = pairs targetNode , pairsEp = pairs targetNode
, pairingEp = Named.PairingAPI $ getPair targetNode , pairingEp = Named.PairingAPI { getPairingEp = getPair targetNode }
---- VIZ ---- VIZ
, scatterAPI = scatterApi targetNode , scatterAPI = scatterApi targetNode
, chartAPI = chartApi targetNode , chartAPI = chartApi targetNode
, pieAPI = pieApi targetNode , pieAPI = pieApi targetNode
, treeAPI = treeApi targetNode , treeAPI = treeApi targetNode
, phyloAPI = phyloAPI targetNode , phyloAPI = phyloAPI targetNode
, moveAPI = Named.MoveAPI $ \parentId -> , moveAPI = Named.MoveAPI { moveNodeEp = \parentId ->
withPolicy authenticatedUser (moveChecks (SourceId targetNode) (TargetId parentId)) $ withPolicy authenticatedUser (moveChecks (SourceId targetNode) (TargetId parentId)) $
moveNode loggedInUserId targetNode parentId moveNode loggedInUserId targetNode parentId }
, fileAPI = Named.FileAPI { fileDownloadEp = fileApi targetNode } , fileAPI = Named.FileAPI { fileDownloadEp = fileApi targetNode }
, fileAsyncAPI = fileAsyncApi authenticatedUser targetNode , fileAsyncAPI = fileAsyncApi authenticatedUser targetNode
, dfwnAPI = DFWN.api authenticatedUser targetNode , dfwnAPI = DFWN.api authenticatedUser targetNode
......
...@@ -24,7 +24,7 @@ module Gargantext.API.Routes.Named.Corpus ( ...@@ -24,7 +24,7 @@ module Gargantext.API.Routes.Named.Corpus (
import Data.Aeson.TH (deriveJSON) import Data.Aeson.TH (deriveJSON)
import Data.Swagger (ToSchema(..), genericDeclareNamedSchema) import Data.Swagger (ToSchema(..), genericDeclareNamedSchema)
import Data.Text (Text) import Data.Text (Text)
import GHC.Generics import GHC.Generics (Generic)
import Gargantext.API.Node.Corpus.Export.Types (Corpus, CorpusSQLite) import Gargantext.API.Node.Corpus.Export.Types (Corpus, CorpusSQLite)
import Gargantext.API.Node.Types (NewWithForm, WithQuery) import Gargantext.API.Node.Types (NewWithForm, WithQuery)
import Gargantext.API.Worker (WorkerAPI) import Gargantext.API.Worker (WorkerAPI)
......
{-# LANGUAGE TypeOperators #-}
module Gargantext.API.Routes.Named.Count (
-- * Routes types
CountAPI(..)
-- * Re-exports
, module X
) where
import GHC.Generics (Generic)
import Gargantext.API.Count.Types as X
import Servant
newtype CountAPI mode = CountAPI
{ postCountsEp :: mode :- Post '[JSON] X.Counts
} deriving Generic
...@@ -30,19 +30,18 @@ import Gargantext.API.Auth.PolicyCheck (PolicyChecked) ...@@ -30,19 +30,18 @@ import Gargantext.API.Auth.PolicyCheck (PolicyChecked)
import Gargantext.API.Routes.Named.Contact (ContactAPI) import Gargantext.API.Routes.Named.Contact (ContactAPI)
import Gargantext.API.Routes.Named.Context (ContextAPI) import Gargantext.API.Routes.Named.Context (ContextAPI)
import Gargantext.API.Routes.Named.Corpus (AddWithTempFile, AddWithQuery, CorpusExportAPI, MakeSubcorpusAPI) import Gargantext.API.Routes.Named.Corpus (AddWithTempFile, AddWithQuery, CorpusExportAPI, MakeSubcorpusAPI)
import Gargantext.API.Routes.Named.Count (CountAPI, Query)
import Gargantext.API.Routes.Named.Document (DocumentExportAPI) import Gargantext.API.Routes.Named.Document (DocumentExportAPI)
import Gargantext.API.Routes.Named.List (GETAPI, JSONAPI, TSVAPI) 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.Remote import Gargantext.API.Routes.Named.Remote (RemoteImportAPI)
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 GHC.Generics import GHC.Generics (Generic)
import Servant.API import Servant.API
import Servant.Auth qualified as SA import Servant.Auth qualified as SA
...@@ -81,9 +80,6 @@ data GargPrivateAPI' mode = GargPrivateAPI' ...@@ -81,9 +80,6 @@ data GargPrivateAPI' mode = GargPrivateAPI'
:> NamedRoutes DocumentExportAPI :> NamedRoutes DocumentExportAPI
, phyloExportAPI :: mode :- "phylo" :> Capture "node_id" DocId , phyloExportAPI :: mode :- "phylo" :> Capture "node_id" DocId
:> NamedRoutes PhyloExportAPI :> NamedRoutes PhyloExportAPI
, countAPI :: mode :- "count" :> Summary "Count endpoint"
:> ReqBody '[JSON] Query
:> NamedRoutes CountAPI
, graphAPI :: mode :- "graph" :> Summary "Graph endpoint" , graphAPI :: mode :- "graph" :> Summary "Graph endpoint"
:> Capture "graph_id" NodeId :> Capture "graph_id" NodeId
:> NamedRoutes GraphAPI :> NamedRoutes GraphAPI
......
{-|
Module : Gargantext.API.Routes.Named.Remote
Description : Server API
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE TypeOperators #-}
module Gargantext.API.Routes.Named.Remote ( module Gargantext.API.Routes.Named.Remote (
-- * Routes types -- * Routes types
RemoteExportAPI(..) RemoteExportAPI(..)
...@@ -13,16 +25,15 @@ import Conduit qualified as C ...@@ -13,16 +25,15 @@ import Conduit qualified as C
import Data.Aeson as JSON import Data.Aeson as JSON
import Data.ByteString.Lazy qualified as BL import Data.ByteString.Lazy qualified as BL
import Data.ByteString qualified as BS import Data.ByteString qualified as BS
import Data.Proxy import Data.Proxy (Proxy(Proxy))
import Data.Swagger hiding (Http) import Data.Swagger (NamedSchema(..), ToSchema, declareNamedSchema, binarySchema, sketchStrictSchema)
import Gargantext.API.Admin.Auth.Types (Token) import Gargantext.API.Admin.Auth.Types (Token)
import Gargantext.API.Auth.PolicyCheck (PolicyChecked) import Gargantext.API.Auth.PolicyCheck (PolicyChecked)
import Gargantext.Database.Admin.Types.Node ( NodeId (..) ) import Gargantext.Database.Admin.Types.Node ( NodeId (..) )
import GHC.Generics import GHC.Generics (Generic)
import Prelude import Prelude
import Servant.API import Servant.API
import Servant.Client.Core.BaseUrl import Servant.Client.Core.BaseUrl (BaseUrl(..), parseBaseUrl, Scheme(Http))
import Test.QuickCheck
data RemoteExportAPI mode = RemoteExportAPI data RemoteExportAPI mode = RemoteExportAPI
...@@ -42,9 +53,6 @@ data RemoteExportRequest = ...@@ -42,9 +53,6 @@ data RemoteExportRequest =
, _rer_instance_auth :: Token , _rer_instance_auth :: Token
} deriving (Show, Eq, Generic) } deriving (Show, Eq, Generic)
instance Arbitrary RemoteExportRequest where
arbitrary = RemoteExportRequest <$> (pure (BaseUrl Http "dev.sub.gargantext.org" 8008 "")) <*> arbitrary
instance ToJSON RemoteExportRequest where instance ToJSON RemoteExportRequest where
toJSON RemoteExportRequest{..} toJSON RemoteExportRequest{..}
= JSON.object [ "instance_url" .= toJSON _rer_instance_url = JSON.object [ "instance_url" .= toJSON _rer_instance_url
......
...@@ -17,7 +17,7 @@ import Data.Aeson (withText) ...@@ -17,7 +17,7 @@ import Data.Aeson (withText)
import Data.Swagger (ToSchema, declareNamedSchema) import Data.Swagger (ToSchema, declareNamedSchema)
import Data.Text qualified as T import Data.Text qualified as T
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 Gargantext.Prelude import Gargantext.Prelude
import Network.URI (parseURI) import Network.URI (parseURI)
import Prelude (fail) import Prelude (fail)
......
{-| {-|
Module : Gargantext.API.Count Module : Gargantext.API.Search
Description : Server API Description : Server API
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
......
...@@ -5,7 +5,6 @@ module Gargantext.API.Server.Named.Private where ...@@ -5,7 +5,6 @@ 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 (contextAPI) import Gargantext.API.Context (contextAPI)
import Gargantext.API.Count qualified as Count
import Gargantext.API.Errors.Types (BackendInternalError) 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
...@@ -54,7 +53,6 @@ serverPrivateGargAPI' authenticatedUser@(AuthenticatedUser userNodeId userId) ...@@ -54,7 +53,6 @@ serverPrivateGargAPI' authenticatedUser@(AuthenticatedUser userNodeId userId)
, tableNgramsAPI = apiNgramsTableDoc authenticatedUser , tableNgramsAPI = apiNgramsTableDoc authenticatedUser
, phyloExportAPI = PhyloExport.api userNodeId , phyloExportAPI = PhyloExport.api userNodeId
, documentExportAPI = documentExportAPI userNodeId , documentExportAPI = documentExportAPI userNodeId
, countAPI = Count.countAPI
, graphAPI = Viz.graphAPI authenticatedUser userId , graphAPI = Viz.graphAPI authenticatedUser userId
, treeAPI = Tree.treeAPI authenticatedUser , treeAPI = Tree.treeAPI authenticatedUser
, treeFlatAPI = Tree.treeFlatAPI authenticatedUser , treeFlatAPI = Tree.treeFlatAPI authenticatedUser
......
...@@ -134,7 +134,7 @@ ...@@ -134,7 +134,7 @@
git: "https://github.com/delanoe/patches-map" git: "https://github.com/delanoe/patches-map"
subdirs: subdirs:
- . - .
- commit: 7694f62af6bc1596d754b42af16da131ac403b3a - commit: c3c558d9278ef239a474f1e1b69afc461be60d01
git: "https://github.com/fpringle/servant-routes.git" git: "https://github.com/fpringle/servant-routes.git"
subdirs: subdirs:
- . - .
......
...@@ -42,6 +42,7 @@ import Gargantext.API.Node.Update.Types qualified as NU ...@@ -42,6 +42,7 @@ import Gargantext.API.Node.Update.Types qualified as NU
import Gargantext.API.Node.Types (NewWithForm, NewWithTempFile(..), RenameNode(..), WithQuery) import Gargantext.API.Node.Types (NewWithForm, NewWithTempFile(..), RenameNode(..), WithQuery)
import Gargantext.API.Public.Types (PublicData(..)) import Gargantext.API.Public.Types (PublicData(..))
import Gargantext.API.Routes.Named.Publish (PublishRequest(..)) import Gargantext.API.Routes.Named.Publish (PublishRequest(..))
import Gargantext.API.Routes.Named.Remote (RemoteExportRequest(..))
import Gargantext.API.Search.Types (SearchQuery(..), SearchResult(..), SearchResultTypes(..), SearchType(..)) import Gargantext.API.Search.Types (SearchQuery(..), SearchResult(..), SearchResultTypes(..), SearchType(..))
import Gargantext.API.Table.Types (TableQuery(..)) import Gargantext.API.Table.Types (TableQuery(..))
import Gargantext.API.Viz.Types (PhyloData) import Gargantext.API.Viz.Types (PhyloData)
...@@ -58,6 +59,7 @@ import Gargantext.Database.Admin.Types.Hyperdata qualified as Hyperdata ...@@ -58,6 +59,7 @@ 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.Database.Query.Facet (OrderBy(..))
import Gargantext.Prelude hiding (replace, Location) import Gargantext.Prelude hiding (replace, Location)
import Servant.Client.Core.BaseUrl (BaseUrl(..), Scheme(Http))
import Text.Parsec.Error (ParseError, Message(..), newErrorMessage) import Text.Parsec.Error (ParseError, Message(..), newErrorMessage)
import Text.Parsec.Pos import Text.Parsec.Pos
import Test.QuickCheck import Test.QuickCheck
...@@ -155,6 +157,11 @@ defaultPublicData = ...@@ -155,6 +157,11 @@ defaultPublicData =
instance Arbitrary PublishRequest where instance Arbitrary PublishRequest where
arbitrary = PublishRequest <$> arbitraryBoundedEnum arbitrary = PublishRequest <$> arbitraryBoundedEnum
instance Arbitrary RemoteExportRequest where
arbitrary = RemoteExportRequest <$> (pure (BaseUrl Http "dev.sub.gargantext.org" 8008 "")) <*> arbitrary
instance Arbitrary SearchQuery where instance Arbitrary SearchQuery where
arbitrary = elements [SearchQuery (RawQuery "electrodes") SearchDoc] arbitrary = elements [SearchQuery (RawQuery "electrodes") SearchDoc]
-- arbitrary = elements [SearchQuery "electrodes" 1 ] --SearchDoc] -- arbitrary = elements [SearchQuery "electrodes" 1 ] --SearchDoc]
......
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