rawlock-0.1.1.0: A writer-biased RAW lock.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.RAWLock

Description

A Read-Append-Write (RAW) lock

A RAW lock allows multiple concurrent readers, at most one appender, which is allowed to run concurrently with the readers, and at most one writer, which has exclusive access to the lock.

The following table summarises which roles are allowed to concurrently access the RAW lock:

ReaderAppenderWriter
ReaderVVX
Appender░░░░░░░░XX
Writer░░░░░░░░░░░░░░░░░░X

It is important to realise that a RAW lock is intended to control access to a piece of in-memory state that should remain in sync with some other state that can only be modified using side-effects, e.g., the file system. If, for example, you're only maintaining a counter shared by threads, then simply use a TVar or an MVar.

Example use case: log files

A RAW lock is useful, for example, to maintain an in-memory index of log files stored on disk.

  • To read data from a log file, you need "read" access to the index to find out the file and offset where the requested piece of data is stored. While holding the RAW lock as a reader, you can perform the IO operation to read the data from the right log file. This can safely happen concurrently with other read operations.
  • To append data to the current log file, you need "append" access to the index so you can append an entry to the index and even to add a new log file to the index when necessary. While holding the RAW lock as an appender, you can perform the IO operation to append the piece of data to the current log file and, if necessary start a new log file. Only one append can happen concurrently. However, reads can safely happen concurrently with appends. Note that the in-memory index is only updated after writing to disk.
  • To remove the oldest log files, you need "write" access to the index, so you can remove files from the index. While holding the RAW lock as a writer, you can perform the IO operations to delete the oldest log files. No other operations can run concurrently with this operation: concurrent reads might try to read from deleted files and a concurrent append could try to append to a deleted file.

Analogy: Chicken coop

Think of readers as chickens, the appender as the rooster, and the writer as the fox. All of them want access to the chicken coop, i.e., the state protected by the RAW lock.

We can allow multiple chickens (readers) together in the chicken coop, they get along (reasonably) fine. We can also let one rooster (appender) in, but not more than one, otherwise he would start fighting with the other rooster (conflict with the other appender). We can only let the fox in when all chickens and the rooster (if present) have left the chicken coop, otherwise the fox would eat them (conflict with the appender and invalidate the results of readers, e.g, closing resources readers try to access).

Usage

To use the lock, use any of the three following operations:

If the standard bracketing the above three operations use doesn't suffice, use the following three acquire-release pairs:

NOTE: an acquire must be followed by the corresponding release, otherwise the correctness of the lock is not guaranteed and a dead-lock can happen.

NOTE: nested locking of the same lock is not allowed, as you might be blocked on yourself.

Notes

  • Only use a RAW lock when it is safe to concurrently read and append.
  • We do not guarantee fairness. Once the lock is released, all waiting actors will race for the access.
  • The state st is always evaluated to WHNF and is subject to the NoThunks check when enabled.
  • All public functions are exception-safe.
Synopsis

API

data RAWLock m st Source #

Instances

Instances details
Generic (RAWLock m st) Source # 
Instance details

Defined in Control.RAWLock

Associated Types

type Rep (RAWLock m st) :: Type -> Type

Methods

from :: RAWLock m st -> Rep (RAWLock m st) x

to :: Rep (RAWLock m st) x -> RAWLock m st

(NoThunks (StrictTMVar m (Poisonable st)), NoThunks (StrictMVar m ()), NoThunks (StrictTVar m (Poisonable RAWState))) => NoThunks (RAWLock m st) Source # 
Instance details

Defined in Control.RAWLock

Methods

noThunks :: Context -> RAWLock m st -> IO (Maybe ThunkInfo) #

wNoThunks :: Context -> RAWLock m st -> IO (Maybe ThunkInfo) #

showTypeOf :: Proxy (RAWLock m st) -> String #

type Rep (RAWLock m st) Source # 
Instance details

Defined in Control.RAWLock

type Rep (RAWLock m st)

new :: (MonadMVar m, MonadLabelledSTM m) => st -> m (RAWLock m st) Source #

poison :: (Exception e, MonadMVar m, MonadSTM m, MonadThrow (STM m), HasCallStack) => RAWLock m st -> (CallStack -> e) -> m (Maybe st) Source #

When a lock is poisoned all subsequent access to it is overridden by the poison. This means that the current actor that holds the lock will free it, and any other concurrent actors will be able to release their access, possibly rising the poison exception in the process.

There is no need (although it is harmless) to release again the current actor once it has poisoned the lock.

read :: (MonadSTM m, MonadThrow (STM m)) => RAWLock m st -> STM m st Source #

withAppendAccess :: (MonadThrow (STM m), MonadSTM m, MonadCatch m, MonadMVar m) => RAWLock m st -> (st -> m (a, st)) -> m a Source #

Acquire the RAWLock as an appender.

Will block when there is a writer or when there is another appender.

withReadAccess :: (MonadSTM m, MonadCatch m, MonadThrow (STM m)) => RAWLock m st -> (st -> m a) -> m a Source #

Acquire the RAWLock as a reader.

Will block when there is a writer or when a writer is waiting to take the lock.

withWriteAccess :: (MonadSTM m, MonadCatch m, MonadThrow (STM m)) => RAWLock m st -> (st -> m (a, st)) -> m a Source #

Acquire the RAWLock as a writer.

Will block when there is another writer, readers or appenders.

Unsafe API

These functions are unsafe in the sense that they do not guard against exceptions, meaning that if you don't take care and ensure exception safety, you might make the RAWLock unusable.

To be safe, you should ensure that every unsafeAcquireXAccess is paired with unsafeReleaseXAccess, even in the presence of exceptions.

Note that for writing and appending, you should restore the original value in presence of an exception!

unsafeReleaseWriteAccess :: (MonadThrow (STM m), MonadSTM m) => RAWLock m st -> st -> m () Source #