waitfree-0.1.4: A wrapping library for waitfree computation.

Control.Concurrent.Waitfree

Synopsis

Documentation

data ZeroT Source

Instances

data SucT t Source

'SucT t' is a Thread if t is a Thread. The name SucT comes from the successor function.

Instances

Thread t => Thread (SucT t) 

data HNil Source

HNil is the empty IOerSequent

Instances

Lconvertible HNil 
IOerSequent HNil 
IOerSequent l => HAppend HNil l l 
HLast (HCons a HNil) a HNil 

data HCons e l Source

'HCons (K t e)' adds a remote computation in front of a IOerSequent

Instances

(Thread t, Lconvertible l) => Lconvertible (HCons (K t ThreadStatus) l) 
IOerSequent l => IOerSequent (HCons (K t e) l) 
HLast (HCons a HNil) a HNil 
HLast (HCons lh ll) a heads => HLast (HCons b (HCons lh ll)) a (HCons b heads) 
(IOerSequent l, HAppend l l' l'') => HAppend (HCons x l) l' (HCons x l'') 

type :*: e l = HCons e lSource

an abreviation for HCons

data K t a Source

A value of type 'K t a' represents a remote computation returning a that is performed by a thread t.

Instances

(Thread t, Lconvertible l) => Lconvertible (HCons (K t ThreadStatus) l) 
IOerSequent l => IOerSequent (HCons (K t e) l) 

single :: Thread t => (t -> IO a) -> IO (K t a :*: HNil)Source

single creates a IO hypersequent consisting of a single remote computation.

class Thread t whereSource

An abstract representation of a thread. Threads are actually implemented using forkIO.

Instances

comm :: (Thread s, Thread t, HAppend l l' l'') => IO (HCons (K t (b, a)) l) -> (t -> b -> IO ThreadStatus) -> IO (HCons (K s (d, c)) l') -> (s -> d -> IO ThreadStatus) -> IO (K t (b, c) :*: (K s (d, a) :*: l''))Source

comm stands for communication. comm combines two hypersequents with a communicating component from each hypersequent. | 'comm hypersequent1 error1 hypersequent2 error2' where error1 and error2 specifies what to do in case of read failure.

follows :: HAppend l l' l'' => IO l -> IO l' -> IO l''Source

cycling :: HLast l last heads => IO l -> IO (HCons last heads)Source

execute :: Lconvertible l => IO l -> IO ()Source

execute executes a IO hypersequent.

(-*-) :: (Thread t, IOerSequent l, IOerSequent l') => (t -> a -> IO b) -> (l -> IO l') -> HCons (K t a) l -> IO (HCons (K t b) l')Source

extend a IO hypersequent with another computation

data ThreadStatus Source

ThreadStatus shows whether a thread is finished or have to try executing another job.

Constructors

TryAnotherJob 
Finished 

Instances

(Thread t, Lconvertible l) => Lconvertible (HCons (K t ThreadStatus) l)