Commit 398223ff authored by Alexandre Delanoë's avatar Alexandre Delanoë

[VIZ.API][FACTO]

parent 73114c78
......@@ -17,44 +17,45 @@ Portability : POSIX
{-# LANGUAGE OverloadedStrings #-} -- allows to write Text literals
{-# LANGUAGE OverloadedLists #-} -- allows to write Map and HashMap as lists
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
module Gargantext.Viz.Graph.API
where
import Control.Monad.IO.Class (liftIO)
import Control.Lens (set)
--import Servant.Job.Utils (swaggerOptions)
import Gargantext.Database.Schema.Ngrams
import Control.Monad.IO.Class (liftIO)
import Gargantext.API.Ngrams.Tools
import Gargantext.API.Types
import Gargantext.Core.Types.Main
import Gargantext.Database.Metrics.NgramsByNode (getNodesByNgramsOnlyUser)
import Gargantext.Database.Schema.Ngrams
import Gargantext.Database.Schema.Node ( getNode)
import Gargantext.Database.Schema.Node (defaultList)
import Gargantext.Database.Types.Node -- (GraphId, ListId, CorpusId, NodeId)
import Gargantext.Prelude
import Gargantext.API.Ngrams.Tools
import Gargantext.Core.Types.Main
import Gargantext.Viz.Graph.Tools -- (cooc2graph)
import Gargantext.Database.Schema.Node (defaultList)
import Gargantext.Viz.Graph
import Gargantext.Viz.Graph.Tools -- (cooc2graph)
import Servant
import qualified Data.Map as Map
{-
getgraph :: GraphId -> GraphView
getgraph _GraphId = phyloView
--getgraph :: GraphId -> Maybe PhyloQueryView -> PhyloView
--getgraph _GraphId _phyloQueryView = phyloView
postgraph :: CorpusId -> Maybe ListId -> GraphQueryBuild -> Phylo
postgraph = undefined
------------------------------------------------------------------------
putgraph :: GraphId -> Maybe ListId -> PhyloQueryBuild -> Phylo
putgraph = undefined
-}
-- | There is no Delete specific API for Graph since it can be deleted
-- as simple Node.
type GraphAPI = Get '[JSON] Graph
:<|> Post '[JSON] [NodeId]
:<|> Put '[JSON] Int
type GraphAPI = Get '[JSON] Graph
graphAPI :: NodeId -> GargServer GraphAPI
graphAPI nId = do
graphAPI n = getGraph n
:<|> postGraph n
:<|> putGraph n
------------------------------------------------------------------------
getGraph :: NodeId -> GargServer (Get '[JSON] Graph)
getGraph nId = do
nodeGraph <- getNode nId HyperdataGraph
let metadata = GraphMetadata "Title" [maybe 0 identity $ _node_parentId nodeGraph]
......@@ -74,5 +75,14 @@ graphAPI nId = do
liftIO $ set graph_metadata (Just metadata) <$> cooc2graph myCooc
postGraph :: NodeId -> GargServer (Post '[JSON] [NodeId])
postGraph = undefined
putGraph :: NodeId -> GargServer (Put '[JSON] Int)
putGraph = undefined
-- | Instances
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