]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Viz/Phylo/Aggregates/Cooc.hs
[Phylo][Merge] Fix warnings and adding Eq instance to Phylo for Behavior test.
[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 Data.Tuple (fst, snd)
23 import Gargantext.Prelude hiding (head)
24 import Gargantext.Viz.Phylo
25 import Gargantext.Viz.Phylo.Tools
26 import qualified Data.Map as Map
27 import qualified Data.Set as Set
28
29
30
31 -- | To transform the Fis into a coocurency Matrix in a Phylo
32 fisToCooc :: Map (Date, Date) [Fis] -> Phylo -> Map (Int, Int) Double
33 fisToCooc m p = map (/docs)
34 $ foldl (\mem x -> adjust (+1) (getKeyPair x mem) mem) cooc
35 $ concat
36 $ map (\x -> listToUnDirectedCombiWith (\y -> getIdxInFoundations y p) $ (Set.toList . fst) x)
37 $ (concat . elems) m
38 where
39 --------------------------------------
40 fisNgrams :: [Ngrams]
41 fisNgrams = foldl (\mem x -> union mem $ (Set.toList . fst) x) [] $ (concat . elems) m
42 --------------------------------------
43 docs :: Double
44 docs = fromIntegral $ foldl (\mem x -> mem + (snd x)) 0 $ (concat . elems) m
45 --------------------------------------
46 cooc :: Map (Int, Int) (Double)
47 cooc = Map.fromList $ map (\x -> (x,0)) (listToUnDirectedCombiWith (\x -> getIdxInFoundations x p) fisNgrams)
48 --------------------------------------