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