Commit 08551cc4 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[MERGE]

parents ddfedc92 72763230
Pipeline #5705 failed with stages
in 94 minutes and 6 seconds
...@@ -131,6 +131,7 @@ library ...@@ -131,6 +131,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
...@@ -258,8 +259,8 @@ library ...@@ -258,8 +259,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
...@@ -282,7 +283,6 @@ library ...@@ -282,7 +283,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
...@@ -302,10 +302,10 @@ library ...@@ -302,10 +302,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
...@@ -404,12 +404,12 @@ library ...@@ -404,12 +404,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
...@@ -417,13 +417,13 @@ library ...@@ -417,13 +417,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
......
...@@ -19,7 +19,7 @@ import Data.Array.Accelerate (Matrix) ...@@ -19,7 +19,7 @@ import Data.Array.Accelerate (Matrix)
import Data.Swagger import Data.Swagger
import Data.Text (Text) import Data.Text (Text)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Gargantext.Core.Methods.Similarities.Accelerate.Conditional (measureConditional) import Gargantext.Core.Methods.Similarities.Accelerate.Conditional (measureConditional')
import Gargantext.Core.Methods.Similarities.Accelerate.Distributional (logDistributional2) import Gargantext.Core.Methods.Similarities.Accelerate.Distributional (logDistributional2)
-- import Gargantext.Core.Text.Metrics.Count (coocOn) -- import Gargantext.Core.Text.Metrics.Count (coocOn)
-- import Gargantext.Core.Viz.Graph.Index -- import Gargantext.Core.Viz.Graph.Index
...@@ -35,13 +35,13 @@ data Similarity = Conditional | Distributional ...@@ -35,13 +35,13 @@ data Similarity = Conditional | Distributional
deriving (Show, Eq) deriving (Show, Eq)
measure :: Similarity -> Matrix Int -> Matrix Double measure :: Similarity -> Matrix Int -> Matrix Double
measure Conditional x = measureConditional x measure Conditional x = measureConditional' x
measure Distributional x = logDistributional2 x measure Distributional x = logDistributional2 x
------------------------------------------------------------------------ ------------------------------------------------------------------------
withMetric :: GraphMetric -> Similarity withMetric :: GraphMetric -> Similarity
withMetric Order1 = Conditional withMetric Order1 = Conditional
withMetric _ = Distributional withMetric _ = Distributional
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- Order2 type is for keeping Database json compatibility -- Order2 type is for keeping Database json compatibility
......
...@@ -48,8 +48,30 @@ import qualified Gargantext.Prelude as P ...@@ -48,8 +48,30 @@ import qualified Gargantext.Prelude as P
-- Filtered with MiniMax. -- Filtered with MiniMax.
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
x :: Acc (Matrix Double) -> Acc (Matrix Double)
x mat = maxOnly $ diagNull r $ divByDiag r mat
r :: Dim
r = dim m
-- Maybe we should use backpermute to accelerate it (no need to access to cells then
maxOnly :: Acc (SymetricMatrix Double) -> Acc (Matrix Double)
maxOnly m' = generate (shape m')
((\coord
-> let (Z :. (i :: Exp Int) :. (j :: Exp Int)) = unlift coord
ij = m' ! (lift $ (Z :. i :. j))
ji = m' ! (lift $ (Z :. j :. i))
in
ifThenElse (ij > ji) ij (constant 0)
)
)
measureConditional' :: Matrix Int -> Matrix Double
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 = matMiniMax $ matProba r mat x mat = matMiniMax $ matProba r mat
...@@ -58,6 +80,7 @@ measureConditional m = run $ x $ map fromIntegral $ use m ...@@ -58,6 +80,7 @@ measureConditional m = run $ x $ map fromIntegral $ use m
r = dim m r = dim m
-- | To filter the nodes -- | To filter the nodes
-- The conditional metric P(i|j) of 2 terms @i@ and @j@, also called -- The conditional metric P(i|j) of 2 terms @i@ and @j@, also called
-- "confidence" , is the maximum probability between @i@ and @j@ to see -- "confidence" , is the maximum probability between @i@ and @j@ to see
......
...@@ -21,7 +21,9 @@ import Data.HashMap.Strict qualified as Map ...@@ -21,7 +21,9 @@ import Data.HashMap.Strict qualified as Map
import Data.Set qualified as Set import Data.Set qualified as Set
import Gargantext.Core.Viz.Graph.Utils (getMax) import Gargantext.Core.Viz.Graph.Utils (getMax)
import Gargantext.Prelude import Gargantext.Prelude
import Data.Map.Strict qualified as M
import Gargantext.Core.Methods.Similarities.Accelerate.Conditional (measureConditional)
import Gargantext.Core.Viz.Graph.Index (score, MatrixShape(..))
type HashMap = Map.HashMap type HashMap = Map.HashMap
------------------------------------------------------------------------ ------------------------------------------------------------------------
...@@ -35,7 +37,11 @@ conditional m' = Map.fromList $ ((catMaybes results') `using` parList rdeepseq) ...@@ -35,7 +37,11 @@ conditional m' = Map.fromList $ ((catMaybes results') `using` parList rdeepseq)
where where
results' = [ let results' = [ let
ij = (/) <$> Map.lookup (i,j) m <*> Map.lookup (j,j) m ij = (/) <$> Map.lookup (i,j) m <*> Map.lookup (j,j) m
ji = (/) <$> Map.lookup (j,i) m <*> Map.lookup (i,i) m -- proba of i|j, high values means i is more generic than j
ji = (/) <$> Map.lookup (i,j) m <*> Map.lookup (i,i) m
-- proba of j|i, high values means j is more generic than i
in getMax (i,j) ij ji in getMax (i,j) ij ji
| i <- keys | i <- keys
...@@ -49,4 +55,45 @@ conditional m' = Map.fromList $ ((catMaybes results') `using` parList rdeepseq) ...@@ -49,4 +55,45 @@ 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_test2 :: HashMap (Text,Text) Double
conditional_test2 = Map.fromList
$ M.toList
$ M.filter (>0)
$ score Square measureConditional
$ M.fromList example_matrix
example_matrix :: [((Text,Text), Int)]
example_matrix = concat [
compte "polygon" "polygon" 19
, compte "polygon" "square" 6
, compte "polygon" "triangle" 10
, compte "polygon" "losange" 3
, compte "triangle" "triangle" 11
, compte "square" "square" 7
, compte "losange" "losange" 15
, compte "shape" "shape" 10
, compte "circle" "circle" 6
, compte "shape" "circle" 3
, compte "shape" "square" 2
, compte "polygon" "shape" 10
]
where
compte a b c = if a /= b
then [((a,b),c), ((b,a), c)]
else [((a,b),c)]
...@@ -79,8 +79,8 @@ cooc2graph' distance threshold myCooc ...@@ -79,8 +79,8 @@ cooc2graph' distance threshold myCooc
$ mat2map $ mat2map
$ measure distance $ measure distance
$ case distance of $ case distance of
Conditional -> map2mat Triangle 0 tiSize Conditional -> map2mat Square 1 tiSize
_ -> map2mat Square 0 tiSize _ -> map2mat Square 0 tiSize
$ Map.filter (> 1) myCooc' $ Map.filter (> 1) myCooc'
where where
......
{-|
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
...@@ -24,6 +24,7 @@ import qualified Test.Offline.Stemming.Lancaster as Lancaster ...@@ -24,6 +24,7 @@ import qualified Test.Offline.Stemming.Lancaster as Lancaster
import qualified Test.Parsers.Date as PD import qualified Test.Parsers.Date as PD
import qualified Test.Utils.Crypto as Crypto import qualified Test.Utils.Crypto as Crypto
import qualified Test.Utils.Jobs as Jobs import qualified Test.Utils.Jobs as Jobs
import qualified Test.Core.Similarity as Similarity
import Test.Tasty import Test.Tasty
import Test.Tasty.Hspec import Test.Tasty.Hspec
...@@ -37,6 +38,7 @@ main = do ...@@ -37,6 +38,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,6 +52,7 @@ main = do ...@@ -50,6 +52,7 @@ main = do
, CorpusQuery.tests , CorpusQuery.tests
, JSON.tests , JSON.tests
, Errors.tests , Errors.tests
, similaritySpec
, Phylo.tests , Phylo.tests
, testGroup "Stemming" [ Lancaster.tests ] , testGroup "Stemming" [ Lancaster.tests ]
] ]
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