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

Copyright(c) 2017--2018 Michael Walker
LicenseMIT
MaintainerMichael Walker <mike@barrucadu.co.uk>
Stabilityexperimental
PortabilityExistentialQuantification, NoMonoLocalBinds, RecordWildCards, TypeFamilies
Safe HaskellNone
LanguageHaskell2010

Test.DejaFu.Conc.Internal.STM

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

The ModelSTM monad

newtype ModelSTM n a Source #

The underlying monad is based on continuations over primitive actions.

This is not Cont because we want to give it a custom MonadFail instance.

Constructors

ModelSTM 

Fields

Instances
Monad (ModelSTM n) Source # 
Instance details

Defined in Test.DejaFu.Conc.Internal.STM

Methods

(>>=) :: ModelSTM n a -> (a -> ModelSTM n b) -> ModelSTM n b #

(>>) :: ModelSTM n a -> ModelSTM n b -> ModelSTM n b #

return :: a -> ModelSTM n a #

fail :: String -> ModelSTM n a #

Functor (ModelSTM n) Source # 
Instance details

Defined in Test.DejaFu.Conc.Internal.STM

Methods

fmap :: (a -> b) -> ModelSTM n a -> ModelSTM n b #

(<$) :: a -> ModelSTM n b -> ModelSTM n a #

MonadFail (ModelSTM n) Source # 
Instance details

Defined in Test.DejaFu.Conc.Internal.STM

Methods

fail :: String -> ModelSTM n a #

Applicative (ModelSTM n) Source # 
Instance details

Defined in Test.DejaFu.Conc.Internal.STM

Methods

pure :: a -> ModelSTM n a #

(<*>) :: ModelSTM n (a -> b) -> ModelSTM n a -> ModelSTM n b #

liftA2 :: (a -> b -> c) -> ModelSTM n a -> ModelSTM n b -> ModelSTM n c #

(*>) :: ModelSTM n a -> ModelSTM n b -> ModelSTM n b #

(<*) :: ModelSTM n a -> ModelSTM n b -> ModelSTM n a #

Alternative (ModelSTM n) Source # 
Instance details

Defined in Test.DejaFu.Conc.Internal.STM

Methods

empty :: ModelSTM n a #

(<|>) :: ModelSTM n a -> ModelSTM n a -> ModelSTM n a #

some :: ModelSTM n a -> ModelSTM n [a] #

many :: ModelSTM n a -> ModelSTM n [a] #

MonadPlus (ModelSTM n) Source # 
Instance details

Defined in Test.DejaFu.Conc.Internal.STM

Methods

mzero :: ModelSTM n a #

mplus :: ModelSTM n a -> ModelSTM n a -> ModelSTM n a #

MonadSTM (ModelSTM n) Source # 
Instance details

Defined in Test.DejaFu.Conc.Internal.STM

Associated Types

type TVar (ModelSTM n) :: Type -> Type #

Methods

newTVar :: a -> ModelSTM n (TVar (ModelSTM n) a) #

newTVarN :: String -> a -> ModelSTM n (TVar (ModelSTM n) a) #

readTVar :: TVar (ModelSTM n) a -> ModelSTM n a #

writeTVar :: TVar (ModelSTM n) a -> a -> ModelSTM n () #

MonadThrow (ModelSTM n) Source # 
Instance details

Defined in Test.DejaFu.Conc.Internal.STM

Methods

throwM :: Exception e => e -> ModelSTM n a #

MonadCatch (ModelSTM n) Source # 
Instance details

Defined in Test.DejaFu.Conc.Internal.STM

Methods

catch :: Exception e => ModelSTM n a -> (e -> ModelSTM n a) -> ModelSTM n a #

type TVar (ModelSTM n) Source # 
Instance details

Defined in Test.DejaFu.Conc.Internal.STM

type TVar (ModelSTM n) = ModelTVar n

Primitive actions

data STMAction n Source #

STM transactions are represented as a sequence of primitive actions.

Constructors

Exception e => SCatch (e -> ModelSTM n a) (ModelSTM n a) (a -> STMAction n) 
SRead (ModelTVar n a) (a -> STMAction n) 
SWrite (ModelTVar n a) a (STMAction n) 
SOrElse (ModelSTM n a) (ModelSTM n a) (a -> STMAction n) 
SNew String a (ModelTVar n a -> STMAction n) 
Exception e => SThrow e 
SRetry 
SStop (n ()) 

TVars

data ModelTVar n a Source #

A TVar is modelled as a unique ID and a reference holding a value.

Constructors

ModelTVar 

Fields

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
Show a => Show (Result a) Source # 
Instance details

Defined in Test.DejaFu.Conc.Internal.STM

Methods

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

show :: Result a -> String #

showList :: [Result a] -> ShowS #

Execution

runTransaction :: MonadConc n => ModelSTM n a -> IdSource -> n (Result a, IdSource, [TAction]) Source #

Run a transaction, returning the result and new initial TVarId. If the transaction failed, any effects are undone.

doTransaction :: MonadConc n => ModelSTM n a -> IdSource -> n (Result a, n (), IdSource, [TAction]) Source #

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

If the transaction fails, its effects will automatically be undone, so the undo action returned will be pure ().

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

Run a transaction for one step.