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 #-}
17 {-# LANGUAGE OverloadedStrings #-}
19 -------------------------------------------------------------------
20 module Gargantext.API.Node
22 -------------------------------------------------------------------
24 import System.IO (putStrLn)
26 import Control.Monad.IO.Class (liftIO)
27 import Control.Monad ((>>))
28 --import System.IO (putStrLn, readFile)
30 -- import Data.Aeson (Value())
31 --import Data.Text (Text(), pack)
32 import Data.Text (Text())
33 import Data.Time (UTCTime)
35 import Database.PostgreSQL.Simple (Connection)
38 -- import Servant.Multipart
40 import Gargantext.Prelude
41 import Gargantext.Types.Node
42 import Gargantext.Database.Node ( getNodesWithParentId
43 , getNode, getNodesWith
44 , deleteNode, deleteNodes)
45 import Gargantext.Database.Facet (FacetDoc, getDocFacet
48 -------------------------------------------------------------------
49 -------------------------------------------------------------------
50 -- | Node API Types management
51 type Roots = Get '[JSON] [Node HyperdataDocument]
54 :<|> Delete '[JSON] Int
56 type NodesAPI = Delete '[JSON] Int
58 type NodeAPI = Get '[JSON] (Node HyperdataDocument)
59 :<|> Delete '[JSON] Int
60 :<|> "children" :> Summary " Summary children"
61 :> QueryParam "type" NodeType
62 :> QueryParam "offset" Int
63 :> QueryParam "limit" Int
64 :> Get '[JSON] [Node HyperdataDocument]
65 :<|> "facet" :> "documents" :> FacetDocAPI
66 -- :<|> "facet" :<|> "sources" :<|> FacetSourcesAPI
67 -- :<|> "facet" :<|> "authors" :<|> FacetAuthorsAPI
68 -- :<|> "facet" :<|> "terms" :<|> FacetTermsAPI
70 --data FacetFormat = Table | Chart
71 --data FacetType = Doc | Term | Source | Author
72 --data Facet = Facet Doc Format
75 type FacetDocAPI = "table"
76 :> QueryParam "offset" Int
77 :> QueryParam "limit" Int
78 :> Get '[JSON] [FacetDoc]
81 :> QueryParam "from" UTCTime
82 :> QueryParam "to" UTCTime
83 :> Get '[JSON] [FacetChart]
85 -- Depending on the Type of the Node, we could post
86 -- New documents for a corpus
88 -- :<|> "process" :> MultipartForm MultipartData :> Post '[JSON] Text
90 -- To launch a query and update the corpus
91 -- :<|> "query" :> Capture "string" Text :> Get '[JSON] Text
94 -- | Node API functions
95 roots :: Connection -> Server Roots
96 roots conn = liftIO (putStrLn "Log Needed" >> getNodesWithParentId conn 0 Nothing)
97 :<|> pure (panic "not implemented yet")
98 :<|> pure (panic "not implemented yet")
99 :<|> pure (panic "not implemented yet")
101 nodeAPI :: Connection -> NodeId -> Server NodeAPI
102 nodeAPI conn id = liftIO (putStrLn "getNode" >> getNode conn id )
103 :<|> deleteNode' conn id
104 :<|> getNodesWith' conn id
105 :<|> getFacet conn id
106 :<|> getChart conn id
110 nodesAPI :: Connection -> [NodeId] -> Server NodesAPI
111 nodesAPI conn ids = deleteNodes' conn ids
113 deleteNodes' :: Connection -> [NodeId] -> Handler Int
114 deleteNodes' conn ids = liftIO (deleteNodes conn ids)
116 deleteNode' :: Connection -> NodeId -> Handler Int
117 deleteNode' conn id = liftIO (deleteNode conn id)
119 getNodesWith' :: Connection -> NodeId -> Maybe NodeType -> Maybe Int -> Maybe Int
120 -> Handler [Node HyperdataDocument]
121 getNodesWith' conn id nodeType offset limit = liftIO (getNodesWith conn id nodeType offset limit)
124 getFacet :: Connection -> NodeId -> Maybe Int -> Maybe Int
125 -> Handler [FacetDoc]
126 getFacet conn id offset limit = liftIO (getDocFacet conn id (Just Document) offset limit)
128 getChart :: Connection -> NodeId -> Maybe UTCTime -> Maybe UTCTime
129 -> Handler [FacetChart]
130 getChart _ _ _ _ = undefined
133 query :: Text -> Handler Text
138 -- TODO Is it possible to adapt the function according to iValue input ?
139 --upload :: MultipartData -> Handler Text
140 --upload multipartData = do
142 -- putStrLn "Inputs:"
143 -- forM_ (inputs multipartData) $ \input ->
144 -- putStrLn $ " " <> show (iName input)
145 -- <> " -> " <> show (iValue input)
147 -- forM_ (files multipartData) $ \file -> do
148 -- content <- readFile (fdFilePath file)
149 -- putStrLn $ "Content of " <> show (fdFileName file)
150 -- <> " at " <> fdFilePath file
152 -- pure (pack "Data loaded")