Skip to content

Commit

Permalink
agent: treat blocked STM and other critical errors that offer restart…
Browse files Browse the repository at this point in the history
… as temporary (#1405)
  • Loading branch information
epoberezkin authored Nov 21, 2024
1 parent a64c1aa commit bbcb1ab
Show file tree
Hide file tree
Showing 2 changed files with 5 additions and 2 deletions.
1 change: 1 addition & 0 deletions src/Simplex/Messaging/Agent/Client.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1388,6 +1388,7 @@ temporaryAgentError = \case
PROXY _ _ (ProxyProtocolError (SMP.PROXY (SMP.BROKER e))) -> tempBrokerError e
PROXY _ _ (ProxyProtocolError (SMP.PROXY SMP.NO_SESSION)) -> True
INACTIVE -> True
CRITICAL True _ -> True -- critical errors that do not show restart button are likely to be permanent
_ -> False
where
tempBrokerError = \case
Expand Down
6 changes: 4 additions & 2 deletions src/Simplex/Messaging/Agent/Env/SQLite.hs
Original file line number Diff line number Diff line change
Expand Up @@ -42,6 +42,7 @@ module Simplex.Messaging.Agent.Env.SQLite
where

import Control.Concurrent (ThreadId)
import Control.Exception (BlockedIndefinitelyOnSTM (..), SomeException, fromException)
import Control.Monad.Except
import Control.Monad.IO.Unlift
import Control.Monad.Reader
Expand Down Expand Up @@ -78,7 +79,6 @@ import Simplex.Messaging.Transport (SMPVersion)
import Simplex.Messaging.Util (allFinally, catchAllErrors, catchAllErrors', tryAllErrors, tryAllErrors')
import System.Mem.Weak (Weak)
import System.Random (StdGen, newStdGen)
import UnliftIO (SomeException)
import UnliftIO.STM

type AM' a = ReaderT Env IO a
Expand Down Expand Up @@ -313,7 +313,9 @@ agentFinally = allFinally mkInternal
{-# INLINE agentFinally #-}

mkInternal :: SomeException -> AgentErrorType
mkInternal = INTERNAL . show
mkInternal e = case fromException e of
Just BlockedIndefinitelyOnSTM -> CRITICAL True "Thread blocked indefinitely in STM transaction"
_ -> INTERNAL $ show e
{-# INLINE mkInternal #-}

data Worker = Worker
Expand Down

0 comments on commit bbcb1ab

Please sign in to comment.