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

Context.Implicit

Synopsis

Introduction

This module provides the same interface provided by Context, but uses an implicit Store where applicable. Usage of this module requires that the implicit parameter is named contextStore in calling code.

This module is designed to be imported qualified:

import qualified Context.Implicit

If you are only working with an implicit Store in your application, you may prefer shortening the import name:

import qualified Context.Implicit as Context

Usage of this module might look something like this:

main :: IO ()
main = do
  let config = -- ...
  withDependencies config \deps -> do
    Context.withNonEmptyStore deps \depsStore -> do
      let ?contextStore = depsStore
      doStuff

doStuff :: (?contextStore :: Store Dependencies) => IO ()
doStuff = do
  deps <- Context.mine
  -- ...

If the application is using a Store in a global variable, then this Store can be conveniently injected in for use with this module via a global implicit parameter:

module Dependencies where

import qualified Context.Implicit as Context
import GHC.Classes(IP(ip)) -- from 'ghc-prim' package

data Dependencies = -- ...

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

instance IP "contextStore" (Store Dependencies) where
  ip = depsStore

With a global implicit parameter, the (?contextStore :: Store Dependencies) constraint does not need to be threaded throughout the application's signatures, but it still can be overridden within local scopes as needed.

For an intro to global implicit parameters, see this post: https://kcsongor.github.io/global-implicit-parameters/

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, ?contextStore :: Store ctx) => ctx -> m a -> m a Source #

Register a context in the implicit 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, ?contextStore :: Store ctx) => (ctx -> ctx) -> m a -> m a Source #

Adjust the calling thread's context in the implicit 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, ?contextStore :: 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, ?contextStore :: Store ctx) => m ctx Source #

Provide the calling thread its current context from the implicit 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, ?contextStore :: Store ctx) => (ctx -> a) -> m a Source #

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

Since: 0.1.0.0

mineMay :: forall m ctx. (MonadIO m, ?contextStore :: Store ctx) => m (Maybe ctx) Source #

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

Since: 0.1.0.0

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

Provide the calling thread a selection from its current context in the implicit 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