]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Viz/Graph/Utils.hs
[Types] Phylo
[gargantext.git] / src / Gargantext / Viz / Graph / Utils.hs
1 {-|
2 Module : Gargantext.Graph.Distances.Utils
3 Description :
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 {-# LANGUAGE BangPatterns #-}
13 {-# LANGUAGE NoImplicitPrelude #-}
14 {-# LANGUAGE FlexibleContexts #-}
15 {-# LANGUAGE Strict #-}
16
17 module Gargantext.Viz.Graph.Utils
18 where
19
20 import Data.Matrix hiding (identity)
21
22 import Data.Map (Map)
23 import qualified Data.Map as M
24
25 import Data.Set (Set)
26 import qualified Data.Set as S
27
28 import Data.Vector (Vector)
29 import qualified Data.Vector as V
30
31 import qualified Data.List as L
32 import Gargantext.Prelude
33
34 ------------------------------------------------------------------------
35 -- | Some utils to build the matrix from cooccurrence results
36
37 type Distance = Double
38 type Cooc = Int
39 type NgramId = Int
40 type Index = Int
41
42 -- Type Families
43 --type Matrix' Index a
44 --type Matrix' NgramId a
45
46 data Matrice a = Matrice { matrice_fromIndex :: !(Map Index NgramId)
47 , matrice_toIndex :: !(Map NgramId Index)
48 , matrice :: !(Matrix a)
49 } deriving (Show)
50
51 --fromMatrice :: Matrice Double -> [(NgramId, NgramId, Double)]
52 --fromMatrice m = undefined
53
54
55 toMatrice :: [(NgramId, NgramId, Int)] -> Matrice Double
56 toMatrice ns = Matrice fromIndx toIndx m
57 where
58 s = cooc2set ns
59 (fromIndx, toIndx) = set2indexes s
60 n = (length (S.toList s))
61 idx = toIndex toIndx ns
62 m = matrix n n (\x -> maybe 0 identity (fromIntegral <$> M.lookup x idx))
63
64 -------------------------------------------------------------------------------
65 -------------------------------------------------------------------------------
66 toIndex :: Map NgramId Index -> [(NgramId, NgramId, a)] -> Map (Index,Index) a
67 toIndex ni ns = to ni ns
68
69 fromIndex :: Map Index NgramId -> [(Index, Index, a)] -> Map (NgramId,NgramId) a
70 fromIndex ni ns = to ni ns
71 -------------------------------------------------------------------------------
72 to :: (Ord b, Ord k) => Map k b -> [(k, k, a)] -> Map (b, b) a
73 to index ns = M.fromList $ map (\(a1,a2,c) -> ( ( (M.!) index a1
74 , (M.!) index a2
75 )
76 , c
77 )
78 ) ns
79
80 -------------------------------------------------------------------------------
81 cooc2set :: [(NgramId, NgramId, a)] -> Set NgramId
82 cooc2set cs' = foldl' (\s (a1,a2,_) -> insert [a1,a2] s ) S.empty cs'
83 where
84 insert as s = foldl' (\s' a -> S.insert a s') s as
85
86
87 set2indexes :: Set NgramId -> (Map Index NgramId, Map NgramId Index)
88 set2indexes s = (M.fromList fromIndex', M.fromList toIndex')
89 where
90 s' = S.toList s
91 fromIndex' = zip [1..] s'
92 toIndex' = zip s' [1..]
93
94
95 ------------------------------------------------------------------------
96 -- Data.Vector.Additions
97 dropAt :: Int -> Vector a -> Vector a
98 dropAt n v = debut <> (V.tail fin)
99 where
100 debut = V.take n v
101 fin = V.drop n v
102
103 ------------------------------------------------------------------------
104 data Axis = Col | Row
105 ---- | Matrix Algebra
106 --data Algebra a = Point a | Vector a | Matrix a
107 --
108 --multiply :: Algebra a -> Matrix a -> Matrix a
109 --multiply (Point a) = undefined
110 --multiply (Vector a) = undefined
111 --multiply (Matrix a) = undefined
112 --
113 --div :: Fractional a => Matrix a -> Matrix a
114 --div m = foldl' (\m c -> divCol c m) m [1.. (ncols m)]
115 -- where
116 -- divCol c m = mapCol (\_ x -> 1/x) c m
117 --
118 --divide :: Fractional a => Matrix a -> Matrix a -> Matrix a
119 --divide a b = a `multStd` (div b)
120
121 ------------------------------------------------------------------------
122 -- | Matrix functions
123 type AxisId = Int
124
125 total :: Num a => Matrix a -> a
126 total m = V.sum $ V.map (\c -> V.sum (getCol c m)) (V.enumFromTo 1 (nOf Col m))
127
128 nOf :: Axis -> Matrix a -> Int
129 nOf Row = nrows
130 nOf Col = ncols
131
132 axis :: Axis -> AxisId -> Matrix a -> Vector a
133 axis Col = getCol
134 axis Row = getRow
135
136
137 toListsWithIndex :: Matrix a -> [((Int, Int), a)]
138 toListsWithIndex m = concat' $ zip [1..] $ map (\c -> zip [1..] c) $ toLists m
139 where
140 concat' :: [(Int, [(Int, a)])] -> [((Int, Int), a)]
141 concat' xs = L.concat $ map (\(x, ys) -> map (\(y, a) -> ((x,y), a)) ys ) xs
142
143
144 -- | For tests only, to be removed
145 m1 :: Matrix Double
146 m1 = fromList 300 300 [1..]
147