Commit a4a4a2fb authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FIX] heads.

parent 9ec52356
...@@ -269,3 +269,4 @@ maximumWith f = L.maximumBy (compare `on` f) ...@@ -269,3 +269,4 @@ maximumWith f = L.maximumBy (compare `on` f)
listToCombi :: forall a b. (a -> b) -> [a] -> [(b,b)] listToCombi :: forall a b. (a -> b) -> [a] -> [(b,b)]
listToCombi f l = [ (f x, f y) | (x:rest) <- L.tails l, y <- rest ] listToCombi f l = [ (f x, f y) | (x:rest) <- L.tails l, y <- rest ]
head' e xs = maybe (panic e) identity (head xs)
...@@ -17,11 +17,10 @@ Portability : POSIX ...@@ -17,11 +17,10 @@ Portability : POSIX
module Gargantext.Viz.Phylo.Aggregates.Cluster module Gargantext.Viz.Phylo.Aggregates.Cluster
where where
import Data.List (null,tail)
import Data.List (head,null,tail)
import Data.Map (Map) import Data.Map (Map)
import Data.Tuple (fst) import Data.Tuple (fst)
import Gargantext.Prelude hiding (head) import Gargantext.Prelude
import Gargantext.Viz.Phylo import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Tools import Gargantext.Viz.Phylo.Tools
import Gargantext.Viz.Phylo.BranchMaker import Gargantext.Viz.Phylo.BranchMaker
...@@ -33,7 +32,7 @@ import qualified Data.Map as Map ...@@ -33,7 +32,7 @@ import qualified Data.Map as Map
graphToClusters :: Cluster -> GroupGraph -> [PhyloCluster] graphToClusters :: Cluster -> GroupGraph -> [PhyloCluster]
graphToClusters clust (nodes,edges) = case clust of graphToClusters clust (nodes,edges) = case clust of
Louvain (LouvainParams _) -> undefined -- louvain (nodes,edges) Louvain (LouvainParams _) -> undefined -- louvain (nodes,edges)
RelatedComponents (RCParams _) -> relatedComp 0 (head nodes) (tail nodes,edges) [] [] RelatedComponents (RCParams _) -> relatedComp 0 (head' "graphToClusters" nodes) (tail nodes,edges) [] []
_ -> panic "[ERR][Viz.Phylo.Aggregates.Cluster.graphToClusters] not implemented" _ -> panic "[ERR][Viz.Phylo.Aggregates.Cluster.graphToClusters] not implemented"
-- | To transform a Phylo into Clusters of PhyloGroups at a given level -- | To transform a Phylo into Clusters of PhyloGroups at a given level
......
...@@ -19,7 +19,8 @@ module Gargantext.Viz.Phylo.Aggregates.Cooc ...@@ -19,7 +19,8 @@ module Gargantext.Viz.Phylo.Aggregates.Cooc
import Data.List (union,concat) import Data.List (union,concat)
import Data.Map (Map, elems, adjust) import Data.Map (Map, elems, adjust)
import Gargantext.Prelude hiding (head) import Data.Maybe (maybe)
import Gargantext.Prelude
import Gargantext.Viz.Phylo import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Tools import Gargantext.Viz.Phylo.Tools
import qualified Data.Map as Map import qualified Data.Map as Map
......
...@@ -19,12 +19,12 @@ module Gargantext.Viz.Phylo.Aggregates.Document ...@@ -19,12 +19,12 @@ module Gargantext.Viz.Phylo.Aggregates.Document
import Control.Lens hiding (both, Level) import Control.Lens hiding (both, Level)
import Data.List (last,head,nub,(++)) import Data.List (last,nub,(++))
import Data.Map (Map,member) import Data.Map (Map,member)
import Data.Text (Text) import Data.Text (Text)
import Data.Tuple (fst, snd) import Data.Tuple (fst, snd)
import Data.Vector (Vector) import Data.Vector (Vector)
import Gargantext.Prelude hiding (head) import Gargantext.Prelude
import Gargantext.Text.Terms.Mono (monoTexts) import Gargantext.Text.Terms.Mono (monoTexts)
import Gargantext.Viz.Phylo import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Tools import Gargantext.Viz.Phylo.Tools
...@@ -35,7 +35,7 @@ import qualified Data.Vector as Vector ...@@ -35,7 +35,7 @@ import qualified Data.Vector as Vector
-- | To init a list of Periods framed by a starting Date and an ending Date -- | To init a list of Periods framed by a starting Date and an ending Date
initPeriods :: (Eq date, Enum date) => Grain -> Step -> (date, date) -> [(date, date)] initPeriods :: (Eq date, Enum date) => Grain -> Step -> (date, date) -> [(date, date)]
initPeriods g s (start,end) = map (\l -> (head l, last l)) initPeriods g s (start,end) = map (\l -> (head' "Doc" l, last l))
$ chunkAlong g s [start .. end] $ chunkAlong g s [start .. end]
......
...@@ -17,10 +17,10 @@ Portability : POSIX ...@@ -17,10 +17,10 @@ Portability : POSIX
module Gargantext.Viz.Phylo.Aggregates.Fis module Gargantext.Viz.Phylo.Aggregates.Fis
where where
import Data.List (head,null) import Data.List (null)
import Data.Map (Map, empty) import Data.Map (Map, empty)
import Data.Tuple (fst, snd) import Data.Tuple (fst, snd)
import Gargantext.Prelude hiding (head) import Gargantext.Prelude
import Gargantext.Text.Metrics.FrequentItemSet (fisWithSizePolyMap, Size(..)) import Gargantext.Text.Metrics.FrequentItemSet (fisWithSizePolyMap, Size(..))
import Gargantext.Viz.Phylo import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Tools import Gargantext.Viz.Phylo.Tools
...@@ -41,7 +41,7 @@ filterMinorFis min' l = filter (\fis -> getSupport fis > min') l ...@@ -41,7 +41,7 @@ filterMinorFis min' l = filter (\fis -> getSupport fis > min') l
-- | To filter nested Fis -- | To filter nested Fis
filterFisByNested :: Map (Date, Date) [PhyloFis] -> Map (Date, Date) [PhyloFis] filterFisByNested :: Map (Date, Date) [PhyloFis] -> Map (Date, Date) [PhyloFis]
filterFisByNested = map (\l -> let cliqueMax = filterNestedSets (head $ map getClique l) (map getClique l) [] filterFisByNested = map (\l -> let cliqueMax = filterNestedSets (head' "Fis" $ map getClique l) (map getClique l) []
in filter (\fis -> elem (getClique fis) cliqueMax) l) in filter (\fis -> elem (getClique fis) cliqueMax) l)
......
...@@ -18,9 +18,9 @@ module Gargantext.Viz.Phylo.BranchMaker ...@@ -18,9 +18,9 @@ module Gargantext.Viz.Phylo.BranchMaker
where where
import Control.Lens hiding (both, Level) import Control.Lens hiding (both, Level)
import Data.List (head,concat,nub,(++),tail) import Data.List (concat,nub,(++),tail)
import Data.Tuple (fst, snd) import Data.Tuple (fst, snd)
import Gargantext.Prelude hiding (head) import Gargantext.Prelude
import Gargantext.Viz.Phylo import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Metrics.Clustering import Gargantext.Viz.Phylo.Metrics.Clustering
import Gargantext.Viz.Phylo.Metrics.Proximity import Gargantext.Viz.Phylo.Metrics.Proximity
...@@ -32,7 +32,7 @@ graphToBranches :: Level -> GroupGraph -> Phylo -> [(Int,PhyloGroupId)] ...@@ -32,7 +32,7 @@ graphToBranches :: Level -> GroupGraph -> Phylo -> [(Int,PhyloGroupId)]
graphToBranches _lvl (nodes,edges) _p = concat graphToBranches _lvl (nodes,edges) _p = concat
$ map (\(idx,gs) -> map (\g -> (idx,getGroupId g)) gs) $ map (\(idx,gs) -> map (\g -> (idx,getGroupId g)) gs)
$ zip [1..] $ zip [1..]
$ relatedComp 0 (head nodes) (tail nodes,edges) [] [] $ relatedComp 0 (head' "branchMaker" nodes) (tail nodes,edges) [] []
-- | To transform a list of PhyloGroups into a PhyloGraph by using a given Proximity mesure -- | To transform a list of PhyloGroups into a PhyloGraph by using a given Proximity mesure
...@@ -55,7 +55,7 @@ groupsToGraph prox groups p = (groups,edges) ...@@ -55,7 +55,7 @@ groupsToGraph prox groups p = (groups,edges)
-- | To set all the PhyloBranches for a given Level in a Phylo -- | To set all the PhyloBranches for a given Level in a Phylo
setPhyloBranches :: Level -> Phylo -> Phylo setPhyloBranches :: Level -> Phylo -> Phylo
setPhyloBranches lvl p = alterGroupWithLevel (\g -> let bIdx = (fst . head) $ filter (\b -> snd b == getGroupId g) bs setPhyloBranches lvl p = alterGroupWithLevel (\g -> let bIdx = (fst $ head' "branchMaker" $ filter (\b -> snd b == getGroupId g) bs)
in over (phylo_groupBranchId) (\_ -> Just (lvl,bIdx)) g) lvl p in over (phylo_groupBranchId) (\_ -> Just (lvl,bIdx)) g) lvl p
where where
-------------------------------------- --------------------------------------
......
...@@ -29,12 +29,12 @@ TODO: ...@@ -29,12 +29,12 @@ TODO:
module Gargantext.Viz.Phylo.Example where module Gargantext.Viz.Phylo.Example where
import Data.Text (Text) import Data.Text (Text)
import Data.List ((++), last, head) import Data.List ((++), last)
import Data.Map (Map) import Data.Map (Map)
import Data.Tuple (fst) import Data.Tuple (fst)
import Data.Tuple.Extra import Data.Tuple.Extra
import Data.Vector (Vector) import Data.Vector (Vector)
import Gargantext.Prelude hiding (head) import Gargantext.Prelude
import Gargantext.Viz.Phylo import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Aggregates.Cluster import Gargantext.Viz.Phylo.Aggregates.Cluster
import Gargantext.Viz.Phylo.Aggregates.Document import Gargantext.Viz.Phylo.Aggregates.Document
...@@ -221,7 +221,7 @@ phyloBase = initPhyloBase periods foundations peaks defaultPhyloParam ...@@ -221,7 +221,7 @@ phyloBase = initPhyloBase periods foundations peaks defaultPhyloParam
periods :: [(Date,Date)] periods :: [(Date,Date)]
periods = initPeriods 5 3 periods = initPeriods 5 3
$ both fst (head corpus,last corpus) $ both fst (head' "Example" corpus,last corpus)
peaks :: PhyloPeaks peaks :: PhyloPeaks
......
...@@ -20,12 +20,12 @@ module Gargantext.Viz.Phylo.LevelMaker ...@@ -20,12 +20,12 @@ module Gargantext.Viz.Phylo.LevelMaker
where where
import Control.Lens hiding (both, Level) import Control.Lens hiding (both, Level)
import Data.List ((++), sort, concat, nub, zip, head, last) import Data.List ((++), sort, concat, nub, zip, last)
import Data.Map (Map, (!), empty, restrictKeys, filterWithKey, singleton, union) import Data.Map (Map, (!), empty, restrictKeys, filterWithKey, singleton, union)
import Data.Text (Text) import Data.Text (Text)
import Data.Tuple.Extra import Data.Tuple.Extra
import Data.Vector (Vector) import Data.Vector (Vector)
import Gargantext.Prelude hiding (head) import Gargantext.Prelude
import Gargantext.Viz.Phylo import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Aggregates.Cluster import Gargantext.Viz.Phylo.Aggregates.Cluster
import Gargantext.Viz.Phylo.Aggregates.Cooc import Gargantext.Viz.Phylo.Aggregates.Cooc
...@@ -190,7 +190,7 @@ toPhyloBase q p c a ts = initPhyloBase periods foundations peaks p ...@@ -190,7 +190,7 @@ toPhyloBase q p c a ts = initPhyloBase periods foundations peaks p
-------------------------------------- --------------------------------------
periods :: [(Date,Date)] periods :: [(Date,Date)]
periods = initPeriods (getPeriodGrain q) (getPeriodSteps q) periods = initPeriods (getPeriodGrain q) (getPeriodSteps q)
$ both fst (head c,last c) $ both fst (head' "LevelMaker" c,last c)
-------------------------------------- --------------------------------------
foundations :: Vector Ngrams foundations :: Vector Ngrams
foundations = initFoundations a foundations = initFoundations a
......
...@@ -18,9 +18,9 @@ module Gargantext.Viz.Phylo.LinkMaker ...@@ -18,9 +18,9 @@ module Gargantext.Viz.Phylo.LinkMaker
where where
import Control.Lens hiding (both, Level) import Control.Lens hiding (both, Level)
import Data.List ((++), nub, sortOn, head, null, tail, splitAt, elem) import Data.List ((++), nub, sortOn, null, tail, splitAt, elem)
import Data.Tuple.Extra import Data.Tuple.Extra
import Gargantext.Prelude hiding (head) import Gargantext.Prelude
import Gargantext.Viz.Phylo import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Tools import Gargantext.Viz.Phylo.Tools
import Gargantext.Viz.Phylo.Metrics.Proximity import Gargantext.Viz.Phylo.Metrics.Proximity
...@@ -107,8 +107,8 @@ getNextPeriods to' id l = case to' of ...@@ -107,8 +107,8 @@ getNextPeriods to' id l = case to' of
unNested :: PhyloPeriodId -> [PhyloPeriodId] -> [PhyloPeriodId] unNested :: PhyloPeriodId -> [PhyloPeriodId] -> [PhyloPeriodId]
unNested x l' unNested x l'
| null l' = [] | null l' = []
| nested (fst $ head l') x = unNested x (tail l') | nested (fst $ head' "getNextPeriods1" l') x = unNested x (tail l')
| nested (snd $ head l') x = unNested x (tail l') | nested (snd $ head' "getNextPeriods2" l') x = unNested x (tail l')
| otherwise = l | otherwise = l
-------------------------------------- --------------------------------------
nested :: Date -> PhyloPeriodId -> Bool nested :: Date -> PhyloPeriodId -> Bool
...@@ -128,7 +128,7 @@ findBestCandidates to' depth max' prox group p ...@@ -128,7 +128,7 @@ findBestCandidates to' depth max' prox group p
next = getNextPeriods to' (getGroupPeriod group) (getPhyloPeriods p) next = getNextPeriods to' (getGroupPeriod group) (getPhyloPeriods p)
-------------------------------------- --------------------------------------
candidates :: [PhyloGroup] candidates :: [PhyloGroup]
candidates = getGroupsWithFilters (getGroupLevel group) (head next) p candidates = getGroupsWithFilters (getGroupLevel group) (head' "findBestCandidates" next) p
-------------------------------------- --------------------------------------
scores :: [(PhyloGroupId, Double)] scores :: [(PhyloGroupId, Double)]
scores = map (\group' -> applyProximity prox group group') candidates scores = map (\group' -> applyProximity prox group group') candidates
......
...@@ -18,9 +18,9 @@ module Gargantext.Viz.Phylo.Metrics.Clustering ...@@ -18,9 +18,9 @@ module Gargantext.Viz.Phylo.Metrics.Clustering
where where
import Data.Graph.Clustering.Louvain.CplusPlus import Data.Graph.Clustering.Louvain.CplusPlus
import Data.List (last,head,concat,null,nub,(++),init,tail,elemIndex,groupBy,(!!)) import Data.List (last,concat,null,nub,(++),init,tail,elemIndex,groupBy,(!!))
import Data.Map (fromList,mapKeys) import Data.Map (fromList,mapKeys)
import Gargantext.Prelude hiding (head) import Gargantext.Prelude
import Gargantext.Viz.Phylo import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Tools import Gargantext.Viz.Phylo.Tools
...@@ -32,8 +32,8 @@ import Gargantext.Viz.Phylo.Tools ...@@ -32,8 +32,8 @@ import Gargantext.Viz.Phylo.Tools
relatedComp :: Int -> PhyloGroup -> GroupGraph -> [PhyloGroup] -> [[PhyloGroup]] -> [[PhyloGroup]] relatedComp :: Int -> PhyloGroup -> GroupGraph -> [PhyloGroup] -> [[PhyloGroup]] -> [[PhyloGroup]]
relatedComp idx curr (nodes,edges) next memo relatedComp idx curr (nodes,edges) next memo
| null nodes' && null next' = memo' | null nodes' && null next' = memo'
| (not . null) next' = relatedComp idx (head next') (nodes',edges) (tail next') memo' | (not . null) next' = relatedComp idx (head' "relatedComp1" next') (nodes',edges) (tail next') memo'
| otherwise = relatedComp (idx + 1) (head nodes') (tail nodes',edges) [] memo' | otherwise = relatedComp (idx + 1) (head' "relatedComp2" nodes') (tail nodes',edges) [] memo'
where where
-------------------------------------- --------------------------------------
memo' :: [[PhyloGroup]] memo' :: [[PhyloGroup]]
......
...@@ -19,7 +19,7 @@ module Gargantext.Viz.Phylo.Metrics.Proximity ...@@ -19,7 +19,7 @@ module Gargantext.Viz.Phylo.Metrics.Proximity
import Data.List (null) import Data.List (null)
import Data.Map (Map,elems,unionWith,intersectionWith,intersection,size) import Data.Map (Map,elems,unionWith,intersectionWith,intersection,size)
import Gargantext.Prelude hiding (head) import Gargantext.Prelude
-- | To process the weightedLogJaccard between two PhyloGroup fields -- | To process the weightedLogJaccard between two PhyloGroup fields
weightedLogJaccard :: Double -> Map (Int, Int) Double -> Map (Int, Int) Double -> Double weightedLogJaccard :: Double -> Map (Int, Int) Double -> Map (Int, Int) Double -> Double
......
...@@ -20,14 +20,14 @@ module Gargantext.Viz.Phylo.Tools ...@@ -20,14 +20,14 @@ module Gargantext.Viz.Phylo.Tools
where where
import Control.Lens hiding (both, Level, Empty) import Control.Lens hiding (both, Level, Empty)
import Data.List (filter, intersect, (++), sort, null, head, tail, last, tails, delete, nub, concat, sortOn) import Data.List (filter, intersect, (++), sort, null, tail, last, tails, delete, nub, concat, sortOn)
import Data.Maybe (mapMaybe,fromMaybe) import Data.Maybe (mapMaybe,fromMaybe)
import Data.Map (Map, mapKeys, member, (!)) import Data.Map (Map, mapKeys, member, (!))
import Data.Set (Set) import Data.Set (Set)
import Data.Text (Text, toLower) import Data.Text (Text, toLower)
import Data.Tuple.Extra import Data.Tuple.Extra
import Data.Vector (Vector,elemIndex) import Data.Vector (Vector,elemIndex)
import Gargantext.Prelude hiding (head) import Gargantext.Prelude
import Gargantext.Viz.Phylo import Gargantext.Viz.Phylo
import qualified Data.Map as Map import qualified Data.Map as Map
import qualified Data.Set as Set import qualified Data.Set as Set
...@@ -54,7 +54,7 @@ doesContains :: Eq a => [a] -> [a] -> Bool ...@@ -54,7 +54,7 @@ doesContains :: Eq a => [a] -> [a] -> Bool
doesContains l l' doesContains l l'
| null l' = True | null l' = True
| length l' > length l = False | length l' > length l = False
| elem (head l') l = doesContains l (tail l') | elem (head' "doesContains" l') l = doesContains l (tail l')
| otherwise = False | otherwise = False
...@@ -62,8 +62,8 @@ doesContains l l' ...@@ -62,8 +62,8 @@ doesContains l l'
doesContainsOrd :: Eq a => Ord a => [a] -> [a] -> Bool doesContainsOrd :: Eq a => Ord a => [a] -> [a] -> Bool
doesContainsOrd l l' doesContainsOrd l l'
| null l' = False | null l' = False
| last l < head l' = False | last l < (head' "doesContainsOrd" l') = False
| head l' `elem` l = True | (head' "doesContainsOrd" l') `elem` l = True
| otherwise = doesContainsOrd l (tail l') | otherwise = doesContainsOrd l (tail l')
...@@ -73,8 +73,8 @@ filterNestedSets h l l' ...@@ -73,8 +73,8 @@ filterNestedSets h l l'
| null l = if doesAnySetContains h l l' | null l = if doesAnySetContains h l l'
then l' then l'
else h : l' else h : l'
| doesAnySetContains h l l' = filterNestedSets (head l) (tail l) l' | doesAnySetContains h l l' = filterNestedSets (head' "filterNestedSets1" l) (tail l) l'
| otherwise = filterNestedSets (head l) (tail l) (h : l') | otherwise = filterNestedSets (head' "filterNestedSets2" l) (tail l) (h : l')
...@@ -142,7 +142,7 @@ initFoundations l = Vector.fromList $ map phyloAnalyzer l ...@@ -142,7 +142,7 @@ initFoundations l = Vector.fromList $ map phyloAnalyzer l
-- | To init the base of a Phylo from a List of Periods and Foundations -- | To init the base of a Phylo from a List of Periods and Foundations
initPhyloBase :: [(Date, Date)] -> Vector Ngrams -> PhyloPeaks -> PhyloParam -> Phylo initPhyloBase :: [(Date, Date)] -> Vector Ngrams -> PhyloPeaks -> PhyloParam -> Phylo
initPhyloBase pds fds pks prm = Phylo ((fst . head) pds, (snd . last) pds) fds pks (map (\pd -> initPhyloPeriod pd []) pds) prm initPhyloBase pds fds pks prm = Phylo ((fst . (head' "initPhyloBase")) pds, (snd . last) pds) fds pks (map (\pd -> initPhyloPeriod pd []) pds) prm
-- | To init the param of a Phylo -- | To init the param of a Phylo
initPhyloParam :: Maybe Text -> Maybe Software -> Maybe PhyloQueryBuild -> PhyloParam initPhyloParam :: Maybe Text -> Maybe Software -> Maybe PhyloQueryBuild -> PhyloParam
...@@ -489,7 +489,7 @@ getNeighbours :: Bool -> PhyloGroup -> GroupEdges -> [PhyloGroup] ...@@ -489,7 +489,7 @@ getNeighbours :: Bool -> PhyloGroup -> GroupEdges -> [PhyloGroup]
getNeighbours directed g e = case directed of getNeighbours directed g e = case directed of
True -> map (\((_s,t),_w) -> t) True -> map (\((_s,t),_w) -> t)
$ filter (\((s,_t),_w) -> s == g) e $ filter (\((s,_t),_w) -> s == g) e
False -> map (\((s,t),_w) -> head $ delete g $ nub [s,t,g]) False -> map (\((s,t),_w) -> (head' "getNeighbours") $ delete g $ nub [s,t,g])
$ filter (\((s,t),_w) -> s == g || t == g) e $ filter (\((s,t),_w) -> s == g || t == g) e
......
...@@ -18,9 +18,8 @@ module Gargantext.Viz.Phylo.View.Display ...@@ -18,9 +18,8 @@ module Gargantext.Viz.Phylo.View.Display
where where
import Control.Lens hiding (makeLenses, both, Level) import Control.Lens hiding (makeLenses, both, Level)
import Data.List (null,(++),sortOn)
import Data.List (head,null,(++),sortOn) import Gargantext.Prelude
import Gargantext.Prelude hiding (head)
import Gargantext.Viz.Phylo import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Tools import Gargantext.Viz.Phylo.Tools
...@@ -33,7 +32,7 @@ toNestedView ns ns' ...@@ -33,7 +32,7 @@ toNestedView ns ns'
where where
-------------------------------------- --------------------------------------
lvl' :: Level lvl' :: Level
lvl' = getNodeLevel $ head $ nested lvl' = getNodeLevel $ head' "toNestedView" nested
-------------------------------------- --------------------------------------
nested :: [PhyloNode] nested :: [PhyloNode]
nested = foldl (\ns'' n -> let nIds' = getNodeParentsId n nested = foldl (\ns'' n -> let nIds' = getNodeParentsId n
...@@ -48,7 +47,7 @@ processDisplay :: DisplayMode -> PhyloView -> PhyloView ...@@ -48,7 +47,7 @@ processDisplay :: DisplayMode -> PhyloView -> PhyloView
processDisplay d v = case d of processDisplay d v = case d of
Flat -> v Flat -> v
Nested -> let ns = sortOn getNodeLevel $ v ^. pv_nodes Nested -> let ns = sortOn getNodeLevel $ v ^. pv_nodes
lvl = getNodeLevel $ head ns lvl = getNodeLevel $ head' "processDisplay" ns
in v & pv_nodes .~ toNestedView (filter (\n -> lvl == getNodeLevel n) ns) in v & pv_nodes .~ toNestedView (filter (\n -> lvl == getNodeLevel n) ns)
(filter (\n -> lvl < getNodeLevel n) ns) (filter (\n -> lvl < getNodeLevel n) ns)
--_ -> panic "[ERR][Viz.Phylo.Example.processDisplay] display not found" --_ -> panic "[ERR][Viz.Phylo.Example.processDisplay] display not found"
...@@ -18,10 +18,10 @@ module Gargantext.Viz.Phylo.View.Filters ...@@ -18,10 +18,10 @@ module Gargantext.Viz.Phylo.View.Filters
where where
import Control.Lens hiding (makeLenses, both, Level) import Control.Lens hiding (makeLenses, both, Level)
import Data.List (notElem,head,null,nub,(\\),intersect) import Data.List (notElem,null,nub,(\\),intersect)
import Data.Maybe (isNothing) import Data.Maybe (isNothing)
import Data.Tuple (fst) import Data.Tuple (fst)
import Gargantext.Prelude hiding (head) import Gargantext.Prelude
import Gargantext.Viz.Phylo import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Tools import Gargantext.Viz.Phylo.Tools
...@@ -61,8 +61,8 @@ filterSmallBranch inf sup min' prds v = cleanNodesEdges v v' ...@@ -61,8 +61,8 @@ filterSmallBranch inf sup min' prds v = cleanNodesEdges v v'
-------------------------------------- --------------------------------------
isLone :: [PhyloNode] -> [PhyloPeriodId] -> Bool isLone :: [PhyloNode] -> [PhyloPeriodId] -> Bool
isLone ns prds' = (length ns <= min') isLone ns prds' = (length ns <= min')
&& notElem (head prds') (take inf prds) && notElem (head' "filterSmallBranch1" prds') (take inf prds)
&& notElem (head prds') (take sup $ reverse prds) && notElem (head' "filterSmallBranch2" prds') (take sup $ reverse prds)
-------------------------------------- --------------------------------------
......
...@@ -18,11 +18,11 @@ module Gargantext.Viz.Phylo.View.Metrics ...@@ -18,11 +18,11 @@ module Gargantext.Viz.Phylo.View.Metrics
where where
import Control.Lens hiding (makeLenses, both, Level) import Control.Lens hiding (makeLenses, both, Level)
import Data.List (last,head,groupBy,sortOn) import Data.List (last,groupBy,sortOn)
import Data.Map (insert) import Data.Map (insert)
import Data.Text (Text) import Data.Text (Text)
import Data.Tuple (fst, snd) import Data.Tuple (fst, snd)
import Gargantext.Prelude hiding (head) import Gargantext.Prelude
import Gargantext.Viz.Phylo import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Tools import Gargantext.Viz.Phylo.Tools
...@@ -38,9 +38,9 @@ addBranchMetrics id lbl val v = over (pv_branches ...@@ -38,9 +38,9 @@ addBranchMetrics id lbl val v = over (pv_branches
-- | To get the age (in year) of all the branches of a PhyloView -- | To get the age (in year) of all the branches of a PhyloView
branchAge :: PhyloView -> PhyloView branchAge :: PhyloView -> PhyloView
branchAge v = foldl (\v' b -> let bId = (fst . head) b branchAge v = foldl (\v' b -> let bId = (fst . (head' "branchAge")) b
prds = sortOn fst $ map snd b prds = sortOn fst $ map snd b
in addBranchMetrics bId "age" ((abs . fromIntegral) $ ((snd . last) prds) - ((fst . head) prds)) v') v in addBranchMetrics bId "age" ((abs . fromIntegral) $ ((snd . last) prds) - (fst $ head' "branchAge" prds)) v') v
$ groupBy ((==) `on` fst) $ groupBy ((==) `on` fst)
$ sortOn fst $ sortOn fst
$ map (\n -> (getNodeBranchId n, (fst . fst) $ getNodeId n)) $ map (\n -> (getNodeBranchId n, (fst . fst) $ getNodeId n))
......
...@@ -20,7 +20,7 @@ module Gargantext.Viz.Phylo.View.Sort ...@@ -20,7 +20,7 @@ module Gargantext.Viz.Phylo.View.Sort
import Control.Lens hiding (makeLenses, both, Level) import Control.Lens hiding (makeLenses, both, Level)
import Data.List (sortOn) import Data.List (sortOn)
import Data.Tuple (fst, snd) import Data.Tuple (fst, snd)
import Gargantext.Prelude hiding (head) import Gargantext.Prelude
import Gargantext.Viz.Phylo import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Tools import Gargantext.Viz.Phylo.Tools
......
...@@ -18,11 +18,11 @@ module Gargantext.Viz.Phylo.View.Taggers ...@@ -18,11 +18,11 @@ module Gargantext.Viz.Phylo.View.Taggers
where where
import Control.Lens hiding (makeLenses, both, Level) import Control.Lens hiding (makeLenses, both, Level)
import Data.List (head,concat,nub,groupBy,sortOn,sort) import Data.List (concat,nub,groupBy,sortOn,sort)
import Data.Text (Text,unwords) import Data.Text (Text,unwords)
import Data.Tuple (fst, snd) import Data.Tuple (fst, snd)
import Data.Vector (Vector) import Data.Vector (Vector)
import Gargantext.Prelude hiding (head) import Gargantext.Prelude
import Gargantext.Viz.Phylo import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Tools import Gargantext.Viz.Phylo.Tools
import qualified Data.Map as Map import qualified Data.Map as Map
...@@ -45,7 +45,7 @@ mostFreqNgrams thr groups = map fst ...@@ -45,7 +45,7 @@ mostFreqNgrams thr groups = map fst
$ take thr $ take thr
$ reverse $ reverse
$ sortOn snd $ sortOn snd
$ map (\g -> (head g,length g)) $ map (\g -> (head' "mostFreqNgrams" g,length g))
$ groupBy (==) $ groupBy (==)
$ (sort . concat) $ (sort . concat)
$ map getGroupNgrams groups $ map getGroupNgrams groups
...@@ -87,7 +87,7 @@ nodeLabelCooc v thr p = over (pv_nodes ...@@ -87,7 +87,7 @@ nodeLabelCooc v thr p = over (pv_nodes
. traverse) . traverse)
(\n -> let lbl = ngramsToLabel (getPeaksLabels p) (\n -> let lbl = ngramsToLabel (getPeaksLabels p)
$ mostOccNgrams thr $ mostOccNgrams thr
$ head $ getGroupsFromIds [getNodeId n] p $ head' "nodeLabelCooc" $ getGroupsFromIds [getNodeId n] p
in n & pn_label .~ lbl) v in n & pn_label .~ lbl) v
......
...@@ -23,7 +23,7 @@ import Data.Text (Text) ...@@ -23,7 +23,7 @@ import Data.Text (Text)
import Data.Map (Map, empty, elems, unionWithKey, fromList) import Data.Map (Map, empty, elems, unionWithKey, fromList)
import Data.Tuple (fst, snd) import Data.Tuple (fst, snd)
import Data.Vector (Vector) import Data.Vector (Vector)
import Gargantext.Prelude hiding (head) import Gargantext.Prelude
import Gargantext.Viz.Phylo import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Tools import Gargantext.Viz.Phylo.Tools
import Gargantext.Viz.Phylo.View.Display import Gargantext.Viz.Phylo.View.Display
......
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