1 {-| Module : Gargantext.Core.Viz.Graph.FGL
2 Description : FGL main functions used in Garg
3 Copyright : (c) CNRS, 2017-Present
4 License : AGPL + CECILL v3
5 Maintainer : team@gargantext.org
6 Stability : experimental
9 Main FGL funs/types to ease portability with IGraph.
13 {-# LANGUAGE ConstraintKinds #-}
15 module Gargantext.Core.Viz.Graph.FGL where
17 import Gargantext.Prelude
18 import qualified Data.Graph.Inductive as FGL
19 import qualified Data.List as List
20 ------------------------------------------------------------------
23 type Graph_Undirected = FGL.Gr () ()
24 type Graph_Directed = FGL.Gr () ()
26 type Graph = FGL.Graph
27 type Node = FGL.Node -- Int
28 type Edge = FGL.Edge -- (Int, Int)
30 ------------------------------------------------------------------
32 mkGraph :: [Node] -> [Edge] -> Graph_Undirected
33 mkGraph = FGL.mkUGraph
35 neighbors :: Graph gr => gr a b -> Node -> [Node]
36 neighbors = FGL.neighbors
38 -- | TODO bug: if graph is undirected, we need to filter
39 -- nub . (map (\(n1,n2) -> if n1 < n2 then (n1,n2) else (n2,n1))) . FGL.edges
40 edges :: Graph gr => gr a b -> [Edge]
43 nodes :: Graph gr => gr a b -> [Node]
46 ------------------------------------------------------------------------
49 filterNeighbors :: Graph_Undirected -> Node -> [Node]
50 filterNeighbors g n = List.nub $ neighbors g n
52 -- Q: why not D.G.I.deg ? (Int as result)
53 degree :: Graph_Undirected -> Node -> Double
54 degree g n = fromIntegral $ List.length (filterNeighbors g n)
56 vcount :: Graph_Undirected -> Double
57 vcount = fromIntegral . List.length . List.nub . nodes
59 -- | TODO tests, optim and use IGraph library, fix IO ?
60 ecount :: Graph_Undirected -> Double
61 ecount = fromIntegral . List.length . List.nub . edges
64 ------------------------------------------------------------------
65 -- | Main sugared functions
66 mkGraphUfromEdges :: [(Int, Int)] -> Graph_Undirected
67 mkGraphUfromEdges es = mkGraph ns es
69 ns = List.nub (a <> b)
71 (a, b) = List.unzip es