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 NoImplicitPrelude #-}
16 {-# LANGUAGE DataKinds #-}
17 {-# LANGUAGE TemplateHaskell #-}
18 {-# LANGUAGE TypeOperators #-}
19 {-# LANGUAGE OverloadedStrings #-}
21 -------------------------------------------------------------------
22 module Gargantext.API.Node
24 -------------------------------------------------------------------
26 import Control.Lens (prism')
27 import Control.Monad.IO.Class (liftIO)
28 import Control.Monad ((>>))
29 --import System.IO (putStrLn, readFile)
31 import Data.Aeson (Value())
32 --import Data.Text (Text(), pack)
33 import Data.Text (Text())
34 import Data.Time (UTCTime)
36 import Database.PostgreSQL.Simple (Connection)
39 -- import Servant.Multipart
41 import Gargantext.Prelude
42 import Gargantext.Database.Types.Node
43 import Gargantext.Database.Node ( getNodesWithParentId
44 , getNode, getNodesWith
45 , deleteNode, deleteNodes)
46 import Gargantext.Database.Facet (FacetDoc, getDocFacet
48 import Gargantext.Database.Tree (treeDB, HasTreeError(..), TreeError(..))
51 import Gargantext.TextFlow
52 import Gargantext.Viz.Graph (Graph)
53 import Gargantext.Core (Lang(..))
54 import Gargantext.Core.Types.Main (Tree, NodeTree)
55 import Gargantext.Text.Terms (TermType(..))
56 -------------------------------------------------------------------
57 -------------------------------------------------------------------
58 -- | Node API Types management
59 type Roots = Get '[JSON] [Node Value]
62 :<|> Delete '[JSON] Int
64 type NodesAPI = Delete '[JSON] Int
66 type NodeAPI = Get '[JSON] (Node Value)
69 :<|> Delete '[JSON] Int
70 :<|> "children" :> Summary " Summary children"
71 :> QueryParam "type" NodeType
72 :> QueryParam "offset" Int
73 :> QueryParam "limit" Int
74 :> Get '[JSON] [Node Value]
75 :<|> "facet" :> Summary " Facet documents"
76 :> "documents" :> FacetDocAPI
77 -- :<|> "facet" :<|> "sources" :<|> FacetSourcesAPI
78 -- :<|> "facet" :<|> "authors" :<|> FacetAuthorsAPI
79 -- :<|> "facet" :<|> "terms" :<|> FacetTermsAPI
81 --data FacetFormat = Table | Chart
82 --data FacetType = Doc | Term | Source | Author
83 --data Facet = Facet Doc Format
86 type FacetDocAPI = "table"
87 :> Summary " Table data"
88 :> QueryParam "offset" Int
89 :> QueryParam "limit" Int
90 :> Get '[JSON] [FacetDoc]
93 :> Summary " Chart data"
94 :> QueryParam "from" UTCTime
95 :> QueryParam "to" UTCTime
96 :> Get '[JSON] [FacetChart]
98 -- Depending on the Type of the Node, we could post
99 -- New documents for a corpus
100 -- New map list terms
101 -- :<|> "process" :> MultipartForm MultipartData :> Post '[JSON] Text
103 -- To launch a query and update the corpus
104 -- :<|> "query" :> Capture "string" Text :> Get '[JSON] Text
107 -- | Node API functions
108 roots :: Connection -> Server Roots
109 roots conn = liftIO (putStrLn ( "/user" :: Text) >> getNodesWithParentId conn 0 Nothing)
110 :<|> pure (panic "not implemented yet")
111 :<|> pure (panic "not implemented yet")
112 :<|> pure (panic "not implemented yet")
115 type GraphAPI = Get '[JSON] Graph
116 graphAPI :: Connection -> NodeId -> Server GraphAPI
117 graphAPI _ _ = liftIO $ textFlow (Mono EN) (Contexts contextText)
119 -- TODO(orphan): There should be a proper APIError data type with a case TreeError.
120 instance HasTreeError ServantErr where
121 _TreeError = prism' mk (const Nothing) -- Note a prism
123 mk NoRoot = err404 { errBody = "Root node not found" }
124 mk EmptyRoot = err500 { errBody = "Root node should not be empty" }
125 mk TooManyRoots = err500 { errBody = "Too many root nodes" }
127 type TreeAPI = Get '[JSON] (Tree NodeTree)
128 treeAPI :: Connection -> NodeId -> Server TreeAPI
131 nodeAPI :: Connection -> NodeId -> Server NodeAPI
132 nodeAPI conn id = liftIO (putStrLn ("/node" :: Text) >> getNode conn id )
133 :<|> postNode conn id
135 :<|> deleteNode' conn id
136 :<|> getNodesWith' conn id
137 :<|> getFacet conn id
138 :<|> getChart conn id
142 nodesAPI :: Connection -> [NodeId] -> Server NodesAPI
143 nodesAPI conn ids = deleteNodes' conn ids
145 postNode :: Connection -> NodeId -> Handler Int
148 putNode :: Connection -> NodeId -> Handler Int
151 deleteNodes' :: Connection -> [NodeId] -> Handler Int
152 deleteNodes' conn ids = liftIO (deleteNodes conn ids)
154 deleteNode' :: Connection -> NodeId -> Handler Int
155 deleteNode' conn id = liftIO (deleteNode conn id)
157 getNodesWith' :: Connection -> NodeId -> Maybe NodeType -> Maybe Int -> Maybe Int
158 -> Handler [Node Value]
159 getNodesWith' conn id nodeType offset limit = liftIO (getNodesWith conn id nodeType offset limit)
162 getFacet :: Connection -> NodeId -> Maybe Int -> Maybe Int
163 -> Handler [FacetDoc]
164 getFacet conn id offset limit = liftIO (putStrLn ( "/facet" :: Text)) >> liftIO (getDocFacet conn NodeCorpus id (Just Document) offset limit)
166 getChart :: Connection -> NodeId -> Maybe UTCTime -> Maybe UTCTime
167 -> Handler [FacetChart]
168 getChart _ _ _ _ = undefined
171 query :: Text -> Handler Text
176 -- TODO Is it possible to adapt the function according to iValue input ?
177 --upload :: MultipartData -> Handler Text
178 --upload multipartData = do
180 -- putStrLn "Inputs:"
181 -- forM_ (inputs multipartData) $ \input ->
182 -- putStrLn $ " " <> show (iName input)
183 -- <> " -> " <> show (iValue input)
185 -- forM_ (files multipartData) $ \file -> do
186 -- content <- readFile (fdFilePath file)
187 -- putStrLn $ "Content of " <> show (fdFileName file)
188 -- <> " at " <> fdFilePath file
190 -- pure (pack "Data loaded")