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

Ouroboros.Consensus.Util.IOLike

Synopsis

Documentation

class (MonadAsync m, MonadMVar m, MonadEventlog m, MonadFork m, MonadST m, MonadDelay m, MonadThread m, MonadThrow m, MonadCatch m, MonadMask m, MonadMonotonicTime m, MonadEvaluate m, Alternative (STM m), MonadCatch (STM m), PrimMonad m, ∀ a. NoThunks (m a), ∀ a. NoThunks a ⇒ NoThunks (StrictTVar m a), ∀ a. NoThunks a ⇒ NoThunks (StrictSVar m a), ∀ a. NoThunks a ⇒ NoThunks (StrictMVar m a)) ⇒ IOLike m where Source #

Methods

forgetSignKeyKESKESAlgorithm v ⇒ SignKeyKES v → m () Source #

Securely forget a KES signing key.

No-op for the IOSim, but forgetSignKeyKES for IO.

Instances

Instances details
IOLike IO Source # 
Instance details

Defined in Ouroboros.Consensus.Util.IOLike

(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

Re-exports

MonadThrow

class (Typeable e, Show e) ⇒ Exception e where #

Any type that you wish to throw or catch as an exception must be an instance of the Exception class. The simplest case is a new exception type directly below the root:

data MyException = ThisException | ThatException
    deriving Show

instance Exception MyException

The default method definitions in the Exception class do what we need in this case. You can now throw and catch ThisException and ThatException as exceptions:

*Main> throw ThisException `catch` \e -> putStrLn ("Caught " ++ show (e :: MyException))
Caught ThisException

In more complicated examples, you may wish to define a whole hierarchy of exceptions:

---------------------------------------------------------------------
-- Make the root exception type for all the exceptions in a compiler

data SomeCompilerException = forall e . Exception e => SomeCompilerException e

instance Show SomeCompilerException where
    show (SomeCompilerException e) = show e

instance Exception SomeCompilerException

compilerExceptionToException :: Exception e => e -> SomeException
compilerExceptionToException = toException . SomeCompilerException

compilerExceptionFromException :: Exception e => SomeException -> Maybe e
compilerExceptionFromException x = do
    SomeCompilerException a <- fromException x
    cast a

---------------------------------------------------------------------
-- Make a subhierarchy for exceptions in the frontend of the compiler

data SomeFrontendException = forall e . Exception e => SomeFrontendException e

instance Show SomeFrontendException where
    show (SomeFrontendException e) = show e

instance Exception SomeFrontendException where
    toException = compilerExceptionToException
    fromException = compilerExceptionFromException

frontendExceptionToException :: Exception e => e -> SomeException
frontendExceptionToException = toException . SomeFrontendException

frontendExceptionFromException :: Exception e => SomeException -> Maybe e
frontendExceptionFromException x = do
    SomeFrontendException a <- fromException x
    cast a

---------------------------------------------------------------------
-- Make an exception type for a particular frontend compiler exception

data MismatchedParentheses = MismatchedParentheses
    deriving Show

instance Exception MismatchedParentheses where
    toException   = frontendExceptionToException
    fromException = frontendExceptionFromException

We can now catch a MismatchedParentheses exception as MismatchedParentheses, SomeFrontendException or SomeCompilerException, but not other types, e.g. IOException:

*Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: MismatchedParentheses))
Caught MismatchedParentheses
*Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: SomeFrontendException))
Caught MismatchedParentheses
*Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: SomeCompilerException))
Caught MismatchedParentheses
*Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: IOException))
*** Exception: MismatchedParentheses

Minimal complete definition

Nothing

Methods

toException ∷ e → SomeException #

fromExceptionSomeExceptionMaybe e #

displayException ∷ e → String #

Render this exception value in a human-friendly manner.

Default implementation: show.

Since: base-4.8.0.0

Instances

Instances details
Exception AesonException 
Instance details

Defined in Data.Aeson.Types.Internal

Exception AsyncCancelled 
Instance details

Defined in Control.Concurrent.Async.Internal

Exception ExceptionInLinkedThread 
Instance details

Defined in Control.Concurrent.Async.Internal

Exception NestedAtomically

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Exception NoMatchingContinuationPrompt

Since: base-4.18

Instance details

Defined in Control.Exception.Base

Exception NoMethodError

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Exception NonTermination

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Exception PatternMatchFail

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Exception RecConError

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Exception RecSelError

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Exception RecUpdError

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Exception TypeError

Since: base-4.9.0.0

Instance details

Defined in Control.Exception.Base

Exception Void

Since: base-4.8.0.0

Instance details

Defined in GHC.Exception.Type

Exception ErrorCall

Since: base-4.0.0.0

Instance details

Defined in GHC.Exception

Exception ArithException

Since: base-4.0.0.0

Instance details

Defined in GHC.Exception.Type

Exception SomeException

Since: base-3.0

Instance details

Defined in GHC.Exception.Type

Exception AllocationLimitExceeded

Since: base-4.8.0.0

Instance details

Defined in GHC.IO.Exception

Exception ArrayException

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Exception AssertionFailed

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Exception AsyncException

Since: base-4.7.0.0

Instance details

Defined in GHC.IO.Exception

Exception BlockedIndefinitelyOnMVar

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Exception BlockedIndefinitelyOnSTM

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Exception CompactionFailed

Since: base-4.10.0.0

Instance details

Defined in GHC.IO.Exception

Exception Deadlock

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Exception ExitCode

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Exception FixIOException

Since: base-4.11.0.0

Instance details

Defined in GHC.IO.Exception

Exception IOException

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Exception SomeAsyncException

Since: base-4.7.0.0

Instance details

Defined in GHC.IO.Exception

Exception ASCII7_Invalid 
Instance details

Defined in Basement.String.Encoding.ASCII7

Exception ISO_8859_1_Invalid 
Instance details

Defined in Basement.String.Encoding.ISO_8859_1

Exception UTF16_Invalid 
Instance details

Defined in Basement.String.Encoding.UTF16

Exception UTF32_Invalid 
Instance details

Defined in Basement.String.Encoding.UTF32

Exception BimapException 
Instance details

Defined in Data.Bimap

Methods

toException ∷ BimapException → SomeException #

fromExceptionSomeExceptionMaybe BimapException #

displayException ∷ BimapException → String #

Exception DecoderError 
Instance details

Defined in Cardano.Binary.FromCBOR

Exception SeedBytesExhausted 
Instance details

Defined in Cardano.Crypto.Seed

Exception DeserialiseFailure 
Instance details

Defined in Codec.CBOR.Read

Exception CryptoError 
Instance details

Defined in Crypto.Error.Types

Exception CryptoError 
Instance details

Defined in Crypto.Error.Types

Exception DNSError 
Instance details

Defined in Network.DNS.Types.Internal

Exception FsError 
Instance details

Defined in System.FS.API.Types

Exception ExceptionInLinkedThread 
Instance details

Defined in Control.Monad.Class.MonadAsync

Exception BlockedIndefinitely 
Instance details

Defined in Control.Monad.Class.MonadSTM.Internal

