Commit 2d5a3e0a authored by Alexandre Delanoë's avatar Alexandre Delanoë

[REFACT] Viz -> Core

parent 4f3320e1
......@@ -30,11 +30,11 @@ import Gargantext.Core.Text.Corpus.Parsers.CSV (csv_title, csv_abstract, csv_pub
import Gargantext.Core.Text.Corpus.Parsers (FileFormat(..),parseFile)
import Gargantext.Core.Text.List.CSV (csvMapTermList)
import Gargantext.Core.Text.Terms.WithList (Patterns, buildPatterns, extractTermsWithList)
import Gargantext.Viz.AdaptativePhylo
import Gargantext.Viz.Phylo.PhyloMaker (toPhylo)
import Gargantext.Viz.Phylo.PhyloTools (printIOMsg, printIOComment)
import Gargantext.Viz.Phylo.PhyloExport (toPhyloExport, dotToFile)
-- import Gargantext.Viz.Phylo.SynchronicClustering (synchronicDistance')
import Gargantext.Core.Viz.AdaptativePhylo
import Gargantext.Core.Viz.Phylo.PhyloMaker (toPhylo)
import Gargantext.Core.Viz.Phylo.PhyloTools (printIOMsg, printIOComment)
import Gargantext.Core.Viz.Phylo.PhyloExport (toPhyloExport, dotToFile)
-- import Gargantext.Core.Viz.Phylo.SynchronicClustering (synchronicDistance')
import GHC.IO (FilePath)
import Prelude (Either(..))
......
......@@ -33,11 +33,11 @@ import Gargantext.Core.Text.Corpus.Parsers (FileFormat(..),parseFile)
import Gargantext.Core.Text.Corpus.Parsers.CSV (csv_title, csv_abstract, csv_publication_year)
import Gargantext.Core.Text.List.CSV (csvMapTermList)
import Gargantext.Core.Text.Terms.WithList
import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.LevelMaker
import Gargantext.Viz.Phylo.Tools
import Gargantext.Viz.Phylo.View.Export
import Gargantext.Viz.Phylo.View.ViewMaker
import Gargantext.Core.Viz.Phylo
import Gargantext.Core.Viz.Phylo.LevelMaker
import Gargantext.Core.Viz.Phylo.Tools
import Gargantext.Core.Viz.Phylo.View.Export
import Gargantext.Core.Viz.Phylo.View.ViewMaker
import System.Directory (doesFileExist)
import System.Environment
import qualified Data.ByteString.Lazy as L
......
......@@ -78,21 +78,21 @@ library:
- Gargantext.Core.Text.Terms.Multi.RAKE
- Gargantext.Core.Text.Terms.WithList
- Gargantext.Core.Text.Flow
- Gargantext.Viz.Graph
- Gargantext.Viz.Graph.Distances.Matrice
- Gargantext.Viz.Graph.Index
- Gargantext.Viz.Phylo
- Gargantext.Viz.AdaptativePhylo
- Gargantext.Viz.Phylo.PhyloMaker
- Gargantext.Viz.Phylo.Tools
- Gargantext.Viz.Phylo.PhyloTools
- Gargantext.Viz.Phylo.PhyloExport
- Gargantext.Viz.Phylo.SynchronicClustering
- Gargantext.Viz.Phylo.Example
- Gargantext.Viz.Phylo.LevelMaker
- Gargantext.Viz.Phylo.View.Export
- Gargantext.Viz.Phylo.View.ViewMaker
- Gargantext.Viz.Types
- Gargantext.Core.Viz.Graph
- Gargantext.Core.Viz.Graph.Distances.Matrice
- Gargantext.Core.Viz.Graph.Index
- Gargantext.Core.Viz.Phylo
- Gargantext.Core.Viz.AdaptativePhylo
- Gargantext.Core.Viz.Phylo.PhyloMaker
- Gargantext.Core.Viz.Phylo.Tools
- Gargantext.Core.Viz.Phylo.PhyloTools
- Gargantext.Core.Viz.Phylo.PhyloExport
- Gargantext.Core.Viz.Phylo.SynchronicClustering
- Gargantext.Core.Viz.Phylo.Example
- Gargantext.Core.Viz.Phylo.LevelMaker
- Gargantext.Core.Viz.Phylo.View.Export
- Gargantext.Core.Viz.Phylo.View.ViewMaker
- Gargantext.Core.Viz.Types
dependencies:
- HSvm
- KMP
......
......@@ -15,11 +15,11 @@ module Gargantext ( module Gargantext.API
, module Gargantext.Core
, module Gargantext.Database
, module Gargantext.Prelude
-- , module Gargantext.Viz
-- , module Gargantext.Core.Viz
) where
import Gargantext.API
import Gargantext.Core
import Gargantext.Database
import Gargantext.Prelude
--import Gargantext.Viz
--import Gargantext.Core.Viz
......@@ -40,8 +40,8 @@ import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata)
import Gargantext.Database.Schema.Node (node_hyperdata)
import Gargantext.Prelude
import Gargantext.Core.Text.Metrics (Scored(..))
import Gargantext.Viz.Chart
import Gargantext.Viz.Types
import Gargantext.Core.Viz.Chart
import Gargantext.Core.Viz.Types
import qualified Gargantext.Database.Action.Metrics as Metrics
-------------------------------------------------------------
......
......@@ -64,7 +64,7 @@ import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata)
import Gargantext.Database.Query.Table.NodeNode
import Gargantext.Database.Query.Tree (tree, TreeMode(..))
import Gargantext.Prelude
import Gargantext.Viz.Phylo.API (PhyloAPI, phyloAPI)
import Gargantext.Core.Viz.Phylo.API (PhyloAPI, phyloAPI)
import qualified Gargantext.API.Node.Share as Share
import qualified Gargantext.API.Node.Update as Update
import qualified Gargantext.API.Search as Search
......
......@@ -29,8 +29,8 @@ import Gargantext.Database.Action.Flow.Pairing (pairing)
import Gargantext.Database.Action.Flow.Types (FlowCmdM)
import Gargantext.Database.Admin.Types.Node
import Gargantext.Prelude (Ord, Eq, (<$>), ($), liftBase, (.), printDebug, pure)
import Gargantext.Viz.Graph.API (recomputeGraph)
import Gargantext.Viz.Graph.Distances (GraphMetric(..), Distance(..))
import Gargantext.Core.Viz.Graph.API (recomputeGraph)
import Gargantext.Core.Viz.Graph.Distances (GraphMetric(..), Distance(..))
import Prelude (Enum, Bounded, minBound, maxBound)
import Servant
import Servant.Job.Async (JobFunction(..), serveJobsAPI)
......
......@@ -39,7 +39,7 @@ import Gargantext.Database.Admin.Types.Hyperdata
import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Admin.Types.Node (NodeId, CorpusId, AnnuaireId)
import Gargantext.Prelude
import Gargantext.Viz.Graph.API
import Gargantext.Core.Viz.Graph.API
import Servant
import Servant.Auth as SA
import Servant.Auth.Swagger ()
......
......@@ -45,8 +45,8 @@ import Gargantext.Core (Lang(EN))
import Gargantext.Core.Types (Terms(..), Label)
import Gargantext.Core.Text.Context (splitBy, SplitContext(Sentences))
import Gargantext.Core.Text.Metrics.Count (Grouped)
import Gargantext.Viz.Graph.Distances.Matrice
import Gargantext.Viz.Graph.Index
import Gargantext.Core.Viz.Graph.Distances.Matrice
import Gargantext.Core.Viz.Graph.Index
import qualified Data.Array.Accelerate as DAA
......
......@@ -25,8 +25,8 @@ import Data.Map (Map)
import Data.List.Extra (sortOn)
import GHC.Real (round)
import Gargantext.Prelude
import Gargantext.Viz.Graph.Distances.Matrice
import Gargantext.Viz.Graph.Index
import Gargantext.Core.Viz.Graph.Distances.Matrice
import Gargantext.Core.Viz.Graph.Index
import Gargantext.Core.Statistics (pcaReduceTo, Dimension(..))
import qualified Data.Array.Accelerate as DAA
import qualified Data.Array.Accelerate.Interpreter as DAA
......
{-|
Module : Gargantext.Viz
Module : Gargantext.Core.Viz
Description : Viz tools
Copyright : (c) CNRS, 2018
License : AGPL + CECILL v3
......@@ -12,6 +12,6 @@ Vizualisation of text stats
-}
module Gargantext.Viz
module Gargantext.Core.Viz
where
{-|
Module : Gargantext.Viz.AdaptativePhylo
Module : Gargantext.Core.Viz.AdaptativePhylo
Description : Phylomemy definitions and types.
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -24,7 +24,7 @@ one 8, e54847.
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Viz.AdaptativePhylo where
module Gargantext.Core.Viz.AdaptativePhylo where
import Data.Aeson
import Data.Aeson.TH (deriveJSON)
......
{-|
Module : Gargantext.Viz.Chart
Module : Gargantext.Core.Viz.Chart
Description : Graph utils
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -11,7 +11,7 @@ Portability : POSIX
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Viz.Chart
module Gargantext.Core.Viz.Chart
where
import Data.List (unzip, sortOn)
......@@ -39,7 +39,7 @@ import Gargantext.Core.Types
import Gargantext.Database.Action.Flow
import Gargantext.Database.Action.Metrics.NgramsByNode
import Gargantext.Database.Schema.Ngrams
import Gargantext.Viz.Types
import Gargantext.Core.Viz.Types
histoData :: CorpusId -> Cmd err Histo
histoData cId = do
......
{-|
Module : Gargantext.Viz.Graph
Module : Gargantext.Core.Viz.Graph
Description : Graph utils
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -13,7 +13,7 @@ Portability : POSIX
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Viz.Graph
module Gargantext.Core.Viz.Graph
where
import Control.Lens (makeLenses)
......@@ -23,7 +23,7 @@ import GHC.IO (FilePath)
import Gargantext.Core.Types (ListId)
import Gargantext.Database.Admin.Types.Hyperdata.Prelude
import Gargantext.Database.Admin.Types.Node (NodeId)
import Gargantext.Viz.Graph.Distances (GraphMetric)
import Gargantext.Core.Viz.Graph.Distances (GraphMetric)
import Gargantext.Prelude
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
......
{-|
Module : Gargantext.Viz.Graph
Module : Gargantext.Core.Viz.Graph
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -15,7 +15,7 @@ Portability : POSIX
{-# LANGUAGE OverloadedLists #-} -- allows to write Map and HashMap as lists
{-# LANGUAGE TypeOperators #-}
module Gargantext.Viz.Graph.API
module Gargantext.Core.Viz.Graph.API
where
import Control.Lens (set, (^.), _Just, (^?))
......@@ -46,10 +46,10 @@ import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata)
import Gargantext.Database.Schema.Ngrams
import Gargantext.Database.Schema.Node (node_parentId, node_hyperdata)
import Gargantext.Prelude
import Gargantext.Viz.Graph
import Gargantext.Viz.Graph.GEXF ()
import Gargantext.Viz.Graph.Tools -- (cooc2graph)
import Gargantext.Viz.Graph.Distances (Distance(..), GraphMetric(..))
import Gargantext.Core.Viz.Graph
import Gargantext.Core.Viz.Graph.GEXF ()
import Gargantext.Core.Viz.Graph.Tools -- (cooc2graph)
import Gargantext.Core.Viz.Graph.Distances (Distance(..), GraphMetric(..))
------------------------------------------------------------------------
-- | There is no Delete specific API for Graph since it can be deleted
......
{-|
Module : Gargantext.Viz.Graph.Bridgeness
Module : Gargantext.Core.Viz.Graph.Bridgeness
Description : Bridgeness filter
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -16,7 +16,7 @@ TODO use Map LouvainNodeId (Map LouvainNodeId)
-}
module Gargantext.Viz.Graph.Bridgeness (bridgeness)
module Gargantext.Core.Viz.Graph.Bridgeness (bridgeness)
where
import Data.Ord (Down(..))
......@@ -26,7 +26,7 @@ import qualified Data.Map as DM
import Data.Maybe (catMaybes)
import Data.List (concat, sortOn)
import Data.Graph.Clustering.Louvain.Utils (LouvainNode(..))
import Gargantext.Viz.Graph.Louvain (LouvainNodeId, CommunityId, nodeId2comId)
import Gargantext.Core.Viz.Graph.Louvain (LouvainNodeId, CommunityId, nodeId2comId)
type Bridgeness = Double
......
......@@ -11,7 +11,7 @@ Portability : POSIX
{-# LANGUAGE Strict #-}
module Gargantext.Viz.Graph.Distances
module Gargantext.Core.Viz.Graph.Distances
where
import Data.Aeson
......@@ -20,7 +20,7 @@ import Data.Swagger
import GHC.Generics (Generic)
import Gargantext.Prelude (Ord, Eq, Int, Double)
import Gargantext.Prelude (Show)
import Gargantext.Viz.Graph.Distances.Matrice (measureConditional, distributional)
import Gargantext.Core.Viz.Graph.Distances.Matrice (measureConditional, distributional)
import Prelude (Enum, Bounded, minBound, maxBound)
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary
......
......@@ -12,7 +12,7 @@ Motivation and definition of the @Conditional@ distance.
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE Strict #-}
module Gargantext.Viz.Graph.Distances.Conditional
module Gargantext.Core.Viz.Graph.Distances.Conditional
where
import Data.Matrix hiding (identity)
......@@ -27,7 +27,7 @@ import qualified Data.Set as S
import qualified Data.Vector as V
import Gargantext.Prelude
import Gargantext.Viz.Graph.Utils
import Gargantext.Core.Viz.Graph.Utils
------------------------------------------------------------------------
------------------------------------------------------------------------
......
......@@ -14,7 +14,7 @@ Motivation and definition of the @Distributional@ distance.
{-# LANGUAGE Strict #-}
module Gargantext.Viz.Graph.Distances.Distributional
module Gargantext.Core.Viz.Graph.Distances.Distributional
where
import Data.Matrix hiding (identity)
......@@ -22,7 +22,7 @@ import qualified Data.Map as M
import Data.Vector (Vector)
import qualified Data.Vector as V
import Gargantext.Prelude
import Gargantext.Viz.Graph.Utils
import Gargantext.Core.Viz.Graph.Utils
distributional' :: (Floating a, Ord a) => Matrix a -> [((Int, Int), a)]
......
......@@ -27,7 +27,7 @@ Implementation use Accelerate library which enables GPU and CPU computation:
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ViewPatterns #-}
module Gargantext.Viz.Graph.Distances.Matrice
module Gargantext.Core.Viz.Graph.Distances.Matrice
where
import qualified Data.Foldable as P (foldl1)
......
{-| Module : Gargantext.Viz.Graph.FGL
{-| Module : Gargantext.Core.Viz.Graph.FGL
Description : FGL main functions used in Garg
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -12,7 +12,7 @@ Main FGL funs/types to ease portability with IGraph.
{-# LANGUAGE ConstraintKinds #-}
module Gargantext.Viz.Graph.FGL where
module Gargantext.Core.Viz.Graph.FGL where
import Gargantext.Prelude
import qualified Data.Graph.Inductive as FGL
......
{-|
Module : Gargantext.Viz.Graph
Module : Gargantext.Core.Viz.Graph
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -15,14 +15,14 @@ Portability : POSIX
{-# LANGUAGE OverloadedLists #-} -- allows to write Map and HashMap as lists
{-# LANGUAGE TypeOperators #-}
module Gargantext.Viz.Graph.GEXF
module Gargantext.Core.Viz.Graph.GEXF
where
import Gargantext.Prelude
import Gargantext.Viz.Graph
import Gargantext.Core.Viz.Graph
import qualified Data.HashMap.Lazy as HashMap
import qualified Gargantext.Prelude as P
import qualified Gargantext.Viz.Graph as G
import qualified Gargantext.Core.Viz.Graph as G
import qualified Xmlbf as Xmlbf
-- Converts to GEXF format
......
{-| Module : Gargantext.Viz.Graph.IGraph
{-| Module : Gargantext.Core.Viz.Graph.IGraph
Description : IGraph main functions used in Garg
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -14,7 +14,7 @@ Reference:
-}
module Gargantext.Viz.Graph.IGraph where
module Gargantext.Core.Viz.Graph.IGraph where
import Data.Serialize (Serialize)
import Data.Singletons (SingI)
......
......@@ -21,7 +21,7 @@ TODO:
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE MonoLocalBinds #-}
module Gargantext.Viz.Graph.Index
module Gargantext.Core.Viz.Graph.Index
where
import qualified Data.Array.Accelerate as A
......
{-|
Module : Gargantext.Viz.Graph.Legend
Module : Gargantext.Core.Viz.Graph.Legend
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -10,7 +10,7 @@ Portability : POSIX
-}
module Gargantext.Viz.Graph.Legend
module Gargantext.Core.Viz.Graph.Legend
where
{-
......@@ -20,7 +20,7 @@ import Data.Map (Map, fromListWith, lookup, toList, mapWithKey, elems)
import qualified Data.Map as DM
import Data.Maybe (catMaybes)
import Data.List (concat, sortOn)
import Gargantext.Viz.Graph.Louvain (LouvainNodeId, CommunityId, comId2nodeId)
import Gargantext.Core.Viz.Graph.Louvain (LouvainNodeId, CommunityId, comId2nodeId)
......
{-|
Module : Gargantext.Viz.Graph.Louvain
Module : Gargantext.Core.Viz.Graph.Louvain
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -10,7 +10,7 @@ Portability : POSIX
-}
module Gargantext.Viz.Graph.Louvain
module Gargantext.Core.Viz.Graph.Louvain
where
import Gargantext.Prelude
......
{-| Module : Gargantext.Viz.Graph.MaxClique
{-| Module : Gargantext.Core.Viz.Graph.MaxClique
Description : MaxCliques function
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -48,7 +48,7 @@ def fast_maximal_cliques(g):
module Gargantext.Viz.Graph.MaxClique
module Gargantext.Core.Viz.Graph.MaxClique
where
import Data.Maybe (catMaybes)
......@@ -59,10 +59,10 @@ import Data.List (sortOn, nub, concat, length)
import Data.Set (Set)
import Data.Set (fromList, toList, isSubsetOf)
import Data.Graph.Inductive hiding (Graph, neighbors, subgraph, (&))
import Gargantext.Viz.Graph.FGL (Graph_Undirected, degree, neighbors, mkGraphUfromEdges)
import Gargantext.Viz.Graph.Tools (cooc2graph', Threshold)
import Gargantext.Viz.Graph.Distances (Distance)
import Gargantext.Viz.Graph.Index (createIndices, toIndex)
import Gargantext.Core.Viz.Graph.FGL (Graph_Undirected, degree, neighbors, mkGraphUfromEdges)
import Gargantext.Core.Viz.Graph.Tools (cooc2graph', Threshold)
import Gargantext.Core.Viz.Graph.Distances (Distance)
import Gargantext.Core.Viz.Graph.Index (createIndices, toIndex)
type Graph = Graph_Undirected
type Neighbor = Node
......
{-| Module : Gargantext.Viz.Graph.Proxemy
{-| Module : Gargantext.Core.Viz.Graph.Proxemy
Description : Proxemy
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -14,7 +14,7 @@ Références:
-}
module Gargantext.Viz.Graph.Proxemy
module Gargantext.Core.Viz.Graph.Proxemy
where
--import Debug.SimpleReflect
......@@ -22,8 +22,8 @@ import Gargantext.Prelude
import Data.Map (Map)
import qualified Data.Map as Map
import qualified Data.List as List
--import Gargantext.Viz.Graph.IGraph
import Gargantext.Viz.Graph.FGL
--import Gargantext.Core.Viz.Graph.IGraph
import Gargantext.Core.Viz.Graph.FGL
type Length = Int
type FalseReflexive = Bool
......@@ -86,7 +86,7 @@ prox_markov g ns l r nf = foldl' (\m _ -> spreading g m r nf) ms path
path
| l == 0 = []
| l > 0 = [0..l-1]
| otherwise = panic "Gargantext.Viz.Graph.Proxemy.prox_markov: Length < 0"
| otherwise = panic "Gargantext.Core.Viz.Graph.Proxemy.prox_markov: Length < 0"
-- TODO if ns empty
ms = case List.length ns > 0 of
True -> Map.fromList $ map (\n -> (n, 1 / (fromIntegral $ List.length ns))) ns
......
{-|
Module : Gargantext.Viz.Graph.Tools
Module : Gargantext.Core.Viz.Graph.Tools
Description : Tools to build Graph
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -10,7 +10,7 @@ Portability : POSIX
-}
module Gargantext.Viz.Graph.Tools
module Gargantext.Core.Viz.Graph.Tools
where
import Debug.Trace (trace)
......@@ -22,12 +22,12 @@ import qualified Data.Set as Set
import Data.Text (Text)
import Gargantext.Prelude
import Gargantext.Core.Statistics
import Gargantext.Viz.Graph
import Gargantext.Viz.Graph.Bridgeness (bridgeness)
import Gargantext.Viz.Graph.Distances (Distance(..), measure)
import Gargantext.Viz.Graph.Index (createIndices, toIndex, map2mat, mat2map, Index)
import Gargantext.Viz.Graph.IGraph (mkGraphUfromEdges)
import Gargantext.Viz.Graph.Proxemy (confluence)
import Gargantext.Core.Viz.Graph
import Gargantext.Core.Viz.Graph.Bridgeness (bridgeness)
import Gargantext.Core.Viz.Graph.Distances (Distance(..), measure)
import Gargantext.Core.Viz.Graph.Index (createIndices, toIndex, map2mat, mat2map, Index)
import Gargantext.Core.Viz.Graph.IGraph (mkGraphUfromEdges)
import Gargantext.Core.Viz.Graph.Proxemy (confluence)
import GHC.Float (sin, cos)
import qualified IGraph as Igraph
import qualified IGraph.Algorithms.Layout as Layout
......
{-|
Module : Gargantext.Viz.Graph.Utils
Module : Gargantext.Core.Viz.Graph.Utils
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -14,7 +14,7 @@ These functions are used for Vector.Matrix only.
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE Strict #-}
module Gargantext.Viz.Graph.Utils
module Gargantext.Core.Viz.Graph.Utils
where
import Data.Matrix hiding (identity)
......
{-|
Module : Gargantext.Viz.Phylo
Module : Gargantext.Core.Viz.Phylo
Description : Phylomemy definitions and types.
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -25,7 +25,7 @@ one 8, e54847.
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Viz.Phylo where
module Gargantext.Core.Viz.Phylo where
import Control.DeepSeq
import Control.Lens (makeLenses)
......
{-|
Module : Gargantext.Viz.Phylo.API
Module : Gargantext.Core.Viz.Phylo.API
Description : Phylo API
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -14,7 +14,7 @@ Portability : POSIX
{-# LANGUAGE OverloadedLists #-} -- allows to write Map and HashMap as lists
{-# LANGUAGE TypeOperators #-}
module Gargantext.Viz.Phylo.API
module Gargantext.Core.Viz.Phylo.API
where
import Control.Lens ((^.))
......@@ -36,9 +36,9 @@ import Gargantext.Database.Admin.Types.Node -- (PhyloId, ListId, CorpusId, UserI
import Gargantext.Database.Query.Table.Node (insertNodes, node, getNodeWith)
import Gargantext.Database.Schema.Node (node_hyperdata)
import Gargantext.Prelude
import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Main
import Gargantext.Viz.Phylo.Example
import Gargantext.Core.Viz.Phylo
import Gargantext.Core.Viz.Phylo.Main
import Gargantext.Core.Viz.Phylo.Example
import Gargantext.Core.Types (TODO(..))
------------------------------------------------------------------------
......
{-|
Module : Gargantext.Viz.Phylo.Tools
Module : Gargantext.Core.Viz.Phylo.Tools
Description : Phylomemy Tools to build/manage it
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -10,7 +10,7 @@ Portability : POSIX
{-# LANGUAGE ViewPatterns #-}
module Gargantext.Viz.Phylo.Aggregates
module Gargantext.Core.Viz.Phylo.Aggregates
where
import Control.Parallel.Strategies
......@@ -19,8 +19,8 @@ import Gargantext.Prelude hiding (elem)
import Gargantext.Core.Text.Context (TermList)
import Gargantext.Core.Text.Metrics.FrequentItemSet (fisWithSizePolyMap, Size(..))
import Gargantext.Core.Text.Terms.Mono (monoTexts)
import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Tools
import Gargantext.Core.Viz.Phylo
import Gargantext.Core.Viz.Phylo.Tools
import Debug.Trace (trace)
......
{-|
Module : Gargantext.Viz.Phylo.Tools
Module : Gargantext.Core.Viz.Phylo.Tools
Description : Phylomemy Tools to build/manage it
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -11,7 +11,7 @@ Portability : POSIX
-}
module Gargantext.Viz.Phylo.BranchMaker
module Gargantext.Core.Viz.Phylo.BranchMaker
where
import Control.Parallel.Strategies
......@@ -20,12 +20,12 @@ import Data.List (concat,nub,(++),sortOn,reverse,sort,null,intersect,unio
import Data.Map (Map,(!), fromListWith, elems)
import Data.Tuple (fst, snd)
import Gargantext.Prelude
import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Cluster
import Gargantext.Viz.Phylo.Aggregates
import Gargantext.Viz.Phylo.Metrics
import Gargantext.Viz.Phylo.Tools
import Gargantext.Viz.Phylo.LinkMaker
import Gargantext.Core.Viz.Phylo
import Gargantext.Core.Viz.Phylo.Cluster
import Gargantext.Core.Viz.Phylo.Aggregates
import Gargantext.Core.Viz.Phylo.Metrics
import Gargantext.Core.Viz.Phylo.Tools
import Gargantext.Core.Viz.Phylo.LinkMaker
import qualified Data.Map as Map
......
{-|
Module : Gargantext.Viz.Phylo.Tools
Module : Gargantext.Core.Viz.Phylo.Tools
Description : Phylomemy Tools to build/manage it
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -12,7 +12,7 @@ Portability : POSIX
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Viz.Phylo.Cluster
module Gargantext.Core.Viz.Phylo.Cluster
where
import Control.Parallel.Strategies
import Data.Graph.Clustering.Louvain.CplusPlus
......@@ -21,10 +21,10 @@ import Data.List (null,concat,sort,intersect,(++), elemIndex, groupBy, nu
import Data.Map (Map, fromList, mapKeys)
import Data.Tuple (fst)
import Gargantext.Prelude
import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Tools
import Gargantext.Viz.Phylo.Metrics
import Gargantext.Viz.Phylo.LinkMaker
import Gargantext.Core.Viz.Phylo
import Gargantext.Core.Viz.Phylo.Tools
import Gargantext.Core.Viz.Phylo.Metrics
import Gargantext.Core.Viz.Phylo.LinkMaker
import qualified Data.Map as Map
import qualified Data.Vector.Storable as VS
......@@ -56,7 +56,7 @@ louvain (nodes,edges) = map (\community -> map (\node -> nodes !! (l_node_id nod
--------------------------------------
idx :: PhyloGroup -> Int
idx e = case elemIndex e nodes of
Nothing -> panic "[ERR][Gargantext.Viz.Phylo.Metrics.Clustering] a node is missing"
Nothing -> panic "[ERR][Gargantext.Core.Viz.Phylo.Metrics.Clustering] a node is missing"
Just i -> i
--------------------------------------
......
{-|
Module : Gargantext.Viz.Phylo.Example
Module : Gargantext.Core.Viz.Phylo.Example
Description : Phylomemy example based on history of Cleopatre.
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -22,7 +22,7 @@ TODO:
-}
module Gargantext.Viz.Phylo.Example where
module Gargantext.Core.Viz.Phylo.Example where
import Data.GraphViz.Types.Generalised (DotGraph)
......@@ -34,16 +34,16 @@ import Data.Tuple (fst)
import Data.Vector (Vector)
import Gargantext.Prelude
import Gargantext.Core.Text.Context (TermList)
import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Cluster
import Gargantext.Viz.Phylo.Aggregates
import Gargantext.Viz.Phylo.BranchMaker
import Gargantext.Viz.Phylo.LevelMaker
import Gargantext.Viz.Phylo.LinkMaker
import Gargantext.Viz.Phylo.Tools
import Gargantext.Viz.Phylo.View.ViewMaker
import Gargantext.Viz.Phylo.View.Export
import Gargantext.Viz.Phylo.Main (writePhylo)
import Gargantext.Core.Viz.Phylo
import Gargantext.Core.Viz.Phylo.Cluster
import Gargantext.Core.Viz.Phylo.Aggregates
import Gargantext.Core.Viz.Phylo.BranchMaker
import Gargantext.Core.Viz.Phylo.LevelMaker
import Gargantext.Core.Viz.Phylo.LinkMaker
import Gargantext.Core.Viz.Phylo.Tools
import Gargantext.Core.Viz.Phylo.View.ViewMaker
import Gargantext.Core.Viz.Phylo.View.Export
import Gargantext.Core.Viz.Phylo.Main (writePhylo)
import GHC.IO (FilePath)
import qualified Data.List as List
......
{-|
Module : Gargantext.Viz.Phylo.Tools
Module : Gargantext.Core.Viz.Phylo.Tools
Description : Phylomemy Tools to build/manage it
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -12,7 +12,7 @@ Portability : POSIX
{-# LANGUAGE TypeSynonymInstances #-}
module Gargantext.Viz.Phylo.LevelMaker
module Gargantext.Core.Viz.Phylo.LevelMaker
where
import Control.Parallel.Strategies
......@@ -23,13 +23,13 @@ import Data.Text (Text)
import Data.Tuple.Extra
import Data.Vector (Vector)
import Gargantext.Prelude
import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Metrics
import Gargantext.Viz.Phylo.Aggregates
import Gargantext.Viz.Phylo.Cluster
import Gargantext.Viz.Phylo.BranchMaker
import Gargantext.Viz.Phylo.LinkMaker
import Gargantext.Viz.Phylo.Tools
import Gargantext.Core.Viz.Phylo
import Gargantext.Core.Viz.Phylo.Metrics
import Gargantext.Core.Viz.Phylo.Aggregates
import Gargantext.Core.Viz.Phylo.Cluster
import Gargantext.Core.Viz.Phylo.BranchMaker
import Gargantext.Core.Viz.Phylo.LinkMaker
import Gargantext.Core.Viz.Phylo.Tools
import Gargantext.Core.Text.Context (TermList)
import qualified Data.Vector.Storable as VS
......
{-|
Module : Gargantext.Viz.Phylo.Tools
Module : Gargantext.Core.Viz.Phylo.Tools
Description : Phylomemy Tools to build/manage it
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -11,7 +11,7 @@ Portability : POSIX
-}
module Gargantext.Viz.Phylo.LinkMaker
module Gargantext.Core.Viz.Phylo.LinkMaker
where
import Control.Parallel.Strategies
......@@ -20,9 +20,9 @@ import Data.List ((++), sortOn, null, tail, splitAt, elem, co
import Data.Tuple.Extra
import Data.Map (Map, (!), fromListWith, elems, restrictKeys, filterWithKey, keys, unionWith, unions, intersectionWith, member, fromList)
import Gargantext.Prelude
import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Tools
import Gargantext.Viz.Phylo.Metrics
import Gargantext.Core.Viz.Phylo
import Gargantext.Core.Viz.Phylo.Tools
import Gargantext.Core.Viz.Phylo.Metrics
import qualified Data.List as List
import qualified Data.Maybe as Maybe
import qualified Data.Map as Map
......
{-|
Module : Gargantext.Viz.Phylo.Main
Module : Gargantext.Core.Viz.Phylo.Main
Description : Phylomemy Main
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -11,7 +11,7 @@ Portability : POSIX
{-# LANGUAGE ViewPatterns #-}
module Gargantext.Viz.Phylo.Main
module Gargantext.Core.Viz.Phylo.Main
where
......@@ -35,11 +35,11 @@ import Gargantext.Database.Schema.Ngrams (NgramsType(..))
import Gargantext.Prelude
import Gargantext.Core.Text.Context (TermList)
import Gargantext.Core.Text.Terms.WithList
import Gargantext.Viz.Phylo hiding (Svg, Dot)
import Gargantext.Viz.Phylo.LevelMaker
import Gargantext.Viz.Phylo.Tools
import Gargantext.Viz.Phylo.View.Export
import Gargantext.Viz.Phylo.View.ViewMaker -- TODO Just Maker is fine
import Gargantext.Core.Viz.Phylo hiding (Svg, Dot)
import Gargantext.Core.Viz.Phylo.LevelMaker
import Gargantext.Core.Viz.Phylo.Tools
import Gargantext.Core.Viz.Phylo.View.Export
import Gargantext.Core.Viz.Phylo.View.ViewMaker -- TODO Just Maker is fine
type MinSizeBranch = Int
......
{-|
Module : Gargantext.Viz.Phylo.Tools
Module : Gargantext.Core.Viz.Phylo.Tools
Description : Phylomemy Tools to build/manage it
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -10,12 +10,12 @@ Portability : POSIX
{-# LANGUAGE ViewPatterns #-}
module Gargantext.Viz.Phylo.Metrics
module Gargantext.Core.Viz.Phylo.Metrics
where
import Gargantext.Prelude
import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Tools
import Gargantext.Core.Viz.Phylo
import Gargantext.Core.Viz.Phylo.Tools
import Control.Lens hiding (Level)
......
{-|
Module : Gargantext.Viz.Phylo.PhyloExample
Module : Gargantext.Core.Viz.Phylo.PhyloExample
Description : Phylomemy example based on history of Cleopatre.
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -13,7 +13,7 @@ Portability : POSIX
-}
module Gargantext.Viz.Phylo.PhyloExample where
module Gargantext.Core.Viz.Phylo.PhyloExample where
import Data.List (sortOn, nub, sort)
import Data.Map (Map)
......@@ -22,12 +22,12 @@ import Data.Text (Text, toLower)
import Gargantext.Prelude
import Gargantext.Core.Text.Context (TermList)
import Gargantext.Core.Text.Terms.Mono (monoTexts)
import Gargantext.Viz.AdaptativePhylo
import Gargantext.Viz.Phylo.PhyloTools
import Gargantext.Viz.Phylo.PhyloMaker
import Gargantext.Viz.Phylo.PhyloExport
import Gargantext.Viz.Phylo.TemporalMatching (adaptativeTemporalMatching, constanteTemporalMatching)
import Gargantext.Viz.Phylo.SynchronicClustering (synchronicClustering)
import Gargantext.Core.Viz.AdaptativePhylo
import Gargantext.Core.Viz.Phylo.PhyloTools
import Gargantext.Core.Viz.Phylo.PhyloMaker
import Gargantext.Core.Viz.Phylo.PhyloExport
import Gargantext.Core.Viz.Phylo.TemporalMatching (adaptativeTemporalMatching, constanteTemporalMatching)
import Gargantext.Core.Viz.Phylo.SynchronicClustering (synchronicClustering)
import Control.Lens
import Data.GraphViz.Types.Generalised (DotGraph)
......
{-|
Module : Gargantext.Viz.Phylo.PhyloExport
Module : Gargantext.Core.Viz.Phylo.PhyloExport
Description : Exportation module of a Phylo
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -10,7 +10,7 @@ Portability : POSIX
{-# LANGUAGE TypeSynonymInstances #-}
module Gargantext.Viz.Phylo.PhyloExport where
module Gargantext.Core.Viz.Phylo.PhyloExport where
import Data.Map (Map, fromList, empty, fromListWith, insert, (!), elems, unionWith, findWithDefault, toList)
import Data.List ((++), sort, nub, concat, sortOn, reverse, groupBy, union, (\\), (!!), init, partition, unwords, nubBy, inits, elemIndex)
......@@ -18,8 +18,8 @@ import Data.Vector (Vector)
import Prelude (writeFile)
import Gargantext.Prelude
import Gargantext.Viz.AdaptativePhylo
import Gargantext.Viz.Phylo.PhyloTools
import Gargantext.Core.Viz.AdaptativePhylo
import Gargantext.Core.Viz.Phylo.PhyloTools
import Control.Lens
import Data.GraphViz hiding (DotGraph, Order)
......
{-|
Module : Gargantext.Viz.Phylo.PhyloMaker
Module : Gargantext.Core.Viz.Phylo.PhyloMaker
Description : Maker engine for rebuilding a Phylo
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -9,21 +9,21 @@ Portability : POSIX
-}
module Gargantext.Viz.Phylo.PhyloMaker where
module Gargantext.Core.Viz.Phylo.PhyloMaker where
import Data.List (concat, nub, partition, sort, (++), group, intersect, null, sortOn, groupBy, tail)
import Data.Map (Map, fromListWith, keys, unionWith, fromList, empty, toList, elems, (!), restrictKeys, foldlWithKey, insert)
import Data.Vector (Vector)
import Gargantext.Prelude
import Gargantext.Viz.AdaptativePhylo
import Gargantext.Viz.Phylo.PhyloTools
import Gargantext.Viz.Phylo.TemporalMatching (adaptativeTemporalMatching, constanteTemporalMatching, getNextPeriods, filterDocs, filterDiago, reduceDiagos, toProximity)
import Gargantext.Viz.Phylo.SynchronicClustering (synchronicClustering)
import Gargantext.Core.Viz.AdaptativePhylo
import Gargantext.Core.Viz.Phylo.PhyloTools
import Gargantext.Core.Viz.Phylo.TemporalMatching (adaptativeTemporalMatching, constanteTemporalMatching, getNextPeriods, filterDocs, filterDiago, reduceDiagos, toProximity)
import Gargantext.Core.Viz.Phylo.SynchronicClustering (synchronicClustering)
import Gargantext.Core.Text.Context (TermList)
import Gargantext.Core.Text.Metrics.FrequentItemSet (fisWithSizePolyMap, Size(..))
import Gargantext.Viz.Graph.MaxClique (getMaxCliques)
import Gargantext.Viz.Graph.Distances (Distance(Conditional))
import Gargantext.Core.Viz.Graph.MaxClique (getMaxCliques)
import Gargantext.Core.Viz.Graph.Distances (Distance(Conditional))
import Control.DeepSeq (NFData)
import Control.Parallel.Strategies (parList, rdeepseq, using)
......
{-|
Module : Gargantext.Viz.Phylo.PhyloTools
Module : Gargantext.Core.Viz.Phylo.PhyloTools
Description : Module dedicated to all the tools needed for making a Phylo
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -10,7 +10,7 @@ Portability : POSIX
{-# LANGUAGE ViewPatterns #-}
module Gargantext.Viz.Phylo.PhyloTools where
module Gargantext.Core.Viz.Phylo.PhyloTools where
import Data.Vector (Vector, elemIndex)
import Data.List (sort, concat, null, union, (++), tails, sortOn, nub, init, tail, partition, tails, nubBy)
......@@ -20,7 +20,7 @@ import Data.String (String)
import Data.Text (Text, unwords)
import Gargantext.Prelude
import Gargantext.Viz.AdaptativePhylo
import Gargantext.Core.Viz.AdaptativePhylo
import Text.Printf
......
{-|
Module : Gargantext.Viz.Phylo.SynchronicClustering
Module : Gargantext.Core.Viz.Phylo.SynchronicClustering
Description : Module dedicated to the adaptative synchronic clustering of a Phylo.
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -9,13 +9,13 @@ Portability : POSIX
-}
module Gargantext.Viz.Phylo.SynchronicClustering where
module Gargantext.Core.Viz.Phylo.SynchronicClustering where
import Gargantext.Prelude
import Gargantext.Viz.AdaptativePhylo
import Gargantext.Viz.Phylo.PhyloTools
import Gargantext.Viz.Phylo.TemporalMatching (weightedLogJaccard', filterDiago, reduceDiagos)
import Gargantext.Viz.Phylo.PhyloExport (processDynamics)
import Gargantext.Core.Viz.AdaptativePhylo
import Gargantext.Core.Viz.Phylo.PhyloTools
import Gargantext.Core.Viz.Phylo.TemporalMatching (weightedLogJaccard', filterDiago, reduceDiagos)
import Gargantext.Core.Viz.Phylo.PhyloExport (processDynamics)
import Data.List ((++), null, intersect, nub, concat, sort, sortOn, all, groupBy, group, maximum)
import Data.Map (Map, fromList, fromListWith, foldlWithKey, (!), insert, empty, restrictKeys, elems, mapWithKey, member)
......
{-|
Module : Gargantext.Viz.Phylo.TemporalMatching
Module : Gargantext.Core.Viz.Phylo.TemporalMatching
Description : Module dedicated to the adaptative temporal matching of a Phylo.
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -9,14 +9,14 @@ Portability : POSIX
-}
module Gargantext.Viz.Phylo.TemporalMatching where
module Gargantext.Core.Viz.Phylo.TemporalMatching where
import Data.List (concat, splitAt, tail, sortOn, (++), intersect, null, inits, groupBy, scanl, nub, nubBy, union, dropWhile, partition, or, sort, (!!))
import Data.Map (Map, fromList, elems, restrictKeys, unionWith, findWithDefault, keys, (!), (!?), filterWithKey, singleton, empty, mapKeys, adjust)
import Gargantext.Prelude
import Gargantext.Viz.AdaptativePhylo
import Gargantext.Viz.Phylo.PhyloTools
import Gargantext.Core.Viz.AdaptativePhylo
import Gargantext.Core.Viz.Phylo.PhyloTools
import Prelude (floor)
import Control.Lens hiding (Level)
......
{-|
Module : Gargantext.Viz.Phylo.Tools
Module : Gargantext.Core.Viz.Phylo.Tools
Description : Phylomemy Tools to build/manage it
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -12,7 +12,7 @@ Portability : POSIX
{-# LANGUAGE ViewPatterns #-}
module Gargantext.Viz.Phylo.Tools
module Gargantext.Core.Viz.Phylo.Tools
where
import Control.Lens hiding (both, Level, Empty)
......@@ -24,7 +24,7 @@ import Data.Text (Text,toLower,unwords)
import Data.Tuple.Extra
import Data.Vector (Vector,elemIndex)
import Gargantext.Prelude
import Gargantext.Viz.Phylo
import Gargantext.Core.Viz.Phylo
import qualified Data.Map as Map
import qualified Data.Set as Set
import qualified Data.Vector as Vector
......
{-|
Module : Gargantext.Viz.Phylo.Tools
Module : Gargantext.Core.Viz.Phylo.Tools
Description : Phylomemy Tools to build/manage it
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -11,14 +11,14 @@ Portability : POSIX
-}
module Gargantext.Viz.Phylo.View.Display
module Gargantext.Core.Viz.Phylo.View.Display
where
import Control.Lens hiding (makeLenses, both, Level)
import Data.List (null,(++),sortOn)
import Gargantext.Prelude
import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Tools
import Gargantext.Core.Viz.Phylo
import Gargantext.Core.Viz.Phylo.Tools
-- | To transform a flat Phyloview into a nested Phyloview
toNestedView :: [PhyloNode] -> [PhyloNode] -> [PhyloNode]
......
{-|
Module : Gargantext.Viz.Phylo.Tools
Module : Gargantext.Core.Viz.Phylo.Tools
Description : Phylomemy Tools to build/manage it
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -11,7 +11,7 @@ Portability : POSIX
-}
module Gargantext.Viz.Phylo.View.Export
module Gargantext.Core.Viz.Phylo.View.Export
where
import Control.Lens hiding (Level)
......@@ -30,8 +30,8 @@ import qualified Data.Text.Lazy as T'
import qualified Data.GraphViz.Attributes.HTML as H
import Gargantext.Prelude
import Gargantext.Viz.Phylo hiding (Dot)
import Gargantext.Viz.Phylo.Tools
import Gargantext.Core.Viz.Phylo hiding (Dot)
import Gargantext.Core.Viz.Phylo.Tools
-- import Debug.Trace (trace)
......
{-|
Module : Gargantext.Viz.Phylo.Tools
Module : Gargantext.Core.Viz.Phylo.Tools
Description : Phylomemy Tools to build/manage it
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -11,7 +11,7 @@ Portability : POSIX
-}
module Gargantext.Viz.Phylo.View.Filters
module Gargantext.Core.Viz.Phylo.View.Filters
where
import Control.Lens hiding (makeLenses, both, Level)
......@@ -19,8 +19,8 @@ import Data.List (notElem,null,nub,(\\),intersect)
import Data.Maybe (isNothing)
import Data.Tuple (fst)
import Gargantext.Prelude
import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Tools
import Gargantext.Core.Viz.Phylo
import Gargantext.Core.Viz.Phylo.Tools
-- | To clean a PhyloView list of Nodes, Edges, etc after having filtered its Branches
......
{-|
Module : Gargantext.Viz.Phylo.Tools
Module : Gargantext.Core.Viz.Phylo.Tools
Description : Phylomemy Tools to build/manage it
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -11,7 +11,7 @@ Portability : POSIX
-}
module Gargantext.Viz.Phylo.View.Metrics
module Gargantext.Core.Viz.Phylo.View.Metrics
where
import Control.Lens hiding (makeLenses, both, Level)
......@@ -20,8 +20,8 @@ import Data.Map (insert)
import Data.Text (Text)
import Data.Tuple (fst, snd)
import Gargantext.Prelude
import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Tools
import Gargantext.Core.Viz.Phylo
import Gargantext.Core.Viz.Phylo.Tools
-- | To add a new meta Metric to a PhyloBranch
......
{-|
Module : Gargantext.Viz.Phylo.Tools
Module : Gargantext.Core.Viz.Phylo.Tools
Description : Phylomemy Tools to build/manage it
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -11,15 +11,15 @@ Portability : POSIX
-}
module Gargantext.Viz.Phylo.View.Sort
module Gargantext.Core.Viz.Phylo.View.Sort
where
import Control.Lens hiding (makeLenses, both, Level)
import Data.List (sortOn)
import Data.Tuple (fst, snd)
import Gargantext.Prelude
import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Tools
import Gargantext.Core.Viz.Phylo
import Gargantext.Core.Viz.Phylo.Tools
-- | To sort a PhyloView by Age
......
{-|
Module : Gargantext.Viz.Phylo.Tools
Module : Gargantext.Core.Viz.Phylo.Tools
Description : Phylomemy Tools to build/manage it
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -11,7 +11,7 @@ Portability : POSIX
-}
module Gargantext.Viz.Phylo.View.Taggers
module Gargantext.Core.Viz.Phylo.View.Taggers
where
import Control.Lens hiding (makeLenses, both, Level)
......@@ -21,10 +21,10 @@ import Data.Tuple (fst, snd)
import Data.Vector (Vector)
import Data.Map (Map, (!), empty, unionWith)
import Gargantext.Prelude
import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Tools
import Gargantext.Viz.Phylo.BranchMaker
import Gargantext.Viz.Phylo.Metrics
import Gargantext.Core.Viz.Phylo
import Gargantext.Core.Viz.Phylo.Tools
import Gargantext.Core.Viz.Phylo.BranchMaker
import Gargantext.Core.Viz.Phylo.Metrics
import qualified Data.Map as Map
import Control.Parallel.Strategies
-- import Debug.Trace (trace)
......
{-|
Module : Gargantext.Viz.Phylo.Tools
Module : Gargantext.Core.Viz.Phylo.Tools
Description : Phylomemy Tools to build/manage it
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -11,7 +11,7 @@ Portability : POSIX
-}
module Gargantext.Viz.Phylo.View.ViewMaker
module Gargantext.Core.Viz.Phylo.View.ViewMaker
where
import Control.Lens hiding (makeLenses, both, Level)
......@@ -21,14 +21,14 @@ import Data.Map (Map, empty, elems, unionWithKey, fromList)
import Data.Tuple (fst, snd)
import Data.Vector (Vector)
import Gargantext.Prelude
import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Tools
import Gargantext.Viz.Phylo.Metrics
import Gargantext.Viz.Phylo.View.Display
import Gargantext.Viz.Phylo.View.Filters
import Gargantext.Viz.Phylo.View.Metrics
import Gargantext.Viz.Phylo.View.Sort
import Gargantext.Viz.Phylo.View.Taggers
import Gargantext.Core.Viz.Phylo
import Gargantext.Core.Viz.Phylo.Tools
import Gargantext.Core.Viz.Phylo.Metrics
import Gargantext.Core.Viz.Phylo.View.Display
import Gargantext.Core.Viz.Phylo.View.Filters
import Gargantext.Core.Viz.Phylo.View.Metrics
import Gargantext.Core.Viz.Phylo.View.Sort
import Gargantext.Core.Viz.Phylo.View.Taggers
import qualified Data.Vector.Storable as VS
import Debug.Trace (trace)
......
......@@ -5,7 +5,7 @@
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Viz.Types where
module Gargantext.Core.Viz.Types where
import Data.Aeson.TH (deriveJSON)
import Data.Swagger
......
......@@ -26,7 +26,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.Viz.Graph
, module Gargantext.Core.Viz.Graph
)
where
......@@ -44,6 +44,6 @@ 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.Viz.Graph (HyperdataGraph(..), defaultHyperdataGraph)
import Gargantext.Core.Viz.Graph (HyperdataGraph(..), defaultHyperdataGraph)
......@@ -22,7 +22,7 @@ module Gargantext.Database.Admin.Types.Hyperdata.List
where
import Gargantext.Prelude
import Gargantext.Viz.Types (Histo(..))
import Gargantext.Core.Viz.Types (Histo(..))
import Gargantext.API.Ngrams.NTree (MyTree)
import Gargantext.Database.Admin.Types.Hyperdata.Prelude
import Gargantext.Database.Admin.Types.Metrics (ChartMetrics(..), Metrics)
......
......@@ -23,7 +23,7 @@ module Gargantext.Database.Admin.Types.Hyperdata.Phylo
import Gargantext.Prelude
import Gargantext.Database.Admin.Types.Hyperdata.Prelude
import Gargantext.Viz.Phylo (Phylo(..))
import Gargantext.Core.Viz.Phylo (Phylo(..))
------------------------------------------------------------------------
......
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