Commit 2467fb40 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[OPTIM][FIX] serialise/deserialise without encode/decode json

parent 84e3f3f0
Pipeline #861 canceled with stage
...@@ -26,14 +26,13 @@ TODO-SECURITY: Critical ...@@ -26,14 +26,13 @@ TODO-SECURITY: Critical
module Gargantext.API.Admin.Settings module Gargantext.API.Admin.Settings
where where
import Codec.Serialise (Serialise(), serialise) import Codec.Serialise (Serialise(), serialise, deserialise)
import Control.Concurrent import Control.Concurrent
import Control.Debounce (mkDebounce, defaultDebounceSettings, debounceFreq, debounceAction) import Control.Debounce (mkDebounce, defaultDebounceSettings, debounceFreq, debounceAction)
import Control.Exception (finally) 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.Aeson hiding (encode)
import Data.ByteString (ByteString) import Data.ByteString (ByteString)
import Data.Either (either) import Data.Either (either)
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
...@@ -191,7 +190,7 @@ repoSnapshot = repoDir <> "/repo.json" ...@@ -191,7 +190,7 @@ repoSnapshot = repoDir <> "/repo.json"
repoSaverAction :: Serialise a => a -> IO () repoSaverAction :: Serialise a => a -> IO ()
repoSaverAction a = do repoSaverAction a = do
withTempFile "repos" "tmp-repo.json" $ \fp h -> do withTempFile "repos" "tmp-repo.json" $ \fp h -> do
-- printDebug "repoSaverAction" fp printDebug "repoSaverAction" fp
L.hPut h $ serialise a L.hPut h $ serialise a
hClose h hClose h
renameFile fp repoSnapshot renameFile fp repoSnapshot
...@@ -230,8 +229,9 @@ readRepoEnv = do ...@@ -230,8 +229,9 @@ readRepoEnv = do
mvar <- newMVar =<< mvar <- newMVar =<<
if repoExists if repoExists
then do then do
e_repo <- eitherDecodeFileStrict repoSnapshot -- e_repo <- eitherDecodeStrict <$> deserialise <$> L.readFile repoSnapshot
repo <- either fail pure e_repo repo <- deserialise <$> L.readFile repoSnapshot
-- repo <- either fail pure e_repo
let archive = repoSnapshot <> ".v" <> show (repo ^. r_version) let archive = repoSnapshot <> ".v" <> show (repo ^. r_version)
copyFile repoSnapshot archive copyFile repoSnapshot archive
pure repo pure repo
......
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