ouroboros-consensus-0.18.0.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 MuxError 
Instance details

Defined in Network.Mux.Trace

Exception MuxRuntimeError 
Instance details

Defined in Network.Mux.Types

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 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

(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

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 Monad m ⇒ MonadST (m ∷ TypeType) where Source #

This class is for abstracting over MonadST 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 MonadST 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.

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 MonadST 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 (WithEarlyExit m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

Associated Types

type PrimState (WithEarlyExit m) 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 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.4.0.0-362fdd0f42a294bc50d5506eb4f5df4c0b16c6b0ef95ea7d123b4769598e451e" '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), 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 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 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

NoThunks SafeZone Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.History.EraParams

NoThunks Bound Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.History.Summary

NoThunks EraEnd Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.History.Summary

NoThunks EraSummary Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.History.Summary

NoThunks TriggerHardFork Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Simple

NoThunks MempoolCapacityBytes Source # 
Instance details

Defined in Ouroboros.Consensus.Mempool.Capacity

NoThunks TicketNo Source # 
Instance details

Defined in Ouroboros.Consensus.Mempool.TxSeq

NoThunks NumCoreNodes Source # 
Instance details

Defined in Ouroboros.Consensus.Node.ProtocolInfo

NoThunks CoreNodeId Source # 
Instance details

Defined in Ouroboros.Consensus.NodeId

NoThunks NodeId Source # 
Instance details

Defined in Ouroboros.Consensus.NodeId

NoThunks BftParams Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.BFT

NoThunks BftValidationErr Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.BFT

NoThunks LeaderSchedule Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.LeaderSchedule

NoThunks PBftParams Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

NoThunks PBftSelectView Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

NoThunks PBftSignatureThreshold Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

NoThunks PBftMockVerKeyHash Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT.Crypto

NoThunks ScheduledGc Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Background

NoThunks FollowerKey Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types

NoThunks IteratorKey Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types

NoThunks PrefixLen Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.Common

NoThunks ChunkInfo Source # 
Instance details

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

NoThunks ChunkNo Source # 
Instance details

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

NoThunks ChunkSize Source # 
Instance details

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

NoThunks RelativeSlot Source # 
Instance details

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

NoThunks ChunkSlot Source # 
Instance details

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

NoThunks PrimaryIndex Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Index.Primary

NoThunks BlockOffset Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Index.Secondary

NoThunks BlockSize Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Index.Secondary

NoThunks HeaderOffset Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Index.Secondary

NoThunks HeaderSize Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Index.Secondary

NoThunks BlockOrEBB Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Types

NoThunks DiskPolicy Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.DiskPolicy

NoThunks BlockOffset Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Types

NoThunks BlockSize Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Types

NoThunks PrettyCallStack Source # 
Instance details

Defined in Ouroboros.Consensus.Util.CallStack

NoThunks Fingerprint Source # 
Instance details

Defined in Ouroboros.Consensus.Util.STM

NoThunks MaxSlotNo 
Instance details

Defined in Ouroboros.Network.Block

NoThunks NetworkMagic 
Instance details

Defined in Ouroboros.Network.Magic

NoThunks AfterSlot 
Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type

NoThunks LedgerStateJudgement 
Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type

NoThunks UseLedgerPeers 
Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type

NoThunks SizeInBytes 
Instance details

Defined in Ouroboros.Network.SizeInBytes

NoThunks Time 
Instance details

Defined in Control.Monad.Class.MonadTime.SI

NoThunks Text 
Instance details

Defined in NoThunks.Class

NoThunks Text 
Instance details

Defined in NoThunks.Class

NoThunks Day 
Instance details

Defined in NoThunks.Class

NoThunks DiffTime 
Instance details

Defined in NoThunks.Class

NoThunks NominalDiffTime 
Instance details

Defined in NoThunks.Class

NoThunks UTCTime 
Instance details

Defined in NoThunks.Class

NoThunks UniversalTime 
Instance details

Defined in NoThunks.Class

NoThunks TimeLocale 
Instance details

Defined in NoThunks.Class

NoThunks LocalTime 
Instance details

Defined in NoThunks.Class

NoThunks TimeOfDay 
Instance details

Defined in NoThunks.Class

NoThunks TimeZone 
Instance details

Defined in NoThunks.Class

NoThunks ZonedTime 
Instance details

Defined in NoThunks.Class

NoThunks Integer 
Instance details

Defined in NoThunks.Class

NoThunks Natural 
Instance details

Defined in NoThunks.Class

NoThunks () 
Instance details

Defined in NoThunks.Class

NoThunks Bool 
Instance details

Defined in NoThunks.Class

NoThunks Char 
Instance details

Defined in NoThunks.Class

NoThunks Double 
Instance details

Defined in NoThunks.Class

NoThunks Float 
Instance details

Defined in NoThunks.Class

NoThunks Int 
Instance details

Defined in NoThunks.Class

NoThunks Word 
Instance details

Defined in NoThunks.Class

NoThunks a ⇒ NoThunks (Identity a) 
Instance details

Defined in NoThunks.Class

NoThunks a ⇒ NoThunks (Sum a) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.Orphans

NoThunks a ⇒ NoThunks (NonEmpty a) 
Instance details

Defined in NoThunks.Class

NoThunks a ⇒ NoThunks (TVar a) 
Instance details

Defined in NoThunks.Class

NoThunks a ⇒ NoThunks (IORef a) 
Instance details

Defined in NoThunks.Class

NoThunks a ⇒ NoThunks (MVar a) 
Instance details

Defined in NoThunks.Class

NoThunks a ⇒ NoThunks (Ratio a) 
Instance details

Defined in NoThunks.Class

NoThunks (SigDSIGN EcdsaSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.EcdsaSecp256k1

NoThunks (SigDSIGN Ed25519DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed25519

NoThunks (SigDSIGN Ed448DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed448

NoThunks (SigDSIGN MockDSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Mock

NoThunks (SigDSIGN NeverDSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.NeverUsed

NoThunks (SigDSIGN SchnorrSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.SchnorrSecp256k1

NoThunks (SignKeyDSIGN EcdsaSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.EcdsaSecp256k1

NoThunks (SignKeyDSIGN Ed25519DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed25519

NoThunks (SignKeyDSIGN Ed448DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed448

NoThunks (SignKeyDSIGN MockDSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Mock

NoThunks (SignKeyDSIGN NeverDSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.NeverUsed

NoThunks (SignKeyDSIGN SchnorrSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.SchnorrSecp256k1

NoThunks (VerKeyDSIGN EcdsaSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.EcdsaSecp256k1

NoThunks (VerKeyDSIGN Ed25519DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed25519

NoThunks (VerKeyDSIGN Ed448DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed448

NoThunks (VerKeyDSIGN MockDSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Mock

NoThunks (VerKeyDSIGN NeverDSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.NeverUsed

NoThunks (VerKeyDSIGN SchnorrSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.SchnorrSecp256k1

DSIGNAlgorithm d ⇒ NoThunks (SigKES (CompactSingleKES d)) 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

KESAlgorithm d ⇒ NoThunks (SigKES (CompactSumKES h d)) 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

NoThunks (SigKES (MockKES t)) 
Instance details

Defined in Cardano.Crypto.KES.Mock

NoThunks (SigKES NeverKES) 
Instance details

Defined in Cardano.Crypto.KES.NeverUsed

DSIGNAlgorithm d ⇒ NoThunks (SigKES (SimpleKES d t)) 
Instance details

Defined in Cardano.Crypto.KES.Simple

DSIGNAlgorithm d ⇒ NoThunks (SigKES (SingleKES d)) 
Instance details

Defined in Cardano.Crypto.KES.Single

KESAlgorithm d ⇒ NoThunks (SigKES (SumKES h d)) 
Instance details

Defined in Cardano.Crypto.KES.Sum

DSIGNAlgorithm d ⇒ NoThunks (SignKeyKES (CompactSingleKES d)) 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

KESAlgorithm d ⇒ NoThunks (SignKeyKES (CompactSumKES h d)) 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

NoThunks (SignKeyKES (MockKES t)) 
Instance details

Defined in Cardano.Crypto.KES.Mock

NoThunks (SignKeyKES NeverKES) 
Instance details

Defined in Cardano.Crypto.KES.NeverUsed

DSIGNAlgorithm d ⇒ NoThunks (SignKeyKES (SimpleKES d t)) 
Instance details

Defined in Cardano.Crypto.KES.Simple

DSIGNAlgorithm d ⇒ NoThunks (SignKeyKES (SingleKES d)) 
Instance details

Defined in Cardano.Crypto.KES.Single

KESAlgorithm d ⇒ NoThunks (SignKeyKES (SumKES h d)) 
Instance details

Defined in Cardano.Crypto.KES.Sum

DSIGNAlgorithm d ⇒ NoThunks (VerKeyKES (CompactSingleKES d)) 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

OptimizedKESAlgorithm d ⇒ NoThunks (VerKeyKES (CompactSumKES h d)) 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

NoThunks (VerKeyKES (MockKES t)) 
Instance details

Defined in Cardano.Crypto.KES.Mock

NoThunks (VerKeyKES NeverKES) 
Instance details

Defined in Cardano.Crypto.KES.NeverUsed

DSIGNAlgorithm d ⇒ NoThunks (VerKeyKES (SimpleKES d t)) 
Instance details

Defined in Cardano.Crypto.KES.Simple

DSIGNAlgorithm d ⇒ NoThunks (VerKeyKES (SingleKES d)) 
Instance details

Defined in Cardano.Crypto.KES.Single

KESAlgorithm d ⇒ NoThunks (VerKeyKES (SumKES h d)) 
Instance details

Defined in Cardano.Crypto.KES.Sum

NoThunks (PackedBytes n) 
Instance details

Defined in Cardano.Crypto.PackedBytes

NoThunks (PinnedSizedBytes n) 
Instance details

Defined in Cardano.Crypto.PinnedSizedBytes

NoThunks (EpochInfo m) 
Instance details

Defined in Cardano.Slotting.EpochInfo.API

NoThunks t ⇒ NoThunks (WithOrigin t) 
Instance details

Defined in Cardano.Slotting.Slot

NoThunks a ⇒ NoThunks (StrictMaybe a) 
Instance details

Defined in Data.Maybe.Strict

NoThunks a ⇒ NoThunks (StrictSeq a)

Instance for StrictSeq checks elements only

The internal fingertree in Seq might have thunks, which is essential for its asymptotic complexity.

Instance details

Defined in Data.Sequence.Strict

NoThunks a ⇒ NoThunks (IntMap a) 
Instance details

Defined in NoThunks.Class

NoThunks a ⇒ NoThunks (Seq a)

Instance for Seq checks elements only

The internal fingertree in Seq might have thunks, which is essential for its asymptotic complexity.

Instance details

Defined in NoThunks.Class

NoThunks a ⇒ NoThunks (Set a) 
Instance details

Defined in NoThunks.Class

NoThunks (SomeHasFS m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.Orphans

NoThunks (Handle h) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.Orphans

NoThunks (IO a)

We do not check IO actions for captured thunks by default

See instance for (a -> b) for detailed discussion.

Instance details

Defined in NoThunks.Class

NoThunks (AllowThunk a) 
Instance details

Defined in NoThunks.Class

Typeable a ⇒ NoThunks (InspectHeap a) 
Instance details

Defined in NoThunks.Class

Typeable a ⇒ NoThunks (OnlyCheckWhnf a) 
Instance details

Defined in NoThunks.Class

CanHardFork xs ⇒ NoThunks (BlockConfig (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

NoThunks (BlockConfig (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

CanHardFork xs ⇒ NoThunks (CodecConfig (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

(NoThunks (CodecConfig m), NoThunks (CodecConfig a)) ⇒ NoThunks (CodecConfig (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

CanHardFork xs ⇒ NoThunks (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

NoThunks (Header (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

CanHardFork xs ⇒ NoThunks (StorageConfig (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

(NoThunks (StorageConfig m), NoThunks (StorageConfig a)) ⇒ NoThunks (StorageConfig (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

(StandardHash blk, Typeable blk) ⇒ NoThunks (RealPoint blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.RealPoint

ConsensusProtocol proto ⇒ NoThunks (SelectViewTentativeState proto) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

NoThunks (BlockchainTime m) Source # 
Instance details

Defined in Ouroboros.Consensus.BlockchainTime.API

NoThunks (SystemTime m) Source # 
Instance details

Defined in Ouroboros.Consensus.BlockchainTime.WallClock.Types

NoThunks (HeaderHash blk) ⇒ NoThunks (CheckpointsMap blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Config

(ConsensusProtocol (BlockProtocol blk), NoThunks (LedgerConfig blk), NoThunks (BlockConfig blk), NoThunks (CodecConfig blk), NoThunks (StorageConfig blk), NoThunks (HeaderHash blk)) ⇒ NoThunks (TopLevelConfig blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Config

CanHardFork xs ⇒ NoThunks (MismatchEraInfo xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

CanHardFork xs ⇒ NoThunks (OneEraEnvelopeErr xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

CanHardFork xs ⇒ NoThunks (OneEraGenTx xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

CanHardFork xs ⇒ NoThunks (OneEraGenTxId xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

CanHardFork xs ⇒ NoThunks (OneEraHeader xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

CanHardFork xs ⇒ NoThunks (OneEraLedgerError xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

CanHardFork xs ⇒ NoThunks (OneEraSelectView xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

CanHardFork xs ⇒ NoThunks (OneEraTentativeHeaderState xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

CanHardFork xs ⇒ NoThunks (OneEraTipInfo xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

CanHardFork xs ⇒ NoThunks (OneEraValidatedGenTx xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

CanHardFork xs ⇒ NoThunks (OneEraValidationErr xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

CanHardFork xs ⇒ NoThunks (PerEraBlockConfig xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

CanHardFork xs ⇒ NoThunks (PerEraCodecConfig xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

CanHardFork xs ⇒ NoThunks (PerEraConsensusConfig xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

CanHardFork xs ⇒ NoThunks (PerEraLedgerConfig xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

CanHardFork xs ⇒ NoThunks (PerEraStorageConfig xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

CanHardFork xs ⇒ NoThunks (HardForkLedgerConfig xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

NoThunks (LedgerEraInfo blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Info

NoThunks (SingleEraInfo blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Info

CanHardFork xs ⇒ NoThunks (HardForkEnvelopeErr xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

CanHardFork xs ⇒ NoThunks (HardForkLedgerError xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

NoThunks (PartialConsensusConfig (BlockProtocol blk)) ⇒ NoThunks (WrapPartialConsensusConfig blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.PartialConfig

NoThunks (PartialLedgerConfig blk) ⇒ NoThunks (WrapPartialLedgerConfig blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.PartialConfig

CanHardFork xs ⇒ NoThunks (HardForkSelectView xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

CanHardFork xs ⇒ NoThunks (HardForkValidationErr xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

NoThunks (EraTranslation xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Translation

NoThunks (Shape xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.History.Summary

NoThunks (Summary xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.History.Summary

(BlockSupportsProtocol blk, HasAnnTip blk) ⇒ NoThunks (HeaderStateHistory blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderStateHistory

HasAnnTip blk ⇒ NoThunks (AnnTip blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

ValidateEnvelope blk ⇒ NoThunks (HeaderEnvelopeError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

(BlockSupportsProtocol blk, ValidateEnvelope blk) ⇒ NoThunks (HeaderError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

(BlockSupportsProtocol blk, HasAnnTip blk) ⇒ NoThunks (HeaderState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

StandardHash blk ⇒ NoThunks (TipInfoIsEBB blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

CanHardFork xs ⇒ NoThunks (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

NoThunks (Validated (GenTx (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

CanHardFork xs ⇒ NoThunks (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

NoThunks (LedgerState (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

(ConsensusProtocol (BlockProtocol blk), NoThunks (BlockConfig blk), NoThunks (CodecConfig blk), NoThunks (LedgerConfig blk), NoThunks (StorageConfig blk), NoThunks (HeaderHash blk)) ⇒ NoThunks (ExtLedgerCfg blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

LedgerSupportsProtocol blk ⇒ NoThunks (ExtLedgerState blk) Source #

We override showTypeOf to show the type of the block

This makes debugging a bit easier, as the block gets used to resolve all kinds of type families.

Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

LedgerSupportsProtocol blk ⇒ NoThunks (ExtValidationError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

CanHardFork xs ⇒ NoThunks (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

NoThunks (GenTx (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

CanHardFork xs ⇒ NoThunks (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

NoThunks (TxId (GenTx (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

(NoThunks (Validated (GenTx blk)), NoThunks (GenTxId blk), NoThunks (Ticked (LedgerState blk)), StandardHash blk, Typeable blk) ⇒ NoThunks (InternalState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Mempool.Impl.Common

NoThunks tx ⇒ NoThunks (TxSeq tx) Source # 
Instance details

Defined in Ouroboros.Consensus.Mempool.TxSeq

NoThunks tx ⇒ NoThunks (TxTicket tx) Source # 
Instance details

Defined in Ouroboros.Consensus.Mempool.TxSeq

(HasHeader blk, NoThunks (Header blk)) ⇒ NoThunks (ChainSyncState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client

NoThunks a ⇒ NoThunks (Our a) Source # 
Instance details

Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client

NoThunks a ⇒ NoThunks (Their a) Source # 
Instance details

Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client

CanHardFork xs ⇒ NoThunks (ConsensusConfig (HardForkProtocol xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

BftCrypto c ⇒ NoThunks (ConsensusConfig (Bft c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.BFT

ConsensusProtocol p ⇒ NoThunks (ConsensusConfig (ModChainSel p s)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.ModChainSel

NoThunks (ConsensusConfig (PBft c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

PBftCrypto c ⇒ NoThunks (PBftCanBeLeader c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

PBftCrypto c ⇒ NoThunks (PBftCannotForge c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

PBftCrypto c ⇒ NoThunks (PBftIsLeader c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

PBftCrypto c ⇒ NoThunks (PBftLedgerView c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

PBftCrypto c ⇒ NoThunks (PBftValidationErr c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

PBftCrypto c ⇒ NoThunks (PBftSigner c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT.State

PBftCrypto c ⇒ NoThunks (PBftState c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT.State

LedgerSupportsProtocol blk ⇒ NoThunks (InvalidBlockReason blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.API

NoThunks a ⇒ NoThunks (LoE a) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.API

NoThunks (InvalidBlockPunishment m) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.API.Types.InvalidBlockPunishment

StandardHash blk ⇒ NoThunks (FollowerRollState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types

LedgerSupportsProtocol blk ⇒ NoThunks (InvalidBlockInfo blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types

(StandardHash blk, Typeable blk) ⇒ NoThunks (StreamFrom blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.Common

(StandardHash blk, Typeable blk) ⇒ NoThunks (StreamTo blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.Common

StandardHash blk ⇒ NoThunks (Tip blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

Methods

noThunksContextTip blk → IO (Maybe ThunkInfo) Source #

wNoThunksContextTip blk → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (Tip blk) → String Source #

StandardHash blk ⇒ NoThunks (Entry blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Index.Secondary

NoThunks a ⇒ NoThunks (WithBlockSize a) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Types

NoThunks l ⇒ NoThunks (Checkpoint l) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.LedgerDB

NoThunks l ⇒ NoThunks (LedgerDB l) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.LedgerDB

NoThunks (LedgerCfg l) ⇒ NoThunks (LedgerDbCfg l) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.LedgerDB

(StandardHash blk, Typeable blk) ⇒ NoThunks (BlockInfo blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.API

StandardHash blk ⇒ NoThunks (FileInfo blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.FileInfo

StandardHash blk ⇒ NoThunks (Index blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Index

(StandardHash blk, Typeable blk) ⇒ NoThunks (InternalBlockInfo blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Types

CanHardFork xs ⇒ NoThunks (Ticked (LedgerState (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

NoThunks (Ticked (LedgerState (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

NoThunks (ChainDepState (BlockProtocol blk)) ⇒ NoThunks (WrapChainDepState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

NoThunks (OtherHeaderEnvelopeError blk) ⇒ NoThunks (WrapEnvelopeErr blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

NoThunks (GenTxId blk) ⇒ NoThunks (WrapGenTxId blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

NoThunks (LedgerError blk) ⇒ NoThunks (WrapLedgerErr blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

NoThunks (SelectView (BlockProtocol blk)) ⇒ NoThunks (WrapSelectView blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

NoThunks (TentativeHeaderState blk) ⇒ NoThunks (WrapTentativeHeaderState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

NoThunks (TipInfo blk) ⇒ NoThunks (WrapTipInfo blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

NoThunks (Validated (GenTx blk)) ⇒ NoThunks (WrapValidatedGenTx blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

NoThunks (ValidationErr (BlockProtocol blk)) ⇒ NoThunks (WrapValidationErr blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

NoThunks (StrictMVar m ()) ⇒ NoThunks (Fuse m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util

NoThunks (m ()) ⇒ NoThunks (Config m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.LeakyBucket

NoThunks cfg ⇒ NoThunks (State cfg) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.LeakyBucket

IOLike m ⇒ NoThunks (ResourceKey m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.ResourceRegistry

IOLike m ⇒ NoThunks (ResourceRegistry m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.ResourceRegistry

NoThunks a ⇒ NoThunks (WithFingerprint a) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.STM

StandardHash block ⇒ NoThunks (Anchor block) 
Instance details

Defined in Ouroboros.Network.AnchoredFragment

Methods

noThunksContextAnchor block → IO (Maybe ThunkInfo) Source #

wNoThunksContextAnchor block → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (Anchor block) → String Source #

NoThunks a ⇒ NoThunks (Vector a) 
Instance details

Defined in NoThunks.Class

NoThunks (Vector a)

Unboxed vectors can't contain thunks

Implementation note: defined manually rather than using OnlyCheckWhnf due to ghc limitation in deriving via, making it impossible to use with it with data families.

Instance details

Defined in NoThunks.Class

NoThunks a ⇒ NoThunks (Maybe a) 
Instance details

Defined in NoThunks.Class

NoThunks a ⇒ NoThunks [a] 
Instance details

Defined in NoThunks.Class

Methods

noThunksContext → [a] → IO (Maybe ThunkInfo) Source #

wNoThunksContext → [a] → IO (Maybe ThunkInfo) Source #

showTypeOfProxy [a] → String Source #

(NoThunks a, NoThunks b) ⇒ NoThunks (Either a b) 
Instance details

Defined in NoThunks.Class

(NoThunks k, NoThunks v) ⇒ NoThunks (Bimap k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.Orphans

DSIGNAlgorithm v ⇒ NoThunks (SignedDSIGN v a) 
Instance details

Defined in Cardano.Crypto.DSIGN.Class

NoThunks (Hash h a) 
Instance details

Defined in Cardano.Crypto.Hash.Class

KESAlgorithm v ⇒ NoThunks (SignedKES v a) 
Instance details

Defined in Cardano.Crypto.KES.Class

NoThunks a ⇒ NoThunks (StrictFingerTree v a) 
Instance details

Defined in Data.FingerTree.Strict

NoThunks (Decoder s a) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.Orphans

(NoThunks k, NoThunks v) ⇒ NoThunks (Map k v) 
Instance details

Defined in NoThunks.Class

Methods

noThunksContextMap k v → IO (Maybe ThunkInfo) Source #

wNoThunksContextMap k v → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (Map k v) → String Source #

NoThunks (Tracer m ev) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.Orphans

(HasFields s a, Generic a, Typeable a, GWNoThunks s (Rep a)) ⇒ NoThunks (AllowThunksIn s a) 
Instance details

Defined in NoThunks.Class

KnownSymbol name ⇒ NoThunks (InspectHeapNamed name a) 
Instance details

Defined in NoThunks.Class

KnownSymbol name ⇒ NoThunks (OnlyCheckWhnfNamed name a) 
Instance details

Defined in NoThunks.Class

NoThunks (CheckInFuture m blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Fragment.InFuture

NoThunks (UpdateLoEFrag m blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Genesis.Governor

NoThunks (OneEraHash xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

NoThunks (f blk) ⇒ NoThunks (Current f blk) Source # 
Instance details

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

(All SingleEraBlock xs, ∀ blk. SingleEraBlock blk ⇒ NoThunks (f blk)) ⇒ NoThunks (HardForkState f xs) Source # 
Instance details

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

NoThunks (DualLedgerConfig m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

NoThunks (DualLedgerError m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

(IOLike m, HasHeader blk, NoThunks (Header blk)) ⇒ NoThunks (ChainSyncClientHandle m blk) Source # 
Instance details

Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client

(IOLike m, HasHeader blk, NoThunks (Header blk)) ⇒ NoThunks (ChainSyncStateView m blk) Source # 
Instance details

Defined in Ouroboros.Consensus.MiniProtocol.ChainSync.Client

(BftCrypto c, Typeable toSign) ⇒ NoThunks (BftFields c toSign) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.BFT

Methods

noThunksContextBftFields c toSign → IO (Maybe ThunkInfo) Source #

wNoThunksContextBftFields c toSign → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (BftFields c toSign) → String Source #

(PBftCrypto c, Typeable toSign) ⇒ NoThunks (PBftFields c toSign) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Methods

noThunksContextPBftFields c toSign → IO (Maybe ThunkInfo) Source #

wNoThunksContextPBftFields c toSign → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (PBftFields c toSign) → String Source #

(IOLike m, LedgerSupportsProtocol blk) ⇒ NoThunks (LgrDB m blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.LgrDB

Methods

noThunksContextLgrDB m blk → IO (Maybe ThunkInfo) Source #

wNoThunksContextLgrDB m blk → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (LgrDB m blk) → String Source #

(IOLike m, LedgerSupportsProtocol blk, BlockSupportsDiffusionPipelining blk) ⇒ NoThunks (ChainDbEnv m blk) Source #

We include blk in showTypeOf because it helps resolving type families (but avoid including m because we cannot impose Typeable m as a constraint and still have it work with the simulator)

Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types

(IOLike m, LedgerSupportsProtocol blk, BlockSupportsDiffusionPipelining blk) ⇒ NoThunks (ChainDbState m blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types

NoThunks (ChainSelQueue m blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types

NoThunks (FollowerHandle m blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types

NoThunks (ImmutableDB m blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

NoThunks (VolatileDB m blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.API

(StandardHash blk, Typeable blk) ⇒ NoThunks (InternalState blk h) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.State

(StandardHash blk, Typeable blk) ⇒ NoThunks (OpenState blk h) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.State

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

Defined in Ouroboros.Consensus.Util.EarlyExit

(IOLike m, NoThunks st) ⇒ NoThunks (RAWLock m st) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.MonadSTM.RAWLock

NoThunks a ⇒ NoThunks (StrictSVar IO a) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.MonadSTM.StrictSVar

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

Defined in Ouroboros.Consensus.Util.EarlyExit

NoThunks (Thread m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.ResourceRegistry

(StandardHash block, Typeable block) ⇒ NoThunks (ChainHash block) 
Instance details

Defined in Ouroboros.Network.Block

StandardHash block ⇒ NoThunks (Point block) 
Instance details

Defined in Ouroboros.Network.Block

Methods

noThunksContextPoint block → IO (Maybe ThunkInfo) Source #

wNoThunksContextPoint block → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (Point block) → String Source #

StandardHash b ⇒ NoThunks (Tip b) 
Instance details

Defined in Ouroboros.Network.Block

(NoThunks slot, NoThunks hash) ⇒ NoThunks (Block slot hash) 
Instance details

Defined in Ouroboros.Network.Point

Methods

noThunksContextBlock slot hash → IO (Maybe ThunkInfo) Source #

wNoThunksContextBlock slot hash → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (Block slot hash) → String Source #

(NoThunks p, NoThunks v, Ord p) ⇒ NoThunks (IntPSQ p v) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.Orphans

NoThunks a ⇒ NoThunks (StrictMVar IO a) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.NormalForm.StrictMVar

NoThunks a ⇒ NoThunks (StrictTVar IO a) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.NormalForm.StrictTVar

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

Defined in Ouroboros.Consensus.Util.EarlyExit

(NoThunks a, NoThunks b) ⇒ NoThunks (a, b) 
Instance details

Defined in NoThunks.Class

Methods

noThunksContext → (a, b) → IO (Maybe ThunkInfo) Source #

wNoThunksContext → (a, b) → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (a, b) → String Source #

NoThunks (a → b)

We do NOT check function closures for captured thunks by default

Since we have no type information about the values captured in a thunk, the only check we could possibly do is checkContainsThunks: we can't recursively call noThunks on those captured values, which is problematic if any of those captured values requires a custom instance (for example, data types that depend on laziness, such as Seq).

By default we therefore only check if the function is in WHNF, and don't check the captured values at all. If you want a stronger check, you can use InspectHeap (a -> b) instead.

Instance details

Defined in NoThunks.Class

Methods

noThunksContext → (a → b) → IO (Maybe ThunkInfo) Source #

wNoThunksContext → (a → b) → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (a → b) → String Source #

(All SingleEraBlock xs, ∀ x. SingleEraBlock x ⇒ NoThunks (f x), KnownSymbol name) ⇒ NoThunks (LiftNamedNP name f xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Lifting

Methods

noThunksContextLiftNamedNP name f xs → IO (Maybe ThunkInfo) Source #

wNoThunksContextLiftNamedNP name f xs → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (LiftNamedNP name f xs) → String Source #

(All SingleEraBlock xs, ∀ x. SingleEraBlock x ⇒ NoThunks (f x), KnownSymbol name) ⇒ NoThunks (LiftNamedNS name f xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Lifting

Methods

noThunksContextLiftNamedNS name f xs → IO (Maybe ThunkInfo) Source #

wNoThunksContextLiftNamedNS name f xs → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (LiftNamedNS name f xs) → String Source #

NoThunks (f a) ⇒ NoThunks (WithBlockNo f a) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol.ChainSel

StandardHash blk ⇒ NoThunks (FollowerState m blk b) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.Impl.Types

NoThunks (Iterator m blk b) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

Methods

noThunksContextIterator m blk b → IO (Maybe ThunkInfo) Source #

wNoThunksContextIterator m blk b → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (Iterator m blk b) → String Source #

NoThunks (Index m blk h) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.Index

Methods

noThunksContextIndex m blk h → IO (Maybe ThunkInfo) Source #

wNoThunksContextIndex m blk h → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (Index m blk h) → String Source #

StandardHash blk ⇒ NoThunks (InternalState m blk h) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.State

StandardHash blk ⇒ NoThunks (OpenState m blk h) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.Impl.State

Methods

noThunksContextOpenState m blk h → IO (Maybe ThunkInfo) Source #

wNoThunksContextOpenState m blk h → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (OpenState m blk h) → String Source #

(NoThunks a, NoThunks b) ⇒ NoThunks (AnchoredSeq v a b) 
Instance details

Defined in Ouroboros.Network.AnchoredSeq

NoThunks b ⇒ NoThunks (MeasuredWith v a b) 
Instance details

Defined in Ouroboros.Network.AnchoredSeq

Methods

noThunksContext → MeasuredWith v a b → IO (Maybe ThunkInfo) Source #

wNoThunksContext → MeasuredWith v a b → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (MeasuredWith v a b) → String Source #

NoThunks a ⇒ NoThunks (K a b) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.Orphans

Methods

noThunksContextK a b → IO (Maybe ThunkInfo) Source #

wNoThunksContextK a b → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (K a b) → String Source #

All (Compose NoThunks f) xs ⇒ NoThunks (NP f xs) 
Instance details

Defined in Data.SOP.Strict.NP

Methods

noThunksContextNP f xs → IO (Maybe ThunkInfo) Source #

wNoThunksContextNP f xs → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (NP f xs) → String Source #

All (Compose NoThunks f) xs ⇒ NoThunks (NS f xs) 
Instance details

Defined in Data.SOP.Strict.NS

Methods

noThunksContextNS f xs → IO (Maybe ThunkInfo) Source #

wNoThunksContextNS f xs → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (NS f xs) → String Source #

(NoThunks a, NoThunks b, NoThunks c) ⇒ NoThunks (a, b, c) 
Instance details

Defined in NoThunks.Class

Methods

noThunksContext → (a, b, c) → IO (Maybe ThunkInfo) Source #

wNoThunksContext → (a, b, c) → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (a, b, c) → String Source #

(All SingleEraBlock xs, ∀ x. SingleEraBlock x ⇒ NoThunks (f x), ∀ x. SingleEraBlock x ⇒ NoThunks (g x), KnownSymbol name) ⇒ NoThunks (LiftNamedMismatch name f g xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Lifting

(All SingleEraBlock xs, ∀ x. SingleEraBlock x ⇒ NoThunks (f x), ∀ x. SingleEraBlock x ⇒ NoThunks (g x), KnownSymbol name) ⇒ NoThunks (LiftNamedTelescope name f g xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Lifting

(Typeable f, Typeable blk) ⇒ NoThunks (SomeSecond (NestedCtxt f) blk) Source #

We can write a manual instance using the following quantified constraint:

forall a. NoThunks (f blk a)

However, this constraint would have to be propagated all the way up, which is rather verbose and annoying (standalone deriving has to be used), hence we use InspectHeap for convenience.

Instance details

Defined in Ouroboros.Consensus.Block.NestedContent

(All (Compose NoThunks f) xs, All (Compose NoThunks g) xs) ⇒ NoThunks (Mismatch f g xs) 
Instance details

Defined in Data.SOP.Match

(All (Compose NoThunks g) xs, All (Compose NoThunks f) xs) ⇒ NoThunks (Telescope g f xs) 
Instance details

Defined in Data.SOP.Telescope

(NoThunks a, NoThunks b, NoThunks c, NoThunks d) ⇒ NoThunks (a, b, c, d) 
Instance details

Defined in NoThunks.Class

Methods

noThunksContext → (a, b, c, d) → IO (Maybe ThunkInfo) Source #

wNoThunksContext → (a, b, c, d) → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (a, b, c, d) → String Source #

NoThunks (Ticked (f a)) ⇒ NoThunks ((Ticked :.: f) a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ticked

NoThunks (f y2 x2) ⇒ NoThunks (Flip f x2 y2) 
Instance details

Defined in Data.SOP.Functors

Methods

noThunksContextFlip f x2 y2 → IO (Maybe ThunkInfo) Source #

wNoThunksContextFlip f x2 y2 → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (Flip f x2 y2) → String Source #

(NoThunks a, NoThunks b, NoThunks c, NoThunks d, NoThunks e) ⇒ NoThunks (a, b, c, d, e) 
Instance details

Defined in NoThunks.Class

Methods

noThunksContext → (a, b, c, d, e) → IO (Maybe ThunkInfo) Source #

wNoThunksContext → (a, b, c, d, e) → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (a, b, c, d, e) → String Source #

(NoThunks a, NoThunks b, NoThunks c, NoThunks d, NoThunks e, NoThunks f) ⇒ NoThunks (a, b, c, d, e, f) 
Instance details

Defined in NoThunks.Class

Methods

noThunksContext → (a, b, c, d, e, f) → IO (Maybe ThunkInfo) Source #

wNoThunksContext → (a, b, c, d, e, f) → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (a, b, c, d, e, f) → String Source #

(NoThunks a, NoThunks b, NoThunks c, NoThunks d, NoThunks e, NoThunks f, NoThunks g) ⇒ NoThunks (a, b, c, d, e, f, g) 
Instance details

Defined in NoThunks.Class

Methods

noThunksContext → (a, b, c, d, e, f, g) → IO (Maybe ThunkInfo) Source #

wNoThunksContext → (a, b, c, d, e, f, g) → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (a, b, c, d, e, f, g) → String Source #