diff --git a/CHANGELOG.md b/CHANGELOG.md index 0980babc..a434c575 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -16,7 +16,7 @@ changes. ### Fixed -- +- Fix sentry reports on multiple reloads of Governance Actions [Issue 2446](https://github.com/IntersectMBO/govtool/issues/2446) ### Changed diff --git a/govtool/backend/app/Main.hs b/govtool/backend/app/Main.hs index e0dd5d3b..a17b535e 100644 --- a/govtool/backend/app/Main.hs +++ b/govtool/backend/app/Main.hs @@ -8,7 +8,7 @@ module Main where -import Control.Exception (Exception, SomeException, fromException, throw) +import Control.Exception (IOException, Exception, SomeException, fromException, throw) import Control.Lens.Operators ((.~)) import Control.Monad import Control.Monad.IO.Class @@ -21,6 +21,7 @@ import Data.ByteString.Char8 (unpack) import qualified Data.Cache as Cache import Data.Function ((&)) import Data.Has (getter) +import Data.List (isInfixOf) import Data.Monoid (mempty) import Data.OpenApi (OpenApi, Server (Server), _openApiServers, _serverDescription, _serverUrl, _serverVariables, @@ -88,7 +89,8 @@ startApp vvaConfig sentryService = do settings = setPort vvaPort $ setHost vvaHost - $ setTimeout 120 -- 120 seconds timeout + $ setTimeout 300-- 300 seconds timeout + $ setGracefulShutdownTimeout (Just 60) -- Allow 60 seconds for cleanup $ setBeforeMainLoop ( Text.hPutStrLn stderr $ Text.pack @@ -130,25 +132,39 @@ startApp vvaConfig sentryService = do exceptionHandler :: VVAConfig -> SentryService -> Maybe Request -> SomeException -> IO () exceptionHandler vvaConfig sentryService mRequest exception = do - print mRequest print exception + -- These are not considered application errors + -- They represent the client closing the connection prematurely + -- or the timeout thread being killed by WARP let isNotTimeoutThread x = case fromException x of Just TimeoutThread -> False _ -> True isNotConnectionClosedByPeer x = case fromException x of Just ConnectionClosedByPeer -> False _ -> True - guard . isNotTimeoutThread $ exception - guard . isNotConnectionClosedByPeer $ exception - let env = sentryEnv vvaConfig - register - sentryService - "vva.be" - Error - (formatMessage mRequest exception) - (recordUpdate env mRequest exception) + isNotClientClosedConnection x = + case fromException x of + Just ioe -> not ("Warp: Client closed connection prematurely" `isInfixOf` show (ioe :: IOException)) + Nothing -> True + isNotThreadKilledByTimeoutManager x = + "Thread killed by timeout manager" `notElem` show x + shouldSkipError = + isNotTimeoutThread exception && + isNotConnectionClosedByPeer exception && + isNotClientClosedConnection exception && + isNotThreadKilledByTimeoutManager exception + guard shouldSkipError + let env = sentryEnv vvaConfig + case mRequest of + Nothing -> return () + Just _ -> register + sentryService + "vva.be" + Error + (formatMessage mRequest exception) + (recordUpdate env mRequest exception) formatMessage :: Maybe Request -> SomeException -> String formatMessage Nothing exception = "Exception before request could be parsed: " ++ show exception diff --git a/govtool/backend/sql/list-proposals.sql b/govtool/backend/sql/list-proposals.sql index 2ee18431..d3bd992c 100644 --- a/govtool/backend/sql/list-proposals.sql +++ b/govtool/backend/sql/list-proposals.sql @@ -105,7 +105,7 @@ SELECT encode(creator_tx.hash, 'hex'), gov_action_proposal.index, gov_action_proposal.type::text, - ( + COALESCE( case when gov_action_proposal.type = 'TreasuryWithdrawals' then ( select json_agg( @@ -159,7 +159,7 @@ SELECT else null end - ) as description, + , '{}'::json) as description, CASE WHEN meta.network_name::text = 'mainnet' OR meta.network_name::text = 'preprod' THEN latest_epoch.start_time + (gov_action_proposal.expiration - latest_epoch.no)::bigint * INTERVAL '5 days' diff --git a/govtool/backend/src/VVA/API.hs b/govtool/backend/src/VVA/API.hs index 2eec41e0..4d7b6d72 100644 --- a/govtool/backend/src/VVA/API.hs +++ b/govtool/backend/src/VVA/API.hs @@ -13,7 +13,7 @@ import Control.Exception (throw, throwIO) import Control.Monad.Except (runExceptT, throwError) import Control.Monad.Reader -import Data.Aeson (Value(..), Array, decode, encode, FromJSON, ToJSON, toJSON) +import Data.Aeson (Value(..), Array, decode, encode, ToJSON, toJSON) import Data.Bool (Bool) import Data.List (sortOn) import qualified Data.Map as Map diff --git a/govtool/backend/src/VVA/Proposal.hs b/govtool/backend/src/VVA/Proposal.hs index 328b091e..c757d381 100644 --- a/govtool/backend/src/VVA/Proposal.hs +++ b/govtool/backend/src/VVA/Proposal.hs @@ -1,13 +1,14 @@ -{-# LANGUAGE FlexibleContexts #-} -{-# LANGUAGE LambdaCase #-} -{-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE RecordWildCards #-} -{-# LANGUAGE TemplateHaskell #-} -{-# LANGUAGE TypeApplications #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE TypeApplications #-} +{-# LANGUAGE ScopedTypeVariables #-} module VVA.Proposal where -import Control.Exception (throw) +import Control.Exception (throw, SomeException, try) import Control.Monad.Except (MonadError, throwError) import Control.Monad.Reader @@ -69,12 +70,18 @@ getProposals :: (Has ConnectionPool r, Has VVAConfig r, MonadReader r m, MonadIO m, MonadFail m, MonadError AppError m) => Maybe [Text] -> m [Proposal] getProposals mSearchTerms = withPool $ \conn -> do - let searchParam = maybe "" head mSearchTerms - liftIO $ SQL.query conn listProposalsSql - ( searchParam - , "%" <> searchParam <> "%" - , "%" <> searchParam <> "%" - , "%" <> searchParam <> "%" - , "%" <> searchParam <> "%" - , "%" <> searchParam <> "%" - ) + let searchParam = fromMaybe "" (head <$> mSearchTerms) + liftIO $ do + result <- try $ SQL.query conn listProposalsSql + ( searchParam + , "%" <> searchParam <> "%" + , "%" <> searchParam <> "%" + , "%" <> searchParam <> "%" + , "%" <> searchParam <> "%" + , "%" <> searchParam <> "%" + ) + case result of + Left (e :: SomeException) -> do + return [] + Right rows -> do + return rows