]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Viz/Graph/Index.hs
[FEAT] Cooc -> Matrix conversions tools.
[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
25
26 module Gargantext.Viz.Graph.Index
27 where
28
29 import qualified Data.Array.Accelerate as A
30 import qualified Data.Array.Accelerate.IO.Data.Vector.Unboxed as AU
31
32 import qualified Data.Vector.Unboxed as DVU
33 import Data.List (concat)
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 Gargantext.Prelude
42
43 type Index = Int
44
45
46 -------------------------------------------------------------------------------
47 {-
48 map'' :: (Ord t) => (A.Matrix Int -> A.Matrix Double)
49 -> Map (t, t) Int
50 -> Map (t, t) Double
51 map'' f m = back . f' . from m
52 where
53 from (fs, m') = unzip $ M.toAscList m
54 f' = f $ A.fromList shape m'
55 shape = (A.Z A.:. n A.:. n)
56 back = M.fromAscList . zip fs . A.toList
57 -}
58 -------------------------------------------------------------------------------
59 map' :: (Ord t) => (A.Matrix Int -> A.Matrix Double)
60 -> Map (t, t) Int
61 -> Map (t, t) Double
62 map' f m = fromIndex fromI . mat2cooc . f $ cooc2mat toI m
63 where
64 (toI, fromI) = createIndexes m
65
66 map'' m = cooc2mat toI m
67 where
68 (toI, fromI) = createIndexes m
69
70 -------------------------------------------------------------------------------
71 -------------------------------------------------------------------------------
72 cooc2mat :: Ord t => Map t Index -> Map (t, t) Int -> A.Matrix Int
73 cooc2mat ti m = A.fromFunction shape (\(A.Z A.:. x A.:. y) -> lookup' x y)
74 where
75 shape = (A.Z A.:. n A.:. n)
76 n = M.size ti
77 lookup' x y = maybe 0 identity (M.lookup (x,y) (toIndex ti m))
78
79 mat2cooc :: A.Matrix Double -> Map (Index, Index) Double
80 mat2cooc m = M.fromList $ concat -- [((Int,Int), Double)]
81 $ map (\(x,xs) -> map (\(y,ys) -> ((x,y),ys)) xs) -- [[((Int,Int), Double)]]
82 $ zip ([1..] :: [Int]) -- [(Int, [(Int, Double)]]
83 $ map (zip ([1..] :: [Int])) -- [[(Int, Double)]]
84 $ splitEvery n (A.toList m) -- [[Double]]
85 where
86 A.Z A.:. _ A.:. n = A.arrayShape m
87
88 -------------------------------------------------------------------------------
89 -------------------------------------------------------------------------------
90 toIndex :: Ord t => Map t Index -> Map (t,t) a -> Map (Index,Index) a
91 toIndex ni ns = indexConversion ni ns
92
93 fromIndex :: Ord t => Map Index t -> Map (Index, Index) a -> Map (t,t) a
94 fromIndex ni ns = indexConversion ni ns
95 ---------------------------------------------------------------------------------
96 indexConversion :: (Ord b, Ord k) => Map k b -> Map (k,k) a -> Map (b, b) a
97 indexConversion index ms = M.fromList $ map (\((k1,k2),c) -> ( ((M.!) index k1, (M.!) index k2), c)) (M.toList ms)
98 -------------------------------------------------------------------------------
99 -------------------------------------------------------------------------------
100 createIndexes :: Ord t => Map (t, t) b -> (Map t Index, Map Index t)
101 createIndexes = set2indexes . cooc2set
102 where
103 cooc2set :: Ord t => Map (t, t) a -> Set t
104 cooc2set cs' = foldl' (\s ((t1,t2),_) -> insert [t1,t2] s ) S.empty (M.toList cs')
105 where
106 insert as s = foldl' (\s' t -> S.insert t s') s as
107
108 set2indexes :: Ord t => Set t -> (Map t Index, Map Index t)
109 set2indexes s = (M.fromList toIndex', M.fromList fromIndex')
110 where
111 fromIndex' = zip [1..] (S.toList s)
112 toIndex' = zip (S.toList s) [1..]
113
114