]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Viz/Graph/Index.hs
[FEAT] Proxemy and confluence implemented and tested (need refactor).
[gargantext.git] / src / Gargantext / Viz / Graph / Index.hs
1 {-|
2 Module : Gargantext.Graph.Distances.Utils
3 Description : Tools to compute distances from Cooccurrences
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
8 Portability : POSIX
9
10 Basically @compute@ takes an accelerate function as first input, a Map
11 of coccurrences as second input and outputs a Map automatically using
12 indexes.
13
14 TODO:
15 --cooc2fgl :: Ord t, Integral n => Map (t, t) n -> Graph
16 --fgl2json
17
18 -}
19
20 {-# LANGUAGE BangPatterns #-}
21 {-# LANGUAGE FlexibleContexts #-}
22 {-# LANGUAGE NoImplicitPrelude #-}
23 {-# LANGUAGE TypeOperators #-}
24 {-# LANGUAGE MonoLocalBinds #-}
25
26 module Gargantext.Viz.Graph.Index
27 where
28
29 import qualified Data.Array.Accelerate as A
30 import qualified Data.Array.Accelerate.Interpreter as A
31 import Data.Array.Accelerate (Matrix, Elt, Shape, (:.)(..), Z(..))
32
33 import Data.Maybe (fromMaybe)
34
35 import Data.Set (Set)
36 import qualified Data.Set as S
37
38 import Data.Map (Map)
39 import qualified Data.Map.Strict as M
40
41 -- import Data.Vector (Vector)
42
43 import Gargantext.Prelude
44
45 type Index = Int
46
47 -------------------------------------------------------------------------------
48 -------------------------------------------------------------------------------
49 score :: (Ord t) => (A.Matrix Int -> A.Matrix Double)
50 -> Map (t, t) Int
51 -> Map (t, t) Double
52 score f m = fromIndex fromI . mat2map . f $ cooc2mat toI m
53 where
54 (toI, fromI) = createIndices m
55
56 -------------------------------------------------------------------------------
57 -------------------------------------------------------------------------------
58 cooc2mat :: Ord t => Map t Index -> Map (t, t) Int -> Matrix Int
59 cooc2mat ti m = map2mat 0 n idx
60 where
61 n = M.size ti
62 idx = toIndex ti m -- it is important to make sure that toIndex is ran only once.
63
64 map2mat :: Elt a => a -> Int -> Map (Index, Index) a -> Matrix a
65 map2mat def n m = A.fromFunction shape (\(Z :. x :. y) -> fromMaybe def $ M.lookup (x, y) m)
66 where
67 shape = (Z :. n :. n)
68
69 mat2map :: (Elt a, Shape (Z :. Index)) =>
70 A.Array (Z :. Index :. Index) a -> Map (Index, Index) a
71 mat2map m = M.fromList . map f . A.toList . A.run . A.indexed $ A.use m
72 where
73 -- Z :. _ :. n = A.arrayShape m
74 f ((Z :. i :. j), x) = ((i, j), x)
75
76 -------------------------------------------------------------------------------
77 -------------------------------------------------------------------------------
78 toIndex :: Ord t => Map t Index -> Map (t,t) a -> Map (Index,Index) a
79 toIndex ni ns = indexConversion ni ns
80
81 fromIndex :: Ord t => Map Index t -> Map (Index, Index) a -> Map (t,t) a
82 fromIndex ni ns = indexConversion ni ns
83
84 indexConversion :: (Ord b, Ord k) => Map k b -> Map (k,k) a -> Map (b, b) a
85 indexConversion index ms = M.fromList $ map (\((k1,k2),c) -> ( ((M.!) index k1, (M.!) index k2), c)) (M.toList ms)
86 ---------------------------------------------------------------------------------
87
88 -------------------------------------------------------------------------------
89 --fromIndex' :: Ord t => Vector t -> Map (Index, Index) a -> Map (t,t) a
90 --fromIndex' vi ns = undefined
91
92 -- TODO: returing a Vector should be faster than a Map
93 -- createIndices' :: Ord t => Map (t, t) b -> (Map t Index, Vector t)
94 -- createIndices' = undefined
95
96 createIndices :: Ord t => Map (t, t) b -> (Map t Index, Map Index t)
97 createIndices = set2indices . map2set
98 where
99 map2set :: Ord t => Map (t, t) a -> Set t
100 map2set cs' = foldl' (\s ((t1,t2),_) -> insert [t1,t2] s ) S.empty (M.toList cs')
101 where
102 insert as s = foldl' (\s' t -> S.insert t s') s as
103
104 set2indices :: Ord t => Set t -> (Map t Index, Map Index t)
105 set2indices s = (M.fromList toIndex', M.fromList fromIndex')
106 where
107 fromIndex' = zip [0..] xs
108 toIndex' = zip xs [0..]
109 xs = S.toList s
110
111