Commit 73bccfaf authored by Alexandre Delanoë's avatar Alexandre Delanoë

Merge branch 'tree-json'

parents 0f0205a3 3be142c7
......@@ -49,7 +49,7 @@ import Gargantext.Database.Facet (FacetDoc, getDocFacet
import Gargantext.TextFlow
import Gargantext.Viz.Graph (Graph)
import Gargantext.Core (Lang(..))
import Gargantext.Core.Types.Main (Tree)
import Gargantext.Core.Types.Main (Tree, NodeTree)
import Gargantext.Text.Terms (TermType(..))
-------------------------------------------------------------------
-------------------------------------------------------------------
......@@ -112,7 +112,7 @@ type GraphAPI = Get '[JSON] Graph
graphAPI :: Connection -> NodeId -> Server GraphAPI
graphAPI _ _ = liftIO $ textFlow (Mono EN) (Contexts contextText)
type TreeAPI = Get '[JSON] (Tree NodeType)
type TreeAPI = Get '[JSON] (Tree NodeTree)
treeAPI :: Connection -> NodeId -> Server TreeAPI
treeAPI _ _ = undefined
......
......@@ -15,18 +15,22 @@ Portability : POSIX
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
------------------------------------------------------------------------
-----------------------------------------------------------------------
module Gargantext.Core.Types.Main where
------------------------------------------------------------------------
import Data.Aeson (FromJSON, ToJSON)
import Data.Aeson (FromJSON, ToJSON, toJSON)
import Data.Aeson as A
import Data.Aeson.TH (deriveJSON)
import Data.Eq (Eq())
import Data.Monoid ((<>))
import Data.Text (Text)
import Data.Swagger
import Gargantext.Database.Types.Node
import Gargantext.Core.Utils.Prefix (unPrefix)
import Gargantext.Prelude
import GHC.Generics (Generic)
......@@ -34,44 +38,45 @@ import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
------------------------------------------------------------------------
-- All the Database is structred like a hierarchical Tree
data Tree a = NodeT a [Tree a]
deriving (Show, Read, Eq, Generic)
instance ToJSON (Tree NodeType)
instance FromJSON (Tree NodeType)
data NodeTree = NodeTree { _nt_name :: Text
, _nt_type :: NodeType
, _nt_id :: Int
} deriving (Show, Read, Generic)
instance ToSchema (Tree NodeType)
instance Arbitrary (Tree NodeType) where
arbitrary = elements [userTree, userTree]
-- data Tree a = NodeT a [Tree a]
-- same as Data.Tree
leafT :: a -> Tree a
leafT x = NodeT x []
$(deriveJSON (unPrefix "_nt_") ''NodeTree)
------------------------------------------------------------------------
-- Garg Network is a network of all Garg nodes
--gargNetwork = undefined
-- | Garg Node is Database Schema Typed as specification
-- gargNode gathers all the Nodes of all users on one Node
gargNode :: [Tree NodeType]
gargNode :: [Tree NodeTree]
gargNode = [userTree]
-- | User Tree simplified
userTree :: Tree NodeType
userTree = NodeT NodeUser [projectTree]
userTree :: Tree NodeTree
userTree = TreeN (NodeTree "user name" NodeUser 1) $
[leafT $ NodeTree "MyPage" UserPage 0] <>
[annuaireTree, projectTree]
-- | Project Tree
projectTree :: Tree NodeType
projectTree = NodeT Project [corpusTree]
projectTree :: Tree NodeTree
projectTree = TreeN (NodeTree "Project CNRS/IMT" Project 2) [corpusTree 10 "A", corpusTree 20 "B"]
type Individu = Document
-- | Corpus Tree
corpusTree :: Tree NodeType
corpusTree = NodeT NodeCorpus ( [ leafT Document ]
<> [ leafT Lists ]
<> [ leafT Metrics ]
<> [ leafT Classification]
annuaireTree :: Tree NodeTree
annuaireTree = TreeN (NodeTree "Annuaire" Annuaire 41) ( [leafT $ NodeTree "IMT" Individu 42]
<> [leafT $ NodeTree "CNRS" Individu 43]
)
corpusTree :: NodeId -> Text -> Tree NodeTree
corpusTree nId t = TreeN (NodeTree ("Corpus " <> t) NodeCorpus nId) ( [ leafT $ NodeTree "Documents" Document (nId +1)]
-- <> [ leafT $ NodeTree "My lists" Lists 5]
-- <> [ leafT (NodeTree "Metrics A" Metrics 6) ]
-- <> [ leafT (NodeTree "Class A" Classification 7)]
)
-- TODO make instances of Nodes
......@@ -92,7 +97,6 @@ data Lists = StopList | MainList | MapList | GroupList
-- | Community Manager Use Case
type Annuaire = NodeCorpus
type Individu = Document
-- | Favorites Node enable Node categorization
type Favorites = Node HyperdataFavorites
......@@ -135,3 +139,24 @@ type ParentId = NodeId
type Limit = Int
type Offset = Int
------------------------------------------------------------------------
-- All the Database is structred like a hierarchical Tree
data Tree a = TreeN a [Tree a]
deriving (Show, Read, Eq, Generic)
instance ToJSON (Tree NodeTree) where
toJSON (TreeN node nodes) =
object ["node" A..= toJSON node, "children" A..= toJSON nodes]
instance FromJSON (Tree NodeTree)
instance ToSchema NodeTree
instance ToSchema (Tree NodeTree)
instance Arbitrary (Tree NodeTree) where
arbitrary = elements [userTree, userTree]
-- data Tree a = NodeT a [Tree a]
-- same as Data.Tree
leafT :: a -> Tree a
leafT x = TreeN x []
......@@ -274,7 +274,7 @@ type NodeCorpus = Node HyperdataCorpus
type Document = Node HyperdataDocument
------------------------------------------------------------------------
data NodeType = NodeUser | Project | Folder | NodeCorpus | Annuaire | Document | UserPage | DocumentCopy | Favorites
data NodeType = NodeUser | Project | Folder | NodeCorpus | Annuaire | Document | Individu | UserPage | DocumentCopy | Favorites
| Classification
| Lists
| Metrics | Occurrences
......
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