Commit 81caa483 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[API][DB] Tree NodeTree: done.

parent fbc34579
...@@ -44,6 +44,7 @@ import Gargantext.Database.Node ( getNodesWithParentId ...@@ -44,6 +44,7 @@ import Gargantext.Database.Node ( getNodesWithParentId
, deleteNode, deleteNodes) , deleteNode, deleteNodes)
import Gargantext.Database.Facet (FacetDoc, getDocFacet import Gargantext.Database.Facet (FacetDoc, getDocFacet
,FacetChart) ,FacetChart)
import Gargantext.Database.Tree (treeDB)
-- Graph -- Graph
import Gargantext.TextFlow import Gargantext.TextFlow
...@@ -116,7 +117,7 @@ graphAPI _ _ = liftIO $ textFlow (Mono EN) (Contexts contextText) ...@@ -116,7 +117,7 @@ graphAPI _ _ = liftIO $ textFlow (Mono EN) (Contexts contextText)
type TreeAPI = Get '[JSON] (Tree NodeTree) type TreeAPI = Get '[JSON] (Tree NodeTree)
treeAPI :: Connection -> NodeId -> Server TreeAPI treeAPI :: Connection -> NodeId -> Server TreeAPI
treeAPI _ _ = undefined treeAPI c n = liftIO $ treeDB c n
nodeAPI :: Connection -> NodeId -> Server NodeAPI nodeAPI :: Connection -> NodeId -> Server NodeAPI
......
...@@ -19,18 +19,24 @@ Gargantext's database. ...@@ -19,18 +19,24 @@ Gargantext's database.
module Gargantext.Database.Config module Gargantext.Database.Config
where where
import Data.Text (pack)
import Data.Maybe (fromMaybe) import Data.Text (pack)
import Data.List (lookup) import Data.Tuple.Extra (swap)
import Data.Maybe (fromMaybe)
import Data.List (lookup)
import Gargantext.Database.Types.Node import Gargantext.Database.Types.Node
import Gargantext.Prelude import Gargantext.Prelude
-- | Nodes are typed in the database according to a specific ID -- | Nodes are typed in the database according to a specific ID
-- --
nodeTypeInv :: [(NodeTypeId, NodeType)]
nodeTypeInv = map swap nodeTypes
nodeTypes :: [(NodeType, NodeTypeId)] nodeTypes :: [(NodeType, NodeTypeId)]
nodeTypes = [ (NodeUser , 1) nodeTypes = [ (NodeUser , 1)
, (Folder , 2) , (Folder , 2)
, (NodeCorpus , 3)
, (NodeCorpus , 30) , (NodeCorpus , 30)
, (Annuaire , 31) , (Annuaire , 31)
, (Document , 4) , (Document , 4)
...@@ -65,4 +71,6 @@ nodeTypeId tn = fromMaybe (panic $ pack $ "Typename " <> show tn <> " does not e ...@@ -65,4 +71,6 @@ nodeTypeId tn = fromMaybe (panic $ pack $ "Typename " <> show tn <> " does not e
(lookup tn nodeTypes) (lookup tn nodeTypes)
typeId2node :: NodeTypeId -> NodeType
typeId2node tId = fromMaybe (panic $ pack $ "Type Id " <> show tId <> " does not exist")
(lookup tId nodeTypeInv)
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