]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Node.hs
[FEAT] Sugar to connect to database in REPL.
[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
18 module Gargantext.API.Node
19 where
20
21 import Control.Monad
22 import Control.Monad.IO.Class (liftIO)
23 import Data.Aeson (Value())
24 import Servant
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, FacetDoc)
31 import Gargantext.Database.Node (getNodesWithParentId
32 , getNode, getNodesWith
33 , deleteNode, deleteNodes
34 , getDocFacet)
35
36
37 -- | Node API Types management
38 type Roots = Get '[JSON] [Node Value]
39
40 type NodesAPI = Delete '[JSON] Int
41
42 type NodeAPI = Get '[JSON] (Node Value)
43 :<|> Delete '[JSON] Int
44
45 :<|> "children" :> QueryParam "type" NodeType
46 :> QueryParam "offset" Int
47 :> QueryParam "limit" Int
48 :> Get '[JSON] [Node Value]
49
50
51 :<|> "facetDoc" :> QueryParam "type" NodeType
52 :> QueryParam "offset" Int
53 :> QueryParam "limit" Int
54 :> Get '[JSON] [FacetDoc Value]
55
56
57 -- Depending on the Type of the Node, we could post
58 -- New documents for a corpus
59 -- New map list terms
60 :<|> "process" :> MultipartForm MultipartData :> Post '[JSON] Text
61
62 -- To launch a query and update the corpus
63 :<|> "query" :> Capture "string" Text :> Get '[JSON] Text
64
65
66
67 -- | Node API functions
68 roots :: Connection -> Server Roots
69 roots conn = liftIO (getNodesWithParentId conn 0 Nothing)
70
71 nodeAPI :: Connection -> NodeId -> Server NodeAPI
72 nodeAPI conn id = liftIO (getNode conn id)
73 :<|> deleteNode' conn id
74 :<|> getNodesWith' conn id
75 :<|> getDocFacet' conn id
76 :<|> upload
77 :<|> query
78
79 nodesAPI :: Connection -> [NodeId] -> Server NodesAPI
80 nodesAPI conn ids = deleteNodes' conn ids
81
82 deleteNodes' :: Connection -> [NodeId] -> Handler Int
83 deleteNodes' conn ids = liftIO (deleteNodes conn ids)
84
85 deleteNode' :: Connection -> NodeId -> Handler Int
86 deleteNode' conn id = liftIO (deleteNode conn id)
87
88 getNodesWith' :: Connection -> NodeId -> Maybe NodeType -> Maybe Int -> Maybe Int
89 -> Handler [Node Value]
90 getNodesWith' conn id nodeType offset limit = liftIO (getNodesWith conn id nodeType offset limit)
91
92 getDocFacet' :: Connection -> NodeId -> Maybe NodeType -> Maybe Int -> Maybe Int
93 -> Handler [FacetDoc Value]
94 getDocFacet' conn id nodeType offset limit = liftIO (getDocFacet conn id nodeType offset limit)
95
96 query :: Text -> Handler Text
97 query s = pure s
98
99
100 -- | Upload files
101 -- TODO Is it possible to adapt the function according to iValue input ?
102 upload :: MultipartData -> Handler Text
103 upload multipartData = do
104 liftIO $ do
105 putStrLn "Inputs:"
106 forM_ (inputs multipartData) $ \input ->
107 putStrLn $ " " <> show (iName input)
108 <> " -> " <> show (iValue input)
109
110 forM_ (files multipartData) $ \file -> do
111 content <- readFile (fdFilePath file)
112 putStrLn $ "Content of " <> show (fdFileName file)
113 <> " at " <> fdFilePath file
114 putStrLn content
115 pure (pack "Data loaded")
116