]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Core/Viz/Graph/Utils.hs
Merge branch 'dev' into 70-dev-searx-parser
[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.Map (Map)
21 import Data.Matrix hiding (identity)
22 import Data.Vector (Vector)
23 import qualified Data.List as L
24 import qualified Data.Map as Map
25 import Gargantext.Prelude
26 import Data.List (unzip)
27 import qualified Data.Vector as V
28 import Data.Maybe (catMaybes)
29 import qualified Data.Set as Set
30 ------------------------------------------------------------------------
31 -- | Some utils to build the matrix from cooccurrence results
32
33 -- | For tests only, to be removed
34 -- m1 :: Matrix Double
35 -- m1 = fromList 300 300 [1..]
36 ------------------------------------------------------------------------
37 ------------------------------------------------------------------------
38 data Axis = Col | Row
39 ------------------------------------------------------------------------
40 -- | Matrix functions
41 type AxisId = Int
42
43 -- Data.Vector.Additions
44 dropAt :: Int -> Vector a -> Vector a
45 dropAt n v = debut <> (V.tail fin)
46 where
47 debut = V.take n v
48 fin = V.drop n v
49
50 total :: Num a => Matrix a -> a
51 total m = V.sum $ V.map (\c -> V.sum (getCol c m)) (V.enumFromTo 1 (nOf Col m))
52
53 nOf :: Axis -> Matrix a -> Int
54 nOf Row = nrows
55 nOf Col = ncols
56
57 axis :: Axis -> AxisId -> Matrix a -> Vector a
58 axis Col = getCol
59 axis Row = getRow
60
61
62 toListsWithIndex :: Matrix a -> [((Int, Int), a)]
63 toListsWithIndex m = concat' $ zip [1..] $ map (\c -> zip [1..] c) $ toLists m
64 where
65 concat' :: [(Int, [(Int, a)])] -> [((Int, Int), a)]
66 concat' xs = L.concat $ map (\(x, ys) -> map (\(y, a) -> ((x,y), a)) ys ) xs
67
68 ------------------------------------------------------------------------
69 -- Utils to manage Graphs
70
71 edgesFilter :: (Ord a, Ord b) => Map (a,a) b -> Map (a,a) b
72 edgesFilter m = Map.fromList $ catMaybes results
73 where
74 results = [ let
75 ij = Map.lookup (i,j) m
76 ji = Map.lookup (j,i) m
77 in getMax (i,j) ij ji
78 | i <- keys
79 , j <- keys
80 , i < j
81 ]
82 keys = Set.toList $ Set.fromList (x <> y)
83 (x,y) = unzip $ Map.keys m
84
85
86
87
88 getMax :: Ord b
89 => (a,a)
90 -> Maybe b
91 -> Maybe b
92 -> Maybe ((a,a), b)
93 getMax (i,j) (Just d) Nothing = Just ((i,j), d)
94 getMax (i,j) Nothing (Just d) = Just ((j,i), d)
95 getMax ij (Just di) (Just dj) = if di >= dj then getMax ij (Just di) Nothing
96 else getMax ij Nothing (Just dj)
97 getMax _ _ _ = Nothing
98
99