Commit 16693beb authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FEAT] IGraph partitions complement

parent a71297fb
Pipeline #1419 canceled with stage
...@@ -27,7 +27,7 @@ import Gargantext.Core.Methods.Graph.BAC.Proxemy (confluence) ...@@ -27,7 +27,7 @@ import Gargantext.Core.Methods.Graph.BAC.Proxemy (confluence)
import Gargantext.Core.Statistics import Gargantext.Core.Statistics
import Gargantext.Core.Viz.Graph import Gargantext.Core.Viz.Graph
import Gargantext.Core.Viz.Graph.Bridgeness (bridgeness) import Gargantext.Core.Viz.Graph.Bridgeness (bridgeness)
import Gargantext.Core.Viz.Graph.IGraph (mkGraphUfromEdges) import Gargantext.Core.Viz.Graph.Tools.IGraph (mkGraphUfromEdges)
import Gargantext.Core.Viz.Graph.Index (createIndices, toIndex, map2mat, mat2map, Index) import Gargantext.Core.Viz.Graph.Index (createIndices, toIndex, map2mat, mat2map, Index)
import Gargantext.Prelude import Gargantext.Prelude
import IGraph.Random -- (Gen(..)) import IGraph.Random -- (Gen(..))
......
{-| Module : Gargantext.Core.Viz.Graph.IGraph {-|
Description : IGraph main functions used in Garg Module : Gargantext.Core.Viz.Graph.Tools.IGraph
Description : Tools to build Graph
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
Maintainer : team@gargantext.org Maintainer : team@gargantext.org
Stability : experimental Stability : experimental
Portability : POSIX Portability : POSIX
Main IGraph funs/types to ease portability with FGL.
Reference: Reference:
* Gábor Csárdi, Tamás Nepusz: The igraph software package for complex network research. InterJournal Complex Systems, 1695, 2006. * Gábor Csárdi, Tamás Nepusz: The igraph software package for complex network research. InterJournal Complex Systems, 1695, 2006.
-} -}
module Gargantext.Core.Viz.Graph.IGraph where module Gargantext.Core.Viz.Graph.Tools.IGraph
where
import Data.Serialize (Serialize) import Data.Serialize
import Data.Singletons (SingI) import Data.Singletons (SingI)
import Gargantext.Prelude
import IGraph hiding (mkGraph, neighbors, edges, nodes, Node, Graph) import IGraph hiding (mkGraph, neighbors, edges, nodes, Node, Graph)
import IGraph.Algorithms.Clique as IAC import Protolude
import qualified IGraph as IG import qualified Data.List as List
import qualified Data.List as List import qualified IGraph as IG
import qualified IGraph.Algorithms.Clique as IG
import qualified IGraph.Algorithms.Community as IG
import qualified IGraph.Random as IG
------------------------------------------------------------------ ------------------------------------------------------------------
-- | Main Types -- | Main Types
type Graph_Undirected = IG.Graph 'U () () type Graph_Undirected = IG.Graph 'U () ()
type Graph_Directed = IG.Graph 'D () () type Graph_Directed = IG.Graph 'D () ()
type Node = IG.Node type Node = IG.Node
type Graph = IG.Graph type Graph = IG.Graph
------------------------------------------------------------------ ------------------------------------------------------------------
-- | Main Functions -- | Main Graph management Functions
neighbors :: IG.Graph d v e -> IG.Node -> [IG.Node]
mkGraph :: (SingI d, Ord v,
Serialize v, Serialize e) =>
[v] -> [LEdge e] -> IG.Graph d v e
mkGraph = IG.mkGraph
neighbors :: IG.Graph d v e -> IG.Node -> [Node]
neighbors = IG.neighbors neighbors = IG.neighbors
edges :: IG.Graph d v e -> [Edge] edges :: IG.Graph d v e -> [Edge]
edges = IG.edges edges = IG.edges
nodes :: IG.Graph d v e -> [Node] nodes :: IG.Graph d v e -> [IG.Node]
nodes = IG.nodes nodes = IG.nodes
------------------------------------------------------------------
-- | Tools ------------------------------------------------------------------
-- | Partitions
maximalCliques :: IG.Graph d v e -> [[Int]] maximalCliques :: IG.Graph d v e -> [[Int]]
maximalCliques g = IAC.maximalCliques g (min',max') maximalCliques g = IG.maximalCliques g (min',max')
where where
min' = 0 min' = 0
max' = 0 max' = 0
------------------------------------------------------------------ ------------------------------------------------------------------
-- | Main sugared functions type Seed = Int
-- | Tools to analyze graphs
partitions_spinglass :: (Serialize v, Serialize e)
=> Seed -> IG.Graph 'U v e -> IO [[Int]]
partitions_spinglass s g = do
gen <- IG.withSeed s pure
pure $ IG.findCommunity g Nothing Nothing IG.spinglass gen
------------------------------------------------------------------
mkGraph :: (SingI d, Ord v,
Serialize v, Serialize e) =>
[v] -> [LEdge e] -> IG.Graph d v e
mkGraph = IG.mkGraph
------------------------------------------------------------------
mkGraphUfromEdges :: [(Int, Int)] -> Graph_Undirected mkGraphUfromEdges :: [(Int, Int)] -> Graph_Undirected
mkGraphUfromEdges es = mkGraph (List.replicate n ()) $ zip es $ repeat () mkGraphUfromEdges es = mkGraph (List.replicate n ()) $ zip es $ repeat ()
where where
......
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