Commit eade2d55 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FEAT] adding pipeline.

parent 2cdbaa72
......@@ -7,7 +7,6 @@ Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
<<<<<<< HEAD
Script to start gargantext with different modes (Dev, Prod, Mock).
-}
......
......@@ -19,3 +19,9 @@ module Gargantext (
import Gargantext.Database
-- import Gargantext.Ngrams
-- import Gargantext.Utils
......@@ -42,8 +42,10 @@ type Label = [Text]
data Terms = Terms { _terms_label :: Label
, _terms_stem :: Stems
} deriving (Show, Ord)
} deriving (Ord)
instance Show Terms where
show (Terms l s) = show l
-- class Inclusion where include
--instance Eq Terms where
-- (==) (Terms _ s1) (Terms _ s2) = s1 `S.isSubsetOf` s2
......
{-|
Module : Gargantext.Pipeline
Description : Server API
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# LANGUAGE NoImplicitPrelude #-}
module Gargantext.Pipeline
where
import Data.Text.IO (readFile)
import Gargantext.Core
import Gargantext.Prelude
import Gargantext.Text.Metrics.Occurrences
import Gargantext.Text.Terms
import Gargantext.Text.Context
pipeline pth = do
text <- readFile pth
let contexts = splitBy Sentences 4 text
cooc <$> map occurrences <$> mapM (terms Mono FR) contexts
-- todo
-- Cooc map -> Matrix
-- distributional or conditional
-- Matrix -> Graph
......@@ -36,7 +36,7 @@ import Protolude ( Bool(True, False), Int, Double, Integer
, putStrLn
, head, flip
, Ord, Integral, Foldable, RealFrac, Monad, filter
, reverse, map, zip, drop, take, zipWith
, reverse, map, mapM, zip, drop, take, zipWith
, sum, fromIntegral, length, fmap, foldl, foldl'
, takeWhile, sqrt, undefined, identity
, abs, min, max, maximum, minimum, return, snd, truncate
......
......@@ -43,9 +43,7 @@ import Data.Attoparsec.Text
------------------------------------------------------------------------
import Gargantext.Prelude
import Gargantext.Core.Types
------------------------------------------------------------------------
type Occ a = Map a Int
type Cooc a = Map (a, a) Int
type FIS a = Map (Set a) Int
......@@ -68,7 +66,6 @@ type Grouped = Stems
--fromList [((fromList ["blue"],fromList ["lagoon"]),2),((fromList ["lagoon"],fromList ["red"]),2)]
----
cooc :: (Ord b, Num a) => [Map b a] -> Map (b, b) a
cooc ts = cooc' $ map cooc'' ts
......
......@@ -58,3 +58,10 @@ $(deriveJSON (unPrefix "g_") ''Graph)
-----------------------------------------------------------
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