Commit 72201d27 authored by Alp Mestanogullari's avatar Alp Mestanogullari

add 'reverse index' for clusters to 'Clust' result type

parent 178eb573
...@@ -54,7 +54,7 @@ main = do ...@@ -54,7 +54,7 @@ main = do
Just d -> d Just d -> d
_ -> Prelude.error "beta must be a Double" _ -> Prelude.error "beta must be a Double"
setupEnv fpin >>= \g -> do setupEnv fpin >>= \g -> do
let (Clust clusts dico score) = withG g (\fg -> clusteringOptim 3 fg beta gc) let (Clust clusts dico _ score) = withG g (\fg -> clusteringOptim 3 fg beta gc)
clusts' = Prelude.map (sort . Prelude.map (lkp dico) . IntSet.toList) clusts' = Prelude.map (sort . Prelude.map (lkp dico) . IntSet.toList)
$ sortBy (\a b -> flipOrd $ comparing IntSet.size a b) $ sortBy (\a b -> flipOrd $ comparing IntSet.size a b)
$ IntMap.elems clusts $ IntMap.elems clusts
......
...@@ -32,6 +32,7 @@ Gaume. ...@@ -32,6 +32,7 @@ Gaume.
#-} #-}
{-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE TupleSections #-}
module Graph.BAC.ProxemyOptim module Graph.BAC.ProxemyOptim
where where
...@@ -75,9 +76,12 @@ clusteringOptim :: forall n a b. KnownNat n ...@@ -75,9 +76,12 @@ clusteringOptim :: forall n a b. KnownNat n
-> Clust a -> Clust a
clusteringOptim l fg@(FiniteGraph g) beta gc = clusteringOptim l fg@(FiniteGraph g) beta gc =
case runClustering gc beta adj prox sorted_edges of case runClustering gc beta adj prox sorted_edges of
(clusts, d) -> Clust clusts idx d (clusts, d) -> Clust clusts dico (index clusts) d
where where
!idx = Dict.fromList (DGI.labNodes g) dico = Dict.fromList (DGI.labNodes g)
index clusts = Dict.foldMapWithKey
(\clustN is -> Dict.fromList $ map (,clustN) (IntSet.toList is))
clusts
!adj = graphMatrix fg True !adj = graphMatrix fg True
!tra = transition adj !tra = transition adj
!prox = proxemie l tra !prox = proxemie l tra
...@@ -405,8 +409,9 @@ clusteringCollector beta adj prox mclust = do ...@@ -405,8 +409,9 @@ clusteringCollector beta adj prox mclust = do
data Clust a = Clust data Clust a = Clust
{ cparts :: !(Dict IntSet) { cparts :: !(Dict IntSet)
, cindex :: !(Dict a) , cdico :: (Dict a)
, cscore :: {-# UNPACK #-} !Double , cindex :: (Dict Int)
, cscore :: !Double
} deriving (Show, Eq) } deriving (Show, Eq)
runClustering runClustering
......
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