Commit 19ff6e2c authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FIX] Order 2 distance is ok (needs node size in graph still)

parent 96a7bf42
......@@ -14,21 +14,21 @@ Portability : POSIX
module Gargantext.Core.Methods.Distances
where
-- import Debug.Trace (trace)
import Data.Aeson
import Data.Array.Accelerate (Matrix)
import Data.Swagger
import GHC.Generics (Generic)
import Gargantext.Core.Methods.Distances.Accelerate.Conditional (measureConditional)
import Gargantext.Core.Methods.Distances.Accelerate.Distributional (logDistributional)
import Gargantext.Prelude (Ord, Eq, Int, Double)
import Gargantext.Prelude (Show)
import Gargantext.Prelude (Ord, Eq, Int, Double, Show{-, ($), show-})
import Prelude (Enum, Bounded, minBound, maxBound)
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary
------------------------------------------------------------------------
data Distance = Conditional | Distributional
deriving (Show)
deriving (Show, Eq)
measure :: Distance -> Matrix Int -> Matrix Double
measure Conditional = measureConditional
......
......@@ -126,6 +126,8 @@ logDistributional m = run
logDistributional' :: Int -> Matrix Int -> Acc (Matrix Double)
logDistributional' n m' = result
where
-- From Matrix Int to Matrix Double, i.e :
-- m :: Matrix Int -> Matrix Double
m = map fromIntegral $ use m'
-- Scalar. Sum of all elements of m.
......@@ -137,9 +139,9 @@ logDistributional' n m' = result
-- Size n vector. s = [s_i]_i
s = sum ((.-) m d_m)
-- Matrix nxn. Vector s replicated as rows.
-- Matrix nxn. Vector s replicated as rows.
s_1 = replicate (constant (Z :. All :. n)) s
-- Matrix nxn. Vector s replicated as columns.
-- Matrix nxn. Vector s replicated as columns.
s_2 = replicate (constant (Z :. n :. All)) s
-- Matrix nxn. ss = [s_i * s_j]_{i,j}. Outer product of s with itself.
......
......@@ -180,8 +180,8 @@ computeGraph cId d nt repo = do
let ngs = filterListWithRoot MapTerm
$ mapTermListRoot [lId] nt repo
myCooc <- HashMap.filter (>2) -- Removing the hapax (ngrams with 1 cooc)
<$> getCoocByNgrams (Diagonal True)
myCooc <- HashMap.filter (>1) -- Removing the hapax (ngrams with 1 cooc)
<$> getCoocByNgrams (if d == Conditional then Diagonal True else Diagonal False)
<$> groupNodesByNgrams ngs
<$> getNodesByNgramsOnlyUser cId (lIds <> [lId]) nt (HashMap.keys ngs)
......
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