Commit ac67946f authored by Alexandre Delanoë's avatar Alexandre Delanoë

[API] Refact + PostNodeAsync route

parent 677fed9b
...@@ -24,7 +24,7 @@ import Data.Either ...@@ -24,7 +24,7 @@ import Data.Either
import Data.Text (Text) import Data.Text (Text)
import Gargantext.API.Node () -- instances import Gargantext.API.Node () -- instances
import Gargantext.API.Admin.Settings (withDevEnv, runCmdDev, DevEnv) import Gargantext.API.Admin.Settings (withDevEnv, runCmdDev, DevEnv)
import Gargantext.API.Admin.Types (GargError) import Gargantext.API.Prelude (GargError)
import Gargantext.Core (Lang(..)) import Gargantext.Core (Lang(..))
import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Database.Action.Flow (FlowCmdM, flowCorpusFile, flowAnnuaire, TermType(..)) import Gargantext.Database.Action.Flow (FlowCmdM, flowCorpusFile, flowAnnuaire, TermType(..))
......
...@@ -22,7 +22,7 @@ module Main where ...@@ -22,7 +22,7 @@ module Main where
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Gargantext.API.Admin.Settings (withDevEnv, runCmdDev) import Gargantext.API.Admin.Settings (withDevEnv, runCmdDev)
import Gargantext.API.Admin.Types (GargError) import Gargantext.API.Prelude (GargError)
import Gargantext.API.Node () -- instances import Gargantext.API.Node () -- instances
import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Database.Action.Flow (getOrMkRoot, getOrMk_RootWithCorpus) import Gargantext.Database.Action.Flow (getOrMkRoot, getOrMk_RootWithCorpus)
......
...@@ -29,7 +29,7 @@ library: ...@@ -29,7 +29,7 @@ library:
- Gargantext.API - Gargantext.API
- Gargantext.API.Node - Gargantext.API.Node
- Gargantext.API.Admin.Settings - Gargantext.API.Admin.Settings
- Gargantext.API.Admin.Types - Gargantext.API.Prelude
- Gargantext.Core - Gargantext.Core
- Gargantext.Core.Types - Gargantext.Core.Types
- Gargantext.Core.Types.Individu - Gargantext.Core.Types.Individu
......
...@@ -50,8 +50,8 @@ module Gargantext.API ...@@ -50,8 +50,8 @@ module Gargantext.API
import Control.Concurrent (threadDelay) import Control.Concurrent (threadDelay)
import Control.Exception (finally) import Control.Exception (finally)
import Control.Lens import Control.Lens
import Control.Monad.Except (withExceptT, ExceptT) import Control.Monad.Except (withExceptT)
import Control.Monad.Reader (ReaderT, runReaderT) import Control.Monad.Reader (runReaderT)
import Data.Aeson.Encode.Pretty (encodePretty) import Data.Aeson.Encode.Pretty (encodePretty)
import Data.List (lookup) import Data.List (lookup)
import Data.Swagger import Data.Swagger
...@@ -64,19 +64,16 @@ import GHC.Generics (D1, Meta (..), Rep) ...@@ -64,19 +64,16 @@ import GHC.Generics (D1, Meta (..), Rep)
import GHC.TypeLits (AppendSymbol, Symbol) import GHC.TypeLits (AppendSymbol, Symbol)
import Gargantext.API.Admin.Auth (AuthRequest, AuthResponse, AuthenticatedUser(..), AuthContext, auth, withAccess, PathId(..)) import Gargantext.API.Admin.Auth (AuthRequest, AuthResponse, AuthenticatedUser(..), AuthContext, auth, withAccess, PathId(..))
import Gargantext.API.Admin.FrontEnd (FrontEndAPI, frontEndServer) import Gargantext.API.Admin.FrontEnd (FrontEndAPI, frontEndServer)
import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.Admin.Settings import Gargantext.API.Admin.Settings
import Gargantext.API.Admin.Types import Gargantext.API.Prelude
import Gargantext.API.Count ( CountAPI, count, Query) import Gargantext.API.Count ( CountAPI, count, Query)
import Gargantext.API.Ngrams (HasRepo(..), HasRepoSaver(..), saveRepo, TableNgramsApi, apiNgramsTableDoc) import Gargantext.API.Ngrams (HasRepoSaver(..), saveRepo, TableNgramsApi, apiNgramsTableDoc)
import Gargantext.API.Node import Gargantext.API.Node
import qualified Gargantext.API.Node.New as NodeNew
import Gargantext.API.Search (SearchPairsAPI, searchPairs) import Gargantext.API.Search (SearchPairsAPI, searchPairs)
import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Database.Query.Table.Node.Contact (HyperdataContact) import Gargantext.Database.Query.Table.Node.Contact (HyperdataContact)
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Admin.Types.Node (NodeId, CorpusId, AnnuaireId) import Gargantext.Database.Admin.Types.Node (NodeId, CorpusId, AnnuaireId)
import Gargantext.Database.Prelude (HasConnectionPool)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Viz.Graph.API import Gargantext.Viz.Graph.API
import Network.HTTP.Types hiding (Query) import Network.HTTP.Types hiding (Query)
...@@ -327,17 +324,6 @@ type API = SwaggerAPI ...@@ -327,17 +324,6 @@ type API = SwaggerAPI
:<|> GargAPI :<|> GargAPI
:<|> FrontEndAPI :<|> FrontEndAPI
-- This is the concrete monad. It needs to be used as little as possible,
-- instead, prefer GargServer, GargServerT, GargServerC.
type GargServerM env err = ReaderT env (ExceptT err IO)
type EnvC env =
( HasConnectionPool env
, HasRepo env
, HasSettings env
, HasJobEnv env ScraperStatus ScraperStatus
)
--------------------------------------------------------------------- ---------------------------------------------------------------------
-- | Server declarations -- | Server declarations
...@@ -474,6 +460,7 @@ portRouteInfo port = do ...@@ -474,6 +460,7 @@ portRouteInfo port = do
T.putStrLn $ "http://localhost:" <> toUrlPiece port <> "/index.html" T.putStrLn $ "http://localhost:" <> toUrlPiece port <> "/index.html"
T.putStrLn $ "http://localhost:" <> toUrlPiece port <> "/swagger-ui" T.putStrLn $ "http://localhost:" <> toUrlPiece port <> "/swagger-ui"
-- TODO clean this Monad condition (more generic) ?
stopGargantext :: HasRepoSaver env => env -> IO () stopGargantext :: HasRepoSaver env => env -> IO ()
stopGargantext env = do stopGargantext env = do
T.putStrLn "----- Stopping gargantext -----" T.putStrLn "----- Stopping gargantext -----"
...@@ -496,7 +483,6 @@ startGargantextMock port = do ...@@ -496,7 +483,6 @@ startGargantextMock port = do
run port application run port application
-} -}
---------------------------------------------------------------------- ----------------------------------------------------------------------
addCorpusWithQuery :: User -> GargServer New.AddWithQuery addCorpusWithQuery :: User -> GargServer New.AddWithQuery
...@@ -532,8 +518,4 @@ addAnnuaireWithForm cid = ...@@ -532,8 +518,4 @@ addAnnuaireWithForm cid =
serveJobsAPI $ serveJobsAPI $
JobFunction (\i log -> Annuaire.addToAnnuaireWithForm cid i (liftBase . log)) JobFunction (\i log -> Annuaire.addToAnnuaireWithForm cid i (liftBase . log))
postNodeAsync :: UserId -> NodeId -> GargServer NodeNew.PostNodeAsync
postNodeAsync uId nId =
serveJobsAPI $
JobFunction (\p log -> NodeNew.postNodeAsync uId nId p (liftBase . log))
...@@ -41,7 +41,7 @@ import Data.Text.Lazy (toStrict) ...@@ -41,7 +41,7 @@ import Data.Text.Lazy (toStrict)
import Data.Text.Lazy.Encoding (decodeUtf8) import Data.Text.Lazy.Encoding (decodeUtf8)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Gargantext.API.Admin.Settings import Gargantext.API.Admin.Settings
import Gargantext.API.Admin.Types (HasJoseError(..), joseError, HasServerError, GargServerC) import Gargantext.API.Prelude (HasJoseError(..), joseError, HasServerError, GargServerC)
import Gargantext.Core.Types.Individu (User(..), Username, Password, arbitraryUsername, arbitraryPassword) import Gargantext.Core.Types.Individu (User(..), Username, Password, arbitraryUsername, arbitraryPassword)
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger) import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
import Gargantext.Database.Query.Tree (isDescendantOf, isIn) import Gargantext.Database.Query.Tree (isDescendantOf, isIn)
......
...@@ -34,7 +34,7 @@ import Gargantext.API.Node.Corpus.New ...@@ -34,7 +34,7 @@ import Gargantext.API.Node.Corpus.New
import Gargantext.API.Node.Corpus.New.File (FileType(..)) import Gargantext.API.Node.Corpus.New.File (FileType(..))
import Gargantext.API.Ngrams import Gargantext.API.Ngrams
import Gargantext.API.Admin.Orchestrator.Types import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.Admin.Types (GargServer) import Gargantext.API.Prelude (GargServer)
import Gargantext.Core.Utils.Prefix (unPrefixSwagger) import Gargantext.Core.Utils.Prefix (unPrefixSwagger)
import Gargantext.Database.Action.Flow (FlowCmdM) import Gargantext.Database.Action.Flow (FlowCmdM)
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
......
...@@ -44,7 +44,7 @@ import Data.Text (Text()) ...@@ -44,7 +44,7 @@ import Data.Text (Text())
import Data.Time (UTCTime) import Data.Time (UTCTime)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Gargantext.API.Admin.Auth (withAccess, PathId(..)) import Gargantext.API.Admin.Auth (withAccess, PathId(..))
import Gargantext.API.Admin.Types import Gargantext.API.Prelude
import Gargantext.API.Metrics import Gargantext.API.Metrics
import Gargantext.API.Ngrams (TabType(..), TableNgramsApi, apiNgramsTableCorpus, QueryParamR) import Gargantext.API.Ngrams (TabType(..), TableNgramsApi, apiNgramsTableCorpus, QueryParamR)
import Gargantext.API.Ngrams.NTree (MyTree) import Gargantext.API.Ngrams.NTree (MyTree)
...@@ -121,7 +121,7 @@ roots = getNodesWithParentId Nothing ...@@ -121,7 +121,7 @@ roots = getNodesWithParentId Nothing
type NodeAPI a = Get '[JSON] (Node a) type NodeAPI a = Get '[JSON] (Node a)
:<|> "rename" :> RenameApi :<|> "rename" :> RenameApi
:<|> PostNodeApi -- TODO move to children POST :<|> PostNodeApi -- TODO move to children POST
-- :<|> PostNodeAsync :<|> PostNodeAsync
:<|> ReqBody '[JSON] a :> Put '[JSON] Int :<|> ReqBody '[JSON] a :> Put '[JSON] Int
:<|> Delete '[JSON] Int :<|> Delete '[JSON] Int
:<|> "children" :> ChildrenApi a :<|> "children" :> ChildrenApi a
...@@ -194,7 +194,7 @@ nodeAPI p uId id' = withAccess (Proxy :: Proxy (NodeAPI a)) Proxy uId (PathNode ...@@ -194,7 +194,7 @@ nodeAPI p uId id' = withAccess (Proxy :: Proxy (NodeAPI a)) Proxy uId (PathNode
nodeAPI' = getNodeWith id' p nodeAPI' = getNodeWith id' p
:<|> rename id' :<|> rename id'
:<|> postNode uId id' :<|> postNode uId id'
-- :<|> postNodeAsync uId id' :<|> postNodeAsyncAPI uId id'
:<|> putNode id' :<|> putNode id'
:<|> deleteNodeApi id' :<|> deleteNodeApi id'
:<|> getChildren id' p :<|> getChildren id' p
...@@ -331,3 +331,4 @@ putNode :: forall err a. (HasNodeError err, JSONB a, ToJSON a) ...@@ -331,3 +331,4 @@ putNode :: forall err a. (HasNodeError err, JSONB a, ToJSON a)
putNode n h = fromIntegral <$> updateHyperdata n h putNode n h = fromIntegral <$> updateHyperdata n h
------------------------------------------------------------- -------------------------------------------------------------
...@@ -34,7 +34,7 @@ import Data.Text (Text) ...@@ -34,7 +34,7 @@ import Data.Text (Text)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Gargantext.API.Ngrams import Gargantext.API.Ngrams
import Gargantext.API.Ngrams.Tools (filterListWithRoot, mapTermListRoot, getRepo) import Gargantext.API.Ngrams.Tools (filterListWithRoot, mapTermListRoot, getRepo)
import Gargantext.API.Admin.Types (GargNoServer) import Gargantext.API.Prelude (GargNoServer)
import Gargantext.Core.Types -- import Gargantext.Core.Types --
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger) import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
import Gargantext.Database.Action.Metrics.NgramsByNode (getNgramsByNodeOnlyUser) import Gargantext.Database.Action.Metrics.NgramsByNode (getNgramsByNodeOnlyUser)
......
...@@ -32,6 +32,7 @@ import Data.Text (Text) ...@@ -32,6 +32,7 @@ import Data.Text (Text)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Gargantext.API.Admin.Orchestrator.Types (ScraperStatus(..)) import Gargantext.API.Admin.Orchestrator.Types (ScraperStatus(..))
import Gargantext.API.Node.Corpus.New (AsyncJobs) import Gargantext.API.Node.Corpus.New (AsyncJobs)
import Gargantext.API.Prelude
import Gargantext.Database.Action.Flow.Types import Gargantext.Database.Action.Flow.Types
import Gargantext.Database.Action.Node import Gargantext.Database.Action.Node
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
...@@ -41,8 +42,10 @@ import Gargantext.Database.Query.Table.Node.User ...@@ -41,8 +42,10 @@ import Gargantext.Database.Query.Table.Node.User
import Gargantext.Database.Schema.Node import Gargantext.Database.Schema.Node
import Gargantext.Prelude import Gargantext.Prelude
import Servant import Servant
import Servant.Job.Async
import Test.QuickCheck (elements) import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary import Test.QuickCheck.Arbitrary
import Web.FormUrlEncoded (FromForm)
------------------------------------------------------------------------ ------------------------------------------------------------------------
data PostNode = PostNode { pn_name :: Text data PostNode = PostNode { pn_name :: Text
...@@ -53,6 +56,7 @@ data PostNode = PostNode { pn_name :: Text ...@@ -53,6 +56,7 @@ data PostNode = PostNode { pn_name :: Text
instance FromJSON PostNode instance FromJSON PostNode
instance ToJSON PostNode instance ToJSON PostNode
instance ToSchema PostNode instance ToSchema PostNode
instance FromForm PostNode
instance Arbitrary PostNode where instance Arbitrary PostNode where
arbitrary = elements [PostNode "Node test" NodeCorpus] arbitrary = elements [PostNode "Node test" NodeCorpus]
...@@ -72,6 +76,12 @@ type PostNodeAsync = Summary "Post Node" ...@@ -72,6 +76,12 @@ type PostNodeAsync = Summary "Post Node"
:> "async" :> "async"
:> AsyncJobs ScraperStatus '[FormUrlEncoded] PostNode ScraperStatus :> AsyncJobs ScraperStatus '[FormUrlEncoded] PostNode ScraperStatus
postNodeAsyncAPI :: UserId -> NodeId -> GargServer PostNodeAsync
postNodeAsyncAPI uId nId =
serveJobsAPI $
JobFunction (\p logs -> postNodeAsync uId nId p (liftBase . logs))
------------------------------------------------------------------------ ------------------------------------------------------------------------
postNodeAsync :: FlowCmdM env err m postNodeAsync :: FlowCmdM env err m
=> UserId => UserId
......
{-| {-|
Module : Gargantext.API.Admin.Types Module : Gargantext.API.Prelude
Description : Server API main Types Description : Server API main Types
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -21,8 +21,8 @@ Portability : POSIX ...@@ -21,8 +21,8 @@ Portability : POSIX
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE UndecidableInstances #-}
module Gargantext.API.Admin.Types module Gargantext.API.Prelude
( module Gargantext.API.Admin.Types ( module Gargantext.API.Prelude
, HasServerError(..) , HasServerError(..)
, serverError , serverError
) )
...@@ -32,6 +32,8 @@ import Control.Exception (Exception) ...@@ -32,6 +32,8 @@ import Control.Exception (Exception)
import Control.Lens (Prism', (#)) import Control.Lens (Prism', (#))
import Control.Lens.TH (makePrisms) import Control.Lens.TH (makePrisms)
import Control.Monad.Error.Class (MonadError(throwError)) import Control.Monad.Error.Class (MonadError(throwError))
import Control.Monad.Except (ExceptT)
import Control.Monad.Reader (ReaderT)
import Crypto.JOSE.Error as Jose import Crypto.JOSE.Error as Jose
import Data.Aeson.Types import Data.Aeson.Types
import Data.Typeable import Data.Typeable
...@@ -93,6 +95,19 @@ type GargServerT env err m api = GargServerC env err m => ServerT api m ...@@ -93,6 +95,19 @@ type GargServerT env err m api = GargServerC env err m => ServerT api m
type GargServer api = type GargServer api =
forall env err m. GargServerT env err m api forall env err m. GargServerT env err m api
-- This is the concrete monad. It needs to be used as little as possible,
-- instead, prefer GargServer, GargServerT, GargServerC.
type GargServerM env err = ReaderT env (ExceptT err IO)
type EnvC env =
( HasConnectionPool env
, HasRepo env
, HasSettings env
, HasJobEnv env ScraperStatus ScraperStatus
)
------------------------------------------------------------------- -------------------------------------------------------------------
-- | This Type is needed to prepare the function before the GargServer -- | This Type is needed to prepare the function before the GargServer
type GargNoServer' env err m = type GargNoServer' env err m =
......
...@@ -30,7 +30,7 @@ import Data.Swagger ...@@ -30,7 +30,7 @@ import Data.Swagger
import Data.Text (Text) import Data.Text (Text)
import Data.Time (UTCTime) import Data.Time (UTCTime)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Gargantext.API.Admin.Types (GargServer) import Gargantext.API.Prelude (GargServer)
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger) import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
import Gargantext.Database.Query.Facet import Gargantext.Database.Query.Facet
import Gargantext.Database.Action.Search import Gargantext.Database.Action.Search
......
...@@ -42,7 +42,7 @@ import qualified Xmlbf as Xmlbf ...@@ -42,7 +42,7 @@ import qualified Xmlbf as Xmlbf
import Gargantext.API.Ngrams (NgramsRepo, r_version) import Gargantext.API.Ngrams (NgramsRepo, r_version)
import Gargantext.API.Ngrams.Tools import Gargantext.API.Ngrams.Tools
import Gargantext.API.Admin.Orchestrator.Types import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.Admin.Types import Gargantext.API.Prelude
import Gargantext.Core.Types.Main import Gargantext.Core.Types.Main
import Gargantext.Database.Admin.Config import Gargantext.Database.Admin.Config
import Gargantext.Database.Action.Metrics.NgramsByNode (getNodesByNgramsOnlyUser) import Gargantext.Database.Action.Metrics.NgramsByNode (getNodesByNgramsOnlyUser)
......
...@@ -30,7 +30,7 @@ import qualified Data.ByteString as DB ...@@ -30,7 +30,7 @@ import qualified Data.ByteString as DB
import qualified Data.ByteString.Lazy as DBL import qualified Data.ByteString.Lazy as DBL
import Data.Proxy (Proxy(..)) import Data.Proxy (Proxy(..))
import Data.Swagger import Data.Swagger
import Gargantext.API.Admin.Types import Gargantext.API.Prelude
import Gargantext.Database.Schema.Node (_node_hyperdata) import Gargantext.Database.Schema.Node (_node_hyperdata)
import Gargantext.Database.Query.Table.Node (insertNodes, nodePhyloW, getNodeWith) import Gargantext.Database.Query.Table.Node (insertNodes, nodePhyloW, getNodeWith)
import Gargantext.Database.Admin.Types.Node -- (PhyloId, ListId, CorpusId, UserId, NodeId(..)) import Gargantext.Database.Admin.Types.Node -- (PhyloId, ListId, CorpusId, UserId, NodeId(..))
......
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