Commit 3804ecd2 authored by Alexandre Delanoë's avatar Alexandre Delanoë

Merge branch 'alp/defaultClustering' of ssh://delanoe.org/gargantext-graph

parents 446fe390 e0317142
...@@ -37,7 +37,7 @@ module Graph.BAC.ProxemyOptim ...@@ -37,7 +37,7 @@ module Graph.BAC.ProxemyOptim
where where
import Data.IntMap (IntMap) import Data.IntMap (IntMap)
import Data.Maybe (isJust) import Data.Maybe (isJust, fromJust)
import Data.Proxy (Proxy(Proxy)) import Data.Proxy (Proxy(Proxy))
import Data.Reflection import Data.Reflection
import GHC.TypeLits (KnownNat, Nat, SomeNat(SomeNat), type(+), natVal, sameNat, someNatVal) import GHC.TypeLits (KnownNat, Nat, SomeNat(SomeNat), type(+), natVal, sameNat, someNatVal)
...@@ -64,9 +64,31 @@ import qualified Data.Vector.Mutable as MV ...@@ -64,9 +64,31 @@ import qualified Data.Vector.Mutable as MV
import qualified Data.Vector.Unboxed.Mutable as MVU import qualified Data.Vector.Unboxed.Mutable as MVU
import qualified Data.IntSet as IntSet import qualified Data.IntSet as IntSet
import qualified Data.IntMap.Strict as IntMap import qualified Data.IntMap.Strict as IntMap
import qualified Data.Map.Strict as Map
---------------------------------------------------------------- ----------------------------------------------------------------
data ClusterNode = ClusterNode
{ cl_node_id :: Int
, cl_community_id :: Int
} deriving Show
defaultClustering :: Map (Int, Int) Double -> [ClusterNode]
defaultClustering adjmap = withG g $ \fg ->
case clusteringOptim len fg beta gc of
Clust _ dico idx _ -> map (lkpId dico) (Dict.toList idx)
where gc = False
beta = 0.0
len = 3
g = DGI.mkGraph ns es
ns = zip [0..] . Set.toList . Set.fromList $
concatMap (\(a, b) -> [a, b]) $ Map.keys adjmap
es = map (\((a, b), w) -> (a, b, w)) $ Map.toList adjmap
lkpId dict (i, clust) = ClusterNode
(fromJust (Dict.lookup i dict))
clust
{-# INLINE clusteringOptim #-} {-# INLINE clusteringOptim #-}
clusteringOptim :: forall n a b. KnownNat n clusteringOptim :: forall n a b. KnownNat n
=> Length -- ^ length of the random walks => Length -- ^ length of the random walks
......
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