DistributedDisplayImpl.mesa
Last Edited by: Crow, September 23, 1986 3:00:59 pm PDT
Bloomenthal, February 26, 1987 11:21:03 pm PST
DIRECTORY
BasicTime   USING [ PulsesToSeconds, GetClockPulses, Now, GMT, Period ],
Atom     USING [ PropList, PutPropOnList, GetPropFromList, RemPropFromList,
         DottedPair, DottedPairNode ],
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 [ Close, PutRope, STREAM, SetIndex, UnsafeGetBlock,
         UnsafePutBlock ],
Rope     USING [ ROPE, Cat, Substr, Index, Length, Equal ],
Convert    USING [ RopeFromCard, RopeFromInt, RopeFromReal, RealFromRope,
         RopeFromTime, TimeFromRope ],
Real     USING [ Fix, RoundC, Float, RoundI ],
Imager    USING [ Rectangle ],
Pixels     USING [ PixelBuffer, Extent, GetScanSeg, PutScanSeg, SampleSetSequence,
         SampleSet, GetSampleSet, PixelOp ],
SampleMapOps  USING [ GetPointer ],
ThreeDBasics  USING [ Box, ClipState, Context, NatSequence, Pair, Quad, RealSequence,
         Rectangle, RGB, ShapeInstance, ShapeSequence, SixSides, Triple,
         Vertex ],
ThreeDScenes  USING [ AddAlphaBuffer, Create, DisplayFromVM, Error,
         FillInBackGround, FillViewPort, GetShading, ReadScene,
         SetEyeSpace, SetWindow, SetViewPort, WriteScene,
         XfmToDisplay, XfmToEyeSpace ],
ThreeDMisc   USING [ CombineBoxes, CopyContextData, CopyDisplayData, StartLog,
         FlushLog, PrependWorkingDirectory, MakeFrame ];
DistributedDisplayImpl: CEDAR MONITOR
IMPORTS Atom, BasicTime, CedarProcess, ComputeServerClient, ComputeClientExtras, ComputeClientInternal, Convert, FS, IO, Pixels, Process, Real, Rope, RPC, SampleMapOps, ThreeDMisc, ThreeDScenes
EXPORTS ThreeDMisc
~ BEGIN
Types
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;
RealSequence: TYPE ~ ThreeDBasics.RealSequence;
RGB: TYPE ~ ThreeDBasics.RGB;
Rectangle: TYPE ~ ThreeDBasics.Rectangle;
NatSequence: TYPE ~ ThreeDBasics.NatSequence;
IntSequence: TYPE ~ RECORD [ length: NAT ← 0, data: SEQUENCE maxLength: NAT OF INT ];
StreamPair: TYPE ~ RECORD [ in, out: IO.STREAM ];
CountedCondition: TYPE ~ RECORD [ count: NAT, condition: CONDITION ];
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
costPerSecond: INT ← 200;        -- cost measure for 1 second compute time
imageSpaceDivision: BOOLEANFALSE;    -- for forcing image subdivision method
computingRemote: BOOLEANTRUE;     -- flag for forcing local execution
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, showGaps: BOOLEANFALSE;   -- pedagogical aids
showBoxCoverage: REAL ← 0.2;
Utility Procedures
Ceiling: PROC[ in: REAL ] RETURNS[ out: INTEGER ] ~ {
out ← Real.RoundI[in];
IF Real.Float[out] < in THEN out ← out + 1;
};
Floor: PROC[ in: REAL ] RETURNS[ out: INTEGER ] ~ {
out ← Real.RoundI[in];
IF Real.Float[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 *(BasicTime.PulsesToSeconds[BasicTime.GetClockPulses[]] - startTime);
RETURN[ Rope.Cat[ Convert.RopeFromReal[ Real.Fix[timeX100] / 100.0 ], " s. " ] ];
};
CurrentTime: PROC[] RETURNS[REAL] ~ {
RETURN[ BasicTime.PulsesToSeconds[BasicTime.GetClockPulses[]] ];
};
AddTimes: PROC[msg: Rope.ROPE, times: REF RealSequence] RETURNS[REF RealSequence] ~ {
newTimes: REF RealSequence ← NEW[RealSequence[timesKept]];
pos, pos2: NAT ← 0;
pos ← MIN[ Rope.Index[msg, pos, "set-up: "] + 8, Rope.Length[msg] ];
pos2 ← Rope.Index[msg, pos, "s."];
IF pos2 <= pos
THEN RETURN [times]
ELSE newTimes[0] ← Convert.RealFromRope[ Rope.Substr[msg, pos, pos2 - pos] ];
times[0] ← times[0] + newTimes[0];
pos ← MIN[ Rope.Index[msg, pos, "rendering: "] + 11, Rope.Length[msg] ];
pos2 ← Rope.Index[msg, pos, "s."];
newTimes[1] ← Convert.RealFromRope[ Rope.Substr[msg, pos, pos2 - pos] ];
times[1] ← times[1] + newTimes[1];
pos ← MIN[ Rope.Index[msg, pos, "output: "] + 8, Rope.Length[msg] ];
pos2 ← Rope.Index[msg, pos, "s."];
newTimes[2] ← Convert.RealFromRope[ Rope.Substr[msg, pos, pos2 - pos] ];
times[2] ← times[2] + newTimes[2];
pos ← MIN[ Rope.Index[msg, pos, "total: "] + 7, Rope.Length[msg] ];
pos2 ← Rope.Index[msg, pos, "s."];
IF pos2 <= pos
THEN newTimes[3] ← newTimes[0] + newTimes[1] + newTimes[2]  -- no total
ELSE newTimes[3] ← Convert.RealFromRope[ Rope.Substr[msg, pos, pos2 - pos] ];
times[3] ← times[3] + newTimes[3];
pos ← MIN[ Rope.Index[msg, pos, "matted in: "] + 11, Rope.Length[msg] ];
pos2 ← Rope.Index[msg, pos, "s."];
newTimes[4] ← 0.0;
IF pos2 > pos THEN newTimes[4] ← Convert.RealFromRope[Rope.Substr[msg, pos, pos2 - pos]];
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;
};
SortShapes: PROC[context: REF Context, numForksHint: NAT] RETURNS [REF NatSequence] ~ {
shapeOrder: REF NatSequence;
Sort Objects
{ shape: REF ShapeSequence ← context.shapes;
shapeOrder ← NEW[ NatSequence[ context.shapes.length - context.lights.length] ];
FOR i: NAT IN [0..context.shapes.length) DO
IF shape[i] # NIL AND Atom.GetPropFromList[shape[i].props, $Hidden] = NIL THEN
IF shape[i].clipState # out AND shape[i].surface # NIL THEN {
Bubble sort shapes, numShapes assumed quite small
FOR j: NAT DECREASING IN [0..shapeOrder.length) DO
IF shape[i].centroid.ez < shape[shapeOrder[j]].centroid.ez
THEN { shapeOrder[j+1] ← shapeOrder[j]; shapeOrder[j] ← i; }
ELSE { shapeOrder[j+1] ← i; EXIT; };
ENDLOOP;
IF shapeOrder.length = 0 THEN shapeOrder[0] ← 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.left > box2.right  OR box2.left > box1.right
OR box1.bottom > box2.top OR box2.bottom > box1.top
THEN RETURN[FALSE]
ELSE RETURN[TRUE];
};
FOR i: NAT IN [0..shapeOrder.length) DO
occlusionList ← NIL;
FOR j: NAT IN [0..i) DO
IF Overlap[context.shapes[shapeOrder[i]].screenExtent,
   context.shapes[shapeOrder[j]].screenExtent]
THEN occlusionList ← CONS[context.shapes[shapeOrder[j]], occlusionList];
ENDLOOP;
context.shapes[shapeOrder[i]].props ← Atom.PutPropOnList[ -- list of occluding shapes
context.shapes[shapeOrder[i]].props,
$Occlusions,
occlusionList
];
ENDLOOP;
};
RETURN[ shapeOrder ];
};
CostHeuristic: PROC[shape: REF ShapeInstance] RETURNS[seconds: INT] ~ {
 Start with area of bounding box
cost: INT ←  INT[(shape.screenExtent.right - shape.screenExtent.left)]
    * (shape.screenExtent.top - shape.screenExtent.bottom);   
times 3 for Non-linear surface
IF shape.type # $ConvexPolygon THEN cost ← cost * 3;
times 2 for Transparency
IF ThreeDScenes.GetShading[shape, $Transmittance] # NIL AND shape.insideVisible
THEN cost ← cost * 2;
times 2 for Mapped Texture
IF ThreeDScenes.GetShading[ shape, $TextureMap ] # NIL THEN cost ← cost * 2;
times 4 for Solid Texture - cost could be higher
IF ThreeDScenes.GetShading[ shape, $ShadingProcs ] # NIL THEN cost ← cost * 4;
Estimated maximum seconds for completion
seconds ← cost / costPerSecond;
};
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;
IF computingRemote = FALSE THEN RETURN[ NIL, 1.0 ];   -- not using compute server
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 ThreeDScenes.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, log: IO.STREAM,
      startTime: REAL ] ~ {
Await completion of processes and log messages
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[" rendering: ", 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,
       shapes: REF ShapeSequence, cost, processCount, startTime: REF]
       RETURNS[tmpCtx: REF Context] ~ {
Build new context to send to forked process
tmpCtx ← NEW[ Context ];
ThreeDMisc.CopyContextData[dstCtx: tmpCtx, srcCtx: context];
ThreeDMisc.CopyDisplayData[dstCtx: tmpCtx, srcCtx: context];
IF killBackground
THEN tmpCtx.props ← Atom.PutPropOnList[tmpCtx.props, $BackGround, NIL] -- no bckgrd
ELSE tmpCtx.props ← Atom.PutPropOnList[    -- copy background from context
tmpCtx.props, $BackGround,
Atom.GetPropFromList[context.props, $BackGround]
];
tmpCtx.props ← Atom.PutPropOnList[tmpCtx.props, $ComputeCost, cost ];
tmpCtx.props ← Atom.PutPropOnList[tmpCtx.props, $ProcessCount, processCount];
tmpCtx.props ← Atom.PutPropOnList[tmpCtx.props, $StartTime, startTime];
tmpCtx.props ← Atom.PutPropOnList[tmpCtx.props, $SubImageName, name];
Kill imager context to avoid side effects
tmpCtx.display.props ← Atom.PutPropOnList[tmpCtx.display.props, $ImagerContext, NIL];
tmpCtx.shapes ← NEW[ ShapeSequence[ context.lights.length + shapes.length] ];          
FOR i: NAT IN [0..context.lights.length) DO       -- retain all light sources
tmpCtx.shapes[i] ← NEW[ ShapeInstance ← context.lights[i]^ ];
ENDLOOP;
FOR i: NAT IN [0 .. shapes.length) DO
j: NAT ← i + context.lights.length;
tmpCtx.shapes[j] ← NEW[ ShapeInstance ← shapes[i]^ ]; -- add each shape
Copy proplists to avoid side effects
tmpCtx.shapes[j].props ← tmpCtx.shapes[j].shadingProps ← NIL;
FOR list: Atom.PropList ← shapes[i].props, list.rest UNTIL list = NIL DO
element: Atom.DottedPair ← NEW[Atom.DottedPairNode ← list.first^];
tmpCtx.shapes[j].props ← CONS[element, tmpCtx.shapes[j].props];
ENDLOOP;
FOR list: Atom.PropList ← shapes[i].shadingProps, list.rest UNTIL list = NIL DO
element: Atom.DottedPair ← NEW[Atom.DottedPairNode ← list.first^];
tmpCtx.shapes[j].shadingProps ← CONS[element, tmpCtx.shapes[j].shadingProps];
ENDLOOP;
ENDLOOP;
};
AddShape: PROC[ shapes: REF ShapeSequence, newShape: REF ShapeInstance ]
   RETURNS [REF ShapeSequence] ~ {
size: NATIF shapes # NIL THEN shapes.length + 1 ELSE 1;
tmpShapes: REF ShapeSequence ← NEW[ ShapeSequence[size] ];
IF shapes # NIL THEN
FOR i: NAT IN [0..shapes.length) DO tmpShapes[i] ← shapes[i]; ENDLOOP; -- copy list
tmpShapes[tmpShapes.length-1] ← newShape;
RETURN[tmpShapes];
};
DeleteShape: PROC[ shapes: REF ShapeSequence, oldShape: REF ShapeInstance ]
    RETURNS [REF ShapeSequence] ~ {
tmpShapes: REF ShapeSequence ← NEW[ ShapeSequence[shapes.length - 1] ];
FOR i: NAT IN [0..shapes.length) DO
IF Rope.Equal[shapes[i].name, oldShape.name] THEN {    -- find matching shape
FOR j: NAT IN [0..i) DO tmpShapes[j] ← shapes[j]; ENDLOOP; -- copy up to oldshape
FOR j: NAT IN [i..shapes.length-1) DO tmpShapes[j] ← shapes[j+1]; ENDLOOP; -- remove
EXIT;
};
ENDLOOP;
RETURN[tmpShapes];
};
Multiprocessor control
RemoteMakeFrame: PUBLIC PROC[context: REF Context, numForksHint: NAT ← 0] ~ {
Uses compute server to parcel out rendering to other processors
log: IO.STREAMNARROW[ Atom.GetPropFromList[context.props, $Log] ];
shape: REF ShapeSequence ← context.shapes;
shapeOrder: REF NatSequence;
startTime: REAL ← CurrentTime[];
context.stopMe ← FALSE;         -- release remote stop flag
IF serverStatsWanted THEN serverStatsOut ← FS.StreamOpen[
fileName: ThreeDMisc.PrependWorkingDirectory[context, Rope.Cat["Temp/", "ServerStats"]],
accessOptions: $create
];
IF serverStatsTime = 0.0 THEN serverStatsTime ← startTime; -- initialize time
IF context.renderMode # $Dorado24 AND context.renderMode # $FullColor
THEN SIGNAL ThreeDScenes.Error[[$MisMatch, "Full color display expected"]];
IF log = NIL THEN log ← ThreeDMisc.StartLog[context];  -- open log file if not yet done
Get Everything (including light centroids) into eyespace
FOR i: NAT IN [0.. shape.length) DO
IF Atom.GetPropFromList[shape[i].props, $Hidden] = NIL OR shape[i].type = $Light
THEN IF shape[i].vtcesInValid THEN { 
shape[i].clipState ← ThreeDScenes.XfmToEyeSpace[context, shape[i]];
IF shape[i].clipState # out
THEN ThreeDScenes.XfmToDisplay[context, shape[i] ];
};
ENDLOOP;
Sort Shapes
IF NOT imageSpaceDivision THEN shapeOrder ← SortShapes[context, numForksHint];
IF numForksHint > 0 THEN {
log.PutRope[Rope.Cat["\n", Convert.RopeFromCard[numForksHint], " processors"] ];
IF imageSpaceDivision THEN log.PutRope[" - slices "];
IF noCostAdjustments THEN log.PutRope[" - No Costing "];
};
log.PutRope[Rope.Cat["\nObject transform and sort: ", ElapsedTime[startTime] ]];
Prepare for display
ThreeDScenes.FillViewPort[context, [0.0, 0.0, 0.0] ];  -- clear all pixel bits
Distribute subscenes to servers
IF imageSpaceDivision
THEN ForkSubImageProcs[context, startTime, log, numForksHint]
ELSE ForkSubSceneProcs[context, shapeOrder, startTime, log, numForksHint];
Finish Frame
IF NOT imageSpaceDivision THEN {
ThreeDMisc.CombineBoxes[context];    -- get combined bounding box on scene
ThreeDScenes.FillInBackGround[context];  -- load background
};
log.PutRope[Rope.Cat["All done at ", ElapsedTime[startTime], "\n\n" ] ];
ThreeDMisc.FlushLog[context];
IF serverStatsOut # NIL THEN IO.Close[serverStatsOut];
};
ForkSubImageProcs: PROC[context: REF Context,
        startTime: REAL, log: IO.STREAM, numForksHint: NAT] ~ {
Edge: TYPE ~ RECORD [shape, position: NAT, entering: BOOLEAN];
EdgeSequence: TYPE ~ RECORD [length: NAT ← 0, s: SEQUENCE maxLength: NAT OF Edge];
shapeEdgeOrder: REF EdgeSequence ← NEW[
EdgeSequence[ 2 * (context.shapes.length - context.lights.length) ]
];
processCount: REF CountedCondition ← NEW[CountedCondition];
procList: LIST OF CedarProcess.Process ← NIL;
shape: REF ShapeSequence ← context.shapes;
cost: REF RealSequence ← NEW[ RealSequence[shape.length] ];
totalCost, averageCost: REAL ← 0;
IF NOT noCostAdjustments THEN {
Find average scan conversion cost
FOR i: NAT IN [0..shape.length) DO
IF shape[i] # NIL AND Atom.GetPropFromList[shape[i].props, $Hidden] = NIL THEN
IF shape[i].clipState # out AND shape[i].surface # NIL THEN {
Estimate relative cost of each shape (untamed heuristics here)
cost[i] ← CostHeuristic[shape[i]];
totalCost ← totalCost + cost[i]
};
ENDLOOP;
IF numForksHint # 0
THEN {
averageCost ← totalCost / numForksHint; -- base division on no. of processors
processCount.count ← numForksHint  -- limit processors (2 processes per processor)
}
ELSE {
should consult Summoner to find number of idle machines
SIGNAL ThreeDScenes.Error[[$MisMatch, "No processors?"]];
};
Adjust costs to unit width
FOR i: NAT IN [0..shape.length) DO
IF shape[i] # NIL AND Atom.GetPropFromList[shape[i].props, $Hidden] = NIL THEN
IF shape[i].clipState # out AND shape[i].surface # NIL THEN {
cost[i] ← cost[i] / ( shape[i].screenExtent.right + 1 - shape[i].screenExtent.left );
};
ENDLOOP;
Sort Object Screen Extents left to right
FOR s: NAT IN [0..shape.length) DO
IF shape[s] # NIL AND Atom.GetPropFromList[shape[s].props, $Hidden] = NIL THEN
IF shape[s].clipState # out AND shape[s].surface # NIL THEN {
Bubble sort left and right shape edges, numShapes assumed quite small
FOR i: NAT IN [0..2) DO
position: NATIF i = 0 THEN shape[s].screenExtent.left
       ELSE
shape[s].screenExtent.right;
left: BOOLEAN ← i = 0;
EnterEdge: PROC[place, shape: NAT] ~ {
shapeEdgeOrder[place].shape ← s;
shapeEdgeOrder[place].position ← position;
shapeEdgeOrder[place].entering ← left;
};
FOR p: NAT DECREASING IN [0..shapeEdgeOrder.length) DO
IF position < shapeEdgeOrder[p].position
THEN { shapeEdgeOrder[p+1] ← shapeEdgeOrder[p]; EnterEdge[p, s]; }
ELSE { EnterEdge[p+1, s]; EXIT; };
ENDLOOP;
IF shapeEdgeOrder.length = 0 THEN EnterEdge[0, s];
shapeEdgeOrder.length ← shapeEdgeOrder.length + 1;
ENDLOOP;
};
ENDLOOP;
};
Parcel out image slices to servers
{ currentPlace: NAT ← 0;
currentCost: REAL ← 0.0;
activeShapes: REF ShapeSequence ← NIL;
lastPos: REAL ← 0.0;
thisPos: REAL ← shapeEdgeOrder[currentPlace].position;
FOR i: NAT IN [0..numForksHint) DO    -- do side to side
sliceCost: REAL ← 0.0;
activeShapesInSlice: REF ShapeSequence ← NIL;
Set up window to clip image apart
viewPortSize: REALMAX[context.viewPort.w, context.viewPort.h];
vuPtWindow: Imager.Rectangle ← [
x: MAX[ 0.0, context.viewPort.h - context.viewPort.w ] / viewPortSize,
y: MAX[ 0.0, context.viewPort.w - context.viewPort.h ] / viewPortSize,
w: 1.0,
h: 1.0
];
left: REAL ← lastPos;
right: REAL ← context.viewPort.w;
top: REAL ← context.viewPort.h;
bottom: REAL ← 0;
forkedProcess: CedarProcess.Process;
tmpCtx: REF Context;
IF context.stopMe
THEN { KillProcs[ context, procList ]; RETURN[]; };  -- escape hatch
IF noCostAdjustments
THEN {
left ← i * right / numForksHint;
right ← (i+1) * right / numForksHint;
activeShapesInSlice ← NEW[
ShapeSequence[ context.shapes.length - context.lights.length ] ];
FOR i: NAT IN [0..activeShapesInSlice.length) DO
j: NAT ← i + context.lights.length;
activeShapesInSlice[i] ← context.shapes[j];
ENDLOOP;
IF numForksHint # 0
THEN processCount.count ← numForksHint
ELSE processCount.count ← 200/2;
sliceCost ← 1.0;     -- to avoid divide errors, etc.
}
ELSE {
Calculate slice width and active shapes
IF activeShapes # NIL THEN {    -- grab all currently active shapes
activeShapesInSlice ← NEW[ ShapeSequence[activeShapes.length] ];
FOR i: NAT IN [0..activeShapes.length) DO
activeShapesInSlice[i] ← activeShapes[i];
ENDLOOP;
};
WHILE TRUE DO
costLeft: REAL ← averageCost - sliceCost; -- ideal slice cost - accumulated cost
IF costLeft > currentCost * (thisPos - lastPos)
THEN {          -- finishing shape, get the next one
sliceCost ← sliceCost + currentCost * (thisPos - lastPos); -- add this shape
IF shapeEdgeOrder[currentPlace].entering
THEN {           -- moving into shape
currentCost ← currentCost + cost[shapeEdgeOrder[currentPlace].shape];
activeShapes ← AddShape[activeShapes,
       shape[ shapeEdgeOrder[currentPlace].shape] ];
activeShapesInSlice ← AddShape[activeShapesInSlice,
       shape[ shapeEdgeOrder[currentPlace].shape] ];
}
ELSE {           -- moving out of shape
currentCost ← currentCost - cost[shapeEdgeOrder[currentPlace].shape];
activeShapes ← DeleteShape[activeShapes,
       shape[ shapeEdgeOrder[currentPlace].shape] ];
};
lastPos ← thisPos;
currentPlace ← currentPlace + 1;
IF currentPlace < shapeEdgeOrder.length
THEN thisPos ← shapeEdgeOrder[currentPlace].position
ELSE EXIT;    -- off end of sorted shape array, must be last slice
}
ELSE {          -- slice ends in middle of shape
oldPos: REAL ← lastPos;
lastPos ← right ← lastPos + costLeft / currentCost; -- no new shapes
sliceCost ← sliceCost + currentCost * (lastPos - oldPos);
EXIT;
};
ENDLOOP;
};
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,
shapes: activeShapesInSlice,
cost: NEW[ INT ← Real.RoundC[sliceCost] ],
processCount: processCount,
startTime: NEW[ REAL ← startTime ]
];
IF i = numForksHint-1 THEN tmpCtx.props ← Atom.PutPropOnList[
tmpCtx.props,
$RightMostSlice,
NEW[BOOLEANTRUE]
];
Set window in context
left ← MAX[0, left];         -- limit window width
right ← MIN[context.viewPort.w-1, right];  -- kludge to keep in bounds
ThreeDScenes.SetViewPort[ tmpCtx, [
left + context.viewPort.x,
bottom + context.viewPort.y,
right - left,
top - bottom
] ];
ThreeDScenes.SetWindow[ tmpCtx, [
x: (2.0 * left / viewPortSize) - 1.0 + vuPtWindow.x, -- window range is -1.0 — +1.0
y: (2.0 * bottom / viewPortSize) - 1.0 + vuPtWindow.y,
w: 2.0 * (right - left) / viewPortSize,
h: 2.0 * (top - bottom) / 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
ENDLOOP;
};
Await completion of processes and log messages
JoinProcs[context: context, procList: procList, log: log, startTime: startTime];
};
ForkSubSceneProcs: PROC[context: REF Context, shapeOrder: REF NatSequence,
        startTime: REAL, log: IO.STREAM, numForksHint: NAT] ~ {
processCount: REF CountedCondition ← NEW[CountedCondition];
allProcsList: LIST OF CedarProcess.Process ← NIL;
cost: REF IntSequence ← NEW[ IntSequence[ shapeOrder.maxLength] ];
totalCost, averageCost: INT ← 0;
Find average scan conversion cost
IF noCostAdjustments
THEN {
averageCost ← 1;
FOR i: NAT IN [0..shapeOrder.maxLength) DO cost[i] ← 1; ENDLOOP;
IF numForksHint # 0
THEN processCount.count ← numForksHint
ELSE processCount.count ← 200/2;
}
ELSE {
shape: REF ShapeSequence ← context.shapes;
FOR j: NAT IN [0..shapeOrder.length) DO
Estimate relative cost of each shape (untamed heuristics here)
i: NAT ← shapeOrder[j];
cost[j] ← CostHeuristic[shape[i]];
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
screenExtent: ThreeDBasics.Box ← context.shapes[shapeOrder[i]].screenExtent;
procList: LIST OF CedarProcess.Process ← NIL;
baseName: Rope.ROPE ← context.shapes[shapeOrder[i]].name;
imageCount: NAT ← Real.RoundC[ Real.Float[ cost[i] ] / averageCost ];
IF imageCount < 1 THEN imageCount ← 1;
IF context.stopMe
THEN { KillProcs[ context, allProcsList ]; RETURN[]; }; -- escape hatch
FOR j: NAT IN [0..imageCount) DO    -- do for each slice of object
Calculate Window to clip object apart
viewPortSize: REALMAX[context.viewPort.w, context.viewPort.h];
vuPtWindow: Imager.Rectangle ← [    -- size of viewPort within unit square
x: -1.0 + MAX[ 0.0, context.viewPort.h - context.viewPort.w ] / viewPortSize,
y: -1.0 + MAX[ 0.0, context.viewPort.w - context.viewPort.h ] / viewPortSize,
w: 2.0,
h: 2.0
];
left: REAL ← screenExtent.left
   + (Real.Float[j] / imageCount) * (screenExtent.right - screenExtent.left);
right: REAL ← screenExtent.left
   + (Real.Float[j+1] / imageCount) * (screenExtent.right - screenExtent.left);
top: REAL ← screenExtent.top;
bottom: REAL ← screenExtent.bottom;
Build new context to send to forked process
forkedProcess: CedarProcess.Process;
tmpCtx: REF Context;
shapes: REF ShapeSequence ← NEW[ ShapeSequence[1] ];
shapes[0] ← context.shapes[shapeOrder[i]];
tmpCtx ← GetTempContext[
context: context,
name: Rope.Cat[ baseName, Convert.RopeFromCard[j] ],  -- get a unique name               
killBackground: TRUE,
shapes: shapes,
cost: NEW[ INT ← cost[i] / imageCount ],
processCount: processCount,
startTime: NEW[ REAL ← startTime ]
];
IF j = imageCount-1 THEN tmpCtx.props ← Atom.PutPropOnList[
tmpCtx.props,
$RightMostSlice,
NEW[BOOLEANTRUE]
];
Set window in context
left ← MAX[0.0, left - 1.0];      -- spread window by a pixel on each side
right ← MIN[context.viewPort.w-1.0, right + 1.0];
ThreeDScenes.SetViewPort[ tmpCtx, [
left + context.viewPort.x,
bottom + context.viewPort.y,
right - left,
top - bottom
] ];
ThreeDScenes.SetWindow[ tmpCtx, [
x: (2.0 * left / viewPortSize) + vuPtWindow.x, -- window range is -1.0 — +1.0
y: (2.0 * bottom / viewPortSize) + vuPtWindow.y,
w: 2.0 * (right - left) / viewPortSize,
h: 2.0 * (top - bottom) / 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;
context.shapes[shapeOrder[i]].props ← Atom.PutPropOnList[ -- store proc refs with shape
context.shapes[shapeOrder[i]].props,
$RemoteProc,
procList          -- leave list of proc refs here
];
IF showBoxes AND computingSerially THEN { -- bounding boxes for pedagogical purposes
area: Pixels.Extent ← [
x: screenExtent.left,
y: screenExtent.bottom,
w: screenExtent.right - screenExtent.left,
h: screenExtent.top - screenExtent.bottom
];
pixelValues: Pixels.SampleSet ← Pixels.GetSampleSet[4];
color: REF RGBNARROW[ThreeDScenes.GetShading[
context.shapes[shapeOrder[i]],
$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 ];
};
ENDLOOP;
Await completion of processes and log messages
JoinProcs[ context, allProcsList, log, startTime ];
FOR i: NAT IN [0..shapeOrder.length) DO      -- clear out process REFs
context.shapes[shapeOrder[i]].props ← Atom.RemPropFromList[
context.shapes[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 ← ThreeDMisc.PrependWorkingDirectory[
context,
Rope.Cat[ "Temp/", NARROW[ Atom.GetPropFromList[context.props, $SubImageName] ] ]
];
input: IO.STREAMNIL;
ref: REF ← Atom.GetPropFromList[context.props, $RightMostSlice];
rightMostSlice: BOOLEANIF ref # NIL THEN NARROW[ ref, REF BOOLEAN ]^ ELSE FALSE;
forkedProc: ARRAY[0..maxProcClonesAllowed) OF CedarProcess.Process;
procIO: ARRAY[0..maxProcClonesAllowed) OF REF StreamPair;
serverName: ARRAY[0..maxProcClonesAllowed) OF Rope.ROPE;
serverPctAvail: ARRAY[0..maxProcClonesAllowed) OF 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., "];
results ← returnMsg;
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 {
returnMsg ← Rope.Cat[returnMsg, "\n "];
FOR k: NAT IN [0..i) DO
returnMsg ← Rope.Cat[
returnMsg,
serverName[k], " "
];
IF CurrentTime[] - lastTime >= (i) * 2 * estComputeTime
THEN returnMsg ← Rope.Cat[returnMsg, "over time limit, "]
ELSE returnMsg ← Rope.Cat[returnMsg, Convert.RopeFromReal[ serverPctAvail[k] ],
        " too busy, "];
ENDLOOP;
};
procIO[i] ← NEW[ StreamPair ];
procIO[i].in ← FS.StreamOpen[
fileName: Rope.Cat[ fileName, "-in", Convert.RopeFromCard[i] ],
accessOptions: $create
];
procIO[i].out ← FS.StreamOpen[
fileName: Rope.Cat[ fileName, "-out", Convert.RopeFromCard[i] ],
accessOptions: $create
];
Start Remote Process and Send Scene Data
ThreeDScenes.WriteScene[context, procIO[i].out]; -- get scene to remote proc
IO.SetIndex[procIO[i].out, 0];  -- reset index for downstream read
returnMsg ← Rope.Cat[returnMsg, "Started proc. at: ", ElapsedTime[startTime], " "];
Limit remote calls to control number of processors used
IF i = 0 THEN GetProcess[NARROW[ Atom.GetPropFromList[context.props, $ProcessCount] ]];
forkedProc[i] ← CedarProcess.Fork[CallComputeServer, procIO[i] ];  -- fork process
Monitor process for completion and remote machine utilization
WHILE CurrentTime[] - lastTime < (i+1) * 2 * estComputeTime  -- allow 2*estimated time
OR NOT computingRemote OR procClonesAllowed = 1 DO-- these stop timeout
KillChildren: PROC[ i: NAT ] ~ {
FOR k: NAT IN [0..i] DO CedarProcess.Abort[ forkedProc[k] ]; ENDLOOP;
ERROR ABORTED;
};
serversAvailable: BOOLEANFALSE;
CedarProcess.CheckAbort[ ! ABORTED => KillChildren[i] ]; -- abort on request
Process.Pause[ Process.SecondsToTicks[1] ];  -- pause for a second
FOR j: NAT IN [0..i] DO        -- check on each forked process
result: REF;
status: CedarProcess.Status ← CedarProcess.GetStatus[ forkedProc[j] ];
IF status = done OR procClonesAllowed = 1  -- don't timeout if no clones allowed
THEN {              -- finished!
FOR k: NAT IN [0..i] DO        -- abort other procs
IF k # j THEN {
returnMsg ← Rope.Cat[
returnMsg, "\n aborted proc on ",
ComputeClientExtras.RemoteProcessSite[forkedProc[k].process],
" "
];
CedarProcess.Abort[ forkedProc[k] ];
};
ENDLOOP;
[status, result] ← CedarProcess.Join[ forkedProc[j] ];  -- get proc results
ReleaseProcess[NARROW[ Atom.GetPropFromList[context.props, $ProcessCount] ]];
returnMsg ← Rope.Cat[ returnMsg, NARROW[result, Rope.ROPE] ];
input ← procIO[j].in;
EXIT;         -- some process finished, stop checking
}
ELSE IF status = aborted
THEN EXIT       -- go try again if aborted
ELSE {         -- check on remote processor utilization
[ serverName[j], serverPctAvail[j] ] ← ServerUsage[ forkedProc[j] ];
IF serverPctAvail[j] > minimumUsefulServerPortion
THEN serversAvailable ← TRUE  -- based on 5 second samples
ELSE { server: Rope.ROPE ← serverName[j]; }; -- place for debug
};
IF NOT serversAvailable AND i < procClonesAllowed-1
THEN EXIT;         -- lousy service, get another server
ENDLOOP;
IF input # NIL THEN EXIT;    -- some process finished, stop waiting
ENDLOOP;
IF input # NIL THEN EXIT;    -- some process finished, stop cloning new ones
ENDLOOP;
IF input = 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] ];
IF i = 0 THEN
ReleaseProcess[ NARROW[ Atom.GetPropFromList[ context.props, $ProcessCount] ] ];
ENDLOOP;
};
Process Return message
times ← AddTimes[returnMsg, times];
returnMsg ← Rope.Cat[returnMsg, "\n cost factor: ",
  RopeFromSeconds[ times[3] / estComputeTime]];
returnMsg ← Rope.Cat[returnMsg, " remote ovrhd: ",    -- compute server overhead
       RopeFromSeconds[ CurrentTime[] - startTime - times[3] ], " s. " ];
IF input # NIL THEN IO.SetIndex[input, 0]; -- reset index for returning pixel stream
Check that all occluding processes are complete
IF NOT imageSpaceDivision THEN {
lastTime ← CurrentTime[];
FOR i: NAT IN [0..context.shapes.length) DO
IF Atom.GetPropFromList[context.shapes[i].props, $Hidden] = NIL THEN { -- no lights
list of occluding shapes
occlusionList: LIST OF REF ShapeInstance ← NARROW[
      Atom.GetPropFromList[ context.shapes[i].props, $Occlusions ] ];
FOR shapes: LIST OF REF ShapeInstance ← occlusionList, shapes.rest
                  UNTIL
shapes = NIL DO
procList: LIST OF CedarProcess.Process ← NARROW[ Atom.GetPropFromList[
 shapes.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;
returnMsg ← Rope.Cat[returnMsg, " waited for: ", ElapsedTime[lastTime] ];
};
Display Pixels from Remote Process
lastTime ← CurrentTime[];
IF input # NIL THEN {
xPos: NAT ← Floor[context.viewPort.x];
yPos: NAT ← Floor[context.viewPort.y];
width: NAT ← Ceiling[context.viewPort.w];
outWidth: NATIF rightMostSlice OR imageSpaceDivision THEN width ELSE width-2;
height: NAT ← Ceiling[context.viewPort.h];
writeOp: ATOMIF imageSpaceDivision THEN $Write ELSE $WriteUnder;
scanSeg: REF Pixels.SampleSetSequence ← Pixels.GetScanSeg[ context.display, 0, 0, width ];
IF showGaps AND NOT rightMostSlice THEN outWidth ← outWidth - 2;
FOR y: NAT IN [ 0 .. height ) DO
Get scanline from remote proc
FOR i: NAT IN [0.. context.display.samplesPerPixel) DO
TRUSTED {
IF IO.UnsafeGetBlock[ -- uses 16 bits per byte (wasting net bandwidth)
self: input,
block: [ base: LOOPHOLE[SampleMapOps.GetPointer[scanSeg[i], 0, width]],
  count: 2*width ]
] = 2*width
THEN NULL
ELSE {
returnMsg ← Rope.Cat[returnMsg, "Unexpected end of stream"]; -- too short
GOTO GiveUp;
};
};
ENDLOOP;
Write to context with appropriate Op
Pixels.PutScanSeg[context.display, 0, y, outWidth, scanSeg, writeOp];
ENDLOOP;
EXITS GiveUp => NULL;
};
returnMsg ← Rope.Cat[returnMsg, " matted in: ", ElapsedTime[lastTime] ];
returnMsg ← Rope.Cat[returnMsg, "\n done at: ", ElapsedTime[startTime] ];
RETURN[returnMsg];
};
CallComputeServer: CedarProcess.ForkableProc ~ {
PROC [data: REF] RETURNS [results: REFNIL]
procIO: REF StreamPair ← NARROW[data];
input: IO.STREAM ← procIO.in;
output: IO.STREAM ← procIO.out;
found: BOOLEAN;
success: ComputeServerClient.RemoteSuccess ← false;
successMsg, procMsg, server: Rope.ROPENIL;
IF NOT computingRemote
THEN [success, procMsg, server] ← RenderFromStream[  -- test code, no remote calls
Convert.RopeFromTime[from: BasicTime.Now[], end: seconds],
output, input
]
ELSE [ found: found, success: success, remoteMsg: procMsg, serverInstance: server ] ←
ComputeServerClient.StartService[
service: "Render3dFromStream",
cmdLine: Convert.RopeFromTime[from: BasicTime.Now[], end: seconds],
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];
};
RenderFromStream: PROC[cmd: Rope.ROPE, input, output: IO.STREAM]
    RETURNS[success: ComputeServerClient.RemoteSuccess, msg, server: Rope.ROPE] ~ {
Renders scene described on input stream, passes pixels back on output stream
startTime, lastTime: REAL ← CurrentTime[];
procTime: BasicTime.GMT ← BasicTime.Now[];
scanSeg: REF Pixels.SampleSetSequence;
displaycontext: REF Context;
context: REF Context ← ThreeDScenes.Create[];
serverDelay: INT ← BasicTime.Period[ Convert.TimeFromRope[cmd], procTime ];
msg ← Rope.Cat[" delay: ", Convert.RopeFromInt[ serverDelay], " s. " ];
ThreeDScenes.ReadScene[context, input];
ThreeDScenes.DisplayFromVM[ displaycontext,   -- get display bits of proper size
Ceiling[context.viewPort.w], Ceiling[context.viewPort.h],
$FullColor ];
ThreeDScenes.AddAlphaBuffer[displaycontext];
context.display ← displaycontext.display;   -- give display bits to context
ThreeDScenes.SetEyeSpace[context];    -- update for actual display size
msg ← Rope.Cat[" set-up: ", ElapsedTime[startTime] ]; lastTime ← CurrentTime[];
ThreeDMisc.MakeFrame[context];        -- render image
msg ← Rope.Cat[msg, " rendering: ", ElapsedTime[lastTime] ]; lastTime ← CurrentTime[];
Write pixels back on output stream
FOR y: NAT IN [0 .. Ceiling[context.viewPort.h] ) DO
scanSeg ← Pixels.GetScanSeg[context.display, 0, y, Ceiling[context.viewPort.w], scanSeg];
FOR i: NAT IN [0.. context.display.samplesPerPixel) DO
TRUSTED {
IO.UnsafePutBlock[ -- uses 16 bits per byte (wasting net bandwidth)
self: output,
block: [ base: LOOPHOLE[SampleMapOps.GetPointer[scanSeg[i], 0, scanSeg[i].length]],
  count: 2*scanSeg[i].length ]
];
};
ENDLOOP;
ENDLOOP;
msg ← Rope.Cat[msg, " output: ", ElapsedTime[lastTime], " total: ", ElapsedTime[startTime] ];
context ← displaycontext ← NIL;     -- kill off everything, no state saved  
success ← true;
server ← "local";
};
END.