Commit 7b00e9fa authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FEA] Graph options with Links Strength

parent 0487ad41
......@@ -2,7 +2,7 @@ module Gargantext.Components.Forest.Tree.Node.Action.Update where
import Gargantext.Prelude
import Gargantext.Components.Forest.Tree.Node.Action.Update.Types (Charts(..), Granularity(..), GraphMetric(..), Method(..), PartitionMethod(..), UpdateNodeParams(..))
import Gargantext.Components.Forest.Tree.Node.Action.Update.Types (Charts(..), Granularity(..), GraphMetric(..), Method(..), PartitionMethod(..), UpdateNodeParams(..), Strength(..))
import DOM.Simple.Console (log3)
import Data.Either (Either(..))
......@@ -78,6 +78,9 @@ updateGraphCpt = here.component "updateGraph" cpt where
methodGraphMetric <- T.useBox Order1
methodGraphMetric' <- T.useLive T.unequal methodGraphMetric
methodGraphEdgesStrength <- T.useBox Strong
methodGraphEdgesStrength' <- T.useLive T.unequal methodGraphEdgesStrength
methodGraphClustering <- T.useBox Spinglass
methodGraphClustering' <- T.useLive T.unequal methodGraphClustering
......@@ -85,11 +88,18 @@ updateGraphCpt = here.component "updateGraph" cpt where
callback :: Action -> Aff Unit
callback = dispatch >=> \_ -> dispatch ClosePopover
pure $ panel [ -- H.text "Update with"
formChoiceSafe { items: [Order1, Order2]
pure $ panel [ H.text "Show subjects with Order1 or concepts with Order2 ?"
, formChoiceSafe { items: [Order1, Order2]
, default: methodGraphMetric'
, callback: \val -> T.write_ val methodGraphMetric
, print: show } []
, H.text "Show Strong (expected) links or weak (maybe unexpected) links?"
, formChoiceSafe { items: [Strong, Weak]
, default: methodGraphEdgesStrength'
, callback: \val -> T.write_ val methodGraphEdgesStrength
, print: show } []
, formChoiceSafe { items: [Spinglass, Infomap, Confluence]
, default: methodGraphClustering'
, callback: \val -> T.write_ val methodGraphClustering
......@@ -98,6 +108,7 @@ updateGraphCpt = here.component "updateGraph" cpt where
]
(submitButton (UpdateNode $ UpdateNodeParamsGraph { methodGraphMetric: methodGraphMetric'
, methodGraphClustering: methodGraphClustering'
, methodGraphEdgesStrength : methodGraphEdgesStrength'
}
) callback
)
......
......@@ -14,6 +14,7 @@ import Simple.JSON.Generics as JSONG
data UpdateNodeParams
= UpdateNodeParamsList { methodList :: Method }
| UpdateNodeParamsGraph { methodGraphMetric :: GraphMetric
, methodGraphEdgesStrength :: Strength
, methodGraphClustering :: PartitionMethod
}
| UpdateNodeParamsTexts { methodTexts :: Granularity }
......@@ -28,9 +29,9 @@ instance JSON.WriteForeign UpdateNodeParams where
writeImpl (UpdateNodeParamsList { methodList }) =
JSON.writeImpl { type: "UpdateNodeParamsList"
, methodList }
writeImpl (UpdateNodeParamsGraph { methodGraphMetric, methodGraphClustering }) =
writeImpl (UpdateNodeParamsGraph { methodGraphMetric, methodGraphClustering, methodGraphEdgesStrength}) =
JSON.writeImpl { type: "UpdateNodeParamsGraph"
, methodGraphMetric, methodGraphClustering }
, methodGraphMetric, methodGraphClustering, methodGraphEdgesStrength}
writeImpl (UpdateNodeParamsTexts { methodTexts }) =
JSON.writeImpl { type: "UpdateNodeParamsTexts"
, methodTexts }
......@@ -71,6 +72,19 @@ instance Read GraphMetric where
instance JSON.ReadForeign GraphMetric where readImpl = JSONG.enumSumRep
instance JSON.WriteForeign GraphMetric where writeImpl = JSON.writeImpl <<< show
data Strength = Strong | Weak
derive instance Generic Strength _
derive instance Eq Strength
instance Show Strength where show = genericShow
instance Read Strength where
read "Strong" = Just Strong
read "Weak" = Just Weak
read _ = Nothing
instance JSON.ReadForeign Strength where readImpl = JSONG.enumSumRep
instance JSON.WriteForeign Strength where writeImpl = JSON.writeImpl <<< show
data PartitionMethod = Spinglass | Infomap | Confluence
derive instance Generic PartitionMethod _
derive instance Eq PartitionMethod
......
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