Squashed commit of the following:

commit 8e19bf65
Author: Grégoire Locqueville <gregoire.locqueville@cnrs.fr>
Date:   Wed Jan 8 18:25:01 2025 +0100

    Remove call to `recursiveClustering'`

    Also removed some dead and commented code around the edited area.

    Note: `recursiveClustering'` was not actually recursive, it just went
    one level deeper.
parent 23e560eb
Pipeline #7269 canceled with stages
...@@ -45,42 +45,6 @@ nodeId2comId (ClusterNode i1 i2) = (i1, i2) ...@@ -45,42 +45,6 @@ nodeId2comId (ClusterNode i1 i2) = (i1, i2)
type NodeId = Int type NodeId = Int
type CommunityId = Int type CommunityId = Int
----------------------------------------------------------------------
-- recursiveClustering : to get more granularity of a given clustering
-- tested with spinglass clustering only (WIP)
recursiveClustering' :: Partitions' -> Map (Int, Int) Double -> IO [[Set NodeId]]
recursiveClustering' f mp = do
let
n :: Double
n = fromIntegral $ Set.size
$ Set.unions $ List.concat
$ map (\(k1,k2) -> map Set.singleton [k1, k2])
$ Map.keys mp
t :: Int
t = round $ 2 * n / sqrt n
ss <- f mp
mapM (\s -> if Set.size s > t then f (removeNodes s mp) else pure [s]) ss
----------------------------------------------------------------------
recursiveClustering :: Partitions -> Map (Int, Int) Double -> IO [ClusterNode]
recursiveClustering f mp = do
let
n :: Double
n = fromIntegral $ Set.size
$ Set.unions $ List.concat
$ map (\(k1,k2) -> map Set.singleton [k1, k2])
$ Map.keys mp
t :: Int
t = round $ 2 * n / sqrt n
(toSplit,others) <- List.span (\a -> Set.size a > t) <$> clusterNodes2sets <$> f mp
cls' <- mapM f $ map (\s -> removeNodes s mp) toSplit
pure $ setNodes2clusterNodes $ others <> (List.concat $ map clusterNodes2sets cls')
---------------------------------------------------------------------- ----------------------------------------------------------------------
setNodes2clusterNodes :: [Set NodeId] -> [ClusterNode] setNodes2clusterNodes :: [Set NodeId] -> [ClusterNode]
setNodes2clusterNodes ns = List.concat $ map (\(n,ns') -> toCluster n ns') $ zip [1..] ns setNodes2clusterNodes ns = List.concat $ map (\(n,ns') -> toCluster n ns') $ zip [1..] ns
......
...@@ -30,7 +30,7 @@ import Gargantext.API.Ngrams.Types (NgramsTerm(..)) ...@@ -30,7 +30,7 @@ import Gargantext.API.Ngrams.Types (NgramsTerm(..))
import Gargantext.Core.Methods.Similarities (Similarity(..), measure) import Gargantext.Core.Methods.Similarities (Similarity(..), measure)
import Gargantext.Core.Statistics ( pcaReduceTo, Dimension(Dimension) ) import Gargantext.Core.Statistics ( pcaReduceTo, Dimension(Dimension) )
import Gargantext.Core.Text.Ngrams (NgramsType(..)) import Gargantext.Core.Text.Ngrams (NgramsType(..))
import Gargantext.Core.Viz.Graph.Bridgeness (bridgeness, Bridgeness(..), Partitions, nodeId2comId, {-recursiveClustering,-} recursiveClustering', setNodes2clusterNodes) import Gargantext.Core.Viz.Graph.Bridgeness (bridgeness, Bridgeness(..), Partitions, nodeId2comId, setNodes2clusterNodes)
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, spinglass') import Gargantext.Core.Viz.Graph.Tools.IGraph (mkGraphUfromEdges, spinglass, spinglass')
import Gargantext.Core.Viz.Graph.Tools.Infomap (infomap) import Gargantext.Core.Viz.Graph.Tools.Infomap (infomap)
...@@ -38,7 +38,7 @@ import Gargantext.Core.Viz.Graph.Types (Attributes(..), Edge(..), Graph(..), Mul ...@@ -38,7 +38,7 @@ import Gargantext.Core.Viz.Graph.Types (Attributes(..), Edge(..), Graph(..), Mul
import Gargantext.Core.Viz.Graph.Utils (edgesFilter, nodesFilter) import Gargantext.Core.Viz.Graph.Utils (edgesFilter, nodesFilter)
import Gargantext.Prelude import Gargantext.Prelude
import Graph.BAC.ProxemyOptim qualified as BAC import Graph.BAC.ProxemyOptim qualified as BAC
import Graph.Types (ClusterNode) import Graph.Types (ClusterNode(..))
import IGraph qualified as Igraph import IGraph qualified as Igraph
import IGraph.Algorithms.Layout qualified as Layout import IGraph.Algorithms.Layout qualified as Layout
import IGraph.Random ( Gen ) -- (Gen(..)) import IGraph.Random ( Gen ) -- (Gen(..))
...@@ -117,7 +117,7 @@ cooc2graphWith' _doPartitions _bridgenessMethod multi similarity threshold stren ...@@ -117,7 +117,7 @@ cooc2graphWith' _doPartitions _bridgenessMethod multi similarity threshold stren
distanceMap `seq` diag `seq` ti `seq` pure () distanceMap `seq` diag `seq` ti `seq` pure ()
partitions <- if (Map.size distanceMap > 0) partitions <- if (Map.size distanceMap > 0)
then recursiveClustering' (spinglass' 1) distanceMap then spinglass' 1 distanceMap
else panic $ Text.unwords [ "I can not compute the graph you request" else panic $ Text.unwords [ "I can not compute the graph you request"
, "because either the quantity of documents" , "because either the quantity of documents"
, "or the quantity of terms" , "or the quantity of terms"
...@@ -130,30 +130,29 @@ cooc2graphWith' _doPartitions _bridgenessMethod multi similarity threshold stren ...@@ -130,30 +130,29 @@ cooc2graphWith' _doPartitions _bridgenessMethod multi similarity threshold stren
let let
!confluence' = BAC.computeConfluences 3 (Map.keys distanceMap) True !confluence' = BAC.computeConfluences 3 (Map.keys distanceMap) True
!bridgeness' = bridgeness (Bridgeness_Recursive partitions 1.0 similarity) distanceMap !bridgeness' = bridgeness
(Bridgeness_Basic (partitionsToClusterNodes partitions) 1.0)
pure $ data2graph multi ti diag bridgeness' confluence' (setNodes2clusterNodes $ List.concat partitions) distanceMap
{- pure $ data2graph multi ti diag bridgeness' confluence' (setNodes2clusterNodes partitions)
cooc2graphWith' _doPartitions _bridgenessMethod multi similarity@Distributional threshold strength myCooc = do
let (distanceMap, diag, ti) = doSimilarityMap similarity threshold strength myCooc
distanceMap `seq` diag `seq` ti `seq` pure () -- | A converter from the partition type returned by `spinglass'`
-- to the partition type required by `bridgeness`
partitions <- if (Map.size distanceMap > 0) partitionsToClusterNodes :: [Set Int] -> [ClusterNode]
then recursiveClustering (spinglass 1) distanceMap partitionsToClusterNodes setlist =
else panic $ Text.unlines [ "[Gargantext.C.V.Graph.Tools] Similarity Matrix is empty" setlist &
, "Maybe you should add more Map Terms in your list" -- Convert sets to lists:
, "Tutorial: TODO" fmap toList &
] -- Assign an integer index to each cluster:
length partitions `seq` pure () zip [1 ..] &
-- Attach cluster IDs to individual nodes instead to whole clusters
let fmap (\(id, clusterIds) -> zip (repeat id) clusterIds) &
!confluence' = BAC.computeConfluences 3 (Map.keys distanceMap) True -- Flatten list of clusters of nodes labeled by cluster indices
!bridgeness' = bridgeness (Bridgeness_Basic partitions 1.0) distanceMap -- into a list of labeled nodes:
join &
pure $ data2graph multi ti diag bridgeness' confluence' partitions -- Turn pairs into `ClusterNode`s
-} fmap (\(clusterId, nodeId) -> ClusterNode nodeId clusterId)
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