2 Module : Gargantext.Core.Viz.Graph.Tools
3 Description : Tools to build Graph
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
13 module Gargantext.Core.Viz.Graph.Tools
16 import Debug.Trace (trace)
17 import Data.Graph.Clustering.Louvain.Utils (LouvainNode(..))
18 -- import Data.Graph.Clustering.Louvain (hLouvain, {-iLouvainMap-})
19 import Data.Graph.Clustering.Louvain.CplusPlus (cLouvain)
21 import qualified Data.Set as Set
22 import Data.Text (Text)
23 import Gargantext.Prelude
24 import Gargantext.Core.Statistics
25 import Gargantext.Core.Viz.Graph
26 import Gargantext.Core.Viz.Graph.Bridgeness (bridgeness)
27 import Gargantext.Core.Viz.Graph.Distances (Distance(..), measure)
28 import Gargantext.Core.Viz.Graph.Index (createIndices, toIndex, map2mat, mat2map, Index)
29 import Gargantext.Core.Viz.Graph.IGraph (mkGraphUfromEdges)
30 import Gargantext.Core.Viz.Graph.Proxemy (confluence)
31 import GHC.Float (sin, cos)
32 import qualified IGraph as Igraph
33 import IGraph.Random -- (Gen(..))
34 import qualified IGraph.Algorithms.Layout as Layout
35 import qualified Data.Vector.Storable as Vec
36 import qualified Data.Map as Map
37 import qualified Data.List as List
39 type Threshold = Double
42 cooc2graph' :: Ord t => Distance
45 -> Map (Index, Index) Double
46 cooc2graph' distance threshold myCooc = distanceMap
48 (ti, _) = createIndices myCooc
49 myCooc' = toIndex ti myCooc
50 matCooc = map2mat 0 (Map.size ti) $ Map.filter (> 1) myCooc'
51 distanceMat = measure distance matCooc
52 distanceMap = Map.filter (> threshold) $ mat2map distanceMat
55 cooc2graph :: Distance
57 -> (Map (Text, Text) Int)
59 cooc2graph distance threshold myCooc = do
60 printDebug "cooc2graph" distance
62 (ti, _) = createIndices myCooc
63 myCooc' = toIndex ti myCooc
64 matCooc = map2mat 0 (Map.size ti)
65 $ Map.filterWithKey (\(a,b) _ -> a /= b)
66 $ Map.filter (> 1) myCooc'
67 distanceMat = measure distance matCooc
68 distanceMap = Map.filter (> threshold) $ mat2map distanceMat
73 (as, bs) = List.unzip $ Map.keys distanceMap
74 n' = Set.size $ Set.fromList $ as <> bs
75 ClustersParams rivers level = clustersParams nodesApprox
78 partitions <- if (Map.size distanceMap > 0)
79 -- then iLouvainMap 100 10 distanceMap
80 -- then hLouvain distanceMap
81 then cLouvain level distanceMap
82 else panic "Text.Flow: DistanceMap is empty"
85 -- bridgeness' = distanceMap
86 bridgeness' = trace ("Rivers: " <> show rivers)
87 $ bridgeness rivers partitions distanceMap
88 confluence' = confluence (Map.keys bridgeness') 3 True False
90 pure $ data2graph (Map.toList ti) myCooc' bridgeness' confluence' partitions
94 data ClustersParams = ClustersParams { bridgness :: Double
98 clustersParams :: Int -> ClustersParams
99 clustersParams x = ClustersParams (fromIntegral x) "0.00000001" -- y
101 y | x < 100 = "0.000001"
102 | x < 350 = "0.000001"
103 | x < 500 = "0.000001"
104 | x < 1000 = "0.000001"
108 ----------------------------------------------------------
109 -- | From data to Graph
110 data2graph :: [(Text, Int)]
111 -> Map (Int, Int) Int
112 -> Map (Int, Int) Double
113 -> Map (Int, Int) Double
116 data2graph labels coocs bridge conf partitions = Graph nodes edges Nothing
119 community_id_by_node_id = Map.fromList [ (n, c) | LouvainNode n c <- partitions ]
121 nodes = map (setCoord ForceAtlas labels bridge)
122 [ (n, Node { node_size = maybe 0 identity (Map.lookup (n,n) coocs)
123 , node_type = Terms -- or Unknown
124 , node_id = cs (show n)
129 Attributes { clust_default = maybe 0 identity
130 (Map.lookup n community_id_by_node_id) } }
133 , Set.member n $ Set.fromList
135 $ map (\((s,t),d) -> if d > 0 && s /=t then [s,t] else [])
139 edges = [ Edge { edge_source = cs (show s)
140 , edge_target = cs (show t)
142 , edge_confluence = maybe 0 identity $ Map.lookup (s,t) conf
143 -- , edge_confluence = maybe (panic "E: data2graph edges") identity $ Map.lookup (s,t) conf
144 , edge_id = cs (show i) }
145 | (i, ((s,t), d)) <- zip ([0..]::[Integer]) (Map.toList bridge), s /= t, d > 0
149 ------------------------------------------------------------------------
151 data Layout = KamadaKawai | ACP | ForceAtlas
154 setCoord' :: (Int -> (Double, Double)) -> (Int, Node) -> Node
155 setCoord' f (i,n) = n { node_x_coord = x, node_y_coord = y }
161 setCoord :: Ord a => Layout -> [(a, Int)] -> Map (Int, Int) Double -> (Int, Node) -> Node
162 setCoord l labels m (n,node) = node { node_x_coord = x
166 (x,y) = getCoord l labels m n
172 -> Map (Int, Int) Double
175 getCoord KamadaKawai _ _m _n = undefined -- layout m n
177 getCoord ForceAtlas _ _ n = (sin d, cos d)
181 getCoord ACP labels m n = to2d $ maybe (panic "Graph.Tools no coordinate") identity
183 $ pcaReduceTo (Dimension 2)
186 to2d :: Vec.Vector Double -> (Double, Double)
189 ds = take 2 $ Vec.toList v
193 mapArray :: Ord a => [(a, Int)] -> Map (Int, Int) Double -> Map Int (Vec.Vector Double)
194 mapArray items m' = Map.fromList [ toVec n' ns m' | n' <- ns ]
198 toVec :: Int -> [Int] -> Map (Int,Int) Double -> (Int, Vec.Vector Double)
199 toVec n' ns' m' = (n', Vec.fromList $ map (\n'' -> maybe 0 identity $ Map.lookup (n',n'') m') ns')
200 ------------------------------------------------------------------------
202 -- | KamadaKawai Layout
203 -- TODO TEST: check labels, nodeId and coordinates
204 layout :: Map (Int, Int) Double -> Int -> Gen -> (Double, Double)
205 layout m n gen = maybe (panic "") identity $ Map.lookup n $ coord
207 coord :: (Map Int (Double,Double))
208 coord = Map.fromList $ List.zip (Igraph.nodes g) $ (Layout.layout g p gen)
209 --p = Layout.defaultLGL
210 p = Layout.kamadaKawai
211 g = mkGraphUfromEdges $ map fst $ List.filter (\e -> snd e > 0) $ Map.toList m