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

[API] Facto and mkdir Admin

parent 6dcedcdc
Pipeline #4664 canceled with stage
...@@ -23,8 +23,8 @@ import Control.Exception (finally) ...@@ -23,8 +23,8 @@ import Control.Exception (finally)
import Data.Either import Data.Either
import Data.Text (Text) import Data.Text (Text)
import Gargantext.API.Node () -- instances import Gargantext.API.Node () -- instances
import Gargantext.API.Settings (withDevEnv, runCmdDev, DevEnv) import Gargantext.API.Admin.Settings (withDevEnv, runCmdDev, DevEnv)
import Gargantext.API.Types (GargError) import Gargantext.API.Admin.Types (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) import Gargantext.Database.Action.Flow (FlowCmdM, flowCorpusFile, flowAnnuaire)
......
...@@ -22,8 +22,8 @@ module Main where ...@@ -22,8 +22,8 @@ module Main where
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Gargantext.API.Node () -- instances import Gargantext.API.Node () -- instances
import Gargantext.API.Settings (withDevEnv, runCmdDev) import Gargantext.API.Admin.Settings (withDevEnv, runCmdDev)
import Gargantext.API.Types (GargError) import Gargantext.API.Admin.Types (GargError)
import Gargantext.Core.Types.Individu (UserId, User(..)) import Gargantext.Core.Types.Individu (UserId, User(..))
import Gargantext.Database.Action.Flow (getOrMkRoot, getOrMk_RootWithCorpus) import Gargantext.Database.Action.Flow (getOrMkRoot, getOrMk_RootWithCorpus)
import Gargantext.Database.Admin.Config (userMaster, corpusMasterName) import Gargantext.Database.Admin.Config (userMaster, corpusMasterName)
......
...@@ -27,14 +27,9 @@ library: ...@@ -27,14 +27,9 @@ library:
exposed-modules: exposed-modules:
- Gargantext - Gargantext
- Gargantext.API - Gargantext.API
- Gargantext.API.Auth
- Gargantext.API.Count
- Gargantext.API.FrontEnd
- Gargantext.API.Ngrams
- Gargantext.API.Node - Gargantext.API.Node
- Gargantext.API.Search - Gargantext.API.Admin.Settings
- Gargantext.API.Settings - Gargantext.API.Admin.Types
- Gargantext.API.Types
- Gargantext.Core - Gargantext.Core
- Gargantext.Core.Types - Gargantext.Core.Types
- Gargantext.Core.Types.Individu - Gargantext.Core.Types.Individu
......
...@@ -62,15 +62,15 @@ import Data.Version (showVersion) ...@@ -62,15 +62,15 @@ import Data.Version (showVersion)
import GHC.Base (Applicative) import GHC.Base (Applicative)
import GHC.Generics (D1, Meta (..), Rep) import GHC.Generics (D1, Meta (..), Rep)
import GHC.TypeLits (AppendSymbol, Symbol) import GHC.TypeLits (AppendSymbol, Symbol)
import Gargantext.API.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.Orchestrator.Types
import Gargantext.API.Admin.Settings
import Gargantext.API.Admin.Types
import Gargantext.API.Count ( CountAPI, count, Query) import Gargantext.API.Count ( CountAPI, count, Query)
import Gargantext.API.FrontEnd (FrontEndAPI, frontEndServer)
import Gargantext.API.Ngrams (HasRepo(..), HasRepoSaver(..), saveRepo, TableNgramsApi, apiNgramsTableDoc) import Gargantext.API.Ngrams (HasRepo(..), HasRepoSaver(..), saveRepo, TableNgramsApi, apiNgramsTableDoc)
import Gargantext.API.Node import Gargantext.API.Node
import Gargantext.API.Orchestrator.Types
import Gargantext.API.Search (SearchPairsAPI, searchPairs) import Gargantext.API.Search (SearchPairsAPI, searchPairs)
import Gargantext.API.Settings
import Gargantext.API.Types
import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Database.Action.Query.Node.Contact (HyperdataContact) import Gargantext.Database.Action.Query.Node.Contact (HyperdataContact)
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
...@@ -94,11 +94,11 @@ import Servant.Swagger.UI ...@@ -94,11 +94,11 @@ import Servant.Swagger.UI
import System.IO (FilePath) import System.IO (FilePath)
import qualified Data.ByteString.Lazy.Char8 as BL8 import qualified Data.ByteString.Lazy.Char8 as BL8
import qualified Data.Text.IO as T import qualified Data.Text.IO as T
import qualified Gargantext.API.Annuaire as Annuaire import qualified Gargantext.API.Corpus.Annuaire as Annuaire
import qualified Gargantext.API.Corpus.New as New import qualified Gargantext.API.Corpus.Export as Export
import qualified Gargantext.API.Export as Export import qualified Gargantext.API.Corpus.New as New
import qualified Gargantext.API.Ngrams.List as List import qualified Gargantext.API.Ngrams.List as List
import qualified Paths_gargantext as PG -- cabal magic build module import qualified Paths_gargantext as PG -- cabal magic build module
showAsServantErr :: GargError -> ServerError showAsServantErr :: GargError -> ServerError
showAsServantErr (GargServerError err) = err showAsServantErr (GargServerError err) = err
......
{-| {-|
Module : Gargantext.API.Auth Module : Gargantext.API.Admin.Auth
Description : Server API Auth Module Description : Server API Auth Module
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -29,7 +29,7 @@ TODO-ACCESS Critical ...@@ -29,7 +29,7 @@ TODO-ACCESS Critical
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
module Gargantext.API.Auth module Gargantext.API.Admin.Auth
where where
import Control.Lens (view) import Control.Lens (view)
...@@ -40,12 +40,12 @@ import Data.Text (Text, reverse) ...@@ -40,12 +40,12 @@ import Data.Text (Text, reverse)
import Data.Text.Lazy (toStrict) 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.Settings import Gargantext.API.Admin.Settings
import Gargantext.API.Types (HasJoseError(..), joseError, HasServerError, GargServerC) import Gargantext.API.Admin.Types (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.Action.Query.Tree.Root (getRoot)
import Gargantext.Database.Action.Query.Tree (isDescendantOf, isIn) import Gargantext.Database.Action.Query.Tree (isDescendantOf, isIn)
import Gargantext.Database.Action.Query.Tree.Root (getRoot)
import Gargantext.Database.Admin.Types.Node (NodePoly(_node_id), NodeId(..), UserId, ListId, DocId) import Gargantext.Database.Admin.Types.Node (NodePoly(_node_id), NodeId(..), UserId, ListId, DocId)
import Gargantext.Database.Admin.Utils (Cmd', CmdM, HasConnectionPool) import Gargantext.Database.Admin.Utils (Cmd', CmdM, HasConnectionPool)
import Gargantext.Prelude hiding (reverse) import Gargantext.Prelude hiding (reverse)
......
{-| {-|
Module : Gargantext.API.FrontEnd Module : Gargantext.API.Admin.FrontEnd
Description : Server FrontEnd API Description : Server FrontEnd API
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -16,7 +16,7 @@ Loads all static file for the front-end. ...@@ -16,7 +16,7 @@ Loads all static file for the front-end.
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
--------------------------------------------------------------------- ---------------------------------------------------------------------
module Gargantext.API.FrontEnd where module Gargantext.API.Admin.FrontEnd where
import Servant import Servant
import Servant.Server.StaticFiles (serveDirectoryFileServer) import Servant.Server.StaticFiles (serveDirectoryFileServer)
......
{-|
Module : Gargantext.API.Admin.Orchestrator
Description : Jobs Orchestrator
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleContexts #-}
...@@ -7,12 +18,12 @@ ...@@ -7,12 +18,12 @@
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
module Gargantext.API.Orchestrator where module Gargantext.API.Admin.Orchestrator where
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.API.Settings import Gargantext.API.Admin.Settings
import Gargantext.API.Orchestrator.Types import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.Orchestrator.Scrapy.Schedule import Gargantext.API.Admin.Orchestrator.Scrapy.Schedule
import Control.Lens hiding (elements) import Control.Lens hiding (elements)
import Data.Aeson import Data.Aeson
import qualified Data.ByteString.Lazy.Char8 as LBS import qualified Data.ByteString.Lazy.Char8 as LBS
......
{-|
Module : Gargantext.API.Admin.Orchestartor.Scrapy.Schedule
Description : Server API Auth Module
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
module Gargantext.API.Orchestrator.Scrapy.Schedule where
module Gargantext.API.Admin.Orchestrator.Scrapy.Schedule
where
import Control.Lens import Control.Lens
import Data.Aeson import Data.Aeson
import qualified Data.HashMap.Strict as H
import Data.Text (Text) import Data.Text (Text)
import GHC.Generics import GHC.Generics
import Servant import Servant
import Servant.Job.Utils (jsonOptions)
import Servant.Client import Servant.Client
import Servant.Job.Utils (jsonOptions)
import Web.FormUrlEncoded hiding (parseMaybe) import Web.FormUrlEncoded hiding (parseMaybe)
import qualified Data.HashMap.Strict as H
------------------------------------------------------------------------
data Schedule = Schedule data Schedule = Schedule
{ s_project :: !Text { s_project :: !Text
......
...@@ -8,21 +8,25 @@ ...@@ -8,21 +8,25 @@
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
module Gargantext.API.Orchestrator.Types where module Gargantext.API.Admin.Orchestrator.Types
where
import Gargantext.Prelude
import Control.Lens hiding (elements) import Control.Lens hiding (elements)
import Data.Aeson import Data.Aeson
import Data.Proxy import Data.Proxy
import Data.Text (Text)
import Data.Swagger hiding (URL, url, port) import Data.Swagger hiding (URL, url, port)
import Data.Text (Text)
import GHC.Generics hiding (to) import GHC.Generics hiding (to)
import Gargantext.Core.Types (TODO(..))
import Gargantext.Prelude
import Servant.Job.Async 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)
import Test.QuickCheck.Arbitrary import Test.QuickCheck.Arbitrary
import Gargantext.Core.Types (TODO(..))
------------------------------------------------------------------------
instance Arbitrary a => Arbitrary (JobStatus 'Safe a) where instance Arbitrary a => Arbitrary (JobStatus 'Safe a) where
arbitrary = panic "TODO" arbitrary = panic "TODO"
......
{-| {-|
Module : Gargantext.API.Settings Module : Gargantext.API.Admin.Settings
Description : Settings of the API (Server and Client) Description : Settings of the API (Server and Client)
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -23,7 +23,7 @@ TODO-SECURITY: Critical ...@@ -23,7 +23,7 @@ TODO-SECURITY: Critical
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
module Gargantext.API.Settings module Gargantext.API.Admin.Settings
where where
import Control.Concurrent import Control.Concurrent
...@@ -41,8 +41,8 @@ import Data.Text ...@@ -41,8 +41,8 @@ import Data.Text
import Database.PostgreSQL.Simple (Connection, connect, close, ConnectInfo) import Database.PostgreSQL.Simple (Connection, connect, close, ConnectInfo)
import GHC.Enum import GHC.Enum
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.Ngrams (NgramsRepo, HasRepoVar(..), HasRepoSaver(..), HasRepo(..), RepoEnv(..), r_version, saveRepo, initRepo, renv_var, renv_lock) import Gargantext.API.Ngrams (NgramsRepo, HasRepoVar(..), HasRepoSaver(..), HasRepo(..), RepoEnv(..), r_version, saveRepo, initRepo, renv_var, renv_lock)
import Gargantext.API.Orchestrator.Types
import Gargantext.Database.Admin.Utils (databaseParameters, HasConnectionPool(..), Cmd', runCmd) import Gargantext.Database.Admin.Utils (databaseParameters, HasConnectionPool(..), Cmd', runCmd)
import Gargantext.Prelude import Gargantext.Prelude
import Network.HTTP.Client (Manager) import Network.HTTP.Client (Manager)
......
{-| {-|
Module : Gargantext.API.Types Module : Gargantext.API.Admin.Types
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
...@@ -22,8 +22,8 @@ Portability : POSIX ...@@ -22,8 +22,8 @@ Portability : POSIX
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE UndecidableInstances #-}
module Gargantext.API.Types module Gargantext.API.Admin.Types
( module Gargantext.API.Types ( module Gargantext.API.Admin.Types
, HasServerError(..) , HasServerError(..)
, serverError , serverError
) )
...@@ -37,9 +37,9 @@ import Crypto.JOSE.Error as Jose ...@@ -37,9 +37,9 @@ import Crypto.JOSE.Error as Jose
import Data.Aeson.Types import Data.Aeson.Types
import Data.Typeable import Data.Typeable
import Data.Validity import Data.Validity
import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.Admin.Settings
import Gargantext.API.Ngrams import Gargantext.API.Ngrams
import Gargantext.API.Orchestrator.Types
import Gargantext.API.Settings
import Gargantext.Core.Types import Gargantext.Core.Types
import Gargantext.Database.Action.Query.Tree import Gargantext.Database.Action.Query.Tree
import Gargantext.Database.Admin.Types.Errors (NodeError(..), HasNodeError(..)) import Gargantext.Database.Admin.Types.Errors (NodeError(..), HasNodeError(..))
......
{-| {-|
Module : Gargantext.API.Utils Module : Gargantext.API.Admin.Utils
Description : Server API main Types Description : Server API main Types
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : BSD3 License : BSD3
...@@ -14,7 +14,7 @@ Mainly copied from Servant.Job.Utils (Thanks) ...@@ -14,7 +14,7 @@ Mainly copied from Servant.Job.Utils (Thanks)
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE NoImplicitPrelude #-}
module Gargantext.API.Utils module Gargantext.API.Admin.Utils
where where
import Gargantext.Prelude import Gargantext.Prelude
......
{-|
Module : Gargantext.API.Application
Description : Application of the API
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Inspired by : http://blog.wuzzeb.org/full-stack-web-haskell/server.html
-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# LANGUAGE OverloadedStrings #-}
module Gargantext.API.Application
where
{-| {-|
Module : Gargantext.API.Annuaire Module : Gargantext.API.Corpus.Annuaire
Description : New annuaire API Description : New annuaire API
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -17,7 +17,7 @@ Portability : POSIX ...@@ -17,7 +17,7 @@ Portability : POSIX
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-} {-# LANGUAGE RankNTypes #-}
module Gargantext.API.Annuaire module Gargantext.API.Corpus.Annuaire
where where
import Control.Lens hiding (elements) import Control.Lens hiding (elements)
...@@ -25,8 +25,7 @@ import Data.Aeson ...@@ -25,8 +25,7 @@ import Data.Aeson
import Data.Swagger import Data.Swagger
import Data.Text (Text) import Data.Text (Text)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import qualified Gargantext.API.Corpus.New.File as NewFile import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.Orchestrator.Types
import Gargantext.Core (Lang(..)) import Gargantext.Core (Lang(..))
import Gargantext.Core.Utils.Prefix (unPrefixSwagger) import Gargantext.Core.Utils.Prefix (unPrefixSwagger)
import Gargantext.Database.Action.Flow (FlowCmdM) -- flowAnnuaire import Gargantext.Database.Action.Flow (FlowCmdM) -- flowAnnuaire
...@@ -37,7 +36,8 @@ import Servant.API.Flatten (Flat) ...@@ -37,7 +36,8 @@ import Servant.API.Flatten (Flat)
import Servant.Job.Core import Servant.Job.Core
import Servant.Job.Types import Servant.Job.Types
import Servant.Job.Utils (jsonOptions) import Servant.Job.Utils (jsonOptions)
import Web.FormUrlEncoded (FromForm) import Web.FormUrlEncoded (FromForm)
import qualified Gargantext.API.Corpus.New.File as NewFile
type Api = Summary "New Annuaire endpoint" type Api = Summary "New Annuaire endpoint"
......
{-| {-|
Module : Gargantext.API.Export Module : Gargantext.API.Corpus.Export
Description : Get Metrics from Storage (Database like) Description : Get Metrics from Storage (Database like)
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -22,7 +22,7 @@ Main exports of Gargantext: ...@@ -22,7 +22,7 @@ Main exports of Gargantext:
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
module Gargantext.API.Export module Gargantext.API.Corpus.Export
where where
import Data.Aeson.TH (deriveJSON) import Data.Aeson.TH (deriveJSON)
...@@ -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.Types (GargNoServer) import Gargantext.API.Admin.Types (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)
......
...@@ -28,20 +28,19 @@ module Gargantext.API.Corpus.New ...@@ -28,20 +28,19 @@ module Gargantext.API.Corpus.New
import Control.Lens hiding (elements) import Control.Lens hiding (elements)
import Data.Aeson import Data.Aeson
import Data.Aeson.TH (deriveJSON) import Data.Aeson.TH (deriveJSON)
import Data.Maybe (fromMaybe)
import Data.Either import Data.Either
import Data.Maybe (fromMaybe)
import Data.Swagger import Data.Swagger
import Data.Text (Text) import Data.Text (Text)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.Corpus.New.File import Gargantext.API.Corpus.New.File
import Gargantext.API.Orchestrator.Types
import Gargantext.Core (Lang(..)) import Gargantext.Core (Lang(..))
import Gargantext.Core.Types.Individu (UserId, User(..))
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger) import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
import Gargantext.Database.Action.Flow (FlowCmdM, flowCorpus, flowCorpusSearchInDatabase) import Gargantext.Database.Action.Flow (FlowCmdM, flowCorpus, flowCorpusSearchInDatabase)
import Gargantext.Database.Admin.Types.Node (CorpusId, ToHyperdataDocument(..)) import Gargantext.Database.Admin.Types.Node (CorpusId, ToHyperdataDocument(..))
import Gargantext.Core.Types.Individu (UserId, User(..))
import Gargantext.Prelude import Gargantext.Prelude
import qualified Gargantext.Text.Corpus.Parsers as Parser (FileFormat(..), parseFormat)
import Gargantext.Text.Terms (TermType(..)) import Gargantext.Text.Terms (TermType(..))
import Servant import Servant
import Servant.API.Flatten (Flat) import Servant.API.Flatten (Flat)
...@@ -53,6 +52,7 @@ import Test.QuickCheck (elements) ...@@ -53,6 +52,7 @@ import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary import Test.QuickCheck.Arbitrary
import Web.FormUrlEncoded (FromForm) import Web.FormUrlEncoded (FromForm)
import qualified Gargantext.Text.Corpus.API as API import qualified Gargantext.Text.Corpus.API as API
import qualified Gargantext.Text.Corpus.Parsers as Parser (FileFormat(..), parseFormat)
------------------------------------------------------------------------ ------------------------------------------------------------------------
data Query = Query { query_query :: Text data Query = Query { query_query :: Text
...@@ -153,8 +153,10 @@ type AsyncJobs event ctI input output = ...@@ -153,8 +153,10 @@ type AsyncJobs event ctI input output =
type Upload = Summary "Corpus Upload endpoint" type Upload = Summary "Corpus Upload endpoint"
:> "corpus" :> "corpus"
:> Capture "corpus_id" CorpusId :> Capture "corpus_id" CorpusId
:<|> "addWithquery" :> AsyncJobsAPI ScraperStatus WithQuery ScraperStatus :<|> "addWithquery"
:<|> "addWithfile" :> AsyncJobs ScraperStatus '[FormUrlEncoded] WithForm ScraperStatus :> AsyncJobsAPI ScraperStatus WithQuery ScraperStatus
:<|> "addWithfile"
:> AsyncJobs ScraperStatus '[FormUrlEncoded] WithForm ScraperStatus
type AddWithQuery = Summary "Add with Query to corpus endpoint" type AddWithQuery = Summary "Add with Query to corpus endpoint"
:> "corpus" :> "corpus"
......
...@@ -33,8 +33,8 @@ import GHC.Generics (Generic) ...@@ -33,8 +33,8 @@ import GHC.Generics (Generic)
import Gargantext.API.Corpus.New import Gargantext.API.Corpus.New
import Gargantext.API.Corpus.New.File (FileType(..)) import Gargantext.API.Corpus.New.File (FileType(..))
import Gargantext.API.Ngrams import Gargantext.API.Ngrams
import Gargantext.API.Orchestrator.Types import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.Types (GargServer) import Gargantext.API.Admin.Types (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,22 +44,22 @@ import Data.Swagger ...@@ -44,22 +44,22 @@ 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.Auth (withAccess, PathId(..)) import Gargantext.API.Admin.Auth (withAccess, PathId(..))
import Gargantext.API.Admin.Types
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)
import Gargantext.API.Search (SearchDocsAPI, searchDocs, SearchPairsAPI, searchPairs) import Gargantext.API.Search (SearchDocsAPI, searchDocs, SearchPairsAPI, searchPairs)
import Gargantext.API.Table import Gargantext.API.Table
import Gargantext.API.Types
import Gargantext.Core.Types (NodeTableResult) import Gargantext.Core.Types (NodeTableResult)
import Gargantext.Core.Types.Main (Tree, NodeTree, ListType) import Gargantext.Core.Types.Main (Tree, NodeTree, ListType)
import Gargantext.Database.Action.Query.Facet (FacetDoc, OrderBy(..))
import Gargantext.Database.Action.Flow.Pairing (pairing) import Gargantext.Database.Action.Flow.Pairing (pairing)
import Gargantext.Database.Action.Query
import Gargantext.Database.Action.Query.Facet (FacetDoc, OrderBy(..))
import Gargantext.Database.Action.Query.Node hiding (postNode)
import Gargantext.Database.Action.Query.Node.Children (getChildren) import Gargantext.Database.Action.Query.Node.Children (getChildren)
import Gargantext.Database.Action.Query.Node.UpdateOpaleye (updateHyperdata) import Gargantext.Database.Action.Query.Node.UpdateOpaleye (updateHyperdata)
import Gargantext.Database.Action.Query.Node.User import Gargantext.Database.Action.Query.Node.User
import Gargantext.Database.Action.Query.Node hiding (postNode)
import Gargantext.Database.Action.Query
import Gargantext.Database.Action.Query.Tree (treeDB) import Gargantext.Database.Action.Query.Tree (treeDB)
import Gargantext.Database.Admin.Config (nodeTypeId) import Gargantext.Database.Admin.Config (nodeTypeId)
import Gargantext.Database.Admin.Types.Errors (HasNodeError(..)) import Gargantext.Database.Admin.Types.Errors (HasNodeError(..))
......
...@@ -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.Types (GargServer) import Gargantext.API.Admin.Types (GargServer)
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger) import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
import Gargantext.Database.Action.Query.Facet import Gargantext.Database.Action.Query.Facet
import Gargantext.Database.Action.Search import Gargantext.Database.Action.Search
......
...@@ -26,7 +26,7 @@ import Data.ByteString.Base64.URL as URL ...@@ -26,7 +26,7 @@ import Data.ByteString.Base64.URL as URL
import Data.Either import Data.Either
import Data.Text (Text) import Data.Text (Text)
import GHC.IO (FilePath) import GHC.IO (FilePath)
import Gargantext.API.Settings import Gargantext.API.Admin.Settings
import Gargantext.Database.Admin.Types.Node (NodeId, NodeType) import Gargantext.Database.Admin.Types.Node (NodeId, NodeType)
import Gargantext.Prelude import Gargantext.Prelude
import System.Directory (createDirectoryIfMissing) import System.Directory (createDirectoryIfMissing)
......
...@@ -24,15 +24,14 @@ module Gargantext.Text.Corpus.API ...@@ -24,15 +24,14 @@ module Gargantext.Text.Corpus.API
where where
import Data.Maybe import Data.Maybe
import Gargantext.Prelude import Gargantext.API.Admin.Orchestrator.Types (ExternalAPIs(..), externalAPIs)
import Gargantext.Core (Lang(..)) import Gargantext.Core (Lang(..))
import Gargantext.API.Orchestrator.Types (ExternalAPIs(..), externalAPIs)
import Gargantext.Database.Admin.Types.Node (HyperdataDocument(..)) import Gargantext.Database.Admin.Types.Node (HyperdataDocument(..))
import Gargantext.Prelude
import qualified Gargantext.Text.Corpus.API.Pubmed as PUBMED
import qualified Gargantext.Text.Corpus.API.Isidore as ISIDORE
import qualified Gargantext.Text.Corpus.API.Hal as HAL import qualified Gargantext.Text.Corpus.API.Hal as HAL
import qualified Gargantext.Text.Corpus.API.Isidore as ISIDORE
import qualified Gargantext.Text.Corpus.API.Istex as ISTEX import qualified Gargantext.Text.Corpus.API.Istex as ISTEX
import qualified Gargantext.Text.Corpus.API.Pubmed as PUBMED
-- | Get External API metadata main function -- | Get External API metadata main function
get :: ExternalAPIs -> Query -> Maybe Limit -> IO [HyperdataDocument] get :: ExternalAPIs -> Query -> Maybe Limit -> IO [HyperdataDocument]
......
...@@ -21,7 +21,8 @@ module Gargantext.Text.List.Learn ...@@ -21,7 +21,8 @@ module Gargantext.Text.List.Learn
where where
import Control.Monad.Reader (MonadReader) import Control.Monad.Reader (MonadReader)
import Gargantext.API.Settings -- TODO remvoe this deps
import Gargantext.API.Admin.Settings
import Data.Map (Map) import Data.Map (Map)
import Data.Maybe (maybe) import Data.Maybe (maybe)
import Gargantext.Core.Types.Main (ListType(..), listTypeId, fromListTypeId) import Gargantext.Core.Types.Main (ListType(..), listTypeId, fromListTypeId)
......
...@@ -41,8 +41,8 @@ import qualified Xmlbf as Xmlbf ...@@ -41,8 +41,8 @@ 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.Orchestrator.Types import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.Types import Gargantext.API.Admin.Types
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)
......
...@@ -29,7 +29,7 @@ import Data.String.Conversions ...@@ -29,7 +29,7 @@ import Data.String.Conversions
import qualified Data.ByteString as DB import qualified Data.ByteString as DB
import qualified Data.ByteString.Lazy as DBL import qualified Data.ByteString.Lazy as DBL
import Data.Swagger import Data.Swagger
import Gargantext.API.Types import Gargantext.API.Admin.Types
import Gargantext.Database.Action.Query.Node (insertNodes, nodePhyloW, getNodePhylo) import Gargantext.Database.Action.Query.Node (insertNodes, nodePhyloW, getNodePhylo)
import Gargantext.Database.Admin.Types.Node -- (PhyloId, ListId, CorpusId, UserId, NodeId(..)) import Gargantext.Database.Admin.Types.Node -- (PhyloId, ListId, CorpusId, UserId, NodeId(..))
import Gargantext.Prelude import Gargantext.Prelude
......
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