Commit 6fa712b5 authored by delanoe's avatar delanoe

FIX : nub

parent 89f88ad5
module Data.Louvain where
import Data.Utils
import Data.List (maximumBy,nub)
import Data.Graph.Inductive
......@@ -11,7 +10,7 @@ inducedGraph :: (Eq b, Ord b, DynGraph gr) => gr a b -> (Node, [Node]) -> gr a b
inducedGraph gr (a,b) = delNodes b (insEdges newEdges gr')
where
gr' = undir gr
newEdges = Prelude.map (\(n,l) -> (a,n,l)) ( uniq $ concat $ Prelude.map (lsuc gr') b )
newEdges = Prelude.map (\(n,l) -> (a,n,l)) ( nub $ concat $ Prelude.map (lsuc gr') b )
-- | TODO exducedGraph (inverse for tests with quickCheck)
inducedGraph' :: (Ord b, DynGraph gr) => gr a b -> [(Node, [Node])] -> gr a b
......
module Data.Utils where
import Data.Graph.Inductive
import Data.Set as S (toList, fromList)
import qualified Data.List (nub)
import Data.List (nub)
label' :: (Graph gr) => gr a b -> Edge -> Maybe b
......
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