ouroboros-consensus-0.18.0.0: Consensus layer for the Ouroboros blockchain protocol
Safe HaskellSafe-Inferred
LanguageHaskell2010

Ouroboros.Consensus.Util.EarlyExit

Synopsis

Documentation

withEarlyExit_Functor m ⇒ WithEarlyExit m () → m () Source #

Re-exports

lift ∷ (MonadTrans t, Monad m) ⇒ m a → t m a #

Lift a computation from the argument monad to the constructed monad.

opaque

data WithEarlyExit m a Source #

Instances

Instances details
MonadTrans WithEarlyExit Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

Methods

liftMonad m ⇒ m a → WithEarlyExit m a #

Monad m ⇒ Alternative (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

Methods

emptyWithEarlyExit m a #

(<|>)WithEarlyExit m a → WithEarlyExit m a → WithEarlyExit m a #

someWithEarlyExit m a → WithEarlyExit m [a] #

manyWithEarlyExit m a → WithEarlyExit m [a] #

Monad m ⇒ Applicative (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

Methods

pure ∷ a → WithEarlyExit m a #

(<*>)WithEarlyExit m (a → b) → WithEarlyExit m a → WithEarlyExit m b #

liftA2 ∷ (a → b → c) → WithEarlyExit m a → WithEarlyExit m b → WithEarlyExit m c #

(*>)WithEarlyExit m a → WithEarlyExit m b → WithEarlyExit m b #

(<*)WithEarlyExit m a → WithEarlyExit m b → WithEarlyExit m a #

Functor m ⇒ Functor (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

Methods

fmap ∷ (a → b) → WithEarlyExit m a → WithEarlyExit m b #

(<$) ∷ a → WithEarlyExit m b → WithEarlyExit m a #

Monad m ⇒ Monad (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

Methods

(>>=)WithEarlyExit m a → (a → WithEarlyExit m b) → WithEarlyExit m b #

(>>)WithEarlyExit m a → WithEarlyExit m b → WithEarlyExit m b #

return ∷ a → WithEarlyExit m a #

Monad m ⇒ MonadPlus (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

Methods

mzeroWithEarlyExit m a #

mplusWithEarlyExit m a → WithEarlyExit m a → WithEarlyExit m a #

(MonadMVar m, MonadMask m, MonadEvaluate m) ⇒ MonadMVar (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

Associated Types

type MVar (WithEarlyExit m) ∷ TypeType Source #

(MonadMask m, MonadAsync m, MonadCatch (STM m)) ⇒ MonadAsync (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

Associated Types

type Async (WithEarlyExit m) = (async ∷ TypeType) Source #

Methods

asyncWithEarlyExit m a → WithEarlyExit m (Async (WithEarlyExit m) a) Source #

asyncBoundWithEarlyExit m a → WithEarlyExit m (Async (WithEarlyExit m) a) Source #

asyncOnIntWithEarlyExit m a → WithEarlyExit m (Async (WithEarlyExit m) a) Source #

asyncThreadIdAsync (WithEarlyExit m) a → ThreadId (WithEarlyExit m) Source #

withAsyncWithEarlyExit m a → (Async (WithEarlyExit m) a → WithEarlyExit m b) → WithEarlyExit m b Source #

withAsyncBoundWithEarlyExit m a → (Async (WithEarlyExit m) a → WithEarlyExit m b) → WithEarlyExit m b Source #

withAsyncOnIntWithEarlyExit m a → (Async (WithEarlyExit m) a → WithEarlyExit m b) → WithEarlyExit m b Source #

waitSTMAsync (WithEarlyExit m) a → STM (WithEarlyExit m) a Source #

pollSTMAsync (WithEarlyExit m) a → STM (WithEarlyExit m) (Maybe (Either SomeException a)) Source #

waitCatchSTMAsync (WithEarlyExit m) a → STM (WithEarlyExit m) (Either SomeException a) Source #

waitAnySTM ∷ [Async (WithEarlyExit m) a] → STM (WithEarlyExit m) (Async (WithEarlyExit m) a, a) Source #

waitAnyCatchSTM ∷ [Async (WithEarlyExit m) a] → STM (WithEarlyExit m) (Async (WithEarlyExit m) a, Either SomeException a) Source #

waitEitherSTMAsync (WithEarlyExit m) a → Async (WithEarlyExit m) b → STM (WithEarlyExit m) (Either a b) Source #

waitEitherSTM_Async (WithEarlyExit m) a → Async (WithEarlyExit m) b → STM (WithEarlyExit m) () Source #

waitEitherCatchSTMAsync (WithEarlyExit m) a → Async (WithEarlyExit m) b → STM (WithEarlyExit m) (Either (Either SomeException a) (Either SomeException b)) Source #

waitBothSTMAsync (WithEarlyExit m) a → Async (WithEarlyExit m) b → STM (WithEarlyExit m) (a, b) Source #

waitAsync (WithEarlyExit m) a → WithEarlyExit m a Source #

pollAsync (WithEarlyExit m) a → WithEarlyExit m (Maybe (Either SomeException a)) Source #

waitCatchAsync (WithEarlyExit m) a → WithEarlyExit m (Either SomeException a) Source #

cancelAsync (WithEarlyExit m) a → WithEarlyExit m () Source #

cancelWithException e ⇒ Async (WithEarlyExit m) a → e → WithEarlyExit m () Source #

uninterruptibleCancelAsync (WithEarlyExit m) a → WithEarlyExit m () Source #

waitAny ∷ [Async (WithEarlyExit m) a] → WithEarlyExit m (Async (WithEarlyExit m) a, a) Source #

waitAnyCatch ∷ [Async (WithEarlyExit m) a] → WithEarlyExit m (Async (WithEarlyExit m) a, Either SomeException a) Source #

waitAnyCancel ∷ [Async (WithEarlyExit m) a] → WithEarlyExit m (Async (WithEarlyExit m) a, a) Source #

waitAnyCatchCancel ∷ [Async (WithEarlyExit m) a] → WithEarlyExit m (Async (WithEarlyExit m) a, Either SomeException a) Source #

waitEitherAsync (WithEarlyExit m) a → Async (WithEarlyExit m) b → WithEarlyExit m (Either a b) Source #

waitEitherCatchAsync (WithEarlyExit m) a → Async (WithEarlyExit m) b → WithEarlyExit m (Either (Either SomeException a) (Either SomeException b)) Source #

waitEitherCancelAsync (WithEarlyExit m) a → Async (WithEarlyExit m) b → WithEarlyExit m (Either a b) Source #

waitEitherCatchCancelAsync (WithEarlyExit m) a → Async (WithEarlyExit m) b → WithEarlyExit m (Either (Either SomeException a) (Either SomeException b)) Source #

waitEither_Async (WithEarlyExit m) a → Async (WithEarlyExit m) b → WithEarlyExit m () Source #

waitBothAsync (WithEarlyExit m) a → Async (WithEarlyExit m) b → WithEarlyExit m (a, b) Source #

raceWithEarlyExit m a → WithEarlyExit m b → WithEarlyExit m (Either a b) Source #

race_WithEarlyExit m a → WithEarlyExit m b → WithEarlyExit m () Source #

concurrentlyWithEarlyExit m a → WithEarlyExit m b → WithEarlyExit m (a, b) Source #

concurrently_WithEarlyExit m a → WithEarlyExit m b → WithEarlyExit m () Source #

asyncWithUnmask ∷ ((∀ b. WithEarlyExit m b → WithEarlyExit m b) → WithEarlyExit m a) → WithEarlyExit m (Async (WithEarlyExit m) a) Source #

asyncOnWithUnmaskInt → ((∀ b. WithEarlyExit m b → WithEarlyExit m b) → WithEarlyExit m a) → WithEarlyExit m (Async (WithEarlyExit m) a) Source #

withAsyncWithUnmask ∷ ((∀ c. WithEarlyExit m c → WithEarlyExit m c) → WithEarlyExit m a) → (Async (WithEarlyExit m) a → WithEarlyExit m b) → WithEarlyExit m b Source #

withAsyncOnWithUnmaskInt → ((∀ c. WithEarlyExit m c → WithEarlyExit m c) → WithEarlyExit m a) → (Async (WithEarlyExit m) a → WithEarlyExit m b) → WithEarlyExit m b Source #

compareAsyncsAsync (WithEarlyExit m) a → Async (WithEarlyExit m) b → Ordering Source #

MonadEventlog m ⇒ MonadEventlog (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

MonadFork m ⇒ MonadFork (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

MonadThread m ⇒ MonadThread (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

Associated Types

type ThreadId (WithEarlyExit m) Source #

MonadST m ⇒ MonadST (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

Methods

stToIOST (PrimState (WithEarlyExit m)) a → WithEarlyExit m a Source #

withLiftST ∷ (∀ s. (∀ a. ST s a → WithEarlyExit m a) → b) → b Source #

MonadSTM m ⇒ MonadSTM (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

Associated Types

type STM (WithEarlyExit m) = (stm ∷ TypeType) Source #

type TVar (WithEarlyExit m) ∷ TypeType Source #

type TMVar (WithEarlyExit m) ∷ TypeType Source #

type TQueue (WithEarlyExit m) ∷ TypeType Source #

type TBQueue (WithEarlyExit m) ∷ TypeType Source #

type TArray (WithEarlyExit m) ∷ TypeTypeType Source #

type TSem (WithEarlyExit m) Source #

type TChan (WithEarlyExit m) ∷ TypeType Source #

Methods

atomicallyHasCallStackSTM (WithEarlyExit m) a → WithEarlyExit m a Source #

newTVar ∷ a → STM (WithEarlyExit m) (TVar (WithEarlyExit m) a) Source #

readTVarTVar (WithEarlyExit m) a → STM (WithEarlyExit m) a Source #

writeTVarTVar (WithEarlyExit m) a → a → STM (WithEarlyExit m) () Source #

retrySTM (WithEarlyExit m) a Source #

orElseSTM (WithEarlyExit m) a → STM (WithEarlyExit m) a → STM (WithEarlyExit m) a Source #

modifyTVarTVar (WithEarlyExit m) a → (a → a) → STM (WithEarlyExit m) () Source #

modifyTVar'TVar (WithEarlyExit m) a → (a → a) → STM (WithEarlyExit m) () Source #

stateTVarTVar (WithEarlyExit m) s → (s → (a, s)) → STM (WithEarlyExit m) a Source #

swapTVarTVar (WithEarlyExit m) a → a → STM (WithEarlyExit m) a Source #

checkBoolSTM (WithEarlyExit m) () Source #

newTMVar ∷ a → STM (WithEarlyExit m) (TMVar (WithEarlyExit m) a) Source #

newEmptyTMVarSTM (WithEarlyExit m) (TMVar (WithEarlyExit m) a) Source #

takeTMVarTMVar (WithEarlyExit m) a → STM (WithEarlyExit m) a Source #

tryTakeTMVarTMVar (WithEarlyExit m) a → STM (WithEarlyExit m) (Maybe a) Source #

putTMVarTMVar (WithEarlyExit m) a → a → STM (WithEarlyExit m) () Source #

tryPutTMVarTMVar (WithEarlyExit m) a → a → STM (WithEarlyExit m) Bool Source #

readTMVarTMVar (WithEarlyExit m) a → STM (WithEarlyExit m) a Source #

tryReadTMVarTMVar (WithEarlyExit m) a → STM (WithEarlyExit m) (Maybe a) Source #

swapTMVarTMVar (WithEarlyExit m) a → a → STM (WithEarlyExit m) a Source #

isEmptyTMVarTMVar (WithEarlyExit m) a → STM (WithEarlyExit m) Bool Source #

newTQueueSTM (WithEarlyExit m) (TQueue (WithEarlyExit m) a) Source #

readTQueueTQueue (WithEarlyExit m) a → STM (WithEarlyExit m) a Source #

tryReadTQueueTQueue (WithEarlyExit m) a → STM (WithEarlyExit m) (Maybe a) Source #

peekTQueueTQueue (WithEarlyExit m) a → STM (WithEarlyExit m) a Source #

tryPeekTQueueTQueue (WithEarlyExit m) a → STM (WithEarlyExit m) (Maybe a) Source #

flushTQueueTQueue (WithEarlyExit m) a → STM (WithEarlyExit m) [a] Source #

writeTQueueTQueue (WithEarlyExit m) a → a → STM (WithEarlyExit m) () Source #

isEmptyTQueueTQueue (WithEarlyExit m) a → STM (WithEarlyExit m) Bool Source #

unGetTQueueTQueue (WithEarlyExit m) a → a → STM (WithEarlyExit m) () Source #

newTBQueueNaturalSTM (WithEarlyExit m) (TBQueue (WithEarlyExit m) a) Source #

readTBQueueTBQueue (WithEarlyExit m) a → STM (WithEarlyExit m) a Source #

tryReadTBQueueTBQueue (WithEarlyExit m) a → STM (WithEarlyExit m) (Maybe a) Source #

peekTBQueueTBQueue (WithEarlyExit m) a → STM (WithEarlyExit m) a Source #

tryPeekTBQueueTBQueue (WithEarlyExit m) a → STM (WithEarlyExit m) (Maybe a) Source #

flushTBQueueTBQueue (WithEarlyExit m) a → STM (WithEarlyExit m) [a] Source #

writeTBQueueTBQueue (WithEarlyExit m) a → a → STM (WithEarlyExit m) () Source #

lengthTBQueueTBQueue (WithEarlyExit m) a → STM (WithEarlyExit m) Natural Source #

isEmptyTBQueueTBQueue (WithEarlyExit m) a → STM (WithEarlyExit m) Bool Source #

isFullTBQueueTBQueue (WithEarlyExit m) a → STM (WithEarlyExit m) Bool Source #

unGetTBQueueTBQueue (WithEarlyExit m) a → a → STM (WithEarlyExit m) () Source #

newTSemIntegerSTM (WithEarlyExit m) (TSem (WithEarlyExit m)) Source #

waitTSemTSem (WithEarlyExit m) → STM (WithEarlyExit m) () Source #

signalTSemTSem (WithEarlyExit m) → STM (WithEarlyExit m) () Source #

signalTSemNNaturalTSem (WithEarlyExit m) → STM (WithEarlyExit m) () Source #

newTChanSTM (WithEarlyExit m) (TChan (WithEarlyExit m) a) Source #

newBroadcastTChanSTM (WithEarlyExit m) (TChan (WithEarlyExit m) a) Source #

dupTChanTChan (WithEarlyExit m) a → STM (WithEarlyExit m) (TChan (WithEarlyExit m) a) Source #

cloneTChanTChan (WithEarlyExit m) a → STM (WithEarlyExit m) (TChan (WithEarlyExit m) a) Source #

readTChanTChan (WithEarlyExit m) a → STM (WithEarlyExit m) a Source #

tryReadTChanTChan (WithEarlyExit m) a → STM (WithEarlyExit m) (Maybe a) Source #

peekTChanTChan (WithEarlyExit m) a → STM (WithEarlyExit m) a Source #

tryPeekTChanTChan (WithEarlyExit m) a → STM (WithEarlyExit m) (Maybe a) Source #

writeTChanTChan (WithEarlyExit m) a → a → STM (WithEarlyExit m) () Source #

unGetTChanTChan (WithEarlyExit m) a → a → STM (WithEarlyExit m) () Source #

isEmptyTChanTChan (WithEarlyExit m) a → STM (WithEarlyExit m) Bool Source #

newTVarIO ∷ a → WithEarlyExit m (TVar (WithEarlyExit m) a) Source #

readTVarIOTVar (WithEarlyExit m) a → WithEarlyExit m a Source #

newTMVarIO ∷ a → WithEarlyExit m (TMVar (WithEarlyExit m) a) Source #

newEmptyTMVarIOWithEarlyExit m (TMVar (WithEarlyExit m) a) Source #

newTQueueIOWithEarlyExit m (TQueue (WithEarlyExit m) a) Source #

newTBQueueIONaturalWithEarlyExit m (TBQueue (WithEarlyExit m) a) Source #

newTChanIOWithEarlyExit m (TChan (WithEarlyExit m) a) Source #

newBroadcastTChanIOWithEarlyExit m (TChan (WithEarlyExit m) a) Source #

MonadCatch m ⇒ MonadCatch (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

Methods

catchException e ⇒ WithEarlyExit m a → (e → WithEarlyExit m a) → WithEarlyExit m a Source #

catchJustException e ⇒ (e → Maybe b) → WithEarlyExit m a → (b → WithEarlyExit m a) → WithEarlyExit m a Source #

tryException e ⇒ WithEarlyExit m a → WithEarlyExit m (Either e a) Source #

tryJustException e ⇒ (e → Maybe b) → WithEarlyExit m a → WithEarlyExit m (Either b a) Source #

handleException e ⇒ (e → WithEarlyExit m a) → WithEarlyExit m a → WithEarlyExit m a Source #

handleJustException e ⇒ (e → Maybe b) → (b → WithEarlyExit m a) → WithEarlyExit m a → WithEarlyExit m a Source #

onExceptionWithEarlyExit m a → WithEarlyExit m b → WithEarlyExit m a Source #

bracketOnErrorWithEarlyExit m a → (a → WithEarlyExit m b) → (a → WithEarlyExit m c) → WithEarlyExit m c Source #

generalBracketWithEarlyExit m a → (a → ExitCase b → WithEarlyExit m c) → (a → WithEarlyExit m b) → WithEarlyExit m (b, c) Source #

(MonadEvaluate m, MonadCatch m) ⇒ MonadEvaluate (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

Methods

evaluate ∷ a → WithEarlyExit m a Source #

MonadMask m ⇒ MonadMask (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

MonadCatch m ⇒ MonadThrow (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

Methods

throwIOException e ⇒ e → WithEarlyExit m a Source #

bracketWithEarlyExit m a → (a → WithEarlyExit m b) → (a → WithEarlyExit m c) → WithEarlyExit m c Source #

bracket_WithEarlyExit m a → WithEarlyExit m b → WithEarlyExit m c → WithEarlyExit m c Source #

finallyWithEarlyExit m a → WithEarlyExit m b → WithEarlyExit m a Source #

MonadMonotonicTimeNSec m ⇒ MonadMonotonicTimeNSec (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

MonadDelay m ⇒ MonadDelay (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

Methods

threadDelayIntWithEarlyExit m () Source #

(IOLike m, ∀ a. NoThunks (StrictTVar (WithEarlyExit m) a), ∀ a. NoThunks (StrictSVar (WithEarlyExit m) a), ∀ a. NoThunks (StrictMVar (WithEarlyExit m) a)) ⇒ IOLike (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

PrimMonad m ⇒ PrimMonad (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

Associated Types

type PrimState (WithEarlyExit m) Source #

MonadMonotonicTime m ⇒ MonadMonotonicTime (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

MonadDelay m ⇒ MonadDelay (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

(∀ a'. NoThunks (m a')) ⇒ NoThunks (WithEarlyExit m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

NoThunks (StrictSVar m a) ⇒ NoThunks (StrictSVar (WithEarlyExit m) a) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

NoThunks (StrictTVar m a) ⇒ NoThunks (StrictTVar (WithEarlyExit m) a) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

type MVar (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

type MVar (WithEarlyExit m) = MVar m
type Async (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

type ThreadId (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

type STM (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

type TArray (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

type TBQueue (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

type TChan (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

type TMVar (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

type TQueue (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

type TSem (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

type TSem (WithEarlyExit m) = TSem m
type TVar (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

type TVar (WithEarlyExit m) = TVar m
type PrimState (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit