[graph] some refactoring of Core.Viz.Graph

parent ce1cc37a
Pipeline #3604 failed with stage
in 53 minutes and 46 seconds
cabal-version: 1.12
-- This file has been generated from package.yaml by hpack version 0.35.1.
-- This file has been generated from package.yaml by hpack version 0.34.7.
--
-- see: https://github.com/sol/hpack
name: gargantext
version: 0.0.6.9.1
version: 0.0.6.9.1
synopsis: Search, map, share
description: Please see README.md
category: Data
......@@ -232,6 +232,7 @@ library
Gargantext.Core.Viz.Graph.FGL
Gargantext.Core.Viz.Graph.GEXF
Gargantext.Core.Viz.Graph.Legend
Gargantext.Core.Viz.Graph.PatriciaTreeTypes
Gargantext.Core.Viz.Graph.Tools.Infomap
Gargantext.Core.Viz.Graph.Types
Gargantext.Core.Viz.Graph.Utils
......
......@@ -184,7 +184,7 @@ toHyperdataRowDocumentGQL hyperdata =
, hrd_uniqId = _hr_uniqId
, hrd_uniqIdBdd = _hr_uniqIdBdd
}
HyperdataRowContact _ _ _ -> Nothing
HyperdataRowContact { } -> Nothing
updateNodeContextCategory :: (HasConnectionPool env, HasConfig env, HasMail env, HasSettings env) =>
NodeContextCategoryMArgs -> GqlM' e env [Int]
......
......@@ -29,9 +29,9 @@ import Gargantext.API.Ngrams.List (reIndexWith)
import Gargantext.API.Prelude (GargM, GargError, simuLogs)
import Gargantext.Core.Methods.Similarities (GraphMetric(..))
import Gargantext.Core.Types.Main (ListType(..))
import Gargantext.Core.Viz.Graph (Strength)
import Gargantext.Core.Viz.Graph.API (recomputeGraph)
import Gargantext.Core.Viz.Graph.Tools (PartitionMethod(..), BridgenessMethod(..))
import Gargantext.Core.Viz.Graph.Types (Strength)
import Gargantext.Core.Viz.Phylo (PhyloSubConfig(..), subConfig2config)
import Gargantext.Core.Viz.Phylo.API.Tools (flowPhyloAPI)
import Gargantext.Database.Action.Flow.Pairing (pairing)
......
......@@ -14,4 +14,3 @@ Vizualisation of text stats
module Gargantext.Core.Viz
where
This diff is collapsed.
......@@ -30,9 +30,9 @@ import Gargantext.API.Prelude
import Gargantext.Core.Methods.Similarities (Similarity(..), GraphMetric(..), withMetric)
import Gargantext.Core.NodeStory
import Gargantext.Core.Types.Main
import Gargantext.Core.Viz.Graph
import Gargantext.Core.Viz.Graph.GEXF ()
import Gargantext.Core.Viz.Graph.Tools -- (cooc2graph)
import Gargantext.Core.Viz.Graph.Types
import Gargantext.Database.Action.Metrics.NgramsByContext (getContextsByNgramsOnlyUser)
import Gargantext.Database.Action.Flow.Types (FlowCmdM)
import Gargantext.Database.Action.Node (mkNodeWithParent)
......
......@@ -19,18 +19,17 @@ module Gargantext.Core.Viz.Graph.GEXF
where
import Gargantext.Prelude
import Gargantext.Core.Viz.Graph
import qualified Data.HashMap.Lazy as HashMap
import qualified Gargantext.Prelude as P
import qualified Gargantext.Core.Viz.Graph as G
import qualified Gargantext.Core.Viz.Graph.Types as G
import qualified Xmlbf as Xmlbf
import Prelude (error)
-- Converts to GEXF format
-- See https://gephi.org/gexf/format/
instance Xmlbf.ToXml Graph where
toXml (Graph { _graph_nodes = graphNodes
, _graph_edges = graphEdges }) = root graphNodes graphEdges
instance Xmlbf.ToXml G.Graph where
toXml (G.Graph { _graph_nodes = graphNodes
, _graph_edges = graphEdges }) = root graphNodes graphEdges
where
root :: [G.Node] -> [G.Edge] -> [Xmlbf.Node]
root gn ge =
......@@ -77,5 +76,5 @@ instance Xmlbf.ToXml Graph where
-- just to be able to derive a client for the entire gargantext API,
-- we however want to avoid sollicitating this instance
instance Xmlbf.FromXml Graph where
instance Xmlbf.FromXml G.Graph where
fromXml = error "FromXml Graph: not defined, just a placeholder"
{-| Module : Gargantext.Core.Viz.Graph.PatriciaTreeTypes
Description :
Copyright : (c) CNRS, Alexandre Delanoë
License : AGPL + CECILL v3
Maintainer : contact@gargantext.org
Stability : experimental
Portability : POSIX
-}
module Gargantext.Core.Viz.Graph.PatriciaTreeTypes where
import qualified Data.Graph.Inductive.PatriciaTree as DGIP
-- import Data.IntMap (IntMap)
-- import qualified Eigen.Matrix as DenseMatrix
-- import Eigen.SparseMatrix (SparseMatrix)
--import qualified Data.Matrix.Sparse.Static as Sparse
-- import qualified Data.Vector.Unboxed as VU
-- import qualified Numeric.LinearAlgebra.Static as Dense
import Protolude hiding (sum, natVal)
-- | Main Types use in this libray
type Dict = IntMap
-- | Use the optimized version of Graph
type Graph a b = DGIP.Gr a b
-- | Type for Matrix computation optimizations (with Eigen)
-- type MatrixD n = Dense.L n n
-- type MatrixS n = Sparse.Matrix n n Double
......@@ -25,11 +25,11 @@ import Gargantext.API.Ngrams.Types (NgramsTerm(..))
import Gargantext.Core.Methods.Similarities (Similarity(..), measure)
import Gargantext.Core.Methods.Similarities.Conditional (conditional)
import Gargantext.Core.Statistics
import Gargantext.Core.Viz.Graph
import Gargantext.Core.Viz.Graph.Bridgeness (bridgeness, Bridgeness(..), Partitions, nodeId2comId)
import Gargantext.Core.Viz.Graph.Index (createIndices, toIndex, map2mat, mat2map, Index, MatrixShape(..))
import Gargantext.Core.Viz.Graph.Tools.IGraph (mkGraphUfromEdges, spinglass)
import Gargantext.Core.Viz.Graph.Tools.Infomap (infomap)
import Gargantext.Core.Viz.Graph.Types (Attributes(..), Edge(..), Graph(..), MultiPartite(..), Node(..), Partite(..), Strength(..))
import Gargantext.Database.Schema.Ngrams (NgramsType(..))
import Gargantext.Core.Viz.Graph.Utils (edgesFilter, nodesFilter)
import Gargantext.Prelude
......@@ -242,6 +242,7 @@ data2graph multi labels' occurences bridge conf partitions =
(bridge', toKeep) = nodesFilter (\v -> v > 1) bridge
edges = [ Edge { edge_source = cs (show s)
, edge_hidden = Nothing
, edge_target = cs (show t)
, edge_weight = weight
, edge_confluence = maybe 0 identity $ Map.lookup (s,t) conf
......@@ -340,7 +341,7 @@ cooc2graph'' distance threshold myCooc = neighbourMap
-- Quentin
filterByNeighbours :: Double -> Map (Index, Index) Double -> Map (Index, Index) Double
filterByNeighbours threshold distanceMap = filteredMap
where
where
indexes :: [Index]
indexes = List.nub $ List.concat $ map (\(idx,idx') -> [idx,idx'] ) $ Map.keys distanceMap
filteredMap :: Map (Index, Index) Double
......@@ -354,4 +355,3 @@ filterByNeighbours threshold distanceMap = filteredMap
$ Map.filterWithKey (\(from,_) _ -> idx == from) distanceMap
in List.take (round threshold) selected
) indexes
This diff is collapsed.
......@@ -10,6 +10,7 @@ Portability : POSIX
-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module Gargantext.Database.Admin.Types.Hyperdata
( module Gargantext.Database.Admin.Types.Hyperdata.Any
......@@ -26,7 +27,7 @@ module Gargantext.Database.Admin.Types.Hyperdata
, module Gargantext.Database.Admin.Types.Hyperdata.Texts
, module Gargantext.Database.Admin.Types.Hyperdata.Phylo
, module Gargantext.Database.Admin.Types.Hyperdata.User
, module Gargantext.Core.Viz.Graph
, module Gargantext.Core.Viz.Graph.Types
)
where
......@@ -44,4 +45,4 @@ import Gargantext.Database.Admin.Types.Hyperdata.Prelude (Hyperdata)
import Gargantext.Database.Admin.Types.Hyperdata.Texts
import Gargantext.Database.Admin.Types.Hyperdata.Phylo
import Gargantext.Database.Admin.Types.Hyperdata.User
import Gargantext.Core.Viz.Graph (HyperdataGraph(..), defaultHyperdataGraph)
import Gargantext.Core.Viz.Graph.Types (HyperdataGraph(..), defaultHyperdataGraph)
......@@ -27,7 +27,7 @@ import Gargantext.Database.Admin.Types.Hyperdata.Prelude
data DefaultHyperdata =
DefaultUser HyperdataUser
DefaultUser HyperdataUser
| DefaultContact HyperdataContact
| DefaultCorpus HyperdataCorpus
......
......@@ -11,7 +11,7 @@ Portability : POSIX
module Gargantext.Database.Admin.Types.Hyperdata.Prelude
( module Control.Lens
( module Control.Lens
, module Data.Aeson
, module Data.Aeson.TH
, module Data.Aeson.Types
......@@ -66,8 +66,3 @@ data Chart =
instance ToJSON Chart
instance FromJSON Chart
instance ToSchema Chart
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