Commit 5993a1f3 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FEAT] iLouvain adapted to Gargantext workflow

parent 1c82ad80
......@@ -19,11 +19,15 @@ References:
module Data.Graph.Clustering.Louvain
where
import Data.Map.Strict (Map)
import Data.List (maximumBy, nub, intersect, foldl', zipWith, concat)
import Data.Graph.Inductive
import Data.Graph.Clustering.Louvain.Utils (LouvainNode(..), toFGraph)
import Data.Graph.Clustering.Louvain.Utils (LouvainNode(..), toFGraph, map2graph)
import Data.Graph.Clustering.FLouvain (louvainFirstStepIterate, initialCGr)
import Data.Graph.Clustering.Louvain.Types (Community(..), comNodes)
import qualified Data.Graph.Clustering.ILouvain as I
------------------------------------------------------------------------
-- | Definitions
------------------------------------------------------------------------
......@@ -33,6 +37,18 @@ type Community = [Node]
-- type Partition = [Community]
type Reverse = Bool
------------------------------------------------------------------------
iLouvain :: I.MaxIterations
-> I.MaxSize
-> Map (Node, Node) Double
-> [LouvainNode]
iLouvain x s m = concat
$ toLouvainNode
$ I.toNodes
$ I.iLouvain x s I.DfsNodes g
where
g = I.toHyperGraph $ map2graph m
------------------------------------------------------------------------
flouvain :: Int -> Gr () Double -> [[Node]]
flouvain n g = map (comNodes . snd) $ labNodes g'
......@@ -44,10 +60,10 @@ hLouvain :: (Eq b, DynGraph gr)
-> gr a b
-> [LouvainNode]
hLouvain r g = concat $ toLouvainNode (bestpartition r g)
where
toLouvainNode :: [[Node]] -> [[LouvainNode]]
toLouvainNode ns = zipWith (\cId ns' -> map (\n -> LouvainNode n cId) ns')
[1..] ns
toLouvainNode :: [[Node]] -> [[LouvainNode]]
toLouvainNode ns = zipWith (\cId ns' -> map (\n -> LouvainNode n cId) ns')
[1..] ns
------------------------------------------------------------------------
-- | Partitionning the graph
------------------------------------------------------------------------
......
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