1 {-| Module : Gargantext.Core.Viz.Graph.MaxClique
2 Description : MaxCliques function
3 Copyright : (c) CNRS, 2017-Present
4 License : AGPL + CECILL v3
5 Maintainer : team@gargantext.org
6 Stability : experimental
9 - Result of the workshop, Pyremiel 2019
10 - First written by Bruno Gaume in Python (see below for details)
11 - Then written by Alexandre Delanoë in Haskell (see below for details)
14 def fast_maximal_cliques(g):
16 def rec_maximal_cliques(g, subv):
18 if subv == []: # stop condition
21 for i in range(len(subv)):
22 newsubv = [j for j in subv[i+1:len(subv)]
23 if (j in g.neighbors(subv[i]))]
24 mci = rec_maximal_cliques(g, newsubv)
31 clustset = [set(x) for x in clust]
33 for i in range(len(clustset)):
35 for j in range(len(clustset)):
36 if clustset[i].issubset(clustset[j]) and (not (len(clustset[i]) == len(clustset[j])) ):
38 if ok and (not (clustset[i] in new_clust)):
39 new_clust.append(clustset[i])
40 return [list(x) for x in new_clust]
42 # to optimize : rank the vertices on the degrees
43 subv = [(v.index, v.degree()) for v in g.vs()]
44 subv.sort(key = lambda z:z[1])
45 subv = [x for (x, y) in subv]
46 return purge(rec_maximal_cliques(g, subv))
52 module Gargantext.Core.Methods.Graph.MaxClique
55 import Data.Maybe (catMaybes)
56 import Gargantext.Prelude
58 import qualified Data.Map as Map
59 import Data.List (sortOn, nub, concat)
61 import Data.Set (fromList, toList, isSubsetOf)
62 import Data.Graph.Inductive hiding (Graph, neighbors, subgraph, (&))
63 import Gargantext.Core.Viz.Graph.FGL (Graph_Undirected, degree, neighbors, mkGraphUfromEdges)
64 import Gargantext.Core.Viz.Graph.Tools (cooc2graph',cooc2graph'', Threshold)
65 import Gargantext.Core.Methods.Distances (Distance)
66 import Gargantext.Core.Viz.Graph.Index (createIndices, toIndex)
67 import Gargantext.Core.Viz.Phylo
68 -- import Debug.Trace (trace)
69 type Graph = Graph_Undirected
73 -- TODO chose distance order
75 getMaxCliques :: Ord a => CliqueFilter -> Distance -> Threshold -> Map (a, a) Int -> [[a]]
76 getMaxCliques f d t m = map fromIndices $ getMaxCliques' t m'
79 (to,from) = createIndices m
80 fromIndices = catMaybes . map (\n -> Map.lookup n from)
82 getMaxCliques' :: Threshold -> Map (Int, Int) Int -> [[Int]]
83 getMaxCliques' t' n = maxCliques graph
85 graph = mkGraphUfromEdges (Map.keys n')
86 -- n' = cooc2graph' d t' n
87 n' = case f of ByThreshold -> cooc2graph' d t' n
88 ByNeighbours -> cooc2graph'' d t' n
91 maxCliques :: Graph -> [[Node]]
92 maxCliques g = map (\n -> subMaxCliques g (n:ns)) ns & concat & takeMax
95 ns = sortOn (degree g) $ nodes g
97 subMaxCliques :: Graph -> [Node] -> [[Node]]
98 subMaxCliques _ [] = [[]]
99 subMaxCliques g' (x:xs) = add x $ subMaxCliques g' ns'
101 ns' = [n | n <- xs, elem n $ neighborsOut g' x]
103 add :: Node -> [[Node]] -> [[Node]]
105 add n (m:ms) = [n:m] <> add n ms
106 -- | Note, it is same as :
107 -- add n ns = map (\m -> n : m) ns
108 -- -- (but using pattern matching and recursivity)
109 -- -- (map is redefined in fact)
111 -- | To be sure self is not in neighbors of self
112 -- (out to exclude the self)
113 neighborsOut :: Graph -> Node -> [Node]
114 neighborsOut g'' n = filter (/= n) $ neighbors g'' n
117 takeMax :: [[Node]] -> [[Node]]
124 purge :: [Set Node] -> [Set Node]
126 purge (x:xs) = x' <> purge xs
128 x' = if all (== False) (map (isSubsetOf x) xs)
133 ------------------------------------------------------------------------
135 -- test_graph = mkGraphUfromEdges [(1,1), (2,2), (3,3)]
136 test_graph = mkGraphUfromEdges [(1,2), (3,3)]
139 test_graph' = mkGraphUfromEdges [(1,2), (3,3), (3,2)]
141 test_graph'' :: Graph
142 test_graph'' = mkGraphUfromEdges [(1,2), (2,3), (1,3)]
144 test_graph''' :: Graph
145 test_graph''' = mkGraphUfromEdges [ (4,1)