Sort.hs 1.38 KB
Newer Older
1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20
{-|
Module      : Gargantext.Viz.Phylo.Tools
Description : Phylomemy Tools to build/manage it
Copyright   : (c) CNRS, 2017-Present
License     : AGPL + CECILL v3
Maintainer  : team@gargantext.org
Stability   : experimental
Portability : POSIX


-}

{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE FlexibleContexts  #-}
{-# LANGUAGE OverloadedStrings #-}

module Gargantext.Viz.Phylo.View.Sort
  where

import Control.Lens     hiding (makeLenses, both, Level)
21
import Data.List        (sortOn)
22
import Data.Tuple       (fst, snd)
Alexandre Delanoë's avatar
Alexandre Delanoë committed
23
import Gargantext.Prelude
24 25 26 27 28 29
import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Tools


-- | To sort a PhyloView by Age
sortBranchByAge :: Order -> PhyloView -> PhyloView
30
sortBranchByAge o v = v & pv_branches %~ f
31 32 33 34 35 36 37 38 39 40
  where
    --------------------------------------
    f :: [PhyloBranch] -> [PhyloBranch] 
    f xs = case o of 
           Asc  -> sortOn (getBranchMeta "age") xs
           Desc -> reverse $ sortOn (getBranchMeta "age") xs
    --------------------------------------

-- | To process a Sort to a PhyloView
processSort :: Maybe (Sort,Order) -> Phylo -> PhyloView -> PhyloView 
41
processSort s _p v = case s of
42
                    Nothing -> v
43 44 45
                    Just s'  -> case fst s' of
                               ByBranchAge -> sortBranchByAge (snd s') v
                               --_           -> panic "[ERR][Viz.Phylo.View.Sort.processSort] sort not found"