Commit b9b42f86 authored by Karen Konou's avatar Karen Konou

[Refactor] Move graph types to graph modules

parent 15a3dfbf
Pipeline #7033 failed with stages
in 4416 minutes and 28 seconds
......@@ -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(..), Strength(..), BridgenessMethod(..), UpdateNodeConfigGraph(..))
import Gargantext.Components.Forest.Tree.Node.Action.Update.Types (Charts(..), Granularity(..), Method(..), UpdateNodeParams(..), UpdateNodeConfigGraph(..))
import DOM.Simple.Console (log3)
import Data.Either (Either(..))
......@@ -16,6 +16,7 @@ import Gargantext.Components.Forest.Tree.Node.Tools as Tools
import Gargantext.Components.PhyloExplorer.API as Phylo
import Gargantext.Components.PhyloExplorer.Config.ConfigForm as PhyloForm
import Gargantext.Components.PhyloExplorer.ConfigFormParser as PhyloHook
import Gargantext.Components.GraphExplorer.Types (GraphMetric(..), Strength(..), PartitionMethod(..), BridgenessMethod(..))
import Gargantext.Config.REST (RESTError, AffRESTError)
import Gargantext.Routes as GR
import Gargantext.Sessions (Session, post)
......
......@@ -5,6 +5,7 @@ import Gargantext.Prelude
import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe(..))
import Data.Show.Generic (genericShow)
import Gargantext.Components.GraphExplorer.Types (BridgenessMethod, GraphMetric, PartitionMethod, Strength)
import Gargantext.Components.PhyloExplorer.API as Phylo
import Gargantext.Types as GT
import Simple.JSON as JSON
......@@ -75,57 +76,6 @@ instance Read Method where
read "WithModel" = Just WithModel
read _ = Nothing
----------------------------------------------------------------------
data GraphMetric = Order1 | Order2
derive instance Generic GraphMetric _
derive instance Eq GraphMetric
instance Show GraphMetric where show = genericShow
instance Read GraphMetric where
read "Order1" = Just Order1
read "Order2" = Just Order2
read _ = Nothing
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
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 = BridgenessMethod_Basic
| BridgenessMethod_Advanced
derive instance Generic BridgenessMethod _
derive instance Eq BridgenessMethod
instance Show BridgenessMethod where show = genericShow
instance Read BridgenessMethod where
read "BridgenessMethod_Basic" = Just BridgenessMethod_Basic
read "BridgenessMethod_Advanced" = Just BridgenessMethod_Advanced
read _ = Nothing
instance JSON.ReadForeign BridgenessMethod where readImpl = JSONG.enumSumRep
instance JSON.WriteForeign BridgenessMethod where writeImpl = JSON.writeImpl <<< show
----------------------------------------------------------------------
......
......@@ -29,6 +29,7 @@ import Gargantext.Components.Bootstrap.Types (ButtonVariant(..), Variant(..))
import Gargantext.Components.Forest.Tree.Node.Action.Upload (uploadArbitraryData)
import Gargantext.Components.Forest.Tree.Node.Action.Upload.Types (FileFormat(..))
import Gargantext.Components.GraphExplorer.API (cloneGraph)
import Gargantext.Components.GraphExplorer.Types (GraphMetric(..))
import Gargantext.Components.GraphExplorer.Types as GET
import Gargantext.Components.GraphExplorer.Utils as GEU
import Gargantext.Data.Louvain as DLouvain
......@@ -219,9 +220,12 @@ louvainButtonCpt = here.component "louvainButton" cpt
corpusId : []
, legend : legend'
, list: { listId : 0, version : 0 }
, metric: "Order1"
, metric: Order1
, startForceAtlas: true
, title : ""
, edgesStrength : Nothing
, partitionMethod : Nothing
, bridgenessMethod : Nothing
}
T.write_ mMetaData'' mMetaData
T.write_ lgraph transformedGraph
......
module Gargantext.Components.GraphExplorer.Types where
import Gargantext.Components.GraphExplorer.GraphTypes
import Gargantext.Prelude
import Data.Array ((!!), length)
import Data.Eq.Generic (genericEq)
import Data.Generic.Rep (class Generic)
......@@ -7,12 +10,11 @@ import Data.Maybe (Maybe(..), fromJust)
import Data.Newtype (class Newtype)
import Data.Ord.Generic (genericCompare)
import Data.Show.Generic (genericShow)
import Gargantext.Components.GraphExplorer.GraphTypes
import Gargantext.Hooks.Sigmax.Camera (Camera)
import Gargantext.Prelude
import Partial.Unsafe (unsafePartial)
import Record as Record
import Simple.JSON as JSON
import Simple.JSON.Generics as JSONG
type GraphId = Int
......@@ -79,9 +81,12 @@ newtype MetaData = MetaData
, list :: { listId :: ListId
, version :: Version
}
, metric :: String -- dummy value
, metric :: GraphMetric -- dummy value
, startForceAtlas :: Boolean
, title :: String
, edgesStrength :: Maybe Strength
, partitionMethod :: Maybe PartitionMethod
, bridgenessMethod :: Maybe BridgenessMethod
}
derive instance Generic MetaData _
derive instance Newtype MetaData _
......@@ -125,12 +130,69 @@ initialGraphData = GraphData {
corpusId : []
, legend : []
, list: { listId : 0, version : 0 }
, metric: "Order1"
, metric: Order1
, startForceAtlas: true
, title : ""
, edgesStrength : Nothing
, partitionMethod : Nothing
, bridgenessMethod : Nothing
}
}
----------------------------------------------------------------------
data GraphMetric = Order1 | Order2
derive instance Generic GraphMetric _
derive instance Eq GraphMetric
instance Show GraphMetric where show = genericShow
instance Read GraphMetric where
read "Order1" = Just Order1
read "Order2" = Just Order2
read _ = Nothing
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
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 = BridgenessMethod_Basic
| BridgenessMethod_Advanced
derive instance Generic BridgenessMethod _
derive instance Eq BridgenessMethod
instance Show BridgenessMethod where show = genericShow
instance Read BridgenessMethod where
read "BridgenessMethod_Basic" = Just BridgenessMethod_Basic
read "BridgenessMethod_Advanced" = Just BridgenessMethod_Advanced
read _ = Nothing
instance JSON.ReadForeign BridgenessMethod where readImpl = JSONG.enumSumRep
instance JSON.WriteForeign BridgenessMethod where writeImpl = JSON.writeImpl <<< show
----------------------------------------------------------------------
newtype Legend = Legend {id_ ::Int , color :: String, label :: String}
derive instance Generic Legend _
......
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