Commit 35b7c4c1 authored by Alexandre Delanoë's avatar Alexandre Delanoë

cosmetics

parent 306a0348
......@@ -7,6 +7,26 @@ Maintainer : alexandre.delanoe+louvain@iscpif.fr
Stability : experimental
Portability : POSIX
# Louvain Algorithm
Our algorithm is divided into two phases that are repeated iteratively.
Assume that we start with a weighted network of N nodes. First, we
assign a different community to each node of the network. So, in this
initial partition there are as many communities as there are nodes.
Then, for each node i we consider the neighbours j of i and we evaluate
the gain of modularity that would take place by removing i from its
community and by placing it in the community of j. The node i is then
placed in the community for which this gain is maximum (in the case of
a tie we use a breaking rule), but only if this gain is positive. If
no positive gain is possible, i stays in its original community. This
process is applied repeatedly and sequentially for all nodes until
no further improvement can be achieved and the first phase is then
complete.
Reference:
Blondel, Vincent D; Guillaume, Jean-Loup; Lambiotte, Renaud; Lefebvre, Etienne (9 October 2008). "Fast unfolding of communities in large networks". Journal of Statistical Mechanics: Theory and Experiment. 2008 (10): P10008. arXiv:0803.0476 Freely accessible. doi:10.1088/1742-5468/2008/10/P10008.
-}
{-# LANGUAGE ConstrainedClassMethods #-}
......@@ -20,24 +40,10 @@ module Data.Graph.Clustering.FLouvain
import Protolude
import Data.Graph.Inductive
-- Our algorithm is divided into two phases that are repeated
-- iteratively. Assume that we start with a weighted network of N nodes. First,
-- we assign a different community to each node of the network. So, in this
-- initial partition there are as many communities as there are nodes. Then, for
-- each node i we consider the neighbours j of i and we evaluate the gain of
-- modularity that would take place by removing i from its community and by
-- placing it in the community of j. The node i is then placed in the community
-- for which this gain is maximum (in the case of a tie we use a breaking rule),
-- but only if this gain is positive. If no positive gain is possible, i stays
-- in its original community. This process is applied repeatedly and
-- sequentially for all nodes until no further improvement can be achieved and
-- the first phase is then complete.
-- "glue" : function to gather/merge communities
-- "klue" : function to split communities
data ClusteringMethod = Glue | Klue
deriving (Eq)
-- | Find LNode of a node (i.e. a node with label)
......@@ -48,11 +54,11 @@ lnode cgr n = case lab cgr n of
-- We need to implement a fold over graph
type CFoldFun a b c = c -> Context a b -> c
type CFunFold a b c = Context a b -> c -> c
xdfsFoldWith :: (Graph gr)
=> CFun a b [Node]
-> CFoldFun a b c
=> CFun a b [Node]
-> CFunFold a b c
-> c
-> [Node]
-> gr a b
......@@ -60,7 +66,7 @@ xdfsFoldWith :: (Graph gr)
xdfsFoldWith _ _ acc [] _ = acc
xdfsFoldWith _ _ acc _ g | isEmpty g = acc
xdfsFoldWith d f acc (v:vs) g = case match v g of
(Just c, g') -> xdfsFoldWith d f (f acc c) (d c++vs) g'
(Just c, g') -> xdfsFoldWith d f (f c acc) (d c++vs) g'
(Nothing, g') -> xdfsFoldWith d f acc vs g'
......@@ -82,10 +88,10 @@ iteration :: (Graph gr) => gr a b -> CGr -> CGr
iteration gr cs = xdfsFoldWith suc' step cs (nodes gr) gr
-- TODO Remember to filter out empty Communities
step :: CFoldFun a b CGr
step cgr (p, v, l, s) = cgr
step :: CFunFold a b CGr
step (p, v, l, s) cgr = cgr
where
nc = nodeCommunity v cgr
nc = nodeCommunity v cgr
ncs = nodeNeighbours v cgr
-- TODO Compute \Delta Q (gain of moving node v into Community C) which consists of:
-- - Community WeightSum
......
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