Commit 782e08bb authored by Alexandre Delanoë's avatar Alexandre Delanoë

[Ord] G.C.Methods.Distances

parent e4f4b071
...@@ -30,7 +30,7 @@ import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs) ...@@ -30,7 +30,7 @@ import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs)
import Gargantext.API.Admin.Types (HasSettings) import Gargantext.API.Admin.Types (HasSettings)
import Gargantext.API.Prelude (GargServer, simuLogs) import Gargantext.API.Prelude (GargServer, simuLogs)
import Gargantext.Core.Viz.Graph.API (recomputeGraph) import Gargantext.Core.Viz.Graph.API (recomputeGraph)
import Gargantext.Core.Viz.Graph.Distances (GraphMetric(..), Distance(..)) import Gargantext.Core.Methods.Distances (GraphMetric(..), Distance(..))
import Gargantext.Database.Action.Flow.Pairing (pairing) import Gargantext.Database.Action.Flow.Pairing (pairing)
import Gargantext.Database.Action.Flow.Types (FlowCmdM) import Gargantext.Database.Action.Flow.Types (FlowCmdM)
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
......
...@@ -11,7 +11,7 @@ Portability : POSIX ...@@ -11,7 +11,7 @@ Portability : POSIX
{-# LANGUAGE Strict #-} {-# LANGUAGE Strict #-}
module Gargantext.Core.Viz.Graph.Distances module Gargantext.Core.Methods.Distances
where where
import Data.Aeson import Data.Aeson
...@@ -20,7 +20,7 @@ import Data.Swagger ...@@ -20,7 +20,7 @@ import Data.Swagger
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Gargantext.Prelude (Ord, Eq, Int, Double) import Gargantext.Prelude (Ord, Eq, Int, Double)
import Gargantext.Prelude (Show) import Gargantext.Prelude (Show)
import Gargantext.Core.Viz.Graph.Distances.Matrice (measureConditional, distributional) import Gargantext.Core.Methods.Distances.Matrice (measureConditional, distributional)
import Prelude (Enum, Bounded, minBound, maxBound) import Prelude (Enum, Bounded, minBound, maxBound)
import Test.QuickCheck (elements) import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary import Test.QuickCheck.Arbitrary
......
{-| {-|
Module : Gargantext.Graph.Distances.Conditional Module : Gargantext.Core.Methods.Distances
Description : Description :
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -12,7 +12,7 @@ Motivation and definition of the @Conditional@ distance. ...@@ -12,7 +12,7 @@ Motivation and definition of the @Conditional@ distance.
{-# LANGUAGE BangPatterns #-} {-# LANGUAGE BangPatterns #-}
{-# LANGUAGE Strict #-} {-# LANGUAGE Strict #-}
module Gargantext.Core.Viz.Graph.Distances.Conditional module Gargantext.Core.Methods.Distances.Conditional
where where
import Data.Matrix hiding (identity) import Data.Matrix hiding (identity)
......
{-| {-|
Module : Gargantext.Graph.Distances.Distributional Module : Gargantext.Core.Methods.Distances
Description : Description :
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -14,7 +14,7 @@ Motivation and definition of the @Distributional@ distance. ...@@ -14,7 +14,7 @@ Motivation and definition of the @Distributional@ distance.
{-# LANGUAGE Strict #-} {-# LANGUAGE Strict #-}
module Gargantext.Core.Viz.Graph.Distances.Distributional module Gargantext.Core.Methods.Distances.Distributional
where where
import Data.Matrix hiding (identity) import Data.Matrix hiding (identity)
......
{-| {-|
Module : Gargantext.Graph.Distances.Matrix Module : Gargantext.Core.Methods.Distances.Matrice
Description : Description :
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -27,7 +27,7 @@ Implementation use Accelerate library which enables GPU and CPU computation: ...@@ -27,7 +27,7 @@ Implementation use Accelerate library which enables GPU and CPU computation:
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ViewPatterns #-} {-# LANGUAGE ViewPatterns #-}
module Gargantext.Core.Viz.Graph.Distances.Matrice module Gargantext.Core.Methods.Distances.Matrice
where where
import qualified Data.Foldable as P (foldl1) import qualified Data.Foldable as P (foldl1)
......
...@@ -6,7 +6,7 @@ Maintainer : team@gargantext.org ...@@ -6,7 +6,7 @@ Maintainer : team@gargantext.org
Stability : experimental Stability : experimental
Portability : POSIX Portability : POSIX
- Result of Pyremiel 2019 - Result of the workshop, Pyremiel 2019
- First written by Bruno Gaume in Python (see below for details) - First written by Bruno Gaume in Python (see below for details)
- Then written by Alexandre Delanoë in Haskell (see below for details) - Then written by Alexandre Delanoë in Haskell (see below for details)
...@@ -49,7 +49,7 @@ def fast_maximal_cliques(g): ...@@ -49,7 +49,7 @@ def fast_maximal_cliques(g):
module Gargantext.Core.Viz.Graph.MaxClique module Gargantext.Core.Methods.Graph.MaxClique
where where
import Data.Maybe (catMaybes) import Data.Maybe (catMaybes)
...@@ -62,12 +62,12 @@ import Data.Set (fromList, toList, isSubsetOf) ...@@ -62,12 +62,12 @@ import Data.Set (fromList, toList, isSubsetOf)
import Data.Graph.Inductive hiding (Graph, neighbors, subgraph, (&)) import Data.Graph.Inductive hiding (Graph, neighbors, subgraph, (&))
import Gargantext.Core.Viz.Graph.FGL (Graph_Undirected, degree, neighbors, mkGraphUfromEdges) import Gargantext.Core.Viz.Graph.FGL (Graph_Undirected, degree, neighbors, mkGraphUfromEdges)
import Gargantext.Core.Viz.Graph.Tools (cooc2graph', Threshold) import Gargantext.Core.Viz.Graph.Tools (cooc2graph', Threshold)
import Gargantext.Core.Viz.Graph.Distances (Distance) import Gargantext.Core.Methods.Distances (Distance)
import Gargantext.Core.Viz.Graph.Index (createIndices, toIndex) import Gargantext.Core.Viz.Graph.Index (createIndices, toIndex)
type Graph = Graph_Undirected type Graph = Graph_Undirected
type Neighbor = Node type Neighbor = Node
-- | getMaxCliques -- | getMaxCliques
-- TODO chose distance order -- TODO chose distance order
getMaxCliques :: Ord a => Distance -> Threshold -> Map (a, a) Int -> [[a]] getMaxCliques :: Ord a => Distance -> Threshold -> Map (a, a) Int -> [[a]]
......
...@@ -26,29 +26,24 @@ This document defines basic of Text definitions according to Gargantext.. ...@@ -26,29 +26,24 @@ This document defines basic of Text definitions according to Gargantext..
module Gargantext.Core.Text.Examples module Gargantext.Core.Text.Examples
where where
import Data.Ord (Down(..)) import Data.Array.Accelerate (toList, Matrix)
import qualified Data.List as L
import Data.Map (Map) import Data.Map (Map)
import qualified Data.Map as M import Data.Ord (Down(..))
import Data.Text (Text) import Data.Text (Text)
import qualified Data.Text as T
import Data.Tuple.Extra (both) import Data.Tuple.Extra (both)
import Data.Array.Accelerate (toList, Matrix)
import Gargantext.Prelude
import Gargantext.Core.Text.Metrics.Count (occurrences, cooc)
import Gargantext.Core.Text.Terms (TermType(MonoMulti), terms)
import Gargantext.Core (Lang(EN)) import Gargantext.Core (Lang(EN))
import Gargantext.Core.Types (Terms(..), Label) import Gargantext.Core.Methods.Distances.Matrice
import Gargantext.Core.Text.Context (splitBy, SplitContext(Sentences)) import Gargantext.Core.Text.Context (splitBy, SplitContext(Sentences))
import Gargantext.Core.Text.Metrics.Count (Grouped) import Gargantext.Core.Text.Metrics.Count (Grouped)
import Gargantext.Core.Viz.Graph.Distances.Matrice import Gargantext.Core.Text.Metrics.Count (occurrences, cooc)
import Gargantext.Core.Text.Terms (TermType(MonoMulti), terms)
import Gargantext.Core.Types (Terms(..), Label)
import Gargantext.Core.Viz.Graph.Index import Gargantext.Core.Viz.Graph.Index
import Gargantext.Prelude
import qualified Data.Array.Accelerate as DAA import qualified Data.Array.Accelerate as DAA
import qualified Data.List as List
import qualified Data.Map as Map
import qualified Data.Text as Text
-- | Sentences -- | Sentences
-- Let be a list of Texts: ['Data.Text.Text']. Each text in this example is a sentence. -- Let be a list of Texts: ['Data.Text.Text']. Each text in this example is a sentence.
...@@ -70,7 +65,7 @@ ex_sentences = [ "There is a table with a glass of wine and a spoon." ...@@ -70,7 +65,7 @@ ex_sentences = [ "There is a table with a glass of wine and a spoon."
-- >>> T.intercalate (T.pack " ") ex_sentences -- >>> T.intercalate (T.pack " ") ex_sentences
-- "There is a table with a glass of wine and a spoon. I can see the glass on the table. There was only a spoon on that table. The glass just fall from the table, pouring wine everywhere. I wish the glass did not contain wine." -- "There is a table with a glass of wine and a spoon. I can see the glass on the table. There was only a spoon on that table. The glass just fall from the table, pouring wine everywhere. I wish the glass did not contain wine."
ex_paragraph :: Text ex_paragraph :: Text
ex_paragraph = T.intercalate " " ex_sentences ex_paragraph = Text.intercalate " " ex_sentences
-- | Let split sentences by Contexts of text. -- | Let split sentences by Contexts of text.
-- More about 'Gargantext.Core.Text.Context' -- More about 'Gargantext.Core.Text.Context'
...@@ -88,10 +83,10 @@ ex_terms = mapM (terms (MonoMulti EN)) $ splitBy (Sentences 0) ex_paragraph ...@@ -88,10 +83,10 @@ ex_terms = mapM (terms (MonoMulti EN)) $ splitBy (Sentences 0) ex_paragraph
-- | Test the Occurrences -- | Test the Occurrences
-- --
-- >>> occurrences <$> L.concat <$> ex_terms -- >>> occurrences <$> List.concat <$> ex_terms
-- fromList [(fromList ["glass"],fromList [(["glass"],4)]),(fromList ["spoon"],fromList [(["spoon"],2)]),(fromList ["tabl"],fromList [(["table"],4)]),(fromList ["wine"],fromList [(["wine"],3)])] -- fromList [(fromList ["glass"],fromList [(["glass"],4)]),(fromList ["spoon"],fromList [(["spoon"],2)]),(fromList ["tabl"],fromList [(["table"],4)]),(fromList ["wine"],fromList [(["wine"],3)])]
ex_occ :: IO (Map Grouped (Map Terms Int)) ex_occ :: IO (Map Grouped (Map Terms Int))
ex_occ = occurrences <$> L.concat <$> ex_terms ex_occ = occurrences <$> List.concat <$> ex_terms
-- | Test the cooccurrences -- | Test the cooccurrences
-- Use the 'Gargantext.Core.Text.Metrics.Count.cooc' function. -- Use the 'Gargantext.Core.Text.Metrics.Count.cooc' function.
...@@ -132,6 +127,6 @@ incExcSpeGen_sorted m = both ordonne (incExcSpeGen $ cooc2mat ti m) ...@@ -132,6 +127,6 @@ incExcSpeGen_sorted m = both ordonne (incExcSpeGen $ cooc2mat ti m)
where where
(ti,fi) = createIndices m (ti,fi) = createIndices m
ordonne x = sortWith (Down . snd) ordonne x = sortWith (Down . snd)
$ zip (map snd $ M.toList fi) (toList x) $ zip (map snd $ Map.toList fi) (toList x)
...@@ -20,7 +20,7 @@ module Gargantext.Core.Text.Metrics ...@@ -20,7 +20,7 @@ module Gargantext.Core.Text.Metrics
--import Math.KMeans (kmeans, euclidSq, elements) --import Math.KMeans (kmeans, euclidSq, elements)
import Data.Map (Map) import Data.Map (Map)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Core.Viz.Graph.Distances.Matrice import Gargantext.Core.Methods.Distances.Matrice
import Gargantext.Core.Viz.Graph.Index import Gargantext.Core.Viz.Graph.Index
import Gargantext.Core.Statistics (pcaReduceTo, Dimension(..)) import Gargantext.Core.Statistics (pcaReduceTo, Dimension(..))
import qualified Data.Array.Accelerate as DAA import qualified Data.Array.Accelerate as DAA
......
...@@ -27,7 +27,7 @@ import qualified Text.Read as T ...@@ -27,7 +27,7 @@ import qualified Text.Read as T
import Gargantext.Core.Types (ListId) import Gargantext.Core.Types (ListId)
import Gargantext.Database.Admin.Types.Hyperdata.Prelude import Gargantext.Database.Admin.Types.Hyperdata.Prelude
import Gargantext.Database.Admin.Types.Node (NodeId) import Gargantext.Database.Admin.Types.Node (NodeId)
import Gargantext.Core.Viz.Graph.Distances (GraphMetric) import Gargantext.Core.Methods.Distances (GraphMetric)
import Gargantext.Prelude import Gargantext.Prelude
......
...@@ -48,7 +48,7 @@ import Gargantext.Prelude ...@@ -48,7 +48,7 @@ import Gargantext.Prelude
import Gargantext.Core.Viz.Graph import Gargantext.Core.Viz.Graph
import Gargantext.Core.Viz.Graph.GEXF () import Gargantext.Core.Viz.Graph.GEXF ()
import Gargantext.Core.Viz.Graph.Tools -- (cooc2graph) import Gargantext.Core.Viz.Graph.Tools -- (cooc2graph)
import Gargantext.Core.Viz.Graph.Distances (Distance(..), GraphMetric(..)) import Gargantext.Core.Methods.Distances (Distance(..), GraphMetric(..))
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | There is no Delete specific API for Graph since it can be deleted -- | There is no Delete specific API for Graph since it can be deleted
......
...@@ -24,7 +24,7 @@ import Gargantext.Prelude ...@@ -24,7 +24,7 @@ import Gargantext.Prelude
import Gargantext.Core.Statistics import Gargantext.Core.Statistics
import Gargantext.Core.Viz.Graph import Gargantext.Core.Viz.Graph
import Gargantext.Core.Viz.Graph.Bridgeness (bridgeness) import Gargantext.Core.Viz.Graph.Bridgeness (bridgeness)
import Gargantext.Core.Viz.Graph.Distances (Distance(..), measure) import Gargantext.Core.Methods.Distances (Distance(..), measure)
import Gargantext.Core.Viz.Graph.Index (createIndices, toIndex, map2mat, mat2map, Index) import Gargantext.Core.Viz.Graph.Index (createIndices, toIndex, map2mat, mat2map, Index)
import Gargantext.Core.Viz.Graph.IGraph (mkGraphUfromEdges) import Gargantext.Core.Viz.Graph.IGraph (mkGraphUfromEdges)
import Gargantext.Core.Methods.Graph.BAC.Proxemy (confluence) import Gargantext.Core.Methods.Graph.BAC.Proxemy (confluence)
......
...@@ -22,8 +22,8 @@ import Gargantext.Core.Viz.Phylo.TemporalMatching (adaptativeTemporalMatching, c ...@@ -22,8 +22,8 @@ import Gargantext.Core.Viz.Phylo.TemporalMatching (adaptativeTemporalMatching, c
import Gargantext.Core.Viz.Phylo.SynchronicClustering (synchronicClustering) import Gargantext.Core.Viz.Phylo.SynchronicClustering (synchronicClustering)
import Gargantext.Core.Text.Context (TermList) import Gargantext.Core.Text.Context (TermList)
import Gargantext.Core.Text.Metrics.FrequentItemSet (fisWithSizePolyMap, Size(..)) import Gargantext.Core.Text.Metrics.FrequentItemSet (fisWithSizePolyMap, Size(..))
import Gargantext.Core.Viz.Graph.MaxClique (getMaxCliques) import Gargantext.Core.Methods.Graph.MaxClique (getMaxCliques)
import Gargantext.Core.Viz.Graph.Distances (Distance(Conditional)) import Gargantext.Core.Methods.Distances (Distance(Conditional))
import Control.DeepSeq (NFData) import Control.DeepSeq (NFData)
import Control.Parallel.Strategies (parList, rdeepseq, using) import Control.Parallel.Strategies (parList, rdeepseq, using)
......
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