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

[FIX] removing cLouvain c++ lib

parent 704dc05e
Pipeline #1438 canceled with stage
......@@ -130,7 +130,6 @@ library:
- cassava
- cereal # (IGraph)
- clock
- clustering-louvain
- conduit
- conduit-extra
- containers
......
......@@ -18,7 +18,6 @@ TODO use Map LouvainNodeId (Map LouvainNodeId)
module Gargantext.Core.Viz.Graph.Bridgeness -- (bridgeness)
where
import Data.Graph.Clustering.Louvain.Utils (LouvainNode(..))
import Data.List (concat, sortOn)
import Data.Map (Map, fromListWith, lookup, toList, mapWithKey, elems)
import Data.Maybe (catMaybes)
......@@ -37,9 +36,6 @@ type NodeId = Int
type CommunityId = Int
----------------------------------------------------------------------
instance ToComId LouvainNode where
nodeId2comId (LouvainNode i1 i2) = (i1, i2)
instance ToComId ClusterNode where
nodeId2comId (ClusterNode i1 i2) = (i1, i2)
......
......@@ -15,7 +15,6 @@ module Gargantext.Core.Viz.Graph.Tools
where
-- import Data.Graph.Clustering.Louvain (hLouvain, {-iLouvainMap-})
import Data.Graph.Clustering.Louvain.CplusPlus (cLouvain)
import Data.HashMap.Strict (HashMap)
import Data.Map (Map)
import Data.Text (Text)
......@@ -28,7 +27,7 @@ import Gargantext.Core.Statistics
import Gargantext.Core.Viz.Graph
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.Tools.IGraph (mkGraphUfromEdges, spinglass)
import Gargantext.Core.Viz.Graph.Tools.IGraph (mkGraphUfromEdges, spinglass, ClusterNode)
import Gargantext.Prelude
import IGraph.Random -- (Gen(..))
import qualified Data.HashMap.Strict as HashMap
......@@ -39,8 +38,15 @@ import qualified Data.Vector.Storable as Vec
import qualified IGraph as Igraph
import qualified IGraph.Algorithms.Layout as Layout
type Threshold = Double
-------------------------------------------------------------
defaultClustering :: Map (Int, Int) Double -> IO [ClusterNode]
defaultClustering = spinglass 1
-------------------------------------------------------------
type Threshold = Double
cooc2graph' :: Ord t => Distance
-> Double
......@@ -68,7 +74,7 @@ cooc2graphWith :: PartitionMethod
-> Threshold
-> HashMap (NgramsTerm, NgramsTerm) Int
-> IO Graph
cooc2graphWith Louvain = cooc2graphWith' (cLouvain "1")
cooc2graphWith Louvain = undefined -- TODO use IGraph bindings
cooc2graphWith Spinglass = cooc2graphWith' (spinglass 1)
......
......@@ -15,11 +15,11 @@ Portability : POSIX
module Gargantext.Core.Viz.Phylo.Cluster
where
import Control.Parallel.Strategies
import Data.Graph.Clustering.Louvain.CplusPlus
import Data.Graph.Clustering.Louvain.Utils (LouvainNode(..))
import Data.List (null,concat,sort,intersect,(++), elemIndex, groupBy, nub, union, (\\), (!!))
import Data.Map (Map, fromList, mapKeys)
import Gargantext.Prelude
import Gargantext.Core.Viz.Graph.Tools (defaultClustering)
import Gargantext.Core.Viz.Graph.Tools.IGraph (ClusterNode(..))
import Gargantext.Core.Viz.Phylo
import Gargantext.Core.Viz.Phylo.Tools
import Gargantext.Core.Viz.Phylo.Metrics
......@@ -48,9 +48,9 @@ relatedComp graphs = foldl' (\mem groups ->
louvain :: ([GroupNode],[GroupEdge]) -> IO [[PhyloGroup]]
louvain (nodes,edges) = map (\community -> map (\node -> nodes !! (l_node_id node)) community)
<$> groupBy (\a b -> (l_community_id a) == (l_community_id b))
<$> (cLouvain "0.0001" $ mapKeys (\(x,y) -> (idx x, idx y)) $ fromList edges)
louvain (nodes,edges) = map (\community -> map (\node -> nodes !! (cl_node_id node)) community)
<$> groupBy (\a b -> (cl_community_id a) == (cl_community_id b))
<$> (defaultClustering $ mapKeys (\(x,y) -> (idx x, idx y)) $ fromList edges)
where
--------------------------------------
idx :: PhyloGroup -> Int
......
......@@ -6,7 +6,6 @@ packages:
#- 'deps/patches-class'
#- 'deps/patches-map'
#- 'deps/servant-job'
#- 'deps/clustering-louvain'
#- 'deps/accelerate'
#- 'deps/accelerate-utility'
......@@ -71,8 +70,6 @@ extra-deps:
# Graph libs
- git: https://github.com/kaizhang/haskell-igraph.git
commit: 34553acc4ebdcae7065311dcefb426e0fd58c5a0
- git: https://gitlab.iscpif.fr/gargantext/clustering-louvain.git
commit: 7d74f96dfea8e51fbab1793cc0429b2fe741f73d
# Accelerate Linear Algebra and specific instances
# (UndecidableInstances for newer GHC version)
......
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