2 Module : Gargantext.Core.Viz.Graph.Utils
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
10 These functions are used for Vector.Matrix only.
14 {-# LANGUAGE BangPatterns #-}
15 {-# LANGUAGE Strict #-}
17 module Gargantext.Core.Viz.Graph.Utils
20 import Data.List (unzip)
22 import Data.Matrix hiding (identity)
23 import Data.Maybe (catMaybes)
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 as Map
30 import qualified Data.Set as Set
31 import qualified Data.Vector as Vector
33 ------------------------------------------------------------------------
34 -- | Some utils to build the matrix from cooccurrence results
36 -- | For tests only, to be removed
37 -- m1 :: Matrix Double
38 -- m1 = fromList 300 300 [1..]
39 ------------------------------------------------------------------------
40 ------------------------------------------------------------------------
42 ------------------------------------------------------------------------
46 -- Data.Vector.Additions
47 dropAt :: Int -> Vector a -> Vector a
48 dropAt n v = debut <> (Vector.tail fin)
50 debut = Vector.take n v
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))
56 nOf :: Axis -> Matrix a -> Int
60 axis :: Axis -> AxisId -> Matrix a -> Vector a
65 toListsWithIndex :: Matrix a -> [((Int, Int), a)]
66 toListsWithIndex m = concat' $ zip [1..] $ List.map (\c -> zip [1..] c) $ toLists m
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
71 ------------------------------------------------------------------------
72 -- Utils to manage Graphs
74 edgesFilter :: (Ord a, Ord b) => Map (a,a) b -> Map (a,a) b
75 edgesFilter m = Map.fromList $ catMaybes results
78 ij = Map.lookup (i,j) m
79 ji = Map.lookup (j,i) m
85 keys = Set.toList $ Set.fromList (x <> y)
86 (x,y) = unzip $ Map.keys m
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)
91 m' = Map.filterWithKey (\(a,b) _ -> Set.member a toKeep && Set.member b toKeep) m
95 $ occurrencesWith identity
99 tupleConcat :: ([a],[a]) -> [a]
100 tupleConcat (a,b) = 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