Commit d3097207 authored by qlobbe's avatar qlobbe

color update

parent e4e913ab
...@@ -52,45 +52,53 @@ import Control.Lens (makeLenses) ...@@ -52,45 +52,53 @@ import Control.Lens (makeLenses)
data CorpusParser = Wos | Csv deriving (Show,Generic,Eq) data CorpusParser = Wos | Csv deriving (Show,Generic,Eq)
data Proximity = WeightedLogJaccard {_sensibility :: Double}
| Hamming
deriving (Show,Generic,Eq)
data Config = data Config =
Config { corpusPath :: FilePath Config { corpusPath :: FilePath
, listPath :: FilePath , listPath :: FilePath
, outputPath :: FilePath , outputPath :: FilePath
, corpusParser :: CorpusParser , corpusParser :: CorpusParser
, corpusLimit :: Int , corpusLimit :: Int
, phyloName :: Text , phyloName :: Text
, phyloLevel :: Int , phyloLevel :: Int
, timeUnit :: Int , phyloProximity :: Proximity
, timeMatching :: Int , timeUnit :: Int
, timePeriod :: Int , maxTimeMatch :: Int
, timeStep :: Int , timePeriod :: Int
, fisSupport :: Int , timeStep :: Int
, fisSize :: Int , fisSupport :: Int
, branchSize :: Int , fisSize :: Int
, branchSize :: Int
} deriving (Show,Generic,Eq) } deriving (Show,Generic,Eq)
defaultConfig :: Config defaultConfig :: Config
defaultConfig = defaultConfig =
Config { corpusPath = "" Config { corpusPath = ""
, listPath = "" , listPath = ""
, outputPath = "" , outputPath = ""
, corpusParser = Csv , corpusParser = Csv
, corpusLimit = 1000 , corpusLimit = 1000
, phyloName = pack "Default Phylo" , phyloName = pack "Default Phylo"
, phyloLevel = 2 , phyloLevel = 2
, timeUnit = 1 , phyloProximity = WeightedLogJaccard 10
, timeMatching = 5 , timeUnit = 1
, timePeriod = 3 , maxTimeMatch = 5
, timeStep = 1 , timePeriod = 3
, fisSupport = 2 , timeStep = 1
, fisSize = 4 , fisSupport = 2
, branchSize = 3 , fisSize = 4
, branchSize = 3
} }
instance FromJSON Config instance FromJSON Config
instance ToJSON Config instance ToJSON Config
instance FromJSON CorpusParser instance FromJSON CorpusParser
instance ToJSON CorpusParser instance ToJSON CorpusParser
instance FromJSON Proximity
instance ToJSON Proximity
-- | Software parameters -- | Software parameters
...@@ -223,6 +231,7 @@ data PhyloGroup = ...@@ -223,6 +231,7 @@ data PhyloGroup =
, _phylo_groupIndex :: Int , _phylo_groupIndex :: Int
, _phylo_groupSupport :: Support , _phylo_groupSupport :: Support
, _phylo_groupNgrams :: [Int] , _phylo_groupNgrams :: [Int]
, _phylo_groupCooc :: !(Cooc)
, _phylo_groupBranchId :: PhyloBranchId , _phylo_groupBranchId :: PhyloBranchId
, _phylo_groupLevelParents :: [Pointer] , _phylo_groupLevelParents :: [Pointer]
, _phylo_groupLevelChilds :: [Pointer] , _phylo_groupLevelChilds :: [Pointer]
...@@ -238,6 +247,8 @@ type Weight = Double ...@@ -238,6 +247,8 @@ type Weight = Double
-- | Pointer : A weighted pointer to a given PhyloGroup -- | Pointer : A weighted pointer to a given PhyloGroup
type Pointer = (PhyloGroupId, Weight) type Pointer = (PhyloGroupId, Weight)
type Link = ((PhyloGroupId, PhyloGroupId), Weight)
data Filiation = ToParents | ToChilds deriving (Generic, Show) data Filiation = ToParents | ToChilds deriving (Generic, Show)
data PointerType = TemporalPointer | LevelPointer deriving (Generic, Show) data PointerType = TemporalPointer | LevelPointer deriving (Generic, Show)
......
...@@ -16,7 +16,7 @@ Portability : POSIX ...@@ -16,7 +16,7 @@ Portability : POSIX
module Gargantext.Viz.Phylo.PhyloMaker where module Gargantext.Viz.Phylo.PhyloMaker where
import Data.List (concat, nub, partition, sort, (++)) import Data.List (concat, nub, partition, sort, (++))
import Data.Map (Map, fromListWith, keys, unionWith, fromList, empty, toList, elems, (!)) import Data.Map (Map, fromListWith, keys, unionWith, fromList, empty, toList, elems, (!), filterWithKey, restrictKeys)
import Data.Set (size) import Data.Set (size)
import Data.Vector (Vector) import Data.Vector (Vector)
...@@ -58,7 +58,7 @@ toPhylo docs lst conf = phylo1 ...@@ -58,7 +58,7 @@ toPhylo docs lst conf = phylo1
-------------------- --------------------
appendGroups :: (a -> PhyloPeriodId -> Level -> Int -> Vector Ngrams -> PhyloGroup) -> Level -> Map (Date,Date) [a] -> Phylo -> Phylo appendGroups :: (a -> PhyloPeriodId -> Level -> Int -> Vector Ngrams -> [Cooc] -> PhyloGroup) -> Level -> Map (Date,Date) [a] -> Phylo -> Phylo
appendGroups f lvl m phylo = trace ("\n" <> "-- | Append " <> show (length $ concat $ elems m) <> " groups to Level " <> show (lvl) <> "\n") appendGroups f lvl m phylo = trace ("\n" <> "-- | Append " <> show (length $ concat $ elems m) <> " groups to Level " <> show (lvl) <> "\n")
$ over ( phylo_periods $ over ( phylo_periods
. traverse . traverse
...@@ -70,20 +70,25 @@ appendGroups f lvl m phylo = trace ("\n" <> "-- | Append " <> show (length $ co ...@@ -70,20 +70,25 @@ appendGroups f lvl m phylo = trace ("\n" <> "-- | Append " <> show (length $ co
phyloFis = m ! pId phyloFis = m ! pId
in phyloLvl in phyloLvl
& phylo_levelGroups .~ (fromList $ foldl (\groups obj -> & phylo_levelGroups .~ (fromList $ foldl (\groups obj ->
groups ++ [(((pId,lvl),length groups),f obj pId lvl (length groups) (getRoots phylo))] ) [] phyloFis) groups ++ [ (((pId,lvl),length groups)
, f obj pId lvl (length groups) (getRoots phylo)
(elems $ restrictKeys (phylo ^. phylo_timeCooc) $ periodsToYears [pId]))
] ) [] phyloFis)
else else
phyloLvl ) phyloLvl )
phylo phylo
fisToGroup :: PhyloFis -> PhyloPeriodId -> Level -> Int -> Vector Ngrams -> PhyloGroup fisToGroup :: PhyloFis -> PhyloPeriodId -> Level -> Int -> Vector Ngrams -> [Cooc] -> PhyloGroup
fisToGroup fis pId lvl idx fdt = fisToGroup fis pId lvl idx fdt coocs =
PhyloGroup pId lvl idx let ngrams = ngramsToIdx (Set.toList $ fis ^. phyloFis_clique) fdt
(fis ^. phyloFis_support) in PhyloGroup pId lvl idx
(ngramsToIdx (Set.toList $ fis ^. phyloFis_clique) fdt) (fis ^. phyloFis_support)
(1,[]) ngrams
[] [] [] [] (ngramsToCooc ngrams coocs)
Nothing (1,[])
[] [] [] []
Nothing
toPhylo1 :: [Document] -> Phylo -> Phylo toPhylo1 :: [Document] -> Phylo -> Phylo
...@@ -160,6 +165,14 @@ toPhyloFis phyloDocs support clique = traceFis "Filtered Fis" ...@@ -160,6 +165,14 @@ toPhyloFis phyloDocs support clique = traceFis "Filtered Fis"
-------------------- --------------------
-- | To build the local cooc matrix of each phylogroup
ngramsToCooc :: [Int] -> [Cooc] -> Cooc
ngramsToCooc ngrams coocs =
let cooc = foldl (\acc cooc' -> sumCooc acc cooc') empty coocs
pairs = listToKeys ngrams
in filterWithKey (\k _ -> elem k pairs) cooc
-- | To transform the docs into a time map of coocurency matrix -- | To transform the docs into a time map of coocurency matrix
docsToCoocByYear :: [Document] -> Vector Ngrams -> Config -> Map Date Cooc docsToCoocByYear :: [Document] -> Vector Ngrams -> Config -> Map Date Cooc
docsToCoocByYear docs fdt conf = docsToCoocByYear docs fdt conf =
......
...@@ -19,7 +19,7 @@ module Gargantext.Viz.Phylo.PhyloTools where ...@@ -19,7 +19,7 @@ module Gargantext.Viz.Phylo.PhyloTools where
import Data.Vector (Vector, elemIndex) import Data.Vector (Vector, elemIndex)
import Data.List (sort, concat, null, union, (++), tails, sortOn) import Data.List (sort, concat, null, union, (++), tails, sortOn)
import Data.Set (Set, size) import Data.Set (Set, size)
import Data.Map (Map, elems, fromList, unionWith, keys, member, (!)) import Data.Map (Map, elems, fromList, unionWith, keys, member, (!), toList)
import Data.String (String) import Data.String (String)
import Gargantext.Prelude import Gargantext.Prelude
...@@ -156,9 +156,9 @@ listToMatrix lst = fromList $ map (\k -> (k,1)) $ listToKeys $ sort lst ...@@ -156,9 +156,9 @@ listToMatrix lst = fromList $ map (\k -> (k,1)) $ listToKeys $ sort lst
sumCooc :: Cooc -> Cooc -> Cooc sumCooc :: Cooc -> Cooc -> Cooc
sumCooc cooc cooc' = unionWith (+) cooc cooc' sumCooc cooc cooc' = unionWith (+) cooc cooc'
--------------- --------------------
-- | Phylo | -- -- | PhyloGroup | --
--------------- --------------------
getGroupId :: PhyloGroup -> PhyloGroupId getGroupId :: PhyloGroup -> PhyloGroupId
getGroupId group = ((group ^. phylo_groupPeriod, group ^. phylo_groupLevel), group ^. phylo_groupIndex) getGroupId group = ((group ^. phylo_groupPeriod, group ^. phylo_groupLevel), group ^. phylo_groupIndex)
...@@ -216,4 +216,17 @@ updatePhyloGroups lvl m phylo = ...@@ -216,4 +216,17 @@ updatePhyloGroups lvl m phylo =
in in
if member id m if member id m
then m ! id then m ! id
else group ) phylo else group ) phylo
\ No newline at end of file
------------------
-- | Pointers | --
------------------
pointersToLinks :: PhyloGroupId -> [Pointer] -> [Link]
pointersToLinks id pointers = map (\p -> ((id,fst p),snd p)) pointers
mergeLinks :: [Link] -> [Link] -> [Link]
mergeLinks toChilds toParents =
let toChilds' = fromList $ map (\((from,to),w) -> ((to,from),w)) toChilds
in toList $ unionWith max (fromList toParents) toChilds'
\ No newline at end of file
...@@ -137,9 +137,9 @@ setPeakDotEdge bId nId = edge bId nId [Width 3, Color [toWColor Black], ArrowHea ...@@ -137,9 +137,9 @@ setPeakDotEdge bId nId = edge bId nId [Width 3, Color [toWColor Black], ArrowHea
colorFromDynamics :: Double -> H.Attribute colorFromDynamics :: Double -> H.Attribute
colorFromDynamics d colorFromDynamics d
| d == 0 = H.BGColor (toColor PaleGreen) | d == 0 = H.BGColor (toColor LightCoral)
| d == 1 = H.BGColor (toColor SkyBlue) | d == 1 = H.BGColor (toColor Khaki)
| d == 2 = H.BGColor (toColor LightPink) | d == 2 = H.BGColor (toColor SkyBlue)
| otherwise = H.Color (toColor Black) | otherwise = H.Color (toColor Black)
......
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