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
13 {-# OPTIONS_GHC -fno-warn-name-shadowing -fno-warn-orphans #-}
15 {-# LANGUAGE DataKinds #-}
16 {-# LANGUAGE DeriveGeneric #-}
17 {-# LANGUAGE FlexibleContexts #-}
18 {-# LANGUAGE NoImplicitPrelude #-}
19 {-# LANGUAGE OverloadedStrings #-}
20 {-# LANGUAGE TemplateHaskell #-}
21 {-# LANGUAGE TypeOperators #-}
23 -------------------------------------------------------------------
24 module Gargantext.API.Node
25 ( module Gargantext.API.Node
27 , HyperdataResource(..)
29 , HyperdataDocument(..)
30 , HyperdataDocumentV3(..)
32 -------------------------------------------------------------------
33 import Prelude (Enum, Bounded, minBound, maxBound)
34 import Control.Lens (prism')
35 import Control.Monad.IO.Class (liftIO)
36 import Control.Monad ((>>))
37 --import System.IO (putStrLn, readFile)
39 import Data.Either(Either(Left))
40 import Data.Aeson (FromJSON, ToJSON, Value())
41 --import Data.Text (Text(), pack)
42 import Data.Text (Text())
44 import Data.Time (UTCTime)
46 import Database.PostgreSQL.Simple (Connection)
48 import GHC.Generics (Generic)
51 import Gargantext.Prelude
52 import Gargantext.Database.Types.Node
53 import Gargantext.Database.Node ( runCmd
54 , getNodesWithParentId
55 , getNode, getNodesWith, CorpusId
56 , deleteNode, deleteNodes, mk, JSONB)
57 import qualified Gargantext.Database.Node.Update as U (update, Update(..))
58 import Gargantext.Database.Facet (FacetDoc , runViewDocuments', OrderBy(..)
60 import Gargantext.Database.Tree (treeDB, HasTreeError(..), TreeError(..))
61 import Gargantext.Database.NodeNode (nodesToFavorite, nodesToTrash)
63 import Gargantext.TextFlow
64 import Gargantext.Viz.Graph (Graph)
65 import Gargantext.Core (Lang(..))
66 import Gargantext.Core.Types (Offset, Limit)
67 import Gargantext.Core.Types.Main (Tree, NodeTree)
68 import Gargantext.Text.Terms (TermType(..))
70 import Test.QuickCheck (elements)
71 import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
72 -------------------------------------------------------------------
73 -- | Node API Types management
74 type Roots = Get '[JSON] [Node Value]
75 :<|> Post '[JSON] Int -- TODO
76 :<|> Put '[JSON] Int -- TODO
77 :<|> Delete '[JSON] Int -- TODO
79 type NodesAPI = Delete '[JSON] Int
82 ------------------------------------------------------------------------
83 ------------------------------------------------------------------------
84 data RenameNode = RenameNode { r_name :: Text }
87 instance FromJSON RenameNode
88 instance ToJSON RenameNode
89 instance ToSchema RenameNode
90 instance Arbitrary RenameNode where
91 arbitrary = elements [RenameNode "test"]
93 ------------------------------------------------------------------------
95 data PostNode = PostNode { pn_name :: Text
96 , pn_typename :: NodeType}
99 instance FromJSON PostNode
100 instance ToJSON PostNode
101 instance ToSchema PostNode
102 instance Arbitrary PostNode where
103 arbitrary = elements [PostNode "Node test" NodeCorpus]
105 ------------------------------------------------------------------------
106 type DocsApi = "documents" :> Summary "Docs api"
107 :> ReqBody '[JSON] Documents
108 :> Delete '[JSON] [Int]
110 data Documents = Documents { documents :: [NodeId]}
113 instance FromJSON Documents
114 instance ToJSON Documents
115 instance ToSchema Documents
117 delDocs :: Connection -> CorpusId -> Documents -> Handler [Int]
118 delDocs c cId ds = liftIO $ nodesToTrash c
119 $ map (\n -> (cId, n, True)) $ documents ds
121 ------------------------------------------------------------------------
122 type FavApi = "favorites" :> Summary "Modify statut"
123 :> ReqBody '[JSON] Favorites
125 :<|> Summary "Delete"
126 :> ReqBody '[JSON] Favorites
127 :> Delete '[JSON] [Int]
129 data Favorites = Favorites { favorites :: [NodeId]}
132 instance FromJSON Favorites
133 instance ToJSON Favorites
134 instance ToSchema Favorites
136 putFav :: Connection -> CorpusId -> Favorites -> Handler [Int]
137 putFav c cId fs = liftIO $ nodesToFavorite c
138 $ map (\n -> (cId, n, True)) $ favorites fs
140 delFav :: Connection -> CorpusId -> Favorites -> Handler [Int]
141 delFav c cId fs = liftIO $ nodesToFavorite c
142 $ map (\n -> (cId, n, False)) $ favorites fs
144 favApi :: Connection -> CorpusId -> (Favorites -> Handler [Int])
145 :<|> (Favorites -> Handler [Int])
146 favApi c cId = putFav c cId :<|> delFav c cId
148 ------------------------------------------------------------------------
149 type NodeAPI a = Get '[JSON] (Node a)
150 :<|> "rename" :> Summary " RenameNode Node"
151 :> ReqBody '[JSON] RenameNode
153 :<|> Summary " PostNode Node with ParentId as {id}"
154 :> ReqBody '[JSON] PostNode
155 :> Post '[JSON] [Int]
157 :<|> Delete '[JSON] Int
158 :<|> "children" :> Summary " Summary children"
159 :> QueryParam "type" NodeType
160 :> QueryParam "offset" Int
161 :> QueryParam "limit" Int
162 :> Get '[JSON] [Node a]
163 :<|> Summary " Tabs" :> FacetDocAPI
166 -- TODO: make the NodeId type indexed by `a`, then we no longer need the proxy.
167 nodeAPI :: JSONB a => Connection -> proxy a -> NodeId -> Server (NodeAPI a)
169 = liftIO (getNode conn id p)
171 :<|> postNode conn id
173 :<|> deleteNode' conn id
174 :<|> getNodesWith' conn id p
175 :<|> getTable conn id
176 :<|> getChart conn id
183 --data FacetFormat = Table | Chart
184 data FacetType = Docs | Terms | Sources | Authors | Trash
185 deriving (Generic, Enum, Bounded)
187 instance FromHttpApiData FacetType
189 parseUrlPiece "Docs" = pure Docs
190 parseUrlPiece "Terms" = pure Terms
191 parseUrlPiece "Sources" = pure Sources
192 parseUrlPiece "Authors" = pure Authors
193 parseUrlPiece "Trash" = pure Trash
194 parseUrlPiece _ = Left "Unexpected value of FacetType"
196 instance ToParamSchema FacetType
197 instance ToJSON FacetType
198 instance FromJSON FacetType
199 instance ToSchema FacetType
200 instance Arbitrary FacetType
202 arbitrary = elements [minBound .. maxBound]
204 ------------------------------------------------------------------------
205 type FacetDocAPI = "table"
206 :> Summary " Table data"
207 :> QueryParam "view" FacetType
208 :> QueryParam "offset" Int
209 :> QueryParam "limit" Int
210 :> QueryParam "order" OrderBy
211 :> Get '[JSON] [FacetDoc]
214 :> Summary " Chart data"
215 :> QueryParam "from" UTCTime
216 :> QueryParam "to" UTCTime
217 :> Get '[JSON] [FacetChart]
218 :<|> Summary " Favorites" :> FavApi
219 :<|> Summary " Documents" :> DocsApi
221 -- Depending on the Type of the Node, we could post
222 -- New documents for a corpus
223 -- New map list terms
224 -- :<|> "process" :> MultipartForm MultipartData :> Post '[JSON] Text
226 -- To launch a query and update the corpus
227 -- :<|> "query" :> Capture "string" Text :> Get '[JSON] Text
230 -- | Node API functions
231 roots :: Connection -> Server Roots
232 roots conn = liftIO (putStrLn ( "/user" :: Text) >> getNodesWithParentId 0 Nothing conn)
233 :<|> pure (panic "not implemented yet") -- TODO
234 :<|> pure (panic "not implemented yet") -- TODO
235 :<|> pure (panic "not implemented yet") -- TODO
238 ------------------------------------------------------------------------
239 type GraphAPI = Get '[JSON] Graph
240 graphAPI :: Connection -> NodeId -> Server GraphAPI
241 graphAPI _ _ = liftIO $ textFlow (Mono EN) (Contexts contextText)
242 -- TODO what do we get about the node? to replace contextText
244 -- TODO(orphan): There should be a proper APIError data type with a case TreeError.
245 instance HasTreeError ServantErr where
246 _TreeError = prism' mk (const Nothing) -- Note a prism
248 mk NoRoot = err404 { errBody = "Root node not found" }
249 mk EmptyRoot = err500 { errBody = "Root node should not be empty" }
250 mk TooManyRoots = err500 { errBody = "Too many root nodes" }
252 type TreeAPI = Get '[JSON] (Tree NodeTree)
253 treeAPI :: Connection -> NodeId -> Server TreeAPI
256 ------------------------------------------------------------------------
257 -- | Check if the name is less than 255 char
258 --rename :: Connection -> NodeId -> Rename -> Server NodeAPI
259 rename :: Connection -> NodeId -> RenameNode -> Handler [Int]
260 rename c nId (RenameNode name) = liftIO $ U.update (U.Rename nId name) c
262 nodesAPI :: Connection -> [NodeId] -> Server NodesAPI
263 nodesAPI conn ids = deleteNodes' conn ids
265 getTable :: Connection -> NodeId -> Maybe FacetType
266 -> Maybe Offset -> Maybe Limit
267 -> Maybe OrderBy -> Handler [FacetDoc]
268 getTable c cId ft o l order = liftIO $ case ft of
269 (Just Docs) -> runViewDocuments' c cId False o l order
270 (Just Trash) -> runViewDocuments' c cId True o l order
271 _ -> panic "not implemented"
273 getChart :: Connection -> NodeId -> Maybe UTCTime -> Maybe UTCTime
274 -> Handler [FacetChart]
275 getChart _ _ _ _ = undefined -- TODO
277 postNode :: Connection -> NodeId -> PostNode -> Handler [Int]
278 postNode c pId (PostNode name nt) = liftIO $ mk c nt (Just pId) name
280 putNode :: Connection -> NodeId -> Handler Int
281 putNode = undefined -- TODO
283 deleteNodes' :: Connection -> [NodeId] -> Handler Int
284 deleteNodes' conn ids = liftIO (runCmd conn $ deleteNodes ids)
286 deleteNode' :: Connection -> NodeId -> Handler Int
287 deleteNode' conn id = liftIO (runCmd conn $ deleteNode id)
289 getNodesWith' :: JSONB a => Connection -> NodeId -> proxy a -> Maybe NodeType
290 -> Maybe Int -> Maybe Int -> Handler [Node a]
291 getNodesWith' conn id p nodeType offset limit = liftIO (getNodesWith conn id p nodeType offset limit)
295 query :: Text -> Handler Text
300 -- TODO Is it possible to adapt the function according to iValue input ?
301 --upload :: MultipartData -> Handler Text
302 --upload multipartData = do
304 -- putStrLn "Inputs:"
305 -- forM_ (inputs multipartData) $ \input ->
306 -- putStrLn $ " " <> show (iName input)
307 -- <> " -> " <> show (iValue input)
309 -- forM_ (files multipartData) $ \file -> do
310 -- content <- readFile (fdFilePath file)
311 -- putStrLn $ "Content of " <> show (fdFileName file)
312 -- <> " at " <> fdFilePath file
314 -- pure (pack "Data loaded")