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.Display
20 import Control.Lens hiding (makeLenses, both, Level)
22 import Data.List (notElem,last,head,union,concat,null,nub,(++),init,tail,elemIndex,groupBy,(!!),sortOn,sort,(\\))
23 import Data.Map (Map,elems,adjust,unionWith,intersectionWith,fromList,mapKeys,insert)
24 import Data.Maybe (isNothing)
26 import Data.Text (Text,unwords)
27 import Data.Tuple (fst, snd)
28 import Data.Vector (Vector)
30 import Gargantext.Prelude hiding (head)
31 import Gargantext.Viz.Phylo
32 import Gargantext.Viz.Phylo.Tools
34 import qualified Data.List as List
35 import qualified Data.Map as Map
36 import qualified Data.Set as Set
37 import qualified Data.Vector as Vector
40 -- | To transform a flat Phyloview into a nested Phyloview
41 toNestedView :: [PhyloNode] -> [PhyloNode] -> [PhyloNode]
44 | otherwise = toNestedView (filter (\n -> lvl' == getNodeLevel n) nested)
45 (filter (\n -> lvl' < getNodeLevel n) nested)
47 --------------------------------------
49 lvl' = getNodeLevel $ head $ nested
50 --------------------------------------
52 nested = foldl (\ns' n -> let nIds' = getNodeParentsId n
53 in map (\n' -> if elem (getNodeId n') nIds'
54 then n' & phylo_nodeLevelChilds %~ (++ [n])
56 --------------------------------------
59 -- | To process a DisplayMode to a PhyloView
60 processDisplay :: DisplayMode -> PhyloView -> PhyloView
61 processDisplay d v = case d of
63 Nested -> let ns = sortOn getNodeLevel $ v ^. phylo_viewNodes
64 lvl = getNodeLevel $ head ns
65 in v & phylo_viewNodes .~ toNestedView (filter (\n -> lvl == getNodeLevel n) ns)
66 (filter (\n -> lvl < getNodeLevel n) ns)
67 _ -> panic "[ERR][Viz.Phylo.Example.processDisplay] display not found"