Commit 99e95bb1 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[REST] Tree api.

parent 2487bd75
...@@ -116,6 +116,7 @@ library: ...@@ -116,6 +116,7 @@ library:
- protolude - protolude
- pureMD5 - pureMD5
- SHA - SHA
- rake
- regex-compat - regex-compat
- resourcet - resourcet
- safe - safe
......
...@@ -68,7 +68,8 @@ import Gargantext.API.FrontEnd (FrontEndAPI, frontEndServer) ...@@ -68,7 +68,8 @@ import Gargantext.API.FrontEnd (FrontEndAPI, frontEndServer)
import Gargantext.API.Node ( Roots , roots import Gargantext.API.Node ( Roots , roots
, NodeAPI , nodeAPI , NodeAPI , nodeAPI
, NodesAPI , nodesAPI , NodesAPI , nodesAPI
, GraphAPI, graphAPI , GraphAPI , graphAPI
, TreeAPI , treeAPI
) )
import Gargantext.API.Count ( CountAPI, count, Query) import Gargantext.API.Count ( CountAPI, count, Query)
import Gargantext.API.Search ( SearchAPI, search, SearchQuery) import Gargantext.API.Search ( SearchAPI, search, SearchQuery)
...@@ -219,6 +220,11 @@ type GargAPI = ...@@ -219,6 +220,11 @@ type GargAPI =
:<|> "graph" :> Summary "Graph endpoint" :<|> "graph" :> Summary "Graph endpoint"
:> Capture "id" Int :> GraphAPI :> Capture "id" Int :> GraphAPI
-- Tree endpoint
:<|> "tree" :> Summary "Tree endpoint"
:> Capture "id" Int :> TreeAPI
-- :<|> "scraper" :> WithCallbacks ScraperAPI -- :<|> "scraper" :> WithCallbacks ScraperAPI
...@@ -245,8 +251,9 @@ server env = do ...@@ -245,8 +251,9 @@ server env = do
:<|> nodeAPI conn :<|> nodeAPI conn
:<|> nodesAPI conn :<|> nodesAPI conn
:<|> count :<|> count
:<|> search conn :<|> search conn
:<|> graphAPI conn :<|> graphAPI conn
:<|> treeAPI conn
-- :<|> orchestrator -- :<|> orchestrator
where where
conn = env ^. env_conn conn = env ^. env_conn
......
...@@ -49,6 +49,7 @@ import Gargantext.Database.Facet (FacetDoc, getDocFacet ...@@ -49,6 +49,7 @@ import Gargantext.Database.Facet (FacetDoc, getDocFacet
import Gargantext.TextFlow import Gargantext.TextFlow
import Gargantext.Viz.Graph (Graph) import Gargantext.Viz.Graph (Graph)
import Gargantext.Core (Lang(..)) import Gargantext.Core (Lang(..))
import Gargantext.Core.Types.Main (Tree)
import Gargantext.Text.Terms (TermType(..)) import Gargantext.Text.Terms (TermType(..))
------------------------------------------------------------------- -------------------------------------------------------------------
------------------------------------------------------------------- -------------------------------------------------------------------
...@@ -111,6 +112,10 @@ type GraphAPI = Get '[JSON] Graph ...@@ -111,6 +112,10 @@ type GraphAPI = Get '[JSON] Graph
graphAPI :: Connection -> NodeId -> Server GraphAPI graphAPI :: Connection -> NodeId -> Server GraphAPI
graphAPI _ _ = liftIO $ textFlow (Mono EN) (Contexts contextText) graphAPI _ _ = liftIO $ textFlow (Mono EN) (Contexts contextText)
type TreeAPI = Get '[JSON] (Tree NodeType)
treeAPI :: Connection -> NodeId -> Server TreeAPI
treeAPI _ _ = undefined
nodeAPI :: Connection -> NodeId -> Server NodeAPI nodeAPI :: Connection -> NodeId -> Server NodeAPI
nodeAPI conn id = liftIO (putStrLn ("/node" :: Text) >> getNode conn id ) nodeAPI conn id = liftIO (putStrLn ("/node" :: Text) >> getNode conn id )
......
...@@ -20,17 +20,30 @@ Portability : POSIX ...@@ -20,17 +20,30 @@ Portability : POSIX
module Gargantext.Core.Types.Main where module Gargantext.Core.Types.Main where
------------------------------------------------------------------------ ------------------------------------------------------------------------
import Data.Aeson (FromJSON, ToJSON)
import Data.Eq (Eq()) import Data.Eq (Eq())
import Data.Monoid ((<>)) import Data.Monoid ((<>))
import Data.Text (Text) import Data.Text (Text)
import Data.Swagger
import Gargantext.Database.Types.Node import Gargantext.Database.Types.Node
import Gargantext.Prelude import Gargantext.Prelude
import GHC.Generics (Generic)
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- All the Database is structred like a hierarchical Tree -- All the Database is structred like a hierarchical Tree
data Tree a = NodeT a [Tree a] data Tree a = NodeT a [Tree a]
deriving (Show, Read, Eq) deriving (Show, Read, Eq, Generic)
instance ToJSON (Tree NodeType)
instance FromJSON (Tree NodeType)
instance ToSchema (Tree NodeType)
instance Arbitrary (Tree NodeType) where
arbitrary = elements [userTree, userTree]
-- data Tree a = NodeT a [Tree a] -- data Tree a = NodeT a [Tree a]
-- same as Data.Tree -- same as Data.Tree
......
...@@ -58,8 +58,9 @@ AMS, and by SIAM. ...@@ -58,8 +58,9 @@ AMS, and by SIAM.
-} -}
{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE FlexibleContexts #-}
module Gargantext.Database.Bashql ( get module Gargantext.Database.Bashql ( get, get'
, ls , ls' , ls , ls'
, home, home' , home, home'
, post, post' , post, post'
...@@ -69,16 +70,19 @@ module Gargantext.Database.Bashql ( get ...@@ -69,16 +70,19 @@ module Gargantext.Database.Bashql ( get
) )
where where
import Gargantext.Core.Types import Control.Monad.Reader -- (Reader, ask)
import Gargantext.Database.Utils (connectGargandb)
import Gargantext.Database.Node
import Gargantext.Prelude
import Database.PostgreSQL.Simple (Connection) import Database.PostgreSQL.Simple (Connection)
import Data.Text (Text, pack) import Data.Text (Text, pack)
import Opaleye hiding (FromField)
import Data.Aeson import Data.Aeson
import Data.List (last, concat) import Data.List (last, concat)
import Gargantext.Core.Types
import Gargantext.Database.Utils (connectGargandb)
import Gargantext.Database.Node
import Gargantext.Prelude
import Opaleye hiding (FromField)
--type UserId = Int --type UserId = Int
--type NodeId = Int --type NodeId = Int
...@@ -100,9 +104,10 @@ home c = map node_id <$> getNodesWithParentId c 0 Nothing ...@@ -100,9 +104,10 @@ home c = map node_id <$> getNodesWithParentId c 0 Nothing
ls :: Connection -> PWD -> IO [Node Value] ls :: Connection -> PWD -> IO [Node Value]
ls = get ls = get
tree :: Connection -> PWD -> IO [Node Value] tree :: Connection -> PWD -> IO [Node Value]
tree c p = do tree c p = do
ns <- get c p ns <- get c p
children <- mapM (\p' -> get c [p']) $ map node_id ns children <- mapM (\p' -> get c [p']) $ map node_id ns
pure $ ns <> (concat children) pure $ ns <> (concat children)
...@@ -140,11 +145,24 @@ del c ns = deleteNodes c ns ...@@ -140,11 +145,24 @@ del c ns = deleteNodes c ns
-- Tests -- Tests
-------------------------------------------------------------- --------------------------------------------------------------
get' :: PWD -> Reader Connection (IO [Node Value])
get' [] = pure $ pure []
get' pwd = do
connection <- ask
pure $ runQuery connection $ selectNodesWithParentID (last pwd)
home' :: IO PWD home' :: IO PWD
home' = do home' = do
c <- connectGargandb "gargantext.ini" c <- connectGargandb "gargantext.ini"
home c home c
--home'' :: Reader Connection (IO PWD)
--home'' = do
-- c <- ask
-- liftIO $ home c
ls' :: IO [Node Value] ls' :: IO [Node Value]
ls' = do ls' = do
c <- connectGargandb "gargantext.ini" c <- connectGargandb "gargantext.ini"
...@@ -203,3 +221,4 @@ del' ns = do ...@@ -203,3 +221,4 @@ del' ns = do
del c ns del c ns
-- corporaOf :: Username -> IO [Corpus]
...@@ -66,4 +66,3 @@ nodeTypeId tn = fromMaybe (panic $ pack $ "Typename " <> show tn <> " does not e ...@@ -66,4 +66,3 @@ nodeTypeId tn = fromMaybe (panic $ pack $ "Typename " <> show tn <> " does not e
...@@ -27,6 +27,7 @@ extra-deps: ...@@ -27,6 +27,7 @@ extra-deps:
- kmeans-vector-0.3.2 - kmeans-vector-0.3.2
- probable-0.1.3 - probable-0.1.3
- protolude-0.2 - protolude-0.2
- rake-0.0.1
- servant-0.13 - servant-0.13
- servant-auth-0.3.0.1 - servant-auth-0.3.0.1
- servant-client-0.13 - servant-client-0.13
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment