Commit 099aca69 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[charts] fix cyclic imports

parent 2c86d84e
...@@ -18,8 +18,13 @@ module Main where ...@@ -18,8 +18,13 @@ module Main where
import Control.Exception (finally) import Control.Exception (finally)
import Data.Either import Data.Either
import Data.Text (Text) import Data.Text (Text)
import Prelude (read)
import System.Environment (getArgs)
import qualified Data.Text as Text
import Gargantext.API.Admin.Settings (withDevEnv, runCmdDev)
import Gargantext.API.Admin.Types (DevEnv(..))
import Gargantext.API.Node () -- instances import Gargantext.API.Node () -- instances
import Gargantext.API.Admin.Settings (withDevEnv, runCmdDev, DevEnv)
import Gargantext.API.Prelude (GargError) import Gargantext.API.Prelude (GargError)
import Gargantext.Core (Lang(..)) import Gargantext.Core (Lang(..))
import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Types.Individu (User(..))
...@@ -30,9 +35,6 @@ import Gargantext.Database.Admin.Types.Node (CorpusId) ...@@ -30,9 +35,6 @@ 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.Core.Text.Corpus.Parsers (FileFormat(..)) import Gargantext.Core.Text.Corpus.Parsers (FileFormat(..))
import Prelude (read)
import System.Environment (getArgs)
import qualified Data.Text as Text
main :: IO () main :: IO ()
main = do main = do
......
...@@ -38,11 +38,14 @@ library: ...@@ -38,11 +38,14 @@ library:
exposed-modules: exposed-modules:
- Gargantext - Gargantext
- Gargantext.API - Gargantext.API
- Gargantext.API.Dev
- Gargantext.API.HashedResponse - Gargantext.API.HashedResponse
- Gargantext.API.Node - Gargantext.API.Node
- Gargantext.API.Node.File - Gargantext.API.Node.File
- Gargantext.API.Ngrams - Gargantext.API.Ngrams
- Gargantext.API.Ngrams.Types
- Gargantext.API.Admin.Settings - Gargantext.API.Admin.Settings
- Gargantext.API.Admin.Types
- Gargantext.API.Prelude - Gargantext.API.Prelude
- Gargantext.Core - Gargantext.Core
- Gargantext.Core.Types - Gargantext.Core.Types
......
...@@ -54,14 +54,6 @@ import Data.Version (showVersion) ...@@ -54,14 +54,6 @@ import Data.Version (showVersion)
import GHC.Base (Applicative) import GHC.Base (Applicative)
import GHC.Generics (D1, Meta (..), Rep, Generic) import GHC.Generics (D1, Meta (..), Rep, Generic)
import GHC.TypeLits (AppendSymbol, Symbol) import GHC.TypeLits (AppendSymbol, Symbol)
import Gargantext.Prelude.Config (gc_url)
import Gargantext.API.Admin.Auth (AuthContext, auth)
import Gargantext.API.Admin.FrontEnd (frontEndServer)
import Gargantext.API.Admin.Settings
import Gargantext.API.Ngrams (HasRepoSaver(..), saveRepo)
import Gargantext.API.Prelude
import Gargantext.API.Routes
import Gargantext.Prelude
import Network.HTTP.Types hiding (Query) import Network.HTTP.Types hiding (Query)
import Network.Wai import Network.Wai
import Network.Wai.Handler.Warp hiding (defaultSettings) import Network.Wai.Handler.Warp hiding (defaultSettings)
...@@ -76,8 +68,19 @@ import System.IO (FilePath) ...@@ -76,8 +68,19 @@ import System.IO (FilePath)
import qualified Data.ByteString.Lazy.Char8 as BL8 import qualified Data.ByteString.Lazy.Char8 as BL8
import qualified Data.Text.IO as T import qualified Data.Text.IO as T
import qualified Paths_gargantext as PG -- cabal magic build module import qualified Paths_gargantext as PG -- cabal magic build module
import qualified Gargantext.API.Public as Public import qualified Gargantext.API.Public as Public
import Gargantext.Prelude.Config (gc_url)
import Gargantext.API.Admin.Auth (AuthContext, auth)
import Gargantext.API.Admin.FrontEnd (frontEndServer)
import Gargantext.API.Admin.Settings (newEnv)
import Gargantext.API.Admin.Types (FireWall(..), PortNumber, cookieSettings, env_gargConfig, jwtSettings, settings)
import Gargantext.API.Ngrams (HasRepoSaver(..), saveRepo)
import Gargantext.API.Prelude
import Gargantext.API.Routes
import Gargantext.Prelude
data Mode = Dev | Mock | Prod data Mode = Dev | Mock | Prod
deriving (Show, Read, Generic) deriving (Show, Read, Generic)
......
...@@ -33,22 +33,23 @@ import Data.Text (Text) ...@@ -33,22 +33,23 @@ import Data.Text (Text)
import Data.Text.Lazy (toStrict) import Data.Text.Lazy (toStrict)
import Data.Text.Lazy.Encoding (decodeUtf8) import Data.Text.Lazy.Encoding (decodeUtf8)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Gargantext.API.Admin.Settings import Servant
import Servant.Auth.Server
import Test.QuickCheck (elements, oneof)
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
import qualified Gargantext.Prelude.Crypto.Auth as Auth
import Gargantext.API.Admin.Types
import Gargantext.API.Prelude (HasJoseError(..), joseError, HasServerError, GargServerC) import Gargantext.API.Prelude (HasJoseError(..), joseError, HasServerError, GargServerC)
import Gargantext.Core.Types.Individu (User(..), Username, GargPassword(..), arbitraryUsername, arbitraryPassword) import Gargantext.Core.Types.Individu (User(..), Username, GargPassword(..), arbitraryUsername, arbitraryPassword)
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger) import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
import Gargantext.Database.Query.Tree (isDescendantOf, isIn) import Gargantext.Database.Query.Tree (isDescendantOf, isIn)
import Gargantext.Database.Query.Tree.Root (getRoot) import Gargantext.Database.Query.Tree.Root (getRoot)
import Gargantext.Database.Schema.Node (NodePoly(_node_id)) import Gargantext.Database.Schema.Node (NodePoly(_node_id))
import Gargantext.Database.Admin.Types.Node (NodeId(..), UserId, ListId, DocId) import Gargantext.Database.Admin.Types.Node (NodeId(..), UserId, ListId, DocId)
import Gargantext.Database.Prelude (Cmd', CmdM, HasConnectionPool, HasConfig) import Gargantext.Database.Prelude (Cmd', CmdM, HasConnectionPool, HasConfig)
import Gargantext.Prelude hiding (reverse) import Gargantext.Prelude hiding (reverse)
import Gargantext.Database.Query.Table.User import Gargantext.Database.Query.Table.User
import Servant
import Servant.Auth.Server
import Test.QuickCheck (elements, oneof)
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
import qualified Gargantext.Prelude.Crypto.Auth as Auth
--------------------------------------------------- ---------------------------------------------------
......
...@@ -17,10 +17,6 @@ module Gargantext.API.Admin.Orchestrator where ...@@ -17,10 +17,6 @@ module Gargantext.API.Admin.Orchestrator where
import Control.Lens hiding (elements) import Control.Lens hiding (elements)
import Data.Aeson import Data.Aeson
import Data.Text import Data.Text
import Gargantext.API.Admin.Orchestrator.Scrapy.Schedule
import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.Admin.Settings
import Gargantext.Prelude
import Servant import Servant
import Servant.Job.Async import Servant.Job.Async
import Servant.Job.Client import Servant.Job.Client
...@@ -28,6 +24,11 @@ import Servant.Job.Server ...@@ -28,6 +24,11 @@ import Servant.Job.Server
import Servant.Job.Utils (extendBaseUrl) import Servant.Job.Utils (extendBaseUrl)
import qualified Data.ByteString.Lazy.Char8 as LBS import qualified Data.ByteString.Lazy.Char8 as LBS
import Gargantext.API.Admin.Orchestrator.Scrapy.Schedule
import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.Admin.Types
import Gargantext.Prelude
callJobScrapy :: (ToJSON e, FromJSON e, FromJSON o, MonadClientJob m) callJobScrapy :: (ToJSON e, FromJSON e, FromJSON o, MonadClientJob m)
=> JobServerURL e Schedule o => JobServerURL e Schedule o
-> (URL -> Schedule) -> (URL -> Schedule)
......
...@@ -25,24 +25,15 @@ import Control.Exception (finally) ...@@ -25,24 +25,15 @@ import Control.Exception (finally)
import Control.Lens import Control.Lens
import Control.Monad.Logger import Control.Monad.Logger
import Control.Monad.Reader import Control.Monad.Reader
import Data.ByteString (ByteString)
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
import Data.Pool (Pool, createPool) import Data.Pool (Pool, createPool)
import Data.Text import Data.Text
import Database.PostgreSQL.Simple (Connection, connect, close, ConnectInfo) import Database.PostgreSQL.Simple (Connection, connect, close, ConnectInfo)
import GHC.Enum
import GHC.Generics (Generic)
import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.Ngrams (NgramsRepo, HasRepoVar(..), HasRepoSaver(..), HasRepo(..), RepoEnv(..), r_version, saveRepo, initRepo, renv_var, renv_lock)
import Gargantext.Database.Prelude (databaseParameters, HasConnectionPool(..), Cmd', runCmd, HasConfig(..))
import Gargantext.Prelude
import Network.HTTP.Client (Manager)
import Network.HTTP.Client.TLS (newTlsManager) import Network.HTTP.Client.TLS (newTlsManager)
import Servant import Servant
import Servant.Auth.Server (defaultJWTSettings, JWTSettings, CookieSettings(..), XsrfCookieSettings(..), defaultCookieSettings, defaultXsrfCookieSettings, readKey, writeKey) import Servant.Auth.Server (defaultJWTSettings, CookieSettings(..), XsrfCookieSettings(..), defaultCookieSettings, defaultXsrfCookieSettings, readKey, writeKey)
import Servant.Client (BaseUrl, parseBaseUrl) import Servant.Client (parseBaseUrl)
import Servant.Job.Async (newJobEnv, defaultSettings, HasJobEnv(..), Job) import Servant.Job.Async (newJobEnv, defaultSettings)
import System.Directory import System.Directory
import System.Environment (lookupEnv) import System.Environment (lookupEnv)
import System.FileLock (tryLockFile, unlockFile, SharedExclusive(Exclusive)) import System.FileLock (tryLockFile, unlockFile, SharedExclusive(Exclusive))
...@@ -50,35 +41,13 @@ import System.IO (FilePath, hClose) ...@@ -50,35 +41,13 @@ import System.IO (FilePath, hClose)
import System.IO.Temp (withTempFile) import System.IO.Temp (withTempFile)
import System.Log.FastLogger import System.Log.FastLogger
import qualified Data.ByteString.Lazy as L import qualified Data.ByteString.Lazy as L
import qualified Servant.Job.Core
import Gargantext.Prelude.Config (GargConfig(..), gc_repofilepath, readConfig, defaultConfig)
type PortNumber = Int
data SendEmailType = SendEmailViaAws
| LogEmailToConsole
| WriteEmailToFile
deriving (Show, Read, Enum, Bounded, Generic)
data Settings = Settings
{ _allowedOrigin :: ByteString -- allowed origin for CORS
, _allowedHost :: ByteString -- allowed host for CORS
, _appPort :: PortNumber
, _logLevelLimit :: LogLevel -- log level from the monad-logger package
-- , _dbServer :: Text
-- ^ this is not used yet
, _jwtSettings :: JWTSettings
, _cookieSettings :: CookieSettings
, _sendLoginEmails :: SendEmailType
, _scrapydUrl :: BaseUrl
, _config :: GargConfig
}
makeLenses ''Settings
class HasSettings env where import Gargantext.API.Admin.Types
settings :: Getter env Settings import Gargantext.API.Ngrams.Types (NgramsRepo, HasRepo(..), RepoEnv(..), r_version, initRepo, renv_var, renv_lock)
import Gargantext.API.Ngrams (saveRepo)
import Gargantext.Database.Prelude (databaseParameters, Cmd', runCmd, HasConfig(..))
import Gargantext.Prelude
import Gargantext.Prelude.Config (GargConfig(..), gc_repofilepath, readConfig, defaultConfig)
devSettings :: FilePath -> IO Settings devSettings :: FilePath -> IO Settings
devSettings jwkFile = do devSettings jwkFile = do
...@@ -124,53 +93,6 @@ optSetting name d = do ...@@ -124,53 +93,6 @@ optSetting name d = do
-- <*> (parseJwk <$> reqSetting "JWT_SECRET") -- <*> (parseJwk <$> reqSetting "JWT_SECRET")
-- <*> optSetting "SEND_EMAIL" SendEmailViaAws -- <*> optSetting "SEND_EMAIL" SendEmailViaAws
data FireWall = FireWall { unFireWall :: Bool }
data Env = Env
{ _env_settings :: !Settings
, _env_logger :: !LoggerSet
, _env_pool :: !(Pool Connection)
, _env_repo :: !RepoEnv
, _env_manager :: !Manager
, _env_self_url :: !BaseUrl
, _env_scrapers :: !ScrapersEnv
, _env_gargConfig :: !GargConfig
}
deriving (Generic)
makeLenses ''Env
instance HasConfig Env where
hasConfig = env_gargConfig
instance HasConnectionPool Env where
connPool = env_pool
instance HasRepoVar Env where
repoVar = repoEnv . repoVar
instance HasRepoSaver Env where
repoSaver = repoEnv . repoSaver
instance HasRepo Env where
repoEnv = env_repo
instance HasSettings Env where
settings = env_settings
instance Servant.Job.Core.HasEnv Env (Job JobLog JobLog) where
_env = env_scrapers . Servant.Job.Core._env
instance HasJobEnv Env JobLog JobLog where
job_env = env_scrapers
data MockEnv = MockEnv
{ _menv_firewall :: !FireWall
}
deriving (Generic)
makeLenses ''MockEnv
----------------------------------------------------------------------- -----------------------------------------------------------------------
-- | RepoDir FilePath configuration -- | RepoDir FilePath configuration
type RepoDirFilePath = FilePath type RepoDirFilePath = FilePath
...@@ -266,33 +188,6 @@ newEnv port file = do ...@@ -266,33 +188,6 @@ 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
data DevEnv = DevEnv
{ _dev_env_pool :: !(Pool Connection)
, _dev_env_repo :: !RepoEnv
, _dev_env_settings :: !Settings
, _dev_env_config :: !GargConfig
}
makeLenses ''DevEnv
instance HasConfig DevEnv where
hasConfig = dev_env_config
instance HasConnectionPool DevEnv where
connPool = dev_env_pool
instance HasRepoVar DevEnv where
repoVar = repoEnv . repoVar
instance HasRepoSaver DevEnv where
repoSaver = repoEnv . repoSaver
instance HasRepo DevEnv where
repoEnv = dev_env_repo
instance HasSettings DevEnv where
settings = dev_env_settings
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)
......
-- |
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.API.Admin.Types where
import Control.Lens
import Control.Monad.Logger
import Data.ByteString (ByteString)
import Data.Pool (Pool)
import Database.PostgreSQL.Simple (Connection)
import GHC.Enum
import GHC.Generics (Generic)
import Network.HTTP.Client (Manager)
import Servant.Auth.Server (JWTSettings, CookieSettings(..))
import Servant.Client (BaseUrl)
import Servant.Job.Async (HasJobEnv(..), Job)
import System.Log.FastLogger
import qualified Servant.Job.Core
import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.Ngrams.Types (HasRepoVar(..), HasRepoSaver(..), HasRepo(..), RepoEnv(..))
import Gargantext.Database.Prelude (HasConnectionPool(..), HasConfig(..))
import Gargantext.Prelude
import Gargantext.Prelude.Config (GargConfig(..))
type PortNumber = Int
data SendEmailType = SendEmailViaAws
| LogEmailToConsole
| WriteEmailToFile
deriving (Show, Read, Enum, Bounded, Generic)
data Settings = Settings
{ _allowedOrigin :: ByteString -- allowed origin for CORS
, _allowedHost :: ByteString -- allowed host for CORS
, _appPort :: PortNumber
, _logLevelLimit :: LogLevel -- log level from the monad-logger package
-- , _dbServer :: Text
-- ^ this is not used yet
, _jwtSettings :: JWTSettings
, _cookieSettings :: CookieSettings
, _sendLoginEmails :: SendEmailType
, _scrapydUrl :: BaseUrl
, _config :: GargConfig
}
makeLenses ''Settings
class HasSettings env where
settings :: Getter env Settings
data FireWall = FireWall { unFireWall :: Bool }
data Env = Env
{ _env_settings :: !Settings
, _env_logger :: !LoggerSet
, _env_pool :: !(Pool Connection)
, _env_repo :: !RepoEnv
, _env_manager :: !Manager
, _env_self_url :: !BaseUrl
, _env_scrapers :: !ScrapersEnv
, _env_gargConfig :: !GargConfig
}
deriving (Generic)
makeLenses ''Env
instance HasConfig Env where
hasConfig = env_gargConfig
instance HasConnectionPool Env where
connPool = env_pool
instance HasRepoVar Env where
repoVar = repoEnv . repoVar
instance HasRepoSaver Env where
repoSaver = repoEnv . repoSaver
instance HasRepo Env where
repoEnv = env_repo
instance HasSettings Env where
settings = env_settings
instance Servant.Job.Core.HasEnv Env (Job JobLog JobLog) where
_env = env_scrapers . Servant.Job.Core._env
instance HasJobEnv Env JobLog JobLog where
job_env = env_scrapers
data MockEnv = MockEnv
{ _menv_firewall :: !FireWall
}
deriving (Generic)
makeLenses ''MockEnv
data DevEnv = DevEnv
{ _dev_env_pool :: !(Pool Connection)
, _dev_env_repo :: !RepoEnv
, _dev_env_settings :: !Settings
, _dev_env_config :: !GargConfig
}
makeLenses ''DevEnv
instance HasConfig DevEnv where
hasConfig = dev_env_config
instance HasConnectionPool DevEnv where
connPool = dev_env_pool
instance HasRepoVar DevEnv where
repoVar = repoEnv . repoVar
instance HasRepoSaver DevEnv where
repoSaver = repoEnv . repoSaver
instance HasRepo DevEnv where
repoEnv = dev_env_repo
instance HasSettings DevEnv where
settings = dev_env_settings
-- |
module Gargantext.API.Dev where
import Gargantext.API.Admin.Settings
import Gargantext.API.Prelude
import Gargantext.API.Admin.Types
import Gargantext.Database.Prelude
import Gargantext.Prelude
-------------------------------------------------------------------
runCmdReplEasy :: Cmd' DevEnv GargError a -> IO a
runCmdReplEasy f = withDevEnv "gargantext.ini" $ \env -> runCmdDev env f
...@@ -25,7 +25,8 @@ import Data.Text (Text) ...@@ -25,7 +25,8 @@ import Data.Text (Text)
import Servant import Servant
import Gargantext.API.HashedResponse import Gargantext.API.HashedResponse
import Gargantext.API.Ngrams import Gargantext.API.Ngrams (ngramsTypeFromTabType)
import Gargantext.API.Ngrams.Types
import Gargantext.API.Ngrams.NTree import Gargantext.API.Ngrams.NTree
import Gargantext.API.Prelude (GargServer) import Gargantext.API.Prelude (GargServer)
import Gargantext.Core.Types (CorpusId, Limit, ListId, ListType(..)) import Gargantext.Core.Types (CorpusId, Limit, ListId, ListType(..))
......
...@@ -21,7 +21,6 @@ add get ...@@ -21,7 +21,6 @@ add get
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeFamilies #-}
{-# OPTIONS -fno-warn-orphans #-}
module Gargantext.API.Ngrams module Gargantext.API.Ngrams
( TableNgramsApi ( TableNgramsApi
...@@ -44,7 +43,6 @@ module Gargantext.API.Ngrams ...@@ -44,7 +43,6 @@ module Gargantext.API.Ngrams
, NgramsElement(..) , NgramsElement(..)
, mkNgramsElement , mkNgramsElement
, mergeNgramsElement
, RootParent(..) , RootParent(..)
...@@ -120,10 +118,12 @@ import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary) ...@@ -120,10 +118,12 @@ import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
import Prelude (error) import Prelude (error)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.API.Admin.Types (HasSettings)
import Gargantext.API.Ngrams.Types import Gargantext.API.Ngrams.Types
import Gargantext.Core.Types (ListType(..), NodeId, ListId, DocId, Limit, Offset, HasInvalidError, assertValid) import Gargantext.Core.Types (ListType(..), NodeId, ListId, DocId, Limit, Offset, HasInvalidError, assertValid)
import Gargantext.Core.Types (TODO) import Gargantext.Core.Types (TODO)
import Gargantext.Core.Viz.Graph.API (graphRecompute) import Gargantext.Core.Viz.Graph.API (recomputeGraph)
import Gargantext.Core.Viz.Graph.Distances (Distance(Conditional))
import Gargantext.Database.Action.Metrics.NgramsByNode (getOccByNgramsOnlyFast') import Gargantext.Database.Action.Metrics.NgramsByNode (getOccByNgramsOnlyFast')
import Gargantext.Database.Query.Table.Node.Select import Gargantext.Database.Query.Table.Node.Select
import Gargantext.Database.Query.Table.Ngrams hiding (NgramsType(..), ngrams, ngramsType, ngrams_terms) import Gargantext.Database.Query.Table.Ngrams hiding (NgramsType(..), ngrams, ngramsType, ngrams_terms)
...@@ -132,6 +132,8 @@ import Gargantext.Database.Query.Table.Node.Error (HasNodeError) ...@@ -132,6 +132,8 @@ import Gargantext.Database.Query.Table.Node.Error (HasNodeError)
import Gargantext.Database.Admin.Types.Node (NodeType(..)) import Gargantext.Database.Admin.Types.Node (NodeType(..))
import Gargantext.Database.Prelude (HasConnectionPool, HasConfig) import Gargantext.Database.Prelude (HasConnectionPool, HasConfig)
import qualified Gargantext.Database.Query.Table.Ngrams as TableNgrams import qualified Gargantext.Database.Query.Table.Ngrams as TableNgrams
import Gargantext.Database.Query.Table.Node (getNode)
import Gargantext.Database.Schema.Node (NodePoly(..))
{- {-
-- TODO sequences of modifications (Patchs) -- TODO sequences of modifications (Patchs)
...@@ -389,7 +391,12 @@ tableNgramsPull listId ngramsType p_version = do ...@@ -389,7 +391,12 @@ tableNgramsPull listId ngramsType p_version = do
-- Apply the given patch to the DB and returns the patch to be applied on the -- Apply the given patch to the DB and returns the patch to be applied on the
-- client. -- client.
-- TODO-ACCESS check -- TODO-ACCESS check
tableNgramsPut :: (HasInvalidError err, RepoCmdM env err m) tableNgramsPut :: (HasNodeError err,
HasInvalidError err,
HasConfig env,
HasConnectionPool env,
HasSettings env,
RepoCmdM env err m)
=> TabType => TabType
-> ListId -> ListId
-> Versioned NgramsTablePatch -> Versioned NgramsTablePatch
...@@ -410,15 +417,13 @@ tableNgramsPut tabType listId (Versioned p_version p_table) ...@@ -410,15 +417,13 @@ tableNgramsPut tabType listId (Versioned p_version p_table)
ret <- commitStatePatch (Versioned p_version p) ret <- commitStatePatch (Versioned p_version p)
<&> v_data %~ (view (_PatchMap . at ngramsType . _Just . _PatchMap . at listId . _Just)) <&> v_data %~ (view (_PatchMap . at ngramsType . _Just . _PatchMap . at listId . _Just))
node <- getNodeWith ListId node <- getNode listId
let nId = _node_id node let nId = _node_id node
uId = _node_userId node uId = _node_userId node
recomputeGraph uId nId Conditional _ <- recomputeGraph uId nId Conditional
pure ret pure ret
mergeNgramsElement :: NgramsRepoElement -> NgramsRepoElement -> NgramsRepoElement
mergeNgramsElement _neOld neNew = neNew
{- {-
{ _ne_list :: ListType { _ne_list :: ListType
If we merge the parents/children we can potentially create cycles! If we merge the parents/children we can potentially create cycles!
...@@ -589,7 +594,6 @@ scoresRecomputeTableNgrams nId tabType listId = do ...@@ -589,7 +594,6 @@ scoresRecomputeTableNgrams nId tabType listId = do
-- APIs -- APIs
-- TODO: find a better place for the code above, All APIs stay here -- TODO: find a better place for the code above, All APIs stay here
type QueryParamR = QueryParam' '[Required, Strict]
data OrderBy = TermAsc | TermDesc | ScoreAsc | ScoreDesc data OrderBy = TermAsc | TermDesc | ScoreAsc | ScoreDesc
deriving (Generic, Enum, Bounded, Read, Show) deriving (Generic, Enum, Bounded, Read, Show)
...@@ -700,6 +704,7 @@ apiNgramsTableCorpus :: ( RepoCmdM env err m ...@@ -700,6 +704,7 @@ apiNgramsTableCorpus :: ( RepoCmdM env err m
, HasInvalidError err , HasInvalidError err
, HasConnectionPool env , HasConnectionPool env
, HasConfig env , HasConfig env
, HasSettings env
) )
=> NodeId -> ServerT TableNgramsApi m => NodeId -> ServerT TableNgramsApi m
apiNgramsTableCorpus cId = getTableNgramsCorpus cId apiNgramsTableCorpus cId = getTableNgramsCorpus cId
...@@ -712,6 +717,7 @@ apiNgramsTableDoc :: ( RepoCmdM env err m ...@@ -712,6 +717,7 @@ apiNgramsTableDoc :: ( RepoCmdM env err m
, HasInvalidError err , HasInvalidError err
, HasConnectionPool env , HasConnectionPool env
, HasConfig env , HasConfig env
, HasSettings env
) )
=> DocId -> ServerT TableNgramsApi m => DocId -> ServerT TableNgramsApi m
apiNgramsTableDoc dId = getTableNgramsDoc dId apiNgramsTableDoc dId = getTableNgramsDoc dId
......
...@@ -27,15 +27,16 @@ import Servant.Job.Async ...@@ -27,15 +27,16 @@ import Servant.Job.Async
import Servant.Job.Utils (jsonOptions) import Servant.Job.Utils (jsonOptions)
import Web.FormUrlEncoded (FromForm) import Web.FormUrlEncoded (FromForm)
import Gargantext.Prelude
import Gargantext.API.Node.Corpus.New.File (FileType(..))
import Gargantext.API.Ngrams
import Gargantext.API.Admin.Orchestrator.Types import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.Ngrams (getNgramsTableMap, setListNgrams)
import Gargantext.API.Ngrams.Types (NgramsTableMap, RepoCmdM, Versioned(..))
import Gargantext.API.Node.Corpus.New.File (FileType(..))
import Gargantext.API.Prelude (GargServer) import Gargantext.API.Prelude (GargServer)
import Gargantext.Core.Utils.Prefix (unPrefixSwagger) import Gargantext.Core.Utils.Prefix (unPrefixSwagger)
import Gargantext.Database.Action.Flow (FlowCmdM) import Gargantext.Database.Action.Flow (FlowCmdM)
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Schema.Ngrams (NgramsType(..), ngramsTypes) import Gargantext.Database.Schema.Ngrams (NgramsType(..), ngramsTypes)
import Gargantext.Prelude
------------------------------------------------------------------------ ------------------------------------------------------------------------
type NgramsList = (Map NgramsType (Versioned NgramsTableMap)) type NgramsList = (Map NgramsType (Versioned NgramsTableMap))
......
...@@ -29,7 +29,7 @@ import Test.QuickCheck ...@@ -29,7 +29,7 @@ import Test.QuickCheck
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.API.Ngrams import Gargantext.API.Ngrams.Types
import Gargantext.Core.Types (ListType(..), NodeId) import Gargantext.Core.Types (ListType(..), NodeId)
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger) import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
......
...@@ -23,11 +23,14 @@ import Data.Set (Set) ...@@ -23,11 +23,14 @@ import Data.Set (Set)
import Data.Text (Text) import Data.Text (Text)
import Data.Validity import Data.Validity
import Gargantext.API.Ngrams import Gargantext.API.Ngrams.Types
import Gargantext.Core.Types (ListType(..), NodeId, ListId) import Gargantext.Core.Types (ListType(..), NodeId, ListId)
import Gargantext.Database.Schema.Ngrams (NgramsType) import Gargantext.Database.Schema.Ngrams (NgramsType)
import Gargantext.Prelude import Gargantext.Prelude
mergeNgramsElement :: NgramsRepoElement -> NgramsRepoElement -> NgramsRepoElement
mergeNgramsElement _neOld neNew = neNew
type RootTerm = Text type RootTerm = Text
getRepo :: RepoCmdM env err m => m NgramsRepo getRepo :: RepoCmdM env err m => m NgramsRepo
......
...@@ -712,6 +712,9 @@ type RepoCmdM env err m = ...@@ -712,6 +712,9 @@ type RepoCmdM env err m =
) )
type QueryParamR = QueryParam' '[Required, Strict]
-- Instances -- Instances
instance Arbitrary NgramsRepoElement where instance Arbitrary NgramsRepoElement where
arbitrary = elements $ map ngramsElementToRepo ns arbitrary = elements $ map ngramsElementToRepo ns
......
...@@ -29,8 +29,13 @@ import Data.Maybe (Maybe(..)) ...@@ -29,8 +29,13 @@ import Data.Maybe (Maybe(..))
import Data.Swagger import Data.Swagger
import Data.Text (Text) import Data.Text (Text)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Servant
import Servant.Job.Async (JobFunction(..), serveJobsAPI)
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary
import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs) import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs)
import Gargantext.API.Admin.Settings (HasSettings) import Gargantext.API.Admin.Types (HasSettings)
import Gargantext.API.Node import Gargantext.API.Node
import Gargantext.API.Prelude (GargServer, simuLogs) import Gargantext.API.Prelude (GargServer, simuLogs)
import Gargantext.Core (Lang(..)) import Gargantext.Core (Lang(..))
...@@ -42,10 +47,6 @@ import Gargantext.Database.Admin.Types.Hyperdata (HyperdataAnnuaire(..), Hyperda ...@@ -42,10 +47,6 @@ 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 Servant
import Servant.Job.Async (JobFunction(..), serveJobsAPI)
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary
------------------------------------------------------------------------ ------------------------------------------------------------------------
type API = "contact" :> Summary "Contact endpoint" type API = "contact" :> Summary "Contact endpoint"
......
...@@ -28,7 +28,7 @@ import Data.Set (Set) ...@@ -28,7 +28,7 @@ import Data.Set (Set)
import Data.Swagger import Data.Swagger
import Data.Text (Text) import Data.Text (Text)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Gargantext.API.Ngrams 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)
......
...@@ -37,7 +37,7 @@ import Gargantext.Prelude ...@@ -37,7 +37,7 @@ 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 qualified Gargantext.API.Admin.Orchestrator.Types as T
import Gargantext.API.Admin.Settings (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-})
......
...@@ -29,7 +29,7 @@ import qualified Gargantext.Prelude.Utils as GPU ...@@ -29,7 +29,7 @@ import qualified Gargantext.Prelude.Utils as GPU
import Gargantext.Core.Types (TODO) import Gargantext.Core.Types (TODO)
import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs) import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs)
import Gargantext.API.Admin.Settings (HasSettings) import Gargantext.API.Admin.Types (HasSettings)
import Gargantext.API.Node.Types import Gargantext.API.Node.Types
import Gargantext.API.Prelude import Gargantext.API.Prelude
import Gargantext.Database.Action.Flow.Types import Gargantext.Database.Action.Flow.Types
......
...@@ -18,19 +18,20 @@ Polymorphic Get Node API ...@@ -18,19 +18,20 @@ Polymorphic Get Node API
module Gargantext.API.Node.Get module Gargantext.API.Node.Get
where where
-- import Gargantext.API.Admin.Settings (HasSettings) -- import Gargantext.API.Admin.Types (HasSettings)
-- import Servant.Job.Async (JobFunction(..), serveJobsAPI) -- import Servant.Job.Async (JobFunction(..), serveJobsAPI)
-- import Test.QuickCheck (elements) -- import Test.QuickCheck (elements)
-- import Gargantext.Database.Action.Flow.Types (FlowCmdM) -- import Gargantext.Database.Action.Flow.Types (FlowCmdM)
import Data.Aeson import Data.Aeson
import Data.Swagger import Data.Swagger
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Servant
import Test.QuickCheck.Arbitrary
import Gargantext.API.Prelude import Gargantext.API.Prelude
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Query.Table.Node (JSONB{-, getNodeWith-}) import Gargantext.Database.Query.Table.Node (JSONB{-, getNodeWith-})
import Gargantext.Prelude import Gargantext.Prelude
import Servant
import Test.QuickCheck.Arbitrary
------------------------------------------------------------------------ ------------------------------------------------------------------------
type API a = Summary "Polymorphic Get Node Endpoint" type API a = Summary "Polymorphic Get Node Endpoint"
......
...@@ -11,7 +11,6 @@ Portability : POSIX ...@@ -11,7 +11,6 @@ Portability : POSIX
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Gargantext.API.Node.Share module Gargantext.API.Node.Share
where where
...@@ -20,6 +19,10 @@ import Data.Aeson ...@@ -20,6 +19,10 @@ import Data.Aeson
import Data.Swagger import Data.Swagger
import Data.Text (Text) import Data.Text (Text)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Servant
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary
import Gargantext.API.Prelude import Gargantext.API.Prelude
import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Database.Action.Share (ShareNodeWith(..)) import Gargantext.Database.Action.Share (ShareNodeWith(..))
...@@ -28,9 +31,6 @@ import Gargantext.Database.Admin.Types.Node ...@@ -28,9 +31,6 @@ import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Prelude import Gargantext.Database.Prelude
import Gargantext.Database.Query.Table.Node.Error (HasNodeError(..)) import Gargantext.Database.Query.Table.Node.Error (HasNodeError(..))
import Gargantext.Prelude import Gargantext.Prelude
import Servant
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary
------------------------------------------------------------------------ ------------------------------------------------------------------------
data ShareNodeParams = ShareTeamParams { username :: Text } data ShareNodeParams = ShareTeamParams { username :: Text }
......
...@@ -20,8 +20,14 @@ import Data.Aeson ...@@ -20,8 +20,14 @@ import Data.Aeson
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Swagger import Data.Swagger
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Prelude (Enum, Bounded, minBound, maxBound)
import Servant
import Servant.Job.Async (JobFunction(..), serveJobsAPI)
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary
import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs) import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs)
import Gargantext.API.Admin.Settings (HasSettings) import Gargantext.API.Admin.Types (HasSettings)
import Gargantext.API.Prelude (GargServer, simuLogs) import Gargantext.API.Prelude (GargServer, simuLogs)
import Gargantext.Core.Viz.Graph.API (recomputeGraph) import Gargantext.Core.Viz.Graph.API (recomputeGraph)
import Gargantext.Core.Viz.Graph.Distances (GraphMetric(..), Distance(..)) import Gargantext.Core.Viz.Graph.Distances (GraphMetric(..), Distance(..))
...@@ -29,11 +35,6 @@ import Gargantext.Database.Action.Flow.Pairing (pairing) ...@@ -29,11 +35,6 @@ import Gargantext.Database.Action.Flow.Pairing (pairing)
import Gargantext.Database.Action.Flow.Types (FlowCmdM) import Gargantext.Database.Action.Flow.Types (FlowCmdM)
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
import Gargantext.Prelude (Ord, Eq, (<$>), ($), liftBase, (.), printDebug, pure, show, cs, (<>), panic) import Gargantext.Prelude (Ord, Eq, (<$>), ($), liftBase, (.), printDebug, pure, show, cs, (<>), panic)
import Prelude (Enum, Bounded, minBound, maxBound)
import Servant
import Servant.Job.Async (JobFunction(..), serveJobsAPI)
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary
------------------------------------------------------------------------ ------------------------------------------------------------------------
type API = Summary " Update node according to NodeType params" type API = Summary " Update node according to NodeType params"
......
...@@ -38,8 +38,8 @@ import Servant.Job.Async ...@@ -38,8 +38,8 @@ import Servant.Job.Async
import Servant.Job.Core (HasServerError(..), serverError) import Servant.Job.Core (HasServerError(..), serverError)
import Gargantext.API.Admin.Orchestrator.Types import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.Admin.Settings import Gargantext.API.Admin.Types
import Gargantext.API.Ngrams import Gargantext.API.Ngrams.Types
import Gargantext.Core.Types import Gargantext.Core.Types
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(..))
...@@ -104,10 +104,6 @@ type EnvC env = ...@@ -104,10 +104,6 @@ type EnvC env =
, HasConfig env , HasConfig env
) )
-------------------------------------------------------------------
runCmdReplEasy :: Cmd' DevEnv GargError a -> IO a
runCmdReplEasy f = withDevEnv "gargantext.ini" $ \env -> runCmdDev env f
------------------------------------------------------------------- -------------------------------------------------------------------
-- | This Type is needed to prepare the function before the GargServer -- | This Type is needed to prepare the function before the GargServer
type GargNoServer' env err m = type GargNoServer' env err m =
......
...@@ -19,18 +19,19 @@ module Gargantext.Core.Text.List.Learn ...@@ -19,18 +19,19 @@ module Gargantext.Core.Text.List.Learn
import Control.Monad.Reader (MonadReader) import Control.Monad.Reader (MonadReader)
-- TODO remvoe this deps -- TODO remvoe this deps
import Gargantext.API.Admin.Settings
import Data.Map (Map)
import Gargantext.Core.Types.Main (ListType(..), listTypeId, fromListTypeId)
import Gargantext.Prelude
import Gargantext.Prelude.Utils
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 Data.Map (Map)
import qualified Data.Map as Map import qualified Data.Map as Map
import qualified Data.SVM as SVM import qualified Data.SVM as SVM
import qualified Data.Vector as Vec import qualified Data.Vector as Vec
import Gargantext.API.Admin.Types
import Gargantext.Core.Text.Metrics.Count (occurrencesWith)
import Gargantext.Core.Types.Main (ListType(..), listTypeId, fromListTypeId)
import Gargantext.Prelude
import Gargantext.Prelude.Utils
------------------------------------------------------------------------ ------------------------------------------------------------------------
train :: Double -> Double -> SVM.Problem -> IO SVM.Model train :: Double -> Double -> SVM.Problem -> IO SVM.Model
train x y = (SVM.train (SVM.CSvc x) (SVM.RBF y)) train x y = (SVM.train (SVM.CSvc x) (SVM.RBF y))
......
...@@ -10,8 +10,6 @@ Portability : POSIX ...@@ -10,8 +10,6 @@ Portability : POSIX
-} -}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE OverloadedLists #-} -- allows to write Map and HashMap as lists {-# LANGUAGE OverloadedLists #-} -- allows to write Map and HashMap as lists
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
......
...@@ -21,7 +21,7 @@ import Control.Lens (view, (^.)) ...@@ -21,7 +21,7 @@ import Control.Lens (view, (^.))
import Data.Text import Data.Text
import Servant import Servant
import Gargantext.API.Admin.Settings import Gargantext.API.Admin.Types
import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Database.Action.Flow.Utils (getUserId) import Gargantext.Database.Action.Flow.Utils (getUserId)
import Gargantext.Database.Action.Share (delFolderTeam) import Gargantext.Database.Action.Share (delFolderTeam)
......
...@@ -9,8 +9,6 @@ Portability : POSIX ...@@ -9,8 +9,6 @@ Portability : POSIX
-} -}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Gargantext.Prelude.Utils module Gargantext.Prelude.Utils
where where
...@@ -27,7 +25,7 @@ import System.IO.Error ...@@ -27,7 +25,7 @@ import System.IO.Error
import System.Random (newStdGen) import System.Random (newStdGen)
import qualified System.Random.Shuffle as SRS import qualified System.Random.Shuffle as SRS
import Gargantext.API.Admin.Settings import Gargantext.API.Admin.Types
import Gargantext.Prelude.Config import Gargantext.Prelude.Config
import Gargantext.Prelude.Crypto.Hash import Gargantext.Prelude.Crypto.Hash
import Gargantext.Database.Admin.Types.Node (NodeId, NodeType) import Gargantext.Database.Admin.Types.Node (NodeId, NodeType)
......
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