Commit 670bc6c8 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[GRAPH] Distances

parent 7879431c
...@@ -17,9 +17,16 @@ module Gargantext.Viz.Graph.Distances ...@@ -17,9 +17,16 @@ module Gargantext.Viz.Graph.Distances
where where
import Data.Array.Accelerate
import Gargantext.Viz.Graph.Distances.Matrice (measureConditional, distributional)
data Distance = Conditional | Distributional
measure :: Distance -> Matrix Int -> Matrix Double
measure Conditional = measureConditional
measure Distributional = distributional
...@@ -120,12 +120,13 @@ conditional m = filterMat (threshold m') m' ...@@ -120,12 +120,13 @@ conditional m = filterMat (threshold m') m'
(length nodes_kept) (length nodes_kept)
(\(i,j) -> getElem ((M.!) dico_nodes i) ((M.!) dico_nodes j) x') (\(i,j) -> getElem ((M.!) dico_nodes i) ((M.!) dico_nodes j) x')
threshold m'' = V.minimum $ V.map (\cId -> V.maximum $ getCol cId m'') (V.enumFromTo 1 (nOf Col m'')) threshold m'' = V.minimum
$ V.map (\cId -> V.maximum $ getCol cId m'')
(V.enumFromTo 1 (nOf Col m'') )
filterMat t m'' = mapAll (\x -> filter' t x) m'' filterMat t m'' = mapAll (\x -> filter' t x) m''
where where
filter' t' x = case (x >= t') of filter' t' x = case (x >= t') of
True -> x True -> x
False -> 0 False -> 0
------------------------------------------------------------------------ ------------------------------------------------------------------------
...@@ -26,7 +26,7 @@ import Gargantext.Prelude ...@@ -26,7 +26,7 @@ import Gargantext.Prelude
import Gargantext.Core.Statistics import Gargantext.Core.Statistics
import Gargantext.Viz.Graph import Gargantext.Viz.Graph
import Gargantext.Viz.Graph.Bridgeness (bridgeness) import Gargantext.Viz.Graph.Bridgeness (bridgeness)
import Gargantext.Viz.Graph.Distances.Matrice (measureConditional) import Gargantext.Viz.Graph.Distances (Distance(..), measure)
import Gargantext.Viz.Graph.Index (createIndices, toIndex, map2mat, mat2map, Index) import Gargantext.Viz.Graph.Index (createIndices, toIndex, map2mat, mat2map, Index)
import Gargantext.Viz.Graph.IGraph (mkGraphUfromEdges) import Gargantext.Viz.Graph.IGraph (mkGraphUfromEdges)
import Gargantext.Viz.Graph.Proxemy (confluence) import Gargantext.Viz.Graph.Proxemy (confluence)
...@@ -48,7 +48,7 @@ cooc2graph' threshold myCooc = distanceMap ...@@ -48,7 +48,7 @@ cooc2graph' threshold myCooc = distanceMap
(ti, _) = createIndices myCooc (ti, _) = createIndices myCooc
myCooc' = toIndex ti myCooc myCooc' = toIndex ti myCooc
matCooc = map2mat 0 (Map.size ti) $ Map.filter (> 1) myCooc' matCooc = map2mat 0 (Map.size ti) $ Map.filter (> 1) myCooc'
distanceMat = measureConditional matCooc distanceMat = measure Conditional matCooc
distanceMap = Map.filter (> threshold) $ mat2map distanceMat distanceMap = Map.filter (> threshold) $ mat2map distanceMat
...@@ -60,7 +60,7 @@ cooc2graph threshold myCooc = do ...@@ -60,7 +60,7 @@ cooc2graph threshold myCooc = do
(ti, _) = createIndices myCooc (ti, _) = createIndices myCooc
myCooc' = toIndex ti myCooc myCooc' = toIndex ti myCooc
matCooc = map2mat 0 (Map.size ti) $ Map.filter (> 1) myCooc' matCooc = map2mat 0 (Map.size ti) $ Map.filter (> 1) myCooc'
distanceMat = measureConditional matCooc distanceMat = measure Conditional matCooc
distanceMap = Map.filter (> threshold) $ mat2map distanceMat distanceMap = Map.filter (> threshold) $ mat2map distanceMat
nodesApprox :: Int nodesApprox :: Int
......
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