IOSpec-0.3.1.1: A pure specification of the IO monad.

Safe HaskellSafe
LanguageHaskell98

Test.IOSpec.VirtualMachine

Contents

Description

The virtual machine on which the specifications execute.

Synopsis

The Virtual Machine

type VM a = StateT Store Effect a Source #

The VM monad is essentially a state monad, modifying the store. Besides returning pure values, various primitive effects may occur, such as printing characters or failing with an error message.

type Loc = Int Source #

data ThreadId Source #

Instances
Eq ThreadId Source # 
Instance details

Defined in Test.IOSpec.VirtualMachine

Show ThreadId Source # 
Instance details

Defined in Test.IOSpec.VirtualMachine

Arbitrary ThreadId Source # 
Instance details

Defined in Test.IOSpec.VirtualMachine

CoArbitrary ThreadId Source # 
Instance details

Defined in Test.IOSpec.VirtualMachine

Methods

coarbitrary :: ThreadId -> Gen b -> Gen b #

Primitive operations on the VM

alloc :: VM Loc Source #

The alloc function allocate a fresh location on the heap.

emptyLoc :: Loc -> VM () Source #

The emptyLoc function removes the data stored at a given location. This corresponds, for instance, to emptying an MVar.

freshThreadId :: VM ThreadId Source #

The freshThreadId function returns a previously unallocated ThreadId.

finishThread :: ThreadId -> VM () Source #

The finishThread function kills the thread with the specified ThreadId.

lookupHeap :: Loc -> VM (Maybe Data) Source #

The lookupHeap function returns the data stored at a given heap location, if there is any.

mainTid :: ThreadId Source #

The mainTid constant is the ThreadId of the main process.

readChar :: VM Char Source #

The readChar and printChar functions are the primitive counterparts of getChar and putChar in the VM monad.

updateHeap :: Loc -> Data -> VM () Source #

The updateHeap function overwrites a given location with new data.

updateSoup :: Executable f => ThreadId -> IOSpec f a -> VM () Source #

The updateSoup function updates the process associated with a given ThreadId.

The observable effects on the VM

data Effect a Source #

The Effect type contains all the primitive effects that are observable on the virtual machine.

Constructors

Done a 
ReadChar (Char -> Effect a) 
Print Char (Effect a) 
Fail String 
Instances
Monad Effect Source # 
Instance details

Defined in Test.IOSpec.VirtualMachine

Methods

(>>=) :: Effect a -> (a -> Effect b) -> Effect b #

(>>) :: Effect a -> Effect b -> Effect b #

return :: a -> Effect a #

fail :: String -> Effect a #

Functor Effect Source # 
Instance details

Defined in Test.IOSpec.VirtualMachine

Methods

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

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

Applicative Effect Source # 
Instance details

Defined in Test.IOSpec.VirtualMachine

Methods

pure :: a -> Effect a #

(<*>) :: Effect (a -> b) -> Effect a -> Effect b #

liftA2 :: (a -> b -> c) -> Effect a -> Effect b -> Effect c #

(*>) :: Effect a -> Effect b -> Effect b #

(<*) :: Effect a -> Effect b -> Effect a #

Eq a => Eq (Effect a) Source # 
Instance details

Defined in Test.IOSpec.VirtualMachine

Methods

(==) :: Effect a -> Effect a -> Bool #

(/=) :: Effect a -> Effect a -> Bool #

Sample schedulers

There are two example scheduling algorithms roundRobin and singleThreaded. Note that Scheduler is also an instance of Arbitrary. Using QuickCheck to generate random schedulers is a great way to maximise the number of interleavings that your tests cover.

roundRobin :: Scheduler Source #

The roundRobin scheduler provides a simple round-robin scheduler.

singleThreaded :: Scheduler Source #

The singleThreaded scheduler will never schedule forked threads, always scheduling the main thread. Only use this scheduler if your code is not concurrent.

Executing code on the VM

class Functor f => Executable f where Source #

The Executable type class captures all the different types of operations that can be executed in the VM monad.

Methods

step :: f a -> VM (Step a) Source #

Instances
Executable Teletype Source # 
Instance details

Defined in Test.IOSpec.Teletype

Methods

step :: Teletype a -> VM (Step a) Source #

Executable STMS Source # 
Instance details

Defined in Test.IOSpec.STM

Methods

step :: STMS a -> VM (Step a) Source #

Executable MVarS Source # 
Instance details

Defined in Test.IOSpec.MVar

Methods

step :: MVarS a -> VM (Step a) Source #

Executable IORefS Source #

The Executable instance for the IORefS monad.

Instance details

Defined in Test.IOSpec.IORef

Methods

step :: IORefS a -> VM (Step a) Source #

Executable ForkS Source # 
Instance details

Defined in Test.IOSpec.Fork

Methods

step :: ForkS a -> VM (Step a) Source #

(Executable f, Executable g) => Executable (f :+: g) Source # 
Instance details

Defined in Test.IOSpec.VirtualMachine

Methods

step :: (f :+: g) a -> VM (Step a) Source #

data Step a Source #

Constructors

Step a 
Block 

runIOSpec :: Executable f => IOSpec f a -> Scheduler -> Effect (a, Store) Source #

The runIOSpec function is the heart of this library. Given the scheduling algorithm you want to use, it will run a value of type IOSpec f a, returning the sequence of observable effects together with the final store.

evalIOSpec :: Executable f => IOSpec f a -> Scheduler -> Effect a Source #

The evalIOSpec function returns the effects a computation yields, but discards the final state of the virtual machine.

execIOSpec :: Executable f => IOSpec f a -> Scheduler -> Store Source #

The execIOSpec returns the final Store after executing a computation.

Beware: this function assumes that your computation will succeed, without any other visible Effect. If your computation reads a character from the teletype, for instance, it will return an error.