Stability : experimental
Portability : POSIX
-
-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
-{-# LANGUAGE UndecidableInstances #-}
---------------------------------------------------------------------
module Gargantext.API.Routes
where
---------------------------------------------------------------------
+
+-- import qualified Gargantext.API.Search as Search
import Control.Concurrent (threadDelay)
+import Control.Lens (view)
import Data.Text (Text)
import Data.Validity
-import Servant
-import Servant.Auth as SA
-import Servant.Auth.Swagger ()
-import Servant.Job.Async
-import Servant.Swagger.UI
-
import Gargantext.API.Admin.Auth (AuthRequest, AuthResponse, AuthenticatedUser(..), withAccess, PathId(..))
import Gargantext.API.Admin.FrontEnd (FrontEndAPI)
-import Gargantext.API.Prelude
import Gargantext.API.Count (CountAPI, count, Query)
import Gargantext.API.Ngrams (TableNgramsApi, apiNgramsTableDoc)
import Gargantext.API.Node
-import Gargantext.API.Search (SearchPairsAPI, searchPairs)
+import Gargantext.API.Prelude
import Gargantext.Core.Types.Individu (User(..))
-import Gargantext.Database.Query.Table.Node.Contact (HyperdataContact)
+import Gargantext.Core.Viz.Graph.API
+import Gargantext.Database.Prelude (HasConfig(..))
import Gargantext.Database.Admin.Types.Hyperdata
import Gargantext.Database.Admin.Types.Node
-import Gargantext.Database.Admin.Types.Node (NodeId, CorpusId, AnnuaireId)
import Gargantext.Prelude
-import Gargantext.Viz.Graph.API
+import Gargantext.Prelude.Config (gc_max_docs_scrapers)
+import Servant
+import Servant.Auth as SA
+import Servant.Auth.Swagger ()
+import Servant.Job.Async
+import Servant.Swagger.UI
+import qualified Gargantext.API.Ngrams.List as List
+import qualified Gargantext.API.Node.Contact as Contact
import qualified Gargantext.API.Node.Corpus.Annuaire as Annuaire
import qualified Gargantext.API.Node.Corpus.Export as Export
import qualified Gargantext.API.Node.Corpus.New as New
-import qualified Gargantext.API.Ngrams.List as List
-
-
+import qualified Gargantext.API.Public as Public
type GargAPI = "api" :> Summary "API " :> GargAPIVersion
-- | TODO :<|> Summary "Latest API" :> GargAPI'
-
type GargAPIVersion = "v1.0"
:> Summary "Garg API Version "
:> GargAPI'
-- TODO-ACCESS here we want to request a particular header for
-- auth and capabilities.
:<|> GargPrivateAPI
+ :<|> "public" :> Public.API
-type GargPrivateAPI = SA.Auth '[SA.JWT, SA.Cookie] AuthenticatedUser :> GargPrivateAPI'
+type GargPrivateAPI = SA.Auth '[SA.JWT, SA.Cookie] AuthenticatedUser
+ :> GargPrivateAPI'
type GargAdminAPI
-- Roots endpoint
:<|> "annuaire" :> Summary "Contact endpoint"
:> Capture "annuaire_id" NodeId
- :> "contact"
- :> Capture "contact_id" NodeId
- :> NodeNodeAPI HyperdataContact
+ :> Contact.API
-- Document endpoint
:<|> "document" :> Summary "Document endpoint"
:> Capture "doc_id" DocId
- :> "ngrams" :> TableNgramsApi
+ :> "ngrams"
+ :> TableNgramsApi
-- :<|> "counts" :> Stream GET NewLineFraming '[JSON] Count :> CountAPI
-- TODO-SECURITY
:> CountAPI
-- Corpus endpoint --> TODO rename s/search/filter/g
- :<|> "search" :> Capture "corpus" NodeId
- :> SearchPairsAPI
+ -- :<|> "search" :> Capture "corpus" NodeId
+ -- :> (Search.API Search.SearchResult)
-- TODO move to NodeAPI?
:<|> "graph" :> Summary "Graph endpoint"
-- :<|> New.Upload
:<|> New.AddWithForm
+ :<|> New.AddWithFile
:<|> New.AddWithQuery
-- :<|> "annuaire" :> Annuaire.AddWithForm
:<|> nodeNodeAPI (Proxy :: Proxy HyperdataAny) uid
:<|> Export.getCorpus -- uid
:<|> nodeAPI (Proxy :: Proxy HyperdataAnnuaire) uid
- :<|> nodeNodeAPI (Proxy :: Proxy HyperdataContact) uid
+ :<|> Contact.api uid
:<|> withAccess (Proxy :: Proxy TableNgramsApi) Proxy uid
<$> PathNode <*> apiNgramsTableDoc
:<|> count -- TODO: undefined
- :<|> withAccess (Proxy :: Proxy SearchPairsAPI) Proxy uid
- <$> PathNode <*> searchPairs -- TODO: move elsewhere
+ -- :<|> withAccess (Proxy :: Proxy (Search.API Search.SearchResult)) Proxy uid
+ -- <$> PathNode <*> Search.api -- TODO: move elsewhere
:<|> withAccess (Proxy :: Proxy GraphAPI) Proxy uid
<$> PathNode <*> graphAPI uid -- TODO: mock
:<|> withAccess (Proxy :: Proxy TreeAPI) Proxy uid
<$> PathNode <*> treeAPI
-- TODO access
- :<|> addCorpusWithForm (UserDBId uid)
- :<|> addCorpusWithQuery (RootId (NodeId uid))
+ :<|> addCorpusWithForm (RootId (NodeId uid))
+ :<|> addCorpusWithFile (RootId (NodeId uid))
+ :<|> addCorpusWithQuery (RootId (NodeId uid))
-- :<|> addAnnuaireWithForm
-- :<|> New.api uid -- TODO-SECURITY
pure $ "Waited: " <> (cs $ show n)
----------------------------------------
-
addCorpusWithQuery :: User -> GargServer New.AddWithQuery
addCorpusWithQuery user cid =
serveJobsAPI $
- JobFunction (\q log ->
- let
- log' x = do
- printDebug "addToCorpusWithQuery" x
- liftBase $ log x
- in New.addToCorpusWithQuery user cid q log'
+ JobFunction (\q log -> do
+ limit <- view $ config . gc_max_docs_scrapers
+ New.addToCorpusWithQuery user cid q (Just limit) (liftBase . log)
+ {- let log' x = do
+ printDebug "addToCorpusWithQuery" x
+ liftBase $ log x
+ -}
)
{-
liftBase $ log x
in New.addToCorpusWithForm user cid i log')
+addCorpusWithFile :: User -> GargServer New.AddWithFile
+addCorpusWithFile user cid =
+ serveJobsAPI $
+ JobFunction (\i log ->
+ let
+ log' x = do
+ printDebug "addToCorpusWithFile" x
+ liftBase $ log x
+ in New.addToCorpusWithFile user cid i log')
+
addAnnuaireWithForm :: GargServer Annuaire.AddWithForm
addAnnuaireWithForm cid =
serveJobsAPI $