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

[FIX] graph generation

parent 963e28f6
...@@ -158,7 +158,7 @@ library: ...@@ -158,7 +158,7 @@ library:
- full-text-search - full-text-search
- fullstop - fullstop
- gargantext-prelude - gargantext-prelude
- gargantext-graph >= 0.1.0.0 # - gargantext-graph >= 0.1.0.0
- graphviz - graphviz
- hashable - hashable
- haskell-igraph - haskell-igraph
......
...@@ -189,8 +189,10 @@ computeGraph cId d nt repo = do ...@@ -189,8 +189,10 @@ computeGraph cId d nt repo = do
listNgrams <- getListNgrams [lId] nt listNgrams <- getListNgrams [lId] nt
-- graph <- liftBase $ cooc2graphWith Bac d 0 myCooc
graph <- liftBase $ cooc2graphWith Spinglass d 0 myCooc graph <- liftBase $ cooc2graphWith Spinglass d 0 myCooc
-- saveAsFileDebug "debug/graph" graph -- saveAsFileDebug "debug/graph" graph
pure $ mergeGraphNgrams graph (Just listNgrams) pure $ mergeGraphNgrams graph (Just listNgrams)
......
...@@ -24,7 +24,9 @@ import Data.Maybe (catMaybes) ...@@ -24,7 +24,9 @@ import Data.Maybe (catMaybes)
import Data.Ord (Down(..)) import Data.Ord (Down(..))
import Gargantext.Prelude import Gargantext.Prelude
import qualified Data.Map as DM import qualified Data.Map as DM
import Graph.Types (ClusterNode(..)) import Gargantext.Core.Viz.Graph.Types (ClusterNode(..))
---------------------------------------------------------------------- ----------------------------------------------------------------------
type Partitions a = Map (Int, Int) Double -> IO [a] type Partitions a = Map (Int, Int) Double -> IO [a]
......
...@@ -28,9 +28,9 @@ import Gargantext.Core.Viz.Graph ...@@ -28,9 +28,9 @@ import Gargantext.Core.Viz.Graph
import Gargantext.Core.Viz.Graph.Bridgeness (bridgeness, Partitions, ToComId(..)) import Gargantext.Core.Viz.Graph.Bridgeness (bridgeness, Partitions, ToComId(..))
import Gargantext.Core.Viz.Graph.Index (createIndices, toIndex, map2mat, mat2map, Index, MatrixShape(..)) import Gargantext.Core.Viz.Graph.Index (createIndices, toIndex, map2mat, mat2map, Index, MatrixShape(..))
import Gargantext.Core.Viz.Graph.Tools.IGraph (mkGraphUfromEdges, spinglass) import Gargantext.Core.Viz.Graph.Tools.IGraph (mkGraphUfromEdges, spinglass)
import Gargantext.Core.Viz.Graph.Types (ClusterNode)
import Gargantext.Prelude import Gargantext.Prelude
import Graph.Types (ClusterNode) -- import qualified Graph.BAC.ProxemyOptim as BAC
import qualified Graph.BAC.ProxemyOptim as BAC
import IGraph.Random -- (Gen(..)) import IGraph.Random -- (Gen(..))
import qualified Data.HashMap.Strict as HashMap import qualified Data.HashMap.Strict as HashMap
import qualified Data.List as List import qualified Data.List as List
...@@ -43,7 +43,8 @@ import qualified IGraph.Algorithms.Layout as Layout ...@@ -43,7 +43,8 @@ import qualified IGraph.Algorithms.Layout as Layout
------------------------------------------------------------- -------------------------------------------------------------
defaultClustering :: Map (Int, Int) Double -> IO [ClusterNode] defaultClustering :: Map (Int, Int) Double -> IO [ClusterNode]
defaultClustering x = pure $ BAC.defaultClustering x -- defaultClustering x = pure $ BAC.defaultClustering x
defaultClustering x = spinglass 1 x
------------------------------------------------------------- -------------------------------------------------------------
type Threshold = Double type Threshold = Double
...@@ -67,7 +68,7 @@ cooc2graph' distance threshold myCooc ...@@ -67,7 +68,7 @@ cooc2graph' distance threshold myCooc
myCooc' = toIndex ti myCooc myCooc' = toIndex ti myCooc
data PartitionMethod = Louvain | Spinglass | Bac data PartitionMethod = Louvain | Spinglass -- | Bac
-- | coocurrences graph computation -- | coocurrences graph computation
cooc2graphWith :: PartitionMethod cooc2graphWith :: PartitionMethod
...@@ -75,9 +76,9 @@ cooc2graphWith :: PartitionMethod ...@@ -75,9 +76,9 @@ cooc2graphWith :: PartitionMethod
-> Threshold -> Threshold
-> HashMap (NgramsTerm, NgramsTerm) Int -> HashMap (NgramsTerm, NgramsTerm) Int
-> IO Graph -> IO Graph
cooc2graphWith Louvain = undefined -- TODO use IGraph bindings cooc2graphWith Louvain = undefined
cooc2graphWith Spinglass = cooc2graphWith' (spinglass 1) cooc2graphWith Spinglass = cooc2graphWith' (spinglass 1)
cooc2graphWith Bac = undefined -- cooc2graphWith' BAC.defaultClustering -- cooc2graphWith Bac = cooc2graphWith' (\x -> pure $ BAC.defaultClustering x)
cooc2graph'' :: Ord t => Distance cooc2graph'' :: Ord t => Distance
-> Double -> Double
...@@ -113,9 +114,12 @@ filterByNeighbours threshold distanceMap = filteredMap ...@@ -113,9 +114,12 @@ filterByNeighbours threshold distanceMap = filteredMap
doDistanceMap :: Distance doDistanceMap :: Distance
-> Threshold -> Threshold
-> HashMap (NgramsTerm, NgramsTerm) Int -> HashMap (NgramsTerm, NgramsTerm) Int
-> (Map (Int,Int) Double, Map (Index, Index) Int, Map NgramsTerm Index) -> ( Map (Int,Int) Double
, Map (Index, Index) Int
, Map NgramsTerm Index
)
doDistanceMap distance threshold myCooc = (distanceMap, myCooc', ti) doDistanceMap distance threshold myCooc = (distanceMap, myCooc', ti)
where where
-- TODO remove below -- TODO remove below
...@@ -125,9 +129,10 @@ doDistanceMap distance threshold myCooc = (distanceMap, myCooc', ti) ...@@ -125,9 +129,10 @@ doDistanceMap distance threshold myCooc = (distanceMap, myCooc', ti)
(ti, _) = createIndices theMatrix (ti, _) = createIndices theMatrix
tiSize = Map.size ti tiSize = Map.size ti
myCooc' = toIndex ti theMatrix myCooc' = toIndex ti theMatrix
matCooc = case distance of -- Shape of the Matrix matCooc = case distance of -- Shape of the Matrix
Conditional -> map2mat Triangle 0 tiSize Conditional -> map2mat Triangle 0 tiSize
Distributional -> map2mat Square 0 tiSize Distributional -> map2mat Square 0 tiSize
$ case distance of -- Removing the Diagonal ? $ case distance of -- Removing the Diagonal ?
Conditional -> Map.filterWithKey (\(a,b) _ -> a /= b) Conditional -> Map.filterWithKey (\(a,b) _ -> a /= b)
Distributional -> identity Distributional -> identity
...@@ -136,7 +141,8 @@ doDistanceMap distance threshold myCooc = (distanceMap, myCooc', ti) ...@@ -136,7 +141,8 @@ doDistanceMap distance threshold myCooc = (distanceMap, myCooc', ti)
similarities = measure distance matCooc similarities = measure distance matCooc
links = round (let n :: Double = fromIntegral tiSize in n * log n) links = round (let n :: Double = fromIntegral tiSize in n * log n)
distanceMap = Map.fromList $ List.take links distanceMap = Map.fromList
$ List.take links
$ List.sortOn snd $ List.sortOn snd
$ Map.toList $ Map.toList
$ case distance of $ case distance of
......
...@@ -20,7 +20,8 @@ import Data.Singletons (SingI) ...@@ -20,7 +20,8 @@ import Data.Singletons (SingI)
import IGraph hiding (mkGraph, neighbors, edges, nodes, Node, Graph) import IGraph hiding (mkGraph, neighbors, edges, nodes, Node, Graph)
import Protolude import Protolude
import Gargantext.Core.Viz.Graph.Index import Gargantext.Core.Viz.Graph.Index
import Graph.Types -- import Graph.Types
import Gargantext.Core.Viz.Graph.Types
import qualified Data.List as List import qualified Data.List as List
import qualified IGraph as IG import qualified IGraph as IG
import qualified IGraph.Algorithms.Clique as IG import qualified IGraph.Algorithms.Clique as IG
......
{-| Module : Graph.Types
Description :
Copyright : (c) CNRS, Alexandre Delanoë
License : AGPL + CECILL v3
Maintainer : contact@gargantext.org
Stability : experimental
Portability : POSIX
-}
module Gargantext.Core.Viz.Graph.Types where
import qualified Data.Graph.Inductive.PatriciaTree as DGIP
-- import Data.IntMap (IntMap)
-- import qualified Eigen.Matrix as DenseMatrix
-- import Eigen.SparseMatrix (SparseMatrix)
--import qualified Data.Matrix.Sparse.Static as Sparse
-- import qualified Data.Vector.Unboxed as VU
-- import qualified Numeric.LinearAlgebra.Static as Dense
import Protolude hiding (sum, natVal)
-- | Main Types use in this libray
type Dict = IntMap
-- | Use the optimized version of Graph
type Graph a b = DGIP.Gr a b
-- | Type for Matrix computation optimizations (with Eigen)
-- type MatrixD n = Dense.L n n
-- type MatrixS n = Sparse.Matrix n n Double
data ClusterNode = ClusterNode
{ cl_node_id :: Int
, cl_community_id :: Int
} 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