Blammo-2.1.1.0: Batteries-included Structured Logging library
Safe HaskellSafe-Inferred
LanguageHaskell2010

Blammo.Logging.ThreadContext

Synopsis

Documentation

class MonadCatch m => MonadMask (m :: Type -> Type) #

A class for monads which provide for the ability to account for all possible exit points from a computation, and to mask asynchronous exceptions. Continuation-based monads are invalid instances of this class.

Instances should ensure that, in the following code:

fg = f `finally` g

The action g is called regardless of what occurs within f, including async exceptions. Some monads allow f to abort the computation via other effects than throwing an exception. For simplicity, we will consider aborting and throwing an exception to be two forms of "throwing an error".

If f and g both throw an error, the error thrown by fg depends on which errors we're talking about. In a monad transformer stack, the deeper layers override the effects of the inner layers; for example, ExceptT e1 (Except e2) a represents a value of type Either e2 (Either e1 a), so throwing both an e1 and an e2 will result in Left e2. If f and g both throw an error from the same layer, instances should ensure that the error from g wins.

Effects other than throwing an error are also overridden by the deeper layers. For example, StateT s Maybe a represents a value of type s -> Maybe (a, s), so if an error thrown from f causes this function to return Nothing, any changes to the state which f also performed will be erased. As a result, g will see the state as it was before f. Once g completes, f's error will be rethrown, so g' state changes will be erased as well. This is the normal interaction between effects in a monad transformer stack.

By contrast, lifted-base's version of finally always discards all of g's non-IO effects, and g never sees any of f's non-IO effects, regardless of the layer ordering and regardless of whether f throws an error. This is not the result of interacting effects, but a consequence of MonadBaseControl's approach.

Minimal complete definition

mask, uninterruptibleMask, generalBracket

Instances

Instances details
MonadMask IO 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: HasCallStack => ((forall a. IO a -> IO a) -> IO b) -> IO b #

uninterruptibleMask :: HasCallStack => ((forall a. IO a -> IO a) -> IO b) -> IO b #

generalBracket :: HasCallStack => IO a -> (a -> ExitCase b -> IO c) -> (a -> IO b) -> IO (b, c) #

e ~ SomeException => MonadMask (Either e)

Since: exceptions-0.8.3

Instance details

Defined in Control.Monad.Catch

Methods

mask :: HasCallStack => ((forall a. Either e a -> Either e a) -> Either e b) -> Either e b #

uninterruptibleMask :: HasCallStack => ((forall a. Either e a -> Either e a) -> Either e b) -> Either e b #

generalBracket :: HasCallStack => Either e a -> (a -> ExitCase b -> Either e c) -> (a -> Either e b) -> Either e (b, c) #

MonadMask m => MonadMask (LoggingT m) 
Instance details

Defined in Control.Monad.Logger

Methods

mask :: HasCallStack => ((forall a. LoggingT m a -> LoggingT m a) -> LoggingT m b) -> LoggingT m b #

uninterruptibleMask :: HasCallStack => ((forall a. LoggingT m a -> LoggingT m a) -> LoggingT m b) -> LoggingT m b #

generalBracket :: HasCallStack => LoggingT m a -> (a -> ExitCase b -> LoggingT m c) -> (a -> LoggingT m b) -> LoggingT m (b, c) #

MonadMask m => MonadMask (NoLoggingT m) 
Instance details

Defined in Control.Monad.Logger

Methods

mask :: HasCallStack => ((forall a. NoLoggingT m a -> NoLoggingT m a) -> NoLoggingT m b) -> NoLoggingT m b #

uninterruptibleMask :: HasCallStack => ((forall a. NoLoggingT m a -> NoLoggingT m a) -> NoLoggingT m b) -> NoLoggingT m b #

generalBracket :: HasCallStack => NoLoggingT m a -> (a -> ExitCase b -> NoLoggingT m c) -> (a -> NoLoggingT m b) -> NoLoggingT m (b, c) #

MonadMask m => MonadMask (WriterLoggingT m) 
Instance details

Defined in Control.Monad.Logger

Methods

mask :: HasCallStack => ((forall a. WriterLoggingT m a -> WriterLoggingT m a) -> WriterLoggingT m b) -> WriterLoggingT m b #

uninterruptibleMask :: HasCallStack => ((forall a. WriterLoggingT m a -> WriterLoggingT m a) -> WriterLoggingT m b) -> WriterLoggingT m b #

generalBracket :: HasCallStack => WriterLoggingT m a -> (a -> ExitCase b -> WriterLoggingT m c) -> (a -> WriterLoggingT m b) -> WriterLoggingT m (b, c) #

