Commit 8e00be36 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FEAT] Bridgeness (needs tests).

parent 930b75fc
......@@ -26,12 +26,14 @@ module Gargantext.Prelude
, module Text.Read
, cs
, module Data.Maybe
, round
, sortWith
)
where
import GHC.Exts (sortWith)
import GHC.Err.Located (undefined)
import GHC.Real (round)
import Control.Monad.IO.Class (MonadIO)
import Data.Maybe (isJust, fromJust, maybe)
import Protolude ( Bool(True, False), Int, Int64, Double, Integer
......
......@@ -43,6 +43,7 @@ import Gargantext.Viz.Graph.Index (createIndices, toIndex, map2mat, mat2map)
import Gargantext.Viz.Graph.Distances.Matrice (measureConditional)
import Gargantext.Viz.Graph (Graph(..), data2graph)
import Gargantext.Text.Metrics.Count (cooc)
import Gargantext.Viz.Graph.Bridgeness (bridgeness)
import Gargantext.Text.Metrics (filterCooc, FilterConfig(..), Clusters(..), SampleBins(..), DefaultValue(..), MapListSize(..), InclusionSize(..))
import Gargantext.Text.Terms (TermType, extractTerms)
import Gargantext.Text.Context (splitBy, SplitContext(Sentences))
......@@ -168,5 +169,6 @@ cooc2graph myCooc = do
-- Building : -> Graph -> JSON
--printDebug "partitions" $ DS.size $ DS.fromList $ map (l_community_id) partitions
--printDebug "partitions" partitions
pure $ data2graph (M.toList ti) myCooc4 distanceMap partitions
let distanceMap' = bridgeness 5 partitions distanceMap
pure $ data2graph (M.toList ti) myCooc4 distanceMap' partitions
{-|
Module : Gargantext.Viz.Graph.Bridgeness
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE NoImplicitPrelude #-}
module Gargantext.Viz.Graph.Bridgeness (bridgeness)
where
import Gargantext.Prelude
--import Gargantext.Viz.Graph
import Data.Map (Map, fromListWith, lookup, fromList, keys)
import Data.Maybe (catMaybes)
import Data.List (sortOn, concat)
import Data.Graph.Clustering.Louvain.CplusPlus (LouvainNode(..))
type Bridgeness = Double
-- TODO mv in Louvain Lib
type LouvainNodeId = Int
type CommunityId = Int
partition2map :: [LouvainNode] -> Map CommunityId [LouvainNodeId]
partition2map ns = fromListWith (<>) [ (cId, [nId]) | LouvainNode nId cId <- ns]
ordEdgesBetween :: (Ord distance, Ord node)
=> [node] -> [node]
-> Map (node, node) distance
-> [((node, node), distance)]
ordEdgesBetween c1 c2 d = reverse $ sortOn snd $ catMaybes
[ (,) <$> Just (n1,n2)
<*> lookup (n1,n2) d
| n1 <- c1
, n2 <- c2
, n1 < n2
]
filterEdgesBetween :: (RealFrac b, Ord node, Ord distance) =>
b -> [node] -> [node]
-> Map (node, node) distance
-> [((node, node), distance)]
filterEdgesBetween b c1 c2 d = take n d'
where
n = round $ b * i / (s1 + s2)
d' = ordEdgesBetween c1 c2 d
i = fromIntegral $ length d'
s1 = fromIntegral $ length (ordEdgesBetween c1 c2 d)
s2 = fromIntegral $ length (ordEdgesBetween c2 c2 d)
bridgeness :: Bridgeness
-> [LouvainNode]
-> Map (LouvainNodeId, LouvainNodeId) Double
-> Map (LouvainNodeId, LouvainNodeId) Double
bridgeness b ns' ds = fromList . concat . map (\(c1,c2) -> filterEdgesBetween b c1 c2 ds) $ p
where
p = catMaybes [ (,) <$> lookup k1 ns <*> lookup k2 ns | k1 <- ks, k2 <- ks, k1 < k2]
ns = partition2map ns'
ks = keys ns
{-|
Module : Gargantext.Graph.Distances.Utils
Module : Gargantext.Viz.Graph.Utils
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......
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