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 #-}
15 {-# LANGUAGE NoImplicitPrelude #-}
16 {-# LANGUAGE DataKinds #-}
17 {-# LANGUAGE TemplateHaskell #-}
18 {-# LANGUAGE TypeOperators #-}
19 {-# LANGUAGE OverloadedStrings #-}
21 -------------------------------------------------------------------
22 module Gargantext.API.Node
24 -------------------------------------------------------------------
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.Database.Types.Node
42 import Gargantext.Database.Node ( getNodesWithParentId
43 , getNode, getNodesWith
44 , deleteNode, deleteNodes)
45 import Gargantext.Database.Facet (FacetDoc, getDocFacet
49 import Gargantext.TextFlow
50 import Gargantext.Viz.Graph (Graph)
51 import Gargantext.Core (Lang(..))
52 import Gargantext.Core.Types.Main (Tree, NodeTree)
53 import Gargantext.Text.Terms (TermType(..))
54 -------------------------------------------------------------------
55 -------------------------------------------------------------------
56 -- | Node API Types management
57 type Roots = Get '[JSON] [Node Value]
60 :<|> Delete '[JSON] Int
62 type NodesAPI = Delete '[JSON] Int
64 type NodeAPI = Get '[JSON] (Node Value)
65 :<|> Delete '[JSON] Int
66 :<|> "children" :> Summary " Summary children"
67 :> QueryParam "type" NodeType
68 :> QueryParam "offset" Int
69 :> QueryParam "limit" Int
70 :> Get '[JSON] [Node Value]
71 :<|> "facet" :> Summary " Facet documents"
72 :> "documents" :> FacetDocAPI
73 -- :<|> "facet" :<|> "sources" :<|> FacetSourcesAPI
74 -- :<|> "facet" :<|> "authors" :<|> FacetAuthorsAPI
75 -- :<|> "facet" :<|> "terms" :<|> FacetTermsAPI
77 --data FacetFormat = Table | Chart
78 --data FacetType = Doc | Term | Source | Author
79 --data Facet = Facet Doc Format
82 type FacetDocAPI = "table"
83 :> Summary " Table data"
84 :> QueryParam "offset" Int
85 :> QueryParam "limit" Int
86 :> Get '[JSON] [FacetDoc]
89 :> Summary " Chart data"
90 :> QueryParam "from" UTCTime
91 :> QueryParam "to" UTCTime
92 :> Get '[JSON] [FacetChart]
94 -- Depending on the Type of the Node, we could post
95 -- New documents for a corpus
97 -- :<|> "process" :> MultipartForm MultipartData :> Post '[JSON] Text
99 -- To launch a query and update the corpus
100 -- :<|> "query" :> Capture "string" Text :> Get '[JSON] Text
103 -- | Node API functions
104 roots :: Connection -> Server Roots
105 roots conn = liftIO (putStrLn ( "/user" :: Text) >> getNodesWithParentId conn 0 Nothing)
106 :<|> pure (panic "not implemented yet")
107 :<|> pure (panic "not implemented yet")
108 :<|> pure (panic "not implemented yet")
111 type GraphAPI = Get '[JSON] Graph
112 graphAPI :: Connection -> NodeId -> Server GraphAPI
113 graphAPI _ _ = liftIO $ textFlow (Mono EN) (Contexts contextText)
115 type TreeAPI = Get '[JSON] (Tree NodeTree)
116 treeAPI :: Connection -> NodeId -> Server TreeAPI
117 treeAPI _ _ = undefined
120 nodeAPI :: Connection -> NodeId -> Server NodeAPI
121 nodeAPI conn id = liftIO (putStrLn ("/node" :: Text) >> getNode conn id )
122 :<|> deleteNode' conn id
123 :<|> getNodesWith' conn id
124 :<|> getFacet conn id
125 :<|> getChart conn id
131 nodesAPI :: Connection -> [NodeId] -> Server NodesAPI
132 nodesAPI conn ids = deleteNodes' conn ids
134 deleteNodes' :: Connection -> [NodeId] -> Handler Int
135 deleteNodes' conn ids = liftIO (deleteNodes conn ids)
137 deleteNode' :: Connection -> NodeId -> Handler Int
138 deleteNode' conn id = liftIO (deleteNode conn id)
140 getNodesWith' :: Connection -> NodeId -> Maybe NodeType -> Maybe Int -> Maybe Int
141 -> Handler [Node Value]
142 getNodesWith' conn id nodeType offset limit = liftIO (getNodesWith conn id nodeType offset limit)
145 getFacet :: Connection -> NodeId -> Maybe Int -> Maybe Int
146 -> Handler [FacetDoc]
147 getFacet conn id offset limit = liftIO (putStrLn ( "/facet" :: Text)) >> liftIO (getDocFacet conn NodeCorpus id (Just Document) offset limit)
149 getChart :: Connection -> NodeId -> Maybe UTCTime -> Maybe UTCTime
150 -> Handler [FacetChart]
151 getChart _ _ _ _ = undefined
154 query :: Text -> Handler Text
159 -- TODO Is it possible to adapt the function according to iValue input ?
160 --upload :: MultipartData -> Handler Text
161 --upload multipartData = do
163 -- putStrLn "Inputs:"
164 -- forM_ (inputs multipartData) $ \input ->
165 -- putStrLn $ " " <> show (iName input)
166 -- <> " -> " <> show (iValue input)
168 -- forM_ (files multipartData) $ \file -> do
169 -- content <- readFile (fdFilePath file)
170 -- putStrLn $ "Content of " <> show (fdFileName file)
171 -- <> " at " <> fdFilePath file
173 -- pure (pack "Data loaded")