2 Module : Gargantext.Core.Viz.Graph
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
12 {-# LANGUAGE BangPatterns #-}
13 {-# LANGUAGE OverloadedLists #-} -- allows to write Map and HashMap as lists
14 {-# LANGUAGE TypeOperators #-}
16 module Gargantext.Core.Viz.Graph.API
19 import Control.Lens (set, (^.), _Just, (^?), at)
21 import Data.Maybe (fromMaybe)
23 import Data.Text hiding (head)
24 import Debug.Trace (trace)
25 import GHC.Generics (Generic)
26 import Gargantext.API.Admin.EnvTypes (GargJob(..), Env)
27 import Gargantext.API.Admin.Orchestrator.Types
28 import Gargantext.API.Ngrams.Tools
29 import Gargantext.API.Prelude
30 import Gargantext.Core.Methods.Similarities (Similarity(..), GraphMetric(..), withMetric)
31 import Gargantext.Core.NodeStory
32 import Gargantext.Core.Types.Main
33 import Gargantext.Core.Viz.Graph.GEXF ()
34 import Gargantext.Core.Viz.Graph.Tools -- (cooc2graph)
35 import Gargantext.Core.Viz.Graph.Types
36 import Gargantext.Database.Action.Metrics.NgramsByContext (getContextsByNgramsOnlyUser)
37 import Gargantext.Database.Action.Flow.Types (FlowCmdM)
38 import Gargantext.Database.Action.Node (mkNodeWithParent)
39 import Gargantext.Database.Admin.Config
40 import Gargantext.Database.Admin.Types.Node
41 import Gargantext.Database.Prelude (Cmd)
42 import Gargantext.Database.Query.Table.Node
43 import Gargantext.Database.Query.Table.Node.Error (HasNodeError)
44 import Gargantext.Database.Query.Table.Node.Select
45 import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata)
46 import Gargantext.Database.Query.Table.Node.User (getNodeUser)
47 import Gargantext.Database.Schema.Node
48 import Gargantext.Database.Schema.Ngrams
49 import Gargantext.Prelude
50 import Gargantext.Utils.Jobs (serveJobsAPI)
52 import Servant.Job.Async (AsyncJobsAPI)
54 import qualified Data.HashMap.Strict as HashMap
56 ------------------------------------------------------------------------
57 -- | There is no Delete specific API for Graph since it can be deleted
59 type GraphAPI = Get '[JSON] HyperdataGraphAPI
60 :<|> "async" :> GraphAsyncAPI
62 :> ReqBody '[JSON] HyperdataGraphAPI
63 :> Post '[JSON] NodeId
64 :<|> "gexf" :> Get '[XML] (Headers '[Servant.Header "Content-Disposition" Text] Graph)
65 :<|> "versions" :> GraphVersionsAPI
68 GraphVersions { gv_graph :: Maybe Int
71 deriving (Show, Generic)
73 instance FromJSON GraphVersions
74 instance ToJSON GraphVersions
75 instance ToSchema GraphVersions
77 graphAPI :: UserId -> NodeId -> ServerT GraphAPI (GargM Env GargError)
78 graphAPI u n = getGraph u n
82 :<|> graphVersionsAPI u n
84 ------------------------------------------------------------------------
85 --getGraph :: UserId -> NodeId -> GargServer HyperdataGraphAPI
86 getGraph :: FlowCmdM env err m
89 -> m HyperdataGraphAPI
90 getGraph _uId nId = do
91 nodeGraph <- getNodeWith nId (Proxy :: Proxy HyperdataGraph)
94 graph = nodeGraph ^. node_hyperdata . hyperdataGraph
95 camera = nodeGraph ^. node_hyperdata . hyperdataCamera
97 mcId <- getClosestParentIdByType nId NodeCorpus
98 let cId = maybe (panic "[G.V.G.API] Node has no parent") identity mcId
100 -- printDebug "[getGraph] getting list for cId" cId
101 listId <- defaultList cId
102 repo <- getRepo [listId]
104 -- TODO Similarity in Graph params
107 let defaultMetric = Order1
108 let defaultPartitionMethod = Spinglass
109 let defaultEdgesStrength = Strong
110 let defaultBridgenessMethod = BridgenessMethod_Basic
111 graph' <- computeGraph cId defaultPartitionMethod defaultBridgenessMethod (withMetric defaultMetric) defaultEdgesStrength (NgramsTerms, NgramsTerms) repo
112 mt <- defaultGraphMetadata cId "Title" repo defaultMetric defaultEdgesStrength
114 graph'' = set graph_metadata (Just mt) graph'
115 hg = HyperdataGraphAPI graph'' camera
116 -- _ <- updateHyperdata nId hg
117 _ <- updateHyperdata nId (HyperdataGraph (Just graph'') camera)
118 pure $ trace "[G.V.G.API] Graph empty, computing" hg
120 Just graph' -> pure $ trace "[G.V.G.API] Graph exists, returning" $
121 HyperdataGraphAPI graph' camera
124 --recomputeGraph :: UserId -> NodeId -> Maybe GraphMetric -> GargNoServer Graph
125 recomputeGraph :: FlowCmdM env err m
136 recomputeGraph _uId nId partitionMethod bridgeMethod maybeSimilarity maybeStrength nt1 nt2 force = do
137 nodeGraph <- getNodeWith nId (Proxy :: Proxy HyperdataGraph)
139 graph = nodeGraph ^. node_hyperdata . hyperdataGraph
140 camera = nodeGraph ^. node_hyperdata . hyperdataCamera
141 graphMetadata = graph ^? _Just . graph_metadata . _Just
142 listVersion = graph ^? _Just . graph_metadata . _Just . gm_list . lfg_version
143 graphMetric = case maybeSimilarity of
144 Nothing -> graph ^? _Just . graph_metadata . _Just . gm_metric
146 similarity = case graphMetric of
147 Nothing -> withMetric Order1
148 Just m -> withMetric m
150 strength = case maybeStrength of
151 Nothing -> case graph ^? _Just . graph_metadata . _Just . gm_edgesStrength of
153 Just mr -> fromMaybe Strong mr
156 mcId <- getClosestParentIdByType nId NodeCorpus
157 let cId = maybe (panic "[G.V.G.API] Node has no parent") identity mcId
159 listId <- defaultList cId
160 repo <- getRepo [listId]
161 let v = repo ^. unNodeStory . at listId . _Just . a_version
164 !g <- computeGraph cId partitionMethod bridgeMethod similarity strength (nt1,nt2) repo
165 let g' = set graph_metadata mt g
166 _nentries <- updateHyperdata nId (HyperdataGraph (Just g') camera)
171 mt <- defaultGraphMetadata cId "Title" repo (fromMaybe Order1 maybeSimilarity) strength
172 g <- computeG $ Just mt
173 pure $ trace "[G.V.G.API.recomputeGraph] Graph empty, computed" g
174 Just graph' -> if (listVersion == Just v) && (not force)
177 g <- computeG graphMetadata
178 pure $ trace "[G.V.G.API] Graph exists, recomputing" g
182 computeGraph :: FlowCmdM env err m
188 -> (NgramsType, NgramsType)
191 computeGraph corpusId partitionMethod bridgeMethod similarity strength (nt1,nt2) repo = do
192 -- Getting the Node parameters
193 lId <- defaultList corpusId
194 lIds <- selectNodesWithUsername NodeList userMaster
196 -- Getting the Ngrams to compute with and grouping it according to the lists
198 groupedContextsByNgrams nt corpusId' (lists_master, lists_user) = do
200 ngs = filterListWithRoot [MapTerm] $ mapTermListRoot lists_user nt repo
201 groupNodesByNgrams ngs <$> getContextsByNgramsOnlyUser corpusId'
202 (lists_user <> lists_master) nt (HashMap.keys ngs)
204 -- Optim if nt1 == nt2 : do not compute twice
206 m1 <- groupedContextsByNgrams nt1 corpusId (lIds, [lId])
211 m2 <- groupedContextsByNgrams nt2 corpusId (lIds, [lId])
214 -- Removing the hapax (ngrams with 1 cooc)
215 let !myCooc = {- HashMap.filter (>0)
216 $ -} getCoocByNgrams'' (Diagonal True) (identity, identity) (m1,m2)
218 -- TODO MultiPartite Here
220 $ cooc2graphWith partitionMethod bridgeMethod (MultiPartite (Partite (HashMap.keysSet m1) nt1)
221 (Partite (HashMap.keysSet m2) nt2)
223 similarity 0 strength myCooc
229 defaultGraphMetadata :: HasNodeError err
235 -> Cmd err GraphMetadata
236 defaultGraphMetadata cId t repo gm str = do
237 lId <- defaultList cId
239 pure $ GraphMetadata { _gm_title = t
241 , _gm_edgesStrength = Just str
242 , _gm_corpusId = [cId]
244 LegendField 1 "#FFF" "Cluster1"
245 , LegendField 2 "#FFF" "Cluster2"
246 , LegendField 3 "#FFF" "Cluster3"
247 , LegendField 4 "#FFF" "Cluster4"
249 , _gm_list = (ListForGraph lId (repo ^. unNodeStory . at lId . _Just . a_version))
250 , _gm_startForceAtlas = True
252 -- (map (\n -> LegendField n "#FFFFFF" (pack $ show n)) [1..10])
254 ------------------------------------------------------------
255 type GraphAsyncAPI = Summary "Recompute graph"
257 :> AsyncJobsAPI JobLog () JobLog
260 graphAsync :: UserId -> NodeId -> ServerT GraphAsyncAPI (GargM Env GargError)
262 serveJobsAPI RecomputeGraphJob $ \_ log' ->
263 graphRecompute u n (liftBase . log')
266 --graphRecompute :: UserId
268 -- -> (JobLog -> GargNoServer ())
269 -- -> GargNoServer JobLog
270 -- TODO get Graph Metadata to recompute
271 graphRecompute :: FlowCmdM env err m
276 graphRecompute u n logStatus = do
277 logStatus JobLog { _scst_succeeded = Just 0
278 , _scst_failed = Just 0
279 , _scst_remaining = Just 1
280 , _scst_events = Just []
282 _g <- recomputeGraph u n Spinglass BridgenessMethod_Basic Nothing Nothing NgramsTerms NgramsTerms False
283 pure JobLog { _scst_succeeded = Just 1
284 , _scst_failed = Just 0
285 , _scst_remaining = Just 0
286 , _scst_events = Just []
289 ------------------------------------------------------------
290 type GraphVersionsAPI = Summary "Graph versions"
291 :> Get '[JSON] GraphVersions
292 :<|> Summary "Recompute graph version"
293 :> Post '[JSON] Graph
295 graphVersionsAPI :: UserId -> NodeId -> GargServer GraphVersionsAPI
296 graphVersionsAPI u n =
298 :<|> recomputeVersions u n
300 graphVersions :: Int -> NodeId -> GargNoServer GraphVersions
301 graphVersions n nId = do
302 nodeGraph <- getNodeWith nId (Proxy :: Proxy HyperdataGraph)
315 mcId <- getClosestParentIdByType nId NodeCorpus
316 let cId = maybe (panic "[G.V.G.API] Node has no parent") identity mcId
318 maybeListId <- defaultListMaybe cId
321 then graphVersions (n+1) cId
322 else panic "[G.V.G.API] list not found after iterations"
325 repo <- getRepo [listId]
326 let v = repo ^. unNodeStory . at listId . _Just . a_version
327 -- printDebug "graphVersions" v
329 pure $ GraphVersions { gv_graph = listVersion
332 --recomputeVersions :: UserId -> NodeId -> GargNoServer Graph
333 recomputeVersions :: FlowCmdM env err m
337 recomputeVersions uId nId = recomputeGraph uId nId Spinglass BridgenessMethod_Basic Nothing Nothing NgramsTerms NgramsTerms False
339 ------------------------------------------------------------
343 -> GargNoServer NodeId
344 graphClone uId pId (HyperdataGraphAPI { _hyperdataAPIGraph = graph
345 , _hyperdataAPICamera = camera }) = do
346 let nodeType = NodeGraph
347 nodeUser <- getNodeUser (NodeId uId)
348 nodeParent <- getNodeWith pId (Proxy :: Proxy HyperdataGraph)
349 let uId' = nodeUser ^. node_user_id
350 nIds <- mkNodeWithParent nodeType (Just pId) uId' $ nodeParent ^. node_name
355 let graphP' = set (graph_metadata . _Just . gm_startForceAtlas) False graphP
357 _ <- updateHyperdata nId (HyperdataGraph (Just graphP') camera)
361 ------------------------------------------------------------
362 --getGraphGexf :: UserId
364 -- -> GargNoServer (Headers '[Servant.Header "Content-Disposition" Text] Graph)
365 getGraphGexf :: FlowCmdM env err m
368 -> m (Headers '[Servant.Header "Content-Disposition" Text] Graph)
369 getGraphGexf uId nId = do
370 HyperdataGraphAPI { _hyperdataAPIGraph = graph } <- getGraph uId nId
371 pure $ addHeader "attachment; filename=graph.gexf" graph