Commit 66d5c192 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[WIP] G.P.Utils.shuffle + maxClique.

parent eeeb82c8
......@@ -160,6 +160,8 @@ library:
- profunctors
- protolude
- pureMD5
- random-shuffle
- MonadRandom
- SHA
- simple-reflect
- cereal # (IGraph)
......
......@@ -18,17 +18,24 @@ module Gargantext.Prelude.Utils
import Control.Lens (view)
import Control.Monad.Reader (MonadReader)
import Control.Monad.IO.Class (MonadIO, liftIO)
import Control.Monad.Random.Class (MonadRandom)
import Data.Text (Text)
import Control.Monad.Reader (ask)
import GHC.IO (FilePath)
import Gargantext.Prelude
import Gargantext.API.Settings
import System.Random (newStdGen)
import qualified System.Random.Shuffle as SRS
import System.Directory (createDirectoryIfMissing)
import qualified Data.ByteString.Lazy.Char8 as Char
import qualified Data.Digest.Pure.SHA as SHA (sha256, showDigest)
import qualified Data.Text as Text
shuffle :: MonadRandom m => [a] -> m [a]
shuffle ns = SRS.shuffleM ns
type FolderPath = FilePath
type FileName = FilePath
......
......@@ -45,6 +45,24 @@ edges = FGL.edges
nodes :: Graph gr => gr a b -> [Node]
nodes = FGL.nodes
------------------------------------------------------------------------
-- | Graph Tools
filterNeighbors :: Graph_Undirected -> Node -> [Node]
filterNeighbors g n = List.nub $ neighbors g n
-- Q: why not D.G.I.deg ? (Int as result)
degree :: Graph_Undirected -> Node -> Double
degree g n = fromIntegral $ List.length (filterNeighbors g n)
vcount :: Graph_Undirected -> Double
vcount = fromIntegral . List.length . List.nub . nodes
-- | TODO tests, optim and use IGraph library, fix IO ?
ecount :: Graph_Undirected -> Double
ecount = fromIntegral . List.length . List.nub . edges
------------------------------------------------------------------
-- | Main sugared functions
......
......@@ -19,6 +19,7 @@ import Data.Serialize (Serialize)
import Data.Singletons (SingI)
import Gargantext.Prelude
import IGraph hiding (mkGraph, neighbors, edges, nodes, Node, Graph)
import IGraph.Algorithms.Clique as IAC
import qualified IGraph as IG
import qualified Data.List as List
......@@ -46,10 +47,17 @@ edges = IG.edges
nodes :: IG.Graph d v e -> [Node]
nodes = IG.nodes
------------------------------------------------------------------
-- | Tools
maximalCliques :: IG.Graph d v e -> [[Int]]
maximalCliques g = IAC.maximalCliques g (min,max)
where
min = 0
max = 0
------------------------------------------------------------------
-- | Main sugared functions
mkGraphUfromEdges :: [(Int, Int)] -> Graph_Undirected
mkGraphUfromEdges es = mkGraph (List.replicate n ()) $ zip es $ repeat ()
where
......
{-# LANGUAGE NoImplicitPrelude #-}
module Gargantext.Viz.Graph.MaxClique where
import Gargantext.Prelude
import Data.List (sortOn, nub)
import Data.Bool
import Data.Graph.Inductive hiding (Graph, neighbors, subgraph)
import qualified Data.Graph.Inductive as DGI
import Gargantext.Viz.Graph.FGL (Graph_Undirected, degree, neighbors, mkGraphUfromEdges)
import qualified Data.Set as Set
type Graph = Graph_Undirected
type Neighbor = Node
subgraph g ns = DGI.subgraph ns g
subGraphOn :: Graph -> Node -> Graph
subGraphOn g n = subgraph g (filter (/= n) $ neighbors g n)
maximalClique :: Graph -> [Node] -> [[Node]]
maximalClique _ [] = [[]]
maximalClique _ [n] = [[n]]
cliqueFinder :: Graph -> [[Node]]
cliqueFinder = undefined
{-
------------------------------------------------------------------------
-- TODO: filter subset de cliques
maxClique :: Graph -> [[Node]]
maxClique g = filterClique g
$ map (maxCliqueOn g) (nodes g)
------------------------------------------------------------------------
-- TODO: ask Bruno
-- copier python
filterClique :: Graph -> [Set.Set Node] -> [Set.Set Node]
filterClique = undefined
------------------------------------------------------------------------
type CliqueMax = [Node]
maxCliqueOn :: Graph -> Node -> [CliqueMax]
maxCliqueOn = undefined
maxCliqueOn' :: Graph -> Node -> [Node] -> [CliqueMax]
maxCliqueOn' g n [] = [[n]]
maxCliqueOn' g n [m] = if (neighbors g n = [m])
then [n,m]
else maxCliqueOn' g n [] <> maxCliqueOn' g m []
maxCliqueOn' g n (x:xs) = undefined
stopClique :: Graph -> Node -> [Node] -> [Node]
-- no self, no reflexivity
stopClique _ n [] = [n]
stopClique g n [m] = if (neighbors g n) == [m]
then [n,m]
else []
stopClique g n ns = case all (\n' -> clique g n == clique g n') (x:xs) of
True -> n : ns
-- False -> stopClique g x xs
False -> stopClique g x xs
where
(x:xs) = sort g ns
subGraph :: Graph -> Node -> Graph
subGraph g n = mkGraphUfromEdges (edges voisin <> edges g n)
-}
------------------------------------------------------------------------
-- Some Tools
--
{-
sortWith :: (Node -> Node -> Ord) -> Graph -> [Node] -> [Node]
sortWith f g ns = undefined
-}
sort :: Graph -> [Node] -> [Node]
sort _ [] = []
sort g ns = sortOn (degree g) ns
areEdged = areNeighbors
areNeighbors :: Graph -> Node -> Node -> Bool
areNeighbors g n m = neighbors g n == [m]
------------------------------------------------------------------------
test_graph :: Graph
-- test_graph = mkGraphUfromEdges [(1,1), (2,2), (3,3)]
test_graph = mkGraphUfromEdges [(1,2), (3,3)]
test_graph' :: Graph
test_graph' = mkGraphUfromEdges [(1,2), (3,3), (3,2)]
test_graph'' :: Graph
test_graph'' = mkGraphUfromEdges [(1,2), (2,3), (1,3)]
test_graph''' :: Graph
test_graph''' = mkGraphUfromEdges [ (4,1)
, (4,2)
, (3,1)
, (3,2)
, (2,1)
]
......@@ -95,7 +95,11 @@ prox_markov g ns l r nf = foldl' (\m _ -> spreading g m r nf) ms path
_ -> Map.empty
spreading :: Graph_Undirected -> Map Node Double -> FalseReflexive -> NeighborsFilter -> Map Node Double
spreading :: Graph_Undirected
-> Map Node Double
-> FalseReflexive
-> NeighborsFilter
-> Map Node Double
spreading g ms r nf = Map.fromListWith (+) $ List.concat $ map pvalue (Map.keys ms)
where
-- TODO if list empty ...
......@@ -107,22 +111,6 @@ spreading g ms r nf = Map.fromListWith (+) $ List.concat $ map pvalue (Map.keys
neighborhood = (nf g n) <> (if r then [n] else [])
------------------------------------------------------------------------
-- | Graph Tools
filterNeighbors :: Graph_Undirected -> Node -> [Node]
filterNeighbors g n = List.nub $ neighbors g n
degree :: Graph_Undirected -> Node -> Double
degree g n = fromIntegral $ List.length (filterNeighbors g n)
vcount :: Graph_Undirected -> Double
vcount = fromIntegral . List.length . List.nub . nodes
-- | TODO tests, optim and use IGraph library, fix IO ?
ecount :: Graph_Undirected -> Double
ecount = fromIntegral . List.length . List.nub . edges
------------------------------------------------------------------------
-- | Behavior tests
......
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