MonadMask m => MonadMask (ResourceT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

mask :: HasCallStack => ((forall a. ResourceT m a -> ResourceT m a) -> ResourceT m b) -> ResourceT m b #

uninterruptibleMask :: HasCallStack => ((forall a. ResourceT m a -> ResourceT m a) -> ResourceT m b) -> ResourceT m b #

generalBracket :: HasCallStack => ResourceT m a -> (a -> ExitCase b -> ResourceT m c) -> (a -> ResourceT m b) -> ResourceT m (b, c) #

MonadMask m => MonadMask (MaybeT m)

Since: exceptions-0.10.0

Instance details

Defined in Control.Monad.Catch

Methods

mask :: HasCallStack => ((forall a. MaybeT m a -> MaybeT m a) -> MaybeT m b) -> MaybeT m b #

uninterruptibleMask :: HasCallStack => ((forall a. MaybeT m a -> MaybeT m a) -> MaybeT m b) -> MaybeT m b #

generalBracket :: HasCallStack => MaybeT m a -> (a -> ExitCase b -> MaybeT m c) -> (a -> MaybeT m b) -> MaybeT m (b, c) #

MonadMask m => MonadMask (ExceptT e m)

Since: exceptions-0.9.0

Instance details

Defined in Control.Monad.Catch

Methods

mask :: HasCallStack => ((forall a. ExceptT e m a -> ExceptT e m a) -> ExceptT e m b) -> ExceptT e m b #

uninterruptibleMask :: HasCallStack => ((forall a. ExceptT e m a -> ExceptT e m a) -> ExceptT e m b) -> ExceptT e m b #

generalBracket :: HasCallStack => ExceptT e m a -> (a -> ExitCase b -> ExceptT e m c) -> (a -> ExceptT e m b) -> ExceptT e m (b, c) #

MonadMask m => MonadMask (IdentityT m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: HasCallStack => ((forall a. IdentityT m a -> IdentityT m a) -> IdentityT m b) -> IdentityT m b #

uninterruptibleMask :: HasCallStack => ((forall a. IdentityT m a -> IdentityT m a) -> IdentityT m b) -> IdentityT m b #

generalBracket :: HasCallStack => IdentityT m a -> (a -> ExitCase b -> IdentityT m c) -> (a -> IdentityT m b) -> IdentityT m (b, c) #

MonadMask m => MonadMask (ReaderT r m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: HasCallStack => ((forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m b) -> ReaderT r m b #

uninterruptibleMask :: HasCallStack => ((forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m b) -> ReaderT r m b #

generalBracket :: HasCallStack => ReaderT r m a -> (a -> ExitCase b -> ReaderT r m c) -> (a -> ReaderT r m b) -> ReaderT r m (b, c) #

MonadMask m => MonadMask (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: HasCallStack => ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

uninterruptibleMask :: HasCallStack => ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

generalBracket :: HasCallStack => StateT s m a -> (a -> ExitCase b -> StateT s m c) -> (a -> StateT s m b) -> StateT s m (b, c) #

MonadMask m => MonadMask (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: HasCallStack => ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

uninterruptibleMask :: HasCallStack => ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

generalBracket :: HasCallStack => StateT s m a -> (a -> ExitCase b -> StateT s m c) -> (a -> StateT s m b) -> StateT s m (b, c) #

(MonadMask m, Monoid w) => MonadMask (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: HasCallStack => ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

uninterruptibleMask :: HasCallStack => ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

generalBracket :: HasCallStack => WriterT w m a -> (a -> ExitCase b -> WriterT w m c) -> (a -> WriterT w m b) -> WriterT w m (b, c) #

(MonadMask m, Monoid w) => MonadMask (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: HasCallStack => ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

uninterruptibleMask :: HasCallStack => ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

generalBracket :: HasCallStack => WriterT w m a -> (a -> ExitCase b -> WriterT w m c) -> (a -> WriterT w m b) -> WriterT w m (b, c) #

(MonadMask m, Monoid w) => MonadMask (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: HasCallStack => ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

uninterruptibleMask :: HasCallStack => ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

generalBracket :: HasCallStack => RWST r w s m a -> (a -> ExitCase b -> RWST r w s m c) -> (a -> RWST r w s m b) -> RWST r w s m (b, c) #

(MonadMask m, Monoid w) => MonadMask (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: HasCallStack => ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

uninterruptibleMask :: HasCallStack => ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

generalBracket :: HasCallStack => RWST r w s m a -> (a -> ExitCase b -> RWST r w s m c) -> (a -> RWST r w s m b) -> RWST r w s m (b, c) #

withThreadContext :: (MonadIO m, MonadMask m) => [Pair] -> m a -> m a #

This function lets us register structured, contextual info for the duration of the provided action. All messages logged within the provided action will automatically include this contextual info. This function is thread-safe, as the contextual info is scoped to the calling thread only.

This function is additive: if we nest calls to it, each nested call will add to the existing thread context. In the case of overlapping keys, the nested call's Pair value(s) will win. Whenever the inner action completes, the thread context is rolled back to its value set in the enclosing action.

If we wish to include the existing thread context from one thread in another thread, we must register the thread context explicitly on that other thread. myThreadContext can be leveraged in this case.

Registering thread context for messages can be useful in many scenarios. One particularly apt scenario is in wai middlewares. We can generate an ID for each incoming request then include it in the thread context. Now all messages subsequently logged from our endpoint handler will automatically include that request ID:

import Control.Monad.Logger.Aeson ((.=), withThreadContext)
import Network.Wai (Middleware)
import qualified Data.UUID.V4 as UUID

addRequestId :: Middleware
addRequestId app = \request sendResponse -> do
  uuid <- UUID.nextRandom
  withThreadContext ["requestId" .= uuid] do
    app request sendResponse

If we're coming from a Java background, it may be helpful for us to draw parallels between this function and log4j2's ThreadContext (or perhaps log4j's MDC). They all enable the same thing: setting some thread-local info that will be automatically pulled into each logged message.

Since: monad-logger-aeson-0.1.0.0

myThreadContext :: (MonadIO m, MonadThrow m) => m (KeyMap Value) #

This function lets us retrieve the calling thread's thread context. For more detail, we can consult the docs for withThreadContext.

Note that even though the type signature lists MonadThrow as a required constraint, the library guarantees that myThreadContext will never throw.

Since: monad-logger-aeson-0.1.0.0

type Pair = (Key, Value) #

A key/value pair for an Object.