DistributedRenderImpl.mesa
Last Edited by: Crow, May 10, 1989 12:42:47 pm PDT
DIRECTORY
BasicTime   USING [ PulsesToSeconds, GetClockPulses ],
Atom     USING [ PropList, PutPropOnList, GetPropFromList, RemPropFromList ],
Process    USING [ Pause, SecondsToTicks ],
CedarProcess   USING [ Abort, CheckAbort, Fork, ForkableProc, GetStatus, Join, Process,
         Status ],
RPC     USING [ CallFailed ],
ComputeServerClient      USING [ RemoteSuccess, StartService ],
ComputeClientExtras      USING [ RemoteProcessSite ],
ComputeClientInternal     USING [ ControllerInterface ],
ComputeServerControllerRpcControl USING [ InterfaceRecord ],
FS      USING [ StreamOpen ],
IO      USING [ PutRope, STREAM, SetIndex, UnsafeGetBlock ],
Rope     USING [ ROPE, Cat, Find, Index, Length, Equal, Substr ],
Convert    USING [ RopeFromCard, RopeFromInt, RopeFromReal, RealFromRope ],
Real     USING [ Fix, Round ],
Imager    USING [ Rectangle ],
ImagerPixel   USING [ GetPixels, PixelBuffer, PutPixels ],
ImagerSample  USING [ PointerToSamples ],
ThreeDBasics  USING [ Box, ClipState, Context, Error, GetShading, IntSequence,
         NatSequence, Pair, Quad, RealSequence, Rectangle, RGB,
         ShapeInstance, ShapeSequence, SixSides, Triple, Vertex ],
RenderWithPixels USING [ FillInConstantBackGround ],
SurfaceRender  USING [ CombineBoxes, FlushLog, ValidateContext ],
ShapeUtilities  USING [ XfmToDisplay ],
SceneUtilities  USING [ CopyContextData, CopyShapeDirect, PrependWorkingDirectory,
         SetViewPort, SetWindow, StartLog, WriteScene ],
DistributedRender USING [ ];
DistributedRenderImpl: CEDAR MONITOR
IMPORTS Atom, BasicTime, CedarProcess, ComputeServerClient, ComputeClientExtras, ComputeClientInternal, Convert, FS, ImagerPixel, ImagerSample, IO, Process, Real, RenderWithPixels, Rope, RPC, SceneUtilities, ShapeUtilities, SurfaceRender, ThreeDBasics
EXPORTS DistributedRender
~ BEGIN
Types
PixelBuffer: TYPE ~ ImagerPixel.PixelBuffer;
Context: TYPE ~ ThreeDBasics.Context;
ShapeSequence: TYPE ~ ThreeDBasics.ShapeSequence;
ShapeInstance: TYPE ~ ThreeDBasics.ShapeInstance;
BoolSequence: TYPE ~ RECORD [ length: NAT ← 0,
          data: SEQUENCE maxLength: NAT OF BOOLEAN];
Pair: TYPE ~ ThreeDBasics.Pair;           -- RECORD [ x, y: REAL];
Triple: TYPE ~ ThreeDBasics.Triple;
Box: TYPE ~ ThreeDBasics.Box;
RealSequence: TYPE ~ ThreeDBasics.RealSequence;
RGB: TYPE ~ ThreeDBasics.RGB;
Rectangle: TYPE ~ ThreeDBasics.Rectangle;
NatSequence: TYPE ~ ThreeDBasics.NatSequence;
IntSequence: TYPE ~ ThreeDBasics.IntSequence;
StreamPair: TYPE ~ RECORD [ in, out: IO.STREAM ];
CountedCondition: TYPE ~ RECORD [ count: NAT, condition: CONDITION ];
Edge: TYPE ~ RECORD [shape: REF ShapeInstance, cost: REAL, position: NAT, entering: BOOL];
EdgeSequence: TYPE ~ RECORD [ currentPlace: NAT, currentCost, averageCost: REAL,
          length: NAT ← 0, s: SEQUENCE maxLength: NAT OF Edge ];
ForkedProcess: TYPE ~ RECORD [ proc: CedarProcess.Process, io: REF StreamPair,
          server: Rope.ROPE, pctAvail: REAL ];
ForkedProcessSequence: TYPE ~ RECORD [ length: NAT ← 0,
            s: SEQUENCE maxLength: NAT OF ForkedProcess ];
LORA: TYPE ~ LIST OF REF ANY;
Global Constant/Variables
stopMe: BOOLEANFALSE;        -- external stop signal
masterTimeOut: REAL ← 1800;      -- 1/2 hr, max time for a multiprocess picture
remoteProcessTimeOut: INT ← 300;    -- 5 min., max time for remote process
maxProcClonesAllowed: NAT ~ 3;   -- times process may be replicated to get better service
procClonesAllowed: NAT ← 3;
timesKept: NAT ~ 5;          -- number of timings recorded and summed
pixelsPerSecond: INT ← 200;       -- cost measure for 1 second compute time
jaggyPixelsPerSecond: INT ← 2000;
imageSpaceDivision: BOOLEANFALSE;    -- for forcing image subdivision method
computingSerially: BOOLEANFALSE;    -- flag for forcing serialization
noCostAdjustments: BOOLEANFALSE; -- flag for skipping optimization with cost estimation
serverStats: Rope.ROPENIL;       -- Parameters for Server statistics
serverStatsTime: REAL ← 0.0;
serverStatsWanted: BOOLEANFALSE;
serverStatsOut: IO.STREAMNIL;
minimumUsefulServerPortion: REAL ← .5;
showBoxes: BOOLEANFALSE;   -- pedagogical aids (showGaps deleted)
showBoxCoverage: REAL ← 0.2;
Utility Procedures
Ceiling: PROC[ in: REAL ] RETURNS[ out: INTEGER ] ~ {
out ← Real.Round[in];
IF REAL[out] < in THEN out ← out + 1;
};
Floor: PROC[ in: REAL ] RETURNS[ out: INTEGER ] ~ {
out ← Real.Round[in];
IF REAL[out] > in THEN out ← out - 1;
};
RopeFromSeconds: PROC[seconds: REAL] RETURNS[Rope.ROPE] ~ {
RETURN[ Rope.Cat[ Convert.RopeFromReal[ Real.Fix[100.0 * seconds] / 100.0 ] ] ];
};
ElapsedTime: PROC[startTime: REAL] RETURNS[Rope.ROPE] ~ {
timeX100: REAL ← 100.0 * (CurrentTime[] - startTime);
RETURN[ Rope.Cat[ Convert.RopeFromReal[ Real.Fix[timeX100] / 100.0 ], "s," ] ];
};
CurrentTime: PROC[] RETURNS[REAL] ~ {
RETURN[ BasicTime.PulsesToSeconds[BasicTime.GetClockPulses[]] ];
};
PlaceAfter: PROC[toBeFound, rope: Rope.ROPE, startPos: NAT ← 0] RETURNS[position: NAT] ~ {
Reteurns position after string toBeFound, returns startPos if not found
newPos: INT ← Rope.Find[rope, toBeFound, startPos];
IF newPos >= 0 THEN position ← newPos + Rope.Length[toBeFound];
};
AddTimes: PROC[msg: Rope.ROPE, times: REF RealSequence] RETURNS[REF RealSequence] ~ {
NextTime: PROC[] RETURNS[REAL] ~ {
checks that previous PlaceAfter succeeded then looks for "s." as time indicator
IF pos2 > pos
THEN {
pos ← pos2;
pos2 ← Rope.Index[msg, pos, "s"];
IF pos2 > pos AND pos2 - pos < 10
THEN RETURN [Convert.RealFromRope[ Rope.Substr[msg, pos, pos2 - pos] ] ];
};
RETURN[0.0];
};
newTimes: REF RealSequence ← NEW[RealSequence[timesKept]];
pos, pos2: NAT ← 0;
pos2 ← PlaceAfter["Readin: ", msg, pos];
newTimes[0] ← NextTime[];
times[0] ← times[0] + newTimes[0];
pos2 ← PlaceAfter["VtxOps: ", msg, pos];
newTimes[0] ← NextTime[];
times[0] ← times[0] + newTimes[0];
pos2 ← PlaceAfter["Sort: ", msg, pos];
newTimes[0] ← NextTime[];
times[0] ← times[0] + newTimes[0];
pos2 ← PlaceAfter["Shade: ", msg, pos];
newTimes[1] ← NextTime[];
times[1] ← times[1] + newTimes[1];
pos2 ← PlaceAfter["output: ", msg, pos];
newTimes[2] ← NextTime[];
times[2] ← times[2] + newTimes[2];
pos2 ← PlaceAfter["total: ", msg, pos];
newTimes[3] ← NextTime[];
IF newTimes[3] = 0.0
THEN newTimes[3] ← newTimes[0] + newTimes[1] + newTimes[2];  -- no total
times[3] ← times[3] + newTimes[3];
pos2 ← PlaceAfter["matted in: ", msg, pos];
newTimes[4] ← NextTime[];
times[4] ← times[4] + newTimes[4];
RETURN [times];
};
Support Procedures
RemoteStop: PUBLIC ENTRY PROC[] ~ { stopMe ← TRUE; };
GetProcess: ENTRY PROC[processCount: REF CountedCondition] ~ {
ENABLE UNWIND => NULL;
WHILE processCount.count <= 0 DO WAIT processCount.condition; ENDLOOP;
processCount.count ← processCount.count - 1;
};
ReleaseProcess: ENTRY PROC[processCount: REF CountedCondition] ~ {
processCount.count ← processCount.count + 1;
NOTIFY processCount.condition;
};
CostHeuristic: PROC[shape: REF ShapeInstance, antiAliasing: BOOL] RETURNS[seconds: INT] ~{
 Start with area of bounding box
cost: INT ←  INT[(shape.screenExtent.max.f - shape.screenExtent.min.f)]
    * (shape.screenExtent.max.s - shape.screenExtent.min.s);   
times 3 for Non-linear surface
IF shape.class.type # $ConvexPolygon AND poly.type # $Poly THEN cost ← cost * 3;
IF NOT antiAliasing
THEN seconds ← cost / jaggyPixelsPerSecond
ELSE {
 times 2 for Transparency
IF ThreeDBasics.GetShading[shape, $Transmittance] # NIL AND shape.insideVisible
THEN cost ← cost * 2;
times 2 for Mapped Texture
IF ThreeDBasics.GetShading[ shape, $TextureMap ] # NIL THEN cost ← cost * 2;
times 4 for Solid Texture - cost could be higher
IF ThreeDBasics.GetShading[ shape, $ShadingProcs ] # NIL THEN cost ← cost * 4;
Estimated maximum seconds for completion
seconds ← cost / pixelsPerSecond;
};
};
ServerUsage: ENTRY PROC[process: CedarProcess.Process]
      RETURNS
[server: Rope.ROPE, pctAvailable: REAL ] ~ {
Returns percent of remote machine process is getting (in theory).
If anything goes wrong, return indicates process is getting all of machine.
ENABLE UNWIND => NULL;
server ← ComputeClientExtras.RemoteProcessSite[process.process];
IF CurrentTime[] - serverStatsTime > 5.0 THEN {
newserverStats: Rope.ROPE;
success: ATOM;
controllerInterface: ComputeServerControllerRpcControl.InterfaceRecord ←
              ComputeClientInternal.ControllerInterface;
IF controllerInterface # NIL
THEN [success, newserverStats] ← controllerInterface.clientStubGenericToController[
interface: controllerInterface,
requestCode: $ServerLoads,
requestString: NIL
! RPC.CallFailed => CONTINUE
];
IF success = $success THEN {
serverStats ← newserverStats;
serverStatsTime ← CurrentTime[];
IF serverStatsOut # NIL THEN serverStatsOut.PutRope[Rope.Cat["\n\n", newserverStats]];
};
};
Analyze Stats for current behavior
Stats format:
eg. Hornet( 0.11, 0.40, 0.40, 0.40, 0), Wasp( 0.83, 0.40, 0.40, 0.70, 1)
- aveBackgroundLoad: the average number of ready background processes.
- nonBackgroundCPULoad: fraction of CPU used that was not idle or background
- CPULoad: CPU load returned by Watch expressed as a fraction.
- FOM: Figure of Merit - same as SummonerInfo - 0.0 is idle
- numberOfCurrentRequests: count of Summoner requests on the server
pctAvailable ← 101.0;          -- indicates no answer
IF server # NIL THEN {
aveBackgroundLoad, nonBackgroundCPULoad: REAL ← 0.0;
pos: INT ← Rope.Index[serverStats, 0, server] + Rope.Length[server] + 1;
pos2: INT ← Rope.Index[serverStats, pos, ","];
IF pos2 > pos THEN {        -- if not at end of string
aveBackgroundLoad ← Convert.RealFromRope[ Rope.Substr[serverStats, pos, pos2 - pos] ];
pos ← pos2 + 1; pos2 ← Rope.Index[serverStats, pos, ","];
nonBackgroundCPULoad ← Convert.RealFromRope[
              Rope.Substr[serverStats, pos, pos2 - pos] ];
IF nonBackgroundCPULoad > 1.0 OR nonBackgroundCPULoad < 0.0
OR aveBackgroundLoad < -1.0 OR aveBackgroundLoad > 100.0
THEN SIGNAL ThreeDBasics.Error[[ $MisMatch, Rope.Cat[server, " - ", serverStats] ]];
nonBackgroundCPULoad ← MAX[0.0, MIN[1.0, nonBackgroundCPULoad]];
aveBackgroundLoad ← MAX[0.0, MIN[5.0, aveBackgroundLoad]];
IF serverStatsOut # NIL AND nonBackgroundCPULoad > 0.0 THEN {
serverStatsOut.PutRope[ Rope.Cat[ "\n", server] ];
serverStatsOut.PutRope[ Rope.Cat[ " - load: ",
Convert.RopeFromReal[nonBackgroundCPULoad],
" pctAvailable: ",
Convert.RopeFromReal[ (1.0 - nonBackgroundCPULoad)
              / MAX[1.0, aveBackgroundLoad] ]
] ];
};
};
pctAvailable ← (1.0 - nonBackgroundCPULoad) / MAX[1.0, aveBackgroundLoad];
};
};
KillProcs: PROC[ context: REF Context, procList: LIST OF CedarProcess.Process ] ~ {
FOR procs: LIST OF CedarProcess.Process ← procList, procs.rest UNTIL procs = NIL DO
CedarProcess.Abort[procs.first];
ENDLOOP;
};
JoinProcs: PROC[ context: REF Context, procList: LIST OF CedarProcess.Process ] ~ {
Await completion of processes and log messages
log: IO.STREAMNARROW[ Atom.GetPropFromList[context.props, $Log] ];
startTime: REALNARROW[Atom.GetPropFromList[context.props, $StartTime], REF REAL]^;
procTimes: REF RealSequence ← NEW[ RealSequence[5] ];
FOR i: NAT IN [0..5) DO procTimes[i] ← 0.0; ENDLOOP;
log.PutRope[Rope.Cat[" Processes all forked at: ", ElapsedTime[startTime], "\n" ]];
FOR procs: LIST OF CedarProcess.Process ← procList, procs.rest UNTIL procs = NIL DO
status: CedarProcess.Status ← busy;
result: REF;
returnMsg: Rope.ROPE;
WHILE status = busy DO         -- wait loop for process completion
IF context.stopMe^ OR CurrentTime[] - startTime > masterTimeOut  -- bailouts
THEN { KillProcs[context, procs]; RETURN[]; };
status ← CedarProcess.GetStatus[procs.first]; 
IF status # busy THEN LOOP;
Process.Pause[ Process.SecondsToTicks[1] ];
ENDLOOP;
[status, result] ← CedarProcess.Join[procs.first];   -- wait for process completion
procs.first ← NIL;           -- drop REF
returnMsg ← NARROW[result];
IF status # done
THEN returnMsg ← Rope.Cat[" process failed - ", returnMsg]
ELSE [procTimes] ← AddTimes[returnMsg, procTimes];     -- get timings
log.PutRope[Rope.Cat[returnMsg, "\n" ] ];
ENDLOOP;
procList ← NIL;             -- drop REF
log.PutRope[Rope.Cat["Totals - Set-up: ", Convert.RopeFromReal[procTimes[0]] ] ];
log.PutRope[Rope.Cat[", Scan conversion: ", Convert.RopeFromReal[procTimes[1]] ] ];
log.PutRope[Rope.Cat[", Output: ", Convert.RopeFromReal[procTimes[2]] ] ];
log.PutRope[Rope.Cat[", Grand Total: ", Convert.RopeFromReal[procTimes[3]] ] ];
log.PutRope[Rope.Cat[", Matting: ", Convert.RopeFromReal[procTimes[4]], "\n"] ];
};
GetTempContext: PROC[context: REF Context, name: Rope.ROPE, killBackground: BOOLEAN,
       shape: REF ShapeSequence, cost, processCount: REF]
       RETURNS[tmpCtx: REF Context] ~ {
Build new context to send to forked process
k: NAT ← context.lightSources.length;
tmpCtx ← NEW[ Context ];
SceneUtilities.CopyContextData[dstCtx: tmpCtx, srcCtx: context];  -- copies props too
tmpCtx.pixels ← context.pixels;    -- pixels need to be directed to parent display
IF killBackground
THEN tmpCtx.props ← Atom.PutPropOnList[tmpCtx.props, $BackGround, NIL]; -- no bckgrd
tmpCtx.props ← Atom.PutPropOnList[tmpCtx.props, $ComputeCost, cost ];
tmpCtx.props ← Atom.PutPropOnList[tmpCtx.props, $ProcessCount, processCount];
tmpCtx.props ← Atom.PutPropOnList[tmpCtx.props, $SubImageName, name];
Kill imager context to avoid side effects
tmpCtx.displayProps ← Atom.RemPropFromList[tmpCtx.displayProps, $ImagerContext];
Get light sources
tmpCtx.shapes ← NEW[ ShapeSequence[ shape.length + context.lightSources.length] ];          
FOR j: NAT IN [0 .. context.lightSources.length) DO
tmpCtx.shapes[j] ← SceneUtilities.CopyShapeDirect[ context.lightSources[j] ];
ENDLOOP;
FOR i: NAT IN [0 .. shape.length) DO
IF shape[i].class.type # $Light THEN { -- add shape, shapes used as lights already there
tmpCtx.shapes[k] ← SceneUtilities.CopyShapeDirect[ shape[i] ]; k ← k + 1;
};
ENDLOOP;
tmpCtx.shapes.length ← k;
};
Image Slicing Support Procedures
AddShape: PROC[ shape: REF ShapeSequence, newShape: REF ShapeInstance ] ~ {
shape[shape.length] ← newShape;
shape.length ← shape.length + 1;
};
DeleteShape: PROC[ shape: REF ShapeSequence, oldShape: REF ShapeInstance ] ~ {
foundIt: BOOLEANFALSE;
FOR i: NAT IN [0..shape.length) DO
IF Rope.Equal[shape[i].name, oldShape.name] THEN {    -- find matching shape
FOR j: NAT IN [i..shape.length-1) DO shape[j] ← shape[j+1]; ENDLOOP; -- remove
foundIt ← TRUE; EXIT;
};
ENDLOOP;
IF foundIt THEN { shape.length ← shape.length - 1; shape[shape.length] ← NIL; };
};
GetBBoxOrder: PROC[ context: REF Context, shape: REF ShapeSequence, numForksHint: NAT ]
     RETURNS[ shapeEdgeOrder: REF EdgeSequence] ~ {
Sort bounding boxes left to right for balancing image slices
totalCost: REAL ← 0;
cost: REF RealSequence ← NEW[ RealSequence[shape.length] ];
shapeEdgeOrder ← NEW[ EdgeSequence[ 2 * shape.length ] ];
Find average scan conversion cost
FOR i: NAT IN [0..shape.length) DO
Estimate relative cost of each shape (untamed heuristics here)
cost[i] ← CostHeuristic[shape[i], context.antiAliasing];
totalCost ← totalCost + cost[i]
ENDLOOP;
shapeEdgeOrder.averageCost ← totalCost / numForksHint; -- base division on no. of processors
Adjust costs to unit width
FOR i: NAT IN [0..shape.length) DO
cost[i] ← cost[i] / ( shape[i].screenExtent.max.f + 1 - shape[i].screenExtent.min.f );
ENDLOOP;
Sort Object Screen Extents left to right
FOR s: NAT IN [0..shape.length) DO
Insertion sort left and right shape edges, (crude, numShapes assumed small)
FOR i: NAT IN [0..2) DO
position: NATIF i = 0 THEN shape[s].screenExtent.min.f
       ELSE
shape[s].screenExtent.max.f;
left: BOOLEAN ← i = 0;        -- chooses left edge of bounding box
EnterEdge: PROC[place, s: NAT] ~ {
RECORD [shape: REF ShapeInstance, cost: REAL, position: NAT, entering: BOOLEAN];
shapeEdgeOrder[place].shape ← shape[s];
shapeEdgeOrder[place].cost ← cost[s];
shapeEdgeOrder[place].position ← position;
shapeEdgeOrder[place].entering ← left;  -- entering bounding box if left edge
};
FOR p: NAT DECREASING IN [0..shapeEdgeOrder.length) DO -- find insertion point
IF position < shapeEdgeOrder[p].position
THEN {
shapeEdgeOrder[p+1] ← shapeEdgeOrder[p];
IF p = 0 THEN EnterEdge[p, s];     -- insert if done with sequence
}
ELSE { EnterEdge[p+1, s]; EXIT; };   -- found! insert
ENDLOOP;
IF shapeEdgeOrder.length = 0 THEN EnterEdge[0, s];
shapeEdgeOrder.length ← shapeEdgeOrder.length + 1;
ENDLOOP;
ENDLOOP;
shapeEdgeOrder.currentPlace ← 0;    -- initialize cost accounting
shapeEdgeOrder.currentCost ← 0.0;
};
UpdateActiveShapes: PROC[shapeEdgeOrder: REF EdgeSequence,
         activeShapesInSlice: REF ShapeSequence, leftX: NAT]
       RETURNS[REF ShapeSequence, NAT] ~ {
Evaluates ordered edges and produces shape set and slice width of given cost
sliceCost: REAL ← 0.0;
currentCost: REAL ← shapeEdgeOrder.currentCost;
Calculate slice width and active shapes
rightX: NAT ← shapeEdgeOrder[shapeEdgeOrder.currentPlace].position;
shapesInSlice: REF ShapeSequence ← NEW[ ShapeSequence[shapeEdgeOrder.length/2] ];
IF activeShapesInSlice = NIL
THEN activeShapesInSlice ← NEW[ ShapeSequence[shapeEdgeOrder.length/2] ]
ELSE {
FOR i: NAT IN [0..activeShapesInSlice.length) DO
shapesInSlice[i] ← activeShapesInSlice[i];
ENDLOOP;
shapesInSlice.length ← activeShapesInSlice.length;
};
WHILE TRUE DO   -- work across, adding shapes until slice cost exceeds average
costLeft: REAL ← shapeEdgeOrder.averageCost - sliceCost;
IF costLeft > currentCost * (rightX - leftX)
THEN {        -- room for another shape, get the next one
sliceCost ← sliceCost + currentCost * (rightX - leftX); -- go to right of current shape
IF shapeEdgeOrder[shapeEdgeOrder.currentPlace].entering
THEN {           -- moving into shape
currentCost ← currentCost + shapeEdgeOrder[shapeEdgeOrder.currentPlace].cost;
AddShape[ activeShapesInSlice,
   shapeEdgeOrder[shapeEdgeOrder.currentPlace].shape ];
AddShape[ shapesInSlice, shapeEdgeOrder[shapeEdgeOrder.currentPlace].shape ];
}
ELSE {           -- moving out of shape
currentCost ← currentCost - shapeEdgeOrder[shapeEdgeOrder.currentPlace].cost;
DeleteShape[ activeShapesInSlice,
    shapeEdgeOrder[shapeEdgeOrder.currentPlace].shape ];
};
leftX ← rightX;
shapeEdgeOrder.currentPlace ← shapeEdgeOrder.currentPlace + 1;
IF shapeEdgeOrder.currentPlace < shapeEdgeOrder.length
THEN rightX ← shapeEdgeOrder[shapeEdgeOrder.currentPlace].position
ELSE { rightX ← LAST[NAT]; EXIT; };  -- end of sorted shape array, last slice
}
ELSE {          -- slice ends in middle of shape
rightX ← leftX + Real.Round[costLeft / currentCost]; -- pixels left at current cost
EXIT;
};
ENDLOOP;
shapeEdgeOrder.currentCost ← currentCost;
RETURN[shapesInSlice, rightX];
};
Object Slicing Support Procedures
SortShapes: PROC[shape: REF ShapeSequence, numForksHint: NAT]
    RETURNS
[REF ShapeSequence] ~ {
shapeOrder: REF ShapeSequence ← NEW[ ShapeSequence[shape.length] ];
Sort Objects
FOR i: NAT IN [0..shape.length) DO
Insertion sort shapes, (crude sort, numShapes assumed quite small)
FOR j: NAT DECREASING IN [0..shapeOrder.length) DO
IF shape[i].centroid.ez < shapeOrder[j].centroid.ez
THEN {
shapeOrder[j+1] ← shapeOrder[j];
IF j = 0 THEN shapeOrder[j] ← shape[i];     -- insert if done with sequence
}
ELSE { shapeOrder[j+1] ← shape[i]; EXIT; };
ENDLOOP;
IF shapeOrder.length = 0 THEN shapeOrder[0] ← shape[i];
shapeOrder.length ← shapeOrder.length + 1;
ENDLOOP;
Make Lists of Occluding Objects
{ occlusionList: LIST OF REF ShapeInstance;
Overlap: PROC[box1, box2: ThreeDBasics.Box] RETURNS[ BOOLEAN] ~ {
IF  box1.min.f > box2.max.f  OR box2.min.f > box1.max.f
OR box1.min.s > box2.max.s OR box2.min.s > box1.max.s
THEN RETURN[FALSE]
ELSE RETURN[TRUE];
};
FOR i: NAT IN [0..shapeOrder.length) DO
occlusionList ← NIL;
FOR j: NAT IN [0..i) DO  -- higher priority shapes with overlapping bounding boxes?
IF Overlap[ shapeOrder[i].screenExtent, shapeOrder[j].screenExtent ]
THEN occlusionList ← CONS[ shapeOrder[j], occlusionList ];
ENDLOOP;
shapeOrder[i].props ← Atom.PutPropOnList[ -- list of occluding shapes
shapeOrder[i].props,
$Occlusions,
occlusionList
];
ENDLOOP;
};
RETURN[ shapeOrder ];
};
ShowBBox: PROC[context: REF Context, shape: REF ShapeInstance, screenExtent: Box] ~ {
area: Box ← screenExtent;
x: screenExtent.left,
y: screenExtent.bottom,
w: screenExtent.right - screenExtent.left,
h: screenExtent.top - screenExtent.bottom
];
pixelValues: Pixels.SampleSet ← Pixels.GetSampleSet[4];
color: RGB ← shape.shadingClass.color;
pixelValues[0] ← Real.Fix[color.R * 255.0];
pixelValues[1] ← Real.Fix[color.G * 255.0];
pixelValues[2] ← Real.Fix[color.B * 255.0];
pixelValues[3] ← Real.Fix[showBoxCoverage * 255.0];    -- coverage
Pixels.PixelOp[ context.display, area, pixelValues, $WriteUnder ];
};
Remote Rendering Support Procedures
WatchProc: PROC[ forkedProc: REF ForkedProcessSequence, cloneNo: NAT,
      estComputeTime: INT, startTime: REAL ]
    RETURNS[remoteImage: IO.STREAM, reason: Rope.ROPE] ~ {
returnMsg: Rope.ROPE ← NIL;
WHILE CurrentTime[] - startTime < 2 * estComputeTime DO
KillChildren: PROC[ i: NAT ] ~ {
FOR k: NAT IN [0..i] DO CedarProcess.Abort[ forkedProc[k].proc ]; ENDLOOP;
ERROR ABORTED;
};
serversAvailable: BOOLEANFALSE;
CedarProcess.CheckAbort[ ! ABORTED => KillChildren[cloneNo] ]; -- abort on request
Process.Pause[ Process.SecondsToTicks[1] ];  -- pause for a second each time around
FOR j: NAT IN [0..cloneNo] DO   -- check on all forked processes for this shape
SELECT CedarProcess.GetStatus[ forkedProc[j].proc ] FROM
done => {              -- finished!
result: REF;
FOR k: NAT IN [0..cloneNo] DO IF k # j THEN {   -- abort other procs
returnMsg ← Rope.Cat[ returnMsg, "\n aborted proc on ",
ComputeClientExtras.RemoteProcessSite[forkedProc[k].proc.process], " "
];
CedarProcess.Abort[ forkedProc[k].proc ];
};
ENDLOOP;
[ , result] ← CedarProcess.Join[ forkedProc[j].proc ]; -- get proc results
returnMsg ← Rope.Cat[ returnMsg, NARROW[result, Rope.ROPE], " - Done, " ];
RETURN[ forkedProc[j].io.in, returnMsg ]; -- return image
};
aborted  => {
result: REF;
[ , result] ← CedarProcess.Join[ forkedProc[j].proc ]; -- get proc results
returnMsg ← Rope.Cat[ returnMsg, NARROW[result, Rope.ROPE], " - Aborted, " ];
RETURN[ NIL, returnMsg ];
};
ENDCASE => {     -- still going, check on remote processor utilization
[ forkedProc[j].server, forkedProc[j].pctAvail ] ← ServerUsage[ forkedProc[j].proc ];
IF forkedProc[j].pctAvail > minimumUsefulServerPortion
THEN serversAvailable ← TRUE  -- based on 5 second samples
ELSE { server: Rope.ROPE ← forkedProc[j].server; }; -- place for debug break pt.
};
ENDLOOP;
IF NOT serversAvailable AND cloneNo+1 < procClonesAllowed  -- lousy service
THEN RETURN[ NIL, Rope.Cat[returnMsg, " - Servers busy, "] ]; -- get another server
ENDLOOP;
RETURN[ NIL, Rope.Cat[returnMsg, " - Timed out, "] ];
};
AwaitOccludingProcesses: PROC[context: REF Context] ~ {
FOR i: NAT IN [0..context.visibleShapes.length) DO  -- check shapes for this process
occlusionList: LIST OF REF ShapeInstance ← NARROW[ -- list of occluding shapes
Atom.GetPropFromList[ context.visibleShapes[i].props, $Occlusions ]
];
FOR shape: LIST OF REF ShapeInstance ← occlusionList, shape.rest UNTIL shape = NIL DO
procList: LIST OF CedarProcess.Process ← NARROW[  -- find each occluding shape
Atom.GetPropFromList[ shape.first.props, $RemoteProc ]
];
FOR procs: LIST OF CedarProcess.Process ← procList, procs.rest UNTIL procs = NIL DO
[] ← CedarProcess.Join[procs.first];   -- wait for process completion
ENDLOOP;
ENDLOOP;
ENDLOOP;
};
GetRemotePixels: PROC[context: REF Context, remoteImage: IO.STREAM, writeOp: ATOM]
      RETURNS[Rope.ROPE] ~ {
xPos: NAT ← Floor[context.viewPort.x];
yPos: NAT ← Floor[context.viewPort.y];
width: NAT ← Ceiling[context.viewPort.w];
height: NAT ← Ceiling[context.viewPort.h];
scanSeg: PixelBuffer;
ImagerPixel.GetPixels[self: context.pixels, pixels: scanSeg, count: width];
IO.SetIndex[remoteImage, 0]; -- reset index for returning pixel stream
FOR y: NAT IN [ yPos .. height+yPos ) DO
Get scanline from remote proc
FOR i: NAT IN [0.. context.pixels.samplesPerPixel) DO
nBytesRead: INT;
TRUSTED { nBytesRead ← IO.UnsafeGetBlock[
self: remoteImage,        -- uses 16 bits per byte (wasting bandwidth)
block: [ base: LOOPHOLE[ImagerSample.PointerToSamples[scanSeg[i], 0, width]],
  count: 2*width ]
]; };
IF nBytesRead < 2*width THEN RETURN["Unexpected end of remote image stream\n"];
ENDLOOP;
ImagerPixel.PutPixels[ self: context.pixels, pixels: scanSeg,    -- Write to context
       initIndex: [f: xPos, s: y], count: width ];
ENDLOOP;
RETURN[NIL];
};
Multiprocessor control
SetConcurrencyLevel: PUBLIC PROC[context: REF Context, numProcesses: NAT] ~ {
context.props ← Atom.PutPropOnList[ context.props, $NumForksHint,
           NEW[ NAT ← numProcesses] ];
};
MakeFrame: PUBLIC PROC[context: REF Context] ~ {
Uses compute server to parcel out rendering to other processors
GetBBoxes: PROC[shape: REF ShapeSequence] ~ {
IF NOT context.antiAliasing THEN FOR i: NAT IN [0..shape.length) DO
ShapeUtilities.XfmToDisplay[context, shape[i], TRUE];
ENDLOOP; 
};
log: IO.STREAMNARROW[ Atom.GetPropFromList[context.props, $Log] ];
ref: REF ← Atom.GetPropFromList[context.props, $NumForksHint];
numForksHint: NATIF ref # NIL
THEN NARROW[ref, REF NAT]^
ELSE IF imageSpaceDivision THEN 1 ELSE 0;
shape: REF ShapeSequence;
startTime: REAL ← CurrentTime[];
context.props ← Atom.PutPropOnList[context.props, $StartTime, NEW[REAL ← startTime] ];
context.stopMe^ ← FALSE;           -- release remote stop flag
IF log = NIL THEN log ← SceneUtilities.StartLog[context];  -- open log file if necessary
Update Shapes
SurfaceRender.ValidateContext[context]; -- update everything (only bounding boxes needed)
shape ← context.visibleShapes;
GetBBoxes[shape];       -- make sure that legit screen extents are available
IF context.antiAliasing
THEN RenderWithPixels.FillInConstantBackGround[context, [0.0,0.0,0.0], 0 ]; -- clear
IF numForksHint > 0 THEN {     -- diagnostic ouput
log.PutRope[Rope.Cat["\n", Convert.RopeFromCard[numForksHint], " processors"] ];
IF imageSpaceDivision THEN log.PutRope[" - slices "];
};
log.PutRope[Rope.Cat["\nObject transform and sort: ", ElapsedTime[startTime] ]];
Distribute subscenes to servers
IF imageSpaceDivision
THEN ForkSubImageProcs[context, numForksHint]
ELSE ForkSubSceneProcs[context, numForksHint];
Finish Frame
IF context.antiAliasing AND NOT imageSpaceDivision THEN {
SurfaceRender.CombineBoxes[context];   -- get combined bounding box on scene
context.class.loadBackground[context];     -- load background
};
log.PutRope[Rope.Cat["All done at ", ElapsedTime[startTime], "\n\n" ] ];
SurfaceRender.FlushLog[context];
};
ForkSubImageProcs: PROC[context: REF Context, numForksHint: NAT] ~ {
shapeEdgeOrder: REF EdgeSequence;
processCount: REF CountedCondition ← NEW[CountedCondition]; -- for limiting # processes
procList: LIST OF CedarProcess.Process ← NIL;
shape: REF ShapeSequence ← context.visibleShapes;
activeShapesInSlice: REF ShapeSequence ← NEW[ShapeSequence[shape.length]];
lastX, xPos: NAT;
Sort bounding boxes
shapeEdgeOrder ← GetBBoxOrder[context, shape, numForksHint];  -- Sort bounding boxes
processCount.count ← numForksHint; -- limit processes ("procClonesAllowed" process clones)
lastX ← shapeEdgeOrder[shapeEdgeOrder.currentPlace].position;
Parcel out image slices to servers
FOR i: NAT IN [0..numForksHint) DO    -- do side to side, one slice per fork
forkedProcess: CedarProcess.Process;
shapesInSlice: REF ShapeSequence;
tmpCtx: REF Context;
Get limits from parent viewport for calculating slice windows
viewPortSize: REALMAX[context.viewPort.w, context.viewPort.h];
viewPortWindowX: REALMAX[0.0, context.viewPort.h -context.viewPort.w] /viewPortSize;
viewPortWindowY: REALMAX[0.0, context.viewPort.w -context.viewPort.h] /viewPortSize;
IF context.stopMe^ THEN { KillProcs[ context, procList ]; RETURN[]; }; -- escape hatch
Get active shapes for this slice, update slice boundary
[shapesInSlice, xPos] ← UpdateActiveShapes[shapeEdgeOrder, activeShapesInSlice, lastX];
Build new context to send to forked process
tmpCtx ← GetTempContext[
context: context,
name: Rope.Cat["Slice", Convert.RopeFromCard[i] ],  -- get a unique name
killBackground: FALSE,
shape: shapesInSlice,
cost: NEW[ INT ← Real.Round[shapeEdgeOrder.averageCost] ],
processCount: processCount
];
Set window in context
xPos ← MIN[Real.Fix[context.viewPort.w], xPos];  -- keep in bounds
SceneUtilities.SetViewPort[ tmpCtx, [
lastX + context.viewPort.x, context.viewPort.y,
xPos - lastX, context.viewPort.h
] ];
tmpCtx.viewPort^ ← tmpCtx.preferredViewPort; -- force viewport active for scene write
SceneUtilities.SetWindow[ tmpCtx, [
x: (2.0 * lastX / viewPortSize) - 1.0 + viewPortWindowX, -- window range [-1.0..+1.0]
y: (2.0 * context.viewPort.y / viewPortSize) - 1.0 + viewPortWindowY,
w: 2.0 * (xPos - lastX) / viewPortSize,
h: 2.0 * context.viewPort.h / viewPortSize
] ];
Fork new Process to Render each slice of the image
forkedProcess ← CedarProcess.Fork[RenderRemote, tmpCtx ];  -- fork process
procList ← CONS[ forkedProcess, procList];       -- save on list for later
IF computingSerially
THEN [] ← CedarProcess.Join[forkedProcess];   -- wait for process if serializing
lastX ← xPos;
ENDLOOP;             -- end loop through slices
Await completion of processes and log messages
JoinProcs[context: context, procList: procList];
};
ForkSubSceneProcs: PROC[ context: REF Context, numForksHint: NAT ] ~ {
processCount: REF CountedCondition ← NEW[CountedCondition]; -- for limiting # processors
allProcsList: LIST OF CedarProcess.Process ← NIL;
totalCost, averageCost: INT ← 0;
Sort shapes to priority order
shapeOrder: REF ShapeSequence ← SortShapes[context.visibleShapes, numForksHint];
cost: REF IntSequence ← NEW[ IntSequence[ shapeOrder.maxLength] ];
Find average scan conversion cost
FOR j: NAT IN [0..shapeOrder.length) DO
cost[j] ← CostHeuristic[shapeOrder[j], context.antiAliasing];  -- Estimate relative cost of each shape
totalCost ← totalCost + cost[j]
ENDLOOP;
IF numForksHint # 0
THEN {
averageCost ← totalCost / numForksHint; -- base division on no. of processors
processCount.count ← numForksHint  -- limit processors (2 processes per processor)
}
ELSE {
averageCost ← totalCost / shapeOrder.length; -- base division on no. of objects
processCount.count ← 200/2; -- no suggestion, keep safely under cedar limit of 300
};
Parcel out shapes to servers
FOR i: NAT IN [0..shapeOrder.length) DO    -- do front to back
Get limits from parent viewport for calculating windows
viewPortSize: REALMAX[context.viewPort.w, context.viewPort.h];
viewPortWindowX: REALMAX[0.0, context.viewPort.h -context.viewPort.w] /viewPortSize;
viewPortWindowY: REALMAX[0.0, context.viewPort.w -context.viewPort.h] /viewPortSize;
screenExtent: ThreeDBasics.Box ← shapeOrder[i].screenExtent;
shapeWidth: REAL ← screenExtent.max.f - screenExtent.min.f;
procList: LIST OF CedarProcess.Process ← NIL;
baseName: Rope.ROPE ← shapeOrder[i].name;
imageCount: NATMAX[ 1, NAT[Real.Round[ REAL[ cost[i]] / averageCost ]] ];
shapeForCtx: REF ShapeSequence ← NEW[ ShapeSequence[1] ];
shapeForCtx[0] ← shapeOrder[i];
IF context.stopMe^ THEN { KillProcs[ context, allProcsList ]; RETURN[]; }; -- escape hatch
FOR j: NAT IN [0..imageCount) DO    -- do for each slice of object
Build new context to send to forked process
forkedProcess: CedarProcess.Process;
tmpCtx: REF Context ← GetTempContext[
context: context,
name: Rope.Cat[ baseName, Convert.RopeFromCard[j] ],  -- get a unique name               
killBackground: TRUE,
shape: shapeForCtx,
cost: NEW[ INT ← cost[i] / imageCount ],
processCount: processCount
];
Set window in context
left: REAL ← screenExtent.min.f + shapeWidth * j / imageCount;
SceneUtilities.SetViewPort[ tmpCtx, [
context.viewPort.x + left, screenExtent.min.s + context.viewPort.y,
shapeWidth / imageCount, screenExtent.max.s - screenExtent.min.s
] ];
SceneUtilities.SetWindow[ tmpCtx, [    -- window range is [-1.0..+1.0]
x: (2.0 * left / viewPortSize) - 1.0 + viewPortWindowX,
y: (2.0 * screenExtent.min.s / viewPortSize) - 1.0 + viewPortWindowY,
w: 2.0 * (shapeWidth / imageCount) / viewPortSize,
h: 2.0 * (screenExtent.max.s - screenExtent.min.s) / viewPortSize
] ];
Fork new Process to Render each piece of the Shape
forkedProcess ← CedarProcess.Fork[RenderRemote, tmpCtx ];  -- fork process
procList ← CONS[ forkedProcess, procList];       -- save on list for later
allProcsList ← CONS[ forkedProcess, allProcsList];
IF computingSerially
THEN [] ← CedarProcess.Join[forkedProcess];   -- wait for process if serializing
ENDLOOP;
shapeOrder[i].props ← Atom.PutPropOnList[ -- store proc refs @shape
shapeOrder[i].props,
$RemoteProc,
procList          -- leave list of proc refs here
];
IF showBoxes AND computingSerially -- make cute little transparent boxes behind shapes
THEN ShowBBox[context, shapeOrder[i], screenExtent];
ENDLOOP;
Await completion of processes and log messages
JoinProcs[ context, allProcsList ];
FOR i: NAT IN [0..shapeOrder.length) DO       -- clear out process REFs
shapeOrder[i].props ← Atom.RemPropFromList[ shapeOrder[i].props, $RemoteProc ];
ENDLOOP;
};
RenderRemote: CedarProcess.ForkableProc ~ {
PROC [data: REF] RETURNS [results: REFNIL]
context: REF Context ← NARROW[data];
startTime: REALNARROW[ Atom.GetPropFromList[context.props, $StartTime], REF REAL ]^;
lastTime: REAL ← CurrentTime[];
fileName: Rope.ROPE ← SceneUtilities.PrependWorkingDirectory[
context,
Rope.Cat[ "Temp/", NARROW[ Atom.GetPropFromList[context.props, $SubImageName] ] ]
];
remoteImage: IO.STREAMNIL;
reason: Rope.ROPE;
forkedProc: REF ForkedProcessSequence ←
            NEW
[ForkedProcessSequence[maxProcClonesAllowed]];
[ proc: CedarProcess.Process, io: StreamPair, server: Rope.ROPE, pctAvail: REAL ];
returnMsg: Rope.ROPE ← Rope.Cat[
NARROW[ Atom.GetPropFromList[context.props, $SubImageName] ], " - " ];
estComputeTime: INTNARROW[
Atom.GetPropFromList[context.props, $ComputeCost], REF INT
]^;
times: REF RealSequence ← NEW[ RealSequence[5] ];
FOR i: NAT IN [0..5) DO times[i] ← 0.0; ENDLOOP;
returnMsg ← Rope.Cat[returnMsg, "est. ", Convert.RopeFromInt[estComputeTime], " s., "];
Robust remote processes. Start a process, check status regularly, clone process on evidence of poor remote service, LIMIT CLONES!!
FOR i: NAT IN [0..procClonesAllowed) DO
IF i > 0 THEN {     -- cloning process, state reasons on ouput message
returnMsg ← Rope.Cat[returnMsg, "\n ", forkedProc[i-1].server, " " ]; -- name
returnMsg ← Rope.Cat[ returnMsg, reason]; -- reason for giving up on previous one
};
forkedProc[i].io ← NEW[ StreamPair ← [   -- get streams for communication
in: FS.StreamOpen[ fileName: Rope.Cat[ fileName, "-in", Convert.RopeFromCard[i] ],
      accessOptions: $create ],
out: FS.StreamOpen[ fileName: Rope.Cat[ fileName, "-out", Convert.RopeFromCard[i] ],
      accessOptions: $create ]
] ];
Set up Scene Data
SceneUtilities.WriteScene[context, forkedProc[i].io.out];  -- get scene to remote proc!!!!
IO.PutRope[ forkedProc[i].io.out, "Render:\n"];   -- make an image
IO.PutRope[ forkedProc[i].io.out, "EndOfScene:\n"];  -- shuts down process
IO.SetIndex[forkedProc[i].io.out, 0];  -- reset index for downstream read
Start Remote Process
Wait for available process, limits remote calls to control number of processors used
IF i = 0 THEN GetProcess[NARROW[ Atom.GetPropFromList[context.props, $ProcessCount] ]];
returnMsg ← Rope.Cat[returnMsg, "Started proc. at: ", ElapsedTime[startTime], " "];
forkedProc[i].proc ← CedarProcess.Fork[  -- fork process to call compute server
CallComputeServer,
LIST[ NEW[REAL ← startTime], forkedProc[i].io ]  -- start time and i/o streams
];
Monitor process for completion and remote machine utilization
[remoteImage, reason] ← WatchProc[ forkedProc, i, estComputeTime, lastTime ];
returnMsg ← Rope.Cat[returnMsg, reason];
IF remoteImage # NIL THEN EXIT;  -- some process finished, stop cloning new ones
ENDLOOP;
Process Results
IF remoteImage = NIL THEN {      -- clean up processes on timeout
returnMsg ← Rope.Cat[returnMsg, " process forker timed-out!! "];
FOR i: NAT IN [0..procClonesAllowed) DO CedarProcess.Abort[forkedProc[i].proc]; ENDLOOP;
ReleaseProcess[ NARROW[ Atom.GetPropFromList[ context.props, $ProcessCount] ] ];
};
Check that all occluding processes are complete
IF NOT imageSpaceDivision THEN{
lastTime ← CurrentTime[];
AwaitOccludingProcesses[context]; -- wait for processes of occluding objects to finish
returnMsg ← Rope.Cat[returnMsg, " waited for: ", ElapsedTime[lastTime] ];
};
Display Pixels from Remote Process
lastTime ← CurrentTime[];
IF remoteImage # NIL THEN returnMsg ← Rope.Cat[
returnMsg,
GetRemotePixels[    -- get pixels from IO stream and put on context.display
context: context,
remoteImage: remoteImage,
writeOp: IF imageSpaceDivision OR NOT context.antiAliasing THEN $Write
                  ELSE $WriteUnder
]
];
returnMsg ← Rope.Cat[returnMsg, " matted in: ", ElapsedTime[lastTime] ];
returnMsg ← Rope.Cat[returnMsg, "\n Home process done at: ", ElapsedTime[startTime] ];
times ← AddTimes[returnMsg, times];
returnMsg ← Rope.Cat[returnMsg, ", cost factor: ",   -- actual vs. estimated cost
       RopeFromSeconds[ times[3] / estComputeTime]];
returnMsg ← Rope.Cat[returnMsg, ", remote ovrhd: ",    -- compute server overhead
       RopeFromSeconds[ CurrentTime[] - startTime - times[3] ], " s. " ];
results ← returnMsg;       -- formal return parameter
RETURN[returnMsg];
};
CallComputeServer: CedarProcess.ForkableProc ~ {
PROC [data: REF] RETURNS [results: REFNIL]
list: LORANARROW[data];
startTime: REALNARROW[list.first, REF REAL]^;
procIO: REF StreamPair ← NARROW[list.rest.first];
input: IO.STREAM ← procIO.in;
output: IO.STREAM ← procIO.out;
found: BOOLEAN;
success: ComputeServerClient.RemoteSuccess ← false;
successMsg, procMsg, server: Rope.ROPENIL;
[ found: found, success: success, remoteMsg: procMsg, serverInstance: server ] ←
ComputeServerClient.StartService[
service: "3dRenderWithStream",
cmdLine: Convert.RopeFromReal[startTime],
in: output, out: input, -- in/out as seen from server
queueService: TRUE,
timeToWait: remoteProcessTimeOut, -- estimate of time to wait before giving up
retries: 3    -- default number of retries
! ANY => ERROR ABORTED
];
SELECT success FROM
true => {};
false => {
IF ~found
THEN successMsg ← "compute server command not found"
ELSE successMsg ← "compute server success was false (Compute Server bug?)";
};
timeOut   => successMsg ← "timeOut";
commandNotFound  => successMsg ← "commandNotFound";
aborted   => successMsg ← "command aborted";
communicationFailure => successMsg ← "communicationFailure";
cantImportController => successMsg ← "cantImportController";
cantImportServer => successMsg ← "cantImportServer";
serverTooBusy  => successMsg ← "serverTooBusy";
clientNotRunning  => successMsg ← "clientNotRunning";
ENDCASE  => successMsg ← "unknown Compute Server error code";
successMsg ← Rope.Cat["Server: ", server, " - ", successMsg, "\n"];
IF procMsg # NIL
THEN successMsg ← Rope.Cat[successMsg, " Remote: ", procMsg];
RETURN[successMsg];
};
END.