2 Module : Gargantext.API.Routes
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
12 {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
14 {-# LANGUAGE ConstraintKinds #-}
15 {-# LANGUAGE TemplateHaskell #-}
16 {-# LANGUAGE TypeOperators #-}
17 {-# LANGUAGE KindSignatures #-}
18 {-# LANGUAGE ScopedTypeVariables #-}
19 {-# LANGUAGE TypeFamilies #-}
21 ---------------------------------------------------------------------
22 module Gargantext.API.Routes
24 ---------------------------------------------------------------------
26 -- import qualified Gargantext.API.Search as Search
27 import Control.Concurrent (threadDelay)
28 import Control.Lens (view)
29 import Data.Text (Text)
31 import Gargantext.API.Admin.Auth (AuthRequest, AuthResponse, AuthenticatedUser(..), withAccess, PathId(..))
32 import Gargantext.API.Admin.FrontEnd (FrontEndAPI)
33 import Gargantext.API.Count (CountAPI, count, Query)
34 import Gargantext.API.Ngrams (TableNgramsApi, apiNgramsTableDoc)
35 import Gargantext.API.Node
36 import Gargantext.API.Prelude
37 import Gargantext.Core.Types.Individu (User(..))
38 import Gargantext.Core.Viz.Graph.API
39 import Gargantext.Database.Prelude (HasConfig(..))
40 import Gargantext.Database.Admin.Types.Hyperdata
41 import Gargantext.Database.Admin.Types.Node
42 import Gargantext.Prelude
43 import Gargantext.Prelude.Config (gc_max_docs_scrapers)
45 import Servant.Auth as SA
46 import Servant.Auth.Swagger ()
47 import Servant.Job.Async
48 import Servant.Swagger.UI
49 import qualified Gargantext.API.Ngrams.List as List
50 import qualified Gargantext.API.Node.Contact as Contact
51 import qualified Gargantext.API.Node.Corpus.Annuaire as Annuaire
52 import qualified Gargantext.API.Node.Corpus.Export as Export
53 import qualified Gargantext.API.Node.Corpus.New as New
54 import qualified Gargantext.API.Public as Public
56 type GargAPI = "api" :> Summary "API " :> GargAPIVersion
57 -- | TODO :<|> Summary "Latest API" :> GargAPI'
59 type GargAPIVersion = "v1.0"
60 :> Summary "Garg API Version "
63 type GargVersion = "version"
64 :> Summary "Backend version"
69 "auth" :> Summary "AUTH API"
70 :> ReqBody '[JSON] AuthRequest
71 :> Post '[JSON] AuthResponse
73 -- TODO-ACCESS here we want to request a particular header for
74 -- auth and capabilities.
76 :<|> "public" :> Public.API
79 type GargPrivateAPI = SA.Auth '[SA.JWT, SA.Cookie] AuthenticatedUser
84 = "user" :> Summary "First user endpoint"
86 :<|> "nodes" :> Summary "Nodes endpoint"
87 :> ReqBody '[JSON] [NodeId] :> NodesAPI
89 type GargPrivateAPI' =
93 :<|> "node" :> Summary "Node endpoint"
94 :> Capture "node_id" NodeId
95 :> NodeAPI HyperdataAny
98 :<|> "corpus" :> Summary "Corpus endpoint"
99 :> Capture "corpus_id" CorpusId
100 :> NodeAPI HyperdataCorpus
102 :<|> "corpus" :> Summary "Corpus endpoint"
103 :> Capture "node1_id" NodeId
105 :> Capture "node2_id" NodeId
106 :> NodeNodeAPI HyperdataAny
108 :<|> "corpus" :> Capture "node_id" CorpusId
112 :<|> "annuaire" :> Summary "Annuaire endpoint"
113 :> Capture "annuaire_id" AnnuaireId
114 :> NodeAPI HyperdataAnnuaire
116 :<|> "annuaire" :> Summary "Contact endpoint"
117 :> Capture "annuaire_id" NodeId
121 :<|> "document" :> Summary "Document endpoint"
122 :> Capture "doc_id" DocId
126 -- :<|> "counts" :> Stream GET NewLineFraming '[JSON] Count :> CountAPI
128 :<|> "count" :> Summary "Count endpoint"
129 :> ReqBody '[JSON] Query
132 -- Corpus endpoint --> TODO rename s/search/filter/g
133 -- :<|> "search" :> Capture "corpus" NodeId
134 -- :> (Search.API Search.SearchResult)
136 -- TODO move to NodeAPI?
137 :<|> "graph" :> Summary "Graph endpoint"
138 :> Capture "graph_id" NodeId
141 -- TODO move to NodeAPI?
143 :<|> "tree" :> Summary "Tree endpoint"
144 :> Capture "tree_id" NodeId
150 :<|> New.AddWithQuery
152 -- :<|> "annuaire" :> Annuaire.AddWithForm
153 -- :<|> New.AddWithFile
154 -- :<|> "scraper" :> WithCallbacks ScraperAPI
155 -- :<|> "new" :> New.Api
157 :<|> "lists" :> Summary "List export API"
158 :> Capture "listId" ListId
161 :<|> "wait" :> Summary "Wait test"
163 :> WaitAPI -- Get '[JSON] Int
169 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
170 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
171 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
172 ---------------------------------------------------------------------
174 type API = SwaggerAPI
178 -- | API for serving @swagger.json@
179 type SwaggerAPI = SwaggerSchemaUI "swagger-ui" "swagger.json"
181 -- | API for serving main operational routes of @gargantext.org@
187 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
188 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
189 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
190 ---------------------------------------------------------------------
192 ---------------------------------------------------------------------
193 -- | Server declarations
195 -- TODO-SECURITY admin only: withAdmin
196 -- Question: How do we mark admins?
197 serverGargAdminAPI :: GargServer GargAdminAPI
198 serverGargAdminAPI = roots
202 serverPrivateGargAPI' :: AuthenticatedUser -> GargServer GargPrivateAPI'
203 serverPrivateGargAPI' (AuthenticatedUser (NodeId uid))
205 :<|> nodeAPI (Proxy :: Proxy HyperdataAny) uid
206 :<|> nodeAPI (Proxy :: Proxy HyperdataCorpus) uid
207 :<|> nodeNodeAPI (Proxy :: Proxy HyperdataAny) uid
208 :<|> Export.getCorpus -- uid
209 :<|> nodeAPI (Proxy :: Proxy HyperdataAnnuaire) uid
212 :<|> withAccess (Proxy :: Proxy TableNgramsApi) Proxy uid
213 <$> PathNode <*> apiNgramsTableDoc
215 :<|> count -- TODO: undefined
217 -- :<|> withAccess (Proxy :: Proxy (Search.API Search.SearchResult)) Proxy uid
218 -- <$> PathNode <*> Search.api -- TODO: move elsewhere
220 :<|> withAccess (Proxy :: Proxy GraphAPI) Proxy uid
221 <$> PathNode <*> graphAPI uid -- TODO: mock
223 :<|> withAccess (Proxy :: Proxy TreeAPI) Proxy uid
224 <$> PathNode <*> treeAPI
226 :<|> addCorpusWithForm (RootId (NodeId uid))
227 :<|> addCorpusWithFile (RootId (NodeId uid))
228 :<|> addCorpusWithQuery (RootId (NodeId uid))
230 -- :<|> addAnnuaireWithForm
231 -- :<|> New.api uid -- TODO-SECURITY
232 -- :<|> New.info uid -- TODO-SECURITY
237 ----------------------------------------------------------------------
239 type WaitAPI = Get '[JSON] Text
241 waitAPI :: Int -> GargServer WaitAPI
244 m = (10 :: Int) ^ (6 :: Int)
245 _ <- liftBase $ threadDelay ( m * n)
246 pure $ "Waited: " <> (cs $ show n)
247 ----------------------------------------
249 addCorpusWithQuery :: User -> GargServer New.AddWithQuery
250 addCorpusWithQuery user cid =
252 JobFunction (\q log -> do
253 limit <- view $ config . gc_max_docs_scrapers
254 New.addToCorpusWithQuery user cid q (Just limit) (liftBase . log)
256 printDebug "addToCorpusWithQuery" x
262 addWithFile :: GargServer New.AddWithFile
263 addWithFile cid i f =
265 JobFunction (\_i log -> New.addToCorpusWithFile cid i f (liftBase . log))
268 addCorpusWithForm :: User -> GargServer New.AddWithForm
269 addCorpusWithForm user cid =
271 JobFunction (\i log ->
274 printDebug "addToCorpusWithForm" x
276 in New.addToCorpusWithForm user cid i log')
278 addCorpusWithFile :: User -> GargServer New.AddWithFile
279 addCorpusWithFile user cid =
281 JobFunction (\i log ->
284 printDebug "addToCorpusWithFile" x
286 in New.addToCorpusWithFile user cid i log')
288 addAnnuaireWithForm :: GargServer Annuaire.AddWithForm
289 addAnnuaireWithForm cid =
291 JobFunction (\i log -> Annuaire.addToAnnuaireWithForm cid i (liftBase . log))