]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Node.hs
[FIX] masterListId bug, make it simple finally.
[gargantext.git] / src / Gargantext / API / Node.hs
1 {-|
2 Module : Gargantext.API.Node
3 Description : Server API
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
8 Portability : POSIX
9
10 Node API
11 -}
12
13 {-# OPTIONS_GHC -fno-warn-name-shadowing -fno-warn-orphans #-}
14
15 {-# LANGUAGE DataKinds #-}
16 {-# LANGUAGE DeriveGeneric #-}
17 {-# LANGUAGE FlexibleContexts #-}
18 {-# LANGUAGE NoImplicitPrelude #-}
19 {-# LANGUAGE OverloadedStrings #-}
20 {-# LANGUAGE TemplateHaskell #-}
21 {-# LANGUAGE TypeOperators #-}
22
23 -------------------------------------------------------------------
24 module Gargantext.API.Node
25 ( module Gargantext.API.Node
26 , HyperdataAny(..)
27 , HyperdataAnnuaire(..)
28 , HyperdataCorpus(..)
29 , HyperdataResource(..)
30 , HyperdataUser(..)
31 , HyperdataDocument(..)
32 , HyperdataDocumentV3(..)
33 ) where
34 -------------------------------------------------------------------
35 import Control.Lens (prism')
36 import Control.Monad.IO.Class (liftIO)
37 import Control.Monad ((>>))
38 --import System.IO (putStrLn, readFile)
39
40 import Data.Aeson (FromJSON, ToJSON)
41 --import Data.Text (Text(), pack)
42 import Data.Text (Text())
43 import Data.Swagger
44 import Data.Time (UTCTime)
45
46 import Database.PostgreSQL.Simple (Connection)
47
48 import GHC.Generics (Generic)
49 import Servant
50
51 import Gargantext.API.Ngrams (TabType(..), TableNgramsApi, TableNgramsApiGet,tableNgramsPatch, getTableNgrams, NgramsIdPatchsFeed, NgramsIdPatchsBack, NgramsTable)
52 import Gargantext.Prelude
53 import Gargantext.Database.Types.Node
54 import Gargantext.Database.Node ( runCmd
55 , getNodesWithParentId
56 , getNode, getNodesWith
57 , deleteNode, deleteNodes, mk, JSONB)
58 import qualified Gargantext.Database.Node.Update as U (update, Update(..))
59 import Gargantext.Database.Facet (FacetDoc , runViewDocuments', OrderBy(..)
60 ,FacetChart)
61 import Gargantext.Database.Tree (treeDB, HasTreeError(..), TreeError(..))
62 import Gargantext.Database.NodeNode (nodesToFavorite, nodesToTrash)
63 -- Graph
64 --import Gargantext.Text.Flow
65 import Gargantext.Viz.Graph (Graph,readGraphFromJson,defaultGraph)
66 -- import Gargantext.Core (Lang(..))
67 import Gargantext.Core.Types (Offset, Limit)
68 import Gargantext.Core.Types.Main (Tree, NodeTree, ListId, CorpusId)
69 -- import Gargantext.Text.Terms (TermType(..))
70
71 import Test.QuickCheck (elements)
72 import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
73
74 -------------------------------------------------------------------
75 -- | TODO : access by admin only
76 type NodesAPI = Delete '[JSON] Int
77
78 -- | Delete Nodes
79 -- Be careful: really delete nodes
80 -- Access by admin only
81 nodesAPI :: Connection -> [NodeId] -> Server NodesAPI
82 nodesAPI conn ids = deleteNodes' conn ids
83
84 ------------------------------------------------------------------------
85 -- | TODO: access by admin only
86 -- To manager the Users roots
87 type Roots = Get '[JSON] [NodeAny]
88 :<|> Post '[JSON] Int -- TODO
89 :<|> Put '[JSON] Int -- TODO
90 :<|> Delete '[JSON] Int -- TODO
91
92 -- | TODO: access by admin only
93 roots :: Connection -> Server Roots
94 roots conn = liftIO (putStrLn ( "/user" :: Text) >> getNodesWithParentId 0 Nothing conn)
95 :<|> pure (panic "not implemented yet") -- TODO
96 :<|> pure (panic "not implemented yet") -- TODO
97 :<|> pure (panic "not implemented yet") -- TODO
98
99 -------------------------------------------------------------------
100 -- | Node API Types management
101 -- TODO : access by users
102 type NodeAPI a = Get '[JSON] (Node a)
103 :<|> "rename" :> RenameApi
104 :<|> PostNodeApi
105 :<|> Put '[JSON] Int
106 :<|> Delete '[JSON] Int
107 :<|> "children" :> ChildrenApi a
108
109 -- TODO gather it
110 :<|> "table" :> TableApi
111 :<|> "list" :> TableNgramsApi
112 :<|> "listGet" :> TableNgramsApiGet
113
114 :<|> "chart" :> ChartApi
115 :<|> "favorites" :> FavApi
116 :<|> "documents" :> DocsApi
117
118 type RenameApi = Summary " RenameNode Node"
119 :> ReqBody '[JSON] RenameNode
120 :> Put '[JSON] [Int]
121
122 type PostNodeApi = Summary " PostNode Node with ParentId as {id}"
123 :> ReqBody '[JSON] PostNode
124 :> Post '[JSON] [Int]
125
126 type ChildrenApi a = Summary " Summary children"
127 :> QueryParam "type" NodeType
128 :> QueryParam "offset" Int
129 :> QueryParam "limit" Int
130 :> Get '[JSON] [Node a]
131 ------------------------------------------------------------------------
132 -- TODO: make the NodeId type indexed by `a`, then we no longer need the proxy.
133 nodeAPI :: JSONB a => Connection -> proxy a -> NodeId -> Server (NodeAPI a)
134 nodeAPI conn p id
135 = liftIO (getNode conn id p)
136 :<|> rename conn id
137 :<|> postNode conn id
138 :<|> putNode conn id
139 :<|> deleteNode' conn id
140 :<|> getNodesWith' conn id p
141
142 -- TODO gather it
143 :<|> getTable conn id
144 :<|> tableNgramsPatch' conn id
145 :<|> getTableNgrams' conn id
146
147 :<|> getChart conn id
148 :<|> favApi conn id
149 :<|> delDocs conn id
150 -- Annuaire
151 -- :<|> upload
152 -- :<|> query
153 ------------------------------------------------------------------------
154 data RenameNode = RenameNode { r_name :: Text }
155 deriving (Generic)
156
157 instance FromJSON RenameNode
158 instance ToJSON RenameNode
159 instance ToSchema RenameNode
160 instance Arbitrary RenameNode where
161 arbitrary = elements [RenameNode "test"]
162 ------------------------------------------------------------------------
163 data PostNode = PostNode { pn_name :: Text
164 , pn_typename :: NodeType}
165 deriving (Generic)
166
167 instance FromJSON PostNode
168 instance ToJSON PostNode
169 instance ToSchema PostNode
170 instance Arbitrary PostNode where
171 arbitrary = elements [PostNode "Node test" NodeCorpus]
172
173 ------------------------------------------------------------------------
174 type DocsApi = Summary "Docs : Move to trash"
175 :> ReqBody '[JSON] Documents
176 :> Delete '[JSON] [Int]
177
178 data Documents = Documents { documents :: [NodeId]}
179 deriving (Generic)
180
181 instance FromJSON Documents
182 instance ToJSON Documents
183 instance ToSchema Documents
184
185 delDocs :: Connection -> CorpusId -> Documents -> Handler [Int]
186 delDocs c cId ds = liftIO $ nodesToTrash c
187 $ map (\n -> (cId, n, True)) $ documents ds
188
189 ------------------------------------------------------------------------
190 type FavApi = Summary " Favorites label"
191 :> ReqBody '[JSON] Favorites
192 :> Put '[JSON] [Int]
193 :<|> Summary " Favorites unlabel"
194 :> ReqBody '[JSON] Favorites
195 :> Delete '[JSON] [Int]
196
197 data Favorites = Favorites { favorites :: [NodeId]}
198 deriving (Generic)
199
200 instance FromJSON Favorites
201 instance ToJSON Favorites
202 instance ToSchema Favorites
203
204 putFav :: Connection -> CorpusId -> Favorites -> Handler [Int]
205 putFav c cId fs = liftIO $ nodesToFavorite c
206 $ map (\n -> (cId, n, True)) $ favorites fs
207
208 delFav :: Connection -> CorpusId -> Favorites -> Handler [Int]
209 delFav c cId fs = liftIO $ nodesToFavorite c
210 $ map (\n -> (cId, n, False)) $ favorites fs
211
212 favApi :: Connection -> CorpusId -> (Favorites -> Handler [Int])
213 :<|> (Favorites -> Handler [Int])
214 favApi c cId = putFav c cId :<|> delFav c cId
215
216 ------------------------------------------------------------------------
217 type TableApi = Summary " Table API"
218 :> QueryParam "view" TabType
219 :> QueryParam "offset" Int
220 :> QueryParam "limit" Int
221 :> QueryParam "order" OrderBy
222 :> Get '[JSON] [FacetDoc]
223
224 ------------------------------------------------------------------------
225 type ChartApi = Summary " Chart API"
226 :> QueryParam "from" UTCTime
227 :> QueryParam "to" UTCTime
228 :> Get '[JSON] [FacetChart]
229
230 -- Depending on the Type of the Node, we could post
231 -- New documents for a corpus
232 -- New map list terms
233 -- :<|> "process" :> MultipartForm MultipartData :> Post '[JSON] Text
234
235 -- To launch a query and update the corpus
236 -- :<|> "query" :> Capture "string" Text :> Get '[JSON] Text
237
238 ------------------------------------------------------------------------
239 type GraphAPI = Get '[JSON] Graph
240 graphAPI :: Connection -> NodeId -> Server GraphAPI
241 graphAPI _ _ = do
242 liftIO $ maybe defaultGraph identity <$> readGraphFromJson "purescript-gargantext/dist/examples/imtNew.json"
243 -- t <- textFlow (Mono EN) (Contexts contextText)
244 -- liftIO $ liftIO $ pure $ maybe t identity maybeGraph
245 -- TODO what do we get about the node? to replace contextText
246
247 -- TODO(orphan): There should be a proper APIError data type with a case TreeError.
248 instance HasTreeError ServantErr where
249 _TreeError = prism' mk (const Nothing) -- Note a prism
250 where
251 mk NoRoot = err404 { errBody = "Root node not found" }
252 mk EmptyRoot = err500 { errBody = "Root node should not be empty" }
253 mk TooManyRoots = err500 { errBody = "Too many root nodes" }
254
255 type TreeAPI = Get '[JSON] (Tree NodeTree)
256 treeAPI :: Connection -> NodeId -> Server TreeAPI
257 treeAPI = treeDB
258
259 ------------------------------------------------------------------------
260 -- | Check if the name is less than 255 char
261 rename :: Connection -> NodeId -> RenameNode -> Handler [Int]
262 rename c nId (RenameNode name) = liftIO $ U.update (U.Rename nId name) c
263
264 getTable :: Connection -> NodeId -> Maybe TabType
265 -> Maybe Offset -> Maybe Limit
266 -> Maybe OrderBy -> Handler [FacetDoc]
267 getTable c cId ft o l order = liftIO $ case ft of
268 (Just Docs) -> runViewDocuments' c cId False o l order
269 (Just Trash) -> runViewDocuments' c cId True o l order
270 _ -> panic "not implemented"
271
272 getChart :: Connection -> NodeId -> Maybe UTCTime -> Maybe UTCTime
273 -> Handler [FacetChart]
274 getChart _ _ _ _ = undefined -- TODO
275
276 postNode :: Connection -> NodeId -> PostNode -> Handler [Int]
277 postNode c pId (PostNode name nt) = liftIO $ mk c nt (Just pId) name
278
279 putNode :: Connection -> NodeId -> Handler Int
280 putNode = undefined -- TODO
281
282 deleteNodes' :: Connection -> [NodeId] -> Handler Int
283 deleteNodes' conn ids = liftIO (runCmd conn $ deleteNodes ids)
284
285 deleteNode' :: Connection -> NodeId -> Handler Int
286 deleteNode' conn id = liftIO (runCmd conn $ deleteNode id)
287
288 getNodesWith' :: JSONB a => Connection -> NodeId -> proxy a -> Maybe NodeType
289 -> Maybe Int -> Maybe Int -> Handler [Node a]
290 getNodesWith' conn id p nodeType offset limit = liftIO (getNodesWith conn id p nodeType offset limit)
291
292 tableNgramsPatch' :: Connection -> CorpusId -> Maybe ListId -> NgramsIdPatchsFeed -> Handler NgramsIdPatchsBack
293 tableNgramsPatch' c cId mL ns = liftIO $ tableNgramsPatch c cId mL ns
294
295 getTableNgrams' :: Connection -> CorpusId -> Maybe TabType -> Maybe ListId -> Handler NgramsTable
296 getTableNgrams' c cId nType mL = liftIO $ getTableNgrams c cId nType mL
297
298 query :: Text -> Handler Text
299 query s = pure s
300
301
302 -- | Upload files
303 -- TODO Is it possible to adapt the function according to iValue input ?
304 --upload :: MultipartData -> Handler Text
305 --upload multipartData = do
306 -- liftIO $ do
307 -- putStrLn "Inputs:"
308 -- forM_ (inputs multipartData) $ \input ->
309 -- putStrLn $ " " <> show (iName input)
310 -- <> " -> " <> show (iValue input)
311 --
312 -- forM_ (files multipartData) $ \file -> do
313 -- content <- readFile (fdFilePath file)
314 -- putStrLn $ "Content of " <> show (fdFileName file)
315 -- <> " at " <> fdFilePath file
316 -- putStrLn content
317 -- pure (pack "Data loaded")
318