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

[REFACT] Text -> Core

parent 2f9e26f5
...@@ -25,11 +25,11 @@ import Data.Text (Text, unwords, unpack) ...@@ -25,11 +25,11 @@ import Data.Text (Text, unwords, unpack)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Database.Admin.Types.Hyperdata (HyperdataDocument(..)) import Gargantext.Database.Admin.Types.Hyperdata (HyperdataDocument(..))
import Gargantext.Text.Context (TermList) import Gargantext.Core.Text.Context (TermList)
import Gargantext.Text.Corpus.Parsers.CSV (csv_title, csv_abstract, csv_publication_year) import Gargantext.Core.Text.Corpus.Parsers.CSV (csv_title, csv_abstract, csv_publication_year)
import Gargantext.Text.Corpus.Parsers (FileFormat(..),parseFile) import Gargantext.Core.Text.Corpus.Parsers (FileFormat(..),parseFile)
import Gargantext.Text.List.CSV (csvMapTermList) import Gargantext.Core.Text.List.CSV (csvMapTermList)
import Gargantext.Text.Terms.WithList (Patterns, buildPatterns, extractTermsWithList) import Gargantext.Core.Text.Terms.WithList (Patterns, buildPatterns, extractTermsWithList)
import Gargantext.Viz.AdaptativePhylo import Gargantext.Viz.AdaptativePhylo
import Gargantext.Viz.Phylo.PhyloMaker (toPhylo) import Gargantext.Viz.Phylo.PhyloMaker (toPhylo)
import Gargantext.Viz.Phylo.PhyloTools (printIOMsg, printIOComment) import Gargantext.Viz.Phylo.PhyloTools (printIOMsg, printIOComment)
...@@ -44,7 +44,7 @@ import Control.Concurrent.Async (mapConcurrently) ...@@ -44,7 +44,7 @@ import Control.Concurrent.Async (mapConcurrently)
import qualified Data.ByteString.Lazy as Lazy import qualified Data.ByteString.Lazy as Lazy
import qualified Data.Vector as Vector import qualified Data.Vector as Vector
import qualified Gargantext.Text.Corpus.Parsers.CSV as Csv import qualified Gargantext.Core.Text.Corpus.Parsers.CSV as Csv
--------------- ---------------
......
...@@ -22,8 +22,8 @@ import Data.Vector (Vector) ...@@ -22,8 +22,8 @@ import Data.Vector (Vector)
import qualified Data.Vector as V import qualified Data.Vector as V
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Text.Search import Gargantext.Core.Text.Search
import qualified Gargantext.Text.Corpus.Parsers.CSV as CSV import qualified Gargantext.Core.Text.Corpus.Parsers.CSV as CSV
------------------------------------------------------------------------ ------------------------------------------------------------------------
type Query = [S.Term] type Query = [S.Term]
......
...@@ -49,13 +49,13 @@ import Prelude ((>>)) ...@@ -49,13 +49,13 @@ import Prelude ((>>))
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Core import Gargantext.Core
import Gargantext.Core.Types import Gargantext.Core.Types
import Gargantext.Text.Terms import Gargantext.Core.Text.Terms
import Gargantext.Text.Context import Gargantext.Core.Text.Context
import Gargantext.Text.Terms.WithList import Gargantext.Core.Text.Terms.WithList
import Gargantext.Text.Corpus.Parsers.CSV (readFile, csv_title, csv_abstract, csv_publication_year) import Gargantext.Core.Text.Corpus.Parsers.CSV (readFile, csv_title, csv_abstract, csv_publication_year)
import Gargantext.Text.List.CSV (csvMapTermList) import Gargantext.Core.Text.List.CSV (csvMapTermList)
import Gargantext.Text.Terms (terms) import Gargantext.Core.Text.Terms (terms)
import Gargantext.Text.Metrics.Count (coocOnContexts, Coocs) import Gargantext.Core.Text.Metrics.Count (coocOnContexts, Coocs)
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- OUTPUT format -- OUTPUT format
......
...@@ -29,7 +29,7 @@ import Gargantext.Database.Admin.Types.Hyperdata (toHyperdataDocument) ...@@ -29,7 +29,7 @@ import Gargantext.Database.Admin.Types.Hyperdata (toHyperdataDocument)
import Gargantext.Database.Admin.Types.Node (CorpusId) import Gargantext.Database.Admin.Types.Node (CorpusId)
import Gargantext.Database.Prelude (Cmd) import Gargantext.Database.Prelude (Cmd)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Text.Corpus.Parsers (FileFormat(..)) import Gargantext.Core.Text.Corpus.Parsers (FileFormat(..))
import Prelude (read) import Prelude (read)
import System.Environment (getArgs) import System.Environment (getArgs)
import qualified Data.Text as Text import qualified Data.Text as Text
......
...@@ -28,11 +28,11 @@ import GHC.IO (FilePath) ...@@ -28,11 +28,11 @@ import GHC.IO (FilePath)
import Gargantext.Database.Admin.Types.Hyperdata import Gargantext.Database.Admin.Types.Hyperdata
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Text.Context (TermList) import Gargantext.Core.Text.Context (TermList)
import Gargantext.Text.Corpus.Parsers (FileFormat(..),parseFile) import Gargantext.Core.Text.Corpus.Parsers (FileFormat(..),parseFile)
import Gargantext.Text.Corpus.Parsers.CSV (csv_title, csv_abstract, csv_publication_year) import Gargantext.Core.Text.Corpus.Parsers.CSV (csv_title, csv_abstract, csv_publication_year)
import Gargantext.Text.List.CSV (csvMapTermList) import Gargantext.Core.Text.List.CSV (csvMapTermList)
import Gargantext.Text.Terms.WithList import Gargantext.Core.Text.Terms.WithList
import Gargantext.Viz.Phylo import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.LevelMaker import Gargantext.Viz.Phylo.LevelMaker
import Gargantext.Viz.Phylo.Tools import Gargantext.Viz.Phylo.Tools
...@@ -45,7 +45,7 @@ import qualified Data.List as DL ...@@ -45,7 +45,7 @@ import qualified Data.List as DL
import qualified Data.Map as DM import qualified Data.Map as DM
import qualified Data.Text as DT import qualified Data.Text as DT
import qualified Data.Vector as DV import qualified Data.Vector as DV
import qualified Gargantext.Text.Corpus.Parsers.CSV as CSV import qualified Gargantext.Core.Text.Corpus.Parsers.CSV as CSV
import qualified Prelude as P import qualified Prelude as P
......
...@@ -58,26 +58,26 @@ library: ...@@ -58,26 +58,26 @@ library:
- Gargantext.Database.Admin.Types.Node - Gargantext.Database.Admin.Types.Node
- Gargantext.Prelude - Gargantext.Prelude
- Gargantext.Prelude.Utils - Gargantext.Prelude.Utils
- Gargantext.Text - Gargantext.Core.Text
- Gargantext.Text.Context - Gargantext.Core.Text.Context
- Gargantext.Text.Corpus.Parsers - Gargantext.Core.Text.Corpus.Parsers
- Gargantext.Text.Corpus.Parsers.Date.Parsec - Gargantext.Core.Text.Corpus.Parsers.Date.Parsec
- Gargantext.Text.Corpus.API - Gargantext.Core.Text.Corpus.API
- Gargantext.Text.Corpus.Parsers.CSV - Gargantext.Core.Text.Corpus.Parsers.CSV
- Gargantext.Text.Examples - Gargantext.Core.Text.Examples
- Gargantext.Text.List.CSV - Gargantext.Core.Text.List.CSV
- Gargantext.Text.Metrics - Gargantext.Core.Text.Metrics
- Gargantext.Text.Metrics.TFICF - Gargantext.Core.Text.Metrics.TFICF
- Gargantext.Text.Metrics.CharByChar - Gargantext.Core.Text.Metrics.CharByChar
- Gargantext.Text.Metrics.Count - Gargantext.Core.Text.Metrics.Count
- Gargantext.Text.Search - Gargantext.Core.Text.Search
- Gargantext.Text.Terms - Gargantext.Core.Text.Terms
- Gargantext.Text.Terms.Mono - Gargantext.Core.Text.Terms.Mono
- Gargantext.Text.Terms.Multi.Lang.En - Gargantext.Core.Text.Terms.Multi.Lang.En
- Gargantext.Text.Terms.Multi.Lang.Fr - Gargantext.Core.Text.Terms.Multi.Lang.Fr
- Gargantext.Text.Terms.Multi.RAKE - Gargantext.Core.Text.Terms.Multi.RAKE
- Gargantext.Text.Terms.WithList - Gargantext.Core.Text.Terms.WithList
- Gargantext.Text.Flow - Gargantext.Core.Text.Flow
- Gargantext.Viz.Graph - Gargantext.Viz.Graph
- Gargantext.Viz.Graph.Distances.Matrice - Gargantext.Viz.Graph.Distances.Matrice
- Gargantext.Viz.Graph.Index - Gargantext.Viz.Graph.Index
......
...@@ -15,7 +15,6 @@ module Gargantext ( module Gargantext.API ...@@ -15,7 +15,6 @@ module Gargantext ( module Gargantext.API
, module Gargantext.Core , module Gargantext.Core
, module Gargantext.Database , module Gargantext.Database
, module Gargantext.Prelude , module Gargantext.Prelude
, module Gargantext.Text
-- , module Gargantext.Viz -- , module Gargantext.Viz
) where ) where
...@@ -23,5 +22,4 @@ import Gargantext.API ...@@ -23,5 +22,4 @@ import Gargantext.API
import Gargantext.Core import Gargantext.Core
import Gargantext.Database import Gargantext.Database
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Text
--import Gargantext.Viz --import Gargantext.Viz
...@@ -39,7 +39,7 @@ import Gargantext.Database.Query.Table.Node.Error (HasNodeError) ...@@ -39,7 +39,7 @@ import Gargantext.Database.Query.Table.Node.Error (HasNodeError)
import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata) import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata)
import Gargantext.Database.Schema.Node (node_hyperdata) import Gargantext.Database.Schema.Node (node_hyperdata)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Text.Metrics (Scored(..)) import Gargantext.Core.Text.Metrics (Scored(..))
import Gargantext.Viz.Chart import Gargantext.Viz.Chart
import Gargantext.Viz.Types import Gargantext.Viz.Types
import qualified Gargantext.Database.Action.Metrics as Metrics import qualified Gargantext.Database.Action.Metrics as Metrics
......
...@@ -72,7 +72,7 @@ import qualified Gargantext.Database.Action.Delete as Action (deleteNode) ...@@ -72,7 +72,7 @@ import qualified Gargantext.Database.Action.Delete as Action (deleteNode)
import qualified Gargantext.Database.Query.Table.Node.Update as U (update, Update(..)) import qualified Gargantext.Database.Query.Table.Node.Update as U (update, Update(..))
{- {-
import qualified Gargantext.Text.List.Learn as Learn import qualified Gargantext.Core.Text.List.Learn as Learn
import qualified Data.Vector as Vec import qualified Data.Vector as Vec
--} --}
......
...@@ -42,7 +42,7 @@ import Gargantext.Database.Admin.Types.Hyperdata (HyperdataAnnuaire(..), Hyperda ...@@ -42,7 +42,7 @@ import Gargantext.Database.Admin.Types.Hyperdata (HyperdataAnnuaire(..), Hyperda
import Gargantext.Database.Admin.Types.Hyperdata.Contact (hyperdataContact) import Gargantext.Database.Admin.Types.Hyperdata.Contact (hyperdataContact)
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
import Gargantext.Prelude (($), liftBase, (.), printDebug, pure) import Gargantext.Prelude (($), liftBase, (.), printDebug, pure)
import Gargantext.Text.Terms (TermType(..)) import Gargantext.Core.Text.Terms (TermType(..))
import Servant import Servant
import Servant.Job.Async (JobFunction(..), serveJobsAPI) import Servant.Job.Async (JobFunction(..), serveJobsAPI)
import Test.QuickCheck (elements) import Test.QuickCheck (elements)
......
...@@ -58,8 +58,8 @@ import Gargantext.Database.Query.Table.Node (getNodeWith) ...@@ -58,8 +58,8 @@ import Gargantext.Database.Query.Table.Node (getNodeWith)
import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata) import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata)
import Gargantext.Database.Schema.Node (node_hyperdata) import Gargantext.Database.Schema.Node (node_hyperdata)
import qualified Gargantext.Prelude.Utils as GPU import qualified Gargantext.Prelude.Utils as GPU
import qualified Gargantext.Text.Corpus.API as API import qualified Gargantext.Core.Text.Corpus.API as API
import qualified Gargantext.Text.Corpus.Parsers as Parser (FileFormat(..), parseFormat) import qualified Gargantext.Core.Text.Corpus.Parsers as Parser (FileFormat(..), parseFormat)
------------------------------------------------------------------------ ------------------------------------------------------------------------
{- {-
......
...@@ -14,7 +14,7 @@ Portability : POSIX ...@@ -14,7 +14,7 @@ Portability : POSIX
module Gargantext.Core.Flow.Ngrams where module Gargantext.Core.Flow.Ngrams where
-- import Gargantext.Text.Terms.WithList (filterWith) -- import Gargantext.Core.Text.Terms.WithList (filterWith)
...@@ -18,7 +18,7 @@ import Control.Lens (Lens') ...@@ -18,7 +18,7 @@ import Control.Lens (Lens')
import Data.Map (Map) import Data.Map (Map)
import Data.Maybe (Maybe) import Data.Maybe (Maybe)
-- import Control.Applicative -- import Control.Applicative
import Gargantext.Text (HasText(..)) import Gargantext.Core.Text (HasText(..))
import Gargantext.Core.Types.Main (HashId) import Gargantext.Core.Types.Main (HashId)
import Gargantext.Database.Admin.Types.Hyperdata import Gargantext.Database.Admin.Types.Hyperdata
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
......
{-| {-|
Module : Gargantext.Text Module : Gargantext.Core.Text
Description : Ngrams tools Description : Ngrams tools
Copyright : (c) CNRS, 2018 Copyright : (c) CNRS, 2018
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -12,7 +12,7 @@ Text gathers terms in unit of contexts. ...@@ -12,7 +12,7 @@ Text gathers terms in unit of contexts.
-} -}
module Gargantext.Text module Gargantext.Core.Text
where where
import Data.Text (Text, split) import Data.Text (Text, split)
......
{-| {-|
Module : Gargantext.Text.Context Module : Gargantext.Core.Text.Context
Description : How to manage contexts of texts ? Description : How to manage contexts of texts ?
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -20,14 +20,14 @@ How to split contexts is describes in this module. ...@@ -20,14 +20,14 @@ How to split contexts is describes in this module.
-} -}
module Gargantext.Text.Context module Gargantext.Core.Text.Context
where where
import Data.Text (Text, pack, unpack) import Data.Text (Text, pack, unpack)
import Data.String (IsString) import Data.String (IsString)
import Text.HTML.TagSoup (parseTags, isTagText, Tag(..)) import Text.HTML.TagSoup (parseTags, isTagText, Tag(..))
import Gargantext.Text import Gargantext.Core.Text
import Gargantext.Prelude hiding (length) import Gargantext.Prelude hiding (length)
------------------------------------------------------------------------ ------------------------------------------------------------------------
...@@ -49,7 +49,7 @@ data SplitContext = Chars Int | Sentences Int | Paragraphs Int ...@@ -49,7 +49,7 @@ data SplitContext = Chars Int | Sentences Int | Paragraphs Int
-- | splitBy contexts of Chars or Sentences or Paragraphs -- | splitBy contexts of Chars or Sentences or Paragraphs
-- To see some examples at a higher level (sentences and paragraph), see -- To see some examples at a higher level (sentences and paragraph), see
-- 'Gargantext.Text.Examples.ex_terms' -- 'Gargantext.Core.Text.Examples.ex_terms'
-- --
-- >>> splitBy (Chars 0) (pack "abcde") -- >>> splitBy (Chars 0) (pack "abcde")
-- ["a","b","c","d","e"] -- ["a","b","c","d","e"]
......
{-| {-|
Module : Gargantext.Text.Convert Module : Gargantext.Core.Text.Convert
Description : All parsers of Gargantext in one file. Description : All parsers of Gargantext in one file.
Copyright : (c) CNRS, 2017 Copyright : (c) CNRS, 2017
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -13,13 +13,13 @@ Format Converter. ...@@ -13,13 +13,13 @@ Format Converter.
{-# LANGUAGE PackageImports #-} {-# LANGUAGE PackageImports #-}
module Gargantext.Text.Convert (risPress2csvWrite) module Gargantext.Core.Text.Convert (risPress2csvWrite)
where where
import System.FilePath (FilePath()) -- , takeExtension) import System.FilePath (FilePath()) -- , takeExtension)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Text.Corpus.Parsers.CSV (writeDocs2Csv) import Gargantext.Core.Text.Corpus.Parsers.CSV (writeDocs2Csv)
import Gargantext.Text.Corpus.Parsers (parseFile, FileFormat(..)) import Gargantext.Core.Text.Corpus.Parsers (parseFile, FileFormat(..))
risPress2csvWrite :: FilePath -> IO () risPress2csvWrite :: FilePath -> IO ()
......
{-| {-|
Module : Gargantext.Text.Corpus.API Module : Gargantext.Core.Text.Corpus.API
Description : All crawlers of Gargantext in one file. Description : All crawlers of Gargantext in one file.
Copyright : (c) CNRS, 2017 Copyright : (c) CNRS, 2017
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -11,7 +11,7 @@ Portability : POSIX ...@@ -11,7 +11,7 @@ Portability : POSIX
{-# LANGUAGE InstanceSigs #-} {-# LANGUAGE InstanceSigs #-}
module Gargantext.Text.Corpus.API module Gargantext.Core.Text.Corpus.API
( ExternalAPIs(..) ( ExternalAPIs(..)
, Query , Query
, Limit , Limit
...@@ -25,10 +25,10 @@ import Gargantext.API.Admin.Orchestrator.Types (ExternalAPIs(..), externalAPIs) ...@@ -25,10 +25,10 @@ import Gargantext.API.Admin.Orchestrator.Types (ExternalAPIs(..), externalAPIs)
import Gargantext.Core (Lang(..)) import Gargantext.Core (Lang(..))
import Gargantext.Database.Admin.Types.Hyperdata (HyperdataDocument(..)) import Gargantext.Database.Admin.Types.Hyperdata (HyperdataDocument(..))
import Gargantext.Prelude import Gargantext.Prelude
import qualified Gargantext.Text.Corpus.API.Hal as HAL import qualified Gargantext.Core.Text.Corpus.API.Hal as HAL
import qualified Gargantext.Text.Corpus.API.Isidore as ISIDORE import qualified Gargantext.Core.Text.Corpus.API.Isidore as ISIDORE
import qualified Gargantext.Text.Corpus.API.Istex as ISTEX import qualified Gargantext.Core.Text.Corpus.API.Istex as ISTEX
import qualified Gargantext.Text.Corpus.API.Pubmed as PUBMED import qualified Gargantext.Core.Text.Corpus.API.Pubmed as PUBMED
-- | Get External API metadata main function -- | Get External API metadata main function
get :: ExternalAPIs get :: ExternalAPIs
......
{-| {-|
Module : Gargantext.Text.Corpus.API.Hal Module : Gargantext.Core.Text.Corpus.API.Hal
Description : Pubmed API connection Description : Pubmed API connection
Copyright : (c) CNRS, 2017 Copyright : (c) CNRS, 2017
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -10,7 +10,7 @@ Portability : POSIX ...@@ -10,7 +10,7 @@ Portability : POSIX
-} -}
module Gargantext.Text.Corpus.API.Hal module Gargantext.Core.Text.Corpus.API.Hal
where where
import Data.Maybe import Data.Maybe
...@@ -19,7 +19,7 @@ import Data.Text (Text, pack, intercalate) ...@@ -19,7 +19,7 @@ import Data.Text (Text, pack, intercalate)
import Gargantext.Core (Lang(..)) import Gargantext.Core (Lang(..))
import Gargantext.Database.Admin.Types.Hyperdata (HyperdataDocument(..)) import Gargantext.Database.Admin.Types.Hyperdata (HyperdataDocument(..))
import Gargantext.Prelude import Gargantext.Prelude
import qualified Gargantext.Text.Corpus.Parsers.Date as Date import qualified Gargantext.Core.Text.Corpus.Parsers.Date as Date
import qualified HAL as HAL import qualified HAL as HAL
import qualified HAL.Client as HAL import qualified HAL.Client as HAL
import qualified HAL.Doc.Corpus as HAL import qualified HAL.Doc.Corpus as HAL
......
{-| {-|
Module : Gargantext.Text.Corpus.API.Isidore Module : Gargantext.Core.Text.Corpus.API.Isidore
Description : To query French Humanities publication database from its API Description : To query French Humanities publication database from its API
Copyright : (c) CNRS, 2019-Present Copyright : (c) CNRS, 2019-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -11,7 +11,7 @@ Portability : POSIX ...@@ -11,7 +11,7 @@ Portability : POSIX
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
module Gargantext.Text.Corpus.API.Isidore where module Gargantext.Core.Text.Corpus.API.Isidore where
import System.FilePath (FilePath()) import System.FilePath (FilePath())
import Data.Text (Text) import Data.Text (Text)
...@@ -21,10 +21,10 @@ import Gargantext.Database.Admin.Types.Hyperdata (HyperdataDocument(..)) ...@@ -21,10 +21,10 @@ import Gargantext.Database.Admin.Types.Hyperdata (HyperdataDocument(..))
import Gargantext.Prelude import Gargantext.Prelude
import Isidore.Client import Isidore.Client
import Servant.Client import Servant.Client
import qualified Gargantext.Text.Corpus.Parsers.Date as Date import qualified Gargantext.Core.Text.Corpus.Parsers.Date as Date
import qualified Isidore as Isidore import qualified Isidore as Isidore
import Gargantext.Text.Corpus.Parsers.CSV (writeDocs2Csv) import Gargantext.Core.Text.Corpus.Parsers.CSV (writeDocs2Csv)
import Gargantext.Text.Corpus.Parsers (cleanText) import Gargantext.Core.Text.Corpus.Parsers (cleanText)
-- | TODO work with the ServantErr -- | TODO work with the ServantErr
get :: Lang -> Maybe Isidore.Limit get :: Lang -> Maybe Isidore.Limit
......
{-| {-|
Module : Gargantext.Text.Corpus.API.Istex Module : Gargantext.Core.Text.Corpus.API.Istex
Description : Pubmed API connection Description : Pubmed API connection
Copyright : (c) CNRS, 2017 Copyright : (c) CNRS, 2017
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -10,7 +10,7 @@ Portability : POSIX ...@@ -10,7 +10,7 @@ Portability : POSIX
-} -}
module Gargantext.Text.Corpus.API.Istex module Gargantext.Core.Text.Corpus.API.Istex
where where
import Data.Either (either) import Data.Either (either)
...@@ -22,7 +22,7 @@ import Data.Text (Text, pack) ...@@ -22,7 +22,7 @@ import Data.Text (Text, pack)
import Gargantext.Core (Lang(..)) import Gargantext.Core (Lang(..))
import Gargantext.Database.Admin.Types.Hyperdata (HyperdataDocument(..)) import Gargantext.Database.Admin.Types.Hyperdata (HyperdataDocument(..))
import Gargantext.Prelude import Gargantext.Prelude
import qualified Gargantext.Text.Corpus.Parsers.Date as Date import qualified Gargantext.Core.Text.Corpus.Parsers.Date as Date
import qualified ISTEX as ISTEX import qualified ISTEX as ISTEX
import qualified ISTEX.Client as ISTEX import qualified ISTEX.Client as ISTEX
......
{-| {-|
Module : Gargantext.Text.Corpus.API.Pubmed Module : Gargantext.Core.Text.Corpus.API.Pubmed
Description : Pubmed API connection Description : Pubmed API connection
Copyright : (c) CNRS, 2017 Copyright : (c) CNRS, 2017
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -10,7 +10,7 @@ Portability : POSIX ...@@ -10,7 +10,7 @@ Portability : POSIX
-} -}
module Gargantext.Text.Corpus.API.Pubmed module Gargantext.Core.Text.Corpus.API.Pubmed
where where
import Data.Maybe import Data.Maybe
......
{-| {-|
Module : Gargantext.Text.Corpus.Parsers Module : Gargantext.Core.Text.Corpus.Parsers
Description : All parsers of Gargantext in one file. Description : All parsers of Gargantext in one file.
Copyright : (c) CNRS, 2017 Copyright : (c) CNRS, 2017
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -20,7 +20,7 @@ please follow the types. ...@@ -20,7 +20,7 @@ please follow the types.
{-# LANGUAGE PackageImports #-} {-# LANGUAGE PackageImports #-}
module Gargantext.Text.Corpus.Parsers (FileFormat(..), clean, parseFile, cleanText, parseFormat) module Gargantext.Core.Text.Corpus.Parsers (FileFormat(..), clean, parseFile, cleanText, parseFormat)
where where
import "zip" Codec.Archive.Zip (withArchive, getEntry, getEntries) import "zip" Codec.Archive.Zip (withArchive, getEntry, getEntries)
...@@ -39,18 +39,18 @@ import Data.Tuple.Extra (both, first, second) ...@@ -39,18 +39,18 @@ import Data.Tuple.Extra (both, first, second)
import Gargantext.Core (Lang(..)) import Gargantext.Core (Lang(..))
import Gargantext.Database.Admin.Types.Hyperdata (HyperdataDocument(..)) import Gargantext.Database.Admin.Types.Hyperdata (HyperdataDocument(..))
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Text.Corpus.Parsers.CSV (parseHal, parseHal', parseCsv, parseCsv') import Gargantext.Core.Text.Corpus.Parsers.CSV (parseHal, parseHal', parseCsv, parseCsv')
import Gargantext.Text.Corpus.Parsers.RIS.Presse (presseEnrich) import Gargantext.Core.Text.Corpus.Parsers.RIS.Presse (presseEnrich)
import Gargantext.Text.Learn (detectLangDefault) import Gargantext.Core.Text.Learn (detectLangDefault)
import System.FilePath (FilePath(), takeExtension) import System.FilePath (FilePath(), takeExtension)
import qualified Data.ByteString as DB import qualified Data.ByteString as DB
import qualified Data.ByteString.Char8 as DBC import qualified Data.ByteString.Char8 as DBC
import qualified Data.ByteString.Lazy as DBL import qualified Data.ByteString.Lazy as DBL
import qualified Data.Map as DM import qualified Data.Map as DM
import qualified Data.Text as DT import qualified Data.Text as DT
import qualified Gargantext.Text.Corpus.Parsers.Date as Date import qualified Gargantext.Core.Text.Corpus.Parsers.Date as Date
import qualified Gargantext.Text.Corpus.Parsers.RIS as RIS import qualified Gargantext.Core.Text.Corpus.Parsers.RIS as RIS
import qualified Gargantext.Text.Corpus.Parsers.WOS as WOS import qualified Gargantext.Core.Text.Corpus.Parsers.WOS as WOS
------------------------------------------------------------------------ ------------------------------------------------------------------------
type ParseError = String type ParseError = String
......
{-| {-|
Module : Gargantext.Text.Corpus.Parsers.CSV Module : Gargantext.Core.Text.Corpus.Parsers.CSV
Description : Description :
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -12,7 +12,7 @@ CSV parser for Gargantext corpus files. ...@@ -12,7 +12,7 @@ CSV parser for Gargantext corpus files.
-} -}
module Gargantext.Text.Corpus.Parsers.CSV where module Gargantext.Core.Text.Corpus.Parsers.CSV where
import Control.Applicative import Control.Applicative
import qualified Data.ByteString as BS import qualified Data.ByteString as BS
...@@ -30,8 +30,8 @@ import GHC.Word (Word8) ...@@ -30,8 +30,8 @@ import GHC.Word (Word8)
import Gargantext.Database.Admin.Types.Hyperdata (HyperdataDocument(..)) import Gargantext.Database.Admin.Types.Hyperdata (HyperdataDocument(..))
import Gargantext.Prelude hiding (length) import Gargantext.Prelude hiding (length)
import Gargantext.Text import Gargantext.Core.Text
import Gargantext.Text.Context import Gargantext.Core.Text.Context
--------------------------------------------------------------- ---------------------------------------------------------------
headerCsvGargV3 :: Header headerCsvGargV3 :: Header
......
{-| {-|
Module : Gargantext.Text.Corpus.Parsers.Date Module : Gargantext.Core.Text.Corpus.Parsers.Date
Description : Some utils to parse dates Description : Some utils to parse dates
Copyright : (c) CNRS 2017-present Copyright : (c) CNRS 2017-present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -10,12 +10,12 @@ Portability : POSIX ...@@ -10,12 +10,12 @@ Portability : POSIX
According to the language of the text, parseDateRaw returns date as Text: According to the language of the text, parseDateRaw returns date as Text:
TODO : Add some tests TODO : Add some tests
import Gargantext.Text.Corpus.Parsers.Date as DGP import Gargantext.Core.Text.Corpus.Parsers.Date as DGP
DGP.parseDateRaw DGP.FR "12 avril 2010" == "2010-04-12T00:00:00.000+00:00" DGP.parseDateRaw DGP.FR "12 avril 2010" == "2010-04-12T00:00:00.000+00:00"
-} -}
module Gargantext.Text.Corpus.Parsers.Date (parse, parseRaw, dateSplit, Year, Month, Day) where module Gargantext.Core.Text.Corpus.Parsers.Date (parse, parseRaw, dateSplit, Year, Month, Day) where
import Data.HashMap.Strict as HM hiding (map) import Data.HashMap.Strict as HM hiding (map)
import Data.Text (Text, unpack, splitOn, pack) import Data.Text (Text, unpack, splitOn, pack)
......
{-| {-|
Module : Gargantext.Text.Corpus.Parsers.Date.Attoparsec Module : Gargantext.Core.Text.Corpus.Parsers.Date.Attoparsec
Description : Description :
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -11,7 +11,7 @@ Portability : POSIX ...@@ -11,7 +11,7 @@ Portability : POSIX
-} -}
module Gargantext.Text.Corpus.Parsers.Date.Attoparsec module Gargantext.Core.Text.Corpus.Parsers.Date.Attoparsec
where where
import Control.Applicative ((<*)) import Control.Applicative ((<*))
......
{-| {-|
Module : Gargantext.Text.Corpus.Parsers.Date Module : Gargantext.Core.Text.Corpus.Parsers.Date
Description : Some utils to parse dates Description : Some utils to parse dates
Copyright : (c) CNRS 2017-present Copyright : (c) CNRS 2017-present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -10,7 +10,7 @@ Portability : POSIX ...@@ -10,7 +10,7 @@ Portability : POSIX
-} -}
module Gargantext.Text.Corpus.Parsers.Date.Parsec module Gargantext.Core.Text.Corpus.Parsers.Date.Parsec
where where
import Control.Monad ((=<<)) import Control.Monad ((=<<))
......
{-| {-|
Module : Gargantext.Text.Corpus.Parsers.GrandDebat Module : Gargantext.Core.Text.Corpus.Parsers.GrandDebat
Description : Grand Debat Types Description : Grand Debat Types
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -23,7 +23,7 @@ _flowCorpusDebat u n l fp = do ...@@ -23,7 +23,7 @@ _flowCorpusDebat u n l fp = do
-} -}
module Gargantext.Text.Corpus.Parsers.GrandDebat module Gargantext.Core.Text.Corpus.Parsers.GrandDebat
where where
import Data.Aeson (ToJSON, FromJSON) import Data.Aeson (ToJSON, FromJSON)
......
{-| {-|
Module : Gargantext.Text.Corpus.Parsers.Isidore Module : Gargantext.Core.Text.Corpus.Parsers.Isidore
Description : To query French Humanities publication database Description : To query French Humanities publication database
Copyright : (c) CNRS, 2019-Present Copyright : (c) CNRS, 2019-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -17,7 +17,7 @@ TODO: ...@@ -17,7 +17,7 @@ TODO:
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
module Gargantext.Text.Corpus.Parsers.Isidore where module Gargantext.Core.Text.Corpus.Parsers.Isidore where
import Control.Lens hiding (contains) import Control.Lens hiding (contains)
import Data.ByteString.Lazy (ByteString) import Data.ByteString.Lazy (ByteString)
......
{-| {-|
Module : Gargantext.Text.Corpus.Parsers.Json2Csv Module : Gargantext.Core.Text.Corpus.Parsers.Json2Csv
Description : Description :
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -14,7 +14,7 @@ Json parser to export towoard CSV GargV3 format. ...@@ -14,7 +14,7 @@ Json parser to export towoard CSV GargV3 format.
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
module Gargantext.Text.Corpus.Parsers.Json2Csv (json2csv, readPatents) module Gargantext.Core.Text.Corpus.Parsers.Json2Csv (json2csv, readPatents)
where where
import Prelude (read) import Prelude (read)
...@@ -25,7 +25,7 @@ import Data.Text (Text, unpack) ...@@ -25,7 +25,7 @@ import Data.Text (Text, unpack)
import Gargantext.Core.Utils.Prefix (unPrefix) import Gargantext.Core.Utils.Prefix (unPrefix)
import Gargantext.Prelude import Gargantext.Prelude
import System.IO (FilePath) import System.IO (FilePath)
import Gargantext.Text.Corpus.Parsers.CSV (CsvDoc(..), writeFile, headerCsvGargV3) import Gargantext.Core.Text.Corpus.Parsers.CSV (CsvDoc(..), writeFile, headerCsvGargV3)
import Data.Vector (fromList) import Data.Vector (fromList)
data Patent = Patent { _patent_title :: Text data Patent = Patent { _patent_title :: Text
......
{-| {-|
Module : Gargantext.Text.Corpus.Parsers.RIS Module : Gargantext.Core.Text.Corpus.Parsers.RIS
Description : Description :
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -17,7 +17,7 @@ citation programs to exchange data. ...@@ -17,7 +17,7 @@ citation programs to exchange data.
-} -}
module Gargantext.Text.Corpus.Parsers.RIS (parser, onField, fieldWith, lines) where module Gargantext.Core.Text.Corpus.Parsers.RIS (parser, onField, fieldWith, lines) where
import Data.List (lookup) import Data.List (lookup)
import Control.Applicative import Control.Applicative
......
{-| {-|
Module : Gargantext.Text.Corpus.Parsers.RIS.Presse Module : Gargantext.Core.Text.Corpus.Parsers.RIS.Presse
Description : Description :
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -12,7 +12,7 @@ Presse RIS format parser for Europresse Database. ...@@ -12,7 +12,7 @@ Presse RIS format parser for Europresse Database.
-} -}
module Gargantext.Text.Corpus.Parsers.RIS.Presse (presseEnrich) where module Gargantext.Core.Text.Corpus.Parsers.RIS.Presse (presseEnrich) where
import Data.List (lookup) import Data.List (lookup)
import Data.Either (either) import Data.Either (either)
...@@ -20,9 +20,9 @@ import Data.Tuple.Extra (first, both, uncurry) ...@@ -20,9 +20,9 @@ import Data.Tuple.Extra (first, both, uncurry)
import Data.Attoparsec.ByteString (parseOnly) import Data.Attoparsec.ByteString (parseOnly)
import Data.ByteString (ByteString, length) import Data.ByteString (ByteString, length)
import Gargantext.Prelude hiding (takeWhile, take, length) import Gargantext.Prelude hiding (takeWhile, take, length)
import Gargantext.Text.Corpus.Parsers.RIS (onField) import Gargantext.Core.Text.Corpus.Parsers.RIS (onField)
import Gargantext.Core (Lang(..)) import Gargantext.Core (Lang(..))
import qualified Gargantext.Text.Corpus.Parsers.Date.Attoparsec as Date import qualified Gargantext.Core.Text.Corpus.Parsers.Date.Attoparsec as Date
......
{-| {-|
Module : Gargantext.Text.Corpus.Parsers.WOS Module : Gargantext.Core.Text.Corpus.Parsers.WOS
Description : Description :
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -12,14 +12,14 @@ commentary with @some markup@. ...@@ -12,14 +12,14 @@ commentary with @some markup@.
-} -}
module Gargantext.Text.Corpus.Parsers.WOS (parser, keys) where module Gargantext.Core.Text.Corpus.Parsers.WOS (parser, keys) where
import Control.Applicative import Control.Applicative
import Data.Attoparsec.ByteString (Parser, string, takeTill, take, manyTill, many1) import Data.Attoparsec.ByteString (Parser, string, takeTill, take, manyTill, many1)
import Data.Attoparsec.ByteString.Char8 (anyChar, isEndOfLine) import Data.Attoparsec.ByteString.Char8 (anyChar, isEndOfLine)
import Data.ByteString (ByteString) import Data.ByteString (ByteString)
import Data.ByteString.Char8 (pack) import Data.ByteString.Char8 (pack)
import Gargantext.Text.Corpus.Parsers.RIS (fieldWith) import Gargantext.Core.Text.Corpus.Parsers.RIS (fieldWith)
import Prelude hiding (takeWhile, take, concat, readFile, lines, concat) import Prelude hiding (takeWhile, take, concat, readFile, lines, concat)
------------------------------------------------------------- -------------------------------------------------------------
......
{-| {-|
Module : Gargantext.Text.Corpus.Parsers.Wikimedia Module : Gargantext.Core.Text.Corpus.Parsers.Wikimedia
Description : Parser for Wikimedia dump Description : Parser for Wikimedia dump
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -7,14 +7,14 @@ Maintainer : team@gargantext.org ...@@ -7,14 +7,14 @@ Maintainer : team@gargantext.org
Stability : experimental Stability : experimental
Portability : POSIX Portability : POSIX
@Gargantext.Text.Corpus.Parsers.Wikimedia@: @Gargantext.Core.Text.Corpus.Parsers.Wikimedia@:
This module provide a parser for wikipedia dump. This module provide a parser for wikipedia dump.
This include an xml parser for wikipedia's xml This include an xml parser for wikipedia's xml
and an wikimedia to plaintext converter for the wikipedia text field and an wikimedia to plaintext converter for the wikipedia text field
-} -}
module Gargantext.Text.Corpus.Parsers.Wikimedia module Gargantext.Core.Text.Corpus.Parsers.Wikimedia
where where
import Control.Monad.Catch import Control.Monad.Catch
......
{-| {-|
Module : Gargantext.Text.Examples Module : Gargantext.Core.Text.Examples
Description : Minimal Examples to test behavior of the functions. Description : Minimal Examples to test behavior of the functions.
Copyright : (c) CNRS, 2017 - present Copyright : (c) CNRS, 2017 - present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -23,7 +23,7 @@ This document defines basic of Text definitions according to Gargantext.. ...@@ -23,7 +23,7 @@ This document defines basic of Text definitions according to Gargantext..
{-# LANGUAGE BangPatterns #-} {-# LANGUAGE BangPatterns #-}
module Gargantext.Text.Examples module Gargantext.Core.Text.Examples
where where
import Data.Ord (Down(..)) import Data.Ord (Down(..))
...@@ -39,12 +39,12 @@ import Data.Tuple.Extra (both) ...@@ -39,12 +39,12 @@ import Data.Tuple.Extra (both)
import Data.Array.Accelerate (toList, Matrix) import Data.Array.Accelerate (toList, Matrix)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Text.Metrics.Count (occurrences, cooc) import Gargantext.Core.Text.Metrics.Count (occurrences, cooc)
import Gargantext.Text.Terms (TermType(MonoMulti), terms) 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.Types (Terms(..), Label)
import Gargantext.Text.Context (splitBy, SplitContext(Sentences)) import Gargantext.Core.Text.Context (splitBy, SplitContext(Sentences))
import Gargantext.Text.Metrics.Count (Grouped) import Gargantext.Core.Text.Metrics.Count (Grouped)
import Gargantext.Viz.Graph.Distances.Matrice import Gargantext.Viz.Graph.Distances.Matrice
import Gargantext.Viz.Graph.Index import Gargantext.Viz.Graph.Index
...@@ -73,7 +73,7 @@ ex_paragraph :: Text ...@@ -73,7 +73,7 @@ ex_paragraph :: Text
ex_paragraph = T.intercalate " " ex_sentences ex_paragraph = T.intercalate " " ex_sentences
-- | Let split sentences by Contexts of text. -- | Let split sentences by Contexts of text.
-- More about 'Gargantext.Text.Context' -- More about 'Gargantext.Core.Text.Context'
-- --
-- >>> ex_sentences == splitBy (Sentences 0) ex_paragraph -- >>> ex_sentences == splitBy (Sentences 0) ex_paragraph
-- True -- True
...@@ -94,7 +94,7 @@ ex_occ :: IO (Map Grouped (Map Terms Int)) ...@@ -94,7 +94,7 @@ ex_occ :: IO (Map Grouped (Map Terms Int))
ex_occ = occurrences <$> L.concat <$> ex_terms ex_occ = occurrences <$> L.concat <$> ex_terms
-- | Test the cooccurrences -- | Test the cooccurrences
-- Use the 'Gargantext.Text.Metrics.Count.cooc' function. -- Use the 'Gargantext.Core.Text.Metrics.Count.cooc' function.
-- --
-- >>> cooc <$> ex_terms -- >>> cooc <$> ex_terms
-- fromList [((["glass"],["glass"]),4),((["spoon"],["glass"]),1),((["spoon"],["spoon"]),2),((["table"],["glass"]),3),((["table"],["spoon"]),2),((["table"],["table"]),4),((["wine"],["glass"]),3),((["wine"],["spoon"]),1),((["wine"],["table"]),2),((["wine"],["wine"]),3)] -- fromList [((["glass"],["glass"]),4),((["spoon"],["glass"]),1),((["spoon"],["spoon"]),2),((["table"],["glass"]),3),((["table"],["spoon"]),2),((["table"],["table"]),4),((["wine"],["glass"]),3),((["wine"],["spoon"]),1),((["wine"],["table"]),2),((["wine"],["wine"]),3)]
......
{-| {-|
Module : Gargantext.Text.Flow Module : Gargantext.Core.Text.Flow
Description : Server API Description : Server API
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -12,7 +12,7 @@ From text to viz, all the flow of texts in Gargantext. ...@@ -12,7 +12,7 @@ From text to viz, all the flow of texts in Gargantext.
-} -}
module Gargantext.Text.Flow module Gargantext.Core.Text.Flow
where where
import qualified Data.Text as T import qualified Data.Text as T
......
{-| {-|
Module : Gargantext.Text.Terms.Stop Module : Gargantext.Core.Text.Terms.Stop
Description : Mono Terms module Description : Mono Terms module
Copyright : (c) CNRS, 2017 - present Copyright : (c) CNRS, 2017 - present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -16,7 +16,7 @@ TODO: ...@@ -16,7 +16,7 @@ TODO:
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
module Gargantext.Text.Learn -- (detectLang, detectLangs, stopList) module Gargantext.Core.Text.Learn -- (detectLang, detectLangs, stopList)
where where
import Codec.Serialise import Codec.Serialise
...@@ -37,14 +37,14 @@ import qualified Data.ByteString.Lazy as BSL ...@@ -37,14 +37,14 @@ import qualified Data.ByteString.Lazy as BSL
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Prelude.Utils import Gargantext.Prelude.Utils
import Gargantext.Core (Lang(..), allLangs) import Gargantext.Core (Lang(..), allLangs)
import Gargantext.Text.Terms.Mono (words) import Gargantext.Core.Text.Terms.Mono (words)
import Gargantext.Text.Metrics.Count (occurrencesWith) import Gargantext.Core.Text.Metrics.Count (occurrencesWith)
import qualified Gargantext.Text.Samples.FR as FR import qualified Gargantext.Core.Text.Samples.FR as FR
import qualified Gargantext.Text.Samples.EN as EN import qualified Gargantext.Core.Text.Samples.EN as EN
--import qualified Gargantext.Text.Samples.DE as DE --import qualified Gargantext.Core.Text.Samples.DE as DE
--import qualified Gargantext.Text.Samples.SP as SP --import qualified Gargantext.Core.Text.Samples.SP as SP
--import qualified Gargantext.Text.Samples.CH as CH --import qualified Gargantext.Core.Text.Samples.CH as CH
------------------------------------------------------------------------ ------------------------------------------------------------------------
data Candidate = Candidate { stop :: Double data Candidate = Candidate { stop :: Double
......
{-| {-|
Module : Gargantext.Text.Ngrams.Lists Module : Gargantext.Core.Text.Ngrams.Lists
Description : Tools to build lists Description : Tools to build lists
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -10,7 +10,7 @@ Portability : POSIX ...@@ -10,7 +10,7 @@ Portability : POSIX
-} -}
module Gargantext.Text.List module Gargantext.Core.Text.List
where where
-- import Data.Either (partitionEithers, Either(..)) -- import Data.Either (partitionEithers, Either(..))
...@@ -22,12 +22,12 @@ import Gargantext.API.Ngrams (NgramsElement, mkNgramsElement, RootParent(..), mS ...@@ -22,12 +22,12 @@ import Gargantext.API.Ngrams (NgramsElement, mkNgramsElement, RootParent(..), mS
import Gargantext.Core (Lang(..)) import Gargantext.Core (Lang(..))
import Gargantext.Core.Types (ListType(..), MasterCorpusId, UserCorpusId, Ordering(..)) import Gargantext.Core.Types (ListType(..), MasterCorpusId, UserCorpusId, Ordering(..))
import Gargantext.Database.Action.Metrics.NgramsByNode (getTficf, ngramsGroup, getNodesByNgramsUser, groupNodesByNgramsWith) import Gargantext.Database.Action.Metrics.NgramsByNode (getTficf, ngramsGroup, getNodesByNgramsUser, groupNodesByNgramsWith)
import Gargantext.Text.Metrics.TFICF (sortTficf) import Gargantext.Core.Text.Metrics.TFICF (sortTficf)
import Gargantext.Database.Prelude (Cmd) import Gargantext.Database.Prelude (Cmd)
import Gargantext.Database.Schema.Ngrams (NgramsType(..)) import Gargantext.Database.Schema.Ngrams (NgramsType(..))
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Text.List.Learn (Model(..)) import Gargantext.Core.Text.List.Learn (Model(..))
-- import Gargantext.Text.Metrics (takeScored) -- import Gargantext.Core.Text.Metrics (takeScored)
import qualified Data.Char as Char import qualified Data.Char as Char
import qualified Data.List as List import qualified Data.List as List
import qualified Data.Map as Map import qualified Data.Map as Map
......
{-| {-|
Module : Gargantext.Text.List.CSV Module : Gargantext.Core.Text.List.CSV
Description : Description :
Copyright : (c) CNRS, 2018-Present Copyright : (c) CNRS, 2018-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -12,7 +12,7 @@ CSV parser for Gargantext corpus files. ...@@ -12,7 +12,7 @@ CSV parser for Gargantext corpus files.
-} -}
module Gargantext.Text.List.CSV where module Gargantext.Core.Text.List.CSV where
import GHC.IO (FilePath) import GHC.IO (FilePath)
...@@ -31,7 +31,7 @@ import Data.Vector (Vector) ...@@ -31,7 +31,7 @@ import Data.Vector (Vector)
import qualified Data.Vector as V import qualified Data.Vector as V
import Gargantext.Prelude hiding (length) import Gargantext.Prelude hiding (length)
import Gargantext.Text.Context import Gargantext.Core.Text.Context
------------------------------------------------------------------------ ------------------------------------------------------------------------
......
{-| {-|
Module : Gargantext.Text.List.Learn Module : Gargantext.Core.Text.List.Learn
Description : Learn to make lists Description : Learn to make lists
Copyright : (c) CNRS, 2018-Present Copyright : (c) CNRS, 2018-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -14,7 +14,7 @@ CSV parser for Gargantext corpus files. ...@@ -14,7 +14,7 @@ CSV parser for Gargantext corpus files.
{-# OPTIONS_GHC -fno-warn-orphans #-} {-# OPTIONS_GHC -fno-warn-orphans #-}
module Gargantext.Text.List.Learn module Gargantext.Core.Text.List.Learn
where where
import Control.Monad.Reader (MonadReader) import Control.Monad.Reader (MonadReader)
...@@ -25,7 +25,7 @@ import Data.Maybe (maybe) ...@@ -25,7 +25,7 @@ import Data.Maybe (maybe)
import Gargantext.Core.Types.Main (ListType(..), listTypeId, fromListTypeId) import Gargantext.Core.Types.Main (ListType(..), listTypeId, fromListTypeId)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Prelude.Utils import Gargantext.Prelude.Utils
import Gargantext.Text.Metrics.Count (occurrencesWith) import Gargantext.Core.Text.Metrics.Count (occurrencesWith)
import qualified Data.IntMap as IntMap import qualified Data.IntMap as IntMap
import qualified Data.List as List import qualified Data.List as List
import qualified Data.Map as Map import qualified Data.Map as Map
...@@ -87,7 +87,7 @@ type Param = Double ...@@ -87,7 +87,7 @@ type Param = Double
grid :: (MonadReader env m, MonadBase IO m, HasSettings env) grid :: (MonadReader env m, MonadBase IO m, HasSettings env)
=> Param -> Param -> Train -> [Tests] -> m (Maybe Model) => Param -> Param -> Train -> [Tests] -> m (Maybe Model)
grid _ _ _ [] = panic "Gargantext.Text.List.Learn.grid : empty test data" grid _ _ _ [] = panic "Gargantext.Core.Text.List.Learn.grid : empty test data"
grid s e tr te = do grid s e tr te = do
let let
grid' :: (MonadReader env m, MonadBase IO m, HasSettings env) grid' :: (MonadReader env m, MonadBase IO m, HasSettings env)
......
{-| {-|
Module : Gargantext.Text.Metrics Module : Gargantext.Core.Text.Metrics
Description : All parsers of Gargantext in one file. Description : All parsers of Gargantext in one file.
Copyright : (c) CNRS, 2017 - present Copyright : (c) CNRS, 2017 - present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -13,7 +13,7 @@ Mainly reexport functions in @Data.Text.Metrics@ ...@@ -13,7 +13,7 @@ Mainly reexport functions in @Data.Text.Metrics@
{-# LANGUAGE BangPatterns #-} {-# LANGUAGE BangPatterns #-}
module Gargantext.Text.Metrics module Gargantext.Core.Text.Metrics
where where
--import Data.Array.Accelerate ((:.)(..), Z(..)) --import Data.Array.Accelerate ((:.)(..), Z(..))
......
{-| {-|
Module : Gargantext.Text.Metrics.CharByChar Module : Gargantext.Core.Text.Metrics.CharByChar
Description : All parsers of Gargantext in one file. Description : All parsers of Gargantext in one file.
Copyright : (c) CNRS, 2017 - present Copyright : (c) CNRS, 2017 - present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -12,7 +12,7 @@ Mainly reexport functions in @Data.Text.Metrics@ ...@@ -12,7 +12,7 @@ Mainly reexport functions in @Data.Text.Metrics@
module Gargantext.Text.Metrics.CharByChar (levenshtein module Gargantext.Core.Text.Metrics.CharByChar (levenshtein
, levenshteinNorm , levenshteinNorm
, damerauLevenshtein , damerauLevenshtein
, damerauLevenshteinNorm , damerauLevenshteinNorm
......
{-| {-|
Module : Gargantext.Text.Metrics.Count Module : Gargantext.Core.Text.Metrics.Count
Description : Description :
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -23,7 +23,7 @@ Source : https://en.wikipedia.org/wiki/Type%E2%80%93token_distinction#Occurrence ...@@ -23,7 +23,7 @@ Source : https://en.wikipedia.org/wiki/Type%E2%80%93token_distinction#Occurrence
-} -}
module Gargantext.Text.Metrics.Count module Gargantext.Core.Text.Metrics.Count
where where
import Data.Text (Text) import Data.Text (Text)
...@@ -121,7 +121,6 @@ coocOn' fun ts = DMS.fromListWith (+) xs ...@@ -121,7 +121,6 @@ coocOn' fun ts = DMS.fromListWith (+) xs
------------------------------------------------------------------------ ------------------------------------------------------------------------
coocOnContexts :: (a -> [Text]) -> [[a]] -> Map ([Text], [Text]) Int coocOnContexts :: (a -> [Text]) -> [[a]] -> Map ([Text], [Text]) Int
coocOnContexts fun = DMS.fromListWith (+) . List.concat . map (coocOnSingleContext fun) coocOnContexts fun = DMS.fromListWith (+) . List.concat . map (coocOnSingleContext fun)
......
{-| {-|
Module : Gargantext.Text.Metrics.Freq Module : Gargantext.Core.Text.Metrics.Freq
Description : Some functions to count. Description : Some functions to count.
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -10,7 +10,7 @@ Portability : POSIX ...@@ -10,7 +10,7 @@ Portability : POSIX
-} -}
module Gargantext.Text.Metrics.Freq where module Gargantext.Core.Text.Metrics.Freq where
import Gargantext.Prelude import Gargantext.Prelude
import Data.Bool (otherwise) import Data.Bool (otherwise)
......
{-| {-|
Module : Gargantext.Text.Metrics.FrequentItemSet Module : Gargantext.Core.Text.Metrics.FrequentItemSet
Description : Ngrams tools Description : Ngrams tools
Copyright : (c) CNRS, 2018 Copyright : (c) CNRS, 2018
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -12,7 +12,7 @@ Domain Specific Language to manage Frequent Item Set (FIS) ...@@ -12,7 +12,7 @@ Domain Specific Language to manage Frequent Item Set (FIS)
-} -}
module Gargantext.Text.Metrics.FrequentItemSet module Gargantext.Core.Text.Metrics.FrequentItemSet
( Fis, Size(..) ( Fis, Size(..)
, occ_hlcm, cooc_hlcm , occ_hlcm, cooc_hlcm
, allFis, between , allFis, between
......
{-| {-|
Module : Gargantext.Text.Metrics.TFICF Module : Gargantext.Core.Text.Metrics.TFICF
Description : TFICF Ngrams tools Description : TFICF Ngrams tools
Copyright : (c) CNRS, 2017 Copyright : (c) CNRS, 2017
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -14,7 +14,7 @@ TFICF is a generalization of [TFIDF](https://en.wikipedia.org/wiki/Tf%E2%80%93id ...@@ -14,7 +14,7 @@ TFICF is a generalization of [TFIDF](https://en.wikipedia.org/wiki/Tf%E2%80%93id
-} -}
module Gargantext.Text.Metrics.TFICF ( TFICF module Gargantext.Core.Text.Metrics.TFICF ( TFICF
, TficfContext(..) , TficfContext(..)
, Total(..) , Total(..)
, Count(..) , Count(..)
......
{-| {-|
Module : Gargantext.Text.Samples.CH Module : Gargantext.Core.Text.Samples.CH
Description : Sample of Chinese Text Description : Sample of Chinese Text
Copyright : (c) CNRS, 2017 - present Copyright : (c) CNRS, 2017 - present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -14,7 +14,7 @@ Page : text mining ...@@ -14,7 +14,7 @@ Page : text mining
module Gargantext.Text.Samples.CH where module Gargantext.Core.Text.Samples.CH where
import Data.String (String) import Data.String (String)
......
{-| {-|
Module : Gargantext.Text.Samples.DE Module : Gargantext.Core.Text.Samples.DE
Description : Sample of German Text Description : Sample of German Text
Copyright : (c) CNRS, 2017 - present Copyright : (c) CNRS, 2017 - present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -13,7 +13,7 @@ Page : text mining ...@@ -13,7 +13,7 @@ Page : text mining
-} -}
module Gargantext.Text.Samples.DE where module Gargantext.Core.Text.Samples.DE where
import Data.String (String) import Data.String (String)
......
{-| {-|
Module : Gargantext.Text.Samples.EN Module : Gargantext.Core.Text.Samples.EN
Description : Sample of English Text Description : Sample of English Text
Copyright : (c) CNRS, 2017 - present Copyright : (c) CNRS, 2017 - present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -14,7 +14,7 @@ Page : text mining ...@@ -14,7 +14,7 @@ Page : text mining
module Gargantext.Text.Samples.EN where module Gargantext.Core.Text.Samples.EN where
import Data.String (String) import Data.String (String)
......
{-| {-|
Module : Gargantext.Text.Samples.FR Module : Gargantext.Core.Text.Samples.FR
Description : Sample of French Text Description : Sample of French Text
Copyright : (c) CNRS, 2017 - present Copyright : (c) CNRS, 2017 - present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -13,7 +13,7 @@ Page : text mining ...@@ -13,7 +13,7 @@ Page : text mining
-} -}
module Gargantext.Text.Samples.FR where module Gargantext.Core.Text.Samples.FR where
import Gargantext.Prelude ((<>)) import Gargantext.Prelude ((<>))
import Data.String (String) import Data.String (String)
......
{-| {-|
Module : Gargantext.Text.Samples.SP Module : Gargantext.Core.Text.Samples.SP
Description : Sample of Spanish Text Description : Sample of Spanish Text
Copyright : (c) CNRS, 2017 - present Copyright : (c) CNRS, 2017 - present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -13,7 +13,7 @@ Page : text mining ...@@ -13,7 +13,7 @@ Page : text mining
module Gargantext.Text.Samples.SP where module Gargantext.Core.Text.Samples.SP where
import Data.String (String) import Data.String (String)
......
{-| {-|
Module : Gargantext.Text.Search Module : Gargantext.Core.Text.Search
Description : All parsers of Gargantext in one file. Description : All parsers of Gargantext in one file.
Copyright : (c) CNRS, 2017 - present Copyright : (c) CNRS, 2017 - present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -15,7 +15,7 @@ Starting from this model, a specific Gargantext engine will be made ...@@ -15,7 +15,7 @@ Starting from this model, a specific Gargantext engine will be made
{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE NamedFieldPuns #-}
module Gargantext.Text.Search where module Gargantext.Core.Text.Search where
import Data.SearchEngine import Data.SearchEngine
...@@ -27,9 +27,9 @@ import Data.Ix ...@@ -27,9 +27,9 @@ import Data.Ix
import Data.Text (Text) import Data.Text (Text)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Text.Terms.Mono (monoTexts) import Gargantext.Core.Text.Terms.Mono (monoTexts)
import Gargantext.Text.Terms.Mono.Stem as ST import Gargantext.Core.Text.Terms.Mono.Stem as ST
import Gargantext.Text.Corpus.Parsers.CSV import Gargantext.Core.Text.Corpus.Parsers.CSV
type DocId = Int type DocId = Int
......
{-| {-|
Module : Gargantext.Text.Ngrams Module : Gargantext.Core.Text.Ngrams
Description : Ngrams definition and tools Description : Ngrams definition and tools
Copyright : (c) CNRS, 2017 - present Copyright : (c) CNRS, 2017 - present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -31,7 +31,7 @@ compute graph ...@@ -31,7 +31,7 @@ compute graph
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE ConstrainedClassMethods #-} {-# LANGUAGE ConstrainedClassMethods #-}
module Gargantext.Text.Terms module Gargantext.Core.Text.Terms
where where
import Control.Lens import Control.Lens
...@@ -45,14 +45,14 @@ import Gargantext.Core ...@@ -45,14 +45,14 @@ import Gargantext.Core
import Gargantext.Core.Types import Gargantext.Core.Types
import Gargantext.Core.Flow.Types import Gargantext.Core.Flow.Types
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Text (sentences, HasText(..)) import Gargantext.Core.Text (sentences, HasText(..))
import Gargantext.Text.Terms.Eleve (mainEleveWith, Tries, Token, buildTries, toToken) import Gargantext.Core.Text.Terms.Eleve (mainEleveWith, Tries, Token, buildTries, toToken)
import Gargantext.Database.Schema.Ngrams (Ngrams(..), NgramsType(..)) import Gargantext.Database.Schema.Ngrams (Ngrams(..), NgramsType(..))
import Gargantext.Text.Terms.Mono (monoTerms) import Gargantext.Core.Text.Terms.Mono (monoTerms)
import Gargantext.Database.Prelude (Cmd) import Gargantext.Database.Prelude (Cmd)
import Gargantext.Text.Terms.Mono.Stem (stem) import Gargantext.Core.Text.Terms.Mono.Stem (stem)
import Gargantext.Text.Terms.Mono.Token.En (tokenize) import Gargantext.Core.Text.Terms.Mono.Token.En (tokenize)
import Gargantext.Text.Terms.Multi (multiterms) import Gargantext.Core.Text.Terms.Multi (multiterms)
import qualified Data.List as List import qualified Data.List as List
import qualified Data.Set as Set import qualified Data.Set as Set
import qualified Data.Text as Text import qualified Data.Text as Text
......
{-| {-|
Module : Gargantext.Text.Terms.Eleve Module : Gargantext.Core.Text.Terms.Eleve
Description : Unsupervized Word segmentation Description : Unsupervized Word segmentation
Copyright : (c) CNRS, 2019-Present Copyright : (c) CNRS, 2019-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -24,7 +24,7 @@ Notes for current implementation: ...@@ -24,7 +24,7 @@ Notes for current implementation:
- TODO AD TEST: prop (Node c _e f) = c == Map.size f - TODO AD TEST: prop (Node c _e f) = c == Map.size f
- AD: Real ngrams extraction test - AD: Real ngrams extraction test
from Gargantext.Text.Terms import extractTermsUnsupervised from Gargantext.Core.Text.Terms import extractTermsUnsupervised
docs <- runCmdRepl $ selectDocs 1004 docs <- runCmdRepl $ selectDocs 1004
extractTermsUnsupervised 3 $ DT.intercalate " " extractTermsUnsupervised 3 $ DT.intercalate " "
$ catMaybes $ catMaybes
...@@ -35,7 +35,7 @@ Notes for current implementation: ...@@ -35,7 +35,7 @@ Notes for current implementation:
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeFamilies #-}
module Gargantext.Text.Terms.Eleve where module Gargantext.Core.Text.Terms.Eleve where
-- import Debug.Trace (trace) -- import Debug.Trace (trace)
-- import Debug.SimpleReflect -- import Debug.SimpleReflect
......
{-| {-|
Module : Gargantext.Text.Terms.Mono Module : Gargantext.Core.Text.Terms.Mono
Description : Mono Terms module Description : Mono Terms module
Copyright : (c) CNRS, 2017 - present Copyright : (c) CNRS, 2017 - present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -12,7 +12,7 @@ Mono-terms are Nterms where n == 1. ...@@ -12,7 +12,7 @@ Mono-terms are Nterms where n == 1.
-} -}
module Gargantext.Text.Terms.Mono (monoTerms, monoTexts, monoTextsBySentence, words) module Gargantext.Core.Text.Terms.Mono (monoTerms, monoTexts, monoTextsBySentence, words)
where where
import Prelude (String) import Prelude (String)
...@@ -25,7 +25,7 @@ import qualified Data.Set as S ...@@ -25,7 +25,7 @@ import qualified Data.Set as S
import Gargantext.Core import Gargantext.Core
import Gargantext.Core.Types import Gargantext.Core.Types
import Gargantext.Text.Terms.Mono.Stem (stem) import Gargantext.Core.Text.Terms.Mono.Stem (stem)
import Gargantext.Prelude import Gargantext.Prelude
--import Data.Char (isAlphaNum, isSpace) --import Data.Char (isAlphaNum, isSpace)
......
{-| {-|
Module : Gargantext.Text.Ngrams.Stem Module : Gargantext.Core.Text.Ngrams.Stem
Description : Description :
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -18,7 +18,7 @@ Source : https://en.wikipedia.org/wiki/Stemming ...@@ -18,7 +18,7 @@ Source : https://en.wikipedia.org/wiki/Stemming
-} -}
module Gargantext.Text.Terms.Mono.Stem (stem, Lang(..)) module Gargantext.Core.Text.Terms.Mono.Stem (stem, Lang(..))
where where
import Data.Text (Text) import Data.Text (Text)
......
{-| {-|
Module : Gargantext.Text.Ngrams.Stem.En Module : Gargantext.Core.Text.Ngrams.Stem.En
Description : Porter Algorithm Implementation purely Haskell Description : Porter Algorithm Implementation purely Haskell
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -16,7 +16,7 @@ Adapted from: ...@@ -16,7 +16,7 @@ Adapted from:
-} -}
module Gargantext.Text.Terms.Mono.Stem.En (stemIt) module Gargantext.Core.Text.Terms.Mono.Stem.En (stemIt)
where where
import Control.Monad import Control.Monad
......
{-| {-|
Module : Gargantext.Text.Ngrams.Token Module : Gargantext.Core.Text.Ngrams.Token
Description : Tokens and tokenizing a text Description : Tokens and tokenizing a text
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -16,11 +16,11 @@ Source: https://en.wikipedia.org/wiki/Tokenize ...@@ -16,11 +16,11 @@ Source: https://en.wikipedia.org/wiki/Tokenize
-} -}
module Gargantext.Text.Terms.Mono.Token (tokenize) module Gargantext.Core.Text.Terms.Mono.Token (tokenize)
where where
import Data.Text (Text) import Data.Text (Text)
import qualified Gargantext.Text.Terms.Mono.Token.En as En import qualified Gargantext.Core.Text.Terms.Mono.Token.En as En
-- | Contexts depend on the lang -- | Contexts depend on the lang
--import Gargantext.Core (Lang(..)) --import Gargantext.Core (Lang(..))
......
{-| {-|
Module : Gargantext.Text.Ngrams.Token.Text Module : Gargantext.Core.Text.Ngrams.Token.Text
Description : Tokenizer main functions Description : Tokenizer main functions
Copyright : (c) Grzegorz Chrupała first, after: CNRS, 2018-Present Copyright : (c) Grzegorz Chrupała first, after: CNRS, 2018-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -11,7 +11,7 @@ First inspired from https://bitbucket.org/gchrupala/lingo/overview ...@@ -11,7 +11,7 @@ First inspired from https://bitbucket.org/gchrupala/lingo/overview
-} -}
module Gargantext.Text.Terms.Mono.Token.En module Gargantext.Core.Text.Terms.Mono.Token.En
( EitherList(..) ( EitherList(..)
, Tokenizer , Tokenizer
, tokenize , tokenize
......
{-| {-|
Module : Gargantext.Text.Terms.Multi Module : Gargantext.Core.Text.Terms.Multi
Description : Multi Terms module Description : Multi Terms module
Copyright : (c) CNRS, 2017 - present Copyright : (c) CNRS, 2017 - present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -12,7 +12,7 @@ Multi-terms are ngrams where n > 1. ...@@ -12,7 +12,7 @@ Multi-terms are ngrams where n > 1.
-} -}
module Gargantext.Text.Terms.Multi (multiterms, multiterms_rake) module Gargantext.Core.Text.Terms.Multi (multiterms, multiterms_rake)
where where
import Data.Text hiding (map, group, filter, concat) import Data.Text hiding (map, group, filter, concat)
...@@ -23,12 +23,12 @@ import Gargantext.Prelude ...@@ -23,12 +23,12 @@ import Gargantext.Prelude
import Gargantext.Core (Lang(..)) import Gargantext.Core (Lang(..))
import Gargantext.Core.Types import Gargantext.Core.Types
import Gargantext.Text.Terms.Multi.PosTagging import Gargantext.Core.Text.Terms.Multi.PosTagging
import Gargantext.Text.Terms.Mono.Stem (stem) import Gargantext.Core.Text.Terms.Mono.Stem (stem)
import qualified Gargantext.Text.Terms.Multi.Lang.En as En import qualified Gargantext.Core.Text.Terms.Multi.Lang.En as En
import qualified Gargantext.Text.Terms.Multi.Lang.Fr as Fr import qualified Gargantext.Core.Text.Terms.Multi.Lang.Fr as Fr
import Gargantext.Text.Terms.Multi.RAKE (multiterms_rake) import Gargantext.Core.Text.Terms.Multi.RAKE (multiterms_rake)
multiterms :: Lang -> Text -> IO [Terms] multiterms :: Lang -> Text -> IO [Terms]
multiterms lang txt = concat multiterms lang txt = concat
......
{-| {-|
Module : Gargantext.Text.Terms.Multi.Group Module : Gargantext.Core.Text.Terms.Multi.Group
Description : English Grammar rules to group postag tokens. Description : English Grammar rules to group postag tokens.
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -13,7 +13,7 @@ group the tokens into extracted terms. ...@@ -13,7 +13,7 @@ group the tokens into extracted terms.
-} -}
module Gargantext.Text.Terms.Multi.Group (group2) module Gargantext.Core.Text.Terms.Multi.Group (group2)
where where
import Data.Maybe (Maybe(Just)) import Data.Maybe (Maybe(Just))
......
{-| {-|
Module : Gargantext.Text.Terms.Multi.Lang.En Module : Gargantext.Core.Text.Terms.Multi.Lang.En
Description : English Grammar rules to group postag tokens. Description : English Grammar rules to group postag tokens.
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -13,12 +13,12 @@ the tokens into extracted terms. ...@@ -13,12 +13,12 @@ the tokens into extracted terms.
-} -}
module Gargantext.Text.Terms.Multi.Lang.En (group) module Gargantext.Core.Text.Terms.Multi.Lang.En (group)
where where
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Core.Types import Gargantext.Core.Types
import Gargantext.Text.Terms.Multi.Group import Gargantext.Core.Text.Terms.Multi.Group
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | Rule grammar to group tokens -- | Rule grammar to group tokens
......
{-| {-|
Module : Gargantext.Text.Terms.Multi.Lang.Fr Module : Gargantext.Core.Text.Terms.Multi.Lang.Fr
Description : French Grammar rules to group postag tokens. Description : French Grammar rules to group postag tokens.
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -14,12 +14,12 @@ is ADJectiv in french. ...@@ -14,12 +14,12 @@ is ADJectiv in french.
-} -}
module Gargantext.Text.Terms.Multi.Lang.Fr (group) module Gargantext.Core.Text.Terms.Multi.Lang.Fr (group)
where where
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Core.Types import Gargantext.Core.Types
import Gargantext.Text.Terms.Multi.Group (group2) import Gargantext.Core.Text.Terms.Multi.Group (group2)
group :: [TokenTag] -> [TokenTag] group :: [TokenTag] -> [TokenTag]
group [] = [] group [] = []
......
{-| {-|
Module : Gargantext.Text.Terms.Multi.PosTagging Module : Gargantext.Core.Text.Terms.Multi.PosTagging
Description : PosTagging module using Stanford java REST API Description : PosTagging module using Stanford java REST API
Copyright : (c) CNRS, 2017 Copyright : (c) CNRS, 2017
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -22,7 +22,7 @@ Source: https://en.wikipedia.org/wiki/Part-of-speech_tagging ...@@ -22,7 +22,7 @@ Source: https://en.wikipedia.org/wiki/Part-of-speech_tagging
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
module Gargantext.Text.Terms.Multi.PosTagging module Gargantext.Core.Text.Terms.Multi.PosTagging
where where
import GHC.Generics import GHC.Generics
......
{-| {-|
Module : Gargantext.Text.Terms.Multi.RAKE Module : Gargantext.Core.Text.Terms.Multi.RAKE
Description : Rapid automatic keyword extraction (RAKE) Description : Rapid automatic keyword extraction (RAKE)
Copyright : (c) CNRS, 2017 Copyright : (c) CNRS, 2017
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -28,14 +28,14 @@ list quality in time. ...@@ -28,14 +28,14 @@ list quality in time.
-} -}
module Gargantext.Text.Terms.Multi.RAKE (multiterms_rake, select, hardStopList) module Gargantext.Core.Text.Terms.Multi.RAKE (multiterms_rake, select, hardStopList)
where where
import GHC.Real (round) import GHC.Real (round)
import Data.Text (Text) import Data.Text (Text)
import NLP.RAKE.Text import NLP.RAKE.Text
import Gargantext.Text.Samples.EN (stopList) import Gargantext.Core.Text.Samples.EN (stopList)
import Gargantext.Prelude import Gargantext.Prelude
select :: Double -> [a] -> [a] select :: Double -> [a] -> [a]
......
{-| {-|
Module : Gargantext.Text.Terms.WithList Module : Gargantext.Core.Text.Terms.WithList
Description : Description :
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -13,14 +13,14 @@ commentary with @some markup@. ...@@ -13,14 +13,14 @@ commentary with @some markup@.
-} -}
{-# LANGUAGE BangPatterns #-} {-# LANGUAGE BangPatterns #-}
module Gargantext.Text.Terms.WithList where module Gargantext.Core.Text.Terms.WithList where
import Data.List (null, concatMap) import Data.List (null, concatMap)
import Data.Ord import Data.Ord
import Data.Text (Text, concat) import Data.Text (Text, concat)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Text.Context import Gargantext.Core.Text.Context
import Gargantext.Text.Terms.Mono (monoTextsBySentence) import Gargantext.Core.Text.Terms.Mono (monoTextsBySentence)
import Prelude (error) import Prelude (error)
import qualified Data.Algorithms.KMP as KMP import qualified Data.Algorithms.KMP as KMP
import qualified Data.IntMap.Strict as IntMap import qualified Data.IntMap.Strict as IntMap
......
...@@ -81,14 +81,14 @@ import Gargantext.Database.Query.Table.NodeNodeNgrams2 ...@@ -81,14 +81,14 @@ import Gargantext.Database.Query.Table.NodeNodeNgrams2
import Gargantext.Ext.IMT (toSchoolName) import Gargantext.Ext.IMT (toSchoolName)
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger) import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
import Gargantext.Ext.IMTUser (deserialiseImtUsersFromFile) import Gargantext.Ext.IMTUser (deserialiseImtUsersFromFile)
import Gargantext.Text import Gargantext.Core.Text
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Text.Corpus.Parsers (parseFile, FileFormat) import Gargantext.Core.Text.Corpus.Parsers (parseFile, FileFormat)
import Gargantext.Text.List (buildNgramsLists,StopSize(..)) import Gargantext.Core.Text.List (buildNgramsLists,StopSize(..))
import Gargantext.Text.Terms.Mono.Stem.En (stemIt) import Gargantext.Core.Text.Terms.Mono.Stem.En (stemIt)
import Gargantext.Text.Terms import Gargantext.Core.Text.Terms
import qualified Gargantext.Database.Query.Table.Node.Document.Add as Doc (add) import qualified Gargantext.Database.Query.Table.Node.Document.Add as Doc (add)
import qualified Gargantext.Text.Corpus.API as API import qualified Gargantext.Core.Text.Corpus.API as API
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- TODO use internal with API name (could be old data) -- TODO use internal with API name (could be old data)
...@@ -277,11 +277,7 @@ insertMasterDocs c lang hs = do ...@@ -277,11 +277,7 @@ insertMasterDocs c lang hs = do
pure ids' pure ids'
------------------------------------------------------------------------ ------------------------------------------------------------------------
------------------------------------------------------------------------ ------------------------------------------------------------------------
viewUniqId' :: UniqId a viewUniqId' :: UniqId a
=> a => a
...@@ -307,14 +303,11 @@ mergeData rs = catMaybes . map toDocumentWithId . Map.toList ...@@ -307,14 +303,11 @@ mergeData rs = catMaybes . map toDocumentWithId . Map.toList
<*> Just hpd <*> Just hpd
------------------------------------------------------------------------ ------------------------------------------------------------------------
instance HasText HyperdataContact instance HasText HyperdataContact
where where
hasText = undefined hasText = undefined
------------------------------------------------------------------------ ------------------------------------------------------------------------
------------------------------------------------------------------------ ------------------------------------------------------------------------
documentIdWithNgrams :: HasNodeError err documentIdWithNgrams :: HasNodeError err
=> (a => (a
-> Cmd err (Map Ngrams (Map NgramsType Int))) -> Cmd err (Map Ngrams (Map NgramsType Int)))
...@@ -328,8 +321,6 @@ documentIdWithNgrams f = traverse toDocumentIdWithNgrams ...@@ -328,8 +321,6 @@ documentIdWithNgrams f = traverse toDocumentIdWithNgrams
------------------------------------------------------------------------ ------------------------------------------------------------------------
instance ExtractNgramsT HyperdataContact instance ExtractNgramsT HyperdataContact
where where
extractNgramsT l hc = filterNgramsT 255 <$> extract l hc extractNgramsT l hc = filterNgramsT 255 <$> extract l hc
......
...@@ -20,8 +20,8 @@ module Gargantext.Database.Action.Flow.Types ...@@ -20,8 +20,8 @@ module Gargantext.Database.Action.Flow.Types
where where
import Gargantext.Core.Flow.Types import Gargantext.Core.Flow.Types
import Gargantext.Text import Gargantext.Core.Text
import Gargantext.Text.Terms import Gargantext.Core.Text.Terms
import Gargantext.API.Ngrams (HasRepoVar, RepoCmdM) import Gargantext.API.Ngrams (HasRepoVar, RepoCmdM)
import Gargantext.Database.Query.Table.Node.Error (HasNodeError) import Gargantext.Database.Query.Table.Node.Error (HasNodeError)
import Gargantext.Database.Prelude (CmdM) import Gargantext.Database.Prelude (CmdM)
......
...@@ -24,7 +24,7 @@ import Gargantext.Database.Admin.Types.Hyperdata ...@@ -24,7 +24,7 @@ import Gargantext.Database.Admin.Types.Hyperdata
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Prelude (Cmd) import Gargantext.Database.Prelude (Cmd)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Text.Learn import Gargantext.Core.Text.Learn
import qualified Data.List as List import qualified Data.List as List
import qualified Data.Text as Text import qualified Data.Text as Text
......
...@@ -27,7 +27,7 @@ import Gargantext.Database.Admin.Types.Node (ListId, CorpusId) ...@@ -27,7 +27,7 @@ import Gargantext.Database.Admin.Types.Node (ListId, CorpusId)
import Gargantext.Database.Query.Table.Node (defaultList) import Gargantext.Database.Query.Table.Node (defaultList)
import Gargantext.Database.Query.Table.Node.Select import Gargantext.Database.Query.Table.Node.Select
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Text.Metrics (scored, Scored(..), {-localMetrics, toScored-}) import Gargantext.Core.Text.Metrics (scored, Scored(..), {-localMetrics, toScored-})
import qualified Data.Map as Map import qualified Data.Map as Map
getMetrics :: FlowCmdM env err m getMetrics :: FlowCmdM env err m
......
...@@ -23,7 +23,7 @@ import Gargantext.API.Ngrams (TabType(..)) ...@@ -23,7 +23,7 @@ import Gargantext.API.Ngrams (TabType(..))
import Gargantext.Core.Types -- (NodePoly(..), NodeCorpus, ListId) import Gargantext.Core.Types -- (NodePoly(..), NodeCorpus, ListId)
import Gargantext.Database.Action.Flow (FlowCmdM) import Gargantext.Database.Action.Flow (FlowCmdM)
import Gargantext.Prelude hiding (sum, head) import Gargantext.Prelude hiding (sum, head)
import Gargantext.Text.Metrics (Scored(..)) import Gargantext.Core.Text.Metrics (Scored(..))
import Prelude hiding (null, id, map, sum) import Prelude hiding (null, id, map, sum)
import qualified Data.Map as Map import qualified Data.Map as Map
import qualified Data.Vector as Vec import qualified Data.Vector as Vec
......
...@@ -30,8 +30,8 @@ import Gargantext.Database.Admin.Types.Node -- (ListId, CorpusId, NodeId) ...@@ -30,8 +30,8 @@ import Gargantext.Database.Admin.Types.Node -- (ListId, CorpusId, NodeId)
import Gargantext.Database.Prelude (Cmd, runPGSQuery) import Gargantext.Database.Prelude (Cmd, runPGSQuery)
import Gargantext.Database.Schema.Ngrams (ngramsTypeId, NgramsType(..)) import Gargantext.Database.Schema.Ngrams (ngramsTypeId, NgramsType(..))
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Text.Metrics.TFICF import Gargantext.Core.Text.Metrics.TFICF
import Gargantext.Text.Terms.Mono.Stem (stem) import Gargantext.Core.Text.Terms.Mono.Stem (stem)
import qualified Data.List as List import qualified Data.List as List
import qualified Data.Map.Strict as Map import qualified Data.Map.Strict as Map
import qualified Data.Set as Set import qualified Data.Set as Set
...@@ -56,7 +56,6 @@ ngramsGroup l _m _n = Text.intercalate " " ...@@ -56,7 +56,6 @@ ngramsGroup l _m _n = Text.intercalate " "
. Text.replace "-" " " . Text.replace "-" " "
getTficf :: UserCorpusId getTficf :: UserCorpusId
-> MasterCorpusId -> MasterCorpusId
-> NgramsType -> NgramsType
......
...@@ -34,7 +34,7 @@ import Gargantext.Database.Query.Table.Node ...@@ -34,7 +34,7 @@ import Gargantext.Database.Query.Table.Node
import Gargantext.Database.Query.Table.NodeNode import Gargantext.Database.Query.Table.NodeNode
import Gargantext.Database.Schema.Node import Gargantext.Database.Schema.Node
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Text.Terms.Mono.Stem.En (stemIt) import Gargantext.Core.Text.Terms.Mono.Stem.En (stemIt)
import Opaleye hiding (Query, Order) import Opaleye hiding (Query, Order)
import Data.Profunctor.Product (p4) import Data.Profunctor.Product (p4)
import qualified Opaleye as O hiding (Order) import qualified Opaleye as O hiding (Order)
......
...@@ -14,7 +14,7 @@ Enabling "common goods" of text data and respecting privacy. ...@@ -14,7 +14,7 @@ Enabling "common goods" of text data and respecting privacy.
Gargantext shares as "common good" the links between context of texts Gargantext shares as "common good" the links between context of texts
and terms / words / ngrams. and terms / words / ngrams.
Basically a context of text can be defined as a document (see 'Gargantext.Text'). Basically a context of text can be defined as a document (see 'Gargantext.Core.Text').
Issue to tackle in that module: each global document of Gargantext has Issue to tackle in that module: each global document of Gargantext has
to be unique, then shared, but how to respect privacy if needed ? to be unique, then shared, but how to respect privacy if needed ?
......
...@@ -142,7 +142,7 @@ fromNgramsTypeId id = lookup id ...@@ -142,7 +142,7 @@ fromNgramsTypeId id = lookup id
] ]
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | TODO put it in Gargantext.Text.Ngrams -- | TODO put it in Gargantext.Core.Text.Ngrams
data Ngrams = Ngrams { _ngramsTerms :: Text data Ngrams = Ngrams { _ngramsTerms :: Text
, _ngramsSize :: Int , _ngramsSize :: Int
} deriving (Generic, Show, Eq, Ord) } deriving (Generic, Show, Eq, Ord)
...@@ -155,7 +155,7 @@ text2ngrams :: Text -> Ngrams ...@@ -155,7 +155,7 @@ text2ngrams :: Text -> Ngrams
text2ngrams txt = Ngrams txt $ length $ splitOn " " txt text2ngrams txt = Ngrams txt $ length $ splitOn " " txt
------------------------------------------------------------------------- -------------------------------------------------------------------------
-- | TODO put it in Gargantext.Text.Ngrams -- | TODO put it in Gargantext.Core.Text.Ngrams
-- Named entity are typed ngrams of Terms Ngrams -- Named entity are typed ngrams of Terms Ngrams
data NgramsT a = data NgramsT a =
NgramsT { _ngramsType :: NgramsType NgramsT { _ngramsType :: NgramsType
......
...@@ -20,8 +20,8 @@ import qualified Data.List as DL ...@@ -20,8 +20,8 @@ import qualified Data.List as DL
import qualified Data.Vector as DV import qualified Data.Vector as DV
import qualified Data.Map as M import qualified Data.Map as M
import Gargantext.Text.Metrics.Freq as F import Gargantext.Core.Text.Metrics.Freq as F
import Gargantext.Text.Corpus.Parsers.CSV as CSV import Gargantext.Core.Text.Corpus.Parsers.CSV as CSV
data School = School { school_shortName :: Text data School = School { school_shortName :: Text
, school_longName :: Text , school_longName :: Text
......
...@@ -34,7 +34,7 @@ import Data.Map (Map) ...@@ -34,7 +34,7 @@ import Data.Map (Map)
import Gargantext.Core.Utils.Prefix (unPrefix) import Gargantext.Core.Utils.Prefix (unPrefix)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Text.Context (TermList) import Gargantext.Core.Text.Context (TermList)
import GHC.Generics import GHC.Generics
import GHC.IO (FilePath) import GHC.IO (FilePath)
......
...@@ -30,7 +30,7 @@ import Gargantext.Database.Query.Table.Node.Select ...@@ -30,7 +30,7 @@ import Gargantext.Database.Query.Table.Node.Select
import Gargantext.Database.Query.Table.NodeNode (selectDocsDates) import Gargantext.Database.Query.Table.NodeNode (selectDocsDates)
import Gargantext.Database.Schema.Node import Gargantext.Database.Schema.Node
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Text.Metrics.Count (occurrencesWith) import Gargantext.Core.Text.Metrics.Count (occurrencesWith)
-- Pie Chart -- Pie Chart
import Gargantext.API.Ngrams.NTree import Gargantext.API.Ngrams.NTree
......
...@@ -39,7 +39,7 @@ import Data.Vector (Vector) ...@@ -39,7 +39,7 @@ import Data.Vector (Vector)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger) import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Text.Context (TermList) import Gargantext.Core.Text.Context (TermList)
import Prelude (Bounded) import Prelude (Bounded)
-------------------- --------------------
......
...@@ -16,9 +16,9 @@ module Gargantext.Viz.Phylo.Aggregates ...@@ -16,9 +16,9 @@ module Gargantext.Viz.Phylo.Aggregates
import Control.Parallel.Strategies import Control.Parallel.Strategies
import Gargantext.Prelude hiding (elem) import Gargantext.Prelude hiding (elem)
import Gargantext.Text.Context (TermList) import Gargantext.Core.Text.Context (TermList)
import Gargantext.Text.Metrics.FrequentItemSet (fisWithSizePolyMap, Size(..)) import Gargantext.Core.Text.Metrics.FrequentItemSet (fisWithSizePolyMap, Size(..))
import Gargantext.Text.Terms.Mono (monoTexts) import Gargantext.Core.Text.Terms.Mono (monoTexts)
import Gargantext.Viz.Phylo import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Tools import Gargantext.Viz.Phylo.Tools
......
...@@ -33,7 +33,7 @@ import Data.Map (Map,empty) ...@@ -33,7 +33,7 @@ import Data.Map (Map,empty)
import Data.Tuple (fst) import Data.Tuple (fst)
import Data.Vector (Vector) import Data.Vector (Vector)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Text.Context (TermList) import Gargantext.Core.Text.Context (TermList)
import Gargantext.Viz.Phylo import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Cluster import Gargantext.Viz.Phylo.Cluster
import Gargantext.Viz.Phylo.Aggregates import Gargantext.Viz.Phylo.Aggregates
......
...@@ -30,7 +30,7 @@ import Gargantext.Viz.Phylo.Cluster ...@@ -30,7 +30,7 @@ import Gargantext.Viz.Phylo.Cluster
import Gargantext.Viz.Phylo.BranchMaker import Gargantext.Viz.Phylo.BranchMaker
import Gargantext.Viz.Phylo.LinkMaker import Gargantext.Viz.Phylo.LinkMaker
import Gargantext.Viz.Phylo.Tools import Gargantext.Viz.Phylo.Tools
import Gargantext.Text.Context (TermList) import Gargantext.Core.Text.Context (TermList)
import qualified Data.Vector.Storable as VS import qualified Data.Vector.Storable as VS
import qualified Data.Set as Set import qualified Data.Set as Set
......
...@@ -33,8 +33,8 @@ import Gargantext.Database.Query.Table.Node(defaultList) ...@@ -33,8 +33,8 @@ import Gargantext.Database.Query.Table.Node(defaultList)
import Gargantext.Database.Query.Table.NodeNode (selectDocs) import Gargantext.Database.Query.Table.NodeNode (selectDocs)
import Gargantext.Database.Schema.Ngrams (NgramsType(..)) import Gargantext.Database.Schema.Ngrams (NgramsType(..))
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Text.Context (TermList) import Gargantext.Core.Text.Context (TermList)
import Gargantext.Text.Terms.WithList import Gargantext.Core.Text.Terms.WithList
import Gargantext.Viz.Phylo hiding (Svg, Dot) import Gargantext.Viz.Phylo hiding (Svg, Dot)
import Gargantext.Viz.Phylo.LevelMaker import Gargantext.Viz.Phylo.LevelMaker
import Gargantext.Viz.Phylo.Tools import Gargantext.Viz.Phylo.Tools
......
...@@ -20,8 +20,8 @@ import Data.Map (Map) ...@@ -20,8 +20,8 @@ import Data.Map (Map)
import Data.Text (Text, toLower) import Data.Text (Text, toLower)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Text.Context (TermList) import Gargantext.Core.Text.Context (TermList)
import Gargantext.Text.Terms.Mono (monoTexts) import Gargantext.Core.Text.Terms.Mono (monoTexts)
import Gargantext.Viz.AdaptativePhylo import Gargantext.Viz.AdaptativePhylo
import Gargantext.Viz.Phylo.PhyloTools import Gargantext.Viz.Phylo.PhyloTools
import Gargantext.Viz.Phylo.PhyloMaker import Gargantext.Viz.Phylo.PhyloMaker
......
...@@ -20,8 +20,8 @@ import Gargantext.Viz.AdaptativePhylo ...@@ -20,8 +20,8 @@ import Gargantext.Viz.AdaptativePhylo
import Gargantext.Viz.Phylo.PhyloTools import Gargantext.Viz.Phylo.PhyloTools
import Gargantext.Viz.Phylo.TemporalMatching (adaptativeTemporalMatching, constanteTemporalMatching, getNextPeriods, filterDocs, filterDiago, reduceDiagos, toProximity) import Gargantext.Viz.Phylo.TemporalMatching (adaptativeTemporalMatching, constanteTemporalMatching, getNextPeriods, filterDocs, filterDiago, reduceDiagos, toProximity)
import Gargantext.Viz.Phylo.SynchronicClustering (synchronicClustering) import Gargantext.Viz.Phylo.SynchronicClustering (synchronicClustering)
import Gargantext.Text.Context (TermList) import Gargantext.Core.Text.Context (TermList)
import Gargantext.Text.Metrics.FrequentItemSet (fisWithSizePolyMap, Size(..)) import Gargantext.Core.Text.Metrics.FrequentItemSet (fisWithSizePolyMap, Size(..))
import Gargantext.Viz.Graph.MaxClique (getMaxCliques) import Gargantext.Viz.Graph.MaxClique (getMaxCliques)
import Gargantext.Viz.Graph.Distances (Distance(Conditional)) import Gargantext.Viz.Graph.Distances (Distance(Conditional))
......
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