]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Core/Methods/Matrix/Accelerate/Utils.hs
[FEAT] Distributional (WIP)
[gargantext.git] / src / Gargantext / Core / Methods / Matrix / Accelerate / Utils.hs
1 {-|
2 Module : Gargantext.Core.Methods.Matrix.Accelerate.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 This module aims at implementig distances of terms context by context is
11 the same referential of corpus.
12
13 Implementation use Accelerate library which enables GPU and CPU computation:
14
15 * Manuel M. T. Chakravarty, Gabriele Keller, Sean Lee, Trevor L. McDonell, and Vinod Grover.
16 [Accelerating Haskell Array Codes with Multicore GPUs][CKLM+11].
17 In _DAMP '11: Declarative Aspects of Multicore Programming_, ACM, 2011.
18
19 * Trevor L. McDonell, Manuel M. T. Chakravarty, Vinod Grover, and Ryan R. Newton.
20 [Type-safe Runtime Code Generation: Accelerate to LLVM][MCGN15].
21 In _Haskell '15: The 8th ACM SIGPLAN Symposium on Haskell_, ACM, 2015.
22
23 -}
24
25 {-# LANGUAGE TypeFamilies #-}
26 {-# LANGUAGE TypeOperators #-}
27 {-# LANGUAGE ScopedTypeVariables #-}
28 {-# LANGUAGE ViewPatterns #-}
29
30 module Gargantext.Core.Methods.Matrix.Accelerate.Utils
31 where
32
33 import qualified Data.Foldable as P (foldl1)
34 import Debug.Trace (trace)
35 import Data.Array.Accelerate
36 import Data.Array.Accelerate.Array.Sugar (Elt(..), Shape(..), Slice(..), (:.))
37 import Data.Array.Accelerate.Smart (Exp(..))
38 import Data.Array.Accelerate.Interpreter (run)
39 import qualified Gargantext.Prelude as P
40 import Data.Array.Accelerate.LinearAlgebra hiding (Matrix, transpose, Vector)
41
42 -----------------------------------------------------------------------
43 -- | Main operators
44 -- Matrix Multiplication
45 (#*#) :: ( Shape ix
46 , Slice ix
47 , Elt a
48 , P.Num (Exp a)
49 )
50 => Acc (Array ((ix :. Int) :. Int) a)
51 -> Acc (Array ((ix :. Int) :. Int) a)
52 -> Acc (Array ((ix :. Int) :. Int) a)
53 (#*#) = multiplyMatrixMatrix
54
55
56 -- | Matrix cell by cell multiplication
57 (.*) :: ( Shape ix
58 , Slice ix
59 , Elt a
60 , P.Num (Exp a)
61 )
62 => Acc (Array ((ix :. Int) :. Int) a)
63 -> Acc (Array ((ix :. Int) :. Int) a)
64 -> Acc (Array ((ix :. Int) :. Int) a)
65 (.*) = zipWith (*)
66
67 (.**) :: ( Shape ix
68 , Slice ix
69 , Elt a
70 , P.Num (Exp a)
71 )
72 => Acc (Array ((ix :. Int) :. Int) a)
73 -> Acc (Array ((ix :. Int) :. Int) a)
74 (.**) m = (.*) m m
75
76
77 (./) :: ( Shape ix
78 , Slice ix
79 , Elt a
80 , P.Num (Exp a)
81 , P.Fractional (Exp a)
82 )
83 => Acc (Array ((ix :. Int) :. Int) a)
84 -> Acc (Array ((ix :. Int) :. Int) a)
85 -> Acc (Array ((ix :. Int) :. Int) a)
86 (./) = zipWith (/)
87
88 (.-) :: ( Shape ix
89 , Slice ix
90 , Elt a
91 , P.Num (Exp a)
92 , P.Fractional (Exp a)
93 )
94 => Acc (Array ((ix :. Int) :. Int) a)
95 -> Acc (Array ((ix :. Int) :. Int) a)
96 -> Acc (Array ((ix :. Int) :. Int) a)
97 (.-) = zipWith (-)
98
99 (.+) :: ( Shape ix
100 , Slice ix
101 , Elt a
102 , P.Num (Exp a)
103 , P.Fractional (Exp a)
104 )
105 => Acc (Array ((ix :. Int) :. Int) a)
106 -> Acc (Array ((ix :. Int) :. Int) a)
107 -> Acc (Array ((ix :. Int) :. Int) a)
108 (.+) = zipWith (+)
109
110 -----------------------------------------------------------------------
111 matrixOne :: Num a => Dim -> Acc (Matrix a)
112 matrixOne n' = ones
113 where
114 ones = fill (index2 n n) 1
115 n = constant n'
116
117
118 matrixIdentity :: Num a => Dim -> Acc (Matrix a)
119 matrixIdentity n' =
120 let zeros = fill (index2 n n) 0
121 ones = fill (index1 n) 1
122 n = constant n'
123 in
124 permute const zeros (\(unindex1 -> i) -> index2 i i) ones
125
126
127 matrixEye :: Num a => Dim -> Acc (Matrix a)
128 matrixEye n' =
129 let ones = fill (index2 n n) 1
130 zeros = fill (index1 n) 0
131 n = constant n'
132 in
133 permute const ones (\(unindex1 -> i) -> index2 i i) zeros
134
135
136 diagNull :: Num a => Dim -> Acc (Matrix a) -> Acc (Matrix a)
137 diagNull n m = zipWith (*) m (matrixEye n)
138
139 -----------------------------------------------------------------------
140 _runExp :: Elt e => Exp e -> e
141 _runExp e = indexArray (run (unit e)) Z
142
143 -----------------------------------------------------------------------
144 -- | Define a vector
145 --
146 -- >>> vector 3
147 -- Vector (Z :. 3) [0,1,2]
148 vector :: Elt c => Int -> [c] -> (Array (Z :. Int) c)
149 vector n l = fromList (Z :. n) l
150
151 -- | Define a matrix
152 --
153 -- >>> matrix 3 ([1..] :: [Double])
154 -- Matrix (Z :. 3 :. 3)
155 -- [ 1.0, 2.0, 3.0,
156 -- 4.0, 5.0, 6.0,
157 -- 7.0, 8.0, 9.0]
158 matrix :: Elt c => Int -> [c] -> Matrix c
159 matrix n l = fromList (Z :. n :. n) l
160
161 -- | Two ways to get the rank (as documentation)
162 --
163 -- >>> rank (matrix 3 ([1..] :: [Int]))
164 -- 2
165 rank :: (Matrix a) -> Int
166 rank m = arrayRank $ arrayShape m
167
168 -----------------------------------------------------------------------
169 -- | Dimension of a square Matrix
170 -- How to force use with SquareMatrix ?
171 type Dim = Int
172
173 -- | Get Dimension of a square Matrix
174 --
175 -- >>> dim (matrix 3 ([1..] :: [Int]))
176 -- 3
177 dim :: Matrix a -> Dim
178 dim m = n
179 where
180 Z :. _ :. n = arrayShape m
181 -- indexTail (arrayShape m)
182
183 -----------------------------------------------------------------------
184
185 -- | Sum of a Matrix by Column
186 --
187 -- >>> run $ matSumCol 3 (use $ matrix 3 [1..])
188 -- Matrix (Z :. 3 :. 3)
189 -- [ 12.0, 15.0, 18.0,
190 -- 12.0, 15.0, 18.0,
191 -- 12.0, 15.0, 18.0]
192 matSumCol :: (Elt a, P.Num (Exp a)) => Dim -> Acc (Matrix a) -> Acc (Matrix a)
193 matSumCol r mat = replicate (constant (Z :. (r :: Int) :. All)) $ sum $ transpose mat
194
195 matSumCol' :: (Elt a, P.Num (Exp a)) => Matrix a -> Matrix a
196 matSumCol' m = run $ matSumCol n m'
197 where
198 n = dim m
199 m' = use m
200
201
202 -- | Proba computes de probability matrix: all cells divided by thee sum of its column
203 -- if you need get the probability on the lines, just transpose it
204 --
205 -- >>> run $ matProba 3 (use $ matrix 3 [1..])
206 -- Matrix (Z :. 3 :. 3)
207 -- [ 8.333333333333333e-2, 0.13333333333333333, 0.16666666666666666,
208 -- 0.3333333333333333, 0.3333333333333333, 0.3333333333333333,
209 -- 0.5833333333333334, 0.5333333333333333, 0.5]
210 matProba :: Dim -> Acc (Matrix Double) -> Acc (Matrix Double)
211 matProba d mat = zipWith (/) mat (matSumCol d mat)
212
213 -- | Diagonal of the matrix
214 --
215 -- >>> run $ diag (use $ matrix 3 ([1..] :: [Int]))
216 -- Vector (Z :. 3) [1,5,9]
217 diag :: Elt e
218 => Acc (Matrix e)
219 -> Acc (Vector e)
220 diag m = backpermute (indexTail (shape m))
221 (lift1 (\(Z :. x) -> (Z :. x :. (x :: Exp Int))))
222 m
223
224 -- | Divide by the Diagonal of the matrix
225 --
226 -- >>> run $ divByDiag 3 (use $ matrix 3 ([1..] :: [Double]))
227 -- Matrix (Z :. 3 :. 3)
228 -- [ 1.0, 0.4, 0.3333333333333333,
229 -- 4.0, 1.0, 0.6666666666666666,
230 -- 7.0, 1.6, 1.0]
231 divByDiag :: Dim -> Acc (Matrix Double) -> Acc (Matrix Double)
232 divByDiag d mat = zipWith (/) mat (replicate (constant (Z :. (d :: Int) :. All)) $ diag mat)
233
234 -----------------------------------------------------------------------
235 -- | Filters the matrix with the minimum of maximums
236 --
237 -- >>> run $ matMiniMax $ use $ matrix 3 [1..]
238 -- Matrix (Z :. 3 :. 3)
239 -- [ 0.0, 4.0, 7.0,
240 -- 0.0, 5.0, 8.0,
241 -- 0.0, 6.0, 9.0]
242 matMiniMax :: (Elt a, Ord a, P.Num a)
243 => Acc (Matrix a)
244 -> Acc (Matrix a)
245 matMiniMax m = filterWith' miniMax' (constant 0) m
246 where
247 miniMax' = the $ minimum $ maximum m
248
249
250 -- | Filters the matrix with a constant
251 --
252 -- >>> run $ matFilter 5 $ use $ matrix 3 [1..]
253 -- Matrix (Z :. 3 :. 3)
254 -- [ 0.0, 0.0, 7.0,
255 -- 0.0, 0.0, 8.0,
256 -- 0.0, 6.0, 9.0]
257 filter' :: Double -> Acc (Matrix Double) -> Acc (Matrix Double)
258 filter' t m = filterWith t 0 m
259
260 filterWith :: Double -> Double -> Acc (Matrix Double) -> Acc (Matrix Double)
261 filterWith t v m = map (\x -> ifThenElse (x > (constant t)) x (constant v)) (transpose m)
262
263 filterWith' :: (Elt a, Ord a) => Exp a -> Exp a -> Acc (Matrix a) -> Acc (Matrix a)
264 filterWith' t v m = map (\x -> ifThenElse (x > t) x v) m
265
266
267 ------------------------------------------------------------------------
268 ------------------------------------------------------------------------
269
270
271
272 -- | TODO use Lenses
273 data Direction = MatCol (Exp Int) | MatRow (Exp Int) | Diag
274
275 nullOf :: Num a => Dim -> Direction -> Acc (Matrix a)
276 nullOf n' dir =
277 let ones = fill (index2 n n) 1
278 zeros = fill (index2 n n) 0
279 n = constant n'
280 in
281 permute const ones ( lift1 ( \(Z :. (i :: Exp Int) :. (_j:: Exp Int))
282 -> case dir of
283 MatCol m -> (Z :. i :. m)
284 MatRow m -> (Z :. m :. i)
285 Diag -> (Z :. i :. i)
286 )
287 )
288 zeros
289
290 nullOfWithDiag :: Num a => Dim -> Direction -> Acc (Matrix a)
291 nullOfWithDiag n dir = zipWith (*) (nullOf n dir) (nullOf n Diag)
292
293
294 divide :: (Elt a, Ord a, P.Fractional (Exp a), P.Num a)
295 => Acc (Matrix a) -> Acc (Matrix a) -> Acc (Matrix a)
296 divide = zipWith divide'
297 where
298 divide' a b = ifThenElse (b > (constant 0))
299 (a / b)
300 (constant 0)
301
302 -- | Nominator
303 sumRowMin :: (Num a, Ord a) => Dim -> Acc (Matrix a) -> Acc (Matrix a)
304 sumRowMin n m = {-trace (P.show $ run m') $-} m'
305 where
306 m' = reshape (shape m) vs
307 vs = P.foldl1 (++)
308 $ P.map (\z -> sumRowMin1 n (constant z) m) [0..n-1]
309
310 sumRowMin1 :: (Num a, Ord a) => Dim -> Exp Int -> Acc (Matrix a) -> Acc (Vector a)
311 sumRowMin1 n x m = trace (P.show (run m,run $ transpose m)) $ m''
312 where
313 m'' = sum $ zipWith min (transpose m) m
314 _m' = zipWith (*) (zipWith (*) (nullOf n (MatCol x)) $ nullOfWithDiag n (MatRow x)) m
315
316 -- | Denominator
317 sumColMin :: (Num a, Ord a) => Dim -> Acc (Matrix a) -> Acc (Matrix a)
318 sumColMin n m = reshape (shape m) vs
319 where
320 vs = P.foldl1 (++)
321 $ P.map (\z -> sumColMin1 n (constant z) m) [0..n-1]
322
323
324 sumColMin1 :: (Num a) => Dim -> Exp Int -> Acc (Matrix a) -> Acc (Matrix a)
325 sumColMin1 n x m = zipWith (*) (nullOfWithDiag n (MatCol x)) m
326
327
328
329 {- | WIP fun with indexes
330 selfMatrix :: Num a => Dim -> Acc (Matrix a)
331 selfMatrix n' =
332 let zeros = fill (index2 n n) 0
333 ones = fill (index2 n n) 1
334 n = constant n'
335 in
336 permute const ones ( lift1 ( \(Z :. (i :: Exp Int) :. (_j:: Exp Int))
337 -> -- ifThenElse (i /= j)
338 -- (Z :. i :. j)
339 (Z :. i :. i)
340 )) zeros
341
342 selfMatrix' :: (Elt a, P.Num (Exp a)) => Array DIM2 a -> Matrix a
343 selfMatrix' m' = run $ selfMatrix n
344 where
345 n = dim m'
346 m = use m'
347 -}
348 -------------------------------------------------
349 -------------------------------------------------
350 crossProduct :: Dim -> Acc (Matrix Double) -> Acc (Matrix Double)
351 crossProduct n m = {-trace (P.show (run m',run m'')) $-} zipWith (*) m' m''
352 where
353 m' = cross n m
354 m'' = transpose $ cross n m
355
356
357 crossT :: Matrix Double -> Matrix Double
358 crossT = run . transpose . use
359
360 crossProduct' :: Matrix Double -> Matrix Double
361 crossProduct' m = run $ crossProduct n m'
362 where
363 n = dim m
364 m' = use m
365
366 runWith :: (Arrays c, Elt a1)
367 => (Dim -> Acc (Matrix a1) -> a2 -> Acc c)
368 -> Matrix a1
369 -> a2
370 -> c
371 runWith f m = run . f (dim m) (use m)
372
373 -- | cross
374 cross :: Dim -> Acc (Matrix Double) -> Acc (Matrix Double)
375 cross n mat = diagNull n (matSumCol n $ diagNull n mat)
376
377 cross' :: Matrix Double -> Matrix Double
378 cross' mat = run $ cross n mat'
379 where
380 mat' = use mat
381 n = dim mat
382
383
384 {-
385 -- | Hypothesis to test maybe later (or not)
386 -- TODO ask accelerate for instances to ease such writtings:
387 p_ :: (Elt e, P.Fractional (Exp e)) => Acc (Array DIM2 e) -> Acc (Array DIM2 e)
388 p_ m = zipWith (/) m (n_ m)
389 where
390 n_ :: Elt e => Acc (SymetricMatrix e) -> Acc (Matrix e)
391 n_ m = backpermute (shape m)
392 (lift1 ( \(Z :. (i :: Exp Int) :. (j:: Exp Int))
393 -> (ifThenElse (i < j) (lift (Z :. j :. j)) (lift (Z :. i :. i)) :: Exp DIM2)
394 )
395 ) m
396 -}
397
398 theMatrixDouble :: Int -> Matrix Double
399 theMatrixDouble n = run $ map fromIntegral (use $ theMatrixInt n)
400
401 theMatrixInt :: Int -> Matrix Int
402 theMatrixInt n = matrix n (dataMatrix n)
403 where
404 dataMatrix :: Int -> [Int]
405 dataMatrix x | (P.==) x 2 = [ 1, 1
406 , 1, 2
407 ]
408
409 | (P.==) x 3 = [ 1, 1, 2
410 , 1, 2, 3
411 , 2, 3, 4
412 ]
413 | (P.==) x 4 = [ 1, 1, 2, 3
414 , 1, 2, 3, 4
415 , 2, 3, 4, 5
416 , 3, 4, 5, 6
417 ]
418 | P.otherwise = P.undefined
419
420 {-
421 theResult :: Int -> Matrix Double
422 theResult n | (P.==) n 2 = let r = 1.6094379124341003 in [ 0, r, r, 0]
423 | P.otherwise = [ 1, 1 ]
424 -}
425
426
427 colMatrix :: Elt e
428 => Int -> [e] -> Acc (Array ((Z :. Int) :. Int) e)
429 colMatrix n ns = replicate (constant (Z :. (n :: Int) :. All)) v
430 where
431 v = use $ vector (P.length ns) ns
432
433 -----------------------------------------------------------------------
434