Commit 519719a9 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[WORKFLOW] cleaned, adding data2graph.

parent 54d4ebd0
...@@ -28,12 +28,13 @@ import Gargantext.Prelude ...@@ -28,12 +28,13 @@ import Gargantext.Prelude
import Gargantext.Viz.Graph.Index (score, createIndices, toIndex, fromIndex, cooc2mat, mat2map) import Gargantext.Viz.Graph.Index (score, createIndices, toIndex, fromIndex, cooc2mat, mat2map)
import Gargantext.Viz.Graph.Distances.Matrice (conditional', conditional) import Gargantext.Viz.Graph.Distances.Matrice (conditional', conditional)
import Gargantext.Viz.Graph.Index (Index) import Gargantext.Viz.Graph.Index (Index)
import Gargantext.Viz.Graph (Graph)
import Gargantext.Text.Metrics.Count (cooc, removeApax) import Gargantext.Text.Metrics.Count (cooc, removeApax)
import Gargantext.Text.Metrics import Gargantext.Text.Metrics
import Gargantext.Text.Terms (TermType(Multi, Mono), extractTerms) import Gargantext.Text.Terms (TermType(Multi, Mono), extractTerms)
import Gargantext.Text.Context (splitBy, SplitContext(Sentences)) import Gargantext.Text.Context (splitBy, SplitContext(Sentences))
import Data.Graph.Clustering.Louvain.CplusPlus (cLouvain) import Data.Graph.Clustering.Louvain.CplusPlus (cLouvain, LouvainNode)
{- {-
...@@ -46,6 +47,12 @@ import Data.Graph.Clustering.Louvain.CplusPlus (cLouvain) ...@@ -46,6 +47,12 @@ import Data.Graph.Clustering.Louvain.CplusPlus (cLouvain)
-} -}
-----------------------------------------------------------
data2graph :: Map (Int, Int) Int -> Map (Int, Int) Double -> [LouvainNode] -> Graph
data2graph = undefined
-----------------------------------------------------------
workflow lang path = do workflow lang path = do
-- Text <- IO Text <- FilePath -- Text <- IO Text <- FilePath
text <- readFile path text <- readFile path
...@@ -55,14 +62,16 @@ workflow lang path = do ...@@ -55,14 +62,16 @@ workflow lang path = do
-- TODO filter (\t -> not . elem t stopList) myterms -- TODO filter (\t -> not . elem t stopList) myterms
-- TODO groupBy (Stem | GroupList) -- TODO groupBy (Stem | GroupList)
-- @np FIXME optimization issue of filterCooc (too much memory consumed)
let myCooc = filterCooc $ removeApax $ cooc myterms let myCooc = filterCooc $ removeApax $ cooc myterms
--pure myCooc
-- Cooc -> Matrix -- Cooc -> Matrix
--let (ti, fi) = createIndices myCooc let (ti, _) = createIndices myCooc
-- @np FIXME optimization issue of filterCooc (too much memory consumed)
pure myCooc
-- Matrix -> Clustering -- Matrix -> Clustering
-- pure $ bestpartition False $ map2graph $ toIndex ti myCooc let distance = score conditional $ toIndex ti myCooc
--partitions <- cLouvain $ toIndex ti $ M.map (\v -> (fromIntegral v) :: Double) myCooc partitions <- cLouvain distance
--pure partitions --pure partitions
---- | Building : -> Graph -> JSON ---- | Building : -> Graph -> JSON
pure partitions
--pure $ data2graph myCooc distance partitions
...@@ -19,11 +19,14 @@ module Gargantext.Viz.Graph ...@@ -19,11 +19,14 @@ module Gargantext.Viz.Graph
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Data.Aeson.TH (deriveJSON) import Data.Aeson.TH (deriveJSON)
import Data.Text (Text) import Data.Text (Text)
import Data.Map (Map)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Core.Utils.Prefix (unPrefix) import Gargantext.Core.Utils.Prefix (unPrefix)
----------------------------------------------------------- import Data.Graph.Clustering.Louvain.CplusPlus (LouvainNode)
data TypeNode = Terms | Unknown data TypeNode = Terms | Unknown
deriving (Show, Generic) deriving (Show, Generic)
......
...@@ -109,7 +109,6 @@ conditional m = run (miniMax $ proba (dim m) $ map fromIntegral $ use m) ...@@ -109,7 +109,6 @@ conditional m = run (miniMax $ proba (dim m) $ map fromIntegral $ use m)
conditional' :: Matrix Int -> (Matrix InclusionExclusion, Matrix SpecificityGenericity) conditional' :: Matrix Int -> (Matrix InclusionExclusion, Matrix SpecificityGenericity)
conditional' m = (run $ ie $ map fromIntegral $ use m, run $ sg $ map fromIntegral $ use m) conditional' m = (run $ ie $ map fromIntegral $ use m, run $ sg $ map fromIntegral $ use m)
where where
ie :: Acc (Matrix Double) -> Acc (Matrix Double) ie :: Acc (Matrix Double) -> Acc (Matrix Double)
ie mat = map (\x -> x / (2*n-1)) $ zipWith (+) (xs mat) (ys mat) ie mat = map (\x -> x / (2*n-1)) $ zipWith (+) (xs mat) (ys mat)
sg :: Acc (Matrix Double) -> Acc (Matrix Double) sg :: Acc (Matrix Double) -> Acc (Matrix Double)
......
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