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

[ILouvain] doc + Class

parent 7d350225
...@@ -9,6 +9,10 @@ Portability : POSIX ...@@ -9,6 +9,10 @@ Portability : POSIX
ILouvain: really inductive Graph clustering with destructives updates ILouvain: really inductive Graph clustering with destructives updates
Metagraph:
metagraph (plural metagraphs) (mathematics) A graphical representation of a set of objects and the morphisms relating them
https://en.wiktionary.org/wiki/metagraph
todo FGL improvements: todo FGL improvements:
- deg should have return type Maybe Int - deg should have return type Maybe Int
- match should be Maybe (Context, Graph) - match should be Maybe (Context, Graph)
...@@ -30,22 +34,18 @@ import qualified Data.Graph.Clustering.HLouvain as H ...@@ -30,22 +34,18 @@ import qualified Data.Graph.Clustering.HLouvain as H
data NodePath = AllNodes | DfsNodes data NodePath = AllNodes | DfsNodes
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- HyperGraph Definition -- data MetaGraph = LabGraph (HyperGraph) | EdgeGraph (StreamGraph)
type HyperGraph' a b c = Gr (HyperGraph a b) c -- MetaGraph (x,y) where x is space (hyper structure of labels), y is
-- time like (stream structure)
-- (Below LabGraph definition)
type HyperGraph' a b c = HyperGraph (HyperGraph a b) c
type HyperGraph a b = Gr (Gr () a) b type HyperGraph a b = Gr (Gr () a) b
type HyperContext a b = Context (Gr () a) b type HyperContext a b = Context (Gr () a) b
-- TODO Later (hypothesis still)
-- type StreamGraph a b = Gr a (Gr () b)
-- TODO: EdgeGraph (StreamGraph)
-- type StreamGraph a b = Gr a (Gr () b)
------------------------------------------------------------------------ ------------------------------------------------------------------------
toNodes :: HyperGraph a a -> [[Node]]
toNodes g = map (hnodes g) (nodes g)
isFlat :: HyperGraph a b -> Bool
isFlat g = all (isEmpty . snd) (labNodes g)
------------------------------------------------------------------------ ------------------------------------------------------------------------
type MaxIterations = Int type MaxIterations = Int
type MaxSize = Int type MaxSize = Int
...@@ -154,11 +154,32 @@ stepMax g g' x xs = ...@@ -154,11 +154,32 @@ stepMax g g' x xs =
$ zip (x:xs) xs $ zip (x:xs) xs
------------------------------------------------------------------------ ------------------------------------------------------------------------
class IsHyperGraph a where
hnodes_ :: a -> Node -> [Node]
imodularity_ :: a -> a -> [Node] -> Double
gmodularity_ :: a -> a -> Double
toHyperGraph_ :: Gr () Double -> a
toNodes_ :: a -> [Node]
isFlat_ :: a -> Bool
------------------------------------------------------------------------
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 , _) -> []
(Just (p, n, l, s), _) -> n : nodes l (Just (p, n, l, s), _) -> n : nodes l
hnodes' :: HyperGraph' a b c -> Node -> [Node]
hnodes' g n = concat $ map (hnodes g) $ hnodes g n
------------------------------------------------------------------------
toNodes :: HyperGraph a a -> [[Node]]
toNodes g = map (hnodes g) (nodes g)
isFlat :: HyperGraph a b -> Bool
isFlat g = all (isEmpty . snd) (labNodes g)
{- {-
hdeg :: Graph gr => gr a b -> Node -> Maybe Int hdeg :: Graph gr => gr a b -> Node -> Maybe Int
hdeg = undefined hdeg = undefined
...@@ -172,13 +193,32 @@ imodularity g g' ns = -- trace ("imodul" :: Text) $ ...@@ -172,13 +193,32 @@ imodularity g g' ns = -- trace ("imodul" :: Text) $
$ concat $ concat
$ map (hnodes g') ns $ map (hnodes g') ns
imodularity' :: HyperGraph' a b c -> HyperGraph' a b c -> [Node] -> Double
imodularity' g g' ns =
H.hmodularity g
$ fromList
$ concat
$ map (hnodes' g') ns
gmodularity :: HyperGraph a b -> HyperGraph a a -> Double gmodularity :: HyperGraph a b -> HyperGraph a a -> Double
gmodularity g g' = sum $ map (\n -> imodularity g g' [n]) $ nodes g' gmodularity g g' = sum $ map (\n -> imodularity g g' [n]) $ nodes g'
gmodularity' :: HyperGraph' a b c -> HyperGraph' a b c -> Double
gmodularity' g g' = sum $ map (\n -> imodularity' g g' [n]) $ nodes g'
------------------------------------------------------------------------ ------------------------------------------------------------------------
toHyperGraph :: Gr () Double -> HyperGraph Double Double toHyperGraph :: Gr () Double -> HyperGraph Double Double
toHyperGraph g = nmap (\_ -> empty) g toHyperGraph g = nmap (\_ -> empty) g
emptyHyperGraph :: HyperGraph Double Double
emptyHyperGraph = toHyperGraph empty
{-
toHyperGraph' :: Gr () Double -> HyperGraph' Double Double Double
toHyperGraph' g = nmap (\_ -> emptyHyperGraph) g
-}
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- Spoon Graph -- Spoon Graph
-- 1 -- 1
......
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