Commit 3eca5e5e authored by Alexandre Delanoë's avatar Alexandre Delanoë

[GRAPH] removing trace + unconnected nodes (some left still).

parent 5a6c70c6
......@@ -24,7 +24,6 @@ Portability : POSIX
module Gargantext.Viz.Graph.API
where
import Debug.Trace (trace)
import Control.Lens (set, (^.), _Just, (^?))
import Control.Monad.IO.Class (liftIO)
import Data.Maybe (Maybe(..))
......@@ -112,7 +111,7 @@ computeGraph cId nt v = do
<$> groupNodesByNgrams ngs
<$> getNodesByNgramsOnlyUser cId (lIds <> [lId]) nt (Map.keys ngs)
graph <- trace (show myCooc) $ liftIO $ cooc2graph 0 myCooc
graph <- liftIO $ cooc2graph 0 myCooc
let graph' = set graph_metadata (Just metadata) graph
pure graph'
......
......@@ -89,7 +89,7 @@ data2graph labels coocs bridge conf partitions = do
, edge_confluence = maybe 0 identity $ Map.lookup (s,t) conf
-- , edge_confluence = maybe (panic "E: data2graph edges") identity $ Map.lookup (s,t) conf
, edge_id = cs (show i) }
| (i, ((s,t), d)) <- zip ([0..]::[Integer]) (Map.toList bridge), s /= t
| (i, ((s,t), d)) <- zip ([0..]::[Integer]) (Map.toList bridge), s /= t, d > 0.001
]
pure $ Graph nodes edges 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