Commit 60629353 authored by Grégoire Locqueville's avatar Grégoire Locqueville

Add option for intercluster filtering method

Also remove the "partition method" parameter for graphs, which has
no effect
parent 2e43c474
Pipeline #7309 passed with stages
in 21 minutes and 33 seconds
...@@ -2,8 +2,6 @@ module Gargantext.Components.Forest.Tree.Node.Action.Update where ...@@ -2,8 +2,6 @@ module Gargantext.Components.Forest.Tree.Node.Action.Update where
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Components.Forest.Tree.Node.Action.Update.Types (Charts(..), Granularity(..), GraphMetric(..), Method(..), PartitionMethod(..), UpdateNodeParams(..), Strength(..), BridgenessMethod(..), UpdateNodeConfigGraph(..))
import DOM.Simple.Console (log3) import DOM.Simple.Console (log3)
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
...@@ -13,11 +11,12 @@ import Gargantext.AsyncTasks as GAT ...@@ -13,11 +11,12 @@ import Gargantext.AsyncTasks as GAT
import Gargantext.Components.Bootstrap as B import Gargantext.Components.Bootstrap as B
import Gargantext.Components.Bootstrap.Types (ComponentStatus(..)) import Gargantext.Components.Bootstrap.Types (ComponentStatus(..))
import Gargantext.Components.Forest.Tree.Node.Action.Types (Action(..)) import Gargantext.Components.Forest.Tree.Node.Action.Types (Action(..))
import Gargantext.Components.Forest.Tree.Node.Action.Update.Types (BridgenessMethod(..), Charts(..), Granularity(..), GraphMetric(..), Method(..), Strength(..), UpdateNodeConfigGraph(..), UpdateNodeParams(..))
import Gargantext.Components.Forest.Tree.Node.Tools as Tools import Gargantext.Components.Forest.Tree.Node.Tools as Tools
import Gargantext.Components.PhyloExplorer.API as Phylo import Gargantext.Components.PhyloExplorer.API as Phylo
import Gargantext.Components.PhyloExplorer.Config.ConfigForm as PhyloForm import Gargantext.Components.PhyloExplorer.Config.ConfigForm as PhyloForm
import Gargantext.Components.PhyloExplorer.ConfigFormParser as PhyloHook import Gargantext.Components.PhyloExplorer.ConfigFormParser as PhyloHook
import Gargantext.Config.REST (RESTError, AffRESTError) import Gargantext.Config.REST (AffRESTError)
import Gargantext.Routes as GR import Gargantext.Routes as GR
import Gargantext.Sessions (Session, post) import Gargantext.Sessions (Session, post)
import Gargantext.Types (ID, NodeType(..)) import Gargantext.Types (ID, NodeType(..))
...@@ -104,10 +103,7 @@ updateGraphCpt = here.component "updateGraph" cpt ...@@ -104,10 +103,7 @@ updateGraphCpt = here.component "updateGraph" cpt
methodGraphNodeType2 <- T.useBox GT.CTabTerms methodGraphNodeType2 <- T.useBox GT.CTabTerms
methodGraphNodeType2' <- T.useLive T.unequal methodGraphNodeType2 methodGraphNodeType2' <- T.useLive T.unequal methodGraphNodeType2
methodGraphClustering <- T.useBox Spinglass methodGraphBridgeness <- T.useBox BridgenessBasic
methodGraphClustering' <- T.useLive T.unequal methodGraphClustering
methodGraphBridgeness <- T.useBox BridgenessMethod_Basic
methodGraphBridgeness' <- T.useLive T.unequal methodGraphBridgeness methodGraphBridgeness' <- T.useLive T.unequal methodGraphBridgeness
let let
...@@ -117,7 +113,6 @@ updateGraphCpt = here.component "updateGraph" cpt ...@@ -117,7 +113,6 @@ updateGraphCpt = here.component "updateGraph" cpt
let let
config = UpdateNodeConfigGraph config = UpdateNodeConfigGraph
{ methodGraphMetric: methodGraphMetric' { methodGraphMetric: methodGraphMetric'
, methodGraphClustering: methodGraphClustering'
, methodGraphBridgeness: methodGraphBridgeness' , methodGraphBridgeness: methodGraphBridgeness'
, methodGraphEdgesStrength: methodGraphEdgesStrength' , methodGraphEdgesStrength: methodGraphEdgesStrength'
, methodGraphNodeType1: methodGraphNodeType1' , methodGraphNodeType1: methodGraphNodeType1'
...@@ -141,43 +136,16 @@ updateGraphCpt = here.component "updateGraph" cpt ...@@ -141,43 +136,16 @@ updateGraphCpt = here.component "updateGraph" cpt
, label: "Show subjects with Order1 or concepts with Order2 ?" , label: "Show subjects with Order1 or concepts with Order2 ?"
} }
[] []
, Tools.formChoiceSafe
{ items: [ BridgenessBasic, BridgenessAdvanced ]
, default: methodGraphBridgeness'
, callback: \val -> T.write_ val methodGraphBridgeness
, print: show
, label: "Intercluster link filtering method"
}
[]
] ]
{-
, H.text "Bridgness Method : Basic is ok, Advanced in Development"
, formChoiceSafe { items: [BridgenessMethod_Basic, BridgenessMethod_Advanced]
, default: methodGraphBridgeness'
, callback: \val -> T.write_ val methodGraphBridgeness
, print: show } []
, H.text "NodeType 1 ?"
, formChoiceSafe { items: [GT.CTabTerms, GT.CTabSources, GT.CTabAuthors, GT.CTabInstitutes]
, default: methodGraphNodeType1'
, callback: \val -> T.write_ val methodGraphNodeType1
, print: show } []
, H.text "Ngrams ?"
, formChoiceSafe { items: [GT.CTabTerms, GT.CTabSources, GT.CTabAuthors, GT.CTabInstitutes]
, default: methodGraphNodeType2'
, callback: \val -> T.write_ val methodGraphNodeType2
, 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
, print: show } []
-}
updatePhylo :: R2.Leaf UpdateProps updatePhylo :: R2.Leaf UpdateProps
updatePhylo = R2.leaf updatePhyloCpt updatePhylo = R2.leaf updatePhyloCpt
...@@ -246,37 +214,6 @@ updateCorpusCpt = here.component "updateTexts" cpt ...@@ -246,37 +214,6 @@ updateCorpusCpt = here.component "updateTexts" cpt
methodList <- T.useBox Basic methodList <- T.useBox Basic
methodList' <- T.useLive T.unequal methodList methodList' <- T.useLive T.unequal methodList
-- method for graph metric
methodGraphMetric <- T.useBox Order1
methodGraphMetric' <- T.useLive T.unequal methodGraphMetric
let
graphConfig = UpdateNodeConfigGraph
{ methodGraphMetric: methodGraphMetric'
, methodGraphEdgesStrength: Strong
, methodGraphClustering: Spinglass
, methodGraphBridgeness: BridgenessMethod_Basic
, methodGraphNodeType1: GT.CTabTerms
, methodGraphNodeType2: GT.CTabTerms
}
let
phyloConfig = Phylo.UpdateData
{ defaultMode: true
, proximity: 0.5
, synchrony: 0.5
, quality: 0.8
, exportFilter: 3.0
, timeUnit: Phylo.Year $ Phylo.TimeUnitCriteria
{ period: 3
, step: 1
, matchingFrame: 5
}
, clique: Phylo.MaxClique
{ size: 5
, threshold: 0.0001
, filter: Phylo.ByThreshold
}
}
let methodTexts = Both let methodTexts = Both
pure $ pure $
...@@ -354,13 +291,7 @@ updateTextsCpt = here.component "updateTexts" cpt ...@@ -354,13 +291,7 @@ updateTextsCpt = here.component "updateTexts" cpt
, iconName: "reload-with-settings" , iconName: "reload-with-settings"
, textTitle: "Update documents (contexts)" , textTitle: "Update documents (contexts)"
} }
[] -- H.text "Update with" []
-- formChoiceSafe { items: [NewNgrams, NewTexts, Both]
-- , default: methodTexts'
-- , callback: \val -> T.write_ val methodTexts
-- , print: show } []
-- (submitButton (UpdateNode $ UpdateNodeParamsTexts { methodTexts: methodTexts' }) dispatch)
updateOther :: R2.Component UpdateProps updateOther :: R2.Component UpdateProps
updateOther = R.createElement updateOtherCpt updateOther = R.createElement updateOtherCpt
...@@ -370,5 +301,3 @@ updateOtherCpt = here.component "updateOther" cpt ...@@ -370,5 +301,3 @@ updateOtherCpt = here.component "updateOther" cpt
where where
cpt _ _ = do cpt _ _ = do
pure $ H.div {} [] pure $ H.div {} []
-- fragmentPT $ "Update " <> show nodeType
...@@ -13,7 +13,6 @@ import Simple.JSON.Generics as JSONG ...@@ -13,7 +13,6 @@ import Simple.JSON.Generics as JSONG
newtype UpdateNodeConfigGraph = UpdateNodeConfigGraph newtype UpdateNodeConfigGraph = UpdateNodeConfigGraph
{ methodGraphMetric :: GraphMetric { methodGraphMetric :: GraphMetric
, methodGraphEdgesStrength :: Strength , methodGraphEdgesStrength :: Strength
, methodGraphClustering :: PartitionMethod
, methodGraphBridgeness :: BridgenessMethod , methodGraphBridgeness :: BridgenessMethod
, methodGraphNodeType1 :: GT.CTabNgramType , methodGraphNodeType1 :: GT.CTabNgramType
, methodGraphNodeType2 :: GT.CTabNgramType , methodGraphNodeType2 :: GT.CTabNgramType
...@@ -143,28 +142,9 @@ instance JSON.ReadForeign Strength where ...@@ -143,28 +142,9 @@ instance JSON.ReadForeign Strength where
instance JSON.WriteForeign Strength where instance JSON.WriteForeign Strength where
writeImpl = JSON.writeImpl <<< show writeImpl = JSON.writeImpl <<< show
data PartitionMethod = Spinglass | Infomap | Confluence
derive instance Generic PartitionMethod _
derive instance Eq PartitionMethod
instance Show PartitionMethod where
show = genericShow
instance Read PartitionMethod where
read "Spinglass" = Just Spinglass
read "Confluence" = Just Confluence
read "Infomap" = Just Infomap
read _ = Nothing
instance JSON.ReadForeign PartitionMethod where
readImpl = JSONG.enumSumRep
instance JSON.WriteForeign PartitionMethod where
writeImpl = JSON.writeImpl <<< show
data BridgenessMethod data BridgenessMethod
= BridgenessMethod_Basic = BridgenessBasic
| BridgenessMethod_Advanced | BridgenessAdvanced
derive instance Generic BridgenessMethod _ derive instance Generic BridgenessMethod _
derive instance Eq BridgenessMethod derive instance Eq BridgenessMethod
...@@ -172,8 +152,8 @@ instance Show BridgenessMethod where ...@@ -172,8 +152,8 @@ instance Show BridgenessMethod where
show = genericShow show = genericShow
instance Read BridgenessMethod where instance Read BridgenessMethod where
read "BridgenessMethod_Basic" = Just BridgenessMethod_Basic read "BridgenessBasic" = Just BridgenessBasic
read "BridgenessMethod_Advanced" = Just BridgenessMethod_Advanced read "BridgenessAdvanced" = Just BridgenessAdvanced
read _ = Nothing read _ = Nothing
instance JSON.ReadForeign BridgenessMethod where instance JSON.ReadForeign BridgenessMethod where
......
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