Commit 986f3316 authored by Alfredo Di Napoli's avatar Alfredo Di Napoli

WIP: Attempt to speed up logDistributional2

parent 3dcb75f8
Pipeline #7311 passed with stages
in 52 minutes and 18 seconds
......@@ -17,7 +17,7 @@ import Gargantext.Prelude.Crypto.Auth (createPasswordHash)
import Paths_gargantext
import qualified Data.Array.Accelerate as A
import qualified Data.Array.Accelerate as Accelerate
import qualified Data.Array.Accelerate.Interpreter as LLVM
import qualified Data.Array.Accelerate.LLVM.Native as LLVM
import qualified Data.Array.Accelerate.Interpreter as Naive
import qualified Data.List.Split as Split
import qualified Data.Massiv.Array as Massiv
......@@ -95,15 +95,31 @@ main = do
, bgroup "Phylo" [
bench "toPhylo (small)" $ nf toPhylo issue290PhyloSmall
]
, bgroup "logDistributional2" [
bench "Accelerate (Naive)" $ nf (Accelerate.logDistributional2With @Double Naive.run) accInput
, bench "Accelerate (LLVM)" $ nf (Accelerate.logDistributional2With @Double LLVM.run) accInput
, bench "Massiv" $ nf (LA.logDistributional2 @_ @Double) massivInput
]
, bgroup "distributional" [
bench "Accelerate (Naive)" $ nf (Accelerate.distributionalWith @Double Naive.run) accInput
, bench "Accelerate (LLVM)" $ nf (Accelerate.distributionalWith @Double LLVM.run) accInput
, bench "Massiv (reference implementation)" $ nf (LA.distributionalReferenceImplementation @_ @Double) massivInput
, bench "Massiv " $ nf (LA.distributional @_ @Double) massivInput
]
, bgroup "diag" [
bench "Accelerate (Naive)" $ nf (Naive.run . Accelerate.diag . Accelerate.use) accInput
, bench "Accelerate (LLVM)" $ nf (LLVM.run . Accelerate.diag . Accelerate.use) accInput
, bench "Massiv " $ nf (LA.diag @_) massivInput
]
, bgroup "identityMatrix" [
, bgroup "matrixIdentity" [
bench "Accelerate (Naive)" $ nf (Naive.run . Accelerate.matrixIdentity @Double) 1000
, bench "Accelerate (LLVM)" $ nf (LLVM.run . Accelerate.matrixIdentity @Double) 1000
, bench "Massiv " $ nf (Massiv.compute @Massiv.U . Massiv.identityMatrix @Double . Massiv.Sz1) 1000
, bench "Massiv " $ nf (LA.matrixIdentity @Double) 1000
]
, bgroup "matrixEye" [
bench "Accelerate (Naive)" $ nf (Naive.run . Accelerate.matrixEye @Double) 1000
, bench "Accelerate (LLVM)" $ nf (LLVM.run . Accelerate.matrixEye @Double) 1000
, bench "Massiv " $ nf (LA.matrixEye @Double) 1000
]
, bgroup "matMaxMini" [
bench "Accelerate (Naive)" $ nf (\v -> Naive.run . Accelerate.matMaxMini @Double . Accelerate.use) accDoubleInput
......@@ -132,16 +148,5 @@ main = do
nf (\m -> LLVM.run $ Accelerate.termDivNan (Accelerate.use m) (Accelerate.use m)) accDoubleInput
, bench "Massiv " $ nf (\m -> LA.termDivNan @Massiv.U m m) massivDoubleInput
]
, bgroup "distributional" [
bench "Accelerate (Naive)" $ nf (Accelerate.distributionalWith @Double Naive.run) accInput
, bench "Accelerate (LLVM)" $ nf Accelerate.distributional accInput
, bench "Massiv (reference implementation)" $ nf (LA.distributionalReferenceImplementation @_ @Double) massivInput
, bench "Massiv " $ nf (LA.distributional @_ @Double) massivInput
]
, bgroup "logDistributional2" [
bench "Accelerate (Naive)" $ nf (Accelerate.logDistributional2With @Double Naive.run) accInput
, bench "Accelerate (LLVM)" $ nf Accelerate.logDistributional2 accInput
, bench "Massiv" $ nf (LA.logDistributional2 @_ @Double) massivInput
]
]
]
......@@ -897,7 +897,7 @@ benchmark garg-bench
build-depends: base
, bytestring ^>= 0.11.5.3
, accelerate
, accelerate-llvm
, accelerate-llvm-native
, massiv
, deepseq
, gargantext
......
......@@ -2,6 +2,7 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -Wall-missed-specialisations #-}
{-|
Module : Gargantext.Core.LinearAlgebra.Distributional
Description : The "distributional" algorithm, fast and slow implementations
......@@ -227,6 +228,7 @@ logDistributional2 m = A.computeP
$ logDistributional' n m
where
n = dim m
{-# SPECIALIZE logDistributional2 :: Matrix A.U Int -> Matrix A.U Double #-}
logDistributional' :: forall r e.
( A.Manifest r e
......@@ -244,8 +246,8 @@ logDistributional' :: forall r e.
-> Matrix r e
logDistributional' n m' = result
where
m :: Matrix A.D e
m = A.map fromIntegral m'
m :: Matrix A.U e
m = A.compute $ A.map fromIntegral m'
-- Scalar. Sum of all elements of m.
to :: e
......@@ -257,7 +259,7 @@ logDistributional' n m' = result
-- Size n vector. s = [s_i]_i
s :: Vector A.U e
s = A.computeP $ sumRowsD (m `subD` d_m)
s = A.compute $ sumRowsD (m `subD` d_m)
-- Matrix nxn. Vector s replicated as rows.
s_1 :: Matrix D e
......
......@@ -199,11 +199,13 @@ sumMin_go n mi = A.makeArray (A.getComp mi) (A.Sz2 n n) $ \(i A.:. j) ->
| k <- [0 .. n - 1]
]
matrixEye :: Num e => Int -> Matrix D e
matrixEye n = A.makeArrayR A.D A.Seq (A.Sz2 n n) $ \(i A.:. j) -> if i == j then 0 else 1
matrixEye :: (A.Unbox e, Num e) => Int -> Matrix A.U e
matrixEye n = A.makeArrayR A.U A.Seq (A.Sz2 n n) $ \(i A.:. j) -> if i == j then 0 else 1
{-# INLINE matrixEye #-}
{-# SPECIALIZE matrixEye :: Int -> Matrix A.U Double #-}
matrixIdentity :: Num e => Int -> Matrix D e
matrixIdentity n = A.makeArrayR A.D A.Seq (A.Sz2 n n) $ \(i A.:. j) -> if i == j then 1 else 0
matrixIdentity :: (A.Unbox e, Num e) => Int -> Matrix A.U e
matrixIdentity n = A.compute $ A.identityMatrix (A.Sz1 n)
diagNull :: (A.Source r e, Num e) => Int -> Matrix r e -> Matrix D e
diagNull n m = A.zipWith (*) m (matrixEye n)
diagNull :: (A.Unbox e, A.Source r e, Num e) => Int -> Matrix r e -> Matrix A.U e
diagNull n m = A.compute $ A.zipWith (*) m (matrixEye n)
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment