Commit c5c019e7 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[OK] New bridgeness implemented: user should either use the old one or the new...

[OK] New bridgeness implemented: user should either use the old one or the new one. The difference is showing the difference between a mindmap and a topoimap, if I had to use an BIG analogy
parent 99f5ac3d
......@@ -52,21 +52,18 @@ type Confluence = Map (NodeId, NodeId) Double
bridgeness3 :: Confluence
-> Map (NodeId, NodeId) Double
-> Map (NodeId, NodeId) Double
bridgeness3 c m = trace ("bridgeness c' size: " <> (show $ List.length c'))
$ Map.fromList
bridgeness3 c m = Map.fromList
$ map (\(ks, (v1,_v2)) -> (ks,v1))
$ List.take n
-- $ List.sortOn (Down . (snd . snd))
$ Map.toList c'
$ List.sortOn (Down . (snd . snd))
$ Map.toList
$ trace ("bridgeness3 m c" <> show (m,c)) $ Map.intersectionWithKey (\k v1 v2 -> trace ("intersectionWithKey " <> (show (k, v1, v2))) (v1, v2)) m c
where
-- !c' = map2intMap c
!c' = Map.intersectionWithKey (\_k v1 v2 -> (v1, v2)) m c
!m' = Map.toList m
n :: Int
!n = trace ("bridgeness m size: " <> (show $ List.length m'))
$ round
$ (fromIntegral $ List.length m') / (10 :: Double)
$ (fromIntegral $ List.length m') / (50 :: Double)
map2intMap :: Map (Int, Int) a -> IntMap (IntMap a)
......
......@@ -14,6 +14,7 @@ Portability : POSIX
module Gargantext.Core.Viz.Graph.Tools
where
import Debug.Trace (trace)
import Data.Aeson
import Data.HashMap.Strict (HashMap)
import Data.Map (Map)
......@@ -129,8 +130,9 @@ cooc2graphWith' doPartitions multi similarity threshold strength myCooc = do
length partitions `seq` return ()
let
!confluence' = BAC.computeConfluences 3 (Map.keys bridgeness') True
!bridgeness' = bridgeness3 confluence' distanceMap
!confluence' = BAC.computeConfluences 3 (Map.keys distanceMap) True
!bridgeness' = trace ("bridgeness3 in tools" <> show (confluence', distanceMap)) $ bridgeness3 confluence' distanceMap
pure $ data2graph multi ti diag bridgeness' confluence' partitions
type Reverse = Bool
......
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