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.LinkMaker
20 import Control.Lens hiding (both, Level)
21 import Data.List ((++), sort, concat, nub, words, zip, sortOn, head, null, tail, splitAt, (!!), elem)
24 import Data.Tuple.Extra
26 import Gargantext.Prelude hiding (head)
27 import Gargantext.Viz.Phylo
28 import Gargantext.Viz.Phylo.Tools
29 import Gargantext.Viz.Phylo.Metrics.Proximity
31 import qualified Data.List as List
32 import qualified Data.Map as Map
33 import qualified Data.Maybe as Maybe
36 ------------------------------------------------------------------------
37 -- | Make links from Level to Level
40 -- | To choose a LevelLink strategy based an a given Level
41 shouldLink :: (Level,Level) -> PhyloGroup -> PhyloGroup -> Bool
42 shouldLink (lvl,lvl') g g'
43 | lvl <= 1 = doesContainsOrd (getGroupNgrams g) (getGroupNgrams g')
44 | lvl > 1 = elem (getGroupId g) (getGroupLevelChildsId g')
45 | otherwise = panic ("[ERR][Viz.Phylo.LinkMaker.shouldLink] Level not defined")
48 -- | To set the LevelLinks between a given PhyloGroup and a list of childs/parents PhyloGroups
49 linkGroupToGroups :: (Level,Level) -> PhyloGroup -> [PhyloGroup] -> PhyloGroup
50 linkGroupToGroups (lvl,lvl') current targets
51 | lvl < lvl' = setLevelParents current
52 | lvl > lvl' = setLevelChilds current
55 --------------------------------------
56 setLevelChilds :: PhyloGroup -> PhyloGroup
57 setLevelChilds = over (phylo_groupLevelChilds) addPointers
58 --------------------------------------
59 setLevelParents :: PhyloGroup -> PhyloGroup
60 setLevelParents = over (phylo_groupLevelParents) addPointers
61 --------------------------------------
62 addPointers :: [Pointer] -> [Pointer]
63 addPointers lp = lp ++ Maybe.mapMaybe (\target ->
64 if shouldLink (lvl,lvl') current target
65 then Just ((getGroupId target),1)
67 --------------------------------------
70 -- | To set the LevelLinks between two lists of PhyloGroups
71 linkGroupsByLevel :: (Level,Level) -> Phylo -> [PhyloGroup] -> [PhyloGroup]
72 linkGroupsByLevel (lvl,lvl') p groups = map (\group ->
73 if getGroupLevel group == lvl
74 then linkGroupToGroups (lvl,lvl') group (getGroupsWithFilters lvl' (getGroupPeriod group) p)
78 -- | To set the LevelLink of all the PhyloGroups of a Phylo
79 setLevelLinks :: (Level,Level) -> Phylo -> Phylo
80 setLevelLinks (lvl,lvl') p = alterPhyloGroups (linkGroupsByLevel (lvl,lvl') p) p
83 ------------------------------------------------------------------------
84 -- | Make links from Period to Period
87 -- | To apply the corresponding proximity function based on a given Proximity
88 getProximity :: (Proximity,[Double]) -> PhyloGroup -> PhyloGroup -> (PhyloGroupId, Double)
89 getProximity (prox,param) g1 g2 = case prox of
90 WeightedLogJaccard -> ((getGroupId g2),weightedLogJaccard (param !! 1) (getGroupCooc g1) (unifySharedKeys (getGroupCooc g2) (getGroupCooc g1)))
91 Hamming -> ((getGroupId g2),hamming (getGroupCooc g1) (unifySharedKeys (getGroupCooc g2) (getGroupCooc g1)))
92 _ -> panic ("[ERR][Viz.Phylo.Example.getProximity] Proximity function not defined")
95 -- | To get the next or previous PhyloPeriod based on a given PhyloPeriodId
96 getNextPeriods :: PairTo -> PhyloPeriodId -> [PhyloPeriodId] -> [PhyloPeriodId]
97 getNextPeriods to id l = case to of
98 Childs -> unNested id ((tail . snd) next)
99 Parents -> unNested id ((reverse . fst) next)
100 _ -> panic ("[ERR][Viz.Phylo.Example.getNextPeriods] PairTo type not defined")
102 --------------------------------------
103 next :: ([PhyloPeriodId], [PhyloPeriodId])
105 --------------------------------------
107 idx = case (List.elemIndex id l) of
108 Nothing -> panic ("[ERR][Viz.Phylo.Example.getNextPeriods] PhyloPeriodId not defined")
110 --------------------------------------
111 -- | To have an non-overlapping next period
112 unNested :: PhyloPeriodId -> [PhyloPeriodId] -> [PhyloPeriodId]
115 | nested (fst $ head l) x = unNested x (tail l)
116 | nested (snd $ head l) x = unNested x (tail l)
118 --------------------------------------
119 nested :: Date -> PhyloPeriodId -> Bool
120 nested d prd = d >= fst prd && d <= snd prd
121 --------------------------------------
124 -- | To find the best set (max = 2) of Childs/Parents candidates based on a given Proximity mesure until a maximum depth (max = Period + 5 units )
125 findBestCandidates :: PairTo -> Int -> Int -> (Proximity,[Double]) -> PhyloGroup -> Phylo -> [(PhyloGroupId, Double)]
126 findBestCandidates to depth max (prox,param) group p
127 | depth > max || null next = []
128 | (not . null) best = take 2 best
129 | otherwise = findBestCandidates to (depth + 1) max (prox,param) group p
131 --------------------------------------
132 next :: [PhyloPeriodId]
133 next = getNextPeriods to (getGroupPeriod group) (getPhyloPeriods p)
134 --------------------------------------
135 candidates :: [PhyloGroup]
136 candidates = getGroupsWithFilters (getGroupLevel group) (head next) p
137 --------------------------------------
138 scores :: [(PhyloGroupId, Double)]
139 scores = map (\group' -> getProximity (prox,param) group group') candidates
140 --------------------------------------
141 best :: [(PhyloGroupId, Double)]
144 $ filter (\(id,score) -> case prox of
145 WeightedLogJaccard -> score >= (param !! 0)
146 Hamming -> score <= (param !! 0)) scores
147 --------------------------------------
150 -- | To add a new list of Pointers into an existing Childs/Parents list of Pointers
151 makePair :: PairTo -> PhyloGroup -> [(PhyloGroupId, Double)] -> PhyloGroup
152 makePair to group ids = case to of
153 Childs -> over (phylo_groupPeriodChilds) addPointers group
154 Parents -> over (phylo_groupPeriodParents) addPointers group
155 _ -> panic ("[ERR][Viz.Phylo.Example.makePair] PairTo type not defined")
157 --------------------------------------
158 addPointers :: [Pointer] -> [Pointer]
159 addPointers l = nub $ (l ++ ids)
160 --------------------------------------
163 -- | To pair all the Phylogroups of given PhyloLevel to their best Parents or Childs
164 pairGroupsToGroups :: PairTo -> Level -> (Proximity,[Double]) -> Phylo -> Phylo
165 pairGroupsToGroups to lvl (prox,param) p = alterPhyloGroups
168 if (getGroupLevel group) == lvl
171 --------------------------------------
172 candidates :: [(PhyloGroupId, Double)]
173 candidates = findBestCandidates to 1 5 (prox,param) group p
174 --------------------------------------
176 makePair to group candidates