]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Viz/Graph/MaxClique.hs
[WIP] G.P.Utils.shuffle + maxClique.
[gargantext.git] / src / Gargantext / Viz / Graph / MaxClique.hs
1 {-# LANGUAGE NoImplicitPrelude #-}
2
3 module Gargantext.Viz.Graph.MaxClique where
4
5 import Gargantext.Prelude
6 import Data.List (sortOn, nub)
7 import Data.Bool
8 import Data.Graph.Inductive hiding (Graph, neighbors, subgraph)
9 import qualified Data.Graph.Inductive as DGI
10 import Gargantext.Viz.Graph.FGL (Graph_Undirected, degree, neighbors, mkGraphUfromEdges)
11 import qualified Data.Set as Set
12
13 type Graph = Graph_Undirected
14 type Neighbor = Node
15
16 subgraph g ns = DGI.subgraph ns g
17
18 subGraphOn :: Graph -> Node -> Graph
19 subGraphOn g n = subgraph g (filter (/= n) $ neighbors g n)
20
21 maximalClique :: Graph -> [Node] -> [[Node]]
22 maximalClique _ [] = [[]]
23 maximalClique _ [n] = [[n]]
24
25 cliqueFinder :: Graph -> [[Node]]
26 cliqueFinder = undefined
27
28
29 {-
30 ------------------------------------------------------------------------
31 -- TODO: filter subset de cliques
32 maxClique :: Graph -> [[Node]]
33 maxClique g = filterClique g
34 $ map (maxCliqueOn g) (nodes g)
35
36 ------------------------------------------------------------------------
37
38 -- TODO: ask Bruno
39 -- copier python
40 filterClique :: Graph -> [Set.Set Node] -> [Set.Set Node]
41 filterClique = undefined
42
43 ------------------------------------------------------------------------
44
45 type CliqueMax = [Node]
46
47 maxCliqueOn :: Graph -> Node -> [CliqueMax]
48 maxCliqueOn = undefined
49
50 maxCliqueOn' :: Graph -> Node -> [Node] -> [CliqueMax]
51 maxCliqueOn' g n [] = [[n]]
52 maxCliqueOn' g n [m] = if (neighbors g n = [m])
53 then [n,m]
54 else maxCliqueOn' g n [] <> maxCliqueOn' g m []
55 maxCliqueOn' g n (x:xs) = undefined
56
57
58 stopClique :: Graph -> Node -> [Node] -> [Node]
59 -- no self, no reflexivity
60 stopClique _ n [] = [n]
61
62 stopClique g n [m] = if (neighbors g n) == [m]
63 then [n,m]
64 else []
65 stopClique g n ns = case all (\n' -> clique g n == clique g n') (x:xs) of
66 True -> n : ns
67 -- False -> stopClique g x xs
68 False -> stopClique g x xs
69 where
70 (x:xs) = sort g ns
71
72 subGraph :: Graph -> Node -> Graph
73 subGraph g n = mkGraphUfromEdges (edges voisin <> edges g n)
74
75 -}
76 ------------------------------------------------------------------------
77 -- Some Tools
78 --
79 {-
80 sortWith :: (Node -> Node -> Ord) -> Graph -> [Node] -> [Node]
81 sortWith f g ns = undefined
82 -}
83
84 sort :: Graph -> [Node] -> [Node]
85 sort _ [] = []
86 sort g ns = sortOn (degree g) ns
87
88 areEdged = areNeighbors
89 areNeighbors :: Graph -> Node -> Node -> Bool
90 areNeighbors g n m = neighbors g n == [m]
91
92 ------------------------------------------------------------------------
93
94 test_graph :: Graph
95 -- test_graph = mkGraphUfromEdges [(1,1), (2,2), (3,3)]
96 test_graph = mkGraphUfromEdges [(1,2), (3,3)]
97
98 test_graph' :: Graph
99 test_graph' = mkGraphUfromEdges [(1,2), (3,3), (3,2)]
100
101 test_graph'' :: Graph
102 test_graph'' = mkGraphUfromEdges [(1,2), (2,3), (1,3)]
103
104 test_graph''' :: Graph
105 test_graph''' = mkGraphUfromEdges [ (4,1)
106 , (4,2)
107 , (3,1)
108 , (3,2)
109 , (2,1)
110 ]