Commit 68881fa0 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[GRAPH] Legend funs

parent b3cff82c
Pipeline #958 failed with stage
......@@ -190,7 +190,11 @@ graphV3ToGraph (GraphV3 links nodes) = Graph (map nodeV32node nodes) (zipWith li
= Node no_s' Terms (cs $ show no_id') no_lb' 0 0 (Attributes cl')
linkV32edge :: Int -> EdgeV3 -> Edge
linkV32edge n (EdgeV3 eo_s' eo_t' eo_w') = Edge (cs $ show eo_s') (cs $ show eo_t') ((T.read $ T.unpack eo_w') :: Double) 0.5 (cs $ show n)
linkV32edge n (EdgeV3 eo_s' eo_t' eo_w') = Edge (cs $ show eo_s')
(cs $ show eo_t')
((T.read $ T.unpack eo_w') :: Double)
0.5
(cs $ show n)
graphV3ToGraphWithFiles :: FilePath -> FilePath -> IO ()
......
......@@ -135,15 +135,6 @@ computeGraph :: HasNodeError err
computeGraph cId d nt repo = do
lId <- defaultList cId
let metadata = GraphMetadata "Title"
Order1
[cId]
[ LegendField 1 "#FFF" "Cluster"
, LegendField 2 "#FFF" "Cluster"
]
(ListForGraph lId (repo ^. r_version))
-- (map (\n -> LegendField n "#FFFFFF" (pack $ show n)) [1..10])
lIds <- selectNodesWithUsername NodeList userMaster
let ngs = filterListWithRoot MapTerm $ mapTermListRoot [lId] nt repo
......@@ -154,8 +145,21 @@ computeGraph cId d nt repo = do
<$> getNodesByNgramsOnlyUser cId (lIds <> [lId]) nt (Map.keys ngs)
graph <- liftBase $ cooc2graph d 0 myCooc
let graph' = set graph_metadata (Just metadata) graph
pure graph'
let metadata = GraphMetadata "Title"
Order1
[cId]
[ LegendField 1 "#FFF" "Cluster1"
, LegendField 2 "#FFF" "Cluster2"
, LegendField 3 "#FFF" "Cluster3"
, LegendField 4 "#FFF" "Cluster4"
]
(ListForGraph lId (repo ^. r_version))
-- (map (\n -> LegendField n "#FFFFFF" (pack $ show n)) [1..10])
pure $ set graph_metadata (Just metadata) graph
------------------------------------------------------------
type GraphAsyncAPI = Summary "Update graph"
......
......@@ -13,11 +13,6 @@ filters inter-communities links.
TODO rewrite Bridgeness with "equivalence structurale" metrics (Confluence)
TODO use Map LouvainNodeId (Map LouvainNodeId)
-}
......@@ -26,17 +21,14 @@ module Gargantext.Viz.Graph.Bridgeness (bridgeness)
import Data.Ord (Down(..))
import Gargantext.Prelude
import Data.Map (Map, fromListWith, lookup, fromList, toList, mapWithKey, elems)
import Data.Map (Map, fromListWith, lookup, toList, mapWithKey, elems)
import qualified Data.Map as DM
import Data.Maybe (catMaybes)
import Data.List (concat, sortOn)
import Data.Graph.Clustering.Louvain.Utils (LouvainNode(..))
import Gargantext.Viz.Graph.Louvain (LouvainNodeId, CommunityId, nodeId2comId)
-- TODO mv in Louvain Lib
type LouvainNodeId = Int
type CommunityId = Int
type Bridgeness = Double
......@@ -50,11 +42,6 @@ bridgeness b ns = DM.fromList
. filterComs b
. groupEdges (nodeId2comId ns)
nodeId2comId :: [LouvainNode] -> Map LouvainNodeId CommunityId
nodeId2comId ns = fromList [(nId,cId) | LouvainNode nId cId <- ns]
groupEdges :: Map LouvainNodeId CommunityId
-> Map (LouvainNodeId, LouvainNodeId) Double
-> Map (CommunityId, CommunityId) [((LouvainNodeId, LouvainNodeId), Double)]
......@@ -84,4 +71,3 @@ filterComs _b m = DM.filter (\n -> length n > 0) $ mapWithKey filter' m
a'= fromIntegral $ length a
t :: Double
t = fromIntegral $ length $ concat $ elems m
......@@ -63,7 +63,6 @@ ecount = fromIntegral . List.length . List.nub . edges
------------------------------------------------------------------
-- | Main sugared functions
mkGraphUfromEdges :: [(Int, Int)] -> Graph_Undirected
mkGraphUfromEdges es = mkGraph ns es
where
......
{-|
Module : Gargantext.Viz.Graph.Legend
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
module Gargantext.Viz.Graph.Legend
where
import Data.Ord (Down(..))
import Gargantext.Prelude
import Data.Map (Map, fromListWith, lookup, toList, mapWithKey, elems)
import qualified Data.Map as DM
import Data.Maybe (catMaybes)
import Data.List (concat, sortOn)
import Gargantext.Viz.Graph.Louvain (LouvainNodeId, CommunityId, comId2nodeId)
{-
[LouvainNode] -> Map CommunityId LouvainNodeId
[(CommunityId, [LouvainNodeId])]
sort by length LouvainNodeIds
Cooc -> DGI.Graph
sort [LouvainNodeId]
subgraph with [LouvainNodeId]
-> prendre le noeud le mieux connecté (degree to start with)
Map NodeId Label
-> map [LouvainNodeId] -> [(CommunityId, take 3 [Label])]
take 7 [(CommunityId, take 3 [Label])]
-}
{-|
Module : Gargantext.Viz.Graph.Louvain
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
module Gargantext.Viz.Graph.Louvain
where
import Gargantext.Prelude
import Data.Map (Map, fromList)
import Data.Graph.Clustering.Louvain.Utils (LouvainNode(..))
type LouvainNodeId = Int
type CommunityId = Int
nodeId2comId :: [LouvainNode] -> Map LouvainNodeId CommunityId
nodeId2comId ns = fromList [(nId,cId) | LouvainNode nId cId <- ns]
comId2nodeId :: [LouvainNode] -> Map CommunityId LouvainNodeId
comId2nodeId ns = fromList [(cId,nId) | LouvainNode nId cId <- ns]
......@@ -82,7 +82,8 @@ cooc2graph distance threshold myCooc = do
let
-- bridgeness' = distanceMap
bridgeness' = trace ("Rivers: " <> show rivers) $ bridgeness rivers partitions distanceMap
bridgeness' = trace ("Rivers: " <> show rivers)
$ bridgeness rivers partitions distanceMap
confluence' = confluence (Map.keys bridgeness') 3 True False
pure $ data2graph (Map.toList ti) myCooc' bridgeness' confluence' partitions
......
......@@ -64,3 +64,7 @@ toListsWithIndex m = concat' $ zip [1..] $ map (\c -> zip [1..] c) $ toLists m
concat' xs = L.concat $ map (\(x, ys) -> map (\(y, a) -> ((x,y), a)) ys ) xs
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