-}
+{-# LANGUAGE ScopedTypeVariables #-}
module Gargantext.Core.Viz.Graph.Tools
where
-import Debug.Trace (trace)
-import Data.Graph.Clustering.Louvain.Utils (LouvainNode(..))
-- import Data.Graph.Clustering.Louvain (hLouvain, {-iLouvainMap-})
-import Data.Graph.Clustering.Louvain.CplusPlus (cLouvain)
+import Data.HashMap.Strict (HashMap)
import Data.Map (Map)
-import qualified Data.Set as Set
import Data.Text (Text)
-import Gargantext.Prelude
+import Debug.Trace (trace)
+import GHC.Float (sin, cos)
+import Gargantext.API.Ngrams.Types (NgramsTerm(..))
+import Gargantext.Core.Methods.Distances (Distance(..), measure)
+import Gargantext.Core.Methods.Graph.BAC.Proxemy (confluence)
import Gargantext.Core.Statistics
import Gargantext.Core.Viz.Graph
-import Gargantext.Core.Viz.Graph.Bridgeness (bridgeness)
-import Gargantext.Core.Viz.Graph.Distances (Distance(..), measure)
-import Gargantext.Core.Viz.Graph.Index (createIndices, toIndex, map2mat, mat2map, Index)
-import Gargantext.Core.Viz.Graph.IGraph (mkGraphUfromEdges)
-import Gargantext.Core.Viz.Graph.Proxemy (confluence)
-import GHC.Float (sin, cos)
-import qualified IGraph as Igraph
+import Gargantext.Core.Viz.Graph.Bridgeness (bridgeness, Partitions, ToComId(..))
+import Gargantext.Core.Viz.Graph.Index (createIndices, toIndex, map2mat, mat2map, Index, MatrixShape(..))
+import Gargantext.Core.Viz.Graph.Tools.IGraph (mkGraphUfromEdges, spinglass)
+import Gargantext.Core.Viz.Graph.Types (ClusterNode)
+import Gargantext.Prelude
+-- import qualified Graph.BAC.ProxemyOptim as BAC
+import IGraph.Random -- (Gen(..))
+import qualified Data.HashMap.Strict as HashMap
+import qualified Data.List as List
+import qualified Data.Map as Map
+import qualified Data.Set as Set
+import qualified Data.Vector.Storable as Vec
+import qualified IGraph as Igraph
import qualified IGraph.Algorithms.Layout as Layout
-import qualified Data.Vector.Storable as Vec
-import qualified Data.Map as Map
-import qualified Data.List as List
-type Threshold = Double
+-------------------------------------------------------------
+defaultClustering :: Map (Int, Int) Double -> IO [ClusterNode]
+-- defaultClustering x = pure $ BAC.defaultClustering x
+defaultClustering x = spinglass 1 x
+
+-------------------------------------------------------------
+type Threshold = Double
cooc2graph' :: Ord t => Distance
-> Double
-> Map (t, t) Int
-> Map (Index, Index) Double
-cooc2graph' distance threshold myCooc = distanceMap
- where
- (ti, _) = createIndices myCooc
- myCooc' = toIndex ti myCooc
- matCooc = map2mat 0 (Map.size ti) $ Map.filter (> 1) myCooc'
- distanceMat = measure distance matCooc
- distanceMap = Map.filter (> threshold) $ mat2map distanceMat
-
-
-cooc2graph :: Distance
- -> Threshold
- -> (Map (Text, Text) Int)
- -> IO Graph
-cooc2graph distance threshold myCooc = do
- printDebug "cooc2graph" distance
+cooc2graph' distance threshold myCooc
+ = Map.filter (> threshold)
+ $ mat2map
+ $ measure distance
+ $ case distance of
+ Conditional -> map2mat Triangle 0 tiSize
+ Distributional -> map2mat Square 0 tiSize
+ $ Map.filter (> 1) myCooc'
+
+ where
+ (ti, _) = createIndices myCooc
+ tiSize = Map.size ti
+ myCooc' = toIndex ti myCooc
+
+
+data PartitionMethod = Louvain | Spinglass -- | Bac
+
+-- | coocurrences graph computation
+cooc2graphWith :: PartitionMethod
+ -> Distance
+ -> Threshold
+ -> HashMap (NgramsTerm, NgramsTerm) Int
+ -> IO Graph
+cooc2graphWith Louvain = undefined
+cooc2graphWith Spinglass = cooc2graphWith' (spinglass 1)
+-- cooc2graphWith Bac = cooc2graphWith' (\x -> pure $ BAC.defaultClustering x)
+
+
+cooc2graphWith' :: ToComId a
+ => Partitions a
+ -> Distance
+ -> Threshold
+ -> HashMap (NgramsTerm, NgramsTerm) Int
+ -> IO Graph
+cooc2graphWith' doPartitions distance threshold myCooc = do
let
- (ti, _) = createIndices myCooc
- myCooc' = toIndex ti myCooc
- matCooc = map2mat 0 (Map.size ti)
- $ Map.filterWithKey (\(a,b) _ -> a /= b)
- $ Map.filter (> 1) myCooc'
- distanceMat = measure distance matCooc
- distanceMap = Map.filter (> threshold) $ mat2map distanceMat
+ (distanceMap, diag, ti) = doDistanceMap distance threshold myCooc
nodesApprox :: Int
nodesApprox = n'
where
(as, bs) = List.unzip $ Map.keys distanceMap
n' = Set.size $ Set.fromList $ as <> bs
- ClustersParams rivers level = clustersParams nodesApprox
+ ClustersParams rivers _level = clustersParams nodesApprox
+{- -- Debug
+ saveAsFileDebug "debug/distanceMap" distanceMap
+ printDebug "similarities" similarities
+-}
partitions <- if (Map.size distanceMap > 0)
- -- then iLouvainMap 100 10 distanceMap
- -- then hLouvain distanceMap
- then cLouvain level distanceMap
+ then doPartitions distanceMap
else panic "Text.Flow: DistanceMap is empty"
let
-- bridgeness' = distanceMap
bridgeness' = trace ("Rivers: " <> show rivers)
$ bridgeness rivers partitions distanceMap
+
confluence' = confluence (Map.keys bridgeness') 3 True False
- pure $ data2graph (Map.toList ti) myCooc' bridgeness' confluence' partitions
+ pure $ data2graph (Map.toList $ Map.mapKeys unNgramsTerm ti)
+ diag bridgeness' confluence' partitions
+
+doDistanceMap :: Distance
+ -> Threshold
+ -> HashMap (NgramsTerm, NgramsTerm) Int
+ -> ( Map (Int,Int) Double
+ , Map (Index, Index) Int
+ , Map NgramsTerm Index
+ )
+doDistanceMap distance threshold myCooc = (distanceMap, toIndex ti diag, ti)
+ where
+ -- TODO remove below
+ (diag, theMatrix) = Map.partitionWithKey (\(x,y) _ -> x == y)
+ $ Map.fromList
+ $ HashMap.toList myCooc
+
+ (ti, _it) = createIndices theMatrix
+ tiSize = Map.size ti
+
+ matCooc = case distance of -- Shape of the Matrix
+ Conditional -> map2mat Triangle 0 tiSize
+ Distributional -> map2mat Square 0 tiSize
+ {-$ case distance of -- Removing the Diagonal ?
+ Conditional -> Map.filterWithKey (\(a,b) _ -> a /= b)
+ Distributional -> Map.filterWithKey (\(a,b) _ -> a /= b)
+ -}
+ $ toIndex ti theMatrix
+
+ similarities = measure distance matCooc
+ links = round (let n :: Double = fromIntegral tiSize in n * log n)
+
+ distanceMap = Map.fromList
+ $ List.take links
+ $ List.sortOn snd
+ $ Map.toList
+ $ Map.filter (> threshold)
+ $ mat2map similarities
+
+
+
+------------------------------------------------------------------------
+------------------------------------------------------------------------
data ClustersParams = ClustersParams { bridgness :: Double
, louvain :: Text
} deriving (Show)
----------------------------------------------------------
-- | From data to Graph
-data2graph :: [(Text, Int)]
- -> Map (Int, Int) Int
+
+type Occurrences = Map (Int, Int) Int
+
+data2graph :: ToComId a
+ => [(Text, Int)]
+ -> Occurrences
-> Map (Int, Int) Double
-> Map (Int, Int) Double
- -> [LouvainNode]
+ -> [a]
-> Graph
-data2graph labels coocs bridge conf partitions = Graph nodes edges Nothing
+data2graph labels occurences bridge conf partitions = Graph { _graph_nodes = nodes
+ , _graph_edges = edges
+ , _graph_metadata = Nothing }
where
- community_id_by_node_id = Map.fromList [ (n, c) | LouvainNode n c <- partitions ]
+ community_id_by_node_id = Map.fromList
+ $ map nodeId2comId partitions
nodes = map (setCoord ForceAtlas labels bridge)
- [ (n, Node { node_size = maybe 0 identity (Map.lookup (n,n) coocs)
- , node_type = Terms -- or Unknown
- , node_id = cs (show n)
- , node_label = l
- , node_x_coord = 0
- , node_y_coord = 0
- , node_attributes =
- Attributes { clust_default = maybe 0 identity
- (Map.lookup n community_id_by_node_id) } }
+ [ (n, Node { node_size = maybe 0 identity (Map.lookup (n,n) occurences)
+ , node_type = Terms -- or Unknown
+ , node_id = cs (show n)
+ , node_label = l
+ , node_x_coord = 0
+ , node_y_coord = 0
+ , node_attributes =
+ Attributes { clust_default = maybe 0 identity
+ (Map.lookup n community_id_by_node_id) }
+ , node_children = [] }
)
| (l, n) <- labels
, Set.member n $ Set.fromList
, edge_weight = d
, edge_confluence = maybe 0 identity $ Map.lookup (s,t) conf
-- , edge_confluence = maybe (panic "E: data2graph edges") identity $ Map.lookup (s,t) conf
- , edge_id = cs (show i) }
- | (i, ((s,t), d)) <- zip ([0..]::[Integer]) (Map.toList bridge), s /= t, d > 0
+ , edge_id = cs (show i)
+ }
+ | (i, ((s,t), d)) <- zip ([0..]::[Integer] )
+ (Map.toList bridge)
+ , s /= t, d > 0
]
-- | KamadaKawai Layout
-- TODO TEST: check labels, nodeId and coordinates
-layout :: Map (Int, Int) Double -> Int -> IO (Double, Double)
-layout m n = maybe (panic "") identity <$> Map.lookup n <$> coord
+layout :: Map (Int, Int) Double -> Int -> Gen -> (Double, Double)
+layout m n gen = maybe (panic "") identity $ Map.lookup n $ coord
where
- coord :: IO (Map Int (Double,Double))
- coord = Map.fromList <$> List.zip (Igraph.nodes g) <$> (Layout.getLayout g p)
+ coord :: (Map Int (Double,Double))
+ coord = Map.fromList $ List.zip (Igraph.nodes g) $ (Layout.layout g p gen)
--p = Layout.defaultLGL
- p = Layout.defaultKamadaKawai
+ p = Layout.kamadaKawai
g = mkGraphUfromEdges $ map fst $ List.filter (\e -> snd e > 0) $ Map.toList m
+-----------------------------------------------------------------------------
+-- MISC Tools
+cooc2graph'' :: Ord t => Distance
+ -> Double
+ -> Map (t, t) Int
+ -> Map (Index, Index) Double
+cooc2graph'' distance threshold myCooc = neighbourMap
+ where
+ (ti, _) = createIndices myCooc
+ myCooc' = toIndex ti myCooc
+ matCooc = map2mat Triangle 0 (Map.size ti) $ Map.filter (> 1) myCooc'
+ distanceMat = measure distance matCooc
+ neighbourMap = filterByNeighbours threshold
+ $ mat2map distanceMat
+
+-- Quentin
+filterByNeighbours :: Double -> Map (Index, Index) Double -> Map (Index, Index) Double
+filterByNeighbours threshold distanceMap = filteredMap
+ where
+ indexes :: [Index]
+ indexes = List.nub $ List.concat $ map (\(idx,idx') -> [idx,idx'] ) $ Map.keys distanceMap
+ filteredMap :: Map (Index, Index) Double
+ filteredMap = Map.fromList
+ $ List.concat
+ $ map (\idx ->
+ let selected = List.reverse
+ $ List.sortOn snd
+ $ Map.toList
+ $ Map.filter (> 0)
+ $ Map.filterWithKey (\(from,_) _ -> idx == from) distanceMap
+ in List.take (round threshold) selected
+ ) indexes
+
+
+
+
+