Commit aaed14eb authored by Alexandre Delanoë's avatar Alexandre Delanoë

[ILouvain] basics function to render (still bug on karate).

parent 15a3031c
...@@ -14,7 +14,7 @@ module Data.Graph.Clustering.ILouvain ...@@ -14,7 +14,7 @@ module Data.Graph.Clustering.ILouvain
where where
import Data.Set (fromList) import Data.Set (fromList)
import Data.Maybe (catMaybes) import Data.Maybe (catMaybes, maybe)
import Data.List (zip, cycle) import Data.List (zip, cycle)
import Protolude hiding (empty, (&)) import Protolude hiding (empty, (&))
import Data.Graph.Inductive import Data.Graph.Inductive
...@@ -38,10 +38,15 @@ convergence g = if m - m' > 0.1 then g else g' ...@@ -38,10 +38,15 @@ convergence g = if m - m' > 0.1 then g else g'
steps :: HyperGraph a a -> [Node] -> HyperGraph a a iLouvain :: (Eq a) => HyperGraph a a -> [[Node]]
steps g [ ] = g iLouvain g = toNodes $ iLouvain' g $ path' g
steps g [_] = g where
steps g ns = foldl' (\g1 n -> step' g g1 n $ neighbors g1 n) g ns toNodes g = map (\n -> hnodes g n) (nodes g)
iLouvain' :: HyperGraph a a -> [Node] -> HyperGraph a a
iLouvain' g [ ] = g
iLouvain' g [_] = g
iLouvain' g ns = foldl' (\g1 n -> step' g g1 n $ neighbors g1 n) g ns
step' :: HyperGraph a b step' :: HyperGraph a b
-> HyperGraph a a -> HyperGraph a a
...@@ -64,7 +69,6 @@ step g g' n1 n2 = ...@@ -64,7 +69,6 @@ step g g' n1 n2 =
s2 = imodularity g [n1,n2] s2 = imodularity g [n1,n2]
------------------------------------------------------------------------ ------------------------------------------------------------------------
hnodes :: HyperGraph a b -> Node -> [Node] hnodes :: HyperGraph a b -> Node -> [Node]
hnodes g n = case match n g of hnodes g n = case match n g of
(Nothing, _) -> [] (Nothing, _) -> []
...@@ -78,6 +82,10 @@ hdeg = undefined ...@@ -78,6 +82,10 @@ hdeg = undefined
imodularity :: HyperGraph a b -> [Node] -> Double imodularity :: HyperGraph a b -> [Node] -> Double
imodularity g ns = H.modularity g (fromList ns) imodularity g ns = H.modularity g (fromList ns)
------------------------------------------------------------------------
toHyperGraph :: Gr () Double -> HyperGraph Double Double
toHyperGraph g = nmap (\_ -> empty) g
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- Spoon Graph -- Spoon Graph
-- 1 -- 1
...@@ -193,5 +201,9 @@ path g' = map sortNodes cs ...@@ -193,5 +201,9 @@ path g' = map sortNodes cs
Just n -> dfs [n] g -- dfs for glustering, bfs for klustering Just n -> dfs [n] g -- dfs for glustering, bfs for klustering
cs = components g cs = components g
g = undir g' g = undir g'
path' :: (DynGraph gr, Eq b) => gr a b -> [Node]
path' = maybe [] identity . head . path
------------------------------------------------------------------------ ------------------------------------------------------------------------
------------------------------------------------------------------------ ------------------------------------------------------------------------
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