Commit 28b288c7 authored by Alfredo Di Napoli's avatar Alfredo Di Napoli Committed by Alfredo Di Napoli

Code review amendments

parent b2b68a63
Pipeline #7374 failed with stages
in 18 minutes and 12 seconds
...@@ -21,7 +21,6 @@ import qualified Data.Array.Accelerate.LLVM.Native as LLVM ...@@ -21,7 +21,6 @@ import qualified Data.Array.Accelerate.LLVM.Native as LLVM
import qualified Data.Array.Accelerate.Interpreter as Naive import qualified Data.Array.Accelerate.Interpreter as Naive
import qualified Data.List.Split as Split import qualified Data.List.Split as Split
import qualified Data.Massiv.Array as Massiv import qualified Data.Massiv.Array as Massiv
import qualified Data.Massiv.Array.Numeric as Massiv
import qualified Gargantext.Core.LinearAlgebra as LA import qualified Gargantext.Core.LinearAlgebra as LA
import qualified Gargantext.Core.Methods.Matrix.Accelerate.Utils as Accelerate import qualified Gargantext.Core.Methods.Matrix.Accelerate.Utils as Accelerate
import qualified Gargantext.Core.Methods.Similarities.Accelerate.Distributional as Accelerate import qualified Gargantext.Core.Methods.Similarities.Accelerate.Distributional as Accelerate
...@@ -81,7 +80,6 @@ main = do ...@@ -81,7 +80,6 @@ main = do
issue290PhyloSmall <- force . setConfig phyloConfig <$> (readPhylo =<< getDataFileName "bench-data/phylo/issue-290-small.json") issue290PhyloSmall <- force . setConfig phyloConfig <$> (readPhylo =<< getDataFileName "bench-data/phylo/issue-290-small.json")
let !accInput = force testMatrix let !accInput = force testMatrix
let !accVector = force testVector let !accVector = force testVector
let !massivInput = force testMassivMatrix
let !massivVector = force testMassivVector let !massivVector = force testMassivVector
let !(accDoubleInput :: Accelerate.Matrix Double) = force $ Naive.run $ Accelerate.map Accelerate.fromIntegral (Accelerate.use testMatrix) let !(accDoubleInput :: Accelerate.Matrix Double) = force $ Naive.run $ Accelerate.map Accelerate.fromIntegral (Accelerate.use testMatrix)
let !massivInput = force testMassivMatrix let !massivInput = force testMassivMatrix
...@@ -124,8 +122,8 @@ main = do ...@@ -124,8 +122,8 @@ main = do
, bench "Massiv " $ nf (LA.matrixEye @Double) 1000 , bench "Massiv " $ nf (LA.matrixEye @Double) 1000
] ]
, bgroup "matMaxMini" [ , bgroup "matMaxMini" [
bench "Accelerate (Naive)" $ nf (\v -> Naive.run . Accelerate.matMaxMini @Double . Accelerate.use) accDoubleInput bench "Accelerate (Naive)" $ nf (Naive.run . Accelerate.matMaxMini @Double . Accelerate.use) accDoubleInput
, bench "Accelerate (LLVM)" $ nf (\v -> LLVM.run . Accelerate.matMaxMini @Double . Accelerate.use) accDoubleInput , bench "Accelerate (LLVM)" $ nf (LLVM.run . Accelerate.matMaxMini @Double . Accelerate.use) accDoubleInput
, bench "Massiv " $ nf LA.matMaxMini massivDoubleInput , bench "Massiv " $ nf LA.matMaxMini massivDoubleInput
] ]
, bgroup "(.*)" [ , bgroup "(.*)" [
......
...@@ -710,15 +710,17 @@ executable gargantext ...@@ -710,15 +710,17 @@ executable gargantext
, vector >= 0.12.3.0 && <= 0.13.1.0 , vector >= 0.12.3.0 && <= 0.13.1.0
ghc-options: -Wall -Wincomplete-uni-patterns -Wincomplete-record-updates -Wmissing-signatures -Wunused-binds -Wunused-imports -Werror -freduction-depth=300 -fprint-potential-instances ghc-options: -Wall -Wincomplete-uni-patterns -Wincomplete-record-updates -Wmissing-signatures -Wunused-binds -Wunused-imports -Werror -freduction-depth=300 -fprint-potential-instances
common testDependencies -- Dependencies needed by both test stanzas. Dependencies
-- which are not shared must be placed in the `build-depends`
-- of each separate stanza to not trigger any warning if `-Wunused-packages`
-- is enabled.
common commonTestDependencies
build-depends: build-depends:
base >=4.7 && <5 base >=4.7 && <5
, QuickCheck ^>= 2.14.2 , QuickCheck ^>= 2.14.2
, accelerate >= 1.3.0.0
, aeson ^>= 2.1.2.1 , aeson ^>= 2.1.2.1
, aeson-qq , aeson-qq
, async ^>= 2.2.4 , async ^>= 2.2.4
, bimap >= 0.5.0
, bytestring ^>= 0.11.5.3 , bytestring ^>= 0.11.5.3
, cache >= 0.1.3.0 , cache >= 0.1.3.0
, containers ^>= 0.6.7 , containers ^>= 0.6.7
...@@ -740,8 +742,6 @@ common testDependencies ...@@ -740,8 +742,6 @@ common testDependencies
, http-client-tls == 0.3.6.1 , http-client-tls == 0.3.6.1
, http-types , http-types
, lens >= 5.2.2 && < 5.3 , lens >= 5.2.2 && < 5.3
, massiv < 1.1
, massiv-test < 1.2
, monad-control >= 1.0.3 && < 1.1 , monad-control >= 1.0.3 && < 1.1
, mtl ^>= 2.2.2 , mtl ^>= 2.2.2
, network-uri , network-uri
...@@ -754,7 +754,6 @@ common testDependencies ...@@ -754,7 +754,6 @@ common testDependencies
, raw-strings-qq , raw-strings-qq
, resource-pool >= 0.4.0.0 && < 0.5 , resource-pool >= 0.4.0.0 && < 0.5
, safe-exceptions >= 0.1.7.4 && < 0.2 , safe-exceptions >= 0.1.7.4 && < 0.2
, scientific < 0.4
, servant-auth-client , servant-auth-client
, servant-client >= 0.20 && < 0.21 , servant-client >= 0.20 && < 0.21
, servant-client-core >= 0.20 && < 0.21 , servant-client-core >= 0.20 && < 0.21
...@@ -762,7 +761,6 @@ common testDependencies ...@@ -762,7 +761,6 @@ common testDependencies
, shelly >= 1.9 && < 2 , shelly >= 1.9 && < 2
, stm >= 2.5.1.0 && < 2.6 , stm >= 2.5.1.0 && < 2.6
, streaming-commons , streaming-commons
, split
, tasty-hunit , tasty-hunit
, tasty-quickcheck , tasty-quickcheck
, text ^>= 2.0.2 , text ^>= 2.0.2
...@@ -778,17 +776,20 @@ common testDependencies ...@@ -778,17 +776,20 @@ common testDependencies
test-suite garg-test-tasty test-suite garg-test-tasty
import: import:
defaults defaults
, testDependencies , commonTestDependencies
type: exitcode-stdio-1.0 type: exitcode-stdio-1.0
main-is: drivers/tasty/Main.hs main-is: drivers/tasty/Main.hs
build-depends: build-depends:
aeson-pretty ^>= 0.8.9 aeson-pretty ^>= 0.8.9
, accelerate >= 1.3.0.0
, boolexpr ^>= 0.3 , boolexpr ^>= 0.3
, conduit ^>= 1.3.4.2 , conduit ^>= 1.3.4.2
, crawlerArxiv , crawlerArxiv
, cryptohash , cryptohash
, directory ^>= 1.3.7.1 , directory ^>= 1.3.7.1
, graphviz ^>= 2999.20.1.0 , graphviz ^>= 2999.20.1.0
, massiv < 1.1
, scientific < 0.4
, split , split
, tasty >= 1.4.3 && < 1.6 , tasty >= 1.4.3 && < 1.6
, tasty-golden , tasty-golden
...@@ -861,7 +862,7 @@ test-suite garg-test-tasty ...@@ -861,7 +862,7 @@ test-suite garg-test-tasty
test-suite garg-test-hspec test-suite garg-test-hspec
import: import:
defaults defaults
, testDependencies , commonTestDependencies
type: exitcode-stdio-1.0 type: exitcode-stdio-1.0
main-is: drivers/hspec/Main.hs main-is: drivers/hspec/Main.hs
build-depends: process ^>= 1.6.18.0 build-depends: process ^>= 1.6.18.0
...@@ -905,7 +906,6 @@ benchmark garg-bench ...@@ -905,7 +906,6 @@ benchmark garg-bench
other-modules: other-modules:
Paths_gargantext Paths_gargantext
build-depends: base build-depends: base
, bytestring ^>= 0.11.5.3
, accelerate , accelerate
, accelerate-llvm-native , accelerate-llvm-native
, hmatrix , hmatrix
......
...@@ -15,35 +15,10 @@ Linear algebra utility functions to be used across all the Gargantext modules re ...@@ -15,35 +15,10 @@ Linear algebra utility functions to be used across all the Gargantext modules re
-} -}
module Gargantext.Core.LinearAlgebra ( module Gargantext.Core.LinearAlgebra (
-- * Types
Index(..)
-- * Functions
, createIndices
-- * Handy re-exports -- * Handy re-exports
, module Gargantext.Core.LinearAlgebra.Operations module Gargantext.Core.LinearAlgebra.Operations
, module Gargantext.Core.LinearAlgebra.Distributional , module Gargantext.Core.LinearAlgebra.Distributional
) where ) where
import Data.Bimap (Bimap)
import Data.Bimap qualified as Bimap
import Data.Map.Strict (Map)
import Data.Map.Strict qualified as M
import Data.Set qualified as S
import Data.Set (Set)
import Prelude
import Gargantext.Core.LinearAlgebra.Operations import Gargantext.Core.LinearAlgebra.Operations
import Gargantext.Core.LinearAlgebra.Distributional import Gargantext.Core.LinearAlgebra.Distributional
newtype Index = Index { _Index :: Int }
deriving newtype (Eq, Show, Ord, Num, Enum)
createIndices :: Ord t => Map (t, t) b -> Bimap Index t
createIndices = set2indices . map2set
where
map2set :: Ord t => Map (t, t) a -> Set t
map2set cs' = foldr (\(t1, t2) s -> S.insert t1 $! S.insert t2 $! s) mempty $ M.keys cs'
set2indices :: Ord t => Set t -> Bimap Index t
set2indices s = foldr (uncurry Bimap.insert) Bimap.empty (zip [0..] $ S.toList s)
{-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -Wall-missed-specialisations #-}
{-| {-|
Module : Gargantext.Core.LinearAlgebra.Distributional Module : Gargantext.Core.LinearAlgebra.Distributional
Description : The "distributional" algorithm, fast and slow implementations Description : The "distributional" algorithm, fast and slow implementations
...@@ -27,7 +25,7 @@ import Data.Massiv.Array qualified as A ...@@ -27,7 +25,7 @@ import Data.Massiv.Array qualified as A
import Gargantext.Core.LinearAlgebra.Operations import Gargantext.Core.LinearAlgebra.Operations
import Prelude import Prelude
-- | `distributional m` returns the distributional distance between terms each -- | `distributional m` returns the distributional distance between each
-- pair of terms as a matrix. The argument m is the matrix $[n_{ij}]_{i,j}$ -- pair of terms as a matrix. The argument m is the matrix $[n_{ij}]_{i,j}$
-- where $n_{ij}$ is the coocccurrence between term $i$ and term $j$. -- where $n_{ij}$ is the coocccurrence between term $i$ and term $j$.
-- --
...@@ -228,7 +226,6 @@ logDistributional2 m = A.computeP ...@@ -228,7 +226,6 @@ logDistributional2 m = A.computeP
$ logDistributional' n m $ logDistributional' n m
where where
n = dim m n = dim m
{-# SPECIALIZE logDistributional2 :: Matrix A.U Int -> Matrix A.U Double #-}
logDistributional' :: forall r e. logDistributional' :: forall r e.
( A.Manifest r e ( A.Manifest r e
......
...@@ -10,11 +10,6 @@ module Test.Core.LinearAlgebra where ...@@ -10,11 +10,6 @@ module Test.Core.LinearAlgebra where
import Data.Array.Accelerate hiding (Ord, Eq, map, (<=)) import Data.Array.Accelerate hiding (Ord, Eq, map, (<=))
import Data.Array.Accelerate.Interpreter qualified as Naive import Data.Array.Accelerate.Interpreter qualified as Naive
import Data.Array.Accelerate qualified as A import Data.Array.Accelerate qualified as A
import Data.Bifunctor (first)
import Data.Bimap (Bimap)
import Data.Bimap qualified as Bimap
import Data.Map.Strict (Map)
import Data.Map.Strict qualified as M
import Data.Massiv.Array qualified as Massiv import Data.Massiv.Array qualified as Massiv
import Data.Proxy import Data.Proxy
import Data.Scientific import Data.Scientific
...@@ -22,7 +17,6 @@ import Gargantext.Core.LinearAlgebra qualified as LA ...@@ -22,7 +17,6 @@ import Gargantext.Core.LinearAlgebra qualified as LA
import Gargantext.Core.Methods.Matrix.Accelerate.Utils qualified as A import Gargantext.Core.Methods.Matrix.Accelerate.Utils qualified as A
import Gargantext.Core.Methods.Matrix.Accelerate.Utils qualified as Legacy import Gargantext.Core.Methods.Matrix.Accelerate.Utils qualified as Legacy
import Gargantext.Core.Methods.Similarities.Accelerate.Distributional qualified as Legacy import Gargantext.Core.Methods.Similarities.Accelerate.Distributional qualified as Legacy
import Gargantext.Core.Viz.Graph.Index qualified as Legacy
import Gargantext.Orphans.Accelerate (sliceArray) import Gargantext.Orphans.Accelerate (sliceArray)
import Prelude hiding ((^)) import Prelude hiding ((^))
import Test.Tasty import Test.Tasty
...@@ -43,27 +37,6 @@ instance (Elt a, Show a, Prelude.Num a, Ord a, Arbitrary a) => Arbitrary (Square ...@@ -43,27 +37,6 @@ instance (Elt a, Show a, Prelude.Num a, Ord a, Arbitrary a) => Arbitrary (Square
SquareMatrix . A.fromList sh <$> vectorOf (x*x) arbitrary SquareMatrix . A.fromList sh <$> vectorOf (x*x) arbitrary
shrink = map (SquareMatrix) . sliceArray . _SquareMatrix shrink = map (SquareMatrix) . sliceArray . _SquareMatrix
compareImplementations :: (Arbitrary a, Eq b, Show b)
=> (a -> b)
-> (a -> c)
-> (c -> b)
-> a
-> Property
compareImplementations implementation1 implementation2 mapResults inputData
= implementation1 inputData === mapResults (implementation2 inputData)
compareImplementations' :: (Arbitrary a, Eq c, Show c)
=> (a -> b)
-> (a -> b)
-> (b -> c)
-> a
-> Property
compareImplementations' implementation1 implementation2 mapResults inputData
= mapResults (implementation1 inputData) === mapResults (implementation2 inputData)
mapCreateIndices :: Ord t => (Map t Legacy.Index, Map Legacy.Index t) -> Bimap LA.Index t
mapCreateIndices (_m1, m2) = Bimap.fromList $ map (first LA.Index) $ M.toList m2
type TermDivNanShape = Z :. Int :. Int type TermDivNanShape = Z :. Int :. Int
twoByTwo :: SquareMatrix Int twoByTwo :: SquareMatrix Int
...@@ -126,8 +99,7 @@ testMatrix_04 = SquareMatrix $ fromList (Z :. 8 :. 8) $ ...@@ -126,8 +99,7 @@ testMatrix_04 = SquareMatrix $ fromList (Z :. 8 :. 8) $
tests :: TestTree tests :: TestTree
tests = testGroup "LinearAlgebra" [ tests = testGroup "LinearAlgebra" [
testProperty "createIndices roundtrip" (compareImplementations (LA.createIndices @Int @Int) Legacy.createIndices mapCreateIndices) testProperty "termDivNan" compareTermDivNan
, testProperty "termDivNan" compareTermDivNan
, testProperty "diag" compareDiag , testProperty "diag" compareDiag
, testProperty "sumRows" compareSumRows , testProperty "sumRows" compareSumRows
, testProperty "matMaxMini" compareMatMaxMini , testProperty "matMaxMini" compareMatMaxMini
......
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