Methods

toException ∷ BlockedIndefinitely → SomeException #

fromExceptionSomeExceptionMaybe BlockedIndefinitely #

displayException ∷ BlockedIndefinitely → String #

Exception DataMeasureClassOverflowException 
Instance details

Defined in Data.Measure.Class

Exception InvalidPosException 
Instance details

Defined in Text.Megaparsec.Pos

Exception MuxError 
Instance details

Defined in Network.Mux.Trace

Exception MuxRuntimeError 
Instance details

Defined in Network.Mux.Types

Exception SanityCheckIssue Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsSanityCheck

Exception SystemClockMovedBackException Source # 
Instance details

Defined in Ouroboros.Consensus.BlockchainTime.WallClock.Util

Exception OutsideForecastRange Source # 
Instance details

Defined in Ouroboros.Consensus.Forecast

Exception HardForkEncoderException Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.Common

Exception PastHorizonException Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.History.Qry

Exception BlockFetchServerException Source # 
Instance details

Defined in Ouroboros.Consensus.MiniProtocol.BlockFetch.Server

Exception ChainSyncClientException Source # 
Instance details

Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client

Exception HistoricityException Source # 
Instance details

Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client.HistoricityCheck

Exception HeaderArrivalException Source # 
Instance details

Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client.InFutureCheck

Exception ChunkAssertionFailure Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Chunks.Internal

Exception FuseBlownException Source # 
Instance details

Defined in Ouroboros.Consensus.Util

Exception RegistryClosedException Source # 
Instance details

Defined in Ouroboros.Consensus.Util.ResourceRegistry

Exception ResourceRegistryThreadException Source # 
Instance details

Defined in Ouroboros.Consensus.Util.ResourceRegistry

Exception TempRegistryException Source # 
Instance details

Defined in Ouroboros.Consensus.Util.ResourceRegistry

Exception VersionError Source # 
Instance details

Defined in Ouroboros.Consensus.Util.Versioned

Exception FreeVariableError 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Exception ApplyProgramError 
Instance details

Defined in PlutusCore.Error

Exception CostModelApplyError 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

Exception ScriptDecodeError 
Instance details

Defined in PlutusLedgerApi.Common.SerialisedScript

Exception LedgerBytesError 
Instance details

Defined in PlutusLedgerApi.V1.Bytes

Exception InvalidAccess 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Exception ResourceCleanupException 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Exception AssertionException 
Instance details

Defined in Control.State.Transition.Extended

