Commit 38684ec5 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

Merge branch 'flouvain' of ssh://gitlab.iscpif.fr:20022/gargantext/clustering-louvain into flouvain

parents 3296a916 c351e21d
...@@ -20,14 +20,14 @@ import qualified Text.Parsec.Token as PT ...@@ -20,14 +20,14 @@ import qualified Text.Parsec.Token as PT
iterateOnce :: Gr () Double -> CGr iterateOnce :: Gr () Double -> CGr
iterateOnce gr = iteration fgr cgr iterateOnce gr = iteration fgr cgr
where where
fgr = exampleRemap gr fgr = toFGraph gr
cgr = initialCGr fgr cgr = initialCGr fgr
runIterations :: Int -> Gr () Double -> IO () runIterations :: Int -> Gr () Double -> IO ()
runIterations n gr = do runIterations n gr = do
let fgr = exampleRemap gr let fgr = toFGraph gr
let fgrWeight = graphWeight fgr let fgrWeight = graphWeight fgr
let initCgr = initialCGr fgr let initCgr = initialCGr fgr
putStrLn ("Initial modularity: " :: Text) putStrLn ("Initial modularity: " :: Text)
putStrLn $ T.unpack $ show $ modularity fgr initCgr fgrWeight putStrLn $ T.unpack $ show $ modularity fgr initCgr fgrWeight
...@@ -53,9 +53,9 @@ runIterations n gr = do ...@@ -53,9 +53,9 @@ runIterations n gr = do
runLouvainFirstStepIterate :: Int -> Gr () Double -> (Modularity, CGr) runLouvainFirstStepIterate :: Int -> Gr () Double -> (Modularity, CGr)
runLouvainFirstStepIterate n gr = (modularity fgr cgr m, cgr) runLouvainFirstStepIterate n gr = (modularity fgr cgr m, cgr)
where where
fgr = exampleRemap gr fgr = toFGraph gr
cgr = louvainFirstStepIterate n fgr cgr = louvainFirstStepIterate n fgr
m = graphWeight fgr m = graphWeight fgr
-- | egr <- readPythonGraph "<file-path>" -- | egr <- readPythonGraph "<file-path>"
-- let gr = head $ Data.Either.rights [egr] -- let gr = head $ Data.Either.rights [egr]
...@@ -145,9 +145,7 @@ gU = mkGraph' eU ...@@ -145,9 +145,7 @@ gU = mkGraph' eU
cuiller :: Gr () Double cuiller :: Gr () Double
cuiller = gU cuiller = gU
-- Visual representation: -- Visual representation:
--
-- 2 -- 2
-- / \ -- / \
-- 1 3 -- 1 3
......
...@@ -54,7 +54,10 @@ data ClusteringMethod = Glue | Klue ...@@ -54,7 +54,10 @@ data ClusteringMethod = Glue | Klue
-- 'a' is the initial value -- 'a' is the initial value
fixPt :: Int -> (a -> a) -> (a -> Bool) -> a -> a fixPt :: Int -> (a -> a) -> (a -> Bool) -> a -> a
fixPt 0 iterator _ init = iterator init fixPt 0 iterator _ init = iterator init
fixPt n iterator cond init = if cond next then fixPt (n - 1) iterator cond init else next fixPt n iterator cond init =
if cond next
then fixPt (n - 1) iterator cond init
else next
where where
next = iterator init next = iterator init
...@@ -62,10 +65,10 @@ fixPt n iterator cond init = if cond next then fixPt (n - 1) iterator cond init ...@@ -62,10 +65,10 @@ fixPt n iterator cond init = if cond next then fixPt (n - 1) iterator cond init
louvainFirstStepIterate :: Int -> FGraph a b -> CGr louvainFirstStepIterate :: Int -> FGraph a b -> CGr
louvainFirstStepIterate n gr = fixPt n iterator cond initCGr louvainFirstStepIterate n gr = fixPt n iterator cond initCGr
where where
initCGr = initialCGr gr initCGr = initialCGr gr
grWeight = graphWeight gr grWeight = graphWeight gr
iterator cgr = iteration gr cgr iterator cgr = iteration gr cgr
cond cgr = (unModularity $ modularity gr cgr grWeight) < 0.1 cond cgr = (unModularity $ modularity gr cgr grWeight) < 0.1
------------------------------------------------------------------------ ------------------------------------------------------------------------
......
...@@ -84,7 +84,7 @@ mv g [a,b] [ ] = case match a g of ...@@ -84,7 +84,7 @@ mv g [a,b] [ ] = case match a g of
(Just (p, n, l, s), g1) -> case match b l of (Just (p, n, l, s), g1) -> case match b l of
(Nothing, _) -> panic "mv: snd Node of Path does not exist" (Nothing, _) -> panic "mv: snd Node of Path does not exist"
(Just (p',n',l',s'), g2) -> (p', n', g2 , s') (Just (p',n',l',s'), g2) -> (p', n', g2 , s')
-- & (p , n , empty, s ) -- & (p , n , delNode b l, s )
& g1 & g1
mv g (x:xs) (y:ys) = panic "mv: path too long" mv g (x:xs) (y:ys) = panic "mv: path too long"
......
...@@ -19,10 +19,11 @@ References: ...@@ -19,10 +19,11 @@ References:
module Data.Graph.Clustering.Louvain module Data.Graph.Clustering.Louvain
where where
import Data.Tuple.Extra (fst3)
import Data.List (maximumBy, nub, intersect, foldl', zipWith, concat) import Data.List (maximumBy, nub, intersect, foldl', zipWith, concat)
import Data.Graph.Inductive import Data.Graph.Inductive
import Data.Graph.Clustering.Louvain.Utils (LouvainNode(..)) import Data.Graph.Clustering.Louvain.Utils (LouvainNode(..), toFGraph)
import Data.Graph.Clustering.FLouvain (louvainFirstStepIterate, Community(..), initialCGr)
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | Definitions -- | Definitions
------------------------------------------------------------------------ ------------------------------------------------------------------------
...@@ -32,6 +33,11 @@ type Community = [Node] ...@@ -32,6 +33,11 @@ type Community = [Node]
-- type Partition = [Community] -- type Partition = [Community]
type Reverse = Bool type Reverse = Bool
------------------------------------------------------------------------
flouvain :: Int -> Gr () Double -> [[Node]]
flouvain n g = map (fst3 . unCommunity . snd) $ labNodes g'
where
g' = louvainFirstStepIterate n (toFGraph g)
------------------------------------------------------------------------ ------------------------------------------------------------------------
hLouvain :: (Eq b, DynGraph gr) hLouvain :: (Eq b, DynGraph gr)
=> Reverse => Reverse
...@@ -42,7 +48,6 @@ hLouvain r g = concat $ toLouvainNode (bestpartition r g) ...@@ -42,7 +48,6 @@ hLouvain r g = concat $ toLouvainNode (bestpartition r g)
toLouvainNode :: [[Node]] -> [[LouvainNode]] toLouvainNode :: [[Node]] -> [[LouvainNode]]
toLouvainNode ns = zipWith (\cId ns' -> map (\n -> LouvainNode n cId) ns') toLouvainNode ns = zipWith (\cId ns' -> map (\n -> LouvainNode n cId) ns')
[1..] ns [1..] ns
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | Partitionning the graph -- | Partitionning the graph
------------------------------------------------------------------------ ------------------------------------------------------------------------
......
...@@ -46,16 +46,16 @@ map2graph m = mkGraph' $ map (\((n1,n2), w) -> (n1,n2,w)) $ Map.toList m ...@@ -46,16 +46,16 @@ map2graph m = mkGraph' $ map (\((n1,n2), w) -> (n1,n2,w)) $ Map.toList m
mkFGraph :: [LNode a] -> [LEdge Double] -> FGraph a () mkFGraph :: [LNode a] -> [LEdge Double] -> FGraph a ()
mkFGraph ns es = exampleRemap $ mkGraph ns es mkFGraph ns es = toFGraph $ mkGraph ns es
mkFGraph' :: [LEdge Double] -> FGraph () () mkFGraph' :: [LEdge Double] -> FGraph () ()
mkFGraph' = exampleRemap . mkGraph' mkFGraph' = toFGraph . mkGraph'
-- | Utility function to remap Gr () Double into FGraph () () -- | Utility function to remap Gr () Double into FGraph () ()
exampleRemap :: forall a. Gr a Double -> FGraph a () toFGraph :: forall a. Gr a Double -> FGraph a ()
exampleRemap gr = gmap remap gr toFGraph gr = gmap remap gr
where where
remap :: Context a Double -> Context a (Weight, ()) remap :: Context a Double -> Context a (Weight, ())
remap (p, v, l, s) = (p', v, l, s') remap (p, v, l, s) = (p', v, l, s')
......
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