2 Module : Gargantext.Viz.Phylo.Tools
3 Description : Phylomemy Tools to build/manage it
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
13 {-# OPTIONS_GHC -fno-warn-orphans #-}
15 {-# LANGUAGE FlexibleContexts #-}
16 {-# LANGUAGE FlexibleInstances #-}
17 {-# LANGUAGE RankNTypes #-}
18 {-# LANGUAGE NoImplicitPrelude #-}
19 {-# LANGUAGE OverloadedStrings #-} -- allows to write Text literals
20 {-# LANGUAGE OverloadedLists #-} -- allows to write Map and HashMap as lists
21 {-# LANGUAGE DataKinds #-}
22 {-# LANGUAGE TypeOperators #-}
24 module Gargantext.Viz.Graph.API
27 import Debug.Trace (trace)
28 import Control.Lens (set, (^.), _Just, (^?))
29 import Control.Monad.IO.Class (liftIO)
30 import Data.Maybe (Maybe(..))
31 import Gargantext.API.Ngrams (currentVersion)
32 import Gargantext.API.Ngrams.Tools
33 import Gargantext.API.Types
34 import Gargantext.Core.Types.Main
35 import Gargantext.Database.Config
36 import Gargantext.Database.Metrics.NgramsByNode (getNodesByNgramsOnlyUser)
37 import Gargantext.Database.Schema.Ngrams
38 import Gargantext.Database.Node.Select
39 import Gargantext.Database.Schema.Node (getNode, defaultList, insertGraph)
40 import Gargantext.Database.Types.Node hiding (node_id) -- (GraphId, ListId, CorpusId, NodeId)
41 import Gargantext.Database.Node.UpdateOpaleye (updateHyperdata)
42 import Gargantext.Prelude
43 import Gargantext.Viz.Graph
44 import Gargantext.Viz.Graph.Tools -- (cooc2graph)
46 import qualified Data.Map as Map
48 ------------------------------------------------------------------------
50 -- | There is no Delete specific API for Graph since it can be deleted
52 type GraphAPI = Get '[JSON] Graph
53 :<|> Post '[JSON] [GraphId]
57 graphAPI :: UserId -> NodeId -> GargServer GraphAPI
58 graphAPI u n = getGraph u n
62 ------------------------------------------------------------------------
64 getGraph :: UserId -> NodeId -> GargServer (Get '[JSON] Graph)
66 nodeGraph <- getNode nId HyperdataGraph
67 let graph = nodeGraph ^. node_hyperdata . hyperdataGraph
68 let graphVersion = graph ^? _Just
74 nodeUser <- getNode (NodeId uId) HyperdataUser
76 let uId' = nodeUser ^. node_userId
78 let cId = maybe (panic "[ERR:G.V.G.API] Node has no parent")
80 $ nodeGraph ^. node_parentId
84 graph' <- computeGraph cId NgramsTerms v
85 _ <- insertGraph cId uId' (HyperdataGraph $ Just graph')
88 Just graph' -> if graphVersion == Just v
91 graph'' <- computeGraph cId NgramsTerms v
92 _ <- updateHyperdata nId (HyperdataGraph $ Just graph'')
94 pure $ trace ("salut" <> show g) $ g
97 -- TODO use Database Monad only here ?
98 computeGraph :: CorpusId -> NgramsType -> Int -> GargServer (Get '[JSON] Graph)
99 computeGraph cId nt v = do
100 lId <- defaultList cId
102 let metadata = GraphMetadata "Title" [cId]
103 [ LegendField 1 "#FFF" "Cluster"
104 , LegendField 2 "#FFF" "Cluster"
108 -- (map (\n -> LegendField n "#FFFFFF" (pack $ show n)) [1..10])
110 lIds <- selectNodesWithUsername NodeList userMaster
111 ngs <- filterListWithRoot GraphTerm <$> mapTermListRoot [lId] nt
113 myCooc <- Map.filter (>1)
114 <$> getCoocByNgrams (Diagonal True)
115 <$> groupNodesByNgrams ngs
116 <$> getNodesByNgramsOnlyUser cId (lIds <> [lId]) nt (Map.keys ngs)
118 graph <- liftIO $ cooc2graph 0 myCooc
119 let graph' = set graph_metadata (Just metadata) graph
124 postGraph :: NodeId -> GargServer (Post '[JSON] [NodeId])
125 postGraph = undefined
127 putGraph :: NodeId -> GargServer (Put '[JSON] Int)