diff --git a/package.yaml b/package.yaml
index dba2f292c73954e035145e2e2a8659107e0a6ab4..bd171c6511393fb607968d702fc4f498e0341bb7 100644
--- a/package.yaml
+++ b/package.yaml
@@ -365,19 +365,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
@@ -393,22 +393,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:
diff --git a/src/Gargantext/API/Admin/EnvTypes.hs b/src/Gargantext/API/Admin/EnvTypes.hs
index 83669b324d7059ba346e407dd388cb9f731b3eb4..1b1d497ed72b40e7ea150a51b9e336dffacdf634 100644
--- a/src/Gargantext/API/Admin/EnvTypes.hs
+++ b/src/Gargantext/API/Admin/EnvTypes.hs
@@ -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
-
 
diff --git a/src/Gargantext/API/Admin/Settings.hs b/src/Gargantext/API/Admin/Settings.hs
index a1bad42fcefa700025b12d6fda65ed908fc71a61..56c8aa65f15e41f9156c4e4feae55bc4b1035976 100644
--- a/src/Gargantext/API/Admin/Settings.hs
+++ b/src/Gargantext/API/Admin/Settings.hs
@@ -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)
diff --git a/src/Gargantext/API/Dev.hs b/src/Gargantext/API/Dev.hs
index 53de546423f4c699c525512ac09d5183550623d5..6adc80c50e6eda882db8fa3c96fb603b6d4aa640 100644
--- a/src/Gargantext/API/Dev.hs
+++ b/src/Gargantext/API/Dev.hs
@@ -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
diff --git a/src/Gargantext/API/Ngrams.hs b/src/Gargantext/API/Ngrams.hs
index 271787db0819f99ffb359c9daaf91e0ad98a863e..9433ec4433e577a2aa8b4a0d7accd51ffc10f8e2 100644
--- a/src/Gargantext/API/Ngrams.hs
+++ b/src/Gargantext/API/Ngrams.hs
@@ -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
diff --git a/src/Gargantext/API/Ngrams/Tools.hs b/src/Gargantext/API/Ngrams/Tools.hs
index ed37f48084000681f191d1aae63a582daf1952c5..103b0f0b329f466171bf5737617345a2f47993b8 100644
--- a/src/Gargantext/API/Ngrams/Tools.hs
+++ b/src/Gargantext/API/Ngrams/Tools.hs
@@ -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
diff --git a/src/Gargantext/API/Ngrams/Types.hs b/src/Gargantext/API/Ngrams/Types.hs
index d4362ec12f09a24536f7ed3243e50f0ac77c390e..8c7c3d742f318ea62f8e19c5f26325f4150cb61c 100644
--- a/src/Gargantext/API/Ngrams/Types.hs
+++ b/src/Gargantext/API/Ngrams/Types.hs
@@ -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
 
 ------------------------------------------------------------------------
 
diff --git a/src/Gargantext/Core/NodeStory.hs b/src/Gargantext/Core/NodeStory.hs
index d4294075810fc382048dc7045736b1a7161b4d6f..6505909f56d3ebba9fe20befebc71a93478f6fc7 100644
--- a/src/Gargantext/Core/NodeStory.hs
+++ b/src/Gargantext/Core/NodeStory.hs
@@ -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
diff --git a/src/Gargantext/Database/Query/Table/NodesNgramsRepo.hs b/src/Gargantext/Database/Query/Table/NodesNgramsRepo.hs
index 067c8470049d52f523a60124fdd2cb36bee396d0..4d8193197f21d74d3ced458950eec146f811ba99 100644
--- a/src/Gargantext/Database/Query/Table/NodesNgramsRepo.hs
+++ b/src/Gargantext/Database/Query/Table/NodesNgramsRepo.hs
@@ -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
-
+-}
diff --git a/src/Gargantext/Database/Schema/NodesNgramsRepo.hs b/src/Gargantext/Database/Schema/NodesNgramsRepo.hs
index aa92612162c9f9af3796b13282ddb04839c02972..f2803f639ab37faf64a285ee5ad7b4a4008a96d6 100644
--- a/src/Gargantext/Database/Schema/NodesNgramsRepo.hs
+++ b/src/Gargantext/Database/Schema/NodesNgramsRepo.hs
@@ -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"
                    }
     )
-
+-}