Safe Haskell | None |
---|
- class ComponentInterface s where
- type Send s
- type Receive s
- type State s
- initState :: s -> State s
- componentName :: s -> ComponentName
- componentBehaviour :: s -> State s -> Input (Receive s) -> Sim (State s)
- newtype Sim a = Sim {
- runSim :: SimInternal a
- data Input a
- = Message a ReturnAddress
- | Tick
- newtype ReturnAddress = RA {
- unRA :: (ComponentId, TVar Dynamic)
- type ComponentId = Unique
- type ComponentName = String
- type NodeId = Unique
- data ComponentContext = forall s . (ComponentInterface s, Typeable (Receive s)) => CC {
- componentIface :: s
- componentId :: ComponentId
- creator :: ComponentId
- currentStatus :: TVar (ComponentStatus s)
- componentState :: TVar (State s)
- msgBuffer :: TVar [Input Dynamic]
- traceMsgs :: [String]
- simMetaData :: TVar SimMetaData
- data ComponentStatus a
- = ReadyToIdle
- | WaitingFor ComponentId (() -> Sim (State a))
- | ReadyToRun
- | Killed
- data RequestOrYield request response x
- data Node = Node {}
- data SimMetaData = SimMetaData {}
- type SimMonad = StateT SimState STM
- type SimInternal = Coroutine (RequestOrYield Unique ()) SimMonad
- data SimState = SimState {}
- data NodeInfo = NodeInfo
SoOSiM API Types
class ComponentInterface s whereSource
Type class that defines an OS component
Type of messages send by the component
Type of messages received by the component
Type of internal state of the component
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
ComponentInterface HandlerStub |
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'
Sim | |
|
Events send to components by the simulator
Message a ReturnAddress | A message send another component: the field argument is the
|
Tick | Event send every simulation round |
newtype ReturnAddress Source
RA | |
|
type ComponentId = UniqueSource
type ComponentName = StringSource
SoOSiM Internal Types
data ComponentContext Source
Context of a running component in the simulator.
We need existential types because we need to make a single collection of several component contexts, each having their own type representing their internal state.
forall s . (ComponentInterface s, Typeable (Receive s)) => CC | |
|
data ComponentStatus a Source
Status of a running component
ReadyToIdle | Component is doing nothing |
WaitingFor ComponentId (() -> Sim (State a)) | Component is waiting for a message from |
ReadyToRun | Component is busy doing computations |
Killed | Module scheduled for deletion |
data RequestOrYield request response x Source
MonadUnique SimInternal | |
MonadState SimState SimInternal | |
Functor (RequestOrYield x f) |
Nodes represent computing entities in the simulator, and host the OS components and application threads
Node | |
|
data SimMetaData Source
SimMetaData | |
|
type SimMonad = StateT SimState STMSource
The internal monad of the simulator is currently a simple state-monad wrapping STM
type SimInternal = Coroutine (RequestOrYield Unique ()) SimMonadSource
The internal simulator state
SimState | |
|
MonadUnique SimMonad | |
MonadUnique SimInternal | |
MonadState SimState SimInternal | |
MonadState SimState Sim |