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

Context.Internal

Synopsis

Disclaimer

In general, changes to this module will not be reflected in the library's version updates. Direct use of this module should be done with extreme care as it becomes very easy to violate the library's invariants.

Store-related

data Store ctx Source #

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

Since: 0.1.0.0

Constructors

Store 

Fields

data State ctx Source #

Constructors

State 

Fields

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

withStore Source #

Arguments

:: forall m ctx a. (MonadIO m, MonadMask m) 
=> PropagationStrategy

The strategy used by Context.Concurrent for propagating context from a "parent" thread to a new thread.

-> Maybe ctx

The default value for the Store.

Providing a value will produce a non-empty Store such that mine, mines, and adjust are guaranteed to never throw NotFoundException when applied to this Store.

Providing Nothing will produce an empty Store such that mine, mines, and adjust will throw NotFoundException when the calling thread has no registered context. Providing Nothing is useful when the Store will contain context values that are always thread-specific.

-> (Store ctx -> m a) 
-> m a 

Provides a new Store. This is a lower-level function and is provided mainly to give library authors more fine-grained control when using a Store as an implementation detail.

withNonEmptyStore/withEmptyStore should generally be preferred over this function when acquiring a Store.

Since: 0.1.0.0

newStore Source #

Arguments

:: forall m ctx. MonadIO m 
=> PropagationStrategy

The strategy used by Context.Concurrent for propagating context from a "parent" thread to a new thread.

-> Maybe ctx

The default value for the Store.

Providing a value will produce a non-empty Store such that mine, mines, and adjust are guaranteed to never throw NotFoundException when applied to this Store.

Providing Nothing will produce an empty Store such that mine, mines, and adjust will throw NotFoundException when the calling thread has no registered context. Providing Nothing is useful when the Store will contain context values that are always thread-specific.

-> m (Store ctx) 

Creates a new Store. This is a lower-level function and is provided only to support the use case of creating a Store as a global:

store :: Store Int
store = unsafePerformIO $ Context.newStore Context.defaultPropagation Nothing
{-# NOINLINE store #-}

Outside of the global variable use case, withNonEmptyStore, withEmptyStore, or even the lower-level withStore should always be preferred over this function when acquiring a Store.

Since: 0.1.0.0

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

push :: Store ctx -> ctx -> IO () Source #

pop :: Store ctx -> IO () Source #

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

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

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

Set the default context value for a store. If the store was initialized as an empty store, this function converts it to a non-empty store. If the store was initialized as a non-empty store, this overwrites the default context value.

One common use case for this function is to convert an empty store in a global variable to a non-empty store while the application is initializing/acquiring resources:

depsStore :: Store Dependencies
depsStore = unsafePerformIO $ Context.newStore Context.defaultPropagation Nothing
{-# NOINLINE depsStore #-}

main :: IO ()
main = do
  let config = -- ...
  withDependencies config \deps -> do
    Context.setDefault depsStore deps
    -- ...

Since: 0.1.0.0

throwContextNotFound :: forall m a. (MonadIO m, MonadThrow m) => m a Source #

View-related

data View ctx where Source #

A View provides a read-only view into a Store. View trades the Store ability to register new context for the ability to arbitrarily transform context values locally to the View.

Since: 0.1.1.0

Constructors

MkView :: (ctx' -> ctx) -> Store ctx' -> View ctx 

Instances

Instances details
Functor View Source # 
Instance details

Defined in Context.Internal

Methods

fmap :: (a -> b) -> View a -> View b #

(<$) :: a -> View b -> View a #

view :: (MonadIO m, MonadThrow m) => View ctx -> m ctx Source #

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

Since: 0.1.1.0

viewMay :: MonadIO m => View ctx -> m (Maybe ctx) Source #

Provide the calling thread a view of its current context from the specified View, if present.

Since: 0.1.1.0

toView :: Store ctx -> View ctx Source #

Create a View from the provided Store.

Since: 0.1.1.0

Propagation-related

data PropagationStrategy Source #

The PropagationStrategy controls the behavior used by Context.Concurrent when propagating context from a "parent" thread to a new thread.

Since: 0.1.0.0

newtype Registry Source #

Constructors

Registry 

Fields

data AnyStore where Source #

Constructors

MkAnyStore :: forall ctx. Store ctx -> AnyStore 

withPropagator :: ((IO a -> IO a) -> IO b) -> IO b Source #

withRegisteredPropagator :: Registry -> ((IO a -> IO a) -> IO b) -> IO b Source #

register :: Registry -> Store ctx -> IO () Source #

Miscellaneous