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
10 Basically @compute@ takes an accelerate function as first input, a Map
11 of coccurrences as second input and outputs a Map automatically using
15 --cooc2fgl :: Ord t, Integral n => Map (t, t) n -> Graph
20 {-# LANGUAGE BangPatterns #-}
21 {-# LANGUAGE FlexibleContexts #-}
22 {-# LANGUAGE NoImplicitPrelude #-}
23 {-# LANGUAGE TypeOperators #-}
26 module Gargantext.Viz.Graph.Index
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(..))
33 import qualified Data.Vector.Unboxed as DVU
34 import Data.Maybe (fromMaybe)
37 import qualified Data.Set as S
40 import qualified Data.Map.Strict as M
42 import Gargantext.Prelude
47 -------------------------------------------------------------------------------
49 map'' :: (Ord t) => (A.Matrix Int -> A.Matrix Double)
52 map'' f m = back . f' . from m
54 from (fs, m') = unzip $ M.toAscList m
55 f' = f $ A.fromList shape m'
56 shape = (A.Z A.:. n A.:. n)
57 back = M.fromAscList . zip fs . A.toList
59 -------------------------------------------------------------------------------
60 map' :: (Ord t) => (A.Matrix Int -> A.Matrix Double)
63 map' f m = fromIndex fromI . mat2cooc . f $ cooc2mat toI m
65 (toI, fromI) = createIndexes m
67 map'' m = cooc2mat toI m
69 (toI, fromI) = createIndexes m
71 -------------------------------------------------------------------------------
72 -------------------------------------------------------------------------------
73 cooc2mat :: Ord t => Map t Index -> Map (t, t) Int -> Matrix Int
74 cooc2mat ti m = map2mat 0 n idx
77 idx = toIndex ti m -- it is important to make sure that toIndex is ran only once.
79 map2mat :: Elt a => a -> Int -> Map (Index, Index) a -> Matrix a
80 map2mat def n m = A.fromFunction shape (\(Z :. x :. y) -> fromMaybe def $ M.lookup (x, y) m)
84 -- TODO rename mat2map
85 mat2cooc :: (Elt a, Shape (Z :. Index)) =>
86 A.Array (Z :. Index :. Index) a -> Map (Index, Index) a
87 mat2cooc m = M.fromList . map f . A.toList . A.run . A.indexed $ A.use m
89 Z :. _ :. n = A.arrayShape m
90 f ((Z :. i :. j), x) = ((i, j), x)
92 -------------------------------------------------------------------------------
93 -------------------------------------------------------------------------------
94 toIndex :: Ord t => Map t Index -> Map (t,t) a -> Map (Index,Index) a
95 toIndex ni ns = indexConversion ni ns
97 fromIndex :: Ord t => Map Index t -> Map (Index, Index) a -> Map (t,t) a
98 fromIndex ni ns = indexConversion ni ns
99 ---------------------------------------------------------------------------------
100 indexConversion :: (Ord b, Ord k) => Map k b -> Map (k,k) a -> Map (b, b) a
101 indexConversion index ms = M.fromList $ map (\((k1,k2),c) -> ( ((M.!) index k1, (M.!) index k2), c)) (M.toList ms)
102 -------------------------------------------------------------------------------
103 -------------------------------------------------------------------------------
104 createIndexes :: Ord t => Map (t, t) b -> (Map t Index, Map Index t)
105 createIndexes = set2indexes . cooc2set
107 cooc2set :: Ord t => Map (t, t) a -> Set t
108 cooc2set cs' = foldl' (\s ((t1,t2),_) -> insert [t1,t2] s ) S.empty (M.toList cs')
110 insert as s = foldl' (\s' t -> S.insert t s') s as
112 set2indexes :: Ord t => Set t -> (Map t Index, Map Index t)
113 set2indexes s = (M.fromList toIndex', M.fromList fromIndex')
115 fromIndex' = zip [0..] xs
116 toIndex' = zip xs [0..]