2 Module : Gargantext.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.Viz.Graph.Utils
20 import Data.Matrix hiding (identity)
22 import Data.Vector (Vector)
23 import qualified Data.Vector as V
25 import qualified Data.List as L
26 import Gargantext.Prelude
28 ------------------------------------------------------------------------
29 -- | Some utils to build the matrix from cooccurrence results
31 -- | For tests only, to be removed
32 -- m1 :: Matrix Double
33 -- m1 = fromList 300 300 [1..]
34 ------------------------------------------------------------------------
35 ------------------------------------------------------------------------
37 ------------------------------------------------------------------------
41 -- Data.Vector.Additions
42 dropAt :: Int -> Vector a -> Vector a
43 dropAt n v = debut <> (V.tail fin)
48 total :: Num a => Matrix a -> a
49 total m = V.sum $ V.map (\c -> V.sum (getCol c m)) (V.enumFromTo 1 (nOf Col m))
51 nOf :: Axis -> Matrix a -> Int
55 axis :: Axis -> AxisId -> Matrix a -> Vector a
60 toListsWithIndex :: Matrix a -> [((Int, Int), a)]
61 toListsWithIndex m = concat' $ zip [1..] $ map (\c -> zip [1..] c) $ toLists m
63 concat' :: [(Int, [(Int, a)])] -> [((Int, Int), a)]
64 concat' xs = L.concat $ map (\(x, ys) -> map (\(y, a) -> ((x,y), a)) ys ) xs