Commit 54a4da56 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[NodeStory] NodeStory Integration, compilation with warning ok (WIP)

parent ee823c5a
...@@ -28,36 +28,34 @@ Pouillard (who mainly made it). ...@@ -28,36 +28,34 @@ Pouillard (who mainly made it).
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
---------------------------------------------------------------------
module Gargantext.API module Gargantext.API
where where
---------------------------------------------------------------------
import Control.Exception (finally) import Control.Exception (finally)
import Control.Lens import Control.Lens
import Control.Monad.Reader (runReaderT) import Control.Monad.Reader (runReaderT)
import Data.List (lookup) import Data.List (lookup)
import Data.Text.Encoding (encodeUtf8) import Data.Text.Encoding (encodeUtf8)
import Data.Text.IO (putStrLn)
import Data.Validity import Data.Validity
import GHC.Base (Applicative) import GHC.Base (Applicative)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Network.HTTP.Types hiding (Query)
import Network.Wai
import Network.Wai.Handler.Warp hiding (defaultSettings)
import Network.Wai.Middleware.Cors
import Network.Wai.Middleware.RequestLogger
import Servant
import System.IO (FilePath)
import Data.Text.IO (putStrLn)
import Gargantext.API.Admin.Auth.Types (AuthContext) import Gargantext.API.Admin.Auth.Types (AuthContext)
import Gargantext.API.Admin.Settings (newEnv) import Gargantext.API.Admin.Settings (newEnv)
import Gargantext.API.Admin.Types (FireWall(..), PortNumber, cookieSettings, jwtSettings, settings) import Gargantext.API.Admin.Types (FireWall(..), PortNumber, cookieSettings, jwtSettings, settings)
import Gargantext.API.Ngrams (saveRepo) import Gargantext.API.Ngrams (saveRepo)
import Gargantext.API.Ngrams.Types (HasRepoSaver(..))
import Gargantext.API.Prelude import Gargantext.API.Prelude
import Gargantext.API.Routes import Gargantext.API.Routes
import Gargantext.API.Server (server) import Gargantext.API.Server (server)
import Gargantext.Core.NodeStory
import Gargantext.Prelude hiding (putStrLn) import Gargantext.Prelude hiding (putStrLn)
import Network.HTTP.Types hiding (Query)
import Network.Wai
import Network.Wai.Handler.Warp hiding (defaultSettings)
import Network.Wai.Middleware.Cors
import Network.Wai.Middleware.RequestLogger
import Servant
import System.IO (FilePath)
data Mode = Dev | Mock | Prod data Mode = Dev | Mock | Prod
...@@ -79,7 +77,7 @@ portRouteInfo port = do ...@@ -79,7 +77,7 @@ portRouteInfo port = do
putStrLn $ "http://localhost:" <> toUrlPiece port <> "/swagger-ui" putStrLn $ "http://localhost:" <> toUrlPiece port <> "/swagger-ui"
-- TODO clean this Monad condition (more generic) ? -- TODO clean this Monad condition (more generic) ?
stopGargantext :: HasRepoSaver env => env -> IO () stopGargantext :: HasNodeStorySaver env => env -> IO ()
stopGargantext env = do stopGargantext env = do
putStrLn "----- Stopping gargantext -----" putStrLn "----- Stopping gargantext -----"
runReaderT saveRepo env runReaderT saveRepo env
...@@ -226,4 +224,4 @@ type family GenericTypeName t (r :: *) :: Symbol where ...@@ -226,4 +224,4 @@ type family GenericTypeName t (r :: *) :: Symbol where
GenericTypeName t (D1 ('MetaData name mod pkg nt) f x) = name GenericTypeName t (D1 ('MetaData name mod pkg nt) f x) = name
type Desc t n = Description (AppendSymbol (TypeName t) (AppendSymbol " | " n)) type Desc t n = Description (AppendSymbol (TypeName t) (AppendSymbol " | " n))
-} -}
\ No newline at end of file
...@@ -16,7 +16,6 @@ import qualified Servant.Job.Core ...@@ -16,7 +16,6 @@ import qualified Servant.Job.Core
import Gargantext.API.Admin.Types import Gargantext.API.Admin.Types
import Gargantext.API.Admin.Orchestrator.Types import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.Ngrams.Types (HasRepoVar(..), HasRepoSaver(..), HasRepo(..), RepoEnv(..))
import Gargantext.Database.Prelude (HasConnectionPool(..), HasConfig(..)) import Gargantext.Database.Prelude (HasConnectionPool(..), HasConfig(..))
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Prelude.Config (GargConfig(..)) import Gargantext.Prelude.Config (GargConfig(..))
...@@ -26,7 +25,6 @@ data Env = Env ...@@ -26,7 +25,6 @@ data Env = Env
{ _env_settings :: !Settings { _env_settings :: !Settings
, _env_logger :: !LoggerSet , _env_logger :: !LoggerSet
, _env_pool :: !(Pool Connection) , _env_pool :: !(Pool Connection)
, _env_repo :: !RepoEnv
, _env_nodeStory :: !NodeStoryEnv , _env_nodeStory :: !NodeStoryEnv
, _env_manager :: !Manager , _env_manager :: !Manager
, _env_self_url :: !BaseUrl , _env_self_url :: !BaseUrl
...@@ -43,6 +41,7 @@ instance HasConfig Env where ...@@ -43,6 +41,7 @@ instance HasConfig Env where
instance HasConnectionPool Env where instance HasConnectionPool Env where
connPool = env_pool connPool = env_pool
{- To be removed
instance HasRepoVar Env where instance HasRepoVar Env where
repoVar = repoEnv . repoVar repoVar = repoEnv . repoVar
...@@ -51,6 +50,13 @@ instance HasRepoSaver Env where ...@@ -51,6 +50,13 @@ instance HasRepoSaver Env where
instance HasRepo Env where instance HasRepo Env where
repoEnv = env_repo repoEnv = env_repo
-}
-- TODONS
instance HasNodeStorySaver Env
instance HasNodeStoryEnv Env
instance HasNodeStoryVar Env
instance HasSettings Env where instance HasSettings Env where
settings = env_settings settings = env_settings
...@@ -71,7 +77,7 @@ makeLenses ''MockEnv ...@@ -71,7 +77,7 @@ makeLenses ''MockEnv
data DevEnv = DevEnv data DevEnv = DevEnv
{ _dev_env_pool :: !(Pool Connection) { _dev_env_pool :: !(Pool Connection)
, _dev_env_repo :: !RepoEnv , _dev_env_nodeStory :: !NodeStoryEnv
, _dev_env_settings :: !Settings , _dev_env_settings :: !Settings
, _dev_env_config :: !GargConfig , _dev_env_config :: !GargConfig
} }
...@@ -84,6 +90,10 @@ instance HasConfig DevEnv where ...@@ -84,6 +90,10 @@ instance HasConfig DevEnv where
instance HasConnectionPool DevEnv where instance HasConnectionPool DevEnv where
connPool = dev_env_pool connPool = dev_env_pool
-- TODONS
instance HasNodeStorySaver DevEnv
{-
instance HasRepoVar DevEnv where instance HasRepoVar DevEnv where
repoVar = repoEnv . repoVar repoVar = repoEnv . repoVar
...@@ -92,6 +102,7 @@ instance HasRepoSaver DevEnv where ...@@ -92,6 +102,7 @@ instance HasRepoSaver DevEnv where
instance HasRepo DevEnv where instance HasRepo DevEnv where
repoEnv = dev_env_repo repoEnv = dev_env_repo
-}
instance HasSettings DevEnv where instance HasSettings DevEnv where
settings = dev_env_settings settings = dev_env_settings
...@@ -29,7 +29,6 @@ import Data.Pool (Pool, createPool) ...@@ -29,7 +29,6 @@ import Data.Pool (Pool, createPool)
import Database.PostgreSQL.Simple (Connection, connect, close, ConnectInfo) import Database.PostgreSQL.Simple (Connection, connect, close, ConnectInfo)
import Gargantext.API.Admin.EnvTypes import Gargantext.API.Admin.EnvTypes
import Gargantext.API.Admin.Types import Gargantext.API.Admin.Types
import Gargantext.API.Ngrams.Types (NgramsRepo, HasRepo(..), RepoEnv(..), r_version, initRepo, renv_var, renv_lock)
import Gargantext.Core.NodeStory import Gargantext.Core.NodeStory
import Gargantext.Database.Prelude (databaseParameters, HasConfig(..)) import Gargantext.Database.Prelude (databaseParameters, HasConfig(..))
import Gargantext.Prelude import Gargantext.Prelude
...@@ -110,6 +109,7 @@ repoSaverAction repoDir a = do ...@@ -110,6 +109,7 @@ repoSaverAction repoDir a = do
{-
-- The use of mkDebounce makes sure that repoSaverAction is not called too often. -- The use of mkDebounce makes sure that repoSaverAction is not called too often.
-- If repoSaverAction start taking more time than the debounceFreq then it should -- If repoSaverAction start taking more time than the debounceFreq then it should
-- be increased. -- be increased.
...@@ -158,6 +158,7 @@ readRepoEnv repoDir = do ...@@ -158,6 +158,7 @@ readRepoEnv repoDir = do
-- TODO save in DB here -- TODO save in DB here
saver <- mkRepoSaver repoDir mvar saver <- mkRepoSaver repoDir mvar
pure $ RepoEnv { _renv_var = mvar, _renv_saver = saver, _renv_lock = lock } pure $ RepoEnv { _renv_var = mvar, _renv_saver = saver, _renv_lock = lock }
-}
devJwkFile :: FilePath devJwkFile :: FilePath
devJwkFile = "dev.jwk" devJwkFile = "dev.jwk"
...@@ -173,7 +174,7 @@ newEnv port file = do ...@@ -173,7 +174,7 @@ newEnv port file = do
self_url_env <- parseBaseUrl $ "http://0.0.0.0:" <> show port self_url_env <- parseBaseUrl $ "http://0.0.0.0:" <> show port
dbParam <- databaseParameters file dbParam <- databaseParameters file
pool <- newPool dbParam pool <- newPool dbParam
repo <- readRepoEnv (_gc_repofilepath config_env) -- repo <- readRepoEnv (_gc_repofilepath config_env)
nodeStory_env <- readNodeStoryEnv (_gc_repofilepath config_env) nodeStory_env <- readNodeStoryEnv (_gc_repofilepath config_env)
scrapers_env <- newJobEnv defaultSettings manager_env scrapers_env <- newJobEnv defaultSettings manager_env
logger <- newStderrLoggerSet defaultBufSize logger <- newStderrLoggerSet defaultBufSize
...@@ -182,7 +183,7 @@ newEnv port file = do ...@@ -182,7 +183,7 @@ newEnv port file = do
{ _env_settings = settings' { _env_settings = settings'
, _env_logger = logger , _env_logger = logger
, _env_pool = pool , _env_pool = pool
, _env_repo = repo -- , _env_repo = repo
, _env_nodeStory = nodeStory_env , _env_nodeStory = nodeStory_env
, _env_manager = manager_env , _env_manager = manager_env
, _env_scrapers = scrapers_env , _env_scrapers = scrapers_env
...@@ -193,9 +194,10 @@ newEnv port file = do ...@@ -193,9 +194,10 @@ newEnv port file = do
newPool :: ConnectInfo -> IO (Pool Connection) newPool :: ConnectInfo -> IO (Pool Connection)
newPool param = createPool (connect param) close 1 (60*60) 8 newPool param = createPool (connect param) close 1 (60*60) 8
{-
cleanEnv :: (HasConfig env, HasRepo env) => env -> IO () cleanEnv :: (HasConfig env, HasRepo env) => env -> IO ()
cleanEnv env = do cleanEnv env = do
r <- takeMVar (env ^. repoEnv . renv_var) r <- takeMVar (env ^. repoEnv . renv_var)
repoSaverAction (env ^. hasConfig . gc_repofilepath) r repoSaverAction (env ^. hasConfig . gc_repofilepath) r
unlockFile (env ^. repoEnv . renv_lock) unlockFile (env ^. repoEnv . renv_lock)
-}
...@@ -15,15 +15,15 @@ module Gargantext.API.Dev where ...@@ -15,15 +15,15 @@ module Gargantext.API.Dev where
import Control.Exception (finally) import Control.Exception (finally)
import Control.Monad (fail) import Control.Monad (fail)
import Control.Monad.Reader (runReaderT) import Control.Monad.Reader (runReaderT)
import Servant
import Gargantext.API.Prelude
import Gargantext.API.Admin.Settings
import Gargantext.API.Admin.EnvTypes import Gargantext.API.Admin.EnvTypes
import Gargantext.API.Admin.Settings
import Gargantext.API.Ngrams (saveRepo) import Gargantext.API.Ngrams (saveRepo)
import Gargantext.API.Prelude
import Gargantext.Core.NodeStory
import Gargantext.Database.Prelude import Gargantext.Database.Prelude
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Prelude.Config (GargConfig(..), readConfig) import Gargantext.Prelude.Config (GargConfig(..), readConfig)
import Servant
import System.IO (FilePath) import System.IO (FilePath)
type IniPath = FilePath type IniPath = FilePath
...@@ -31,24 +31,25 @@ type IniPath = FilePath ...@@ -31,24 +31,25 @@ type IniPath = FilePath
withDevEnv :: IniPath -> (DevEnv -> IO a) -> IO a withDevEnv :: IniPath -> (DevEnv -> IO a) -> IO a
withDevEnv iniPath k = do withDevEnv iniPath k = do
env <- newDevEnv env <- newDevEnv
k env `finally` cleanEnv env k env
-- k env `finally` cleanEnv env
where where
newDevEnv = do newDevEnv = do
cfg <- readConfig iniPath cfg <- readConfig iniPath
dbParam <- databaseParameters iniPath dbParam <- databaseParameters iniPath
nodeStory_env <- readNodeStoryEnv (_gc_repofilepath cfg)
pool <- newPool dbParam pool <- newPool dbParam
repo <- readRepoEnv (_gc_repofilepath cfg)
setts <- devSettings devJwkFile setts <- devSettings devJwkFile
pure $ DevEnv pure $ DevEnv
{ _dev_env_pool = pool { _dev_env_pool = pool
, _dev_env_repo = repo , _dev_env_nodeStory = nodeStory_env
, _dev_env_settings = setts , _dev_env_settings = setts
, _dev_env_config = cfg , _dev_env_config = cfg
} }
-- | Run Cmd Sugar for the Repl (GHCI) -- | Run Cmd Sugar for the Repl (GHCI)
runCmdRepl :: Show err => Cmd'' DevEnv err a -> IO a runCmdRepl :: (Show err, HasNodeStorySaver DevEnv) => Cmd'' DevEnv err a -> IO a
runCmdRepl f = withDevEnv "gargantext.ini" $ \env -> runCmdDev env f runCmdRepl f = withDevEnv "gargantext.ini" $ \env -> runCmdDev env f
runCmdReplServantErr :: Cmd'' DevEnv ServerError a -> IO a runCmdReplServantErr :: Cmd'' DevEnv ServerError a -> IO a
...@@ -58,17 +59,17 @@ runCmdReplServantErr = runCmdRepl ...@@ -58,17 +59,17 @@ runCmdReplServantErr = runCmdRepl
-- the command. -- the command.
-- This function is constrained to the DevEnv rather than -- This function is constrained to the DevEnv rather than
-- using HasConnectionPool and HasRepoVar. -- using HasConnectionPool and HasRepoVar.
runCmdDev :: Show err => DevEnv -> Cmd'' DevEnv err a -> IO a runCmdDev :: (Show err, HasNodeStorySaver DevEnv) => DevEnv -> Cmd'' DevEnv err a -> IO a
runCmdDev env f = runCmdDev env f =
(either (fail . show) pure =<< runCmd env f) (either (fail . show) pure =<< runCmd env f)
`finally` `finally`
runReaderT saveRepo env runReaderT saveRepo env
runCmdDevNoErr :: DevEnv -> Cmd' DevEnv () a -> IO a runCmdDevNoErr :: (HasNodeStorySaver DevEnv) => DevEnv -> Cmd' DevEnv () a -> IO a
runCmdDevNoErr = runCmdDev runCmdDevNoErr = runCmdDev
runCmdDevServantErr :: DevEnv -> Cmd' DevEnv ServerError a -> IO a runCmdDevServantErr :: (HasNodeStorySaver DevEnv) => DevEnv -> Cmd' DevEnv ServerError a -> IO a
runCmdDevServantErr = runCmdDev runCmdDevServantErr = runCmdDev
runCmdReplEasy :: Cmd'' DevEnv GargError a -> IO a runCmdReplEasy :: (HasNodeStorySaver DevEnv) => Cmd'' DevEnv GargError a -> IO a
runCmdReplEasy f = withDevEnv "gargantext.ini" $ \env -> runCmdDev env f runCmdReplEasy f = withDevEnv "gargantext.ini" $ \env -> runCmdDev env f
...@@ -30,10 +30,10 @@ import Gargantext.Core.Text.Metrics (Scored(..), {-normalizeGlobal,-} normalizeL ...@@ -30,10 +30,10 @@ import Gargantext.Core.Text.Metrics (Scored(..), {-normalizeGlobal,-} normalizeL
import Gargantext.Core.Types (CorpusId, Limit, ListId, ListType(..)) import Gargantext.Core.Types (CorpusId, Limit, ListId, ListType(..))
import Gargantext.Core.Viz.Chart import Gargantext.Core.Viz.Chart
import Gargantext.Core.Viz.Types import Gargantext.Core.Viz.Types
import Gargantext.Database.Action.Flow
import Gargantext.Database.Admin.Types.Hyperdata (HyperdataList(..), hl_chart, hl_pie, hl_scatter, hl_tree) import Gargantext.Database.Admin.Types.Hyperdata (HyperdataList(..), hl_chart, hl_pie, hl_scatter, hl_tree)
import Gargantext.Database.Admin.Types.Metrics (ChartMetrics(..), Metric(..), Metrics(..)) import Gargantext.Database.Admin.Types.Metrics (ChartMetrics(..), Metric(..), Metrics(..))
import Gargantext.Database.Admin.Types.Node (NodeId) import Gargantext.Database.Admin.Types.Node (NodeId)
import Gargantext.Database.Action.Flow.Types (FlowCmdM)
import Gargantext.Database.Prelude import Gargantext.Database.Prelude
import Gargantext.Database.Query.Table.Node (defaultList, getNodeWith) import Gargantext.Database.Query.Table.Node (defaultList, getNodeWith)
import Gargantext.Database.Query.Table.Node.Error (HasNodeError) import Gargantext.Database.Query.Table.Node.Error (HasNodeError)
......
This diff is collapsed.
...@@ -24,22 +24,13 @@ import Data.Set (Set) ...@@ -24,22 +24,13 @@ import Data.Set (Set)
import Data.Swagger (ToSchema, declareNamedSchema, genericDeclareNamedSchema) import Data.Swagger (ToSchema, declareNamedSchema, genericDeclareNamedSchema)
import Data.Text (Text, concat, pack) import Data.Text (Text, concat, pack)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Network.HTTP.Media ((//), (/:))
import Servant
import Servant.Job.Async
import Servant.Job.Utils (jsonOptions)
import Web.FormUrlEncoded (FromForm)
import qualified Data.HashMap.Strict as HashMap
import qualified Data.List as List
import qualified Data.Map as Map
import qualified Data.Text as Text
import Gargantext.API.Admin.Orchestrator.Types import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.Ngrams (getNgramsTableMap, setListNgrams) import Gargantext.API.Ngrams (getNgramsTableMap, setListNgrams)
import Gargantext.API.Ngrams.Tools (getTermsWith) import Gargantext.API.Ngrams.Tools (getTermsWith)
import Gargantext.API.Ngrams.Types import Gargantext.API.Ngrams.Types
import Gargantext.API.Node.Corpus.New.File (FileType(..)) import Gargantext.API.Node.Corpus.New.File (FileType(..))
import Gargantext.API.Prelude (GargServer) import Gargantext.API.Prelude (GargServer)
import Gargantext.Core.NodeStory
import Gargantext.Core.Text.Terms (ExtractedNgrams(..)) import Gargantext.Core.Text.Terms (ExtractedNgrams(..))
import Gargantext.Core.Text.Terms.WithList (buildPatterns, termsInText) import Gargantext.Core.Text.Terms.WithList (buildPatterns, termsInText)
import Gargantext.Core.Types.Main (ListType(..)) import Gargantext.Core.Types.Main (ListType(..))
...@@ -54,6 +45,15 @@ import Gargantext.Database.Schema.Ngrams ...@@ -54,6 +45,15 @@ import Gargantext.Database.Schema.Ngrams
import Gargantext.Database.Schema.Node import Gargantext.Database.Schema.Node
import Gargantext.Database.Types (Indexed(..)) import Gargantext.Database.Types (Indexed(..))
import Gargantext.Prelude import Gargantext.Prelude
import Network.HTTP.Media ((//), (/:))
import Servant
import Servant.Job.Async
import Servant.Job.Utils (jsonOptions)
import Web.FormUrlEncoded (FromForm)
import qualified Data.HashMap.Strict as HashMap
import qualified Data.List as List
import qualified Data.Map as Map
import qualified Data.Text as Text
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | TODO refactor -- | TODO refactor
...@@ -110,7 +110,7 @@ csvApi = csvPostAsync ...@@ -110,7 +110,7 @@ csvApi = csvPostAsync
------------------------------------------------------------------------ ------------------------------------------------------------------------
get :: RepoCmdM env err m => get :: HasNodeStory env err m =>
ListId -> m (Headers '[Header "Content-Disposition" Text] NgramsList) ListId -> m (Headers '[Header "Content-Disposition" Text] NgramsList)
get lId = do get lId = do
lst <- get' lId lst <- get' lId
...@@ -121,7 +121,7 @@ get lId = do ...@@ -121,7 +121,7 @@ get lId = do
] ]
) lst ) lst
get' :: RepoCmdM env err m get' :: HasNodeStory env err m
=> ListId -> m NgramsList => ListId -> m NgramsList
get' lId = fromList get' lId = fromList
<$> zip ngramsTypes <$> zip ngramsTypes
...@@ -153,8 +153,8 @@ csvPost l m = do ...@@ -153,8 +153,8 @@ csvPost l m = do
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | Re-index documents of a corpus with new ngrams (called orphans here) -- | Re-index documents of a corpus with new ngrams (called orphans here)
reIndexWith :: ( HasRepo env reIndexWith :: ( HasNodeStory env err m
, FlowCmdM env err m , FlowCmdM env err m
) )
=> CorpusId => CorpusId
-> ListId -> ListId
......
...@@ -36,11 +36,6 @@ mergeNgramsElement _neOld neNew = neNew ...@@ -36,11 +36,6 @@ mergeNgramsElement _neOld neNew = neNew
type RootTerm = NgramsTerm type RootTerm = NgramsTerm
getRepo :: RepoCmdM env err m => m NgramsRepo
getRepo = do
v <- view repoVar
liftBase $ readMVar v
getRepo' :: HasNodeStory env err m getRepo' :: HasNodeStory env err m
=> [ListId] -> m NodeListStory => [ListId] -> m NodeListStory
getRepo' listIds = do getRepo' listIds = do
...@@ -80,19 +75,8 @@ getNodeListStory'' n = do ...@@ -80,19 +75,8 @@ getNodeListStory'' n = do
listNgramsFromRepo :: [ListId] -> NgramsType listNgramsFromRepo :: [ListId] -> NgramsType
-> NgramsRepo -> HashMap NgramsTerm NgramsRepoElement
listNgramsFromRepo nodeIds ngramsType repo = ngrams
where
ngramsMap = repo ^. r_state . at ngramsType . _Just
-- TODO HashMap linked
ngrams = HM.fromList $ Map.toList $ Map.unionsWith mergeNgramsElement
[ ngramsMap ^. at nodeId . _Just | nodeId <- nodeIds ]
listNgramsFromRepo' :: [ListId] -> NgramsType
-> NodeListStory -> HashMap NgramsTerm NgramsRepoElement -> NodeListStory -> HashMap NgramsTerm NgramsRepoElement
listNgramsFromRepo' nodeIds ngramsType repo = listNgramsFromRepo nodeIds ngramsType repo =
HM.fromList $ Map.toList HM.fromList $ Map.toList
$ Map.unionsWith mergeNgramsElement ngrams $ Map.unionsWith mergeNgramsElement ngrams
where where
...@@ -110,41 +94,22 @@ listNgramsFromRepo' nodeIds ngramsType repo = ...@@ -110,41 +94,22 @@ listNgramsFromRepo' nodeIds ngramsType repo =
-- Add a static capability parameter would be nice. -- Add a static capability parameter would be nice.
-- Ideally this is the access to `repoVar` which needs to -- Ideally this is the access to `repoVar` which needs to
-- be properly guarded. -- be properly guarded.
getListNgrams :: RepoCmdM env err m getListNgrams :: HasNodeStory env err m
=> [ListId] -> NgramsType => [ListId] -> NgramsType
-> m (HashMap NgramsTerm NgramsRepoElement) -> m (HashMap NgramsTerm NgramsRepoElement)
getListNgrams nodeIds ngramsType = listNgramsFromRepo nodeIds ngramsType <$> getRepo getListNgrams nodeIds ngramsType = listNgramsFromRepo nodeIds ngramsType
getListNgrams' :: HasNodeStory env err m
=> [ListId] -> NgramsType
-> m (HashMap NgramsTerm NgramsRepoElement)
getListNgrams' nodeIds ngramsType = listNgramsFromRepo' nodeIds ngramsType
<$> getRepo' nodeIds <$> getRepo' nodeIds
getTermsWith :: (RepoCmdM env err m, Eq a, Hashable a) getTermsWith :: (HasNodeStory env err m, Eq a, Hashable a)
=> (NgramsTerm -> a) -> [ListId] => (NgramsTerm -> a) -> [ListId]
-> NgramsType -> Set ListType -> NgramsType -> Set ListType
-> m (HashMap a [a]) -> m (HashMap a [a])
getTermsWith f ls ngt lts = HM.fromListWith (<>) getTermsWith f ls ngt lts = HM.fromListWith (<>)
<$> map toTreeWith <$> map toTreeWith
<$> HM.toList <$> HM.toList
<$> HM.filter (\f' -> Set.member (fst f') lts) <$> HM.filter (\f' -> Set.member (fst f') lts)
<$> mapTermListRoot ls ngt <$> mapTermListRoot ls ngt
<$> getRepo
where
toTreeWith (t, (_lt, maybeRoot)) = case maybeRoot of
Nothing -> (f t, [])
Just r -> (f r, [f t])
getTermsWith' :: (HasNodeStory env err m, Eq a, Hashable a)
=> (NgramsTerm -> a) -> [ListId]
-> NgramsType -> Set ListType
-> m (HashMap a [a])
getTermsWith' f ls ngt lts = HM.fromListWith (<>)
<$> map toTreeWith
<$> HM.toList
<$> HM.filter (\f' -> Set.member (fst f') lts)
<$> mapTermListRoot' ls ngt
<$> getRepo' ls <$> getRepo' ls
where where
toTreeWith (t, (_lt, maybeRoot)) = case maybeRoot of toTreeWith (t, (_lt, maybeRoot)) = case maybeRoot of
...@@ -153,22 +118,13 @@ getTermsWith' f ls ngt lts = HM.fromListWith (<>) ...@@ -153,22 +118,13 @@ getTermsWith' f ls ngt lts = HM.fromListWith (<>)
mapTermListRoot :: [ListId] mapTermListRoot :: [ListId]
-> NgramsType -> NgramsType
-> NgramsRepo -> NodeListStory
-> HashMap NgramsTerm (ListType, Maybe NgramsTerm) -> HashMap NgramsTerm (ListType, Maybe NgramsTerm)
mapTermListRoot nodeIds ngramsType repo = mapTermListRoot nodeIds ngramsType repo =
(\nre -> (_nre_list nre, _nre_root nre)) (\nre -> (_nre_list nre, _nre_root nre))
<$> listNgramsFromRepo nodeIds ngramsType repo <$> listNgramsFromRepo nodeIds ngramsType repo
mapTermListRoot' :: [ListId]
-> NgramsType
-> NodeListStory
-> HashMap NgramsTerm (ListType, Maybe NgramsTerm)
mapTermListRoot' nodeIds ngramsType repo =
(\nre -> (_nre_list nre, _nre_root nre))
<$> listNgramsFromRepo' nodeIds ngramsType repo
......
...@@ -719,6 +719,7 @@ data RepoEnv = RepoEnv ...@@ -719,6 +719,7 @@ data RepoEnv = RepoEnv
makeLenses ''RepoEnv makeLenses ''RepoEnv
{-
type RepoCmdM env err m = type RepoCmdM env err m =
( CmdM' env err m ( CmdM' env err m
, HasRepo env , HasRepo env
...@@ -743,7 +744,7 @@ instance HasRepoVar RepoEnv where ...@@ -743,7 +744,7 @@ instance HasRepoVar RepoEnv where
repoVar = renv_var repoVar = renv_var
instance HasRepoSaver RepoEnv where instance HasRepoSaver RepoEnv where
repoSaver = renv_saver repoSaver = renv_saver
-}
------------------------------------------------------------------------ ------------------------------------------------------------------------
......
...@@ -21,10 +21,11 @@ import Data.Maybe (fromMaybe) ...@@ -21,10 +21,11 @@ import Data.Maybe (fromMaybe)
import Data.Set (Set) import Data.Set (Set)
import Gargantext.API.Node.Corpus.Export.Types import Gargantext.API.Node.Corpus.Export.Types
import Gargantext.API.Ngrams.Types import Gargantext.API.Ngrams.Types
import Gargantext.API.Ngrams.Tools (filterListWithRoot, mapTermListRoot, getRepo) import Gargantext.API.Ngrams.Tools (filterListWithRoot, mapTermListRoot, getRepo')
import Gargantext.API.Prelude (GargNoServer) import Gargantext.API.Prelude (GargNoServer)
import Gargantext.Prelude.Crypto.Hash (hash) import Gargantext.Prelude.Crypto.Hash (hash)
import Gargantext.Core.Types import Gargantext.Core.Types
import Gargantext.Core.NodeStory
import Gargantext.Database.Action.Metrics.NgramsByNode (getNgramsByNodeOnlyUser) import Gargantext.Database.Action.Metrics.NgramsByNode (getNgramsByNodeOnlyUser)
import Gargantext.Database.Admin.Config (userMaster) import Gargantext.Database.Admin.Config (userMaster)
import Gargantext.Database.Admin.Types.Hyperdata (HyperdataDocument(..)) import Gargantext.Database.Admin.Types.Hyperdata (HyperdataDocument(..))
...@@ -57,7 +58,8 @@ getCorpus cId lId nt' = do ...@@ -57,7 +58,8 @@ getCorpus cId lId nt' = do
ns <- Map.fromList ns <- Map.fromList
<$> map (\n -> (_node_id n, n)) <$> map (\n -> (_node_id n, n))
<$> selectDocNodes cId <$> selectDocNodes cId
repo <- getRepo
repo <- getRepo' [fromMaybe (panic "[Gargantext.API.Node.Corpus.Export]") lId]
ngs <- getNodeNgrams cId lId nt repo ngs <- getNodeNgrams cId lId nt repo
let -- uniqId is hash computed already for each document imported in database let -- uniqId is hash computed already for each document imported in database
r = Map.intersectionWith (\a b -> Document a (Ngrams (Set.toList b) (hash b)) (d_hash a b) r = Map.intersectionWith (\a b -> Document a (Ngrams (Set.toList b) (hash b)) (d_hash a b)
...@@ -74,7 +76,7 @@ getNodeNgrams :: HasNodeError err ...@@ -74,7 +76,7 @@ getNodeNgrams :: HasNodeError err
=> CorpusId => CorpusId
-> Maybe ListId -> Maybe ListId
-> NgramsType -> NgramsType
-> NgramsRepo -> NodeListStory
-> Cmd err (Map NodeId (Set NgramsTerm)) -> Cmd err (Map NodeId (Set NgramsTerm))
getNodeNgrams cId lId' nt repo = do getNodeNgrams cId lId' nt repo = do
lId <- case lId' of lId <- case lId' of
......
...@@ -18,6 +18,8 @@ New corpus means either: ...@@ -18,6 +18,8 @@ New corpus means either:
module Gargantext.API.Node.Corpus.New module Gargantext.API.Node.Corpus.New
where where
-- import Servant.Multipart
-- import Test.QuickCheck (elements)
import Control.Lens hiding (elements, Empty) import Control.Lens hiding (elements, Empty)
import Data.Aeson import Data.Aeson
import Data.Aeson.TH (deriveJSON) import Data.Aeson.TH (deriveJSON)
...@@ -25,36 +27,33 @@ import Data.Either ...@@ -25,36 +27,33 @@ import Data.Either
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
import Data.Swagger import Data.Swagger
import Data.Text (Text) import Data.Text (Text)
import qualified Data.Text as T
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Servant
import Servant.Job.Utils (jsonOptions)
-- import Servant.Multipart
-- import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary
import Gargantext.Prelude
import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs) import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs)
import qualified Gargantext.API.Admin.Orchestrator.Types as T
import Gargantext.API.Admin.Types (HasSettings) import Gargantext.API.Admin.Types (HasSettings)
import Gargantext.API.Node.Corpus.New.File import Gargantext.API.Node.Corpus.New.File
import Gargantext.API.Node.Types import Gargantext.API.Node.Types
import Gargantext.Core (Lang(..){-, allLangs-}) import Gargantext.Core (Lang(..){-, allLangs-})
import Gargantext.Database.Action.Mail (sendMail)
import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger) import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
import Gargantext.Database.Action.Flow (FlowCmdM, flowCorpus, getDataText, flowDataText, TermType(..), DataOrigin(..){-, allDataOrigins-}) import Gargantext.Database.Action.Flow (flowCorpus, getDataText, flowDataText, TermType(..), DataOrigin(..){-, allDataOrigins-})
import Gargantext.Database.Action.User (getUserId) import Gargantext.Database.Action.Flow.Types (FlowCmdM)
import Gargantext.Database.Action.Mail (sendMail)
import Gargantext.Database.Action.Node (mkNodeWithParent) import Gargantext.Database.Action.Node (mkNodeWithParent)
import Gargantext.Database.Action.User (getUserId)
import Gargantext.Database.Admin.Types.Hyperdata import Gargantext.Database.Admin.Types.Hyperdata
import Gargantext.Database.Admin.Types.Node (CorpusId, NodeType(..), UserId) import Gargantext.Database.Admin.Types.Node (CorpusId, NodeType(..), UserId)
import Gargantext.Database.Query.Table.Node (getNodeWith) 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.Database.GargDB as GargDB import Gargantext.Prelude
import Servant
import Servant.Job.Utils (jsonOptions)
import Test.QuickCheck.Arbitrary
import qualified Data.Text as T
import qualified Gargantext.API.Admin.Orchestrator.Types as T
import qualified Gargantext.Core.Text.Corpus.API as API import qualified Gargantext.Core.Text.Corpus.API as API
import qualified Gargantext.Core.Text.Corpus.Parsers as Parser (FileFormat(..), parseFormat) import qualified Gargantext.Core.Text.Corpus.Parsers as Parser (FileFormat(..), parseFormat)
import qualified Gargantext.Database.GargDB as GargDB
------------------------------------------------------------------------ ------------------------------------------------------------------------
{- {-
......
...@@ -35,6 +35,7 @@ import Gargantext.API.Admin.Orchestrator.Types ...@@ -35,6 +35,7 @@ import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.Admin.Types import Gargantext.API.Admin.Types
import Gargantext.API.Ngrams.Types import Gargantext.API.Ngrams.Types
import Gargantext.Core.Types import Gargantext.Core.Types
import Gargantext.Core.NodeStory
import Gargantext.Database.Prelude import Gargantext.Database.Prelude
import Gargantext.Database.Query.Table.Node.Error (NodeError(..), HasNodeError(..)) import Gargantext.Database.Query.Table.Node.Error (NodeError(..), HasNodeError(..))
import Gargantext.Database.Query.Tree import Gargantext.Database.Query.Tree
...@@ -51,10 +52,10 @@ joseError = throwError . (_JoseError #) ...@@ -51,10 +52,10 @@ joseError = throwError . (_JoseError #)
type EnvC env = type EnvC env =
( HasConnectionPool env ( HasConnectionPool env
, HasRepo env -- TODO rename HasNgramsRepo
, HasSettings env -- TODO rename HasDbSettings , HasSettings env -- TODO rename HasDbSettings
, HasJobEnv env JobLog JobLog , HasJobEnv env JobLog JobLog
, HasConfig env , HasConfig env
, HasNodeStoryEnv env
) )
type ErrC err = type ErrC err =
...@@ -69,6 +70,7 @@ type ErrC err = ...@@ -69,6 +70,7 @@ type ErrC err =
type GargServerC env err m = type GargServerC env err m =
( CmdRandom env err m ( CmdRandom env err m
, HasNodeStory env err m
, EnvC env , EnvC env
, ErrC err , ErrC err
, MimeRender JSON err , MimeRender JSON err
...@@ -91,7 +93,7 @@ type GargNoServer t = ...@@ -91,7 +93,7 @@ type GargNoServer t =
type GargNoServer' env err m = type GargNoServer' env err m =
( CmdM env err m ( CmdM env err m
, HasRepo env , HasNodeStory env err m
, HasSettings env , HasSettings env
, HasNodeError err , HasNodeError err
) )
......
...@@ -15,30 +15,32 @@ Portability : POSIX ...@@ -15,30 +15,32 @@ Portability : POSIX
module Gargantext.Core.NodeStory where module Gargantext.Core.NodeStory where
import System.IO (FilePath, hClose)
import Data.Maybe (fromMaybe)
import Codec.Serialise (Serialise(), serialise, deserialise) import Codec.Serialise (Serialise(), serialise, deserialise)
import Control.Monad.Reader
import Control.Monad.Except
import Control.Concurrent (MVar(), withMVar, newMVar) import Control.Concurrent (MVar(), withMVar, newMVar)
import Control.Debounce (mkDebounce, defaultDebounceSettings, debounceFreq, debounceAction)
import Control.Lens (makeLenses, Getter, (^.)) import Control.Lens (makeLenses, Getter, (^.))
import Control.Monad.Except
import Control.Monad.Reader
import Data.Aeson hiding ((.=)) import Data.Aeson hiding ((.=))
import qualified Data.List as List import Data.Map.Strict (Map)
import Data.Map as Map import Data.Maybe (fromMaybe)
import Data.Monoid import Data.Monoid
import Data.Semigroup import Data.Semigroup
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Gargantext.API.Ngrams.Types import Gargantext.API.Ngrams.Types
import Gargantext.Core.Types (NodeId) import Gargantext.Core.Types (NodeId)
import Gargantext.Core.Utils.Prefix (unPrefix) import Gargantext.Core.Utils.Prefix (unPrefix)
import Gargantext.Database.Prelude (CmdM', HasConnectionPool, HasConfig)
import Gargantext.Database.Query.Table.Node.Error (HasNodeError())
import Gargantext.Prelude import Gargantext.Prelude
import qualified Gargantext.Database.Query.Table.Ngrams as TableNgrams
import qualified Data.Map.Strict.Patch.Internal as Patch
import qualified Data.ByteString.Lazy as L
import System.Directory (renameFile, createDirectoryIfMissing, doesFileExist) import System.Directory (renameFile, createDirectoryIfMissing, doesFileExist)
import System.IO (FilePath, hClose)
import System.IO.Temp (withTempFile) import System.IO.Temp (withTempFile)
import Control.Debounce (mkDebounce, defaultDebounceSettings, debounceFreq, debounceAction) import qualified Data.ByteString.Lazy as L
import Gargantext.Database.Prelude (CmdM', HasConnectionPool, HasConfig) import qualified Data.List as List
import qualified Data.Map.Strict as Map
import qualified Data.Map.Strict.Patch.Internal as Patch
import qualified Gargantext.Database.Query.Table.Ngrams as TableNgrams
------------------------------------------------------------------------ ------------------------------------------------------------------------
data NodeStoryEnv = NodeStoryEnv data NodeStoryEnv = NodeStoryEnv
...@@ -56,6 +58,7 @@ type HasNodeStory env err m = ( CmdM' env err m ...@@ -56,6 +58,7 @@ type HasNodeStory env err m = ( CmdM' env err m
, HasNodeStoryEnv env , HasNodeStoryEnv env
, HasConfig env , HasConfig env
, HasConnectionPool env , HasConnectionPool env
, HasNodeError err
) )
class (HasNodeStoryVar env, HasNodeStorySaver env) class (HasNodeStoryVar env, HasNodeStorySaver env)
......
...@@ -23,7 +23,8 @@ import Data.Monoid (mempty) ...@@ -23,7 +23,8 @@ import Data.Monoid (mempty)
import Data.Ord (Down(..)) import Data.Ord (Down(..))
import Data.Set (Set) import Data.Set (Set)
import Data.Tuple.Extra (both) import Data.Tuple.Extra (both)
import Gargantext.API.Ngrams.Types (NgramsElement, RepoCmdM, NgramsTerm(..)) import Gargantext.API.Ngrams.Types (NgramsElement, NgramsTerm(..))
import Gargantext.Core.NodeStory
import Gargantext.Core.Text (size) import Gargantext.Core.Text (size)
import Gargantext.Core.Text.List.Group import Gargantext.Core.Text.List.Group
import Gargantext.Core.Text.List.Group.Prelude import Gargantext.Core.Text.List.Group.Prelude
...@@ -38,18 +39,18 @@ import Gargantext.Database.Action.Metrics.TFICF (getTficf) ...@@ -38,18 +39,18 @@ import Gargantext.Database.Action.Metrics.TFICF (getTficf)
import Gargantext.Database.Admin.Types.Node (NodeId) import Gargantext.Database.Admin.Types.Node (NodeId)
import Gargantext.Database.Prelude (CmdM) import Gargantext.Database.Prelude (CmdM)
import Gargantext.Database.Query.Table.Ngrams (text2ngrams) import Gargantext.Database.Query.Table.Ngrams (text2ngrams)
import Gargantext.Database.Query.Table.Node (defaultList)
import Gargantext.Database.Query.Table.NgramsPostag (selectLems) import Gargantext.Database.Query.Table.NgramsPostag (selectLems)
import Gargantext.Database.Query.Table.Node (defaultList)
import Gargantext.Database.Query.Table.Node.Error (HasNodeError()) import Gargantext.Database.Query.Table.Node.Error (HasNodeError())
import Gargantext.Database.Query.Tree.Error (HasTreeError) import Gargantext.Database.Query.Tree.Error (HasTreeError)
import Gargantext.Database.Schema.Ngrams (NgramsType(..), Ngrams(..)) import Gargantext.Database.Schema.Ngrams (NgramsType(..), Ngrams(..))
import Gargantext.Prelude import Gargantext.Prelude
import qualified Data.HashMap.Strict as HashMap import qualified Data.HashMap.Strict as HashMap
import qualified Data.HashSet as HashSet
import qualified Data.List as List import qualified Data.List as List
import qualified Data.Map as Map import qualified Data.Map as Map
import qualified Data.Set as Set import qualified Data.Set as Set
import qualified Gargantext.Data.HashMap.Strict.Utils as HashMap import qualified Gargantext.Data.HashMap.Strict.Utils as HashMap
import qualified Data.HashSet as HashSet
{- {-
-- TODO maybe useful for later -- TODO maybe useful for later
...@@ -61,7 +62,7 @@ isStopTerm (StopSize n) x = Text.length x < n || any isStopChar (Text.unpack x) ...@@ -61,7 +62,7 @@ isStopTerm (StopSize n) x = Text.length x < n || any isStopChar (Text.unpack x)
-- | TODO improve grouping functions of Authors, Sources, Institutes.. -- | TODO improve grouping functions of Authors, Sources, Institutes..
buildNgramsLists :: ( RepoCmdM env err m buildNgramsLists :: ( HasNodeStory env err m
, CmdM env err m , CmdM env err m
, HasTreeError err , HasTreeError err
, HasNodeError err , HasNodeError err
...@@ -86,7 +87,7 @@ data MapListSize = MapListSize { unMapListSize :: !Int } ...@@ -86,7 +87,7 @@ data MapListSize = MapListSize { unMapListSize :: !Int }
buildNgramsOthersList ::( HasNodeError err buildNgramsOthersList ::( HasNodeError err
, CmdM env err m , CmdM env err m
, RepoCmdM env err m , HasNodeStory env err m
, HasTreeError err , HasTreeError err
) )
=> User => User
...@@ -128,7 +129,7 @@ buildNgramsOthersList user uCid _groupParams (nt, MapListSize mapListSize) = do ...@@ -128,7 +129,7 @@ buildNgramsOthersList user uCid _groupParams (nt, MapListSize mapListSize) = do
getGroupParams :: ( HasNodeError err getGroupParams :: ( HasNodeError err
, CmdM env err m , CmdM env err m
, RepoCmdM env err m , HasNodeStory env err m
, HasTreeError err , HasTreeError err
) )
=> GroupParams -> HashSet Ngrams -> m GroupParams => GroupParams -> HashSet Ngrams -> m GroupParams
...@@ -142,7 +143,7 @@ getGroupParams gp _ = pure gp ...@@ -142,7 +143,7 @@ getGroupParams gp _ = pure gp
-- TODO use ListIds -- TODO use ListIds
buildNgramsTermsList :: ( HasNodeError err buildNgramsTermsList :: ( HasNodeError err
, CmdM env err m , CmdM env err m
, RepoCmdM env err m , HasNodeStory env err m
, HasTreeError err , HasTreeError err
) )
=> User => User
......
...@@ -16,6 +16,7 @@ import Data.Map (Map) ...@@ -16,6 +16,7 @@ import Data.Map (Map)
import Data.Monoid (mconcat) import Data.Monoid (mconcat)
import Gargantext.API.Ngrams.Tools import Gargantext.API.Ngrams.Tools
import Gargantext.API.Ngrams.Types import Gargantext.API.Ngrams.Types
import Gargantext.Core.NodeStory
import Gargantext.Core.Text.List.Social.Find import Gargantext.Core.Text.List.Social.Find
import Gargantext.Core.Text.List.Social.History import Gargantext.Core.Text.List.Social.History
import Gargantext.Core.Text.List.Social.Patch import Gargantext.Core.Text.List.Social.Patch
...@@ -49,7 +50,7 @@ keepAllParents _ = KeepAllParents True ...@@ -49,7 +50,7 @@ keepAllParents _ = KeepAllParents True
-} -}
------------------------------------------------------------------------ ------------------------------------------------------------------------
flowSocialList :: ( RepoCmdM env err m flowSocialList :: ( HasNodeStory env err m
, CmdM env err m , CmdM env err m
, HasNodeError err , HasNodeError err
, HasTreeError err , HasTreeError err
...@@ -63,7 +64,7 @@ flowSocialList flowPriority user nt flc = ...@@ -63,7 +64,7 @@ flowSocialList flowPriority user nt flc =
(flowSocialListPriority flowPriority) (flowSocialListPriority flowPriority)
where where
flowSocialListByMode' :: ( RepoCmdM env err m flowSocialListByMode' :: ( HasNodeStory env err m
, CmdM env err m , CmdM env err m
, HasNodeError err , HasNodeError err
, HasTreeError err , HasTreeError err
...@@ -77,7 +78,7 @@ flowSocialList flowPriority user nt flc = ...@@ -77,7 +78,7 @@ flowSocialList flowPriority user nt flc =
>>= flowSocialListByModeWith nt' flc' >>= flowSocialListByModeWith nt' flc'
flowSocialListByModeWith :: ( RepoCmdM env err m flowSocialListByModeWith :: ( HasNodeStory env err m
, CmdM env err m , CmdM env err m
, HasNodeError err , HasNodeError err
, HasTreeError err , HasTreeError err
...@@ -94,10 +95,10 @@ flowSocialList flowPriority user nt flc = ...@@ -94,10 +95,10 @@ flowSocialList flowPriority user nt flc =
. toFlowListScores (keepAllParents nt'') flc'' . toFlowListScores (keepAllParents nt'') flc''
-} -}
----------------------------------------------------------------- -----------------------------------------------------------------
getHistoryScores :: ( RepoCmdM env err m getHistoryScores :: ( HasNodeStory env err m
, CmdM env err m , CmdM env err m
, HasNodeError err , HasNodeError err
, HasTreeError err , HasTreeError err
) )
=> History => History
-> NgramsType -> NgramsType
...@@ -107,7 +108,7 @@ getHistoryScores :: ( RepoCmdM env err m ...@@ -107,7 +108,7 @@ getHistoryScores :: ( RepoCmdM env err m
getHistoryScores hist nt fl listes = getHistoryScores hist nt fl listes =
addScorePatches nt listes fl <$> getHistory hist nt listes addScorePatches nt listes fl <$> getHistory hist nt listes
getHistory :: ( RepoCmdM env err m getHistory :: ( HasNodeStory env err m
, CmdM env err m , CmdM env err m
, HasNodeError err , HasNodeError err
, HasTreeError err , HasTreeError err
...@@ -115,7 +116,7 @@ getHistory :: ( RepoCmdM env err m ...@@ -115,7 +116,7 @@ getHistory :: ( RepoCmdM env err m
=> History => History
-> NgramsType -> NgramsType
-> [ListId] -> [ListId]
-> m (Map NgramsType (Map ListId [HashMap NgramsTerm NgramsPatch])) -> m (Map ListId (Map NgramsType [HashMap NgramsTerm NgramsPatch]))
getHistory hist nt listes = getHistory hist nt listes =
history hist [nt] listes <$> getRepo history hist [nt] listes <$> getRepo' listes
...@@ -15,12 +15,14 @@ import Control.Lens hiding (cons) ...@@ -15,12 +15,14 @@ import Control.Lens hiding (cons)
import Data.HashMap.Strict (HashMap) import Data.HashMap.Strict (HashMap)
import Data.Map (Map) import Data.Map (Map)
import Gargantext.API.Ngrams.Types import Gargantext.API.Ngrams.Types
import Gargantext.Core.NodeStory
import Gargantext.Core.Text.List.Social.Prelude import Gargantext.Core.Text.List.Social.Prelude
import Gargantext.Core.Types (ListId) import Gargantext.Core.Types (ListId)
import Gargantext.Database.Schema.Ngrams (NgramsType(..)) import Gargantext.Database.Schema.Ngrams (NgramsType(..))
import Gargantext.Prelude import Gargantext.Prelude
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.HashMap.Strict as HasMap
-- TODO put this in Prelude -- TODO put this in Prelude
cons :: a -> [a] cons :: a -> [a]
...@@ -37,8 +39,8 @@ data History = History_User ...@@ -37,8 +39,8 @@ data History = History_User
history :: History history :: History
-> [NgramsType] -> [NgramsType]
-> [ListId] -> [ListId]
-> Repo s NgramsStatePatch -> NodeStory s NgramsStatePatch'
-> Map NgramsType (Map ListId [HashMap NgramsTerm NgramsPatch]) -> Map ListId (Map NgramsType [HashMap NgramsTerm NgramsPatch])
history History_User t l = clean . (history' t l) history History_User t l = clean . (history' t l)
where where
clean = Map.map (Map.map List.init) clean = Map.map (Map.map List.init)
...@@ -53,35 +55,20 @@ history _ t l = history' t l ...@@ -53,35 +55,20 @@ history _ t l = history' t l
------------------------------------------------------------------------ ------------------------------------------------------------------------
history' :: [NgramsType] history' :: [NgramsType]
-> [ListId] -> [ListId]
-> Repo s NgramsStatePatch -> NodeStory s NgramsStatePatch'
-> Map NgramsType (Map ListId [HashMap NgramsTerm NgramsPatch]) -> Map ListId (Map NgramsType [HashMap NgramsTerm NgramsPatch])
history' types lists = merge history' types lists = (Map.map (Map.unionsWith (<>)))
. map (Map.map ( Map.map cons)) . (Map.map (map (Map.filterWithKey (\k _ -> List.elem k types))))
. map (Map.map ((Map.filterWithKey (\k _ -> List.elem k lists)))) . (Map.map (map toMap))
. map (Map.filterWithKey (\k _ -> List.elem k types)) . (Map.map (view a_history))
. map toMap . (Map.filterWithKey (\k _ -> List.elem k lists))
. view r_history . (view unNodeStory)
merge :: [Map NgramsType (Map ListId [HashMap NgramsTerm NgramsPatch])]
-> Map NgramsType (Map ListId [HashMap NgramsTerm NgramsPatch])
merge = Map.unionsWith merge'
where where
merge' :: Map ListId [HashMap NgramsTerm NgramsPatch]
-> Map ListId [HashMap NgramsTerm NgramsPatch] toMap :: PatchMap NgramsType NgramsTablePatch
-> Map ListId [HashMap NgramsTerm NgramsPatch] -> Map NgramsType [HashMap NgramsTerm NgramsPatch]
merge' = Map.unionWith (<>) toMap m = Map.map (cons . unNgramsTablePatch)
$ unPatchMapToMap m
toMap :: PatchMap NgramsType
(PatchMap ListId
(NgramsTablePatch
)
)
-> Map NgramsType
(Map ListId
(HashMap NgramsTerm NgramsPatch
)
)
toMap = Map.map (Map.map unNgramsTablePatch) . (Map.map unPatchMapToMap) . unPatchMapToMap
...@@ -30,27 +30,29 @@ import qualified Data.Patch.Class as Patch (Replace(..)) ...@@ -30,27 +30,29 @@ import qualified Data.Patch.Class as Patch (Replace(..))
addScorePatches :: NgramsType -> [ListId] addScorePatches :: NgramsType -> [ListId]
-> FlowCont NgramsTerm FlowListScores -> FlowCont NgramsTerm FlowListScores
-> Map NgramsType (Map ListId [HashMap NgramsTerm NgramsPatch]) -> Map ListId (Map NgramsType [HashMap NgramsTerm NgramsPatch])
-> FlowCont NgramsTerm FlowListScores -> FlowCont NgramsTerm FlowListScores
addScorePatches nt listes fl repo = foldl' (addScorePatchesList nt repo) fl listes addScorePatches nt listes fl repo =
foldl' (addScorePatchesList nt repo) fl listes
addScorePatchesList :: NgramsType addScorePatchesList :: NgramsType
-> Map NgramsType (Map ListId [HashMap NgramsTerm NgramsPatch]) -- -> Map NgramsType (Map ListId [HashMap NgramsTerm NgramsPatch])
-> Map ListId (Map NgramsType [HashMap NgramsTerm NgramsPatch])
-> FlowCont NgramsTerm FlowListScores -> FlowCont NgramsTerm FlowListScores
-> ListId -> ListId
-> FlowCont NgramsTerm FlowListScores -> FlowCont NgramsTerm FlowListScores
addScorePatchesList nt repo fl lid = foldl' addScorePatch fl patches addScorePatchesList nt repo fl lid =
foldl' addScorePatch fl patches
where where
patches = maybe [] (List.concat . (map HashMap.toList)) patches' patches = maybe [] (List.concat . (map HashMap.toList)) patches'
patches' = do patches' = do
lists <- Map.lookup nt repo lists <- Map.lookup lid repo
mapPatches <- Map.lookup lid lists mapPatches <- Map.lookup nt lists
pure mapPatches pure mapPatches
addScorePatch :: FlowCont NgramsTerm FlowListScores addScorePatch :: FlowCont NgramsTerm FlowListScores
-> (NgramsTerm , NgramsPatch) -> (NgramsTerm , NgramsPatch)
-> FlowCont NgramsTerm FlowListScores -> FlowCont NgramsTerm FlowListScores
......
...@@ -35,7 +35,7 @@ import Gargantext.API.Ngrams.NgramsTree ...@@ -35,7 +35,7 @@ import Gargantext.API.Ngrams.NgramsTree
import Gargantext.API.Ngrams.Tools import Gargantext.API.Ngrams.Tools
import Gargantext.API.Ngrams.Types import Gargantext.API.Ngrams.Types
import Gargantext.Core.Types import Gargantext.Core.Types
import Gargantext.Database.Action.Flow import Gargantext.Database.Action.Flow.Types
import Gargantext.Database.Action.Metrics.NgramsByNode import Gargantext.Database.Action.Metrics.NgramsByNode
import Gargantext.Database.Schema.Ngrams import Gargantext.Database.Schema.Ngrams
import Gargantext.Core.Viz.Types import Gargantext.Core.Viz.Types
...@@ -59,7 +59,7 @@ chartData :: FlowCmdM env err m ...@@ -59,7 +59,7 @@ chartData :: FlowCmdM env err m
chartData cId nt lt = do chartData cId nt lt = do
ls' <- selectNodesWithUsername NodeList userMaster ls' <- selectNodesWithUsername NodeList userMaster
ls <- map (_node_id) <$> getListsWithParentId cId ls <- map (_node_id) <$> getListsWithParentId cId
ts <- mapTermListRoot ls nt <$> getRepo ts <- mapTermListRoot ls nt <$> getRepo' ls
let let
dico = filterListWithRoot lt ts dico = filterListWithRoot lt ts
terms = catMaybes $ List.concat $ map (\(a,b) -> [Just a, b]) $ HashMap.toList dico terms = catMaybes $ List.concat $ map (\(a,b) -> [Just a, b]) $ HashMap.toList dico
...@@ -79,7 +79,7 @@ treeData :: FlowCmdM env err m ...@@ -79,7 +79,7 @@ treeData :: FlowCmdM env err m
treeData cId nt lt = do treeData cId nt lt = do
ls' <- selectNodesWithUsername NodeList userMaster ls' <- selectNodesWithUsername NodeList userMaster
ls <- map (_node_id) <$> getListsWithParentId cId ls <- map (_node_id) <$> getListsWithParentId cId
ts <- mapTermListRoot ls nt <$> getRepo ts <- mapTermListRoot ls nt <$> getRepo' ls
let let
dico = filterListWithRoot lt ts dico = filterListWithRoot lt ts
......
...@@ -16,11 +16,11 @@ Portability : POSIX ...@@ -16,11 +16,11 @@ Portability : POSIX
module Gargantext.Core.Viz.Graph.API module Gargantext.Core.Viz.Graph.API
where where
import Control.Lens (set, (^.), _Just, (^?)) import Control.Lens (set, (^.), _Just, (^?), at, view)
import Data.Aeson import Data.Aeson
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
import Data.Swagger import Data.Swagger
import Data.Text import Data.Text hiding (head)
import Debug.Trace (trace) import Debug.Trace (trace)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Gargantext.API.Admin.Orchestrator.Types import Gargantext.API.Admin.Orchestrator.Types
...@@ -28,6 +28,7 @@ import Gargantext.API.Ngrams.Tools ...@@ -28,6 +28,7 @@ import Gargantext.API.Ngrams.Tools
import Gargantext.API.Ngrams.Types (NgramsRepo, r_version) import Gargantext.API.Ngrams.Types (NgramsRepo, r_version)
import Gargantext.API.Prelude import Gargantext.API.Prelude
import Gargantext.Core.Methods.Distances (Distance(..), GraphMetric(..), withMetric) import Gargantext.Core.Methods.Distances (Distance(..), GraphMetric(..), withMetric)
import Gargantext.Core.NodeStory
import Gargantext.Core.Types.Main import Gargantext.Core.Types.Main
import Gargantext.Core.Viz.Graph import Gargantext.Core.Viz.Graph
import Gargantext.Core.Viz.Graph.GEXF () import Gargantext.Core.Viz.Graph.GEXF ()
...@@ -48,7 +49,10 @@ import Gargantext.Prelude ...@@ -48,7 +49,10 @@ import Gargantext.Prelude
import Servant import Servant
import Servant.Job.Async import Servant.Job.Async
import Servant.XML import Servant.XML
import qualified Gargantext.Database.Schema.Node as Node
import qualified Data.HashMap.Strict as HashMap import qualified Data.HashMap.Strict as HashMap
import qualified Data.List as List
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | There is no Delete specific API for Graph since it can be deleted -- | There is no Delete specific API for Graph since it can be deleted
-- as simple Node. -- as simple Node.
...@@ -80,7 +84,6 @@ graphAPI u n = getGraph u n ...@@ -80,7 +84,6 @@ graphAPI u n = getGraph u n
getGraph :: UserId -> NodeId -> GargNoServer HyperdataGraphAPI getGraph :: UserId -> NodeId -> GargNoServer HyperdataGraphAPI
getGraph _uId nId = do getGraph _uId nId = do
nodeGraph <- getNodeWith nId (Proxy :: Proxy HyperdataGraph) nodeGraph <- getNodeWith nId (Proxy :: Proxy HyperdataGraph)
repo <- getRepo
let let
graph = nodeGraph ^. node_hyperdata . hyperdataGraph graph = nodeGraph ^. node_hyperdata . hyperdataGraph
...@@ -89,6 +92,9 @@ getGraph _uId nId = do ...@@ -89,6 +92,9 @@ getGraph _uId nId = do
identity identity
$ nodeGraph ^. node_parent_id $ nodeGraph ^. node_parent_id
listId <- defaultList cId
repo <- getRepo' [listId]
-- TODO Distance in Graph params -- TODO Distance in Graph params
case graph of case graph of
Nothing -> do Nothing -> do
...@@ -118,9 +124,7 @@ recomputeGraph _uId nId maybeDistance = do ...@@ -118,9 +124,7 @@ recomputeGraph _uId nId maybeDistance = do
Nothing -> graph ^? _Just . graph_metadata . _Just . gm_metric Nothing -> graph ^? _Just . graph_metadata . _Just . gm_metric
_ -> maybeDistance _ -> maybeDistance
repo <- getRepo
let let
v = repo ^. r_version
cId = maybe (panic "[G.V.G.API.recomputeGraph] Node has no parent") cId = maybe (panic "[G.V.G.API.recomputeGraph] Node has no parent")
identity identity
$ nodeGraph ^. node_parent_id $ nodeGraph ^. node_parent_id
...@@ -128,6 +132,10 @@ recomputeGraph _uId nId maybeDistance = do ...@@ -128,6 +132,10 @@ recomputeGraph _uId nId maybeDistance = do
Nothing -> withMetric Order1 Nothing -> withMetric Order1
Just m -> withMetric m Just m -> withMetric m
listId <- defaultList cId
repo <- getRepo' [listId]
let v = repo ^. unNodeStory . at listId . _Just . a_version
case graph of case graph of
Nothing -> do Nothing -> do
graph' <- computeGraph cId similarity NgramsTerms repo graph' <- computeGraph cId similarity NgramsTerms repo
...@@ -150,7 +158,7 @@ computeGraph :: HasNodeError err ...@@ -150,7 +158,7 @@ computeGraph :: HasNodeError err
=> CorpusId => CorpusId
-> Distance -> Distance
-> NgramsType -> NgramsType
-> NgramsRepo -> NodeListStory
-> Cmd err Graph -> Cmd err Graph
computeGraph cId d nt repo = do computeGraph cId d nt repo = do
lId <- defaultList cId lId <- defaultList cId
...@@ -175,7 +183,7 @@ computeGraph cId d nt repo = do ...@@ -175,7 +183,7 @@ computeGraph cId d nt repo = do
defaultGraphMetadata :: HasNodeError err defaultGraphMetadata :: HasNodeError err
=> CorpusId => CorpusId
-> Text -> Text
-> NgramsRepo -> NodeListStory
-> GraphMetric -> GraphMetric
-> Cmd err GraphMetadata -> Cmd err GraphMetadata
defaultGraphMetadata cId t repo gm = do defaultGraphMetadata cId t repo gm = do
...@@ -191,7 +199,7 @@ defaultGraphMetadata cId t repo gm = do ...@@ -191,7 +199,7 @@ defaultGraphMetadata cId t repo gm = do
, LegendField 3 "#FFF" "Cluster3" , LegendField 3 "#FFF" "Cluster3"
, LegendField 4 "#FFF" "Cluster4" , LegendField 4 "#FFF" "Cluster4"
] ]
, _gm_list = (ListForGraph lId (repo ^. r_version)) , _gm_list = (ListForGraph lId (repo ^. unNodeStory . at lId . _Just . a_version))
, _gm_startForceAtlas = True , _gm_startForceAtlas = True
} }
-- (map (\n -> LegendField n "#FFFFFF" (pack $ show n)) [1..10]) -- (map (\n -> LegendField n "#FFFFFF" (pack $ show n)) [1..10])
...@@ -252,8 +260,13 @@ graphVersions nId = do ...@@ -252,8 +260,13 @@ graphVersions nId = do
. gm_list . gm_list
. lfg_version . lfg_version
repo <- getRepo cId = maybe (panic "[G.V.G.API] Node has no parent")
let v = repo ^. r_version identity
$ nodeGraph ^. node_parent_id
listId <- defaultList cId
repo <- getRepo' [listId]
let v = repo ^. unNodeStory . at listId . _Just . a_version
pure $ GraphVersions { gv_graph = listVersion pure $ GraphVersions { gv_graph = listVersion
, gv_repo = v } , gv_repo = v }
......
...@@ -29,6 +29,7 @@ import Gargantext.Core.Text.Terms.WithList ...@@ -29,6 +29,7 @@ import Gargantext.Core.Text.Terms.WithList
import Gargantext.Database.Query.Table.Node(defaultList) import Gargantext.Database.Query.Table.Node(defaultList)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Database.Action.Flow import Gargantext.Database.Action.Flow
import Gargantext.Database.Action.Flow.Types
import Gargantext.Core.Viz.LegacyPhylo hiding (Svg, Dot) import Gargantext.Core.Viz.LegacyPhylo hiding (Svg, Dot)
import Gargantext.Database.Admin.Types.Hyperdata import Gargantext.Database.Admin.Types.Hyperdata
import Gargantext.Database.Schema.Ngrams (NgramsType(..)) import Gargantext.Database.Schema.Ngrams (NgramsType(..))
......
...@@ -24,8 +24,7 @@ Portability : POSIX ...@@ -24,8 +24,7 @@ Portability : POSIX
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
module Gargantext.Database.Action.Flow -- (flowDatabase, ngrams2list) module Gargantext.Database.Action.Flow -- (flowDatabase, ngrams2list)
( FlowCmdM ( getDataText
, getDataText
, flowDataText , flowDataText
, flow , flow
......
...@@ -18,15 +18,18 @@ module Gargantext.Database.Action.Flow.List ...@@ -18,15 +18,18 @@ module Gargantext.Database.Action.Flow.List
where where
import Control.Concurrent import Control.Concurrent
import Control.Lens (view, (^.), (+~), (%~), at) import Control.Lens (view, (^.), (+~), (%~), at, (.~), _Just)
import Control.Monad.Reader import Control.Monad.Reader
import Data.Map (Map, toList) import Data.Map (Map, toList)
import Data.Maybe (catMaybes) import Data.Maybe (catMaybes)
import Data.Text (Text) import Data.Text (Text)
import Gargantext.API.Ngrams.Types (HasRepoSaver(..), NgramsElement(..), NgramsPatch(..), NgramsRepoElement(..), NgramsTablePatch(..), NgramsTerm(..), RepoCmdM, ne_ngrams, ngramsElementToRepo, r_history, r_state, r_version, repoVar) import Gargantext.API.Ngrams (saveRepo)
import Gargantext.API.Ngrams.Tools (getRepoVar)
import Gargantext.API.Ngrams.Types
import Gargantext.Core.Types (HasInvalidError(..), assertValid) import Gargantext.Core.Types (HasInvalidError(..), assertValid)
import Gargantext.Core.Types.Main (ListType(CandidateTerm)) import Gargantext.Core.Types.Main (ListType(CandidateTerm))
import Gargantext.Core.Utils (something) import Gargantext.Core.Utils (something)
import Gargantext.Core.NodeStory
import Gargantext.Database.Action.Flow.Types import Gargantext.Database.Action.Flow.Types
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Query.Table.NodeNgrams (NodeNgramsPoly(..), NodeNgramsW, listInsertDb, getCgramsId) import Gargantext.Database.Query.Table.NodeNgrams (NodeNgramsPoly(..), NodeNgramsW, listInsertDb, getCgramsId)
...@@ -143,7 +146,7 @@ listInsert lId ngs = mapM_ (\(typeList, ngElmts) ...@@ -143,7 +146,7 @@ listInsert lId ngs = mapM_ (\(typeList, ngElmts)
-- This function is maintained for its usage in Database.Action.Flow.List. -- This function is maintained for its usage in Database.Action.Flow.List.
-- If the given list of ngrams elements contains ngrams already in -- If the given list of ngrams elements contains ngrams already in
-- the repo, they will be ignored. -- the repo, they will be ignored.
putListNgrams :: (HasInvalidError err, RepoCmdM env err m) putListNgrams :: (HasInvalidError err, HasNodeStory env err m)
=> NodeId => NodeId
-> TableNgrams.NgramsType -> TableNgrams.NgramsType
-> [NgramsElement] -> [NgramsElement]
...@@ -153,20 +156,18 @@ putListNgrams nodeId ngramsType nes = putListNgrams' nodeId ngramsType m ...@@ -153,20 +156,18 @@ putListNgrams nodeId ngramsType nes = putListNgrams' nodeId ngramsType m
where where
m = Map.fromList $ map (\n -> (n ^. ne_ngrams, ngramsElementToRepo n)) nes m = Map.fromList $ map (\n -> (n ^. ne_ngrams, ngramsElementToRepo n)) nes
putListNgrams' :: (HasInvalidError err, RepoCmdM env err m) putListNgrams' :: (HasInvalidError err, HasNodeStory env err m)
=> NodeId => NodeId
-> TableNgrams.NgramsType -> TableNgrams.NgramsType
-> Map NgramsTerm NgramsRepoElement -> Map NgramsTerm NgramsRepoElement
-> m () -> m ()
putListNgrams' nodeId ngramsType ns = do putListNgrams' listId ngramsType ns = do
-- printDebug "[putListNgrams'] nodeId" nodeId -- printDebug "[putListNgrams'] nodeId" nodeId
-- printDebug "[putListNgrams'] ngramsType" ngramsType -- printDebug "[putListNgrams'] ngramsType" ngramsType
-- printDebug "[putListNgrams'] ns" ns -- printDebug "[putListNgrams'] ns" ns
let p1 = NgramsTablePatch . PM.fromMap $ NgramsReplace Nothing . Just <$> ns let p1 = NgramsTablePatch . PM.fromMap $ NgramsReplace Nothing . Just <$> ns
(p0, p0_validity) = PM.singleton nodeId p1 (p, p_validity) = PM.singleton ngramsType p1
(p, p_validity) = PM.singleton ngramsType p0
assertValid p0_validity
assertValid p_validity assertValid p_validity
{- {-
-- TODO -- TODO
...@@ -178,23 +179,11 @@ putListNgrams' nodeId ngramsType ns = do ...@@ -178,23 +179,11 @@ putListNgrams' nodeId ngramsType ns = do
-- The modifyMVar_ would test the patch with applicable first. -- The modifyMVar_ would test the patch with applicable first.
-- If valid the rest would be atomic and no merge is required. -- If valid the rest would be atomic and no merge is required.
-} -}
var <- view repoVar var <- getRepoVar listId
liftBase $ modifyMVar_ var $ \r -> do liftBase $ modifyMVar_ var $ \r -> do
pure $ r & r_version +~ 1 pure $ r & unNodeStory . at listId . _Just . a_version +~ 1
& r_history %~ (p :) & unNodeStory . at listId . _Just . a_history %~ (p :)
& r_state . at ngramsType %~ & unNodeStory . at listId . _Just . a_state . at ngramsType .~ Just ns
(Just .
(at nodeId %~
( Just
. (<> ns)
. something
)
)
. something
)
saveRepo saveRepo
saveRepo :: ( MonadReader env m, MonadBase IO m, HasRepoSaver env )
=> m ()
saveRepo = liftBase =<< view repoSaver
...@@ -16,7 +16,7 @@ module Gargantext.Database.Action.Flow.Pairing ...@@ -16,7 +16,7 @@ module Gargantext.Database.Action.Flow.Pairing
-- (pairing) -- (pairing)
where where
import Control.Lens (_Just, (^.)) import Control.Lens (_Just, (^.), view)
import Data.HashMap.Strict (HashMap) import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HM import qualified Data.HashMap.Strict as HM
import Data.Maybe (catMaybes, fromMaybe) import Data.Maybe (catMaybes, fromMaybe)
...@@ -179,8 +179,8 @@ getNgramsDocId :: CorpusId ...@@ -179,8 +179,8 @@ getNgramsDocId :: CorpusId
-> NgramsType -> NgramsType
-> GargNoServer (HashMap DocAuthor (Set NodeId)) -> GargNoServer (HashMap DocAuthor (Set NodeId))
getNgramsDocId cId lId nt = do getNgramsDocId cId lId nt = do
repo <- getRepo
lIds <- selectNodesWithUsername NodeList userMaster lIds <- selectNodesWithUsername NodeList userMaster
repo <- getRepo' lIds
let ngs = filterListWithRoot MapTerm $ mapTermListRoot [lId] nt repo let ngs = filterListWithRoot MapTerm $ mapTermListRoot [lId] nt repo
groupNodesByNgrams ngs groupNodesByNgrams ngs
......
...@@ -25,6 +25,7 @@ import Gargantext.API.Ngrams.Types ...@@ -25,6 +25,7 @@ import Gargantext.API.Ngrams.Types
import Gargantext.Core.Types (HasInvalidError) import Gargantext.Core.Types (HasInvalidError)
import Gargantext.Core.Flow.Types import Gargantext.Core.Flow.Types
import Gargantext.Core.Text import Gargantext.Core.Text
import Gargantext.Core.NodeStory
import Gargantext.Core.Text.Terms import Gargantext.Core.Text.Terms
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)
...@@ -33,10 +34,9 @@ import Gargantext.Database.Query.Tree.Error (HasTreeError) ...@@ -33,10 +34,9 @@ import Gargantext.Database.Query.Tree.Error (HasTreeError)
type FlowCmdM env err m = type FlowCmdM env err m =
( CmdM env err m ( CmdM env err m
, RepoCmdM env err m , HasNodeStory env err m
, HasNodeError err , HasNodeError err
, HasInvalidError err , HasInvalidError err
, HasRepoVar env
, HasTreeError err , HasTreeError err
) )
......
...@@ -15,10 +15,11 @@ module Gargantext.Database.Action.Metrics ...@@ -15,10 +15,11 @@ module Gargantext.Database.Action.Metrics
import Data.HashMap.Strict (HashMap) import Data.HashMap.Strict (HashMap)
import Data.Vector (Vector) import Data.Vector (Vector)
import Gargantext.API.Ngrams.Tools (filterListWithRoot, groupNodesByNgrams, Diagonal(..), getCoocByNgrams, mapTermListRoot, RootTerm, getRepo) import Gargantext.API.Ngrams.Tools (filterListWithRoot, groupNodesByNgrams, Diagonal(..), getCoocByNgrams, mapTermListRoot, RootTerm, getRepo')
import Gargantext.API.Ngrams.Types (TabType(..), ngramsTypeFromTabType, NgramsTerm) import Gargantext.API.Ngrams.Types (TabType(..), ngramsTypeFromTabType, NgramsTerm)
import Gargantext.Core.Text.Metrics (scored, Scored(..), {-localMetrics, toScored-}) import Gargantext.Core.Text.Metrics (scored, Scored(..), {-localMetrics, toScored-})
import Gargantext.Core.Types (ListType(..), Limit, NodeType(..)) import Gargantext.Core.Types (ListType(..), Limit, NodeType(..))
import Gargantext.Core.NodeStory
import Gargantext.Database.Action.Flow.Types (FlowCmdM) import Gargantext.Database.Action.Flow.Types (FlowCmdM)
import Gargantext.Database.Action.Metrics.NgramsByNode (getNodesByNgramsOnlyUser{-, getTficfWith-}) import Gargantext.Database.Action.Metrics.NgramsByNode (getNodesByNgramsOnlyUser{-, getTficfWith-})
import Gargantext.Database.Admin.Config (userMaster) import Gargantext.Database.Admin.Config (userMaster)
...@@ -61,7 +62,7 @@ getNgramsCooc cId maybeListId tabType maybeLimit = do ...@@ -61,7 +62,7 @@ getNgramsCooc cId maybeListId tabType maybeLimit = do
getNgrams :: (FlowCmdM env err m) getNgrams :: (HasNodeStory env err m)
=> CorpusId -> Maybe ListId -> TabType => CorpusId -> Maybe ListId -> TabType
-> m ( HashMap NgramsTerm (ListType, Maybe NgramsTerm) -> m ( HashMap NgramsTerm (ListType, Maybe NgramsTerm)
, HashMap NgramsTerm (Maybe RootTerm) , HashMap NgramsTerm (Maybe RootTerm)
...@@ -72,8 +73,11 @@ getNgrams cId maybeListId tabType = do ...@@ -72,8 +73,11 @@ getNgrams cId maybeListId tabType = do
Nothing -> defaultList cId Nothing -> defaultList cId
Just lId' -> pure lId' Just lId' -> pure lId'
lists <- mapTermListRoot [lId] (ngramsTypeFromTabType tabType) <$> getRepo lists <- mapTermListRoot [lId] (ngramsTypeFromTabType tabType) <$> getRepo' [lId]
let maybeSyn = HM.unions $ map (\t -> filterListWithRoot t lists) let maybeSyn = HM.unions $ map (\t -> filterListWithRoot t lists)
[MapTerm, StopTerm, CandidateTerm] [MapTerm, StopTerm, CandidateTerm]
pure (lists, maybeSyn) pure (lists, maybeSyn)
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