]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Core/Viz/Graph/Utils.hs
[refactoring] add StrictData option, refactor Data.Map to Strict
[gargantext.git] / src / Gargantext / Core / Viz / Graph / Utils.hs
1 {-|
2 Module : Gargantext.Core.Viz.Graph.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 These functions are used for Vector.Matrix only.
11
12 -}
13
14 {-# LANGUAGE BangPatterns #-}
15 {-# LANGUAGE Strict #-}
16
17 module Gargantext.Core.Viz.Graph.Utils
18 where
19
20 import Data.List (unzip)
21 import Data.Map.Strict (Map)
22 import Data.Matrix hiding (identity)
23 import Data.Maybe (catMaybes)
24 import Data.Set (Set)
25 import Data.Vector (Vector)
26 import Gargantext.Core.Text.Metrics.Count (occurrencesWith)
27 import Gargantext.Prelude
28 import qualified Data.List as List
29 import qualified Data.Map.Strict as Map
30 import qualified Data.Set as Set
31 import qualified Data.Vector as Vector
32
33 ------------------------------------------------------------------------
34 -- | Some utils to build the matrix from cooccurrence results
35
36 -- | For tests only, to be removed
37 -- m1 :: Matrix Double
38 -- m1 = fromList 300 300 [1..]
39 ------------------------------------------------------------------------
40 ------------------------------------------------------------------------
41 data Axis = Col | Row
42 ------------------------------------------------------------------------
43 -- | Matrix functions
44 type AxisId = Int
45
46 -- Data.Vector.Additions
47 dropAt :: Int -> Vector a -> Vector a
48 dropAt n v = debut <> (Vector.tail fin)
49 where
50 debut = Vector.take n v
51 fin = Vector.drop n v
52
53 total :: Num a => Matrix a -> a
54 total m = Vector.sum $ Vector.map (\c -> Vector.sum (getCol c m)) (Vector.enumFromTo 1 (nOf Col m))
55
56 nOf :: Axis -> Matrix a -> Int
57 nOf Row = nrows
58 nOf Col = ncols
59
60 axis :: Axis -> AxisId -> Matrix a -> Vector a
61 axis Col = getCol
62 axis Row = getRow
63
64
65 toListsWithIndex :: Matrix a -> [((Int, Int), a)]
66 toListsWithIndex m = concat' $ zip [1..] $ List.map (\c -> zip [1..] c) $ toLists m
67 where
68 concat' :: [(Int, [(Int, a)])] -> [((Int, Int), a)]
69 concat' xs = List.concat $ List.map (\(x, ys) -> List.map (\(y, a) -> ((x,y), a)) ys ) xs
70
71 ------------------------------------------------------------------------
72 -- Utils to manage Graphs
73
74 edgesFilter :: (Ord a, Ord b) => Map (a,a) b -> Map (a,a) b
75 edgesFilter m = Map.fromList $ catMaybes results
76 where
77 results = [ let
78 ij = Map.lookup (i,j) m
79 ji = Map.lookup (j,i) m
80 in getMax (i,j) ij ji
81 | i <- keys
82 , j <- keys
83 , i < j
84 ]
85 keys = Set.toList $ Set.fromList (x <> y)
86 (x,y) = unzip $ Map.keys m
87
88 nodesFilter :: (Show a, Show b, Ord a, Ord b, Num b) => (b -> Bool) -> Map (a,a) b -> (Map (a,a) b, Set a)
89 nodesFilter f m = (m', toKeep)
90 where
91 m' = Map.filterWithKey (\(a,b) _ -> Set.member a toKeep && Set.member b toKeep) m
92 toKeep = Set.fromList
93 $ Map.keys
94 $ Map.filter f
95 $ occurrencesWith identity
96 $ tupleConcat
97 $ List.unzip
98 $ Map.keys m
99 tupleConcat :: ([a],[a]) -> [a]
100 tupleConcat (a,b) = a <> b
101
102
103 getMax :: Ord b
104 => (a,a)
105 -> Maybe b
106 -> Maybe b
107 -> Maybe ((a,a), b)
108 getMax (i,j) (Just d) Nothing = Just ((i,j), d)
109 getMax (i,j) Nothing (Just d) = Just ((j,i), d)
110 getMax ij (Just di) (Just dj) = if di >= dj then getMax ij (Just di) Nothing
111 else getMax ij Nothing (Just dj)
112 getMax _ _ _ = Nothing