Commit 51818eb6 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[Graph] edgeWeight selector by edge weight index in sorted list

parent 98d0e992
...@@ -2,8 +2,7 @@ module Gargantext.Components.GraphExplorer where ...@@ -2,8 +2,7 @@ module Gargantext.Components.GraphExplorer where
import Gargantext.Prelude hiding (max,min) import Gargantext.Prelude hiding (max,min)
import DOM.Simple.Types (Element) import Data.Array as A
import Data.Foldable (foldMap)
import Data.FoldableWithIndex (foldMapWithIndex) import Data.FoldableWithIndex (foldMapWithIndex)
import Data.Int (toNumber) import Data.Int (toNumber)
import Data.Map as Map import Data.Map as Map
...@@ -13,6 +12,7 @@ import Data.Sequence as Seq ...@@ -13,6 +12,7 @@ import Data.Sequence as Seq
import Data.Set as Set import Data.Set as Set
import Data.Tuple (fst, snd, Tuple(..)) import Data.Tuple (fst, snd, Tuple(..))
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import DOM.Simple.Types (Element)
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Math (log) import Math (log)
import Partial.Unsafe (unsafePartial) import Partial.Unsafe (unsafePartial)
...@@ -251,17 +251,19 @@ convert (GET.GraphData r) = Tuple r.metaData $ SigmaxTypes.Graph {nodes, edges} ...@@ -251,17 +251,19 @@ convert (GET.GraphData r) = Tuple r.metaData $ SigmaxTypes.Graph {nodes, edges}
color = GET.intColor (cDef n.attributes) color = GET.intColor (cDef n.attributes)
gargType = unsafePartial $ fromJust $ Types.modeFromString n.type_ gargType = unsafePartial $ fromJust $ Types.modeFromString n.type_
nodesMap = SigmaxTypes.nodesMap nodes nodesMap = SigmaxTypes.nodesMap nodes
edges = foldMap edgeFn r.edges edges = foldMapWithIndex edgeFn $ A.sortWith (\(GET.Edge {weight}) -> weight) r.edges
edgeFn (GET.Edge e) = Seq.singleton { id : e.id_ edgeFn i (GET.Edge e) = Seq.singleton { id : e.id_
, color , color
, confluence : e.confluence , confluence : e.confluence
, hidden : false , hidden : false
, size: 1.0 , size: 1.0
, source : e.source , source : e.source
, sourceNode , sourceNode
, target : e.target , target : e.target
, targetNode , targetNode
, weight : e.weight } , weight : e.weight
, weightIdx: i
}
where where
sourceNode = unsafePartial $ fromJust $ Map.lookup e.source nodesMap sourceNode = unsafePartial $ fromJust $ Map.lookup e.source nodesMap
targetNode = unsafePartial $ fromJust $ Map.lookup e.target nodesMap targetNode = unsafePartial $ fromJust $ Map.lookup e.target nodesMap
...@@ -325,7 +327,7 @@ transformGraph controls graph = SigmaxTypes.Graph {nodes: newNodes, edges: newEd ...@@ -325,7 +327,7 @@ transformGraph controls graph = SigmaxTypes.Graph {nodes: newNodes, edges: newEd
-- else -- else
-- edge { hidden = true } -- edge { hidden = true }
edgeWeightFilter :: Record SigmaxTypes.Edge -> Boolean edgeWeightFilter :: Record SigmaxTypes.Edge -> Boolean
edgeWeightFilter edge@{ weight } = Range.within (fst controls.edgeWeight) weight edgeWeightFilter edge@{ weightIdx } = Range.within (fst controls.edgeWeight) $ toNumber weightIdx
edgeInGraph :: SigmaxTypes.SelectedNodeIds -> Record SigmaxTypes.Edge -> Boolean edgeInGraph :: SigmaxTypes.SelectedNodeIds -> Record SigmaxTypes.Edge -> Boolean
edgeInGraph nodeIds e = (Set.member e.source nodeIds) && (Set.member e.target nodeIds) edgeInGraph nodeIds e = (Set.member e.source nodeIds) && (Set.member e.target nodeIds)
......
...@@ -8,6 +8,7 @@ module Gargantext.Components.GraphExplorer.Controls ...@@ -8,6 +8,7 @@ module Gargantext.Components.GraphExplorer.Controls
) where ) where
import Data.Array as A import Data.Array as A
import Data.Int as I
import Data.Maybe (Maybe(..), maybe) import Data.Maybe (Maybe(..), maybe)
import Data.Sequence as Seq import Data.Sequence as Seq
import Data.Set as Set import Data.Set as Set
...@@ -116,10 +117,14 @@ controlsCpt = R.hooksComponent "GraphControls" cpt ...@@ -116,10 +117,14 @@ controlsCpt = R.hooksComponent "GraphControls" cpt
let edgeConfluenceMax = maybe 100.0 _.confluence $ A.last edgesConfluenceSorted let edgeConfluenceMax = maybe 100.0 _.confluence $ A.last edgesConfluenceSorted
let edgeConfluenceRange = Range.Closed { min: edgeConfluenceMin, max: edgeConfluenceMax } let edgeConfluenceRange = Range.Closed { min: edgeConfluenceMin, max: edgeConfluenceMax }
let edgesWeightSorted = A.sortWith (_.weight) $ Seq.toUnfoldable $ SigmaxTypes.graphEdges props.graph --let edgesWeightSorted = A.sortWith (_.weight) $ Seq.toUnfoldable $ SigmaxTypes.graphEdges props.graph
let edgeWeightMin = maybe 0.0 _.weight $ A.head edgesWeightSorted --let edgeWeightMin = maybe 0.0 _.weight $ A.head edgesWeightSorted
let edgeWeightMax = maybe 100.0 _.weight $ A.last edgesWeightSorted --let edgeWeightMax = maybe 100.0 _.weight $ A.last edgesWeightSorted
let edgeWeightRange = Range.Closed { min: edgeWeightMin, max: edgeWeightMax } --let edgeWeightRange = Range.Closed { min: edgeWeightMin, max: edgeWeightMax }
let edgeWeightRange = Range.Closed {
min: 0.0
, max: I.toNumber $ Seq.length $ SigmaxTypes.graphEdges props.graph
}
let nodesSorted = A.sortWith (_.size) $ Seq.toUnfoldable $ SigmaxTypes.graphNodes props.graph let nodesSorted = A.sortWith (_.size) $ Seq.toUnfoldable $ SigmaxTypes.graphNodes props.graph
let nodeSizeMin = maybe 0.0 _.size $ A.head nodesSorted let nodeSizeMin = maybe 0.0 _.size $ A.head nodesSorted
...@@ -159,7 +164,10 @@ controlsCpt = R.hooksComponent "GraphControls" cpt ...@@ -159,7 +164,10 @@ controlsCpt = R.hooksComponent "GraphControls" cpt
useGraphControls :: SigmaxTypes.SGraph -> R.Hooks (Record Controls) useGraphControls :: SigmaxTypes.SGraph -> R.Hooks (Record Controls)
useGraphControls graph = do useGraphControls graph = do
edgeConfluence <- R.useState' $ Range.Closed { min: 0.0, max: 1.0 } edgeConfluence <- R.useState' $ Range.Closed { min: 0.0, max: 1.0 }
edgeWeight <- R.useState' $ Range.Closed { min: 0.0, max: 1.0 } edgeWeight <- R.useState' $ Range.Closed {
min: 0.0
, max: I.toNumber $ Seq.length $ SigmaxTypes.graphEdges graph
}
forceAtlasState <- R.useState' SigmaxTypes.InitialRunning forceAtlasState <- R.useState' SigmaxTypes.InitialRunning
graphStage <- R.useState' Graph.Init graphStage <- R.useState' Graph.Init
multiSelectEnabled <- R.useState' false multiSelectEnabled <- R.useState' false
......
...@@ -54,7 +54,7 @@ edgeWeightControl (Range.Closed { min, max }) (state /\ setState) = ...@@ -54,7 +54,7 @@ edgeWeightControl (Range.Closed { min, max }) (state /\ setState) =
, sliderProps: { , sliderProps: {
bounds: Range.Closed { min, max } bounds: Range.Closed { min, max }
, initialValue: state , initialValue: state
, epsilon: 0.01 , epsilon: 1.0
, step: 1.0 , step: 1.0
, width: 10.0 , width: 10.0
, height: 5.0 , height: 5.0
......
...@@ -24,11 +24,11 @@ newtype Cluster = Cluster { clustDefault :: Int } ...@@ -24,11 +24,11 @@ newtype Cluster = Cluster { clustDefault :: Int }
derive instance newtypeCluster :: Newtype Cluster _ derive instance newtypeCluster :: Newtype Cluster _
newtype Edge = Edge newtype Edge = Edge
{ id_ :: String { confluence :: Number
, id_ :: String
, source :: String , source :: String
, target :: String , target :: String
, weight :: Number , weight :: Number
, confluence :: Number
} }
derive instance newtypeEdge :: Newtype Edge _ derive instance newtypeEdge :: Newtype Edge _
......
...@@ -53,7 +53,9 @@ type Edge = ...@@ -53,7 +53,9 @@ type Edge =
, sourceNode :: Record Node , sourceNode :: Record Node
, target :: NodeId , target :: NodeId
, targetNode :: Record Node , targetNode :: Record Node
, weight :: Number ) , weight :: Number
, weightIdx :: Int
)
type SelectedNodeIds = Set.Set NodeId type SelectedNodeIds = Set.Set NodeId
type SelectedEdgeIds = Set.Set EdgeId type SelectedEdgeIds = Set.Set EdgeId
......
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