Commit 0eea2d3c authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FEAT] Order 2 fixed with filtered edges (finally...:)

parent 546419c5
...@@ -15,16 +15,18 @@ Motivation and definition of the @Conditional@ distance. ...@@ -15,16 +15,18 @@ Motivation and definition of the @Conditional@ distance.
module Gargantext.Core.Methods.Distances.Conditional module Gargantext.Core.Methods.Distances.Conditional
where where
import Control.DeepSeq (NFData)
import Control.Parallel.Strategies (parList, rdeepseq, using) import Control.Parallel.Strategies (parList, rdeepseq, using)
import Data.Hashable (Hashable) import Data.Hashable (Hashable)
import Data.List (unzip) import Data.List (unzip)
import Data.Maybe (catMaybes) import Data.Maybe (catMaybes)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Core.Viz.Graph.Utils (getMax)
import qualified Data.HashMap.Strict as Map import qualified Data.HashMap.Strict as Map
import qualified Data.Set as Set import qualified Data.Set as Set
import Control.DeepSeq (NFData)
type HashMap = Map.HashMap
type HashMap = Map.HashMap
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- First version as first implementation -- First version as first implementation
-- - qualitatively verified -- - qualitatively verified
...@@ -51,14 +53,6 @@ conditional m' = Map.fromList $ ((catMaybes results') `using` parList rdeepseq) ...@@ -51,14 +53,6 @@ conditional m' = Map.fromList $ ((catMaybes results') `using` parList rdeepseq)
(x,y) = unzip $ Map.keys m (x,y) = unzip $ Map.keys m
getMax :: (a,a)
-> Maybe Double
-> Maybe Double
-> Maybe ((a,a), Double)
getMax (i,j) (Just d) Nothing = Just ((i,j), d)
getMax (i,j) Nothing (Just d) = Just ((j,i), d)
getMax ij (Just di) (Just dj) = if di >= dj then getMax ij (Just di) Nothing
else getMax ij Nothing (Just dj)
getMax _ _ _ = Nothing
...@@ -26,6 +26,7 @@ import Gargantext.Core.Methods.Distances (Distance(..), measure) ...@@ -26,6 +26,7 @@ import Gargantext.Core.Methods.Distances (Distance(..), measure)
import Gargantext.Core.Methods.Graph.BAC.Proxemy (confluence) import Gargantext.Core.Methods.Graph.BAC.Proxemy (confluence)
import Gargantext.Core.Statistics import Gargantext.Core.Statistics
import Gargantext.Core.Viz.Graph import Gargantext.Core.Viz.Graph
import Gargantext.Core.Viz.Graph.Utils (edgesFilter)
import Gargantext.Core.Viz.Graph.Bridgeness (bridgeness, Partitions, ToComId(..)) import Gargantext.Core.Viz.Graph.Bridgeness (bridgeness, Partitions, ToComId(..))
import Gargantext.Core.Viz.Graph.Index (createIndices, toIndex, map2mat, mat2map, Index, MatrixShape(..)) import Gargantext.Core.Viz.Graph.Index (createIndices, toIndex, map2mat, mat2map, Index, MatrixShape(..))
import Gargantext.Core.Viz.Graph.Tools.IGraph (mkGraphUfromEdges, spinglass) import Gargantext.Core.Viz.Graph.Tools.IGraph (mkGraphUfromEdges, spinglass)
...@@ -50,6 +51,7 @@ defaultClustering x = spinglass 1 x ...@@ -50,6 +51,7 @@ defaultClustering x = spinglass 1 x
------------------------------------------------------------- -------------------------------------------------------------
type Threshold = Double type Threshold = Double
cooc2graph' :: Ord t => Distance cooc2graph' :: Ord t => Distance
-> Double -> Double
-> Map (t, t) Int -> Map (t, t) Int
...@@ -151,6 +153,7 @@ doDistanceMap Distributional threshold myCooc = (distanceMap, toIndex ti diag, t ...@@ -151,6 +153,7 @@ doDistanceMap Distributional threshold myCooc = (distanceMap, toIndex ti diag, t
$ List.take links $ List.take links
$ List.sortOn snd $ List.sortOn snd
$ Map.toList $ Map.toList
$ edgesFilter
$ Map.filter (> threshold) $ Map.filter (> threshold)
$ mat2map similarities $ mat2map similarities
......
...@@ -17,14 +17,16 @@ These functions are used for Vector.Matrix only. ...@@ -17,14 +17,16 @@ These functions are used for Vector.Matrix only.
module Gargantext.Core.Viz.Graph.Utils module Gargantext.Core.Viz.Graph.Utils
where where
import Data.Map (Map)
import Data.Matrix hiding (identity) import Data.Matrix hiding (identity)
import Data.Vector (Vector) import Data.Vector (Vector)
import qualified Data.Vector as V
import qualified Data.List as L import qualified Data.List as L
import qualified Data.Map as Map
import Gargantext.Prelude import Gargantext.Prelude
import Data.List (unzip)
import qualified Data.Vector as V
import Data.Maybe (catMaybes)
import qualified Data.Set as Set
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | Some utils to build the matrix from cooccurrence results -- | Some utils to build the matrix from cooccurrence results
...@@ -63,8 +65,35 @@ toListsWithIndex m = concat' $ zip [1..] $ map (\c -> zip [1..] c) $ toLists m ...@@ -63,8 +65,35 @@ toListsWithIndex m = concat' $ zip [1..] $ map (\c -> zip [1..] c) $ toLists m
concat' :: [(Int, [(Int, a)])] -> [((Int, Int), a)] concat' :: [(Int, [(Int, a)])] -> [((Int, Int), a)]
concat' xs = L.concat $ map (\(x, ys) -> map (\(y, a) -> ((x,y), a)) ys ) xs concat' xs = L.concat $ map (\(x, ys) -> map (\(y, a) -> ((x,y), a)) ys ) xs
------------------------------------------------------------------------
-- Utils to manage Graphs
edgesFilter :: (Ord a, Ord b) => Map (a,a) b -> Map (a,a) b
edgesFilter m = Map.fromList $ catMaybes results
where
results = [ let
ij = Map.lookup (i,j) m
ji = Map.lookup (j,i) m
in getMax (i,j) ij ji
| i <- keys
, j <- keys
, i < j
]
keys = Set.toList $ Set.fromList (x <> y)
(x,y) = unzip $ Map.keys m
getMax :: Ord b
=> (a,a)
-> Maybe b
-> Maybe b
-> Maybe ((a,a), b)
getMax (i,j) (Just d) Nothing = Just ((i,j), d)
getMax (i,j) Nothing (Just d) = Just ((j,i), d)
getMax ij (Just di) (Just dj) = if di >= dj then getMax ij (Just di) Nothing
else getMax ij Nothing (Just dj)
getMax _ _ _ = Nothing
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