2 Module : Gargantext.Viz.Phylo.Tools
3 Description : Phylomemy Tools to build/manage it
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
13 {-# LANGUAGE NoImplicitPrelude #-}
14 {-# LANGUAGE FlexibleContexts #-}
15 {-# LANGUAGE OverloadedStrings #-}
17 module Gargantext.Viz.Phylo.View.Metrics
20 import Control.Lens hiding (makeLenses, both, Level)
21 import Data.List (last,groupBy,sortOn)
22 import Data.Map (insert)
23 import Data.Text (Text)
24 import Data.Tuple (fst, snd)
25 import Gargantext.Prelude
26 import Gargantext.Viz.Phylo
27 import Gargantext.Viz.Phylo.Tools
30 -- | To add a new meta Metric to a PhyloBranch
31 addBranchMetrics :: PhyloBranchId -> Text -> Double -> PhyloView -> PhyloView
32 addBranchMetrics id lbl val v = over (pv_branches
34 (\b -> if getBranchId b == id
35 then b & pb_metrics %~ insert lbl [val]
39 -- | To get the age (in year) of all the branches of a PhyloView
40 branchAge :: PhyloView -> PhyloView
41 branchAge v = foldl (\v' b -> let bId = (fst . (head' "branchAge")) b
42 prds = sortOn fst $ map snd b
43 in addBranchMetrics bId "age" ((abs . fromIntegral) $ ((snd . last) prds) - (fst $ head' "branchAge" prds)) v') v
44 $ groupBy ((==) `on` fst)
46 $ map (\n -> (getNodeBranchId n, (fst . fst) $ getNodeId n))
47 $ getNodesInBranches v
50 -- | To process a list of Metrics to a PhyloView
51 processMetrics :: [Metric] -> Phylo -> PhyloView -> PhyloView
52 processMetrics ms _p v = foldl (\v' m -> case m of
53 BranchAge -> branchAge v'
54 -- _ -> panic "[ERR][Viz.Phylo.Example.processMetrics] metric not found"