dejafu-0.4.0.0: Systematic testing for Haskell concurrency.

Copyright(c) 2016 Michael Walker
LicenseMIT
MaintainerMichael Walker <mike@barrucadu.co.uk>
Stabilityexperimental
PortabilityExistentialQuantification, RankNTypes
Safe HaskellNone
LanguageHaskell2010

Test.DejaFu.STM.Internal

Contents

Description

MonadSTM testing implementation, internal types and definitions. This module is NOT considered to form part of the public interface of this library.

Synopsis

Documentation

type M n r a = Cont (STMAction n r) a Source #

The underlying monad is based on continuations over primitive actions.

Primitive actions

data STMAction n r Source #

STM transactions are represented as a sequence of primitive actions.

Constructors

Exception e => SCatch (e -> M n r a) (M n r a) (a -> STMAction n r) 
SRead (TVar r a) (a -> STMAction n r) 
SWrite (TVar r a) a (STMAction n r) 
SOrElse (M n r a) (M n r a) (a -> STMAction n r) 
SNew String a (TVar r a -> STMAction n r) 
Exception e => SThrow e 
SRetry 
SStop (n ()) 

TVars

newtype TVar r a Source #

A TVar is a tuple of a unique ID and the value contained. The ID is so that blocked transactions can be re-run when a TVar they depend on has changed.

Constructors

TVar (TVarId, r a) 

Output

data Result a Source #

The result of an STM transaction, along with which TVars it touched whilst executing.

Constructors

Success [TVarId] [TVarId] a

The transaction completed successfully, reading the first list TVars and writing to the second.

Retry [TVarId]

The transaction aborted by calling retry, and read the returned TVars. It should be retried when at least one of the TVars has been mutated.

Exception SomeException

The transaction aborted by throwing an exception.

Instances

Functor Result Source # 

Methods

fmap :: (a -> b) -> Result a -> Result b #

(<$) :: a -> Result b -> Result a #

Foldable Result Source # 

Methods

fold :: Monoid m => Result m -> m #

foldMap :: Monoid m => (a -> m) -> Result a -> m #

foldr :: (a -> b -> b) -> b -> Result a -> b #

foldr' :: (a -> b -> b) -> b -> Result a -> b #

foldl :: (b -> a -> b) -> b -> Result a -> b #

foldl' :: (b -> a -> b) -> b -> Result a -> b #

foldr1 :: (a -> a -> a) -> Result a -> a #

foldl1 :: (a -> a -> a) -> Result a -> a #

toList :: Result a -> [a] #

null :: Result a -> Bool #

length :: Result a -> Int #

elem :: Eq a => a -> Result a -> Bool #

maximum :: Ord a => Result a -> a #

minimum :: Ord a => Result a -> a #

sum :: Num a => Result a -> a #

product :: Num a => Result a -> a #

Show a => Show (Result a) Source # 

Methods

showsPrec :: Int -> Result a -> ShowS #

show :: Result a -> String #

showList :: [Result a] -> ShowS #

isSTMSuccess :: Result a -> Bool Source #

Check if a Result is a Success.

Execution

doTransaction :: MonadRef r n => M n r a -> IdSource -> n (Result a, n (), IdSource, TTrace) Source #

Run a STM transaction, returning an action to undo its effects.

stepTrans :: MonadRef r n => STMAction n r -> IdSource -> n (STMAction n r, n (), IdSource, [TVarId], [TVarId], TAction) Source #

Run a transaction for one step.