dejafu-1.0.0.2: A library for unit-testing concurrent programs.

Copyright(c) 2016--2017 Michael Walker
LicenseMIT
MaintainerMichael Walker <mike@barrucadu.co.uk>
Stabilityexperimental
PortabilityBangPatterns, GADTs, MultiParamTypeClasses
Safe HaskellNone
LanguageHaskell2010

Test.DejaFu.Conc.Internal.Memory

Contents

Description

Operations over CRefs and MVars. This module is NOT considered to form part of the public interface of this library.

Relaxed memory operations over CRefs are implemented with an explicit write buffer: one per thread for TSO, and one per thread/variable combination for PSO. Unsynchronised writes append to this buffer, and periodically separate threads commit from these buffers to the "actual" CRef.

This model comes from /Dynamic Partial Order Reduction for Relaxed Memory Models/, N. Zhang, M. Kusano, and C. Wang (2015).

Synopsis

Manipulating CRefs

newtype WriteBuffer r Source #

In non-sequentially-consistent memory models, non-synchronised writes get buffered.

The CRefId parameter is only used under PSO. Under TSO each thread has a single buffer.

Constructors

WriteBuffer 

data BufferedWrite r where Source #

A buffered write is a reference to the variable, and the value to write. Universally quantified over the value type so that the only thing which can be done with it is to write it to the reference.

Constructors

BufferedWrite :: ThreadId -> CRef r a -> a -> BufferedWrite r 

emptyBuffer :: WriteBuffer r Source #

An empty write buffer.

bufferWrite :: MonadRef r n => WriteBuffer r -> (ThreadId, Maybe CRefId) -> CRef r a -> a -> n (WriteBuffer r) Source #

Add a new write to the end of a buffer.

commitWrite :: MonadRef r n => WriteBuffer r -> (ThreadId, Maybe CRefId) -> n (WriteBuffer r) Source #

Commit the write at the head of a buffer.

readCRef :: MonadRef r n => CRef r a -> ThreadId -> n a Source #

Read from a CRef, returning a newer thread-local non-committed write if there is one.

readForTicket :: MonadRef r n => CRef r a -> ThreadId -> n (Ticket a) Source #

Read from a CRef, returning a Ticket representing the current view of the thread.

casCRef :: MonadRef r n => CRef r a -> ThreadId -> Ticket a -> a -> n (Bool, Ticket a) Source #

Perform a compare-and-swap on a CRef if the ticket is still valid. This is strict in the "new" value argument.

readCRefPrim :: MonadRef r n => CRef r a -> ThreadId -> n (a, Integer) Source #

Read the local state of a CRef.

writeImmediate :: MonadRef r n => CRef r a -> a -> n () Source #

Write and commit to a CRef immediately, clearing the update map and incrementing the write count.

writeBarrier :: MonadRef r n => WriteBuffer r -> n () Source #

Flush all writes in the buffer.

addCommitThreads :: WriteBuffer r -> Threads n r -> Threads n r Source #

Add phantom threads to the thread list to commit pending writes.

delCommitThreads :: Threads n r -> Threads n r Source #

Remove phantom threads.

Manipulating MVars

data Blocking Source #

Constructors

Blocking 
NonBlocking 

data Emptying Source #

Constructors

Emptying 
NonEmptying 

putIntoMVar :: MonadRef r n => MVar r a -> a -> Action n r -> ThreadId -> Threads n r -> n (Bool, Threads n r, [ThreadId]) Source #

Put into a MVar, blocking if full.

tryPutIntoMVar :: MonadRef r n => MVar r a -> a -> (Bool -> Action n r) -> ThreadId -> Threads n r -> n (Bool, Threads n r, [ThreadId]) Source #

Try to put into a MVar, not blocking if full.

readFromMVar :: MonadRef r n => MVar r a -> (a -> Action n r) -> ThreadId -> Threads n r -> n (Bool, Threads n r, [ThreadId]) Source #

Read from a MVar, blocking if empty.

tryReadFromMVar :: MonadRef r n => MVar r a -> (Maybe a -> Action n r) -> ThreadId -> Threads n r -> n (Bool, Threads n r, [ThreadId]) Source #

Try to read from a MVar, not blocking if empty.

takeFromMVar :: MonadRef r n => MVar r a -> (a -> Action n r) -> ThreadId -> Threads n r -> n (Bool, Threads n r, [ThreadId]) Source #

Take from a MVar, blocking if empty.

tryTakeFromMVar :: MonadRef r n => MVar r a -> (Maybe a -> Action n r) -> ThreadId -> Threads n r -> n (Bool, Threads n r, [ThreadId]) Source #

Try to take from a MVar, not blocking if empty.

mutMVar :: MonadRef r n => Blocking -> MVar r a -> a -> (Bool -> Action n r) -> ThreadId -> Threads n r -> n (Bool, Threads n r, [ThreadId]) Source #

Mutate a MVar, in either a blocking or nonblocking way.

seeMVar :: MonadRef r n => Emptying -> Blocking -> MVar r a -> (Maybe a -> Action n r) -> ThreadId -> Threads n r -> n (Bool, Threads n r, [ThreadId]) Source #

Read a MVar, in either a blocking or nonblocking way.