Commit cdcf9903 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[test] fix tests

parent dc10d9c3
Pipeline #1465 failed with stage
...@@ -16,7 +16,8 @@ commentary with @some markup@. ...@@ -16,7 +16,8 @@ commentary with @some markup@.
module Graph.Distance where module Graph.Distance where
import Test.Hspec import Test.Hspec
import Gargantext.Viz.Graph.Distances.Matrice
import Gargantext.Core.Methods.Matrix.Accelerate.Utils (cross', matrix)
import Gargantext.Prelude import Gargantext.Prelude
test :: IO () test :: IO ()
......
...@@ -28,7 +28,7 @@ import Duckling.Time.Types (toRFC3339) ...@@ -28,7 +28,7 @@ import Duckling.Time.Types (toRFC3339)
----------------------------------------------------------- -----------------------------------------------------------
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Text.Corpus.Parsers.Date.Parsec (fromRFC3339) import Gargantext.Core.Text.Corpus.Parsers.Date.Parsec (fromRFC3339)
import Parsers.Types import Parsers.Types
----------------------------------------------------------- -----------------------------------------------------------
......
...@@ -14,7 +14,9 @@ module Utils.Crypto where ...@@ -14,7 +14,9 @@ module Utils.Crypto where
import Data.Text (Text) import Data.Text (Text)
import Test.Hspec import Test.Hspec
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Prelude.Crypto.Hash
import Gargantext.Prelude.Utils import Gargantext.Prelude.Utils
-- | Crypto Hash tests -- | Crypto Hash tests
......
...@@ -69,6 +69,7 @@ cooc2graph' distance threshold myCooc ...@@ -69,6 +69,7 @@ cooc2graph' distance threshold myCooc
data PartitionMethod = Louvain | Spinglass data PartitionMethod = Louvain | Spinglass
-- | coocurrences graph computation
cooc2graphWith :: PartitionMethod cooc2graphWith :: PartitionMethod
-> Distance -> Distance
-> Threshold -> Threshold
...@@ -134,14 +135,14 @@ cooc2graphWith' doPartitions distance threshold myCooc = do ...@@ -134,14 +135,14 @@ cooc2graphWith' doPartitions distance threshold myCooc = do
similarities = measure distance matCooc similarities = measure distance matCooc
links = round (let n :: Double = fromIntegral tiSize in n * log n) links = round (let n :: Double = fromIntegral tiSize in n * log n)
distanceMap = Map.fromList distanceMap = Map.fromList
$ List.take links $ List.take links
$ List.sortOn snd $ List.sortOn snd
$ Map.toList $ Map.toList
$ case distance of $ case distance of
Conditional -> Map.filter (> threshold) Conditional -> Map.filter (> threshold)
Distributional -> Map.filter (> 0) Distributional -> Map.filter (> 0)
$ mat2map similarities $ mat2map similarities
nodesApprox :: Int nodesApprox :: Int
nodesApprox = n' nodesApprox = 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