]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Viz/Phylo/Aggregates/Cooc.hs
adapt Main to example
[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
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 -- | To transform the Fis into a coocurency Matrix in a Phylo
30 fisToCooc :: Map (Date, Date) [PhyloFis] -> Phylo -> Map (Int, Int) Double
31 fisToCooc m p = map (/docs)
32 $ foldl (\mem x -> adjust (+1) (getKeyPair x mem) mem) cooc
33 $ concat
34 $ map (\x -> listToUnDirectedCombiWith (\y -> getIdxInRoots y p) $ (Set.toList . getClique) x)
35 $ (concat . elems) m
36 where
37 --------------------------------------
38 fisNgrams :: [Ngrams]
39 fisNgrams = foldl (\mem x -> union mem $ (Set.toList . getClique) x) [] $ (concat . elems) m
40 --------------------------------------
41 docs :: Double
42 docs = fromIntegral $ foldl (\mem x -> mem + (getSupport x)) 0 $ (concat . elems) m
43 --------------------------------------
44 cooc :: Map (Int, Int) (Double)
45 cooc = Map.fromList $ map (\x -> (x,0)) (listToUnDirectedCombiWith (\y -> getIdxInRoots y p) fisNgrams)
46 --------------------------------------
47
48
49 -- phyloCooc :: Map (Int, Int) Double
50 -- phyloCooc = fisToCooc phyloFis phylo1_0_1