Commit 89d97fd0 authored by Alfredo Di Napoli's avatar Alfredo Di Napoli

refactoring(logging): rename withLoggerHoisted to withLoggerIO

This will allow us to find all the use site of this function, trying to
see if we can use only `withLogger` or correctly control the logging
verbosity via the `HasLogger` and `LogInitParams`.
parent 8ddb544b
...@@ -55,7 +55,7 @@ import Gargantext.Core.Notifications (withNotifications) ...@@ -55,7 +55,7 @@ import Gargantext.Core.Notifications (withNotifications)
import Gargantext.Database.Prelude qualified as DB import Gargantext.Database.Prelude qualified as DB
import Gargantext.MicroServices.ReverseProxy (microServicesProxyApp) import Gargantext.MicroServices.ReverseProxy (microServicesProxyApp)
import Gargantext.Prelude hiding (putStrLn, to) import Gargantext.Prelude hiding (putStrLn, to)
import Gargantext.System.Logging (withLoggerHoisted) import Gargantext.System.Logging (withLoggerIO)
import Network.HTTP.Types hiding (Query) import Network.HTTP.Types hiding (Query)
import Network.Wai (Middleware, Request, requestHeaders) import Network.Wai (Middleware, Request, requestHeaders)
import Network.Wai.Handler.Warp hiding (defaultSettings) import Network.Wai.Handler.Warp hiding (defaultSettings)
...@@ -70,7 +70,7 @@ import System.Cron.Schedule qualified as Cron ...@@ -70,7 +70,7 @@ import System.Cron.Schedule qualified as Cron
-- | startGargantext takes as parameters port number and Toml file. -- | startGargantext takes as parameters port number and Toml file.
startGargantext :: Mode -> PortNumber -> SettingsFile -> IO () startGargantext :: Mode -> PortNumber -> SettingsFile -> IO ()
startGargantext mode port sf@(SettingsFile settingsFile) = withLoggerHoisted mode $ \logger -> do startGargantext mode port sf@(SettingsFile settingsFile) = withLoggerIO mode $ \logger -> do
config <- readConfig sf <&> (gc_frontend_config . fc_appPort) .~ port config <- readConfig sf <&> (gc_frontend_config . fc_appPort) .~ port
when (port /= config ^. gc_frontend_config . fc_appPort) $ when (port /= config ^. gc_frontend_config . fc_appPort) $
panicTrace "TODO: conflicting settings of port" panicTrace "TODO: conflicting settings of port"
......
...@@ -26,13 +26,13 @@ import Gargantext.Core.Config.Utils (readConfig) ...@@ -26,13 +26,13 @@ import Gargantext.Core.Config.Utils (readConfig)
import Gargantext.Core.NodeStory (fromDBNodeStoryEnv) import Gargantext.Core.NodeStory (fromDBNodeStoryEnv)
import Gargantext.Database.Prelude (Cmd, CmdRandom, connPool, runCmd) import Gargantext.Database.Prelude (Cmd, CmdRandom, connPool, runCmd)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.System.Logging ( withLoggerHoisted ) import Gargantext.System.Logging ( withLoggerIO )
import Network.HTTP.Client.TLS (newTlsManager) import Network.HTTP.Client.TLS (newTlsManager)
import Servant ( ServerError ) import Servant ( ServerError )
------------------------------------------------------------------- -------------------------------------------------------------------
withDevEnv :: SettingsFile -> (DevEnv -> IO a) -> IO a withDevEnv :: SettingsFile -> (DevEnv -> IO a) -> IO a
withDevEnv settingsFile k = withLoggerHoisted Dev $ \logger -> do withDevEnv settingsFile k = withLoggerIO Dev $ \logger -> do
env <- newDevEnv logger env <- newDevEnv logger
k env -- `finally` cleanEnv env k env -- `finally` cleanEnv env
......
...@@ -43,7 +43,7 @@ import Gargantext.Database.Prelude (HasConnectionPool(..)) ...@@ -43,7 +43,7 @@ import Gargantext.Database.Prelude (HasConnectionPool(..))
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.Prelude hiding (to) import Gargantext.Prelude hiding (to)
import Gargantext.System.Logging (HasLogger(..), Logger, LogLevel(..), MonadLogger(..), withLogger, logMsg, withLoggerHoisted) import Gargantext.System.Logging (HasLogger(..), Logger, LogLevel(..), MonadLogger(..), withLogger, logMsg, withLoggerIO)
import Gargantext.Utils.Jobs.Monad ( MonadJobStatus(..), JobHandle ) import Gargantext.Utils.Jobs.Monad ( MonadJobStatus(..), JobHandle )
import GHC.IO.Exception (IOException(..), IOErrorType(OtherError)) import GHC.IO.Exception (IOException(..), IOErrorType(OtherError))
import Prelude qualified import Prelude qualified
...@@ -68,7 +68,7 @@ data WorkerJobState = WorkerJobState ...@@ -68,7 +68,7 @@ data WorkerJobState = WorkerJobState
withWorkerEnv :: SettingsFile -> (WorkerEnv -> IO a) -> IO a withWorkerEnv :: SettingsFile -> (WorkerEnv -> IO a) -> IO a
withWorkerEnv settingsFile k = withLoggerHoisted Dev $ \logger -> do withWorkerEnv settingsFile k = withLoggerIO Dev $ \logger -> do
env <- newWorkerEnv logger env <- newWorkerEnv logger
k env -- `finally` cleanEnv env k env -- `finally` cleanEnv env
......
...@@ -10,7 +10,7 @@ module Gargantext.System.Logging ( ...@@ -10,7 +10,7 @@ module Gargantext.System.Logging (
, logLocM , logLocM
, logLoc , logLoc
, withLogger , withLogger
, withLoggerHoisted , withLoggerIO
) where ) where
import Control.Exception.Safe (MonadMask, bracket) import Control.Exception.Safe (MonadMask, bracket)
...@@ -119,11 +119,11 @@ withLogger params = bracket (initLogger params) destroyLogger ...@@ -119,11 +119,11 @@ withLogger params = bracket (initLogger params) destroyLogger
-- | Like 'withLogger', but it allows creating a 'Logger' that can run in -- | Like 'withLogger', but it allows creating a 'Logger' that can run in
-- a different monad from within an 'IO' action. -- a different monad from within an 'IO' action.
withLoggerHoisted :: (MonadBaseControl IO m, HasLogger m) withLoggerIO :: (MonadBaseControl IO m, HasLogger m)
=> LogInitParams m => LogInitParams m
-> (Logger m -> IO a) -> (Logger m -> IO a)
-> IO a -> IO a
withLoggerHoisted params act = bracket (initLogger params) destroyLogger act withLoggerIO params act = bracket (initLogger params) destroyLogger act
-- | A plain logger in the IO monad, waiting for more serious logging solutions like -- | A plain logger in the IO monad, waiting for more serious logging solutions like
-- the one described in https://gitlab.iscpif.fr/gargantext/haskell-gargantext/issues/229 -- the one described in https://gitlab.iscpif.fr/gargantext/haskell-gargantext/issues/229
......
...@@ -32,10 +32,10 @@ withTwoServerInstances :: (SpecContext (TestEnv,Wai.Application,Warp.Port) -> IO ...@@ -32,10 +32,10 @@ withTwoServerInstances :: (SpecContext (TestEnv,Wai.Application,Warp.Port) -> IO
withTwoServerInstances action = withTwoServerInstances action =
withTestDB $ \testEnv1 -> do withTestDB $ \testEnv1 -> do
withTestDB $ \testEnv2 -> do withTestDB $ \testEnv2 -> do
garg1App <- withLoggerHoisted Mock $ \ioLogger -> do garg1App <- withLoggerIO Mock $ \ioLogger -> do
env <- newTestEnv testEnv1 ioLogger server1Port env <- newTestEnv testEnv1 ioLogger server1Port
makeApp env makeApp env
garg2App <- withLoggerHoisted Mock $ \ioLogger -> do garg2App <- withLoggerIO Mock $ \ioLogger -> do
env <- newTestEnv testEnv2 ioLogger server2Port env <- newTestEnv testEnv2 ioLogger server2Port
makeApp env makeApp env
......
...@@ -109,8 +109,8 @@ nc = NotificationsConfig { _nc_central_exchange_bind = "tcp://*:15560" ...@@ -109,8 +109,8 @@ nc = NotificationsConfig { _nc_central_exchange_bind = "tcp://*:15560"
-- for concurrent tests to be executed in parallel, if we need to. -- for concurrent tests to be executed in parallel, if we need to.
withTestDBAndPort :: (SpecContext () -> IO ()) -> IO () withTestDBAndPort :: (SpecContext () -> IO ()) -> IO ()
withTestDBAndPort action = withNotifications nc $ \dispatcher -> do withTestDBAndPort action = withNotifications nc $ \dispatcher -> do
withTestDB $ \testEnv -> do withTestDB $ \testEnv -> do
withLoggerHoisted Mock $ \ioLogger -> do withLoggerIO Mock $ \ioLogger -> do
env <- newTestEnv testEnv ioLogger 8080 env <- newTestEnv testEnv ioLogger 8080
<&> env_dispatcher .~ dispatcher <&> env_dispatcher .~ dispatcher
app <- makeApp env app <- makeApp env
...@@ -133,21 +133,21 @@ withTestDBAndPort action = withNotifications nc $ \dispatcher -> do ...@@ -133,21 +133,21 @@ withTestDBAndPort action = withNotifications nc $ \dispatcher -> do
withLogger () $ \ioLogger' -> withLogger () $ \ioLogger' ->
logTxt ioLogger' ERROR $ "[withTestDBAndPort] unknown exception: " <> show err logTxt ioLogger' ERROR $ "[withTestDBAndPort] unknown exception: " <> show err
throw err throw err
-- re-throw any other exceptions -- re-throw any other exceptions
, Handler $ \(err :: SomeException) -> throw err ] , Handler $ \(err :: SomeException) -> throw err ]
-- | Starts the backend server /and/ the microservices proxy, the former at -- | Starts the backend server /and/ the microservices proxy, the former at
-- a random port, the latter at a predictable port. -- a random port, the latter at a predictable port.
withBackendServerAndProxy :: (((TestEnv, Warp.Port, Warp.Port)) -> IO ()) -> IO () withBackendServerAndProxy :: (((TestEnv, Warp.Port, Warp.Port)) -> IO ()) -> IO ()
withBackendServerAndProxy action = withBackendServerAndProxy action =
withTestDB $ \testEnv -> do withTestDB $ \testEnv -> do
gargApp <- withLoggerHoisted Mock $ \ioLogger -> do gargApp <- withLoggerIO Mock $ \ioLogger -> do
env <- newTestEnv testEnv ioLogger 8080 env <- newTestEnv testEnv ioLogger 8080
makeApp env makeApp env
proxyCache <- InMemory.newCache Nothing proxyCache <- InMemory.newCache Nothing
proxyApp <- withLoggerHoisted Mock $ \ioLogger -> do proxyApp <- withLoggerIO Mock $ \ioLogger -> do
env <- newTestEnv testEnv ioLogger 8080 env <- newTestEnv testEnv ioLogger 8080
pure $ microServicesProxyApp proxyCache env pure $ microServicesProxyApp proxyCache env
...@@ -186,7 +186,7 @@ dbEnvSetup ctx = do ...@@ -186,7 +186,7 @@ dbEnvSetup ctx = do
_ <- createAliceAndBob testEnv _ <- createAliceAndBob testEnv
pure ctx pure ctx
-- show the full exceptions during testing, rather than shallowing them under a generic -- show the full exceptions during testing, rather than shallowing them under a generic
-- "Something went wrong". -- "Something went wrong".
showDebugExceptions :: SomeException -> Wai.Response showDebugExceptions :: SomeException -> Wai.Response
......
...@@ -28,7 +28,7 @@ import Gargantext.Core.NodeStory (fromDBNodeStoryEnv) ...@@ -28,7 +28,7 @@ import Gargantext.Core.NodeStory (fromDBNodeStoryEnv)
import Gargantext.Core.Worker (initWorkerState) import Gargantext.Core.Worker (initWorkerState)
import Gargantext.Core.Worker.Env (WorkerEnv(..)) import Gargantext.Core.Worker.Env (WorkerEnv(..))
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.System.Logging (withLoggerHoisted) import Gargantext.System.Logging (withLoggerIO)
import Paths_gargantext import Paths_gargantext
import Prelude qualified import Prelude qualified
import Shelly hiding (FilePath, run) import Shelly hiding (FilePath, run)
...@@ -98,7 +98,7 @@ setup = do ...@@ -98,7 +98,7 @@ setup = do
bootstrapDB db pool gargConfig bootstrapDB db pool gargConfig
ugen <- emptyCounter ugen <- emptyCounter
test_nodeStory <- fromDBNodeStoryEnv pool test_nodeStory <- fromDBNodeStoryEnv pool
withLoggerHoisted Mock $ \logger -> do withLoggerIO Mock $ \logger -> do
let wPoolConfig = defaultPoolConfig (PG.connectPostgreSQL (Tmp.toConnectionString db)) let wPoolConfig = defaultPoolConfig (PG.connectPostgreSQL (Tmp.toConnectionString db))
PG.close PG.close
...@@ -107,7 +107,7 @@ setup = do ...@@ -107,7 +107,7 @@ setup = do
wPool <- newPool (setNumStripes (Just 2) wPoolConfig) wPool <- newPool (setNumStripes (Just 2) wPoolConfig)
wNodeStory <- fromDBNodeStoryEnv wPool wNodeStory <- fromDBNodeStoryEnv wPool
_w_env_job_state <- newTVarIO Nothing _w_env_job_state <- newTVarIO Nothing
withLoggerHoisted Mock $ \wioLogger -> do withLoggerIO Mock $ \wioLogger -> do
let wEnv = WorkerEnv { _w_env_config = gargConfig let wEnv = WorkerEnv { _w_env_config = gargConfig
, _w_env_logger = wioLogger , _w_env_logger = wioLogger
, _w_env_pool = wPool , _w_env_pool = wPool
......
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