Commit 30ce86c7 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[WIP] bridgeness optim

parent 5583b556
...@@ -19,10 +19,9 @@ TODO use Map LouvainNodeId (Map LouvainNodeId) ...@@ -19,10 +19,9 @@ TODO use Map LouvainNodeId (Map LouvainNodeId)
module Gargantext.Core.Viz.Graph.Bridgeness -- (bridgeness) module Gargantext.Core.Viz.Graph.Bridgeness -- (bridgeness)
where where
import Data.List (concat, sortOn) import Debug.Trace (trace)
import Data.Map (Map, fromListWith, lookup, toList, mapWithKey, elems) import Data.Map (Map, fromListWith, lookup, toList, mapWithKey, elems)
import Data.Maybe (catMaybes, fromMaybe) import Data.Maybe (catMaybes)
import Data.Set (Set)
import Gargantext.Prelude import Gargantext.Prelude
import Graph.Types (ClusterNode(..)) import Graph.Types (ClusterNode(..))
import Data.Ord (Down(..)) import Data.Ord (Down(..))
...@@ -30,7 +29,6 @@ import Data.IntMap (IntMap) ...@@ -30,7 +29,6 @@ import Data.IntMap (IntMap)
import qualified Data.IntMap as IntMap import qualified Data.IntMap as IntMap
import qualified Data.List as List import qualified Data.List as List
import qualified Data.Map as Map import qualified Data.Map as Map
import qualified Data.Set as Set
---------------------------------------------------------------------- ----------------------------------------------------------------------
type Partitions a = Map (Int, Int) Double -> IO [a] type Partitions a = Map (Int, Int) Double -> IO [a]
...@@ -50,10 +48,24 @@ instance ToComId ClusterNode where ...@@ -50,10 +48,24 @@ instance ToComId ClusterNode where
type Bridgeness = Double type Bridgeness = Double
type Confluence = Map (NodeId, NodeId) Double type Confluence = Map (NodeId, NodeId) Double
bridgeness3 :: Confluence bridgeness3 :: Confluence
-> Map (NodeId, NodeId) Double -> Map (NodeId, NodeId) Double
-> Map (NodeId, NodeId) Double -> Map (NodeId, NodeId) Double
bridgeness3 _ m = m bridgeness3 c m = Map.fromList
$ map fst
$ List.take n
$ List.sortOn (Down . snd)
$ catMaybes
$ map (\(ks,v) -> (,) <$> Just (ks,v) <*> look ks c')
$ Map.toList m
where
!c' = map2intMap c
!m' = Map.toList m
n :: Int
!n = trace ("bridgeness m size: " <> (show $ List.length m')) $ round $ (fromIntegral $ List.length m') / (10 :: Double)
map2intMap :: Map (Int, Int) a -> IntMap (IntMap a) map2intMap :: Map (Int, Int) a -> IntMap (IntMap a)
map2intMap m = IntMap.fromListWith (<>) map2intMap m = IntMap.fromListWith (<>)
...@@ -64,41 +76,13 @@ map2intMap m = IntMap.fromListWith (<>) ...@@ -64,41 +76,13 @@ map2intMap m = IntMap.fromListWith (<>)
$ Map.toList m $ Map.toList m
look :: (Int,Int) -> IntMap (IntMap a) -> Maybe a look :: (Int,Int) -> IntMap (IntMap a) -> Maybe a
look (k1,k2) m = if k1 > k2 look (k1,k2) m = if k1 < k2
then case (IntMap.lookup k1 m) of then case (IntMap.lookup k1 m) of
Just m' -> IntMap.lookup k2 m' Just m' -> IntMap.lookup k2 m'
_ -> Nothing _ -> Nothing
else look (k2,k1) m else look (k2,k1) m
bridgeness2 :: Confluence
-> Map (NodeId, NodeId) Double
-> Map (NodeId, NodeId) Double
bridgeness2 c m = Map.fromList
$ List.filter (\((k1,k2),_v) -> if k1 < k2
then fromMaybe False (Set.member k2 <$> IntMap.lookup k1 toKeep)
else fromMaybe False (Set.member k1 <$> IntMap.lookup k2 toKeep)
)
$ m'
where
toKeep :: IntMap (Set NodeId)
!toKeep = IntMap.fromListWith (<>)
$ map (\((k1,k2), _v) -> if k1 < k2
then (k1, Set.singleton k2)
else (k2, Set.singleton k1)
)
$ List.take n
$ List.sortOn (Down . snd)
$ catMaybes
$ map (\ks -> (,) <$> Just ks <*> look ks c')
$ Map.keys m
c' = map2intMap c
!m' = Map.toList m
n :: Int
!n = round $ (fromIntegral $ List.length m') / (2 :: Double)
{- {-
n :: Int n :: Int
n = Set.size $ Set.fromList $ as <> bs n = Set.size $ Set.fromList $ as <> bs
...@@ -119,7 +103,7 @@ bridgeness = bridgenessWith nodeId2comId ...@@ -119,7 +103,7 @@ bridgeness = bridgenessWith nodeId2comId
-> Map (Int, Int) Double -> Map (Int, Int) Double
-> Map (Int, Int) Double -> Map (Int, Int) Double
bridgenessWith f b ns = Map.fromList bridgenessWith f b ns = Map.fromList
. concat . List.concat
. Map.elems . Map.elems
. filterComs b . filterComs b
. groupEdges (Map.fromList $ map f ns) . groupEdges (Map.fromList $ map f ns)
...@@ -149,13 +133,13 @@ filterComs _b m = Map.filter (\n -> length n > 0) $ mapWithKey filter' m ...@@ -149,13 +133,13 @@ filterComs _b m = Map.filter (\n -> length n > 0) $ mapWithKey filter' m
filter' (c1,c2) a filter' (c1,c2) a
| c1 == c2 = a | c1 == c2 = a
-- TODO use n here -- TODO use n here
| otherwise = take 1 $ sortOn (Down . snd) a | otherwise = take 1 $ List.sortOn (Down . snd) a
where where
_n :: Int _n :: Int
_n = round $ 100 * a' / t _n = round $ 100 * a' / t
a'= fromIntegral $ length a a'= fromIntegral $ length a
t :: Double t :: Double
t = fromIntegral $ length $ concat $ elems m t = fromIntegral $ length $ List.concat $ elems m
-------------------------------------------------------------- --------------------------------------------------------------
......
...@@ -26,7 +26,7 @@ import Gargantext.Core.Methods.Similarities (Similarity(..), measure) ...@@ -26,7 +26,7 @@ import Gargantext.Core.Methods.Similarities (Similarity(..), measure)
import Gargantext.Core.Methods.Similarities.Conditional (conditional) import Gargantext.Core.Methods.Similarities.Conditional (conditional)
import Gargantext.Core.Statistics import Gargantext.Core.Statistics
import Gargantext.Core.Viz.Graph import Gargantext.Core.Viz.Graph
import Gargantext.Core.Viz.Graph.Bridgeness (bridgeness2, Partitions, ToComId(..)) import Gargantext.Core.Viz.Graph.Bridgeness (bridgeness3, Partitions, ToComId(..))
import Gargantext.Core.Viz.Graph.Index (createIndices, toIndex, map2mat, mat2map, Index, MatrixShape(..)) 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.Tools.IGraph (mkGraphUfromEdges, spinglass)
import Gargantext.Core.Viz.Graph.Tools.Infomap (infomap) import Gargantext.Core.Viz.Graph.Tools.Infomap (infomap)
...@@ -130,7 +130,7 @@ cooc2graphWith' doPartitions multi similarity threshold strength myCooc = do ...@@ -130,7 +130,7 @@ cooc2graphWith' doPartitions multi similarity threshold strength myCooc = do
let let
!confluence' = BAC.computeConfluences 3 (Map.keys bridgeness') True !confluence' = BAC.computeConfluences 3 (Map.keys bridgeness') True
!bridgeness' = bridgeness2 confluence' distanceMap !bridgeness' = bridgeness3 confluence' distanceMap
pure $ data2graph multi ti diag bridgeness' confluence' partitions pure $ data2graph multi ti diag bridgeness' confluence' partitions
type Reverse = Bool type Reverse = Bool
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment