MesaRuntime>Processes.mesa (August 26, 1982 11:22 am by Levin)
DIRECTORY
CPSwapDefs USING [ProcessState],
Environment USING [Long, PageCount, PageNumber, wordsPerPage],
Frame USING [Alloc, Free, GetReturnFrame, MyLocalFrame],
Inline USING [BITAND, BITNOT, BITOR, BITSHIFT, COPY],
PrincOps USING [ControlLink, Frame,
FrameHandle, FrameSizeIndex, NullFrame, NullLink, StateVector],
Process USING [Milliseconds, Priority, Ticks],
ProcessInternal USING [DisableInterrupts, EnableInterrupts],
ProcessOperations USING [
Broadcast, EnableAndRequeue, Enter, Exit, HandleToIndex, IndexToHandle,
Notify, ReadPSB, ReEnter, Requeue, Wait, WritePSB, WriteWDC],
ProcessPriorities USING [
priorityClient, priorityClientHigh, priorityClientLow, priorityRealTime],
ProcessorFace USING [millisecondsPerTick, reservedNakedNotifyMask],
PSB USING [
Condition, ConditionVariable, FaultIndex, InterruptItem, Monitor, NoTimeout,
NullPsbHandle, NullStateVectorHandle, PDA, PDABase, Priority,
ProcessDataArea, ProcessStateBlock, PsbHandle, PsbIndex,
PsbNull, Queue, StartPsb, StateVectorHandle, Ticks, UnlockedEmpty],
RuntimeInternal USING [FrameSize],
RuntimePrograms USING [],
SDDefs USING [SD, sFork, sJoin, sProcessTrap],
StartList USING [Base],
StoragePrograms USING [tableBase];
Processes: MONITOR
LOCKS processLock
IMPORTS Frame, Inline, ProcessInternal, ProcessorFace,
ProcessOperations, RuntimeInternal, StoragePrograms
EXPORTS Process, ProcessInternal, RuntimePrograms =
BEGIN OPEN PSB, ProcessOperations;
priorityBackground: PUBLIC Process.Priority ← ProcessPriorities.priorityClientLow;
priorityForeground: PUBLIC Process.Priority ← ProcessPriorities.priorityClientHigh;
priorityInterrupt: PUBLIC Process.Priority ← ProcessPriorities.priorityRealTime;
priorityNormal: PUBLIC Process.Priority ← ProcessPriorities.priorityClient;
ConditionVariable: TYPE = PSB.ConditionVariable;
FrameSizeIndex: TYPE = PrincOps.FrameSizeIndex;
--PrincOps.--FsiFrame: TYPE = MACHINE DEPENDENT RECORD [
fsi (0): FrameSizeIndex, -- must be at 3 MOD 4 boundary.
frame (1): local PrincOps.Frame];
assert1: [FIRST[Process.Priority]..FIRST[Process.Priority]] =
FIRST[PSB.Priority];
assert2: [LAST[Process.Priority]..LAST[Process.Priority]] =
LAST[PSB.Priority];
assert3: [FIRST[Process.Ticks]..FIRST[Process.Ticks]] = FIRST[PSB.Ticks];
assert4: [LAST[Process.Ticks]..LAST[Process.Ticks]] = LAST[PSB.Ticks]; ++ waiting on AR6834.
assert5: [PSB.NoTimeout..PSB.NoTimeout] = 0; -- (see next statement.)
collisionTimeout: PSB.Ticks = PSB.NoTimeout+1; -- value to use if client
wants timeout numerically equal to NoTimeout.
ProcessState: TYPE = CPSwapDefs.ProcessState;
ProcState: -- for access to ProcessState field.
PROCEDURE [psbh: PsbHandle] RETURNS [ProcessState] =
INLINE { RETURN[LOOPHOLE[pda[psbh].flags.available, ProcessState]] };
NakedNotifyLevel: TYPE = [0..16);
DyingFrameHandle: TYPE = POINTER TO dying PrincOps.Frame;
InvalidProcess: PUBLIC ERROR [process: PsbIndex] = CODE;
TooManyProcesses: PUBLIC ERROR = CODE;
Queues of processes which are..
rebirth: CONDITION; -- ..unused.
frameReady: CONDITION; -- ..parents waiting to rejoin their child.
frameTaken: CONDITION; -- ..children waiting to rejoin their parent.
dead: CONDITION; -- ..parents waiting for their child to clean up.
pda: PSB.PDABase = PSB.PDA;
processLock: MONITORLOCK;
busyLevels: WORD; -- bit-mask of busy naked-notify levels
(numbered right-to-left)
deadFrame: DyingFrameHandle ← NIL; -- the top-level frame of a
detached process which needs to be freed.
Bug: PRIVATE ERROR [type: BugType] = CODE;
BugType: TYPE =
{insufficientMappedPDA, noMoreNakedNotifyLevels, noSuchCondition};
~~~~~~~~~~~~ Initialization ~~~~~~~~~~~~
--RuntimePrograms.--InitializeProcesses: PUBLIC PROCEDURE
[pagePDA: Environment.PageNumber, countPDA: Environment.PageCount] =
(pagePDA is not used.)
BEGIN
AlignUp: PROC [unaligned, modulus: UNSPECIFIED] RETURNS [aligned: UNSPECIFIED] =
INLINE { RETURN[ ((unaligned + modulus-1) / modulus) * modulus] };
AlignDown: PROC [unaligned, modulus: UNSPECIFIED] RETURNS [aligned: UNSPECIFIED] =
INLINE { RETURN[unaligned - unaligned MOD modulus] };
rAlloc: PDABase RELATIVE POINTER TO UNSPECIFIED; -- allocation pointer.
DisableTimeout[@dead];
DisableTimeout[@frameReady];
DisableTimeout[@frameTaken];
DisableTimeout[@rebirth];
SDDefs.SD[SDDefs.sProcessTrap] ← ProcessTrap;
SDDefs.SD[SDDefs.sFork] ← Fork;
SDDefs.SD[SDDefs.sJoin] ← Join;
We will start at the end of the PDA and allocate downwards:
rAlloc ← LOOPHOLE[countPDA*Environment.wordsPerPage];
Allocate StateVector pool:
BEGIN
alignmentStateVector: CARDINAL = 4; -- (a D0 requirement)
sizeStateVector: CARDINAL
= AlignUp[MAX[SIZE[PrincOps.StateVector],
StoragePrograms.tableBase.stateVectorSize],
alignmentStateVector];
rState: PSB.StateVectorHandle;
rState ← AlignDown[rAlloc, alignmentStateVector];
FOR pri: PSB.Priority IN PSB.Priority DO
pda.state[pri] ← PSB.NullStateVectorHandle;
FOR k: CARDINAL IN
[0..StoragePrograms.tableBase.stateVectorCounts[pri]) DO
IF LOOPHOLE[rState, CARDINAL]<sizeStateVector THEN
ERROR Bug[insufficientMappedPDA];
rState ← rState - sizeStateVector;
pda[rState].stk[0] ← pda.state[pri]; -- chain onto list..
pda.state[pri] ← rState;
ENDLOOP;
ENDLOOP;
rAlloc ← rState;
END;
BEGIN
Find number of {PSB, timeout words} that will fit in space remaining:
(considering TimeoutVector alignment and unused TimeoutVector
positions.)
sizePSBTimeout: CARDINAL -- (does not include alignment filler)
= SIZE[ProcessStateBlock] + --interruptVectorWord--SIZE[Ticks];
alignmentTimeoutVector: CARDINAL = 16; -- (PrincOps requirement)
rStartPsb: PDABase RELATIVE POINTER TO UNSPECIFIED
= LOOPHOLE[IndexToHandle[StartPsb]];
totalPsbs: CARDINAL;
pda.count ← 0;
FOR nUseful: CARDINAL
DECREASING IN [0..(rAlloc - rStartPsb)/sizePSBTimeout]
--UNTIL nUseful Psbs will fit in available space-- DO
totalPsbs ← StartPsb + nUseful;
pda.timeout ← AlignDown[rAlloc-totalPsbs, alignmentTimeoutVector];
IF (LOOPHOLE[pda.timeout, CARDINAL]+StartPsb -- (first used word
of timeout vector)
- LOOPHOLE[rStartPsb, CARDINAL])
/ SIZE[ProcessStateBlock] >= nUseful THEN
{pda.count ← nUseful; EXIT}; -- that many Psbs fit in avail space.
REPEAT
FINISHED => ERROR Bug[insufficientMappedPDA];
ENDLOOP;
IF pda.count <= 1 THEN ERROR Bug[insufficientMappedPDA];
END;
Initialize TimeoutVector:
(Note: TimeoutVector unused portions overlay Psbs)
FOR psb: PsbIndex IN [StartPsb..StartPsb+pda.count) DO
pda[pda.timeout][psb] ← NoTimeout;
ENDLOOP;
Initialize first PSB to describe self - detached:
pda.block[StartPsb] ← ProcessStateBlock[
link: [failed: FALSE, priority: FIRST[Priority], next: StartPsb,
vector: NULL],
flags: [available: LOOPHOLE[ProcessState[state: alive, detached: TRUE]],
cleanup: PsbNull, waiting: FALSE, abort: FALSE],
context: NULL,
TEMP until microcode uses timeout vector:
mds: Inline.HighHalf[LONG[LOOPHOLE[1, POINTER]]] ];
mds: NoTimeout ];
WritePSB[IndexToHandle[StartPsb]]; -- tell the processor.
TEMP until microcode takes current Psb off readyList:
pda.ready ← Queue[tail: PsbNull];
pda.ready ← Queue[tail: StartPsb];
Finish making self be detached:
Note that someone must have previously set the return link of the topmost frame to PrincOps.NullFrame.
FOR root: PrincOps.FrameHandle ← Frame.MyLocalFrame[],
root.returnlink.frame DO
IF root.returnlink.frame = PrincOps.NullFrame THEN
{ root.returnlink ←
LOOPHOLE[End, procedure PrincOps.ControlLink];
EXIT };
ENDLOOP;
Put rest of PSBs into free pool: (chained off "rebirth" condition)
The free list is set so that each successive new process created
will have a lower PsbIndex, thus causing the most-recently-created
processes to be listed first by CoPilot.
BEGIN
firstFree: PsbIndex ← StartPsb+1;
lastFree: PsbIndex ← StartPsb+pda.count-1;
LOOPHOLE[rebirth, ConditionVariable].condition.tail ← PsbNull;
FOR psb: PsbIndex IN [firstFree..lastFree] DO
pda.block[psb].link.next ← IF psb=firstFree THEN lastFree ELSE psb-1;
Tell CoPilot that process is not in use:
LOOPHOLE[pda.block[psb].flags.available, ProcessState].state ← dead;
TEMP until microcode uses timeout vector:
pda.block[psb].mds ← NoTimeout;
REPEAT
FINISHED =>
LOOPHOLE[rebirth, ConditionVariable].condition.tail ← firstFree;
ENDLOOP;
END;
Initialize FaultVector:
FOR flt: FaultIndex IN FaultIndex DO
pda.fault[flt] ←
[queue: [tail: PsbNull],
condition: [tail: PsbNull, abortable: FALSE, wakeup: FALSE] ];
ENDLOOP;
Initialize naked-notify allocator:
busyLevels ← ProcessorFace.reservedNakedNotifyMask;
ProcessOperations.WriteWDC[0]; -- start interrupts.
END;
~~~~~~~~~~ EXTERNAL Procedures ~~~~~~~~~~
DisableAborts: PUBLIC --EXTERNAL--
PROCEDURE [pCondition: LONG POINTER TO CONDITION] =
{ LOOPHOLE[pCondition^, ConditionVariable]
.condition.abortable ← FALSE };
DisableTimeout: PUBLIC --EXTERNAL--
PROCEDURE [pCondition: LONG POINTER TO CONDITION] =
{ pCondition.timeout ← NoTimeout };
EnableAborts: PUBLIC --EXTERNAL--
PROCEDURE [pCondition: LONG POINTER TO CONDITION] =
{ LOOPHOLE[pCondition^, ConditionVariable]
.condition.abortable ← TRUE};
GetCurrent: PUBLIC --EXTERNAL-- PROCEDURE RETURNS [psbHandle: PROCESS] =
{ RETURN[ LOOPHOLE[HandleToIndex[ReadPSB[]], PROCESS] ] };
GetPriority: PUBLIC --EXTERNAL since atomic action-- SAFE PROCEDURE []
RETURNS [priority: Process.Priority] = TRUSTED {
RETURN[pda[ReadPSB[]].link.priority]};
InitializeCondition: PUBLIC --EXTERNAL--
PROCEDURE [condition: LONG POINTER TO CONDITION, ticks: Process.Ticks] =
{ LOOPHOLE[condition^, ConditionVariable] ←
[ condition: [tail: PsbNull, abortable: FALSE, wakeup: FALSE],
timeout: IF ticks=NoTimeout THEN collisionTimeout ELSE ticks ] };
InitializeMonitor: PUBLIC --EXTERNAL--
PROCEDURE [pMonitor: LONG POINTER TO MONITORLOCK] =
{ LOOPHOLE[pMonitor^, PSB.Monitor] ← UnlockedEmpty };
MsecToTicks: PUBLIC --EXTERNAL-- SAFE PROCEDURE [ms: Process.Milliseconds]
RETURNS [Process.Ticks] = TRUSTED
{ RETURN[
( IF ms >= LAST[Process.Milliseconds]-
(ProcessorFace.millisecondsPerTick-1)
THEN LAST[Process.Milliseconds] -- (avoid overflow)
ELSE ms + ProcessorFace.millisecondsPerTick-1 )
/ ProcessorFace.millisecondsPerTick ] };
ProcessTrap: --EXTERNAL-- PROCEDURE RETURNS [BOOLEAN] =
(called when an aborted process attempts to reenter its monitor.)
BEGIN
Enter: PROCEDURE [a: POINTER TO MONITORLOCK] RETURNS [BOOLEAN] =
LOOPHOLE[ProcessOperations.Enter];
LongEnter: PROCEDURE [a,b: --LONG POINTER TO MONITORLOCK--UNSPECIFIED]
RETURNS [BOOLEAN] =
LOOPHOLE[ProcessOperations.Enter];
abortee: PrincOps.FrameHandle;
state: RECORD [filler: UNSPECIFIED, v: PrincOps.StateVector];
state.v ← STATE;
Acquire abortee's monitor lock:
UNTIL
(IF state.v.stkptr = 4 THEN
LongEnter[state.v.stk[0], state.v.stk[1]]
ELSE Enter[LOOPHOLE[state.v.stk[0], POINTER TO MONITORLOCK]] )
DO ENDLOOP;
abortee ← Frame.GetReturnFrame[];
abortee.pc ← [abortee.pc + 1]; -- step past ME(L) instruction.
pda[ReadPSB[]].flags.abort ← FALSE;
ERROR ABORTED;
if ABORTED is made resumable, we should return [monitorEntered: TRUE]
as the result of the MonitorEnter instruction that got us here.
END;
SetPriority: PUBLIC --EXTERNAL-- PROCEDURE [p: Process.Priority] =
BEGIN
h: PsbHandle;
h ← ReadPSB[];
pda[h].link.priority ← p;
ProcessInternal.DisableInterrupts[]; -- (to cancel subsequent enable)
move to appropriate spot in ready queue:
EnableAndRequeue[@pda.ready, @pda.ready, h];
END;
SecondsToTicks: PUBLIC --EXTERNAL--
SAFE PROCEDURE [sec: CARDINAL] RETURNS [Process.Ticks] = TRUSTED
BEGIN
ticks: Environment.Long = [lc[
(LONG[sec]*LONG[1000] + ProcessorFace.millisecondsPerTick-1)
/ ProcessorFace.millisecondsPerTick]];
RETURN[IF ticks.highbits ~= 0 THEN LAST[Ticks] ELSE ticks.lowbits]
END;
SetTimeout: PUBLIC --EXTERNAL-- PROCEDURE
[condition: LONG POINTER TO CONDITION, ticks: Process.Ticks] =
{condition.timeout ← IF ticks=NoTimeout THEN collisionTimeout ELSE ticks};
TicksToMsec: PUBLIC --EXTERNAL-- SAFE PROCEDURE [ticks: Ticks]
RETURNS [Process.Milliseconds] = TRUSTED
{RETURN[
IF ticks > LAST[Process.Milliseconds]/ProcessorFace.millisecondsPerTick
THEN LAST[Process.Milliseconds]
ELSE ticks*ProcessorFace.millisecondsPerTick ] };
Yield: PUBLIC --EXTERNAL-- SAFE PROCEDURE = TRUSTED
{ ProcessInternal.DisableInterrupts[]; -- (to cancel subsequent enable)
EnableAndRequeue[@pda.ready, @pda.ready, ReadPSB[]] };
~~~~~~~~~~~~ ENTRY Procedures ~~~~~~~~~~~~
Abort: PUBLIC ENTRY PROCEDURE [process: PsbIndex] =
BEGIN
h: PsbHandle;
IF (h ← ValidProcess[process]) = NullPsbHandle THEN
RETURN WITH ERROR InvalidProcess[process];
ProcessInternal.DisableInterrupts[]; -- (also stops
ProcessTimeoutCounter from ticking.)
IF ProcState[h].state = alive THEN {
pda[h].flags.abort ← TRUE;
IF pda[h].flags.waiting THEN -- Wake the victim up..--
{ pda[h].flags.waiting ← FALSE;
pda[pda.timeout][HandleToIndex[h]] ← NoTimeout;
TEMP until microcode uses timeout vector:
pda[h].--timeout--mds ← NoTimeout;
Requeue[NIL, @pda.ready, h] }};
ProcessInternal.EnableInterrupts[];
END;
--ProcessInternal.--AllocateNakedCondition: PUBLIC ENTRY PROC []
RETURNS [cv: LONG POINTER TO CONDITION, mask: WORD] =
BEGIN
level: NakedNotifyLevel;
FOR level IN NakedNotifyLevel DO
mask ← Inline.BITSHIFT[1, LAST[NakedNotifyLevel] - level];
IF Inline.BITAND[mask, busyLevels] = 0 THEN
BEGIN
busyLevels ← Inline.BITOR[busyLevels, mask];
cv ← LOOPHOLE[@pda.interrupt[level]];
RETURN;
END;
ENDLOOP;
ERROR Bug[noMoreNakedNotifyLevels];
END;
--ProcessInternal.--DeallocateNakedCondition:
PUBLIC PROC [cv: LONG POINTER TO CONDITION] =
BEGIN
level: NakedNotifyLevel;
FOR level IN NakedNotifyLevel DO
mask: WORD ← Inline.BITSHIFT[1, LAST[NakedNotifyLevel] - level];
IF cv = LOOPHOLE[@pda.interrupt[level], LONG POINTER TO CONDITION] THEN
BEGIN
busyLevels ← Inline.BITAND[busyLevels, Inline.BITNOT[mask]];
pda.interrupt[level].condition.tail ← PsbNull;
RETURN;
END;
ENDLOOP;
ERROR Bug[noSuchCondition];
END;
Detach: PUBLIC ENTRY PROCEDURE [process: PROCESS] =
BEGIN
h: PsbHandle;
IF (h ← ValidProcess[process]) = NullPsbHandle THEN
RETURN WITH ERROR InvalidProcess[LOOPHOLE[process, UNSPECIFIED]];
LOOPHOLE[pda[h].flags.available, ProcessState].detached ← TRUE;
BROADCAST frameTaken; -- wake child if waiting to JOIN.
END;
End: --"ENTRY"-- PROCEDURE =
When the top context of a process "returns", it Xfers to
this procedure with its results on the stack.
BEGIN
sv: RECORD [filler: UNSPECIFIED, results: PrincOps.StateVector];
frame: DyingFrameHandle;
h: PsbHandle;
sv.results ← STATE; -- save stack containing returned results.
WHILE ~Enter[@processLock] DO NULL ENDLOOP;
frame ← LOOPHOLE[Frame.MyLocalFrame[]];
frame.state ← alive;
h ← ReadPSB[];
LOOPHOLE[pda[h].flags.available, ProcessState].state ← frameReady;
pda[h].flags.abort ← FALSE; -- too late for Aborts: they no-op
Broadcast[@frameReady]; -- wake any parent process waiting to Join.
Wait till this process is Detached or Joined:
UNTIL ProcState[h].state = frameTaken
OR ProcState[h].detached DO
Wait[@processLock, @frameTaken,
LOOPHOLE[frameTaken, ConditionVariable].timeout];
WHILE ~ReEnter[@processLock, @frameTaken] DO NULL ENDLOOP;
ENDLOOP;
Free any frame left over from a previous dead detached process:
IF deadFrame ~= NIL THEN {Frame.Free[deadFrame]; deadFrame ← NIL};
IF ProcState[h].detached THEN
deadFrame ← frame; -- If detached, leave our frame for freeing.
frame.state ← dead; -- tell Joiner that we're done.
LOOPHOLE[pda[h].flags.available, ProcessState].state ← dead;
Broadcast[@dead]; -- tell parent our frame has been left for freeing.
Wait[@processLock, @rebirth,
LOOPHOLE[rebirth, ConditionVariable].timeout];
This process is dead. Its PSB sits in the rebirth queue until
it is recycled into a new process by Fork.
Our current frame however, has one of two fates:
(a) If this process was detached, the frame will simply be freed
by the next process that finishes ("deadFrame").
(b) if this process is being Joined, the parent process will
have acquired a pointer to our frame. The JOIN code will Xfer
to our frame and the code below will be executed
BY THE PARENT PROCESS. The parent process therefore
MUST BE RUNNING IN THE SAME MDS as the child process!
WHILE ~ReEnter[@processLock, @rebirth] DO NULL ENDLOOP;
sv.results.dest ← LOOPHOLE[frame.returnlink, PrincOps.ControlLink]; -- (frame.returnlink was set by Join[] to point to the context of JOIN.)
sv.results.source ← PrincOps.NullLink;
Exit[@processLock];
Reload returned results into stack, return to parent:
RETURN WITH sv.results;
END;
Fork: --"ENTRY"-- PROCEDURE [--argsForRoot,-- root: PrincOps.ControlLink]
RETURNS [childPsb: PsbIndex] =
BEGIN
PForkFrame: TYPE = POINTER TO FRAME[Fork];
ChildBuilder: PROC [--parent's locals--] RETURNS [--MUST BE NULL!--] =
BEGIN
pChild: LONG POINTER TO ProcessStateBlock ← @pda.block[childPsb];
parentFrame: PForkFrame = LOOPHOLE[Frame.GetReturnFrame[]];
fsi: FrameSizeIndex = LOOPHOLE[
(parentFrame-1), POINTER TO FsiFrame].fsi;
childFrame: PForkFrame = Frame.Alloc[fsi];
Inline.COPY[from: parentFrame-1, to: childFrame-1,
nwords: RuntimeInternal.FrameSize[fsi] + SIZE[FrameSizeIndex] ];
childFrame.identity ← child;
pChild.link.failed ← FALSE;
pChild.link.priority ← pda[ReadPSB[]].link.priority;
pChild.flags ←
[available: LOOPHOLE[ProcessState[state: alive, detached: FALSE]],
cleanup: PsbNull, waiting: FALSE, abort: FALSE];
pChild.context ← [frame[LOOPHOLE[childFrame, PrincOps.FrameHandle]]];
TEMP until microcode uses timeout vector:
pChild.mds ← Inline.HighHalf[LONG[LOOPHOLE[1, POINTER]]];
pChild.mds ← NoTimeout;
pda[pda.timeout][childPsb] ← NoTimeout;
Notify[@rebirth]; -- starts the new process executing. Its PC
is set to begin execution at the instruction after the call
to ChildBuilder. Its stack is empty. Therefore,
ChildBuilder MUST NOT RETURN ANY RESULTS!
END;
identity: {parent, child};
argsForChild: PrincOps.StateVector;
("root" is automatically popped off the stack first.)
argsForChild ← STATE; -- must be first!
identity ← parent;
WHILE ~Enter[@processLock] DO NULL ENDLOOP;
IF LOOPHOLE[rebirth, ConditionVariable].condition.tail = PsbNull THEN
{ Exit[@processLock]; ERROR TooManyProcesses };
childPsb ← pda.block[LOOPHOLE[rebirth, ConditionVariable].condition.tail]
.link.next; -- walk to tail, then to head.
[] ← ChildBuilder[--my local vars--];
Both parent and child processes will execute the following code:
SELECT identity FROM
parent =>
{ Exit[@processLock];
RETURN[childPsb] }; -- return child handle to FORKing parent.
child =>
BEGIN
To simulate a procedure call, we must also store dest and
source links *above* the stack since ReturnWithState doesn't.
(stack pointer is *not* incremented.)
argsForChild.stk[argsForChild.stkptr] ← root;
argsForChild.dest ← root;
Set child's top context to call End when it returns:
argsForChild.stk[argsForChild.stkptr+1] ← End;
argsForChild.source ← LOOPHOLE[End, PrincOps.ControlLink];
RETURN WITH argsForChild; -- "call" root procedure of child.
END;
ENDCASE;
END;
Join: ENTRY PROCEDURE [process: PsbIndex]
RETURNS [loadResults: PrincOps.FrameHandle] =
BEGIN
h: PsbHandle;
frame: DyingFrameHandle;
self: PrincOps.FrameHandle = Frame.MyLocalFrame[];
IF (h ← ValidProcess[process]) = NullPsbHandle THEN
RETURN WITH ERROR InvalidProcess[process];
Wait till process ready to be joined:
WHILE ProcState[h].state ~= frameReady DO
WAIT frameReady ENDLOOP;
Guaranteed to be a dying frame by the time we get here.
frame ← LOOPHOLE[pda[h].context.frame, DyingFrameHandle];
LOOPHOLE[pda[h].flags.available, ProcessState].state ← frameTaken;
BROADCAST frameTaken; -- tell child process we've got his frame.
Wait till he has finished cleaning up:
WHILE frame.state ~= dead DO WAIT dead ENDLOOP;
At this point, we (the parent process) have acquired responsibility
for the child's frame. IT MUST BE IN THE SAME MDS AS THE PARENT.
frame.returnlink ← self.returnlink; -- We use the child frame's
return link as a mailbox to pass to the child's frame the address
of the JOINer's frame, which the child should return to.
RETURN[frame]; -- JOINer will next Xfer to "frame", which will reload the
results into the stack and return them to the JOINer.
END;
Pause: PUBLIC ENTRY SAFE PROC [ticks: Process.Ticks] = TRUSTED
BEGIN ENABLE ABORTED => GO TO Aborted;
c: CONDITION;
SetTimeout[@c, ticks];
EnableAborts[@c];
WAIT c;
EXITS Aborted => RETURN WITH ERROR ABORTED;
END;
ValidateProcess: PUBLIC ENTRY PROCEDURE [p: PsbIndex] =
{ IF ValidProcess[p] = NullPsbHandle THEN
RETURN WITH ERROR InvalidProcess[p] };
~~~~~~~~~~~~ INTERNAL Procedures ~~~~~~~~~~~~
ValidProcess: INTERNAL PROCEDURE [p: --PsbIndex--UNSPECIFIED]
RETURNS [h: PsbHandle] = INLINE
returns NullPsbHandle if invalid.
{ RETURN[ IF ~(LOOPHOLE[p, PsbIndex] IN [StartPsb..StartPsb+pda.count))
OR ProcState[h ← IndexToHandle[LOOPHOLE[p, PsbIndex]]].state
IN [frameTaken..dead]
THEN NullPsbHandle ELSE h ] };
END.
LOG
(For earlier log entries see Pilot 4.0 archive version.)
April 29, 1980 5:53 PM Forrest Drop PSB's crossing pages on floor; move Initialize Timeout machinery to ProcessorHead.
May 3, 1980 10:46 AM Forrest Mesa 6.0 Conversion.
May 14, 1980 6:19 PM McJones Use OISProcessorFace.reservedNakedNotifyMask; start interrupts at end of initialization (as before).
June 23, 1980 5:34 PM McJones OISProcessorFace=>ProcessorFace.
August 5, 1980 5:54 PM Sandman New PSB format.
September 29, 1980 10:30 AM Johnsson New ProcessTrap.
January 21, 1981 9:45 AM Knutsen New PDA layout: state vector pool, timeout vector. New Fork. Fix bugs. InitializeProcesses[]. Use waiting bit in Abort.
January 27, 1981 8:17 AM Knutsen Use stateVectorCount from StartList. Forking requires storing controlLinks above the stack.
February 4, 1981 1:25 PM Knutsen Export priorities to Process. Enable ABORTED on Pause. PrincOps fields changed names.
February 25, 1981 2:03 PM Knutsen Use stateVectorSize from StartList. Pause[0] must not wait forever.
March 20, 1981 1:45 PM Fay/Sandman/Knutsen Fix AR 7493 by changing Abort procedure.
March 26, 1981 5:39 PM Luniewski/McJones Abort must clear waiting flag when doing requeue.
August 3, 1982 4:16 pm Levin Correct all occurrences of ~IN.
August 26, 1982 11:22 am Levin Make things SAFE.