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

[FEAT] getMaxCliques function.

parent 70a2339e
Pipeline #746 failed with stage
......@@ -25,12 +25,11 @@ type Graph_Undirected = FGL.Gr () ()
type Graph_Directed = FGL.Gr () ()
type Graph = FGL.Graph
type Node = FGL.Node
type Edge = FGL.Edge
type Node = FGL.Node -- Int
type Edge = FGL.Edge -- (Int, Int)
------------------------------------------------------------------
-- | Main Functions
mkGraph :: [Node] -> [Edge] -> Graph_Undirected
mkGraph = FGL.mkUGraph
......
......@@ -52,35 +52,35 @@ def fast_maximal_cliques(g):
module Gargantext.Viz.Graph.MaxClique
where
import Data.Maybe (catMaybes)
import Gargantext.Prelude
import Data.Map (Map)
import qualified Data.Map as Map
import Data.List (sortOn, nub, concat, length)
import Data.Set (Set)
import Data.Set (fromList, toList, isSubsetOf)
import Data.Graph.Inductive hiding (Graph, neighbors, subgraph, (&))
import Gargantext.Viz.Graph.FGL (Graph_Undirected, degree, neighbors, mkGraphUfromEdges)
import Gargantext.Viz.Graph.Tools (cooc2graph', Threshold)
import Gargantext.Viz.Graph.Index (createIndices, toIndex)
type Graph = Graph_Undirected
type Neighbor = Node
{-
-- prefiltre
-- Texte -> Ngrams
-- Map Terms
-- pré-filtre: spécifiques
-- soit conditionnelle, matrice spécifiques
-- combien de voisins maximum avant le calcul de cliques (les génériques)
-- calcul maxcliques
-- calcul de densité/inclusion si graph gros
--
-- FIS: ensemble de termes un niveau du document
-- maxclique: ensemble de termes au niveau de l'ensemble du document
type Density = Double
maxCliques' :: [[Text]] -> Map (Set Ngrams) Density
maxCliques' = undefined
-}
-- | getMaxCliques
-- TODO chose distance order
getMaxCliques :: Ord a => Threshold -> Map (a, a) Int -> [[a]]
getMaxCliques t m = map fromIndices $ getMaxCliques' t m'
where
m' = toIndex to m
(to,from) = createIndices m
fromIndices = catMaybes . map (\n -> Map.lookup n from)
getMaxCliques' :: Threshold -> Map (Int, Int) Int -> [[Int]]
getMaxCliques' t' n = maxCliques graph
where
graph = mkGraphUfromEdges (Map.keys n')
n' = cooc2graph' t' n
maxCliques :: Graph -> [[Node]]
maxCliques g = map (\n -> subMaxCliques g (n:ns)) ns & concat & takeMax
......
......@@ -26,7 +26,7 @@ import Gargantext.Core.Statistics
import Gargantext.Viz.Graph
import Gargantext.Viz.Graph.Bridgeness (bridgeness)
import Gargantext.Viz.Graph.Distances.Matrice (measureConditional)
import Gargantext.Viz.Graph.Index (createIndices, toIndex, map2mat, mat2map)
import Gargantext.Viz.Graph.Index (createIndices, toIndex, map2mat, mat2map, Index)
import Gargantext.Viz.Graph.IGraph (mkGraphUfromEdges)
import Gargantext.Viz.Graph.Proxemy (confluence)
import GHC.Float (sin, cos)
......@@ -38,6 +38,19 @@ import qualified Data.List as List
type Threshold = Double
cooc2graph' :: Ord t => Double
-> Map (t, t) Int
-> Map (Index, Index) Double
cooc2graph' threshold myCooc = distanceMap
where
(ti, _) = createIndices myCooc
myCooc' = toIndex ti myCooc
matCooc = map2mat 0 (Map.size ti) $ Map.filter (> 1) myCooc'
distanceMat = measureConditional matCooc
distanceMap = Map.filter (> threshold) $ mat2map distanceMat
cooc2graph :: Threshold
-> (Map (Text, Text) Int)
-> IO Graph
......@@ -60,13 +73,14 @@ cooc2graph threshold myCooc = do
True -> trace ("level" <> show level) $ cLouvain level distanceMap
False -> panic "Text.Flow: DistanceMap is empty"
let bridgeness' = {-trace ("rivers: " <> show rivers) $-} bridgeness rivers partitions distanceMap
let bridgeness' = {-trace ("rivers: " <> show rivers) $-}
bridgeness rivers partitions distanceMap
let confluence' = confluence (Map.keys bridgeness') 3 True False
data2graph (Map.toList ti) myCooc' bridgeness' confluence' partitions
data ClustersParams = ClustersParams { bridgness :: Double
, louvain :: Text
} deriving (Show)
......
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