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 #-}
14 {-# LANGUAGE DataKinds #-}
15 {-# LANGUAGE TemplateHaskell #-}
16 {-# LANGUAGE TypeOperators #-}
18 module Gargantext.API.Node
22 import Control.Monad.IO.Class (liftIO)
23 import Data.Aeson (Value())
25 import Servant.Multipart
26 import System.IO (putStrLn, readFile)
27 import Data.Text (Text(), pack)
28 import Database.PostgreSQL.Simple (Connection)
29 import Gargantext.Prelude
30 import Gargantext.Types.Main (Node, NodeId, NodeType)
31 import Gargantext.Database.Node (getNodesWithParentId
32 , getNode, getNodesWith
33 , deleteNode, deleteNodes)
36 -- | Node API Types management
37 type Roots = Get '[JSON] [Node Value]
39 type NodesAPI = Delete '[JSON] Int
41 type NodeAPI = Get '[JSON] (Node Value)
42 :<|> Delete '[JSON] Int
44 -- Example for Document Facet view, to populate the tabular:
45 -- http://localhost:8008/node/347476/children?type=Document&limit=3
46 -- /!\ FIXME : nodeType is case sensitive
47 -- /!\ see NodeTypes in Types/Main.hs
48 :<|> "children" :> QueryParam "type" NodeType
49 :> QueryParam "offset" Int
50 :> QueryParam "limit" Int
51 :> Get '[JSON] [Node Value]
53 -- Depending on the Type of the Node, we could post
54 -- New documents for a corpus
56 :<|> "process" :> MultipartForm MultipartData :> Post '[JSON] Text
58 -- To launch a query and update the corpus
59 :<|> "query" :> Capture "string" Text :> Get '[JSON] Text
63 -- | Node API functions
64 roots :: Connection -> Server Roots
65 roots conn = liftIO (getNodesWithParentId conn 0 Nothing)
67 nodeAPI :: Connection -> NodeId -> Server NodeAPI
68 nodeAPI conn id = liftIO (getNode conn id)
69 :<|> deleteNode' conn id
70 :<|> getNodesWith' conn id
74 nodesAPI :: Connection -> [NodeId] -> Server NodesAPI
75 nodesAPI conn ids = deleteNodes' conn ids
77 deleteNodes' :: Connection -> [NodeId] -> Handler Int
78 deleteNodes' conn ids = liftIO (deleteNodes conn ids)
80 deleteNode' :: Connection -> NodeId -> Handler Int
81 deleteNode' conn id = liftIO (deleteNode conn id)
83 getNodesWith' :: Connection -> NodeId -> Maybe NodeType -> Maybe Int -> Maybe Int
84 -> Handler [Node Value]
85 getNodesWith' conn id nodeType offset limit = liftIO (getNodesWith conn id nodeType offset limit)
88 query :: Text -> Handler Text
93 -- TODO Is it possible to adapt the function according to iValue input ?
94 upload :: MultipartData -> Handler Text
95 upload multipartData = do
98 forM_ (inputs multipartData) $ \input ->
99 putStrLn $ " " <> show (iName input)
100 <> " -> " <> show (iValue input)
102 forM_ (files multipartData) $ \file -> do
103 content <- readFile (fdFilePath file)
104 putStrLn $ "Content of " <> show (fdFileName file)
105 <> " at " <> fdFilePath file
107 pure (pack "Data loaded")