]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Node.hs
[DB][FLOW] fix duplicate ngrams insertion.
[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, CorpusId
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)
66 import Gargantext.Core (Lang(..))
67 import Gargantext.Core.Types (Offset, Limit)
68 import Gargantext.Core.Types.Main (Tree, NodeTree, ListId)
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 -- :<|> upload
151 -- :<|> query
152 ------------------------------------------------------------------------
153 data RenameNode = RenameNode { r_name :: Text }
154 deriving (Generic)
155
156 instance FromJSON RenameNode
157 instance ToJSON RenameNode
158 instance ToSchema RenameNode
159 instance Arbitrary RenameNode where
160 arbitrary = elements [RenameNode "test"]
161 ------------------------------------------------------------------------
162 data PostNode = PostNode { pn_name :: Text
163 , pn_typename :: NodeType}
164 deriving (Generic)
165
166 instance FromJSON PostNode
167 instance ToJSON PostNode
168 instance ToSchema PostNode
169 instance Arbitrary PostNode where
170 arbitrary = elements [PostNode "Node test" NodeCorpus]
171
172 ------------------------------------------------------------------------
173 type DocsApi = Summary "Docs : Move to trash"
174 :> ReqBody '[JSON] Documents
175 :> Delete '[JSON] [Int]
176
177 data Documents = Documents { documents :: [NodeId]}
178 deriving (Generic)
179
180 instance FromJSON Documents
181 instance ToJSON Documents
182 instance ToSchema Documents
183
184 delDocs :: Connection -> CorpusId -> Documents -> Handler [Int]
185 delDocs c cId ds = liftIO $ nodesToTrash c
186 $ map (\n -> (cId, n, True)) $ documents ds
187
188 ------------------------------------------------------------------------
189 type FavApi = Summary " Favorites label"
190 :> ReqBody '[JSON] Favorites
191 :> Put '[JSON] [Int]
192 :<|> Summary " Favorites unlabel"
193 :> ReqBody '[JSON] Favorites
194 :> Delete '[JSON] [Int]
195
196 data Favorites = Favorites { favorites :: [NodeId]}
197 deriving (Generic)
198
199 instance FromJSON Favorites
200 instance ToJSON Favorites
201 instance ToSchema Favorites
202
203 putFav :: Connection -> CorpusId -> Favorites -> Handler [Int]
204 putFav c cId fs = liftIO $ nodesToFavorite c
205 $ map (\n -> (cId, n, True)) $ favorites fs
206
207 delFav :: Connection -> CorpusId -> Favorites -> Handler [Int]
208 delFav c cId fs = liftIO $ nodesToFavorite c
209 $ map (\n -> (cId, n, False)) $ favorites fs
210
211 favApi :: Connection -> CorpusId -> (Favorites -> Handler [Int])
212 :<|> (Favorites -> Handler [Int])
213 favApi c cId = putFav c cId :<|> delFav c cId
214
215 ------------------------------------------------------------------------
216 type TableApi = Summary " Table API"
217 :> QueryParam "view" TabType
218 :> QueryParam "offset" Int
219 :> QueryParam "limit" Int
220 :> QueryParam "order" OrderBy
221 :> Get '[JSON] [FacetDoc]
222
223 ------------------------------------------------------------------------
224 type ChartApi = Summary " Chart API"
225 :> QueryParam "from" UTCTime
226 :> QueryParam "to" UTCTime
227 :> Get '[JSON] [FacetChart]
228
229 -- Depending on the Type of the Node, we could post
230 -- New documents for a corpus
231 -- New map list terms
232 -- :<|> "process" :> MultipartForm MultipartData :> Post '[JSON] Text
233
234 -- To launch a query and update the corpus
235 -- :<|> "query" :> Capture "string" Text :> Get '[JSON] Text
236
237 ------------------------------------------------------------------------
238 type GraphAPI = Get '[JSON] Graph
239 graphAPI :: Connection -> NodeId -> Server GraphAPI
240 graphAPI _ _ = liftIO $ textFlow (Mono EN) (Contexts contextText)
241 -- TODO what do we get about the node? to replace contextText
242
243 -- TODO(orphan): There should be a proper APIError data type with a case TreeError.
244 instance HasTreeError ServantErr where
245 _TreeError = prism' mk (const Nothing) -- Note a prism
246 where
247 mk NoRoot = err404 { errBody = "Root node not found" }
248 mk EmptyRoot = err500 { errBody = "Root node should not be empty" }
249 mk TooManyRoots = err500 { errBody = "Too many root nodes" }
250
251 type TreeAPI = Get '[JSON] (Tree NodeTree)
252 treeAPI :: Connection -> NodeId -> Server TreeAPI
253 treeAPI = treeDB
254
255 ------------------------------------------------------------------------
256 -- | Check if the name is less than 255 char
257 rename :: Connection -> NodeId -> RenameNode -> Handler [Int]
258 rename c nId (RenameNode name) = liftIO $ U.update (U.Rename nId name) c
259
260 getTable :: Connection -> NodeId -> Maybe TabType
261 -> Maybe Offset -> Maybe Limit
262 -> Maybe OrderBy -> Handler [FacetDoc]
263 getTable c cId ft o l order = liftIO $ case ft of
264 (Just Docs) -> runViewDocuments' c cId False o l order
265 (Just Trash) -> runViewDocuments' c cId True o l order
266 _ -> panic "not implemented"
267
268 getChart :: Connection -> NodeId -> Maybe UTCTime -> Maybe UTCTime
269 -> Handler [FacetChart]
270 getChart _ _ _ _ = undefined -- TODO
271
272 postNode :: Connection -> NodeId -> PostNode -> Handler [Int]
273 postNode c pId (PostNode name nt) = liftIO $ mk c nt (Just pId) name
274
275 putNode :: Connection -> NodeId -> Handler Int
276 putNode = undefined -- TODO
277
278 deleteNodes' :: Connection -> [NodeId] -> Handler Int
279 deleteNodes' conn ids = liftIO (runCmd conn $ deleteNodes ids)
280
281 deleteNode' :: Connection -> NodeId -> Handler Int
282 deleteNode' conn id = liftIO (runCmd conn $ deleteNode id)
283
284 getNodesWith' :: JSONB a => Connection -> NodeId -> proxy a -> Maybe NodeType
285 -> Maybe Int -> Maybe Int -> Handler [Node a]
286 getNodesWith' conn id p nodeType offset limit = liftIO (getNodesWith conn id p nodeType offset limit)
287
288 tableNgramsPatch' :: Connection -> CorpusId -> Maybe ListId -> NgramsIdPatchsFeed -> Handler NgramsIdPatchsBack
289 tableNgramsPatch' c cId mL ns = liftIO $ tableNgramsPatch c cId mL ns
290
291 getTableNgrams' :: Connection -> CorpusId -> Maybe TabType -> Maybe ListId -> Handler NgramsTable
292 getTableNgrams' c cId nType mL = liftIO $ getTableNgrams c cId nType mL
293
294 query :: Text -> Handler Text
295 query s = pure s
296
297
298 -- | Upload files
299 -- TODO Is it possible to adapt the function according to iValue input ?
300 --upload :: MultipartData -> Handler Text
301 --upload multipartData = do
302 -- liftIO $ do
303 -- putStrLn "Inputs:"
304 -- forM_ (inputs multipartData) $ \input ->
305 -- putStrLn $ " " <> show (iName input)
306 -- <> " -> " <> show (iValue input)
307 --
308 -- forM_ (files multipartData) $ \file -> do
309 -- content <- readFile (fdFilePath file)
310 -- putStrLn $ "Content of " <> show (fdFileName file)
311 -- <> " at " <> fdFilePath file
312 -- putStrLn content
313 -- pure (pack "Data loaded")
314