context-0.2.1.0: Thread-indexed, nested contexts
Safe HaskellSafe-Inferred
LanguageHaskell2010

Context

Synopsis

Introduction

This module provides an opaque Store for thread-indexed storage around arbitrary context values. The interface supports nesting context values per thread, and at any point, the calling thread may ask for its current context.

Note that threads in Haskell have no explicit parent-child relationship. So if you register a context in a Store produced by withEmptyStore, spin up a separate thread, and from that thread you ask for a context, that thread will not have a context in the Store. Use Context.Concurrent as a drop-in replacement for Control.Concurrent to have the library handle context propagation from one thread to another automatically. Otherwise, you must explicitly register contexts from each thread when using a Store produced by withEmptyStore.

If you have a default context that is always applicable to all threads, you may wish to use withNonEmptyStore. All threads may access this default context (without leveraging Context.Concurrent or explicitly registering context for the threads) when using a Store produced by withNonEmptyStore.

Regardless of how you initialize your Store, every thread is free to nest its own specific context values.

This module is designed to be imported qualified:

import qualified Context

Storage

data Store ctx Source #

Opaque type that manages thread-indexed storage of context values.

Since: 0.1.0.0

withNonEmptyStore :: forall m ctx a. (MonadIO m, MonadMask m) => ctx -> (Store ctx -> m a) -> m a Source #

Provides a new, non-empty Store that uses the specified context value as a default when the calling thread has no registered context. mine, mines, and adjust are guaranteed to never throw NotFoundException when applied to a non-empty Store.

Since: 0.1.0.0

withEmptyStore :: forall m ctx a. (MonadIO m, MonadMask m) => (Store ctx -> m a) -> m a Source #

Provides a new, empty Store. mine, mines, and adjust will throw NotFoundException when the calling thread has no registered context. Useful when the Store will contain context values that are always thread-specific.

Since: 0.1.0.0

Operations

Registering context

use :: forall m ctx a. (MonadIO m, MonadMask m) => Store ctx -> ctx -> m a -> m a Source #

Register a context in the specified Store on behalf of the calling thread, for the duration of the specified action.

Since: 0.1.0.0

adjust :: forall m ctx a. (MonadIO m, MonadMask m) => Store ctx -> (ctx -> ctx) -> m a -> m a Source #

Adjust the calling thread's context in the specified Store for the duration of the specified action. Throws a NotFoundException when the calling thread has no registered context.

Since: 0.1.0.0

withAdjusted :: forall m ctx a. (MonadIO m, MonadMask m) => Store ctx -> (ctx -> ctx) -> (ctx -> m a) -> m a Source #

Convenience function to adjust the context then supply the adjusted context to the inner action. This function is equivalent to calling adjust and then immediately calling mine in the inner action of adjust, e.g.:

doStuff :: Store Thing -> (Thing -> Thing) -> IO ()
doStuff store f = do
  adjust store f do
    adjustedThing <- mine store
    ...

Throws a NotFoundException when the calling thread has no registered context.

Since: 0.2.0.0

Asking for context

mine :: forall m ctx. (MonadIO m, MonadThrow m) => Store ctx -> m ctx Source #

Provide the calling thread its current context from the specified Store. Throws a NotFoundException when the calling thread has no registered context.

Since: 0.1.0.0

mines :: forall m ctx a. (MonadIO m, MonadThrow m) => Store ctx -> (ctx -> a) -> m a Source #

Provide the calling thread a selection from its current context in the specified Store. Throws a NotFoundException when the calling thread has no registered context.

Since: 0.1.0.0

mineMay :: forall m ctx. MonadIO m => Store ctx -> m (Maybe ctx) Source #

Provide the calling thread its current context from the specified Store, if present.

Since: 0.1.0.0

minesMay :: forall m ctx a. MonadIO m => Store ctx -> (ctx -> a) -> m (Maybe a) Source #

Provide the calling thread a selection from its current context in the specified Store, if present.

Since: 0.1.0.0

Views

Exceptions

newtype NotFoundException Source #

An exception which may be thrown when the calling thread does not have a registered context.

Since: 0.1.0.0

Constructors

NotFoundException 

Fields

Instances

Instances details
Exception NotFoundException Source # 
Instance details

Defined in Context.Internal

Generic NotFoundException Source # 
Instance details

Defined in Context.Internal

Associated Types

type Rep NotFoundException :: Type -> Type #

Show NotFoundException Source # 
Instance details

Defined in Context.Internal

Eq NotFoundException Source # 
Instance details

Defined in Context.Internal

type Rep NotFoundException Source # 
Instance details

Defined in Context.Internal

type Rep NotFoundException = D1 ('MetaData "NotFoundException" "Context.Internal" "context-0.2.1.0-4AKJAx41jbHHwVjd5kydLo" 'True) (C1 ('MetaCons "NotFoundException" 'PrefixI 'True) (S1 ('MetaSel ('Just "threadId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ThreadId)))

Concurrency

Lower-level storage