module Ki.Internal.Propagating
( Tid,
peelOffPropagating,
propagate,
)
where
import Control.Concurrent (ThreadId)
import Control.Exception (Exception (..), SomeException, asyncExceptionFromException, asyncExceptionToException, throwTo)
data Propagating = Propagating
{ Propagating -> Tid
childId :: {-# UNPACK #-} !Tid,
Propagating -> SomeException
exception :: !SomeException
}
instance Exception Propagating where
toException :: Propagating -> SomeException
toException = Propagating -> SomeException
forall e. Exception e => e -> SomeException
asyncExceptionToException
fromException :: SomeException -> Maybe Propagating
fromException = SomeException -> Maybe Propagating
forall e. Exception e => SomeException -> Maybe e
asyncExceptionFromException
instance Show Propagating where
show :: Propagating -> String
show Propagating
_ = String
"<<internal ki exception: propagating>>"
pattern PropagatingThe :: SomeException -> SomeException
pattern $mPropagatingThe :: forall {r}.
SomeException -> (SomeException -> r) -> ((# #) -> r) -> r
PropagatingThe exception <- (fromException -> Just Propagating {exception})
type Tid =
Int
peelOffPropagating :: SomeException -> SomeException
peelOffPropagating :: SomeException -> SomeException
peelOffPropagating = \case
PropagatingThe SomeException
exception -> SomeException
exception
SomeException
exception -> SomeException
exception
propagate :: SomeException -> Tid -> ThreadId -> IO ()
propagate :: SomeException -> Tid -> ThreadId -> IO ()
propagate SomeException
exception Tid
childId ThreadId
parentThreadId =
ThreadId -> Propagating -> IO ()
forall e. Exception e => ThreadId -> e -> IO ()
throwTo ThreadId
parentThreadId Propagating {Tid
$sel:childId:Propagating :: Tid
childId :: Tid
childId, SomeException
$sel:exception:Propagating :: SomeException
exception :: SomeException
exception}