Commit 1d67e4f0 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FEAT] Order1 with test fixed

parent fb436075
Pipeline #5703 failed with stages
in 80 minutes and 54 seconds
...@@ -130,6 +130,7 @@ library ...@@ -130,6 +130,7 @@ library
Gargantext.Core Gargantext.Core
Gargantext.Core.Mail.Types Gargantext.Core.Mail.Types
Gargantext.Core.Methods.Similarities Gargantext.Core.Methods.Similarities
Gargantext.Core.Methods.Similarities.Conditional
Gargantext.Core.NLP Gargantext.Core.NLP
Gargantext.Core.NodeStory Gargantext.Core.NodeStory
Gargantext.Core.NodeStory.DB Gargantext.Core.NodeStory.DB
...@@ -256,8 +257,8 @@ library ...@@ -256,8 +257,8 @@ library
Gargantext.API.Node.Corpus.Searx Gargantext.API.Node.Corpus.Searx
Gargantext.API.Node.Document.Export Gargantext.API.Node.Document.Export
Gargantext.API.Node.Document.Export.Types Gargantext.API.Node.Document.Export.Types
Gargantext.API.Node.DocumentsFromWriteNodes
Gargantext.API.Node.DocumentUpload Gargantext.API.Node.DocumentUpload
Gargantext.API.Node.DocumentsFromWriteNodes
Gargantext.API.Node.FrameCalcUpload Gargantext.API.Node.FrameCalcUpload
Gargantext.API.Node.Get Gargantext.API.Node.Get
Gargantext.API.Node.New Gargantext.API.Node.New
...@@ -280,7 +281,6 @@ library ...@@ -280,7 +281,6 @@ library
Gargantext.Core.Methods.Similarities.Accelerate.Conditional Gargantext.Core.Methods.Similarities.Accelerate.Conditional
Gargantext.Core.Methods.Similarities.Accelerate.Distributional Gargantext.Core.Methods.Similarities.Accelerate.Distributional
Gargantext.Core.Methods.Similarities.Accelerate.SpeGen Gargantext.Core.Methods.Similarities.Accelerate.SpeGen
Gargantext.Core.Methods.Similarities.Conditional
Gargantext.Core.Methods.Similarities.Distributional Gargantext.Core.Methods.Similarities.Distributional
Gargantext.Core.Statistics Gargantext.Core.Statistics
Gargantext.Core.Text.Convert Gargantext.Core.Text.Convert
...@@ -300,10 +300,10 @@ library ...@@ -300,10 +300,10 @@ library
Gargantext.Core.Text.Corpus.Parsers.RIS Gargantext.Core.Text.Corpus.Parsers.RIS
Gargantext.Core.Text.Corpus.Parsers.RIS.Presse Gargantext.Core.Text.Corpus.Parsers.RIS.Presse
Gargantext.Core.Text.Corpus.Parsers.Telegram Gargantext.Core.Text.Corpus.Parsers.Telegram
Gargantext.Core.Text.Corpus.Parsers.WOS
Gargantext.Core.Text.Corpus.Parsers.Wikidata Gargantext.Core.Text.Corpus.Parsers.Wikidata
Gargantext.Core.Text.Corpus.Parsers.Wikidata.Crawler Gargantext.Core.Text.Corpus.Parsers.Wikidata.Crawler
Gargantext.Core.Text.Corpus.Parsers.Wikimedia Gargantext.Core.Text.Corpus.Parsers.Wikimedia
Gargantext.Core.Text.Corpus.Parsers.WOS
Gargantext.Core.Text.Learn Gargantext.Core.Text.Learn
Gargantext.Core.Text.List Gargantext.Core.Text.List
Gargantext.Core.Text.List.Group Gargantext.Core.Text.List.Group
...@@ -402,12 +402,12 @@ library ...@@ -402,12 +402,12 @@ library
Gargantext.Database.Query.Table.Node.Select Gargantext.Database.Query.Table.Node.Select
Gargantext.Database.Query.Table.Node.Update Gargantext.Database.Query.Table.Node.Update
Gargantext.Database.Query.Table.Node.User Gargantext.Database.Query.Table.Node.User
Gargantext.Database.Query.Table.Node_NodeNgramsNodeNgrams
Gargantext.Database.Query.Table.NodeContext Gargantext.Database.Query.Table.NodeContext
Gargantext.Database.Query.Table.NodeContext_NodeContext Gargantext.Database.Query.Table.NodeContext_NodeContext
Gargantext.Database.Query.Table.NodeNgrams Gargantext.Database.Query.Table.NodeNgrams
Gargantext.Database.Query.Table.NodeNode Gargantext.Database.Query.Table.NodeNode
Gargantext.Database.Query.Table.NodeNodeNgrams Gargantext.Database.Query.Table.NodeNodeNgrams
Gargantext.Database.Query.Table.Node_NodeNgramsNodeNgrams
Gargantext.Database.Query.Table.NodesNgramsRepo Gargantext.Database.Query.Table.NodesNgramsRepo
Gargantext.Database.Query.Tree Gargantext.Database.Query.Tree
Gargantext.Database.Query.Tree.Error Gargantext.Database.Query.Tree.Error
...@@ -415,13 +415,13 @@ library ...@@ -415,13 +415,13 @@ library
Gargantext.Database.Schema.ContextNodeNgrams Gargantext.Database.Schema.ContextNodeNgrams
Gargantext.Database.Schema.ContextNodeNgrams2 Gargantext.Database.Schema.ContextNodeNgrams2
Gargantext.Database.Schema.NgramsPostag Gargantext.Database.Schema.NgramsPostag
Gargantext.Database.Schema.Node_NodeNgramsNodeNgrams
Gargantext.Database.Schema.NodeContext Gargantext.Database.Schema.NodeContext
Gargantext.Database.Schema.NodeContext_NodeContext Gargantext.Database.Schema.NodeContext_NodeContext
Gargantext.Database.Schema.NodeNgrams Gargantext.Database.Schema.NodeNgrams
Gargantext.Database.Schema.NodeNode Gargantext.Database.Schema.NodeNode
Gargantext.Database.Schema.NodeNodeNgrams Gargantext.Database.Schema.NodeNodeNgrams
Gargantext.Database.Schema.NodeNodeNgrams2 Gargantext.Database.Schema.NodeNodeNgrams2
Gargantext.Database.Schema.Node_NodeNgramsNodeNgrams
Gargantext.Database.Schema.NodesNgramsRepo Gargantext.Database.Schema.NodesNgramsRepo
Gargantext.Database.Schema.Prelude Gargantext.Database.Schema.Prelude
Gargantext.Database.Types Gargantext.Database.Types
......
...@@ -125,7 +125,7 @@ matrixEye n' = ...@@ -125,7 +125,7 @@ matrixEye n' =
diagNull :: Num a => Dim -> Acc (Matrix a) -> Acc (Matrix a) diagNull :: Num a => Dim -> Acc (Matrix a) -> Acc (Matrix a)
diagNull n m = trace ("diagNull") $ zipWith (*) m (matrixEye n) diagNull n m = zipWith (*) m (matrixEye n)
-- Returns an N-dimensional array with the values of x for the indices where -- Returns an N-dimensional array with the values of x for the indices where
......
...@@ -53,26 +53,23 @@ measureConditional :: Matrix Int -> Matrix Double ...@@ -53,26 +53,23 @@ measureConditional :: Matrix Int -> Matrix Double
measureConditional m = run $ x $ map fromIntegral $ use m measureConditional m = run $ x $ map fromIntegral $ use m
where where
x :: Acc (Matrix Double) -> Acc (Matrix Double) x :: Acc (Matrix Double) -> Acc (Matrix Double)
x mat = diagNull r $ divByDiag r mat x mat = maxOnly $ diagNull r $ divByDiag r mat
r :: Dim r :: Dim
r = dim m r = dim m
_maxOnly :: Elt e => Acc (SymetricMatrix e) -> Acc (Matrix e) -- Maybe we should use backpermute to accelerate it (no need to access to cells then
_maxOnly m' = maxOnly :: Acc (SymetricMatrix Double) -> Acc (Matrix Double)
backpermute (shape m') maxOnly m' = generate (shape m')
(lift1 ( \(Z :. (i :: Exp Int) :. (j:: Exp Int)) ((\coord
-> let ij = lift (Z :. i :. j) -> let (Z :. (i :: Exp Int) :. (j :: Exp Int)) = unlift coord
ji = lift (Z :. j :. i) ij = m' ! (lift $ (Z :. i :. j))
in ji = m' ! (lift $ (Z :. j :. i))
((ifThenElse (ij < ji) ji 0 ) :: Exp DIM2) in
) ifThenElse (ij > ji) ij (constant 0)
) m' )
)
-- This function should be removed
measureConditional' :: Matrix Int -> Matrix Double measureConditional' :: Matrix Int -> Matrix Double
measureConditional' m = run $ x $ map fromIntegral $ use m measureConditional' m = run $ x $ map fromIntegral $ use m
where where
......
...@@ -55,12 +55,23 @@ conditional m' = Map.fromList $ ((catMaybes results') `using` parList rdeepseq) ...@@ -55,12 +55,23 @@ conditional m' = Map.fromList $ ((catMaybes results') `using` parList rdeepseq)
keys = Set.toList $ Set.fromList (x <> y) keys = Set.toList $ Set.fromList (x <> y)
(x,y) = unzip $ Map.keys m (x,y) = unzip $ Map.keys m
{-
Only for TESTs
-}
conditional_test :: Bool
conditional_test = conditional_test1 == conditional_test2
conditional_test1 :: HashMap (Text,Text) Double
conditional_test1 = conditional $ Map.fromList example_matrix
conditional_test :: HashMap (Text,Text) Double conditional_test2 :: HashMap (Text,Text) Double
conditional_test = conditional $ Map.fromList example_matrix conditional_test2 = Map.fromList
$ M.toList
$ M.filter (>0)
$ score Square measureConditional
$ M.fromList example_matrix
conditional_test' :: M.Map (Text,Text) Double
conditional_test' = M.filter (>0) $ score Square measureConditional $ M.fromList example_matrix
example_matrix :: [((Text,Text), Int)] example_matrix :: [((Text,Text), Int)]
example_matrix = concat [ example_matrix = concat [
......
{-|
Module : Core.Similarity
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
module Test.Core.Similarity where
import Gargantext.Core.Methods.Similarities.Conditional
import Gargantext.Prelude
import Test.Hspec
test :: Spec
test = do
describe "check if similarities optimizations are well implemented" $ do
it "Conditional" $ do
conditional_test `shouldBe` True
...@@ -14,6 +14,7 @@ import Gargantext.Prelude ...@@ -14,6 +14,7 @@ import Gargantext.Prelude
import qualified Test.Core.Text.Corpus.Query as CorpusQuery import qualified Test.Core.Text.Corpus.Query as CorpusQuery
import qualified Test.Core.Utils as Utils import qualified Test.Core.Utils as Utils
import qualified Test.Core.Similarity as Similarity
import qualified Test.Graph.Clustering as Graph import qualified Test.Graph.Clustering as Graph
import qualified Test.Ngrams.NLP as NLP import qualified Test.Ngrams.NLP as NLP
import qualified Test.Ngrams.Query as NgramsQuery import qualified Test.Ngrams.Query as NgramsQuery
...@@ -36,6 +37,7 @@ main = do ...@@ -36,6 +37,7 @@ main = do
cryptoSpec <- testSpec "Crypto" Crypto.test cryptoSpec <- testSpec "Crypto" Crypto.test
nlpSpec <- testSpec "NLP" NLP.test nlpSpec <- testSpec "NLP" NLP.test
jobsSpec <- testSpec "Jobs" Jobs.test jobsSpec <- testSpec "Jobs" Jobs.test
similaritySpec <- testSpec "Similarity" Similarity.test
defaultMain $ testGroup "Gargantext" defaultMain $ testGroup "Gargantext"
[ utilSpec [ utilSpec
...@@ -50,4 +52,5 @@ main = do ...@@ -50,4 +52,5 @@ main = do
, JSON.tests , JSON.tests
, Errors.tests , Errors.tests
, Phylo.tests , Phylo.tests
, similaritySpec
] ]
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