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

[COSMETICS] max cliques, cut function lines.

parent 10564410
......@@ -49,7 +49,8 @@ def fast_maximal_cliques(g):
{-# LANGUAGE NoImplicitPrelude #-}
module Gargantext.Viz.Graph.MaxClique where
module Gargantext.Viz.Graph.MaxClique
where
import Gargantext.Prelude
import Data.List (sortOn, nub, concat, length)
......@@ -59,7 +60,6 @@ import Data.Graph.Inductive hiding (Graph, neighbors, subgraph, (&))
import Gargantext.Viz.Graph.FGL (Graph_Undirected, degree, neighbors, mkGraphUfromEdges)
type Graph = Graph_Undirected
type Neighbor = Node
......@@ -90,7 +90,11 @@ maxCliques g = map (\n -> subMaxCliques g (n:ns)) ns & concat & takeMax
takeMax :: [[Node]] -> [[Node]]
takeMax = map toList . purge . map fromList . sortOn length . nub
takeMax = map toList
. purge
. map fromList
. sortOn length
. nub
where
purge :: [Set Node] -> [Set Node]
purge [] = []
......
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