SoOSiM-0.2.1.0: Abstract full system simulator

Safe HaskellSafe-Infered

SoOSiM

Contents

Synopsis

Basic API

createComponentSource

Arguments

:: (ComponentInterface iface, Typeable (Receive iface)) 
=> iface

Component Interface

-> Sim ComponentId

ComponentId of the created component

Create a new component

invokeSource

Arguments

:: (ComponentInterface iface, Typeable (Receive iface), Typeable (Send iface)) 
=> iface

Interface type

-> ComponentId

ComponentId of callee

-> Receive iface

Argument

-> Sim (Send iface)

Response from callee

Synchronously invoke another component

invokeAsyncSource

Arguments

:: (ComponentInterface iface, Typeable (Receive iface), Typeable (Send iface)) 
=> iface

Interface type

-> ComponentId

ComponentId of callee

-> Receive iface

Argument

-> (Send iface -> Sim ())

Response Handler

-> Sim ()

Call returns immediately

Invoke another component, handle response asynchronously

respondSource

Arguments

:: (ComponentInterface iface, Typeable (Send iface)) 
=> iface

Interface type

-> ReturnAddress

Return address to send response to

-> Send iface

Value to send as response

-> Sim ()

Call returns immediately

Respond to an invocation

yield :: a -> Sim aSource

Yield internal state to the simulator scheduler

readMemorySource

Arguments

:: Int

Address to read

-> Sim Dynamic 

Read memory of local node

writeMemorySource

Arguments

:: Typeable a 
=> Int

Address to write

-> a

Value to write

-> Sim () 

Write memory of local node

componentLookupSource

Arguments

:: ComponentInterface iface 
=> iface

Interface type of the component you are looking for

-> Sim (Maybe ComponentId)

Just ComponentID if a component is found, Nothing otherwise

Get the unique ComponentId of a component implementing an interface

createNodeSource

Arguments

:: Sim NodeId

NodeId of the created node

Create a new node

Advanced API

runSTM :: STM a -> Sim aSource

getComponentId :: Sim ComponentIdSource

Get the component id of your component

getNodeId :: Sim NodeIdSource

Get the node id of of the node your component is currently running on

componentCreator :: Sim ComponentIdSource

Return the ComponentId of the component that created the current component

Specialized API

createComponentNSource

Arguments

:: (ComponentInterface iface, Typeable (Receive iface)) 
=> iface

Component Interface

-> NodeId 
-> Sim ComponentId 

Create a new component

createComponentNPSource

Arguments

:: (ComponentInterface iface, Typeable (Receive iface)) 
=> NodeId

Node to create component on, leave to Nothing to create on current node

-> ComponentId

ComponentId to set as parent, set to Nothing to use own ComponentId

-> iface

Component Interface

-> Sim ComponentId

ComponentId of the created component

Create a new component

invokeSSource

Arguments

:: forall iface . (ComponentInterface iface, Typeable (Receive iface), Typeable (Send iface)) 
=> iface

Interface type

-> Maybe ComponentId

Caller, leave Nothing to set to current module

-> ComponentId

Callee

-> Receive iface

Argument

-> Sim (Send iface)

Response from recipient

Synchronously invoke another component

invokeAsyncSSource

Arguments

:: forall iface . (ComponentInterface iface, Typeable (Receive iface), Typeable (Send iface)) 
=> iface

Interface type

-> Maybe ComponentId

Parent of handler, leave Nothing to set to the current module

-> ComponentId

Callee

-> Receive iface

Argument

-> (Send iface -> Sim ())

Handler

-> Sim ()

Call returns immediately

Invoke another component, handle response asynchronously

respondSSource

Arguments

:: forall iface . (ComponentInterface iface, Typeable (Send iface)) 
=> iface

Interface type

-> Maybe ComponentId

Callee Id, leave Nothing to set to current module

-> ReturnAddress

Return address

-> Send iface

Value to send as response

-> Sim ()

Call returns immediately

Respond to an invocation

readMemoryNSource

Arguments

:: Maybe NodeId

Node you want to look on, leave Nothing to set to current node

-> Int

Address to read

-> Sim Dynamic 

Read memory of local node

writeMemoryNSource

Arguments

:: Typeable a 
=> Maybe NodeId

Node you want to write on, leave Nothing to set to current node

-> Int

Address to write

-> a

Value to write

-> Sim () 

Write memory of local node

SoOSiM API Types

class ComponentInterface s whereSource

Type class that defines an OS component

Associated Types

type Send s Source

Type of messages send by the component

type Receive s Source

Type of messages received by the component

type State s Source

Type of internal state of the component

Methods

initState :: s -> State sSource

The minimal internal state of your component

componentName :: s -> ComponentNameSource

A function returning the unique global name of your component

componentBehaviour :: s -> State s -> Input (Receive s) -> Sim (State s)Source

The function defining the behaviour of your component

Instances

ComponentInterface HandlerStub 

data Input a Source

Events send to components by the simulator

Constructors

Message a ReturnAddress

A message send another component: the field argument is the ComponentId of the sender, the second field the message content

Tick

Event send every simulation round

Instances

Show (Input a) 

data Sim a Source

The simulator monad used by the OS components offers resumable computations in the form of coroutines. These resumable computations expect a value of type Dynamic, and return a value of type a.

We need resumable computations to simulate synchronous messaging between two components. When a component synchronously sends a message to another component, we store the rest of the computation as part of the execution context in the simulator state. When a message is send back, the stored computation will continue with the message content (of type Dynamic).

To suspend a computation you simply do: 'request componentId'

Where the componentId is the ID of the OS component you are expecting a message from. The execute a resumeable computation you simply do: 'resume comp'

Instances

type ComponentId = UniqueSource

type NodeId = UniqueSource

Imported Types

class Typeable a

The class Typeable allows a concrete representation of a type to be calculated.

data Dynamic

A value of type Dynamic is an object encapsulated together with its type.

A Dynamic may only represent a monomorphic value; an attempt to create a value of type Dynamic from a polymorphically-typed expression will result in an ambiguity error (see toDyn).

Showing a value of type Dynamic returns a pretty-printed representation of the object's type; useful for debugging.

Progress The Simulator

Utility Functions

unmarshall :: forall a. Typeable a => String -> Dynamic -> aSource