unliftio-messagebox-2.0.0: Fast and robust message queues for concurrent processes
Safe HaskellNone
LanguageHaskell2010

UnliftIO.MessageBox.CatchAll

Description

Utilities for exception safe message boxes.

This provides a wrapper around UnliftIO.MessageBox.Class instances to catch SomeException in all methods like deliver and receive.

Synopsis

Documentation

newtype CatchAllArg cfg Source #

A wrapper around values that are instances of IsMessageBoxArg. The factory wraps the result of the delegated newMessageBox invocation into a CatchAllBox.

Constructors

CatchAllArg cfg 

Instances

Instances details
Eq cfg => Eq (CatchAllArg cfg) Source # 
Instance details

Defined in UnliftIO.MessageBox.CatchAll

Methods

(==) :: CatchAllArg cfg -> CatchAllArg cfg -> Bool #

(/=) :: CatchAllArg cfg -> CatchAllArg cfg -> Bool #

Ord cfg => Ord (CatchAllArg cfg) Source # 
Instance details

Defined in UnliftIO.MessageBox.CatchAll

Methods

compare :: CatchAllArg cfg -> CatchAllArg cfg -> Ordering #

(<) :: CatchAllArg cfg -> CatchAllArg cfg -> Bool #

(<=) :: CatchAllArg cfg -> CatchAllArg cfg -> Bool #

(>) :: CatchAllArg cfg -> CatchAllArg cfg -> Bool #

(>=) :: CatchAllArg cfg -> CatchAllArg cfg -> Bool #

max :: CatchAllArg cfg -> CatchAllArg cfg -> CatchAllArg cfg #

min :: CatchAllArg cfg -> CatchAllArg cfg -> CatchAllArg cfg #

Show cfg => Show (CatchAllArg cfg) Source # 
Instance details

Defined in UnliftIO.MessageBox.CatchAll

Methods

showsPrec :: Int -> CatchAllArg cfg -> ShowS #

show :: CatchAllArg cfg -> String #

showList :: [CatchAllArg cfg] -> ShowS #

IsMessageBoxArg cfg => IsMessageBoxArg (CatchAllArg cfg) Source # 
Instance details

Defined in UnliftIO.MessageBox.CatchAll

Associated Types

type MessageBox (CatchAllArg cfg) :: Type -> Type Source #

type MessageBox (CatchAllArg cfg) Source # 
Instance details

Defined in UnliftIO.MessageBox.CatchAll

newtype CatchAllBox box a Source #

A wrapper around values that are instances of IsMessageBox.

The Input type will be wrapped using CatchAllInput.

Constructors

CatchAllBox (box a) 

Instances

Instances details
IsMessageBox box => IsMessageBox (CatchAllBox box) Source # 
Instance details

Defined in UnliftIO.MessageBox.CatchAll

Associated Types

type Input (CatchAllBox box) :: Type -> Type Source #

type Input (CatchAllBox box) Source # 
Instance details

Defined in UnliftIO.MessageBox.CatchAll

newtype CatchAllInput i a Source #

A wrapper around values that are instances of IsInput.

Constructors

CatchAllInput (i a) 

Instances

Instances details
IsInput i => IsInput (CatchAllInput i) Source # 
Instance details

Defined in UnliftIO.MessageBox.CatchAll

Methods

deliver :: MonadUnliftIO m => CatchAllInput i a -> a -> m Bool Source #

deliver_ :: MonadUnliftIO m => CatchAllInput i a -> a -> m () Source #