{-# LANGUAGE ScopedTypeVariables #-}
module Network.QUIC.Exception (
handleLogT,
handleLogUnit,
) where
import qualified Control.Exception as E
import qualified GHC.IO.Exception as E
import qualified System.IO.Error as E
import Network.QUIC.Imports
import Network.QUIC.Logger
handleLogUnit :: DebugLogger -> IO () -> IO ()
handleLogUnit :: DebugLogger -> IO () -> IO ()
handleLogUnit DebugLogger
logAction IO ()
action = IO ()
action IO () -> (SomeException -> IO ()) -> IO ()
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`E.catch` SomeException -> IO ()
handler
where
handler :: E.SomeException -> IO ()
handler :: SomeException -> IO ()
handler SomeException
se | SomeException -> Bool
forall e. Exception e => e -> Bool
isAsyncException SomeException
se = SomeException -> IO ()
forall e a. Exception e => e -> IO a
E.throwIO SomeException
se
handler SomeException
se = case SomeException -> Maybe IOError
forall e. Exception e => SomeException -> Maybe e
E.fromException SomeException
se of
Just IOError
e | IOError -> IOErrorType
E.ioeGetErrorType IOError
e IOErrorType -> IOErrorType -> Bool
forall a. Eq a => a -> a -> Bool
== IOErrorType
E.InvalidArgument -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Just IOError
e | IOError -> IOErrorType
E.ioeGetErrorType IOError
e IOErrorType -> IOErrorType -> Bool
forall a. Eq a => a -> a -> Bool
== IOErrorType
E.NoSuchThing -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Maybe IOError
_ -> DebugLogger
logAction DebugLogger -> DebugLogger
forall a b. (a -> b) -> a -> b
$ SomeException -> Builder
forall a. Show a => a -> Builder
bhow SomeException
se
handleLogT :: DebugLogger -> IO a -> IO a
handleLogT :: forall a. DebugLogger -> IO a -> IO a
handleLogT DebugLogger
logAction IO a
action = IO a
action IO a -> (SomeException -> IO a) -> IO a
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`E.catch` SomeException -> IO a
forall {b}. SomeException -> IO b
handler
where
handler :: SomeException -> IO b
handler (E.SomeException e
e) = do
DebugLogger
logAction DebugLogger -> DebugLogger
forall a b. (a -> b) -> a -> b
$ e -> Builder
forall a. Show a => a -> Builder
bhow e
e
e -> IO b
forall e a. Exception e => e -> IO a
E.throwIO e
e