]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Viz/Graph/Utils.hs
[FIX scores]
[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 These functions are used for Vector.Matrix only.
11
12 -}
13
14 {-# LANGUAGE BangPatterns #-}
15 {-# LANGUAGE NoImplicitPrelude #-}
16 {-# LANGUAGE FlexibleContexts #-}
17 {-# LANGUAGE Strict #-}
18
19 module Gargantext.Viz.Graph.Utils
20 where
21
22 import Data.Matrix hiding (identity)
23
24 import Data.Map (Map)
25 import qualified Data.Map as M
26
27 import Data.Set (Set)
28 import qualified Data.Set as S
29
30 import Data.Vector (Vector)
31 import qualified Data.Vector as V
32
33 import qualified Data.List as L
34 import Gargantext.Prelude
35
36 ------------------------------------------------------------------------
37 -- | Some utils to build the matrix from cooccurrence results
38
39 -- | For tests only, to be removed
40 -- m1 :: Matrix Double
41 -- m1 = fromList 300 300 [1..]
42 ------------------------------------------------------------------------
43 ------------------------------------------------------------------------
44 data Axis = Col | Row
45 ------------------------------------------------------------------------
46 -- | Matrix functions
47 type AxisId = Int
48
49 -- Data.Vector.Additions
50 dropAt :: Int -> Vector a -> Vector a
51 dropAt n v = debut <> (V.tail fin)
52 where
53 debut = V.take n v
54 fin = V.drop n v
55
56 total :: Num a => Matrix a -> a
57 total m = V.sum $ V.map (\c -> V.sum (getCol c m)) (V.enumFromTo 1 (nOf Col m))
58
59 nOf :: Axis -> Matrix a -> Int
60 nOf Row = nrows
61 nOf Col = ncols
62
63 axis :: Axis -> AxisId -> Matrix a -> Vector a
64 axis Col = getCol
65 axis Row = getRow
66
67
68 toListsWithIndex :: Matrix a -> [((Int, Int), a)]
69 toListsWithIndex m = concat' $ zip [1..] $ map (\c -> zip [1..] c) $ toLists m
70 where
71 concat' :: [(Int, [(Int, a)])] -> [((Int, Int), a)]
72 concat' xs = L.concat $ map (\(x, ys) -> map (\(y, a) -> ((x,y), a)) ys ) xs
73
74