]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Node.hs
[CLEAN] fix gitignore on cabal files in order to minimize merge/error risks.
[gargantext.git] / src / Gargantext / API / Node.hs
1 {-|
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
8 Portability : POSIX
9
10 Node API
11 -}
12
13 {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
14 {-# LANGUAGE DataKinds #-}
15 {-# LANGUAGE TemplateHaskell #-}
16 {-# LANGUAGE TypeOperators #-}
17 {-# LANGUAGE OverloadedStrings #-}
18
19 -------------------------------------------------------------------
20 module Gargantext.API.Node
21 where
22 -------------------------------------------------------------------
23
24 import System.IO (putStrLn)
25
26 import Control.Monad.IO.Class (liftIO)
27 import Control.Monad ((>>))
28 --import System.IO (putStrLn, readFile)
29
30 -- import Data.Aeson (Value())
31 --import Data.Text (Text(), pack)
32 import Data.Text (Text())
33
34 import Database.PostgreSQL.Simple (Connection)
35
36 import Servant
37 -- import Servant.Multipart
38
39 import Gargantext.Prelude
40 import Gargantext.Types.Node
41 import Gargantext.Database.Node (getNodesWithParentId
42 , getNode, getNodesWith
43 , deleteNode, deleteNodes)
44 import Gargantext.Database.Facet (FacetDoc, getDocFacet)
45
46 -------------------------------------------------------------------
47 -------------------------------------------------------------------
48
49 -- | Node API Types management
50 type Roots = Get '[JSON] [Node HyperdataDocument]
51 :<|> Post '[JSON] Int
52 :<|> Put '[JSON] Int
53 :<|> Delete '[JSON] Int
54
55 type NodesAPI = Delete '[JSON] Int
56
57 type NodeAPI = Get '[JSON] (Node HyperdataDocument)
58 :<|> Delete '[JSON] Int
59
60 :<|> "children" :> Summary " Summary children"
61 :> QueryParam "type" NodeType
62 :> QueryParam "offset" Int
63 :> QueryParam "limit" Int
64 :> Get '[JSON] [Node HyperdataDocument]
65
66
67 :<|> "facet" :> QueryParam "type" NodeType
68 :> QueryParam "offset" Int
69 :> QueryParam "limit" Int
70 :> Get '[JSON] [FacetDoc]
71
72
73 -- Depending on the Type of the Node, we could post
74 -- New documents for a corpus
75 -- New map list terms
76 -- :<|> "process" :> MultipartForm MultipartData :> Post '[JSON] Text
77
78 -- To launch a query and update the corpus
79 -- :<|> "query" :> Capture "string" Text :> Get '[JSON] Text
80
81
82
83 -- | Node API functions
84 roots :: Connection -> Server Roots
85 roots conn = liftIO (putStrLn "Log Needed" >> getNodesWithParentId conn 0 Nothing)
86 :<|> pure (panic "not implemented yet")
87 :<|> pure (panic "not implemented yet")
88 :<|> pure (panic "not implemented yet")
89
90 nodeAPI :: Connection -> NodeId -> Server NodeAPI
91 nodeAPI conn id = liftIO (putStrLn "getNode" >> getNode conn id )
92 :<|> deleteNode' conn id
93 :<|> getNodesWith' conn id
94 :<|> getDocFacet' conn id
95 -- :<|> upload
96 -- :<|> query
97
98 nodesAPI :: Connection -> [NodeId] -> Server NodesAPI
99 nodesAPI conn ids = deleteNodes' conn ids
100
101 deleteNodes' :: Connection -> [NodeId] -> Handler Int
102 deleteNodes' conn ids = liftIO (deleteNodes conn ids)
103
104 deleteNode' :: Connection -> NodeId -> Handler Int
105 deleteNode' conn id = liftIO (deleteNode conn id)
106
107 getNodesWith' :: Connection -> NodeId -> Maybe NodeType -> Maybe Int -> Maybe Int
108 -> Handler [Node HyperdataDocument]
109 getNodesWith' conn id nodeType offset limit = liftIO (getNodesWith conn id nodeType offset limit)
110
111 getDocFacet' :: Connection -> NodeId -> Maybe NodeType -> Maybe Int -> Maybe Int
112 -> Handler [FacetDoc]
113 getDocFacet' conn id nodeType offset limit = liftIO (getDocFacet conn id nodeType offset limit)
114
115 query :: Text -> Handler Text
116 query s = pure s
117
118
119 -- | Upload files
120 -- TODO Is it possible to adapt the function according to iValue input ?
121 --upload :: MultipartData -> Handler Text
122 --upload multipartData = do
123 -- liftIO $ do
124 -- putStrLn "Inputs:"
125 -- forM_ (inputs multipartData) $ \input ->
126 -- putStrLn $ " " <> show (iName input)
127 -- <> " -> " <> show (iValue input)
128 --
129 -- forM_ (files multipartData) $ \file -> do
130 -- content <- readFile (fdFilePath file)
131 -- putStrLn $ "Content of " <> show (fdFileName file)
132 -- <> " at " <> fdFilePath file
133 -- putStrLn content
134 -- pure (pack "Data loaded")
135