Commit 32783b34 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[REFACT] Graph coordinates.

parent 46aefabe
......@@ -10,6 +10,7 @@ Portability : POSIX
Let be a graph with partitions (from Louvain algo), Bridgeness uniformly
filters inter-communities links.
TODO rewrite Bridgeness with "equivalence structurale" metrics
-}
{-# LANGUAGE NoImplicitPrelude #-}
......
......@@ -15,6 +15,7 @@ Références:
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-}
module Gargantext.Viz.Graph.Proxemy
where
......
......@@ -7,7 +7,6 @@ Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE NoImplicitPrelude #-}
......@@ -16,17 +15,18 @@ Portability : POSIX
module Gargantext.Viz.Graph.Tools
where
import Debug.Trace (trace)
import Data.Graph.Clustering.Louvain.CplusPlus (LouvainNode(..))
import Data.Graph.Clustering.Louvain.CplusPlus (cLouvain)
import Data.Map (Map)
import Data.Text (Text)
import Gargantext.Prelude
import Gargantext.Core.Statistics
import Gargantext.Viz.Graph (Graph(..))
import Gargantext.Viz.Graph -- (Graph(..))
import Gargantext.Viz.Graph.Bridgeness (bridgeness)
import Gargantext.Viz.Graph
--import Gargantext.Viz.Graph.Bridgeness (bridgeness)
import Gargantext.Viz.Graph.Distances.Matrice (measureConditional)
import Gargantext.Viz.Graph.Index (createIndices, toIndex, map2mat, mat2map)
import GHC.Float (sin, cos)
import qualified Data.Vector.Storable as Vec
import qualified Data.Map as Map
......@@ -42,7 +42,7 @@ cooc2graph myCooc = do
True -> cLouvain distanceMap
False -> panic "Text.Flow: DistanceMap is empty"
let distanceMap' = bridgeness 300 partitions distanceMap
let distanceMap' = distanceMap -- bridgeness 300 partitions distanceMap
pure $ data2graph (Map.toList ti) myCooc4 distanceMap' partitions
......@@ -57,8 +57,8 @@ data2graph :: [(Text, Int)] -> Map (Int, Int) Int
data2graph labels coocs distance partitions = Graph nodes edges Nothing
where
community_id_by_node_id = Map.fromList [ (n, c) | LouvainNode n c <- partitions ]
nodes = map (setCoord mapCoord)
nodes = map (setCoord ForceAtlas labels distance)
[ (n, Node { node_size = maybe 0 identity (Map.lookup (n,n) coocs)
, node_type = Terms -- or Unknown
, node_id = cs (show n)
......@@ -72,32 +72,66 @@ data2graph labels coocs distance partitions = Graph nodes edges Nothing
| (l, n) <- labels
]
edges = [ Edge { edge_source = cs (show s)
edges = trace (show distance) [ Edge { edge_source = cs (show s)
, edge_target = cs (show t)
, edge_weight = w
, edge_id = cs (show i) }
| (i, ((s,t), w)) <- zip ([0..]::[Integer]) (Map.toList distance) ]
mapCoord = pcaReduceTo (Dimension 2) $ mapArray labels distance
setCoord :: Map Int (Vec.Vector Double) -> (Int, Node) -> Node
setCoord m (n,node) = node { node_x_coord = x, node_y_coord = y }
------------------------------------------------------------------------
data Layout = KamadaKawai | ACP | ForceAtlas
setCoord'' :: Layout -> (Int, Node) -> Node
setCoord'' ForceAtlas = setCoord' (\i-> (sin $ fromIntegral i, cos $ fromIntegral i))
setCoord'' ACP = undefined
setCoord'' KamadaKawai = undefined
setCoord' :: (Int -> (Double, Double)) -> (Int, Node) -> Node
setCoord' f (i,n) = n { node_x_coord = x, node_y_coord = y }
where
(x,y) = to2d $ maybe (panic "Graph.Tools no coordinate") identity $ Map.lookup n m
(x,y) = f i
to2d :: Vec.Vector Double -> (Double, Double)
to2d v = (x,y)
-- | ACP
setCoord :: Ord a => Layout -> [(a, Int)] -> Map (Int, Int) Double -> (Int, Node) -> Node
setCoord l labels m (n,node) = node { node_x_coord = x, node_y_coord = y }
where
ds = take 2 $ Vec.toList v
x = head' "to2d" ds
y = last' "to2d" ds
(x,y) = getCoord l labels m n
mapArray :: Ord a => [(a, Int)] -> Map (Int, Int) Double -> Map Int (Vec.Vector Double)
mapArray items m = Map.fromList [ toVec n ns m | n <- ns ]
getCoord :: Ord a => Layout
-> [(a, Int)] -> Map (Int, Int) Double -> Int -> (Double, Double)
getCoord KamadaKawai _ _ _ = undefined
getCoord ForceAtlas _ _ n = (sin d, cos d)
where
ns = map snd items
d = fromIntegral n
getCoord ACP labels m n = to2d $ maybe (panic "Graph.Tools no coordinate") identity
$ Map.lookup n
$ pcaReduceTo (Dimension 2)
$ mapArray labels m
where
to2d :: Vec.Vector Double -> (Double, Double)
to2d v = (x',y')
where
ds = take 2 $ Vec.toList v
x' = head' "to2d" ds
y' = last' "to2d" ds
mapArray :: Ord a => [(a, Int)] -> Map (Int, Int) Double -> Map Int (Vec.Vector Double)
mapArray items m' = Map.fromList [ toVec n' ns m' | n' <- ns ]
where
ns = map snd items
toVec :: Int -> [Int] -> Map (Int,Int) Double -> (Int, Vec.Vector Double)
toVec n' ns' m' = (n', Vec.fromList $ map (\n'' -> maybe 0 identity $ Map.lookup (n',n'') m') ns')
------------------------------------------------------------------------
-- | KamadaKawai Layout
layout :: Map (Int, Int) Double -> IO (Map Int (Double, Double))
layout = undefined
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