(Typeable blk, StandardHash blk) ⇒ Exception (ChainDbError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.API

(Typeable blk, StandardHash blk) ⇒ Exception (ChainDbFailure blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.API

(StandardHash blk, Typeable blk) ⇒ Exception (ImmutableDBError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

(StandardHash blk, Typeable blk) ⇒ Exception (VolatileDBError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.API

Exception (UniqueError SrcSpan) 
Instance details

Defined in PlutusCore.Error

(Show s, Show (Token s), Show e, ShowErrorComponent e, VisualStream s, Typeable s, Typeable e) ⇒ Exception (ParseError s e) 
Instance details

Defined in Text.Megaparsec.Error

(Show s, Show (Token s), Show e, ShowErrorComponent e, VisualStream s, TraversableStream s, Typeable s, Typeable e) ⇒ Exception (ParseErrorBundle s e) 
Instance details

Defined in Text.Megaparsec.Error

(PrettyPlc cause, PrettyPlc err, Typeable cause, Typeable err) ⇒ Exception (ErrorWithCause err cause) 
Instance details

Defined in PlutusCore.Evaluation.ErrorWithCause

(ThrowableBuiltins uni fun, Pretty ann, Typeable ann) ⇒ Exception (Error uni fun ann) 
Instance details

Defined in PlutusIR.Error

Methods

toExceptionError uni fun ann → SomeException #

fromExceptionSomeExceptionMaybe (Error uni fun ann) #

displayExceptionError uni fun ann → String #

data ExitCase a Source #

Used in generalBracket

See exceptions package for discussion and motivation.

Instances

Instances details
Functor ExitCase 
Instance details

Defined in Control.Monad.Class.MonadThrow

Methods

fmap ∷ (a → b) → ExitCase a → ExitCase b #

(<$) ∷ a → ExitCase b → ExitCase a #

Show a ⇒ Show (ExitCase a) 
Instance details

Defined in Control.Monad.Class.MonadThrow

Methods

showsPrecIntExitCase a → ShowS #

showExitCase a → String #

showList ∷ [ExitCase a] → ShowS #

class MonadThrow m ⇒ MonadCatch (m ∷ TypeType) where Source #

Catching exceptions.

Covers standard utilities to respond to exceptions.

Minimal complete definition

catch

Methods

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

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

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

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

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

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

onException ∷ m a → m b → m a Source #

bracketOnError ∷ m a → (a → m b) → (a → m c) → m c Source #

generalBracket ∷ m a → (a → ExitCase b → m c) → (a → m b) → m (b, c) Source #

Instances

Instances details
MonadCatch STM 
Instance details

Defined in Control.Monad.Class.MonadThrow

Methods

catchException e ⇒ STM a → (e → STM a) → STM a Source #

catchJustException e ⇒ (e → Maybe b) → STM a → (b → STM a) → STM a Source #

tryException e ⇒ STM a → STM (Either e a) Source #

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

handleException e ⇒ (e → STM a) → STM a → STM a Source #

handleJustException e ⇒ (e → Maybe b) → (b → STM a) → STM a → STM a Source #

onExceptionSTM a → STM b → STM a Source #

bracketOnErrorSTM a → (a → STM b) → (a → STM c) → STM c Source #

generalBracketSTM a → (a → ExitCase b → STM c) → (a → STM b) → STM (b, c) Source #

MonadCatch IO 
Instance details

Defined in Control.Monad.Class.MonadThrow

Methods

catchException e ⇒ IO a → (e → IO a) → IO a Source #

catchJustException e ⇒ (e → Maybe b) → IO a → (b → IO a) → IO a Source #

tryException e ⇒ IO a → IO (Either e a) Source #

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

handleException e ⇒ (e → IO a) → IO a → IO a Source #

handleJustException e ⇒ (e → Maybe b) → (b → IO a) → IO a → IO a Source #

onExceptionIO a → IO b → IO a Source #

bracketOnErrorIO a → (a → IO b) → (a → IO c) → IO c Source #

generalBracketIO a → (a → ExitCase b → IO c) → (a → IO b) → IO (b, c) 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 #

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

Defined in Ouroboros.Consensus.Util

Methods

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

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

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

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

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

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

onExceptionElectric m a → Electric m b → Electric m a Source #

bracketOnErrorElectric m a → (a → Electric m b) → (a → Electric m c) → Electric m c Source #

generalBracketElectric m a → (a → ExitCase b → Electric m c) → (a → Electric m b) → Electric m (b, c) Source #

MonadCatch m ⇒ MonadCatch (WithTempRegistry st m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.ResourceRegistry

Methods

catchException e ⇒ WithTempRegistry st m a → (e → WithTempRegistry st m a) → WithTempRegistry st m a Source #

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

tryException e ⇒ WithTempRegistry st m a → WithTempRegistry st m (Either e a) Source #

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

handleException e ⇒ (e → WithTempRegistry st m a) → WithTempRegistry st m a → WithTempRegistry st m a Source #

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

onExceptionWithTempRegistry st m a → WithTempRegistry st m b → WithTempRegistry st m a Source #

bracketOnErrorWithTempRegistry st m a → (a → WithTempRegistry st m b) → (a → WithTempRegistry st m c) → WithTempRegistry st m c Source #

generalBracketWithTempRegistry st m a → (a → ExitCase b → WithTempRegistry st m c) → (a → WithTempRegistry st m b) → WithTempRegistry st m (b, c) Source #

MonadCatch m ⇒ MonadCatch (ReaderT r m) 
Instance details

Defined in Control.Monad.Class.MonadThrow

Methods

catchException e ⇒ ReaderT r m a → (e → ReaderT r m a) → ReaderT r m a Source #

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

tryException e ⇒ ReaderT r m a → ReaderT r m (Either e a) Source #

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

handleException e ⇒ (e → ReaderT r m a) → ReaderT r m a → ReaderT r m a Source #

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

onExceptionReaderT r m a → ReaderT r m b → ReaderT r m a Source #

bracketOnErrorReaderT r m a → (a → ReaderT r m b) → (a → ReaderT r m c) → ReaderT r m c Source #

generalBracketReaderT r m a → (a → ExitCase b → ReaderT r m c) → (a → ReaderT r m b) → ReaderT r m (b, c) Source #

class MonadCatch m ⇒ MonadMask (m ∷ TypeType) where Source #

Support for safely working in the presence of asynchronous exceptions.

This is typically not needed directly as the utilities in MonadThrow and MonadCatch cover most use cases.

Minimal complete definition

mask, uninterruptibleMask

Methods

mask ∷ ((∀ a. m a → m a) → m b) → m b Source #

uninterruptibleMask ∷ ((∀ a. m a → m a) → m b) → m b Source #

mask_ ∷ m a → m a Source #

uninterruptibleMask_ ∷ m a → m a Source #

Instances

Instances details
MonadMask IO 
Instance details

Defined in Control.Monad.Class.MonadThrow

Methods

mask ∷ ((∀ a. IO a → IO a) → IO b) → IO b Source #

uninterruptibleMask ∷ ((∀ a. IO a → IO a) → IO b) → IO b Source #

mask_IO a → IO a Source #

uninterruptibleMask_IO a → IO a Source #

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

Defined in Ouroboros.Consensus.Util.EarlyExit

MonadMask m ⇒ MonadMask (WithTempRegistry st m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.ResourceRegistry

Methods

mask ∷ ((∀ a. WithTempRegistry st m a → WithTempRegistry st m a) → WithTempRegistry st m b) → WithTempRegistry st m b Source #

uninterruptibleMask ∷ ((∀ a. WithTempRegistry st m a → WithTempRegistry st m a) → WithTempRegistry st m b) → WithTempRegistry st m b Source #

mask_WithTempRegistry st m a → WithTempRegistry st m a Source #

uninterruptibleMask_WithTempRegistry st m a → WithTempRegistry st m a Source #

MonadMask m ⇒ MonadMask (ReaderT r m) 
Instance details

Defined in Control.Monad.Class.MonadThrow

Methods

mask ∷ ((∀ a. ReaderT r m a → ReaderT r m a) → ReaderT r m b) → ReaderT r m b Source #

uninterruptibleMask ∷ ((∀ a. ReaderT r m a → ReaderT r m a) → ReaderT r m b) → ReaderT r m b Source #

mask_ReaderT r m a → ReaderT r m a Source #

uninterruptibleMask_ReaderT r m a → ReaderT r m a Source #

class Monad m ⇒ MonadThrow (m ∷ TypeType) where Source #

Throwing exceptions, and resource handling in the presence of exceptions.

Does not include the ability to respond to exceptions.

Minimal complete definition

throwIO

Methods

throwIOException e ⇒ e → m a Source #

bracket ∷ m a → (a → m b) → (a → m c) → m c Source #

bracket_ ∷ m a → m b → m c → m c Source #

finally ∷ m a → m b → m a Source #

Instances

Instances details
MonadThrow STM 
Instance details

Defined in Control.Monad.Class.MonadThrow

Methods

throwIOException e ⇒ e → STM a Source #

bracketSTM a → (a → STM b) → (a → STM c) → STM c Source #

bracket_STM a → STM b → STM c → STM c Source #

finallySTM a → STM b → STM a Source #

MonadThrow IO 
Instance details

Defined in Control.Monad.Class.MonadThrow

Methods

throwIOException e ⇒ e → IO a Source #

bracketIO a → (a → IO b) → (a → IO c) → IO c Source #

bracket_IO a → IO b → IO c → IO c Source #

finallyIO a → IO b → IO a Source #

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 #

MonadThrow m ⇒ MonadThrow (Electric m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util

Methods

throwIOException e ⇒ e → Electric m a Source #

bracketElectric m a → (a → Electric m b) → (a → Electric m c) → Electric m c Source #

bracket_Electric m a → Electric m b → Electric m c → Electric m c Source #

finallyElectric m a → Electric m b → Electric m a Source #

MonadThrow m ⇒ MonadThrow (WithTempRegistry st m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.ResourceRegistry

Methods

throwIOException e ⇒ e → WithTempRegistry st m a Source #

bracketWithTempRegistry st m a → (a → WithTempRegistry st m b) → (a → WithTempRegistry st m c) → WithTempRegistry st m c Source #

bracket_WithTempRegistry st m a → WithTempRegistry st m b → WithTempRegistry st m c → WithTempRegistry st m c Source #

finallyWithTempRegistry st m a → WithTempRegistry st m b → WithTempRegistry st m a Source #

MonadThrow m ⇒ MonadThrow (ReaderT r m) 
Instance details

Defined in Control.Monad.Class.MonadThrow

Methods

throwIOException e ⇒ e → ReaderT r m a Source #

bracketReaderT r m a → (a → ReaderT r m b) → (a → ReaderT r m c) → ReaderT r m c Source #

bracket_ReaderT r m a → ReaderT r m b → ReaderT r m c → ReaderT r m c Source #

finallyReaderT r m a → ReaderT r m b → ReaderT r m a Source #

data SomeException #

The SomeException type is the root of the exception type hierarchy. When an exception of type e is thrown, behind the scenes it is encapsulated in a SomeException.

Instances

Instances details
Exception SomeException

Since: base-3.0

Instance details

Defined in GHC.Exception.Type

Show SomeException

Since: base-3.0

Instance details

Defined in GHC.Exception.Type

Variables with NoThunks invariants

MonadFork, TODO: Should we hide this in favour of MonadAsync?

class MonadThread m ⇒ MonadFork (m ∷ TypeType) where Source #

Minimal complete definition

forkIO, forkOn, forkIOWithUnmask, forkFinally, throwTo, yield

Methods

forkIO ∷ m () → m (ThreadId m) Source #

forkOnInt → m () → m (ThreadId m) Source #

forkIOWithUnmask ∷ ((∀ a. m a → m a) → m ()) → m (ThreadId m) Source #

forkFinally ∷ m a → (Either SomeException a → m ()) → m (ThreadId m) Source #

throwToException e ⇒ ThreadId m → e → m () Source #

killThreadThreadId m → m () Source #

yield ∷ m () Source #

Instances

Instances details
MonadFork IO 
Instance details

Defined in Control.Monad.Class.MonadFork

Methods

forkIOIO () → IO (ThreadId IO) Source #

forkOnIntIO () → IO (ThreadId IO) Source #

forkIOWithUnmask ∷ ((∀ a. IO a → IO a) → IO ()) → IO (ThreadId IO) Source #

forkFinallyIO a → (Either SomeException a → IO ()) → IO (ThreadId IO) Source #

throwToException e ⇒ ThreadId IO → e → IO () Source #

killThreadThreadId IOIO () Source #

yieldIO () Source #

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

Defined in Ouroboros.Consensus.Util.EarlyExit

MonadFork m ⇒ MonadFork (ReaderT e m) 
Instance details

Defined in Control.Monad.Class.MonadFork

Methods

forkIOReaderT e m () → ReaderT e m (ThreadId (ReaderT e m)) Source #

forkOnIntReaderT e m () → ReaderT e m (ThreadId (ReaderT e m)) Source #

forkIOWithUnmask ∷ ((∀ a. ReaderT e m a → ReaderT e m a) → ReaderT e m ()) → ReaderT e m (ThreadId (ReaderT e m)) Source #

forkFinallyReaderT e m a → (Either SomeException a → ReaderT e m ()) → ReaderT e m (ThreadId (ReaderT e m)) Source #

throwToException e0 ⇒ ThreadId (ReaderT e m) → e0 → ReaderT e m () Source #

killThreadThreadId (ReaderT e m) → ReaderT e m () Source #

yieldReaderT e m () Source #

class (Monad m, Eq (ThreadId m), Ord (ThreadId m), Show (ThreadId m)) ⇒ MonadThread (m ∷ TypeType) where Source #

Associated Types

type ThreadId (m ∷ TypeType) Source #

Methods

myThreadId ∷ m (ThreadId m) Source #

labelThreadThreadId m → String → m () Source #

Instances

Instances details
MonadThread IO 
Instance details

Defined in Control.Monad.Class.MonadFork

Associated Types

type ThreadId IO Source #

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

Defined in Ouroboros.Consensus.Util.EarlyExit

Associated Types

type ThreadId (WithEarlyExit m) Source #

MonadThread m ⇒ MonadThread (ReaderT r m) 
Instance details

Defined in Control.Monad.Class.MonadFork

Associated Types

type ThreadId (ReaderT r m) Source #

Methods

myThreadIdReaderT r m (ThreadId (ReaderT r m)) Source #

labelThreadThreadId (ReaderT r m) → StringReaderT r m () Source #

labelThisThreadMonadThread m ⇒ String → m () Source #

Apply the label to the current thread

MonadAsync

data ExceptionInLinkedThread Source #

Exception from child thread re-raised in parent thread

We record the thread ID of the child thread as a String. This avoids an m parameter in the type, which is important: ExceptionInLinkedThread must be an instance of Exception, requiring it to be Typeable; if m appeared in the type, we would require m to be Typeable, which does not work with with the simulator, as it would require a Typeable constraint on the s parameter of IOSim.

class (MonadSTM m, MonadThread m) ⇒ MonadAsync (m ∷ TypeType) where Source #

Associated Types

type Async (m ∷ TypeType) = (async ∷ TypeType) | async → m Source #

An asynchronous action

See Async.

Methods

async ∷ m a → m (Async m a) Source #

See async.

asyncBound ∷ m a → m (Async m a) Source #

asyncOnInt → m a → m (Async m a) Source #

See asyncOn.

asyncThreadIdAsync m a → ThreadId m Source #

withAsync ∷ m a → (Async m a → m b) → m b Source #

withAsyncBound ∷ m a → (Async m a → m b) → m b Source #

withAsyncOnInt → m a → (Async m a → m b) → m b Source #

waitSTMAsync m a → STM m a Source #

See waitSTM.

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

See pollSTM.

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

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

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

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

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

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

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

waitAsync m a → m a Source #

See wait.

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

See poll.

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

cancelAsync m a → m () Source #

See cancel.

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

uninterruptibleCancelAsync m a → m () Source #

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

See waitAny.

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

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

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

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

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

Note, IO-based implementations should override the default implementation. See the async package implementation and comments. http://hackage.haskell.org/package/async-2.2.1/docs/src/Control.Concurrent.Async.html#waitEitherCatch

See waitEitherCatch.

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

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

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

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

race ∷ m a → m b → m (Either a b) Source #

See race.

race_ ∷ m a → m b → m () Source #

See race_.

concurrently ∷ m a → m b → m (a, b) Source #

concurrently_ ∷ m a → m b → m () Source #

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

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

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

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

compareAsyncsAsync m a → Async m b → Ordering Source #

Instances

Instances details
MonadAsync IO 
Instance details

Defined in Control.Monad.Class.MonadAsync

Associated Types

type Async IO = (async ∷ TypeType) Source #

Methods

asyncIO a → IO (Async IO a) Source #

asyncBoundIO a → IO (Async IO a) Source #

asyncOnIntIO a → IO (Async IO a) Source #

asyncThreadIdAsync IO a → ThreadId IO Source #

withAsyncIO a → (Async IO a → IO b) → IO b Source #

withAsyncBoundIO a → (Async IO a → IO b) → IO b Source #

withAsyncOnIntIO a → (Async IO a → IO b) → IO b Source #

waitSTMAsync IO a → STM IO a Source #

pollSTMAsync IO a → STM IO (Maybe (Either SomeException a)) Source #

waitCatchSTMAsync IO a → STM IO (Either SomeException a) Source #

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

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

waitEitherSTMAsync IO a → Async IO b → STM IO (Either a b) Source #

waitEitherSTM_Async IO a → Async IO b → STM IO () Source #

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

waitBothSTMAsync IO a → Async IO b → STM IO (a, b) Source #

waitAsync IO a → IO a Source #

pollAsync IO a → IO (Maybe (Either SomeException a)) Source #

waitCatchAsync IO a → IO (Either SomeException a) Source #

cancelAsync IO a → IO () Source #

cancelWithException e ⇒ Async IO a → e → IO () Source #

uninterruptibleCancelAsync IO a → IO () Source #

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

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

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

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

waitEitherAsync IO a → Async IO b → IO (Either a b) Source #

waitEitherCatchAsync IO a → Async IO b → IO (Either (Either SomeException a) (Either SomeException b)) Source #

waitEitherCancelAsync IO a → Async IO b → IO (Either a b) Source #

waitEitherCatchCancelAsync IO a → Async IO b → IO (Either (Either SomeException a) (Either SomeException b)) Source #

waitEither_Async IO a → Async IO b → IO () Source #

waitBothAsync IO a → Async IO b → IO (a, b) Source #

raceIO a → IO b → IO (Either a b) Source #

race_IO a → IO b → IO () Source #

concurrentlyIO a → IO b → IO (a, b) Source #

concurrently_IO a → IO b → IO () Source #

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

asyncOnWithUnmaskInt → ((∀ b. IO b → IO b) → IO a) → IO (Async IO a) Source #

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

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

compareAsyncsAsync IO a → Async IO b → Ordering 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 #

(MonadAsync m, MonadCatch (STM m), MonadFork m, MonadMask m) ⇒ MonadAsync (ReaderT r m) 
Instance details

Defined in Control.Monad.Class.MonadAsync

Associated Types

type Async (ReaderT r m) = (async ∷ TypeType) Source #

Methods

asyncReaderT r m a → ReaderT r m (Async (ReaderT r m) a) Source #

asyncBoundReaderT r m a → ReaderT r m (Async (ReaderT r m) a) Source #

asyncOnIntReaderT r m a → ReaderT r m (Async (ReaderT r m) a) Source #

asyncThreadIdAsync (ReaderT r m) a → ThreadId (ReaderT r m) Source #

withAsyncReaderT r m a → (Async (ReaderT r m) a → ReaderT r m b) → ReaderT r m b Source #

withAsyncBoundReaderT r m a → (Async (ReaderT r m) a → ReaderT r m b) → ReaderT r m b Source #

withAsyncOnIntReaderT r m a → (Async (ReaderT r m) a → ReaderT r m b) → ReaderT r m b Source #

waitSTMAsync (ReaderT r m) a → STM (ReaderT r m) a Source #

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

waitCatchSTMAsync (ReaderT r m) a → STM (ReaderT r m) (Either SomeException a) Source #

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

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

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

waitEitherSTM_Async (ReaderT r m) a → Async (ReaderT r m) b → STM (ReaderT r m) () Source #

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

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

waitAsync (ReaderT r m) a → ReaderT r m a Source #

pollAsync (ReaderT r m) a → ReaderT r m (Maybe (Either SomeException a)) Source #

waitCatchAsync (ReaderT r m) a → ReaderT r m (Either SomeException a) Source #

cancelAsync (ReaderT r m) a → ReaderT r m () Source #

cancelWithException e ⇒ Async (ReaderT r m) a → e → ReaderT r m () Source #

uninterruptibleCancelAsync (ReaderT r m) a → ReaderT r m () Source #

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

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

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

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

waitEitherAsync (ReaderT r m) a → Async (ReaderT r m) b → ReaderT r m (Either a b) Source #

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

waitEitherCancelAsync (ReaderT r m) a → Async (ReaderT r m) b → ReaderT r m (Either a b) Source #

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

waitEither_Async (ReaderT r m) a → Async (ReaderT r m) b → ReaderT r m () Source #

waitBothAsync (ReaderT r m) a → Async (ReaderT r m) b → ReaderT r m (a, b) Source #

raceReaderT r m a → ReaderT r m b → ReaderT r m (Either a b) Source #

race_ReaderT r m a → ReaderT r m b → ReaderT r m () Source #

concurrentlyReaderT r m a → ReaderT r m b → ReaderT r m (a, b) Source #

concurrently_ReaderT r m a → ReaderT r m b → ReaderT r m () Source #

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

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

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

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

compareAsyncsAsync (ReaderT r m) a → Async (ReaderT r m) b → Ordering Source #

link ∷ (MonadAsync m, MonadFork m, MonadMask m) ⇒ Async m a → m () Source #

Like link.

linkTo ∷ (MonadAsync m, MonadFork m, MonadMask m) ⇒ ThreadId m → Async m a → m () Source #

Generalization of link that links an async to an arbitrary thread.

Non standard (not in async library)

MonadST

class PrimMonad m ⇒ MonadST (m ∷ TypeType) where Source #

This class is for abstracting over stToIO which allows running ST actions in IO. In this case it is to allow running ST actions within another monad m.

The normal type of stToIO is:

stToIO :: ST RealWorld a -> IO a

We have two approaches to abstracting over this, a new and an older (deprecated) method. The new method borrows the primitive package's PrimMonad and PrimState type family. This gives us:

stToIO :: ST (PrimState m) a -> m a

Which for IO is exactly the same as above. For ST it is identity, while for IOSim it is

stToIO :: ST s a -> IOSim s a

The older (deprecated) method is tricky because we need to not care about both the IO, and also the RealWorld, and it does so avoiding mentioning any s type (which is what the PrimState type family gives access to). The solution is to write an action that is given the liftST as an argument and where that action itself is polymorphic in the s parameter. This allows us to instantiate it with RealWorld in the IO case, and the local s in a case where we are embedding into another ST action.

Minimal complete definition

stToIO

Methods

stToIOST (PrimState m) a → m a Source #

Since: io-classes-1.4.1.0

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

Deprecated. Use stToIO instead.

Instances

Instances details
MonadST IO 
Instance details

Defined in Control.Monad.Class.MonadST

Methods

stToIOST (PrimState IO) a → IO a Source #

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

MonadST (ST s) 
Instance details

Defined in Control.Monad.Class.MonadST

Methods

stToIOST (PrimState (ST s)) a → ST s a Source #

withLiftST ∷ (∀ s0. (∀ a. ST s0 a → ST s a) → b) → b 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 #

(MonadST m, PrimMonad m) ⇒ MonadST (ReaderT r m) 
Instance details

Defined in Control.Monad.Class.MonadST

Methods

stToIOST (PrimState (ReaderT r m)) a → ReaderT r m a Source #

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

class Monad m ⇒ PrimMonad (m ∷ TypeType) where Source #

Class of monads which can perform primitive state-transformer actions.

Associated Types

type PrimState (m ∷ TypeType) Source #

State token type.

Methods

primitive ∷ (State# (PrimState m) → (# State# (PrimState m), a #)) → m a Source #

Execute a primitive operation.

Instances

Instances details
PrimMonad IO 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState IO Source #

Methods

primitive ∷ (State# (PrimState IO) → (# State# (PrimState IO), a #)) → IO a Source #

PrimMonad (ST s) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (ST s) Source #

Methods

primitive ∷ (State# (PrimState (ST s)) → (# State# (PrimState (ST s)), a #)) → ST s a Source #

PrimMonad (ST s) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (ST s) Source #

Methods

primitive ∷ (State# (PrimState (ST s)) → (# State# (PrimState (ST s)), a #)) → ST s a Source #

PrimMonad m ⇒ PrimMonad (GenT m) 
Instance details

Defined in Hedgehog.Internal.Gen

Associated Types

type PrimState (GenT m) Source #

Methods

primitive ∷ (State# (PrimState (GenT m)) → (# State# (PrimState (GenT m)), a #)) → GenT m a Source #

PrimMonad m ⇒ PrimMonad (PropertyT m) 
Instance details

Defined in Hedgehog.Internal.Property

Associated Types

type PrimState (PropertyT m) Source #

Methods

primitive ∷ (State# (PrimState (PropertyT m)) → (# State# (PrimState (PropertyT m)), a #)) → PropertyT m a Source #

PrimMonad m ⇒ PrimMonad (TestT m) 
Instance details

Defined in Hedgehog.Internal.Property

Associated Types

type PrimState (TestT m) Source #

Methods

primitive ∷ (State# (PrimState (TestT m)) → (# State# (PrimState (TestT m)), a #)) → TestT m a Source #

PrimMonad m ⇒ PrimMonad (TreeT m) 
Instance details

Defined in Hedgehog.Internal.Tree

Associated Types

type PrimState (TreeT m) Source #

Methods

primitive ∷ (State# (PrimState (TreeT m)) → (# State# (PrimState (TreeT m)), a #)) → TreeT m a Source #

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

Defined in Ouroboros.Consensus.Util.EarlyExit

Associated Types

type PrimState (WithEarlyExit m) Source #

PrimMonad m ⇒ PrimMonad (ResourceT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Associated Types

type PrimState (ResourceT m) Source #

Methods

primitive ∷ (State# (PrimState (ResourceT m)) → (# State# (PrimState (ResourceT m)), a #)) → ResourceT m a Source #

PrimMonad m ⇒ PrimMonad (MaybeT m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (MaybeT m) Source #

Methods

primitive ∷ (State# (PrimState (MaybeT m)) → (# State# (PrimState (MaybeT m)), a #)) → MaybeT m a Source #

(Monoid w, PrimMonad m) ⇒ PrimMonad (AccumT w m)

Since: primitive-0.6.3.0

Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (AccumT w m) Source #

Methods

primitive ∷ (State# (PrimState (AccumT w m)) → (# State# (PrimState (AccumT w m)), a #)) → AccumT w m a Source #

PrimMonad m ⇒ PrimMonad (ExceptT e m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (ExceptT e m) Source #

Methods

primitive ∷ (State# (PrimState (ExceptT e m)) → (# State# (PrimState (ExceptT e m)), a #)) → ExceptT e m a Source #

PrimMonad m ⇒ PrimMonad (IdentityT m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (IdentityT m) Source #

Methods

primitive ∷ (State# (PrimState (IdentityT m)) → (# State# (PrimState (IdentityT m)), a #)) → IdentityT m a Source #

PrimMonad m ⇒ PrimMonad (ReaderT r m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (ReaderT r m) Source #

Methods

primitive ∷ (State# (PrimState (ReaderT r m)) → (# State# (PrimState (ReaderT r m)), a #)) → ReaderT r m a Source #

PrimMonad m ⇒ PrimMonad (SelectT r m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (SelectT r m) Source #

Methods

primitive ∷ (State# (PrimState (SelectT r m)) → (# State# (PrimState (SelectT r m)), a #)) → SelectT r m a Source #

PrimMonad m ⇒ PrimMonad (StateT s m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (StateT s m) Source #

Methods

primitive ∷ (State# (PrimState (StateT s m)) → (# State# (PrimState (StateT s m)), a #)) → StateT s m a Source #

PrimMonad m ⇒ PrimMonad (StateT s m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (StateT s m) Source #

Methods

primitive ∷ (State# (PrimState (StateT s m)) → (# State# (PrimState (StateT s m)), a #)) → StateT s m a Source #

(Monoid w, PrimMonad m) ⇒ PrimMonad (WriterT w m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (WriterT w m) Source #

Methods

primitive ∷ (State# (PrimState (WriterT w m)) → (# State# (PrimState (WriterT w m)), a #)) → WriterT w m a Source #

(Monoid w, PrimMonad m) ⇒ PrimMonad (WriterT w m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (WriterT w m) Source #

Methods

primitive ∷ (State# (PrimState (WriterT w m)) → (# State# (PrimState (WriterT w m)), a #)) → WriterT w m a Source #

(Monoid w, PrimMonad m) ⇒ PrimMonad (WriterT w m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (WriterT w m) Source #

Methods

primitive ∷ (State# (PrimState (WriterT w m)) → (# State# (PrimState (WriterT w m)), a #)) → WriterT w m a Source #

PrimMonad (CekM uni fun s) 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Associated Types

type PrimState (CekM uni fun s) Source #

Methods

primitive ∷ (State# (PrimState (CekM uni fun s)) → (# State# (PrimState (CekM uni fun s)), a #)) → CekM uni fun s a Source #

PrimMonad m ⇒ PrimMonad (ContT r m)

Since: primitive-0.6.3.0

Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (ContT r m) Source #

Methods

primitive ∷ (State# (PrimState (ContT r m)) → (# State# (PrimState (ContT r m)), a #)) → ContT r m a Source #

(Monoid w, PrimMonad m) ⇒ PrimMonad (RWST r w s m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (RWST r w s m) Source #

Methods

primitive ∷ (State# (PrimState (RWST r w s m)) → (# State# (PrimState (RWST r w s m)), a #)) → RWST r w s m a Source #

(Monoid w, PrimMonad m) ⇒ PrimMonad (RWST r w s m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (RWST r w s m) Source #

Methods

primitive ∷ (State# (PrimState (RWST r w s m)) → (# State# (PrimState (RWST r w s m)), a #)) → RWST r w s m a Source #

(Monoid w, PrimMonad m) ⇒ PrimMonad (RWST r w s m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (RWST r w s m) Source #

Methods

primitive ∷ (State# (PrimState (RWST r w s m)) → (# State# (PrimState (RWST r w s m)), a #)) → RWST r w s m a Source #

MonadTime

data DiffTime #

This is a length of time, as measured by a clock. Conversion functions such as fromInteger and realToFrac will treat it as seconds. For example, (0.010 :: DiffTime) corresponds to 10 milliseconds.

It has a precision of one picosecond (= 10^-12 s). Enumeration functions will treat it as picoseconds.

Instances

Instances details
Data DiffTime 
Instance details

Defined in Data.Time.Clock.Internal.DiffTime

Methods

gfoldl ∷ (∀ d b. Data d ⇒ c (d → b) → d → c b) → (∀ g. g → c g) → DiffTime → c DiffTime #

gunfold ∷ (∀ b r. Data b ⇒ c (b → r) → c r) → (∀ r. r → c r) → Constr → c DiffTime #

toConstrDiffTimeConstr #

dataTypeOfDiffTimeDataType #

dataCast1Typeable t ⇒ (∀ d. Data d ⇒ c (t d)) → Maybe (c DiffTime) #

dataCast2Typeable t ⇒ (∀ d e. (Data d, Data e) ⇒ c (t d e)) → Maybe (c DiffTime) #

gmapT ∷ (∀ b. Data b ⇒ b → b) → DiffTimeDiffTime #

gmapQl ∷ (r → r' → r) → r → (∀ d. Data d ⇒ d → r') → DiffTime → r #

gmapQr ∷ ∀ r r'. (r' → r → r) → r → (∀ d. Data d ⇒ d → r') → DiffTime → r #

gmapQ ∷ (∀ d. Data d ⇒ d → u) → DiffTime → [u] #

gmapQiInt → (∀ d. Data d ⇒ d → u) → DiffTime → u #

gmapMMonad m ⇒ (∀ d. Data d ⇒ d → m d) → DiffTime → m DiffTime #

gmapMpMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → DiffTime → m DiffTime #

gmapMoMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → DiffTime → m DiffTime #

Enum DiffTime 
Instance details

Defined in Data.Time.Clock.Internal.DiffTime

Num DiffTime 
Instance details

Defined in Data.Time.Clock.Internal.DiffTime

Read DiffTime 
Instance details

Defined in Data.Time.Clock.Internal.DiffTime

Fractional DiffTime 
Instance details

Defined in Data.Time.Clock.Internal.DiffTime

Real DiffTime 
Instance details

Defined in Data.Time.Clock.Internal.DiffTime

Methods

toRationalDiffTimeRational #

RealFrac DiffTime 
Instance details

Defined in Data.Time.Clock.Internal.DiffTime

Methods

properFractionIntegral b ⇒ DiffTime → (b, DiffTime) #

truncateIntegral b ⇒ DiffTime → b #

roundIntegral b ⇒ DiffTime → b #

ceilingIntegral b ⇒ DiffTime → b #

floorIntegral b ⇒ DiffTime → b #

Show DiffTime 
Instance details

Defined in Data.Time.Clock.Internal.DiffTime

Methods

showsPrecIntDiffTimeShowS #

showDiffTimeString #

showList ∷ [DiffTime] → ShowS #

NFData DiffTime 
Instance details

Defined in Data.Time.Clock.Internal.DiffTime

Methods

rnfDiffTime → () #

Eq DiffTime 
Instance details

Defined in Data.Time.Clock.Internal.DiffTime

Methods

(==)DiffTimeDiffTimeBool #

(/=)DiffTimeDiffTimeBool #

Ord DiffTime 
Instance details

Defined in Data.Time.Clock.Internal.DiffTime

NoThunks DiffTime 
Instance details

Defined in NoThunks.Class

class MonadMonotonicTimeNSec m ⇒ MonadMonotonicTime (m ∷ TypeType) where Source #

Minimal complete definition

Nothing

newtype Time Source #

A point in time in a monotonic clock.

The epoch for this clock is arbitrary and does not correspond to any wall clock or calendar, and is not guaranteed to be the same epoch across program runs. It is represented as the DiffTime from this arbitrary epoch.

Constructors

Time DiffTime 

Instances

Instances details
Generic Time 
Instance details

Defined in Control.Monad.Class.MonadTime.SI

Associated Types

type Rep TimeTypeType #

Methods

fromTimeRep Time x #

toRep Time x → Time #

Show Time 
Instance details

Defined in Control.Monad.Class.MonadTime.SI

Methods

showsPrecIntTimeShowS #

showTimeString #

showList ∷ [Time] → ShowS #

NFData Time 
Instance details

Defined in Control.Monad.Class.MonadTime.SI

Methods

rnfTime → () #

Eq Time 
Instance details

Defined in Control.Monad.Class.MonadTime.SI

Methods

(==)TimeTimeBool #

(/=)TimeTimeBool #

Ord Time 
Instance details

Defined in Control.Monad.Class.MonadTime.SI

Methods

compareTimeTimeOrdering #

(<)TimeTimeBool #

(<=)TimeTimeBool #

(>)TimeTimeBool #

(>=)TimeTimeBool #

maxTimeTimeTime #

minTimeTimeTime #

NoThunks Time 
Instance details

Defined in Control.Monad.Class.MonadTime.SI

Condense Time Source # 
Instance details

Defined in Ouroboros.Consensus.Util.Condense

Methods

condenseTimeString Source #

type Rep Time 
Instance details

Defined in Control.Monad.Class.MonadTime.SI

type Rep Time = D1 ('MetaData "Time" "Control.Monad.Class.MonadTime.SI" "si-timers-1.5.0.0-021a26bda509542e96f625ada4006d8f6e4805005d95ad81bf668f137fcea505" 'True) (C1 ('MetaCons "Time" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DiffTime)))

addTimeDiffTimeTimeTime infixr 9 Source #

Add a duration to a point in time, giving another time.

diffTimeTimeTimeDiffTime Source #

The time duration between two points in time (positive or negative).

MonadDelay

class (MonadDelay m, MonadMonotonicTime m) ⇒ MonadDelay (m ∷ TypeType) where Source #

Methods

threadDelayDiffTime → m () Source #

Instances

Instances details
MonadDelay IO

Thread delay. This implementation will not over- or underflow.

For delay larger than what Int can represent (see diffTimeToMicrosecondsAsInt), it will recursively call threadDelay.

For delays smaller than `minBound :: Int` seconds, `minBound :: Int` will be used instead.

Instance details

Defined in Control.Monad.Class.MonadTimer.SI

Methods

threadDelayDiffTimeIO () Source #

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

Defined in Ouroboros.Consensus.Util.EarlyExit

MonadDelay m ⇒ MonadDelay (ReaderT r m) 
Instance details

Defined in Control.Monad.Class.MonadTimer.SI

Methods

threadDelayDiffTimeReaderT r m () Source #

MonadEventlog

class Monad m ⇒ MonadEventlog (m ∷ TypeType) where Source #

Methods

traceEventIOString → m () Source #

Emits a message to the eventlog, if eventlog profiling is available and enabled at runtime.

traceMarkerIOString → m () Source #

Emits a marker to the eventlog, if eventlog profiling is available and enabled at runtime.

The String is the name of the marker. The name is just used in the profiling tools to help you keep clear which marker is which.

Instances

Instances details
MonadEventlog IO 
Instance details

Defined in Control.Monad.Class.MonadEventlog

Methods

traceEventIOStringIO () Source #

traceMarkerIOStringIO () Source #

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

Defined in Ouroboros.Consensus.Util.EarlyExit

MonadEventlog m ⇒ MonadEventlog (ReaderT r m) 
Instance details

Defined in Control.Monad.Class.MonadEventlog

Methods

traceEventIOStringReaderT r m () Source #

traceMarkerIOStringReaderT r m () Source #

MonadEvaluate

class MonadThrow m ⇒ MonadEvaluate (m ∷ TypeType) where Source #

Monads which can evaluate.

Methods

evaluate ∷ a → m a Source #

Instances

Instances details
MonadEvaluate IO 
Instance details

Defined in Control.Monad.Class.MonadThrow

Methods

evaluate ∷ a → IO a Source #

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

Defined in Ouroboros.Consensus.Util.EarlyExit

Methods

evaluate ∷ a → WithEarlyExit m a Source #

MonadEvaluate m ⇒ MonadEvaluate (ReaderT r m) 
Instance details

Defined in Control.Monad.Class.MonadThrow

Methods

evaluate ∷ a → ReaderT r m a Source #

NoThunks

class NoThunks a where Source #

Check a value for unexpected thunks

Minimal complete definition

Nothing

Methods

noThunksContext → a → IO (Maybe ThunkInfo) Source #

Check if the argument does not contain any unexpected thunks

For most datatypes, we should have that

noThunks ctxt x == Nothing

if and only if

checkContainsThunks x

For some datatypes however, some thunks are expected. For example, the internal fingertree Sequence might contain thunks (this is important for the asymptotic complexity of this data structure). However, we should still check that the values in the sequence don't contain any unexpected thunks.

This means that we need to traverse the sequence, which might force some of the thunks in the tree. In general, it is acceptable for noThunks to force such "expected thunks", as long as it always reports the unexpected thunks.

The default implementation of noThunks checks that the argument is in WHNF, and if so, adds the type into the context (using showTypeOf or whereFrom if available), and calls wNoThunks. See ThunkInfo for a detailed discussion of the type context.

See also discussion of caveats listed for checkContainsThunks.

wNoThunksContext → a → IO (Maybe ThunkInfo) Source #

Check that the argument is in normal form, assuming it is in WHNF.

The context will already have been extended with the type we're looking at, so all that's left is to look at the thunks inside the type. The default implementation uses GHC Generics to do this.

showTypeOfProxy a → String Source #

Show type a (to add to the context)

We try hard to avoid Typeable constraints in this module: there are types with no Typeable instance but with a NoThunks instance (most important example are types such as ST s which rely on parametric polymorphism). By default we should therefore only show the "outer layer"; for example, if we have a type

Seq (ST s ())

then showTypeOf should just give Seq, leaving it up to the instance for ST to decide how to implement showTypeOf; this keeps things compositional. The default implementation does precisely this using the metadata that GHC Generics provides.

For convenience, however, some of the deriving via newtype wrappers we provide do depend on Typeable; see below.

Instances

Instances details
NoThunks All 
Instance details

Defined in NoThunks.Class

NoThunks Any 
Instance details

Defined in NoThunks.Class

NoThunks Void 
Instance details

Defined in NoThunks.Class

NoThunks ThreadId 
Instance details

Defined in NoThunks.Class

NoThunks Int16 
Instance details

Defined in NoThunks.Class

NoThunks Int32 
Instance details

Defined in NoThunks.Class

NoThunks Int64 
Instance details

Defined in NoThunks.Class

NoThunks Int8 
Instance details

Defined in NoThunks.Class

NoThunks CallStack

Since CallStacks can't retain application data, we don't want to check them for thunks at all

Instance details

Defined in NoThunks.Class

NoThunks Word16 
Instance details

Defined in NoThunks.Class

NoThunks Word32 
Instance details

Defined in NoThunks.Class

NoThunks Word64 
Instance details

Defined in NoThunks.Class

NoThunks Word8 
Instance details

Defined in NoThunks.Class

NoThunks ByteString

Instance for string bytestrings

Strict bytestrings shouldn't contain any thunks, but could, due to https://gitlab.haskell.org/ghc/ghc/issues/17290. However, such thunks can't retain any data that they shouldn't, and so it's safe to ignore such thunks.

Instance details

Defined in NoThunks.Class

NoThunks ByteString

Instance for lazy bytestrings

Defined manually so that it piggy-backs on the one for strict bytestrings.

Instance details

Defined in NoThunks.Class

NoThunks ShortByteString

Instance for short bytestrings

We have

data ShortByteString = SBS ByteArray#

Values of this type consist of a tag followed by an _unboxed_ byte array, which can't contain thunks. Therefore we only check WHNF.

Instance details

Defined in NoThunks.Class

NoThunks Seed 
Instance details

Defined in Cardano.Crypto.Seed

NoThunks Point 
Instance details

Defined in Cardano.Crypto.VRF.Simple

Methods

noThunksContext → Point → IO (Maybe ThunkInfo) Source #

wNoThunksContext → Point → IO (Maybe ThunkInfo) Source #

showTypeOfProxy Point → String Source #

NoThunks Output 
Instance details

Defined in Cardano.Crypto.VRF.Praos

NoThunks Proof 
Instance details

Defined in Cardano.Crypto.VRF.Praos

NoThunks Seed 
Instance details

Defined in Cardano.Crypto.VRF.Praos

NoThunks SignKey 
Instance details

Defined in Cardano.Crypto.VRF.Praos

NoThunks VerKey 
Instance details

Defined in Cardano.Crypto.VRF.Praos

NoThunks Output 
Instance details

Defined in Cardano.Crypto.VRF.PraosBatchCompat

Methods

noThunksContext → Output → IO (Maybe ThunkInfo) Source #

wNoThunksContext → Output → IO (Maybe ThunkInfo) Source #

showTypeOfProxy Output → String Source #

NoThunks Proof 
Instance details

Defined in Cardano.Crypto.VRF.PraosBatchCompat

Methods

noThunksContext → Proof → IO (Maybe ThunkInfo) Source #

wNoThunksContext → Proof → IO (Maybe ThunkInfo) Source #

showTypeOfProxy Proof → String Source #

NoThunks Seed 
Instance details

Defined in Cardano.Crypto.VRF.PraosBatchCompat

NoThunks SignKey 
Instance details

Defined in Cardano.Crypto.VRF.PraosBatchCompat

Methods

noThunksContext → SignKey → IO (Maybe ThunkInfo) Source #

wNoThunksContext → SignKey → IO (Maybe ThunkInfo) Source #

showTypeOfProxy SignKey → String Source #

NoThunks VerKey 
Instance details

Defined in Cardano.Crypto.VRF.PraosBatchCompat

Methods

noThunksContext → VerKey → IO (Maybe ThunkInfo) Source #

wNoThunksContext → VerKey → IO (Maybe ThunkInfo) Source #

showTypeOfProxy VerKey → String Source #

NoThunks BlockNo 
Instance details

Defined in Cardano.Slotting.Block

NoThunks EpochInterval 
Instance details

Defined in Cardano.Slotting.Slot

NoThunks EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

NoThunks EpochSize 
Instance details

Defined in Cardano.Slotting.Slot

NoThunks SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

NoThunks RelativeTime 
Instance details

Defined in Cardano.Slotting.Time

NoThunks SlotLength 
Instance details

Defined in Cardano.Slotting.Time

NoThunks SystemStart 
Instance details

Defined in Cardano.Slotting.Time

NoThunks FsPath Source # 
Instance details

Defined in Ouroboros.Consensus.Util.Orphans

NoThunks CRC Source # 
Instance details

Defined in Ouroboros.Consensus.Util.Orphans

NoThunks GenesisWindow Source # 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

NoThunks IsEBB Source # 
Instance details

Defined in Ouroboros.Consensus.Block.EBB

NoThunks CurrentSlot Source # 
Instance details

Defined in Ouroboros.Consensus.BlockchainTime.API

NoThunks SecurityParam Source # 
Instance details

Defined in Ouroboros.Consensus.Config.SecurityParam

NoThunks Past Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Types

NoThunks TransitionInfo Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Types

NoThunks EraParams Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.History.EraParams