Commit 3bf1b44c authored by Quentin Lobbé's avatar Quentin Lobbé

Add the clustering up to level 2 and more

parent a4815b58
......@@ -189,7 +189,14 @@ data PhyloError = LevelDoesNotExist
deriving (Show)
data Proximity = WeightedLogJaccard | Other
type PhyloGraph = (PhyloNodes,PhyloEdges)
type PhyloNodes = [PhyloGroup]
type PhyloEdges = [(((PhyloGroup,PhyloGroup)),Double)]
data Proximity = WeightedLogJaccard | Hamming | FromPairs
data Clustering = Louvain | RelatedComponents
data PairTo = Childs | Parents
......
This diff is collapsed.
......@@ -18,7 +18,7 @@ module Gargantext.Viz.Phylo.Tools
where
import Control.Lens hiding (both, Level)
import Data.List (filter, intersect, (++), sort, null, head, tail, last, tails)
import Data.List (filter, intersect, (++), sort, null, head, tail, last, tails, delete, nub)
import Data.Map (Map, mapKeys, member)
import Data.Set (Set)
import Data.Text (Text)
......@@ -117,6 +117,11 @@ filterNestedSets h l l'
| otherwise = filterNestedSets (head l) (tail l) (h : l')
-- | To filter some PhyloEdges with a given threshold
filterPhyloEdges :: Double -> PhyloEdges -> PhyloEdges
filterPhyloEdges thr edges = filter (\((s,t),w) -> w > thr) edges
-- | To get the PhyloGroups Childs of a PhyloGroup
getGroupChilds :: PhyloGroup -> Phylo -> [PhyloGroup]
getGroupChilds g p = getGroupsFromIds (map fst $ _phylo_groupPeriodChilds g) p
......@@ -222,6 +227,15 @@ getLevelLinkValue dir link = case dir of
_ -> panic "[ERR][Viz.Phylo.Tools.getLevelLinkValue] Wrong direction"
-- | To get the neighbours (directed/undirected) of a PhyloGroup from a list of PhyloEdges
getNeighbours :: Bool -> PhyloGroup -> PhyloEdges -> [PhyloGroup]
getNeighbours directed g e = case directed of
True -> map (\((s,t),w) -> t)
$ filter (\((s,t),w) -> s == g) e
False -> map (\((s,t),w) -> head $ delete g $ nub [s,t,g])
$ filter (\((s,t),w) -> s == g || t == g) e
-- | To get the Branches of a Phylo
getPhyloBranches :: Phylo -> [PhyloBranch]
getPhyloBranches = _phylo_branches
......
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