Safe Haskell | None |
---|---|
Language | Haskell2010 |
Threadsafe, shared, atomic counters
This is based on Data.Atomics.Counter.
Synopsis
- fresh :: forall a env m. (MonadReader env m, MonadIO m, HasCounterVar a env, Coercible a Int) => m a
- incrementAndGet :: forall a m. (MonadIO m, Coercible a Int) => CounterVar a -> m a
- newCounterVar :: forall a m. MonadIO m => m (CounterVar a)
- class HasCounterVar a env | env -> a where
- getCounterVar :: env -> CounterVar a
- data CounterVar a
Documentation
fresh :: forall a env m. (MonadReader env m, MonadIO m, HasCounterVar a env, Coercible a Int) => m a Source #
A threadsafe atomic a
Atomically increment and get the value of the Counter
for type a
that must be present in the env
.
incrementAndGet :: forall a m. (MonadIO m, Coercible a Int) => CounterVar a -> m a Source #
Atomically increment and get the value of the Counter
for type a
that must be present in the env
.
newCounterVar :: forall a m. MonadIO m => m (CounterVar a) Source #
Create a new CounterVar
starting at 0
.
class HasCounterVar a env | env -> a where Source #
A type class for MonadReader
based
applications.
getCounterVar :: env -> CounterVar a Source #
Instances
HasCounterVar (t :: k) (CounterVar t) Source # | |
Defined in UnliftIO.MessageBox.Util.Fresh getCounterVar :: CounterVar t -> CounterVar t Source # |
data CounterVar a Source #
An AtomicCounter
.
Instances
HasCounterVar (t :: k) (CounterVar t) Source # | |
Defined in UnliftIO.MessageBox.Util.Fresh getCounterVar :: CounterVar t -> CounterVar t Source # | |
HasCallIdCounter (CounterVar CallId) Source # | |
Defined in UnliftIO.MessageBox.Util.CallId |