Commit 468179ec authored by Alexandre Delanoë's avatar Alexandre Delanoë

[CLEAN] removing NgramsRepo which is not used any more

parent 4dc0a50e
......@@ -368,19 +368,19 @@ executables:
- gargantext-prelude
- base
gargantext-upgrade:
main: Main.hs
source-dirs: bin/gargantext-upgrade
ghc-options:
- -threaded
- -rtsopts
- -with-rtsopts=-N
- -O2
- -Wmissing-signatures
dependencies:
- gargantext
- gargantext-prelude
- base
# gargantext-upgrade:
# main: Main.hs
# source-dirs: bin/gargantext-upgrade
# ghc-options:
# - -threaded
# - -rtsopts
# - -with-rtsopts=-N
# - -O2
# - -Wmissing-signatures
# dependencies:
# - gargantext
# - gargantext-prelude
# - base
gargantext-admin:
main: Main.hs
......@@ -396,22 +396,23 @@ executables:
- gargantext-prelude
- base
gargantext-cbor2json:
main: Main.hs
source-dirs: bin/gargantext-cbor2json
ghc-options:
- -threaded
- -rtsopts
- -with-rtsopts=-N
- -O2
- -Wmissing-signatures
dependencies:
- gargantext
- gargantext-prelude
- base
- bytestring
- aeson
- serialise
# gargantext-cbor2json:
# main: Main.hs
# source-dirs: bin/gargantext-cbor2json
# ghc-options:
# - -threaded
# - -rtsopts
# - -with-rtsopts=-N
# - -O2
# - -Wmissing-signatures
# dependencies:
# - gargantext
# - gargantext-prelude
# - base
# - bytestring
# - aeson
# - serialise
tests:
......
......@@ -14,7 +14,6 @@ import Servant.Job.Async (HasJobEnv(..), Job)
import System.Log.FastLogger
import qualified Servant.Job.Core
import Gargantext.API.Ngrams.Types (HasRepoVar(..), HasRepoSaver(..), HasRepo(..), RepoEnv(..))
import Gargantext.API.Admin.Types
import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.Database.Prelude (HasConnectionPool(..), HasConfig(..))
......@@ -26,7 +25,6 @@ data Env = Env
{ _env_settings :: !Settings
, _env_logger :: !LoggerSet
, _env_pool :: !(Pool Connection)
, _env_repo :: !RepoEnv
, _env_nodeStory :: !NodeStoryEnv
, _env_manager :: !Manager
, _env_self_url :: !BaseUrl
......@@ -55,15 +53,6 @@ instance HasNodeStorySaver Env where
instance HasSettings Env where
settings = env_settings
-- Specific to Repo
instance HasRepoVar Env where
repoVar = repoEnv . repoVar
instance HasRepoSaver Env where
repoSaver = repoEnv . repoSaver
instance HasRepo Env where
repoEnv = env_repo
instance Servant.Job.Core.HasEnv Env (Job JobLog JobLog) where
......@@ -83,7 +72,6 @@ makeLenses ''MockEnv
data DevEnv = DevEnv
{ _dev_env_settings :: !Settings
, _dev_env_repo :: !RepoEnv
, _dev_env_config :: !GargConfig
, _dev_env_pool :: !(Pool Connection)
, _dev_env_nodeStory :: !NodeStoryEnv
......@@ -111,11 +99,4 @@ instance HasNodeStorySaver DevEnv where
hasNodeStorySaver = hasNodeStory . nse_saver
instance HasRepoVar DevEnv where
repoVar = repoEnv . repoVar
instance HasRepoSaver DevEnv where
repoSaver = repoEnv . repoSaver
instance HasRepo DevEnv where
repoEnv = dev_env_repo
......@@ -18,9 +18,8 @@ TODO-SECURITY: Critical
module Gargantext.API.Admin.Settings
where
import Codec.Serialise (Serialise(), serialise, deserialise)
import Control.Concurrent
import Control.Debounce (mkDebounce, defaultDebounceSettings, debounceFreq, debounceAction)
-- import Control.Debounce (mkDebounce, defaultDebounceSettings, debounceFreq, debounceAction)
import Codec.Serialise (Serialise(), serialise)
import Control.Lens
import Control.Monad.Logger
import Control.Monad.Reader
......@@ -34,7 +33,7 @@ import Servant.Auth.Server (defaultJWTSettings, CookieSettings(..), XsrfCookieSe
import Servant.Client (parseBaseUrl)
import Servant.Job.Async (newJobEnv, defaultSettings)
import System.Directory
import System.FileLock (tryLockFile, unlockFile, SharedExclusive(Exclusive))
-- import System.FileLock (tryLockFile, unlockFile, SharedExclusive(Exclusive))
import System.IO (FilePath, hClose)
import System.IO.Temp (withTempFile)
import System.Log.FastLogger
......@@ -43,10 +42,10 @@ import qualified Data.ByteString.Lazy as L
import Gargantext.API.Admin.EnvTypes
import Gargantext.API.Admin.Types
import Gargantext.API.Ngrams.Types (NgramsRepo, HasRepo(..), RepoEnv(..), r_version, initRepo, renv_var, renv_lock)
import Gargantext.Database.Prelude (databaseParameters, HasConfig(..))
-- import Gargantext.API.Ngrams.Types (NgramsRepo, HasRepo(..), RepoEnv(..), r_version, initRepo, renv_var, renv_lock)
import Gargantext.Database.Prelude (databaseParameters)
import Gargantext.Prelude
import Gargantext.Prelude.Config (gc_repofilepath)
-- import Gargantext.Prelude.Config (gc_repofilepath)
devSettings :: FilePath -> IO Settings
devSettings jwkFile = do
......@@ -113,7 +112,7 @@ repoSaverAction repoDir a = do
--{-
{-
-- 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
-- be increased.
......@@ -133,6 +132,8 @@ mkRepoSaver repoDir repo_var = mkDebounce settings'
-- Add a new MVar just for saving.
}
-}
{-
readRepoEnv :: FilePath -> IO RepoEnv
readRepoEnv repoDir = do
-- Does file exist ? :: Bool
......@@ -178,7 +179,6 @@ newEnv port file = do
self_url_env <- parseBaseUrl $ "http://0.0.0.0:" <> show port
dbParam <- databaseParameters file
pool <- newPool dbParam
repo <- readRepoEnv (_gc_repofilepath config_env)
nodeStory_env <- readNodeStoryEnv (_gc_repofilepath config_env)
scrapers_env <- newJobEnv defaultSettings manager_env
logger <- newStderrLoggerSet defaultBufSize
......@@ -187,7 +187,6 @@ newEnv port file = do
{ _env_settings = settings'
, _env_logger = logger
, _env_pool = pool
, _env_repo = repo
, _env_nodeStory = nodeStory_env
, _env_manager = manager_env
, _env_scrapers = scrapers_env
......@@ -198,7 +197,7 @@ newEnv port file = do
newPool :: ConnectInfo -> IO (Pool Connection)
newPool param = createPool (connect param) close 1 (60*60) 8
--{-
{-
cleanEnv :: (HasConfig env, HasRepo env) => env -> IO ()
cleanEnv env = do
r <- takeMVar (env ^. repoEnv . renv_var)
......
......@@ -31,7 +31,7 @@ type IniPath = FilePath
withDevEnv :: IniPath -> (DevEnv -> IO a) -> IO a
withDevEnv iniPath k = do
env <- newDevEnv
k env `finally` cleanEnv env
k env -- `finally` cleanEnv env
where
newDevEnv = do
......@@ -39,11 +39,9 @@ withDevEnv iniPath k = do
dbParam <- databaseParameters iniPath
nodeStory_env <- readNodeStoryEnv (_gc_repofilepath cfg)
pool <- newPool dbParam
repo <- readRepoEnv (_gc_repofilepath cfg)
setts <- devSettings devJwkFile
pure $ DevEnv
{ _dev_env_pool = pool
, _dev_env_repo = repo
, _dev_env_nodeStory = nodeStory_env
, _dev_env_settings = setts
, _dev_env_config = cfg
......
......@@ -33,7 +33,6 @@ module Gargantext.API.Ngrams
, apiNgramsTableCorpus
, apiNgramsTableDoc
, NgramsStatePatch
, NgramsTablePatch
, NgramsTableMap
......@@ -52,15 +51,10 @@ module Gargantext.API.Ngrams
, r_version
, r_state
, r_history
, NgramsRepo
, NgramsRepoElement(..)
, saveNodeStory
, initRepo
, RepoEnv(..)
, renv_var
, renv_lock
, TabType(..)
, QueryParamR
......
......@@ -35,12 +35,12 @@ mergeNgramsElement _neOld neNew = neNew
type RootTerm = NgramsTerm
{-
getRepo :: RepoCmdM env err m => m NgramsRepo
getRepo = do
v <- view repoVar
liftBase $ readMVar v
-}
getRepo' :: HasNodeStory env err m
=> [ListId] -> m NodeListStory
......
......@@ -11,8 +11,7 @@ module Gargantext.API.Ngrams.Types where
import Codec.Serialise (Serialise())
import Control.Category ((>>>))
import Control.Concurrent
import Control.Lens (makeLenses, makePrisms, Iso', iso, from, (.~), (?=), (#), to, folded, {-withIndex, ifolded,-} view, use, (^.), (^?), (%~), (.~), (%=), at, _Just, Each(..), itraverse_, both, forOf_, (?~), Getter)
import Control.Lens (makeLenses, makePrisms, Iso', iso, from, (.~), (?=), (#), to, folded, {-withIndex, ifolded,-} view, use, (^.), (^?), (%~), (.~), (%=), at, _Just, Each(..), itraverse_, both, forOf_, (?~))
import Control.Monad.State
import Data.Aeson hiding ((.=))
import Data.Aeson.TH (deriveJSON)
......@@ -39,7 +38,7 @@ import Gargantext.Prelude.Crypto.Hash (IsHashable(..))
import Protolude (maybeToEither)
import Servant hiding (Patch)
import Servant.Job.Utils (jsonOptions)
import System.FileLock (FileLock)
-- import System.FileLock (FileLock)
import Test.QuickCheck (elements, frequency)
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
import qualified Data.HashMap.Strict.InsOrd as InsOrdHashMap
......@@ -676,11 +675,6 @@ data Repo s p = Repo
}
deriving (Generic, Show)
-- | TO REMOVE
type NgramsRepo = Repo NgramsState NgramsStatePatch
type NgramsState = Map TableNgrams.NgramsType (Map NodeId NgramsTableMap)
type NgramsStatePatch = PatchMap TableNgrams.NgramsType (PatchMap NodeId NgramsTablePatch)
----------------------------------------------------------------------
instance (FromJSON s, FromJSON p) => FromJSON (Repo s p) where
......@@ -697,52 +691,16 @@ makeLenses ''Repo
initRepo :: Monoid s => Repo s p
initRepo = Repo 1 mempty []
instance Serialise (PM.PatchMap NodeId NgramsTablePatch)
instance Serialise NgramsStatePatch
initMockRepo :: NgramsRepo
initMockRepo = Repo 1 s []
where
s = Map.singleton TableNgrams.NgramsTerms
$ Map.singleton 47254
$ Map.fromList
[ (n ^. ne_ngrams, ngramsElementToRepo n) | n <- mockTable ^. _NgramsTable ]
--------------------
data RepoEnv = RepoEnv
{ _renv_var :: !(MVar NgramsRepo)
, _renv_saver :: !(IO ())
, _renv_lock :: !FileLock
}
deriving (Generic)
makeLenses ''RepoEnv
type RepoCmdM env err m =
( CmdM' env err m
, HasRepo env
, HasConnectionPool env
, HasConfig env
)
class (HasRepoVar env, HasRepoSaver env)
=> HasRepo env where
repoEnv :: Getter env RepoEnv
class HasRepoVar env where
repoVar :: Getter env (MVar NgramsRepo)
class HasRepoSaver env where
repoSaver :: Getter env (IO ())
instance HasRepo RepoEnv where
repoEnv = identity
instance HasRepoVar (MVar NgramsRepo) where
repoVar = identity
instance HasRepoVar RepoEnv where
repoVar = renv_var
instance HasRepoSaver RepoEnv where
repoSaver = renv_saver
------------------------------------------------------------------------
......
......@@ -32,7 +32,6 @@ import Control.Monad.Except
import Control.Monad.Reader
import Data.Aeson hiding ((.=), decode)
import Data.Map.Strict (Map)
import Data.Maybe (fromMaybe)
import Data.Monoid
import Data.Semigroup
import GHC.Generics (Generic)
......@@ -48,7 +47,6 @@ import System.IO.Temp (withTempFile)
import qualified Data.ByteString.Lazy as DBL
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
------------------------------------------------------------------------
......@@ -207,6 +205,7 @@ nodeStoryPath repoDir nId = repoDir <> "/" <> filename
------------------------------------------------------------------------
-- TODO : repo Migration TODO TESTS
{-
repoMigration :: NodeStoryDir -> NgramsRepo -> IO ()
repoMigration fp r = writeNodeStories fp (repoToNodeListStory r)
......@@ -249,7 +248,7 @@ ngramsStatePatch_migration np' = Map.fromListWith (<>)
-> (nid, [fst $ Patch.singleton nt table])
) $ Patch.toList nTable
) $ Patch.toList p
-}
------------------------------------------------------------------------
{- | Node Story for each NodeType where the Key of the Map is NodeId
......
......@@ -17,10 +17,9 @@ Portability : POSIX
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Database.Query.Table.NodesNgramsRepo
( module Gargantext.Database.Schema.NodesNgramsRepo
)
where
{-
import Gargantext.Database.Schema.Prelude
import Gargantext.API.Ngrams (NgramsStatePatch)
import Gargantext.Database.Schema.NodesNgramsRepo
......@@ -42,4 +41,4 @@ _insertRepos ns = mkCmd $ \conn -> runInsert_ conn $ Insert repoTable (toWrite n
toWrite :: [NgramsStatePatch] -> [RepoDbWrite]
toWrite = undefined
--ns' = map (\(RepoDbNgrams v ps) -> RepoDbWrite (sqlInt4 v) (pgJSONB ps)) ns
-}
......@@ -21,10 +21,11 @@ Portability : POSIX
module Gargantext.Database.Schema.NodesNgramsRepo
where
{-
import Data.Map.Strict.Patch (PatchMap)
import Gargantext.Database.Schema.Prelude
import Gargantext.API.Ngrams.Types (NgramsStatePatch, NgramsTablePatch)
import Gargantext.API.Ngrams.Types (NgramsTablePatch)
import Gargantext.Database.Schema.Ngrams (NgramsType)
import Gargantext.Database.Admin.Types.Node (NodeId)
import Gargantext.Prelude
......@@ -59,4 +60,4 @@ repoTable = Table "nodes_ngrams_repo"
, _rdp_patches = requiredTableField "patches"
}
)
-}
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