]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Viz/Graph/Distances/Matrice.hs
[FEAT] Adding Graph type for the REST api.
[gargantext.git] / src / Gargantext / Viz / Graph / Distances / Matrice.hs
1 {-|
2 Module : Gargantext.Graph.Distances.Matrix
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 Motivation and definition of the @Conditional@ distance.
11 -}
12
13 {-# LANGUAGE NoImplicitPrelude #-}
14 {-# LANGUAGE FlexibleContexts #-}
15 {-# LANGUAGE TypeFamilies #-}
16
17 module Gargantext.Viz.Graph.Distances.Matrice
18 where
19
20 import Data.Array.Accelerate.Data.Bits
21 import Data.Array.Accelerate.Interpreter
22
23 import Data.Array.Accelerate
24 import Data.Array.Accelerate.Smart
25 import Data.Array.Accelerate.Type
26 import Data.Array.Accelerate.Array.Sugar (fromArr, Array, Z)
27
28 import Data.Maybe (Maybe(Just))
29 import qualified Gargantext.Prelude as P
30 import qualified Data.Array.Accelerate.Array.Representation as Repr
31
32 matrix :: Elt c => Int -> [c] -> Matrix c
33 matrix n l = fromList (Z :. n :. n) l
34
35 myMat :: Int -> Matrix Double
36 myMat n = matrix n [1..]
37
38 -- | Two ways to get the rank (as documentation)
39 rank :: (Matrix Double) -> Int
40 rank m = arrayRank $ arrayShape m
41
42 rank' :: (Matrix Double) -> Int
43 rank' m = n
44 where
45 Z :. _ :. n = arrayShape m
46
47 -----------------------------------------------------------------------
48 -- | Conditional Distance
49
50 type Rank = Int
51
52 proba :: Rank -> Acc (Matrix Double) -> Acc (Matrix Double)
53 proba r mat = zipWith (/) mat (mkSum r mat)
54
55 mkSum :: Rank -> Acc (Matrix Double) -> Acc (Matrix Double)
56 mkSum r mat = replicate (constant (Z :. (r :: Int) :. All))
57 $ fold (+) 0 mat
58
59
60 type Matrix' a = Acc (Matrix a)
61
62 conditional :: Matrix Double -> (Matrix Double, Matrix Double)
63 conditional m = (run $ ie (use m), run $ sg (use m))
64 where
65 r :: Rank
66 r = rank' m
67
68 xs :: Matrix' Double -> Matrix' Double
69 xs mat = zipWith (-) (proba r mat) (mkSum r $ proba r mat)
70 ys :: Acc (Matrix Double) -> Acc (Matrix Double)
71 ys mat = zipWith (-) (proba r mat) (mkSum r $ transpose $ proba r mat)
72
73 ie :: Matrix' Double -> Matrix' Double
74 ie mat = map (\x -> x / (2*n-1)) $ zipWith (+) (xs mat) (ys mat)
75 sg :: Acc (Matrix Double) -> Acc (Matrix Double)
76 sg mat = map (\x -> x / (2*n-1)) $ zipWith (-) (xs mat) (ys mat)
77
78 n :: Exp Double
79 n = P.fromIntegral r
80
81 --miniMax m = fold minimum $ fold maximum m
82
83
84
85
86 -- filter with threshold
87 -----------------------------------------------------------------------
88
89 -- | Distributional Distance
90
91 distributional :: Matrix Double -> Matrix Double
92 distributional m = run $ filter $ ri (use m)
93 where
94 n = rank m
95
96 filter m = zipWith (\a b -> max a b) m (transpose m)
97 --miniMax m = fold minimum $ fold maximum m
98
99 ri mat = zipWith (/) mat1 mat2
100 where
101 mat1 = mkSum n $ zipWith min (mi mat) (mi $ transpose mat)
102 mat2 = mkSum n mat
103
104 mi m' = zipWith (\a b -> max (log $ a/b) 0) m'
105 $ zipWith (/) (crossProduct m') (total m')
106
107 total m'' = replicate (constant (Z :. n :. n)) $ fold (+) 0 $ fold (+) 0 m''
108
109 crossProduct m = zipWith (*) (cross m ) (cross (transpose m))
110 cross mat = zipWith (-) (mkSum n mat) (mat)
111