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 OverloadedLists #-} -- allows to write Map and HashMap as lists
13 {-# LANGUAGE TypeOperators #-}
15 module Gargantext.Core.Viz.Graph.API
18 import Control.Lens (set, (^.), _Just, (^?), at)
20 import Data.Maybe (fromMaybe)
22 import Data.Text hiding (head)
23 import Debug.Trace (trace)
24 import GHC.Generics (Generic)
25 import Gargantext.API.Admin.Orchestrator.Types
26 import Gargantext.API.Ngrams.Tools
27 import Gargantext.API.Prelude
28 import Gargantext.Core.Methods.Distances (Distance(..), GraphMetric(..), withMetric)
29 import Gargantext.Core.NodeStory
30 import Gargantext.Core.Types.Main
31 import Gargantext.Core.Viz.Graph
32 import Gargantext.Core.Viz.Graph.GEXF ()
33 import Gargantext.Core.Viz.Graph.Tools -- (cooc2graph)
34 import Gargantext.Database.Action.Metrics.NgramsByContext (getContextsByNgramsOnlyUser)
35 import Gargantext.Database.Action.Flow.Types (FlowCmdM)
36 import Gargantext.Database.Action.Node (mkNodeWithParent)
37 import Gargantext.Database.Admin.Config
38 import Gargantext.Database.Admin.Types.Node
39 import Gargantext.Database.Prelude (Cmd)
40 import Gargantext.Database.Query.Table.Node
41 import Gargantext.Database.Query.Table.Node.Error (HasNodeError)
42 import Gargantext.Database.Query.Table.Node.Select
43 import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata)
44 import Gargantext.Database.Query.Table.Node.User (getNodeUser)
45 import Gargantext.Database.Schema.Node
46 import Gargantext.Database.Schema.Ngrams
47 import Gargantext.Prelude
49 import Servant.Job.Async
51 import qualified Data.HashMap.Strict as HashMap
53 ------------------------------------------------------------------------
54 -- | There is no Delete specific API for Graph since it can be deleted
56 type GraphAPI = Get '[JSON] HyperdataGraphAPI
57 :<|> "async" :> GraphAsyncAPI
59 :> ReqBody '[JSON] HyperdataGraphAPI
60 :> Post '[JSON] NodeId
61 :<|> "gexf" :> Get '[XML] (Headers '[Servant.Header "Content-Disposition" Text] Graph)
62 :<|> "versions" :> GraphVersionsAPI
65 GraphVersions { gv_graph :: Maybe Int
68 deriving (Show, Generic)
70 instance FromJSON GraphVersions
71 instance ToJSON GraphVersions
72 instance ToSchema GraphVersions
74 graphAPI :: UserId -> NodeId -> GargServer GraphAPI
75 graphAPI u n = getGraph u n
79 :<|> graphVersionsAPI u n
81 ------------------------------------------------------------------------
82 --getGraph :: UserId -> NodeId -> GargServer HyperdataGraphAPI
83 getGraph :: FlowCmdM env err m
86 -> m HyperdataGraphAPI
87 getGraph _uId nId = do
88 nodeGraph <- getNodeWith nId (Proxy :: Proxy HyperdataGraph)
91 graph = nodeGraph ^. node_hyperdata . hyperdataGraph
92 camera = nodeGraph ^. node_hyperdata . hyperdataCamera
94 mcId <- getClosestParentIdByType nId NodeCorpus
95 let cId = maybe (panic "[G.V.G.API] Node has no parent") identity mcId
97 printDebug "[getGraph] getting list for cId" cId
98 listId <- defaultList cId
99 repo <- getRepo' [listId]
101 -- TODO Distance in Graph params
104 let defaultMetric = Order1
105 let defaultPartitionMethod = Spinglass
106 graph' <- computeGraph cId defaultPartitionMethod (withMetric defaultMetric) NgramsTerms repo
107 mt <- defaultGraphMetadata cId "Title" repo defaultMetric
109 graph'' = set graph_metadata (Just mt) graph'
110 hg = HyperdataGraphAPI graph'' camera
111 -- _ <- updateHyperdata nId hg
112 _ <- updateHyperdata nId (HyperdataGraph (Just graph'') camera)
113 pure $ trace "[G.V.G.API] Graph empty, computing" hg
115 Just graph' -> pure $ trace "[G.V.G.API] Graph exists, returning" $
116 HyperdataGraphAPI graph' camera
119 --recomputeGraph :: UserId -> NodeId -> Maybe GraphMetric -> GargNoServer Graph
120 recomputeGraph :: FlowCmdM env err m
127 recomputeGraph _uId nId method maybeDistance force = do
128 nodeGraph <- getNodeWith nId (Proxy :: Proxy HyperdataGraph)
130 graph = nodeGraph ^. node_hyperdata . hyperdataGraph
131 camera = nodeGraph ^. node_hyperdata . hyperdataCamera
132 graphMetadata = graph ^? _Just . graph_metadata . _Just
133 listVersion = graph ^? _Just . graph_metadata . _Just . gm_list . lfg_version
134 graphMetric = case maybeDistance of
135 Nothing -> graph ^? _Just . graph_metadata . _Just . gm_metric
137 similarity = case graphMetric of
138 Nothing -> withMetric Order1
139 Just m -> withMetric m
141 mcId <- getClosestParentIdByType nId NodeCorpus
142 let cId = maybe (panic "[G.V.G.API] Node has no parent") identity mcId
144 listId <- defaultList cId
145 repo <- getRepo' [listId]
146 let v = repo ^. unNodeStory . at listId . _Just . a_version
149 g <- computeGraph cId method similarity NgramsTerms repo
150 let g' = set graph_metadata mt g
151 _ <- updateHyperdata nId (HyperdataGraph (Just g') camera)
156 mt <- defaultGraphMetadata cId "Title" repo (fromMaybe Order1 maybeDistance)
157 g <- computeG $ Just mt
158 pure $ trace "[G.V.G.API.recomputeGraph] Graph empty, computed" g
159 Just graph' -> if (listVersion == Just v) && (not force)
162 g <- computeG graphMetadata
163 pure $ trace "[G.V.G.API] Graph exists, recomputing" g
166 computeGraph :: FlowCmdM env err m
173 computeGraph cId method d nt repo = do
174 lId <- defaultList cId
175 lIds <- selectNodesWithUsername NodeList userMaster
177 let ngs = filterListWithRoot [MapTerm]
178 $ mapTermListRoot [lId] nt repo
180 myCooc <- HashMap.filter (>1) -- Removing the hapax (ngrams with 1 cooc)
181 -- <$> HashMap.filterWithKey (\(x,y) _ -> x /= y)
182 -- <$> getCoocByNgrams (if d == Conditional then Diagonal True else Diagonal False)
183 <$> getCoocByNgrams (Diagonal True)
184 <$> groupNodesByNgrams ngs
185 <$> getContextsByNgramsOnlyUser cId (lIds <> [lId]) nt (HashMap.keys ngs)
187 -- printDebug "myCooc" myCooc
188 -- saveAsFileDebug "debug/my-cooc" myCooc
190 listNgrams <- getListNgrams [lId] nt
192 -- graph <- liftBase $ cooc2graphWith Confluence d 0 myCooc
193 -- graph <- liftBase $ cooc2graphWith Spinglass d 0 myCooc
194 graph <- liftBase $ cooc2graphWith method d 0 myCooc
195 -- saveAsFileDebug "debug/graph" graph
197 pure $ mergeGraphNgrams graph (Just listNgrams)
200 defaultGraphMetadata :: HasNodeError err
205 -> Cmd err GraphMetadata
206 defaultGraphMetadata cId t repo gm = do
207 lId <- defaultList cId
209 pure $ GraphMetadata {
212 , _gm_corpusId = [cId]
214 LegendField 1 "#FFF" "Cluster1"
215 , LegendField 2 "#FFF" "Cluster2"
216 , LegendField 3 "#FFF" "Cluster3"
217 , LegendField 4 "#FFF" "Cluster4"
219 , _gm_list = (ListForGraph lId (repo ^. unNodeStory . at lId . _Just . a_version))
220 , _gm_startForceAtlas = True
222 -- (map (\n -> LegendField n "#FFFFFF" (pack $ show n)) [1..10])
224 ------------------------------------------------------------
225 type GraphAsyncAPI = Summary "Recompute graph"
227 :> AsyncJobsAPI JobLog () JobLog
230 graphAsync :: UserId -> NodeId -> GargServer GraphAsyncAPI
233 JobFunction (\_ log' -> graphRecompute u n (liftBase . log'))
236 --graphRecompute :: UserId
238 -- -> (JobLog -> GargNoServer ())
239 -- -> GargNoServer JobLog
240 graphRecompute :: FlowCmdM env err m
245 graphRecompute u n logStatus = do
246 logStatus JobLog { _scst_succeeded = Just 0
247 , _scst_failed = Just 0
248 , _scst_remaining = Just 1
249 , _scst_events = Just []
251 _g <- trace (show u) $ recomputeGraph u n Spinglass Nothing False
252 pure JobLog { _scst_succeeded = Just 1
253 , _scst_failed = Just 0
254 , _scst_remaining = Just 0
255 , _scst_events = Just []
258 ------------------------------------------------------------
259 type GraphVersionsAPI = Summary "Graph versions"
260 :> Get '[JSON] GraphVersions
261 :<|> Summary "Recompute graph version"
262 :> Post '[JSON] Graph
264 graphVersionsAPI :: UserId -> NodeId -> GargServer GraphVersionsAPI
265 graphVersionsAPI u n =
267 :<|> recomputeVersions u n
269 graphVersions :: Int -> NodeId -> GargNoServer GraphVersions
270 graphVersions n nId = do
271 nodeGraph <- getNodeWith nId (Proxy :: Proxy HyperdataGraph)
284 mcId <- getClosestParentIdByType nId NodeCorpus
285 let cId = maybe (panic "[G.V.G.API] Node has no parent") identity mcId
287 maybeListId <- defaultListMaybe cId
290 then graphVersions (n+1) cId
291 else panic "[G.V.G.API] list not found after iterations"
294 repo <- getRepo' [listId]
295 let v = repo ^. unNodeStory . at listId . _Just . a_version
296 printDebug "graphVersions" v
298 pure $ GraphVersions { gv_graph = listVersion
301 --recomputeVersions :: UserId -> NodeId -> GargNoServer Graph
302 recomputeVersions :: FlowCmdM env err m
306 recomputeVersions uId nId = recomputeGraph uId nId Spinglass Nothing False
308 ------------------------------------------------------------
312 -> GargNoServer NodeId
313 graphClone uId pId (HyperdataGraphAPI { _hyperdataAPIGraph = graph
314 , _hyperdataAPICamera = camera }) = do
315 let nodeType = NodeGraph
316 nodeUser <- getNodeUser (NodeId uId)
317 nodeParent <- getNodeWith pId (Proxy :: Proxy HyperdataGraph)
318 let uId' = nodeUser ^. node_user_id
319 nIds <- mkNodeWithParent nodeType (Just pId) uId' $ nodeParent ^. node_name
324 let graphP' = set (graph_metadata . _Just . gm_startForceAtlas) False graphP
326 _ <- updateHyperdata nId (HyperdataGraph (Just graphP') camera)
330 ------------------------------------------------------------
331 --getGraphGexf :: UserId
333 -- -> GargNoServer (Headers '[Servant.Header "Content-Disposition" Text] Graph)
334 getGraphGexf :: FlowCmdM env err m
337 -> m (Headers '[Servant.Header "Content-Disposition" Text] Graph)
338 getGraphGexf uId nId = do
339 HyperdataGraphAPI { _hyperdataAPIGraph = graph } <- getGraph uId nId
340 pure $ addHeader "attachment; filename=graph.gexf" graph