]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Viz/Phylo/Aggregates/Cooc.hs
[MERGE] Fix warnings.
[gargantext.git] / src / Gargantext / Viz / Phylo / Aggregates / Cooc.hs
1 {-|
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
8 Portability : POSIX
9
10
11 -}
12
13 {-# LANGUAGE NoImplicitPrelude #-}
14 {-# LANGUAGE FlexibleContexts #-}
15 {-# LANGUAGE OverloadedStrings #-}
16
17 module Gargantext.Viz.Phylo.Aggregates.Cooc
18 where
19
20 import Data.List (union,concat)
21 import Data.Map (Map, elems, adjust)
22 import Gargantext.Prelude hiding (head)
23 import Gargantext.Viz.Phylo
24 import Gargantext.Viz.Phylo.Tools
25 import qualified Data.Map as Map
26 import qualified Data.Set as Set
27
28
29
30 -- | To transform the Fis into a coocurency Matrix in a Phylo
31 fisToCooc :: Map (Date, Date) [PhyloFis] -> Phylo -> Map (Int, Int) Double
32 fisToCooc m p = map (/docs)
33 $ foldl (\mem x -> adjust (+1) (getKeyPair x mem) mem) cooc
34 $ concat
35 $ map (\x -> listToUnDirectedCombiWith (\y -> getIdxInPeaks y p) $ (Set.toList . getClique) x)
36 $ (concat . elems) m
37 where
38 --------------------------------------
39 fisNgrams :: [Ngrams]
40 fisNgrams = foldl (\mem x -> union mem $ (Set.toList . getClique) x) [] $ (concat . elems) m
41 --------------------------------------
42 docs :: Double
43 docs = fromIntegral $ foldl (\mem x -> mem + (getSupport x)) 0 $ (concat . elems) m
44 --------------------------------------
45 cooc :: Map (Int, Int) (Double)
46 cooc = Map.fromList $ map (\x -> (x,0)) (listToUnDirectedCombiWith (\y -> getIdxInPeaks y p) fisNgrams)
47 --------------------------------------
48
49
50 -- phyloCooc :: Map (Int, Int) Double
51 -- phyloCooc = fisToCooc phyloFis phylo1_0_1