Commit 5d91a271 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[Graph] usability work

NodeSize range is set from graph data.
Search first draft.
parent e77d53ff
...@@ -8,7 +8,6 @@ import Prelude (bind, const, discard, pure, ($), unit) ...@@ -8,7 +8,6 @@ import Prelude (bind, const, discard, pure, ($), unit)
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Nullable (Nullable) import Data.Nullable (Nullable)
import Data.Tuple (fst)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import DOM.Simple.Console (log, log2) import DOM.Simple.Console (log, log2)
import DOM.Simple.Types (Element) import DOM.Simple.Types (Element)
...@@ -22,20 +21,18 @@ import Gargantext.Hooks.Sigmax.Sigma as Sigma ...@@ -22,20 +21,18 @@ import Gargantext.Hooks.Sigmax.Sigma as Sigma
type OnProps = () type OnProps = ()
type Graph = SigmaxTypes.Graph SigmaxTypes.Node SigmaxTypes.Edge
data Stage = Init | Ready | Cleanup data Stage = Init | Ready | Cleanup
type Props sigma forceatlas2 = type Props sigma forceatlas2 =
( elRef :: R.Ref (Nullable Element) ( elRef :: R.Ref (Nullable Element)
, forceAtlas2Settings :: forceatlas2 , forceAtlas2Settings :: forceatlas2
, graph :: Graph , graph :: SigmaxTypes.SGraph
, selectedEdgeIds :: R.State SigmaxTypes.SelectedEdgeIds , selectedEdgeIds :: R.State SigmaxTypes.SelectedEdgeIds
, selectedNodeIds :: R.State SigmaxTypes.SelectedNodeIds , selectedNodeIds :: R.State SigmaxTypes.SelectedNodeIds
, sigmaRef :: R.Ref Sigmax.Sigma , sigmaRef :: R.Ref Sigmax.Sigma
, sigmaSettings :: sigma , sigmaSettings :: sigma
, stage :: R.State Stage , stage :: R.State Stage
, transformedGraph :: Graph , transformedGraph :: SigmaxTypes.SGraph
) )
graph :: forall s fa2. Record (Props s fa2) -> R.Element graph :: forall s fa2. Record (Props s fa2) -> R.Element
...@@ -80,8 +77,8 @@ graphCpt = R.hooksComponent "Graph" cpt ...@@ -80,8 +77,8 @@ graphCpt = R.hooksComponent "Graph" cpt
Sigma.startForceAtlas2 sig props.forceAtlas2Settings Sigma.startForceAtlas2 sig props.forceAtlas2Settings
-- bind the click event only initially, when ref was empty -- bind the click event only initially, when ref was empty
Sigmax.bindSelectedNodesClick props.sigmaRef props.selectedNodeIds Sigmax.bindSelectedNodesClick props.sigmaRef props.selectedNodeIds props.selectedEdgeIds props.graph
Sigmax.bindSelectedEdgesClick props.sigmaRef props.selectedEdgeIds --Sigmax.bindSelectedEdgesClick props.sigmaRef props.selectedEdgeIds
Just sig -> do Just sig -> do
pure unit pure unit
......
...@@ -6,7 +6,7 @@ import Data.FoldableWithIndex (foldMapWithIndex) ...@@ -6,7 +6,7 @@ import Data.FoldableWithIndex (foldMapWithIndex)
import Data.Foldable (foldMap) import Data.Foldable (foldMap)
import Data.Int (toNumber) import Data.Int (toNumber)
import Data.Map as Map import Data.Map as Map
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..), fromJust)
import Data.Nullable (null, Nullable) import Data.Nullable (null, Nullable)
import Data.Sequence as Seq import Data.Sequence as Seq
import Data.Set as Set import Data.Set as Set
...@@ -15,9 +15,10 @@ import Data.Tuple.Nested ((/\)) ...@@ -15,9 +15,10 @@ import Data.Tuple.Nested ((/\))
-- import DOM.Simple.Console (log2) -- import DOM.Simple.Console (log2)
import DOM.Simple.Types (Element) import DOM.Simple.Types (Element)
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Math (log)
import Partial.Unsafe (unsafePartial)
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as RH import Reactix.DOM.HTML as RH
import Math (log)
import Gargantext.Hooks.Loader (useLoader) import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Hooks.Sigmax as Sigmax import Gargantext.Hooks.Sigmax as Sigmax
...@@ -47,7 +48,7 @@ type LayoutProps = ...@@ -47,7 +48,7 @@ type LayoutProps =
) )
type Props = ( type Props = (
graph :: Graph.Graph graph :: SigmaxTypes.SGraph
, mMetaData :: Maybe GET.MetaData , mMetaData :: Maybe GET.MetaData
| LayoutProps | LayoutProps
) )
...@@ -150,7 +151,7 @@ explorerCpt = R.hooksComponent "G.C.GraphExplorer.explorer" cpt ...@@ -150,7 +151,7 @@ explorerCpt = R.hooksComponent "G.C.GraphExplorer.explorer" cpt
RH.div {className: "col-md-2", style: {paddingTop: "60px"}} RH.div {className: "col-md-2", style: {paddingTop: "60px"}}
[forest {sessions, route, frontends, showLogin}] [forest {sessions, route, frontends, showLogin}]
mSidebar :: Graph.Graph mSidebar :: SigmaxTypes.SGraph
-> Maybe GET.MetaData -> Maybe GET.MetaData
-> { frontends :: Frontends -> { frontends :: Frontends
, showSidePanel :: GET.SidePanelState , showSidePanel :: GET.SidePanelState
...@@ -171,7 +172,7 @@ type GraphProps = ( ...@@ -171,7 +172,7 @@ type GraphProps = (
controls :: Record Controls.Controls controls :: Record Controls.Controls
, elRef :: R.Ref (Nullable Element) , elRef :: R.Ref (Nullable Element)
, graphId :: GraphId , graphId :: GraphId
, graph :: Graph.Graph , graph :: SigmaxTypes.SGraph
, graphStage :: R.State Graph.Stage , graphStage :: R.State Graph.Stage
, selectedNodeIds :: R.State SigmaxTypes.SelectedNodeIds , selectedNodeIds :: R.State SigmaxTypes.SelectedNodeIds
, selectedEdgeIds :: R.State SigmaxTypes.SelectedEdgeIds , selectedEdgeIds :: R.State SigmaxTypes.SelectedEdgeIds
...@@ -200,7 +201,7 @@ graphView props = R.createElement el props [] ...@@ -200,7 +201,7 @@ graphView props = R.createElement el props []
, transformedGraph , transformedGraph
} }
convert :: GET.GraphData -> Tuple (Maybe GET.MetaData) Graph.Graph convert :: GET.GraphData -> Tuple (Maybe GET.MetaData) SigmaxTypes.SGraph
convert (GET.GraphData r) = Tuple r.metaData $ SigmaxTypes.Graph {nodes, edges} convert (GET.GraphData r) = Tuple r.metaData $ SigmaxTypes.Graph {nodes, edges}
where where
nodes = foldMapWithIndex nodeFn r.nodes nodes = foldMapWithIndex nodeFn r.nodes
...@@ -359,23 +360,29 @@ getNodes :: Session -> GraphId -> Aff GET.GraphData ...@@ -359,23 +360,29 @@ getNodes :: Session -> GraphId -> Aff GET.GraphData
getNodes session graphId = get session $ NodeAPI Graph (Just graphId) "" getNodes session graphId = get session $ NodeAPI Graph (Just graphId) ""
transformGraph :: Record Controls.Controls -> Graph.Graph -> Graph.Graph transformGraph :: Record Controls.Controls -> SigmaxTypes.SGraph -> SigmaxTypes.SGraph
transformGraph controls graph@(SigmaxTypes.Graph {nodes, edges}) = SigmaxTypes.Graph {nodes: newNodes, edges: newEdges} transformGraph controls graph = SigmaxTypes.Graph {nodes: newNodes, edges: newEdges}
where where
edges = SigmaxTypes.graphEdges graph
nodes = SigmaxTypes.graphNodes graph
graphEdgesMap = SigmaxTypes.edgesGraphMap graph graphEdgesMap = SigmaxTypes.edgesGraphMap graph
graphNodesMap = SigmaxTypes.nodesGraphMap graph graphNodesMap = SigmaxTypes.nodesGraphMap graph
newNodes = nodeSizes <$> nodeMarked <$> nodes newNodes = nodeSizes <$> nodeMarked <$> nodes
newEdges = edgeMarked <$> edges newEdges = edgeMarked <$> edges
hasSelection = not $ Set.isEmpty (fst controls.selectedNodeIds)
nodeSizes node@{ size } = nodeSizes node@{ size } =
if Range.within (fst controls.nodeSize) size then if Range.within (fst controls.nodeSize) size then
node node
else else
node { hidden = true } node { hidden = true }
edgeMarked edge@{ id } = edgeMarked edge@{ id } = do
if Set.member id (fst controls.selectedEdgeIds) then let isSelected = Set.member id (fst controls.selectedEdgeIds)
edge { color = "#ff0000" } let sourceNode = Map.lookup edge.source graphNodesMap
else case Tuple hasSelection isSelected of
edge Tuple false true -> edge { color = "#ff0000" }
Tuple true true -> edge { color = (unsafePartial $ fromJust sourceNode).color }
Tuple true false -> edge { color = "#dddddd" }
_ -> edge
nodeMarked node@{ id } = nodeMarked node@{ id } =
if Set.member id (fst controls.selectedNodeIds) then if Set.member id (fst controls.selectedNodeIds) then
node { color = "#ff0000" } node { color = "#ff0000" }
......
...@@ -10,7 +10,9 @@ module Gargantext.Components.GraphExplorer.Controls ...@@ -10,7 +10,9 @@ module Gargantext.Components.GraphExplorer.Controls
, getMultiNodeSelect, setMultiNodeSelect , getMultiNodeSelect, setMultiNodeSelect
) where ) where
import Data.Maybe (Maybe(..)) import Data.Array as A
import Data.Maybe (Maybe(..), maybe)
import Data.Sequence as Seq
import Data.Set as Set import Data.Set as Set
import Data.Tuple (fst, snd) import Data.Tuple (fst, snd)
import Data.Tuple.Nested ((/\), get1) import Data.Tuple.Nested ((/\), get1)
...@@ -34,7 +36,7 @@ import Gargantext.Utils.Reactix as R2 ...@@ -34,7 +36,7 @@ import Gargantext.Utils.Reactix as R2
type Controls = type Controls =
( cursorSize :: R.State Number ( cursorSize :: R.State Number
, graph :: Graph.Graph , graph :: SigmaxTypes.SGraph
, graphStage :: R.State Graph.Stage , graphStage :: R.State Graph.Stage
, multiNodeSelect :: R.Ref Boolean , multiNodeSelect :: R.Ref Boolean
, nodeSize :: R.State Range.NumberRange , nodeSize :: R.State Range.NumberRange
...@@ -110,6 +112,11 @@ controlsCpt = R.hooksComponent "GraphControls" cpt ...@@ -110,6 +112,11 @@ controlsCpt = R.hooksComponent "GraphControls" cpt
R.setRef mFAPauseRef $ Just timeoutId R.setRef mFAPauseRef $ Just timeoutId
pure unit pure unit
let nodesSorted = A.sortWith (_.size) $ Seq.toUnfoldable $ SigmaxTypes.graphNodes props.graph
let nodeSizeMin = maybe 0.0 _.size $ A.head nodesSorted
let nodeSizeMax = maybe 100.0 _.size $ A.last nodesSorted
let nodeSizeRange = Range.Closed { min: nodeSizeMin, max: nodeSizeMax }
pure $ case getShowControls props of pure $ case getShowControls props of
false -> RH.div {} [] false -> RH.div {} []
true -> RH.div { className: "col-md-12", style: { paddingBottom: "10px" } } true -> RH.div { className: "col-md-12", style: { paddingBottom: "10px" } }
...@@ -127,7 +134,7 @@ controlsCpt = R.hooksComponent "GraphControls" cpt ...@@ -127,7 +134,7 @@ controlsCpt = R.hooksComponent "GraphControls" cpt
-- search topics -- search topics
, RH.li {} [ cursorSizeButton props.cursorSize ] -- cursor size: 0-100 , RH.li {} [ cursorSizeButton props.cursorSize ] -- cursor size: 0-100
, RH.li {} [ labelSizeButton props.sigmaRef localControls.labelSize ] -- labels size: 1-4 , RH.li {} [ labelSizeButton props.sigmaRef localControls.labelSize ] -- labels size: 1-4
, RH.li {} [ nodeSizeControl props.nodeSize ] , RH.li {} [ nodeSizeControl nodeSizeRange props.nodeSize ]
-- zoom: 0 -100 - calculate ratio -- zoom: 0 -100 - calculate ratio
-- toggle multi node selection -- toggle multi node selection
-- save button -- save button
...@@ -136,12 +143,15 @@ controlsCpt = R.hooksComponent "GraphControls" cpt ...@@ -136,12 +143,15 @@ controlsCpt = R.hooksComponent "GraphControls" cpt
] ]
] ]
useGraphControls :: Graph.Graph -> R.Hooks (Record Controls) useGraphControls :: SigmaxTypes.SGraph -> R.Hooks (Record Controls)
useGraphControls graph = do useGraphControls graph = do
let edges = SigmaxTypes.graphEdges graph
let nodes = SigmaxTypes.graphNodes graph
cursorSize <- R.useState' 10.0 cursorSize <- R.useState' 10.0
graphStage <- R.useState' Graph.Init graphStage <- R.useState' Graph.Init
multiNodeSelect <- R.useRef false multiNodeSelect <- R.useRef false
nodeSize <- R.useState' $ Range.Closed { min: 0.0, max: 10.0 } nodeSize <- R.useState' $ Range.Closed { min: 0.0, max: 100.0 }
showTree <- R.useState' false showTree <- R.useState' false
selectedNodeIds <- R.useState' $ Set.empty selectedNodeIds <- R.useState' $ Set.empty
selectedEdgeIds <- R.useState' $ Set.empty selectedEdgeIds <- R.useState' $ Set.empty
......
...@@ -55,12 +55,12 @@ edgeSizeControl sigmaRef (state /\ setState) = ...@@ -55,12 +55,12 @@ edgeSizeControl sigmaRef (state /\ setState) =
} }
} }
nodeSizeControl :: R.State Range.NumberRange -> R.Element nodeSizeControl :: Range.NumberRange -> R.State Range.NumberRange -> R.Element
nodeSizeControl (state /\ setState) = nodeSizeControl (Range.Closed { min: rangeMin, max: rangeMax }) (state /\ setState) =
rangeControl { rangeControl {
caption: "Node Size" caption: "Node Size"
, sliderProps: { , sliderProps: {
bounds: Range.Closed { min: 0.0, max: 15.0 } bounds: Range.Closed { min: rangeMin, max: rangeMax }
, initialValue: state , initialValue: state
, epsilon: 0.1 , epsilon: 0.1
, step: 1.0 , step: 1.0
......
module Gargantext.Components.GraphExplorer.Search
( Props
, nodeSearchControl
) where
import Global (readFloat)
import Prelude
import Data.Set as Set
import Data.Tuple (snd)
import Data.Tuple.Nested ((/\))
import DOM.Simple.Console (log2)
import Effect (Effect)
import FFI.Simple ((..))
import Reactix as R
import Reactix.DOM.HTML as H
import Gargantext.Hooks.Sigmax as Sigmax
import Gargantext.Hooks.Sigmax.Sigma as Sigma
import Gargantext.Hooks.Sigmax.Types as SigmaxTypes
import Gargantext.Utils.Reactix as R2
type Props = (
selectedNodeIds :: R.State SigmaxTypes.SelectedNodeIds
)
nodeSearchControl :: Record Props -> R.Element
nodeSearchControl props = R.createElement sizeButtonCpt props []
sizeButtonCpt :: R.Component Props
sizeButtonCpt = R.hooksComponent "NodeSearchControl" cpt
where
cpt {selectedNodeIds} _ = do
(search /\ setSearch) <- R.useState' ""
pure $
H.span {}
[ H.input { type: "text"
, className: "form-control"
, defaultValue: search
, on: { input: \e -> setSearch $ const $ e .. "target" .. "value" }
}
, H.button { className: "btn btn-primary"
, on: { click: \_ -> log2 "[sizeButtonCpt] search" search }} [ H.text "Search" ]
]
-- TODO Wherefrom do I get graph nodes?
-- How to implement filtering here? I want to set selectedNodeIds based on graph data.
...@@ -14,7 +14,6 @@ import Reactix.DOM.HTML as RH ...@@ -14,7 +14,6 @@ import Reactix.DOM.HTML as RH
import Gargantext.Data.Array (catMaybes) import Gargantext.Data.Array (catMaybes)
import Gargantext.Components.RandomText (words) import Gargantext.Components.RandomText (words)
import Gargantext.Components.Nodes.Corpus.Graph.Tabs as GT import Gargantext.Components.Nodes.Corpus.Graph.Tabs as GT
import Gargantext.Components.Graph as Graph
import Gargantext.Components.GraphExplorer.Types as GET import Gargantext.Components.GraphExplorer.Types as GET
import Gargantext.Ends (Frontends) import Gargantext.Ends (Frontends)
import Gargantext.Hooks.Sigmax.Types as SigmaxTypes import Gargantext.Hooks.Sigmax.Types as SigmaxTypes
...@@ -22,7 +21,7 @@ import Gargantext.Sessions (Session) ...@@ -22,7 +21,7 @@ import Gargantext.Sessions (Session)
type Props = type Props =
( frontends :: Frontends ( frontends :: Frontends
, graph :: Graph.Graph , graph :: SigmaxTypes.SGraph
, metaData :: GET.MetaData , metaData :: GET.MetaData
, selectedNodeIds :: R.State SigmaxTypes.SelectedNodeIds , selectedNodeIds :: R.State SigmaxTypes.SelectedNodeIds
, session :: Session , session :: Session
......
...@@ -88,7 +88,7 @@ type State = ( ...@@ -88,7 +88,7 @@ type State = (
--, showSidePanel :: R.State Boolean --, showSidePanel :: R.State Boolean
--, showControls :: R.State Boolean --, showControls :: R.State Boolean
--, showTree :: R.State Boolean --, showTree :: R.State Boolean
--, sigmaGraphData :: R.State (Maybe Graph.Graph) --, sigmaGraphData :: R.State (Maybe SigmaxTypes.SGraph)
--, sigmaSettings :: R.State ({|Graph.SigmaSettings}) --, sigmaSettings :: R.State ({|Graph.SigmaSettings})
--treeId :: R.State (Maybe TreeId) --treeId :: R.State (Maybe TreeId)
) )
......
module Gargantext.Hooks.Sigmax module Gargantext.Hooks.Sigmax
where where
import Prelude (Unit, bind, discard, flip, pure, unit, ($), (*>), (<<<), (<>), (>>=), (||), not, const, map)
import Data.Array as A import Data.Array as A
import Data.Either (either) import Data.Either (either)
import Data.Foldable (sequence_) import Data.Foldable (sequence_)
...@@ -20,9 +22,8 @@ import Effect.Class.Console (error) ...@@ -20,9 +22,8 @@ import Effect.Class.Console (error)
import Effect.Timer (TimeoutId, clearTimeout) import Effect.Timer (TimeoutId, clearTimeout)
import FFI.Simple ((.=)) import FFI.Simple ((.=))
import Gargantext.Hooks.Sigmax.Sigma as Sigma import Gargantext.Hooks.Sigmax.Sigma as Sigma
import Gargantext.Hooks.Sigmax.Types (Graph(..), EdgesMap, NodesMap, SelectedNodeIds, SelectedEdgeIds) import Gargantext.Hooks.Sigmax.Types (Graph(..), SGraph, EdgesMap, NodesMap, SelectedNodeIds, SelectedEdgeIds)
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Prelude (Unit, bind, discard, flip, pure, unit, ($), (*>), (<<<), (<>), (>>=), not)
import Reactix as R import Reactix as R
type Sigma = type Sigma =
...@@ -209,15 +210,16 @@ updateNodes sigma nodesMap = do ...@@ -209,15 +210,16 @@ updateNodes sigma nodesMap = do
Sigma.refresh sigma Sigma.refresh sigma
bindSelectedNodesClick :: R.Ref Sigma -> R.State SelectedNodeIds -> Effect Unit bindSelectedNodesClick :: R.Ref Sigma -> R.State SelectedNodeIds -> R.State SelectedEdgeIds -> SGraph -> Effect Unit
bindSelectedNodesClick sigmaRef (_ /\ setSelectedNodeIds) = bindSelectedNodesClick sigmaRef (_ /\ setSelectedNodeIds) (_ /\ setSelectedEdgeIds) (Graph {edges, nodes}) =
dependOnSigma (R.readRef sigmaRef) "[graphCpt] no sigma" $ \sigma -> do dependOnSigma (R.readRef sigmaRef) "[graphCpt] no sigma" $ \sigma -> do
Sigma.bindClickNode sigma $ \node -> do Sigma.bindClickNodes sigma $ \nodes -> do
setSelectedNodeIds \nids -> let nodeIds = Set.fromFoldable $ map _.id nodes
if Set.member node.id nids then setSelectedNodeIds $ const nodeIds
Set.delete node.id nids setSelectedEdgeIds \_ ->
else Set.fromFoldable
Set.insert node.id nids $ Seq.map _.id
$ Seq.filter (\e -> Set.member e.source nodeIds) edges
bindSelectedEdgesClick :: R.Ref Sigma -> R.State SelectedEdgeIds -> Effect Unit bindSelectedEdgesClick :: R.Ref Sigma -> R.State SelectedEdgeIds -> Effect Unit
bindSelectedEdgesClick sigmaRef (_ /\ setSelectedEdgeIds) = bindSelectedEdgesClick sigmaRef (_ /\ setSelectedEdgeIds) =
......
...@@ -142,6 +142,11 @@ bindClickNode s f = bind_ s "clickNode" $ \e -> do ...@@ -142,6 +142,11 @@ bindClickNode s f = bind_ s "clickNode" $ \e -> do
unbindClickNode :: Sigma -> Effect Unit unbindClickNode :: Sigma -> Effect Unit
unbindClickNode s = unbind_ s "clickNode" unbindClickNode s = unbind_ s "clickNode"
bindClickNodes :: Sigma -> (Array (Record Types.Node) -> Effect Unit) -> Effect Unit
bindClickNodes s f = bind_ s "clickNodes" $ \e -> do
let nodes = e .. "data" .. "node" :: Array (Record Types.Node)
f nodes
bindOverNode :: Sigma -> (Record Types.Node -> Effect Unit) -> Effect Unit bindOverNode :: Sigma -> (Record Types.Node -> Effect Unit) -> Effect Unit
bindOverNode s f = bind_ s "overNode" $ \e -> do bindOverNode s f = bind_ s "overNode" $ \e -> do
let node = e .. "data" .. "node" :: Record Types.Node let node = e .. "data" .. "node" :: Record Types.Node
......
module Gargantext.Hooks.Sigmax.Types where module Gargantext.Hooks.Sigmax.Types where
import Prelude (map, ($), (&&), (==)) import Prelude (map, ($), (&&), (==), class Ord, Ordering, compare)
import Data.Map as Map import Data.Map as Map
import Data.Sequence (Seq) import Data.Sequence (Seq)
import Data.Set as Set import Data.Set as Set
...@@ -39,6 +39,14 @@ type SelectedEdgeIds = Set.Set String ...@@ -39,6 +39,14 @@ type SelectedEdgeIds = Set.Set String
type EdgesMap = Map.Map String (Record Edge) type EdgesMap = Map.Map String (Record Edge)
type NodesMap = Map.Map String (Record Node) type NodesMap = Map.Map String (Record Node)
type SGraph = Graph Node Edge
graphEdges :: SGraph -> Seq (Record Edge)
graphEdges (Graph {edges}) = edges
graphNodes :: SGraph -> Seq (Record Node)
graphNodes (Graph {nodes}) = nodes
edgesGraphMap :: Graph Node Edge -> EdgesMap edgesGraphMap :: Graph Node Edge -> EdgesMap
edgesGraphMap graph = do edgesGraphMap graph = do
let (Graph {edges}) = graph let (Graph {edges}) = graph
......
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