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 DataKinds #-}
16 {-# LANGUAGE DeriveGeneric #-}
17 {-# LANGUAGE FlexibleContexts #-}
18 {-# LANGUAGE FlexibleInstances #-}
19 {-# LANGUAGE NoImplicitPrelude #-}
20 {-# LANGUAGE OverloadedStrings #-} -- allows to write Text literals
21 {-# LANGUAGE OverloadedLists #-} -- allows to write Map and HashMap as lists
22 {-# LANGUAGE RankNTypes #-}
23 {-# LANGUAGE TypeOperators #-}
25 module Gargantext.Viz.Graph.API
28 import Control.Lens (set, (^.), _Just, (^?))
30 import Debug.Trace (trace)
31 import qualified Data.HashMap.Lazy as HashMap
32 import qualified Data.Map as Map
33 import Data.Maybe (Maybe(..))
36 import GHC.Generics (Generic)
38 import Servant.Job.Async
40 import qualified Xmlbf as Xmlbf
42 import Gargantext.API.Ngrams (NgramsRepo, r_version)
43 import Gargantext.API.Ngrams.Tools
44 import Gargantext.API.Admin.Orchestrator.Types
45 import Gargantext.API.Admin.Types
46 import Gargantext.Core.Types.Main
47 import Gargantext.Database.Admin.Config
48 import Gargantext.Database.Action.Metrics.NgramsByNode (getNodesByNgramsOnlyUser)
49 import Gargantext.Database.Schema.Ngrams
50 import Gargantext.Database.Action.Query.Node.Select
51 import Gargantext.Database.Action.Query.Node
52 import Gargantext.Database.Action.Query.Node.User
53 import Gargantext.Database.Admin.Types.Errors (HasNodeError)
54 import Gargantext.Database.Admin.Types.Node hiding (node_id) -- (GraphId, ListId, CorpusId, NodeId)
55 import Gargantext.Database.Action.Query.Node.UpdateOpaleye (updateHyperdata)
56 import Gargantext.Database.Admin.Utils (Cmd)
57 import Gargantext.Prelude
58 import qualified Gargantext.Prelude as P
59 import Gargantext.Viz.Graph
60 import qualified Gargantext.Viz.Graph as G
61 import Gargantext.Viz.Graph.Tools -- (cooc2graph)
63 -- Converts to GEXF format
64 -- See https://gephi.org/gexf/format/
65 instance Xmlbf.ToXml Graph where
66 toXml (Graph { _graph_nodes = graphNodes
67 , _graph_edges = graphEdges }) = root graphNodes graphEdges
69 root :: [G.Node] -> [G.Edge] -> [Xmlbf.Node]
71 Xmlbf.element "gexf" params $ meta <> (graph gn ge)
73 params = HashMap.fromList [ ("xmlns", "http://www.gexf.net/1.2draft")
74 , ("version", "1.2") ]
75 meta = Xmlbf.element "meta" params $ creator <> desc
77 params = HashMap.fromList [ ("lastmodifieddate", "2020-03-13") ]
78 creator = Xmlbf.element "creator" HashMap.empty $ Xmlbf.text "Gargantext.org"
79 desc = Xmlbf.element "description" HashMap.empty $ Xmlbf.text "Gargantext gexf file"
80 graph :: [G.Node] -> [G.Edge] -> [Xmlbf.Node]
81 graph gn ge = Xmlbf.element "graph" params $ (nodes gn) <> (edges ge)
83 params = HashMap.fromList [ ("mode", "static")
84 , ("defaultedgetype", "directed") ]
85 nodes :: [G.Node] -> [Xmlbf.Node]
86 nodes gn = Xmlbf.element "nodes" HashMap.empty $ P.concatMap node' gn
88 node' :: G.Node -> [Xmlbf.Node]
89 node' (G.Node { node_id = nId, node_label = l }) =
90 Xmlbf.element "node" params []
92 params = HashMap.fromList [ ("id", nId)
94 edges :: [G.Edge] -> [Xmlbf.Node]
95 edges gn = Xmlbf.element "edges" HashMap.empty $ P.concatMap edge gn
96 edge :: G.Edge -> [Xmlbf.Node]
97 edge (G.Edge { edge_id = eId, edge_source = es, edge_target = et }) =
98 Xmlbf.element "edge" params []
100 params = HashMap.fromList [ ("id", eId)
104 ------------------------------------------------------------------------
106 -- | There is no Delete specific API for Graph since it can be deleted
108 type GraphAPI = Get '[JSON] Graph
109 :<|> Post '[JSON] [GraphId]
111 :<|> "gexf" :> Get '[XML] (Headers '[Servant.Header "Content-Disposition" Text] Graph)
113 :<|> "versions" :> GraphVersionsAPI
116 data GraphVersions = GraphVersions { gv_graph :: Maybe Int
117 , gv_repo :: Int } deriving (Show, Generic)
119 instance ToJSON GraphVersions
120 instance ToSchema GraphVersions
122 graphAPI :: UserId -> NodeId -> GargServer GraphAPI
123 graphAPI u n = getGraph u n
126 :<|> getGraphGexf u n
128 :<|> graphVersionsAPI u n
130 ------------------------------------------------------------------------
132 getGraph :: UserId -> NodeId -> GargNoServer Graph
133 getGraph uId nId = do
134 nodeGraph <- getNodeWith nId HyperdataGraph
135 let graph = nodeGraph ^. node_hyperdata . hyperdataGraph
136 -- let listVersion = graph ^? _Just
143 -- let v = repo ^. r_version
144 nodeUser <- getNodeUser (NodeId uId)
146 let uId' = nodeUser ^. node_userId
148 let cId = maybe (panic "[ERR:G.V.G.API] Node has no parent")
150 $ nodeGraph ^. node_parentId
154 graph' <- computeGraph cId NgramsTerms repo
155 _ <- insertGraph cId uId' (HyperdataGraph $ Just graph')
156 pure $ trace "Graph empty, computing" $ graph'
158 Just graph' -> pure $ trace "Graph exists, returning" $ graph'
160 -- Just graph' -> if listVersion == Just v
163 -- graph'' <- computeGraph cId NgramsTerms repo
164 -- _ <- updateHyperdata nId (HyperdataGraph $ Just graph'')
170 recomputeGraph :: UserId -> NodeId -> GargNoServer Graph
171 recomputeGraph uId nId = do
172 nodeGraph <- getNodeWith nId HyperdataGraph
173 let graph = nodeGraph ^. node_hyperdata . hyperdataGraph
174 let listVersion = graph ^? _Just
181 let v = repo ^. r_version
182 nodeUser <- getNodeUser (NodeId uId)
184 let uId' = nodeUser ^. node_userId
186 let cId = maybe (panic "[ERR:G.V.G.API] Node has no parent")
188 $ nodeGraph ^. node_parentId
192 graph' <- computeGraph cId NgramsTerms repo
193 _ <- insertGraph cId uId' (HyperdataGraph $ Just graph')
194 pure $ trace "[recomputeGraph] Graph empty, computing" $ graph'
196 Just graph' -> if listVersion == Just v
199 graph'' <- computeGraph cId NgramsTerms repo
200 _ <- updateHyperdata nId (HyperdataGraph $ Just graph'')
201 pure $ trace "[recomputeGraph] Graph exists, recomputing" $ graph''
205 -- TODO use Database Monad only here ?
206 computeGraph :: HasNodeError err
211 computeGraph cId nt repo = do
212 lId <- defaultList cId
214 let metadata = GraphMetadata "Title" [cId]
215 [ LegendField 1 "#FFF" "Cluster"
216 , LegendField 2 "#FFF" "Cluster"
218 (ListForGraph lId (repo ^. r_version))
219 -- (map (\n -> LegendField n "#FFFFFF" (pack $ show n)) [1..10])
221 lIds <- selectNodesWithUsername NodeList userMaster
222 let ngs = filterListWithRoot GraphTerm $ mapTermListRoot [lId] nt repo
224 myCooc <- Map.filter (>1)
225 <$> getCoocByNgrams (Diagonal False)
226 <$> groupNodesByNgrams ngs
227 <$> getNodesByNgramsOnlyUser cId (lIds <> [lId]) nt (Map.keys ngs)
229 graph <- liftBase $ cooc2graph 0 myCooc
230 let graph' = set graph_metadata (Just metadata) graph
235 postGraph :: NodeId -> GargServer (Post '[JSON] [NodeId])
236 postGraph = undefined
238 putGraph :: NodeId -> GargServer (Put '[JSON] Int)
242 ------------------------------------------------------------
244 getGraphGexf :: UserId -> NodeId -> GargNoServer (Headers '[Servant.Header "Content-Disposition" Text] Graph)
245 getGraphGexf uId nId = do
246 graph <- getGraph uId nId
247 pure $ addHeader (concat [ "attachment; filename=graph.gexf" ]) graph
249 ------------------------------------------------------------
251 type GraphAsyncAPI = Summary "Update graph"
253 :> AsyncJobsAPI ScraperStatus () ScraperStatus
255 graphAsync :: UserId -> NodeId -> GargServer GraphAsyncAPI
258 JobFunction (\_ log' -> graphAsync' u n (liftBase . log'))
261 graphAsync' :: UserId
263 -> (ScraperStatus -> GargNoServer ())
264 -> GargNoServer ScraperStatus
265 graphAsync' u n logStatus = do
266 logStatus ScraperStatus { _scst_succeeded = Just 0
267 , _scst_failed = Just 0
268 , _scst_remaining = Just 1
269 , _scst_events = Just []
271 _g <- trace (show u) $ recomputeGraph u n
272 pure ScraperStatus { _scst_succeeded = Just 1
273 , _scst_failed = Just 0
274 , _scst_remaining = Just 0
275 , _scst_events = Just []
278 ------------------------------------------------------------
280 type GraphVersionsAPI = Summary "Graph versions"
281 :> Get '[JSON] GraphVersions
282 :<|> Summary "Recompute graph version"
283 :> Post '[JSON] Graph
285 graphVersionsAPI :: UserId -> NodeId -> GargServer GraphVersionsAPI
286 graphVersionsAPI u n =
288 :<|> recomputeVersions u n
290 graphVersions :: UserId -> NodeId -> GargNoServer GraphVersions
291 graphVersions _uId nId = do
292 nodeGraph <- getNodeWith nId HyperdataGraph
293 let graph = nodeGraph ^. node_hyperdata . hyperdataGraph
294 let listVersion = graph ^? _Just
301 let v = repo ^. r_version
303 pure $ GraphVersions { gv_graph = listVersion
306 recomputeVersions :: UserId -> NodeId -> GargNoServer Graph
307 recomputeVersions uId nId = recomputeGraph uId nId