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 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; stopMe: BOOLEAN _ FALSE; -- 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: BOOLEAN _ FALSE; -- for forcing image subdivision method computingSerially: BOOLEAN _ FALSE; -- flag for forcing serialization noCostAdjustments: BOOLEAN _ FALSE; -- flag for skipping optimization with cost estimation serverStats: Rope.ROPE _ NIL; -- Parameters for Server statistics serverStatsTime: REAL _ 0.0; serverStatsWanted: BOOLEAN _ FALSE; serverStatsOut: IO.STREAM _ NIL; minimumUsefulServerPortion: REAL _ .5; showBoxes: BOOLEAN _ FALSE; -- pedagogical aids (showGaps deleted) showBoxCoverage: REAL _ 0.2; 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] ~ { 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] ~ { 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]; }; 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] ~{ cost: INT _ INT[(shape.screenExtent.max.f - shape.screenExtent.min.f)] * (shape.screenExtent.max.s - shape.screenExtent.min.s); IF shape.class.type # $ConvexPolygon AND poly.type # $Poly THEN cost _ cost * 3; IF NOT antiAliasing THEN seconds _ cost / jaggyPixelsPerSecond ELSE { IF ThreeDBasics.GetShading[shape, $Transmittance] # NIL AND shape.insideVisible THEN cost _ cost * 2; IF ThreeDBasics.GetShading[ shape, $TextureMap ] # NIL THEN cost _ cost * 2; IF ThreeDBasics.GetShading[ shape, $ShadingProcs ] # NIL THEN cost _ cost * 4; seconds _ cost / pixelsPerSecond; }; }; ServerUsage: ENTRY PROC[process: CedarProcess.Process] RETURNS[server: Rope.ROPE, pctAvailable: REAL ] ~ { 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]]; }; }; 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 ] ~ { log: IO.STREAM _ NARROW[ Atom.GetPropFromList[context.props, $Log] ]; startTime: REAL _ NARROW[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] ~ { 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]; tmpCtx.displayProps _ Atom.RemPropFromList[tmpCtx.displayProps, $ImagerContext]; 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; }; 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: BOOLEAN _ FALSE; 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] ~ { totalCost: REAL _ 0; cost: REF RealSequence _ NEW[ RealSequence[shape.length] ]; shapeEdgeOrder _ NEW[ EdgeSequence[ 2 * shape.length ] ]; FOR i: NAT IN [0..shape.length) DO cost[i] _ CostHeuristic[shape[i], context.antiAliasing]; totalCost _ totalCost + cost[i] ENDLOOP; shapeEdgeOrder.averageCost _ totalCost / numForksHint; -- base division on no. of processors FOR i: NAT IN [0..shape.length) DO cost[i] _ cost[i] / ( shape[i].screenExtent.max.f + 1 - shape[i].screenExtent.min.f ); ENDLOOP; FOR s: NAT IN [0..shape.length) DO FOR i: NAT IN [0..2) DO position: NAT _ IF 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] ~ { 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] ~ { sliceCost: REAL _ 0.0; currentCost: REAL _ shapeEdgeOrder.currentCost; 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]; }; SortShapes: PROC[shape: REF ShapeSequence, numForksHint: NAT] RETURNS [REF ShapeSequence] ~ { shapeOrder: REF ShapeSequence _ NEW[ ShapeSequence[shape.length] ]; FOR i: NAT IN [0..shape.length) DO 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; { 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] ~ { }; 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: BOOLEAN _ FALSE; 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 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]; }; SetConcurrencyLevel: PUBLIC PROC[context: REF Context, numProcesses: NAT] ~ { context.props _ Atom.PutPropOnList[ context.props, $NumForksHint, NEW[ NAT _ numProcesses] ]; }; MakeFrame: PUBLIC PROC[context: REF Context] ~ { 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.STREAM _ NARROW[ Atom.GetPropFromList[context.props, $Log] ]; ref: REF _ Atom.GetPropFromList[context.props, $NumForksHint]; numForksHint: NAT _ IF 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 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] ]]; IF imageSpaceDivision THEN ForkSubImageProcs[context, numForksHint] ELSE ForkSubSceneProcs[context, numForksHint]; 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; shapeEdgeOrder _ GetBBoxOrder[context, shape, numForksHint]; -- Sort bounding boxes processCount.count _ numForksHint; -- limit processes ("procClonesAllowed" process clones) lastX _ shapeEdgeOrder[shapeEdgeOrder.currentPlace].position; FOR i: NAT IN [0..numForksHint) DO -- do side to side, one slice per fork forkedProcess: CedarProcess.Process; shapesInSlice: REF ShapeSequence; tmpCtx: REF Context; viewPortSize: REAL _ MAX[context.viewPort.w, context.viewPort.h]; viewPortWindowX: REAL _ MAX[0.0, context.viewPort.h -context.viewPort.w] /viewPortSize; viewPortWindowY: REAL _ MAX[0.0, context.viewPort.w -context.viewPort.h] /viewPortSize; IF context.stopMe^ THEN { KillProcs[ context, procList ]; RETURN[]; }; -- escape hatch [shapesInSlice, xPos] _ UpdateActiveShapes[shapeEdgeOrder, activeShapesInSlice, lastX]; 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 ]; 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 ] ]; 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 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; shapeOrder: REF ShapeSequence _ SortShapes[context.visibleShapes, numForksHint]; cost: REF IntSequence _ NEW[ IntSequence[ shapeOrder.maxLength] ]; 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 }; FOR i: NAT IN [0..shapeOrder.length) DO -- do front to back viewPortSize: REAL _ MAX[context.viewPort.w, context.viewPort.h]; viewPortWindowX: REAL _ MAX[0.0, context.viewPort.h -context.viewPort.w] /viewPortSize; viewPortWindowY: REAL _ MAX[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: NAT _ MAX[ 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 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 ]; 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 ] ]; 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; 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 ~ { context: REF Context _ NARROW[data]; startTime: REAL _ NARROW[ 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.STREAM _ NIL; reason: Rope.ROPE; forkedProc: REF ForkedProcessSequence _ NEW[ForkedProcessSequence[maxProcClonesAllowed]]; returnMsg: Rope.ROPE _ Rope.Cat[ NARROW[ Atom.GetPropFromList[context.props, $SubImageName] ], " - " ]; estComputeTime: INT _ NARROW[ 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., "]; 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 ] ] ]; 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 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 ]; [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; 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] ] ]; }; IF NOT imageSpaceDivision THEN{ lastTime _ CurrentTime[]; AwaitOccludingProcesses[context]; -- wait for processes of occluding objects to finish returnMsg _ Rope.Cat[returnMsg, " waited for: ", ElapsedTime[lastTime] ]; }; 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 ~ { list: LORA _ NARROW[data]; startTime: REAL _ NARROW[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.ROPE _ NIL; [ 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. bDistributedRenderImpl.mesa Last Edited by: Crow, May 10, 1989 12:42:47 pm PDT Types Global Constant/Variables Utility Procedures Reteurns position after string toBeFound, returns startPos if not found checks that previous PlaceAfter succeeded then looks for "s." as time indicator Support Procedures Start with area of bounding box times 3 for Non-linear surface times 2 for Transparency times 2 for Mapped Texture times 4 for Solid Texture - cost could be higher Estimated maximum seconds for completion Returns percent of remote machine process is getting (in theory). If anything goes wrong, return indicates process is getting all of machine. 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 Await completion of processes and log messages Build new context to send to forked process Kill imager context to avoid side effects Get light sources Image Slicing Support Procedures Sort bounding boxes left to right for balancing image slices Find average scan conversion cost Estimate relative cost of each shape (untamed heuristics here) Adjust costs to unit width Sort Object Screen Extents left to right Insertion sort left and right shape edges, (crude, numShapes assumed small) RECORD [shape: REF ShapeInstance, cost: REAL, position: NAT, entering: BOOLEAN]; Evaluates ordered edges and produces shape set and slice width of given cost Calculate slice width and active shapes Object Slicing Support Procedures Sort Objects Insertion sort shapes, (crude sort, numShapes assumed quite small) Make Lists of Occluding Objects 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 Get scanline from remote proc Multiprocessor control Uses compute server to parcel out rendering to other processors Update Shapes Distribute subscenes to servers Finish Frame Sort bounding boxes Parcel out image slices to servers Get limits from parent viewport for calculating slice windows Get active shapes for this slice, update slice boundary Build new context to send to forked process Set window in context Fork new Process to Render each slice of the image Await completion of processes and log messages Sort shapes to priority order Find average scan conversion cost Parcel out shapes to servers Get limits from parent viewport for calculating windows Build new context to send to forked process Set window in context Fork new Process to Render each piece of the Shape Await completion of processes and log messages PROC [data: REF] RETURNS [results: REF _ NIL] [ proc: CedarProcess.Process, io: StreamPair, server: Rope.ROPE, pctAvail: REAL ]; Robust remote processes. Start a process, check status regularly, clone process on evidence of poor remote service, LIMIT CLONES!! Set up Scene Data Start Remote Process Wait for available process, limits remote calls to control number of processors used Monitor process for completion and remote machine utilization Process Results Check that all occluding processes are complete Display Pixels from Remote Process PROC [data: REF] RETURNS [results: REF _ NIL] Κ$’˜headšœ™Jšœ2™2defaultšΟk ˜ Jšœ œ%˜6Jšœ œ?˜MJšœ œ˜+JšœœV˜jJšœœ˜Jšœ œ!Οc˜@Jšœ œž˜6Jšœœ˜8Jšœ"œ˜˜I—J˜——Jšœ˜ J˜—Jšœ œœ˜:Jšœ œ˜Jšœ(˜(Jšœ˜Jšœ#˜#Jšœ(˜(Jšœ˜Jšœ#˜#Jšœ&˜&Jšœ˜Jšœ#˜#Jšœ'˜'Jšœ˜Jšœ#˜#Jšœ(˜(Jšœ˜Jšœ#˜#Jšœ'˜'Jšœ˜šœ˜JšœD˜H—Jšœ#˜#Jšœ+˜+Jšœ˜Jšœ#˜#Jšœ ˜Jšœ˜——š ™Jš ‘ œœœœœ˜8š‘ œœœœ˜>Jšœœœ˜Jšœœœœ˜FJšœ,˜,J˜—š‘œœœœ˜BJšœ,˜,Jšœ˜J˜—š ‘ œœœœœ œ˜ZJš  ™ šœœœw˜‡Jš ™—Jšœ#œœ˜Pšœœ˜Jšœ&˜*šœ˜Jš ™šœ2œœ˜PJšœ˜Jš ™—šœ1œœ˜MJš 0™0—šœ3œœ˜OJš (™(—Jšœ!˜!J˜——Jšœ˜—š ‘ œœœ œœœ˜qJšœA™AJšœK™KJšœœœ˜JšœA˜Ašœ'œ˜/Jšœ˜Jšœ œ˜Jšœ˜šœœ˜šœO˜SJšœ ˜ Jšœ˜Jšœ˜Jšœœ˜JšΟt˜——šœ ’œœ˜Jšœ˜Jšœ ˜ Jšœœœ:˜VJ˜—J˜—J˜J™"Jšœ ™ šœP™PJšœF™FJšœL™LJšœ>™>Jšœ6™;JšœC™C—Jšœž˜5šœ œœ˜Jšœ)œ˜4Jšœœ@˜HJšœœ%˜.šœ œ ž˜6JšœV˜VJšœ<˜œž ˜T—Jšœ>œ˜GJšœ>œ˜Nšœ>œ˜FJšž)™)—šœP˜PJ™—JšœœI˜\šœœœ$˜3JšœM˜MJšœ˜—šœœœ˜$šœœž1˜XJšœM˜MJ˜—Jšœ˜—Jšœ˜Jšœ˜——š  ™ š‘œœ œœ˜KJšœ˜Jšœ ˜ Jšœ˜—š‘ œœ œœ˜NJšœ œœ˜šœœœ˜"šœ*œž˜LJš œœœœœž ˜OJšœ œœ˜Jšœ˜—Jšœ˜—Jšœ œ>œ˜UJšœ˜—š‘ œœ œœœ œœ˜J™™>Jšœ8˜8Jšœ˜Jšœ˜—Jšœ6ž'˜]Jš ™šœœœ˜#JšœV˜VJšœ˜—J™Jš (™(šœœœ˜#JšΠbcK™Kšœœœ˜Jš œ œœœœ˜fJšœœž$˜Bš‘ œœ œ˜"Jš œ œœ œ œ™PJšœ'˜'Jšœ%˜%Jšœ*˜*Jšœ(ž%˜MJ˜—š œœ œœœž˜Ošœ'˜)šœ˜Jšœ,˜,Jšœœž˜CJšœ˜—Jšœœž˜;—Jšœ˜—Jšœœ˜2Jšœ2˜2Jšœ˜—Jšœ˜—Jšœ$ž˜AJšœ!˜!J˜—š‘œœœ/œœ œœœ˜¦JšœM™MJšœ œ˜Jšœ œ˜/Jš '™'Jšœœ8˜CJšœœœ+˜Qšœœ˜Jšœœ*˜Hšœ˜šœœœ!œ˜1Jšœ,˜,Jšœ˜—Jšœ2˜2J˜——šœœœž>˜NJšœ œ+˜9šœ*˜,šœ ž+˜9Jšœ8ž˜Wšœ5˜7šœ ž˜%JšœM˜MJšœV˜VJšœM˜MJšœ˜—šœ ž˜'JšœM˜MJšœ\˜\J˜——Jšœ˜Jšœ>˜>šœ5˜7Jšœ>˜BJš œ œœœž(˜P—J˜—šœ ž ˜0Jšœ4ž˜SJšœ˜J˜——Jšœ˜—Jšœ)˜)Jšœ˜Jšœ˜——š !™!š ‘ œœœœœœ˜dJšœ œœ ˜CJš  ™ šœœœ˜"Jš£B™Bš œœ œœ˜2šœ2˜4šœ˜Jšœ$˜$Jšœœž˜KJšœ˜—Jšœ"œ˜/—Jšœ˜—Jšœœ˜7Jšœ*˜*Jšœ˜—Jš ™šœœœœ˜,š‘œœœœ˜Ašœœœœ˜pJšœœœ˜Jšœœœ˜—J˜—šœœœœ˜(Jšœ ˜š œœœœž:˜SšœB˜DJšœœ!˜:—Jšœ˜—šœ)ž˜EJšœ˜Jšœ ˜ Jšœ ˜ Jšœ˜—Jšœ˜—J˜—Jšœ˜J˜—š‘œœ œœ&˜Ušœ™Jšœ™Jšœ™Jšœ*™*Jšœ)™)Jšœ™—Jšœ7™7Jšœœ™&Jšœ+™+Jšœ+™+Jšœ+™+Jšœ7ž ™BJšœB™BJšœ˜——š #™#š‘ œœœ!œœ œœœœœ˜°Lšœ ˜šœ0ž˜8š‘ œœœ˜ Lš œœœœ-œ˜LLšœœ˜Lšœ˜—Lšœœœ˜"Lšœœž˜TLšœ-ž'˜Tš œœœœž/˜Ošœ.˜8šœž ˜#Lšœœ˜ š œœœœœœž˜Dšœ;˜;LšœG˜GL˜—Lšœ)˜)L˜Lšœ˜—Lšœ7ž˜JLšœ!œœ˜JLšœ&ž˜;Lšœ˜—šœ ˜ Lšœœ˜ Lšœ7ž˜JLšœ!œœ˜MLšœœ˜L˜—šœ ž5˜FLšœU˜Ušœ5˜7Lšœœž˜:Lšœœž˜P—L˜——Lšœ˜—šœœœ ž˜KLšœœœ-ž˜S—Lšœ˜—Jšœœ*˜5J˜—š‘œœ œ ˜7š œœœ#œž ˜Tš œœœœœž˜OLšœD˜DLšœ˜—š œœœœ+œ œ˜Ušœ œœœž˜NLšœ7˜7Lšœ˜—š œœœ-œ œ˜SLšœ'ž˜ELšœ˜—Lšœ˜—Lšœ˜—L˜—š‘œœ œœœ œ œœ˜sLšœœ˜&Lšœœ˜&Lšœœ˜)Lšœœ˜*Lšœ˜LšœK˜KLšœž)˜Fšœœœ˜(L™šœœœ&˜5Lšœ ˜šœœ˜+Lšœž3˜FLšœœJ˜aLšœ˜—Lšœœœ-˜PLšœ˜—IašœAžœ3˜‡—Lšœ˜Lšœœ˜ L˜——š ™š ‘œœœ œœ˜MPšœPœœ˜kJ˜—š‘ œœœ œ ˜0Jšž?™?š‘ œœœ˜-šœœœœœœœ˜DJšœ/œ˜6Jšœ˜ —J˜—Jšœœœœ.˜EPšœœ6˜>šœœœœ˜!Pšœœœœ˜Pšœœœœ˜)—Pšœœ˜Jšœ œ˜ Jšœ>œœ˜Wšœœ ž˜?Jšœœœ*ž˜Y—Jš  ™ Lšœ(ž2˜ZPšœ˜Pšœž5˜Mšœ˜PšœHž ˜Ušœœž˜2JšœP˜PJšœœ˜6J˜—JšœQ˜Q—Jš ™šœ˜Jšœ*˜.Jšœ+˜/—Jš  ™ šœœœœ˜9Jšœ'ž%˜LJšœ+ž˜=P˜—JšœI˜IJšœ ˜ Jšœ˜—š‘œœ œœ˜DJšœœ˜!Jšœœœž˜WJšœ œœœ˜-Jšœœ'˜1Jšœœœ˜JJšœ œ˜J˜Jš£™Jšœ>ž˜TJšœ#ž7˜ZJšœ=˜=J˜Jš "™"š œœœœž&˜LJšœ$˜$Jšœœ˜!šœœ ˜J™=—Jšœœœ)˜AJšœœœ<˜WJšœœœ=˜XJšœœ'œž˜\Jš 7™7JšœX˜XJš +™+šœ˜Jšœ˜Jšœ1ž˜HJšœœ˜Jšœ˜Jšœœœ,˜;Jšœ˜J˜—J˜Jš ™Jšœœ'ž˜Bšœ%˜%Jšœ1˜1Jšœ!˜!Jšœ˜—Jšœ-ž(˜Ušœ#˜#Jšœ:ž˜VJšœF˜FJšœ(˜(Jšœ+˜+J˜—Jš 3™3Jšœ;ž˜JJšœ œ"ž˜Jšœ˜Jšœ*ž#˜Q—Jšœ ˜ Jšœž˜0—Jš .™.Jšœ0˜0J˜—š‘œœ œœ˜FJšœœœž˜XJšœœœœ˜1Jšœœ˜!Jš ™Jšœ œA˜PJšœœœ'˜BJ™Jš !™!šœœœ˜'Jšœ?ž'˜fJšœ˜Jšœ˜—šœ˜šœ˜Jšœ(ž%˜MJšœ#ž/˜RJ˜—šœ˜Jšœ-ž"˜OJšœž7˜RJ˜——Jš ™š œœœœž˜>J™7Jšœœœ)˜AJšœœœ<˜WJšœœœ<˜WJšœ<˜Lšœ ˜ Lšœœ8˜QLšœ˜—Lšœ œœœ˜Lšœ œ˜šœ œœ.˜fJšœ;œ œ™R—šœœ ˜ LšœA˜G—šœœœ˜Lšœ3œ˜:Lšœ˜—Lšœœœ˜1Lš œœœœœ˜0LšœX˜XLš …™…šœœœ˜'šœœž2˜FLšœJž˜RLšœ*ž'˜QL˜—šœœž ˜ILšœœn˜tLšœœn˜uLšœ˜—Lš ™Lšœ;ž˜ZJšœ0ž˜BJšœ3ž˜JLšœ%ž"˜Iš ™L™T—Lšœœ œ8˜WLšœU˜Ušœ)ž&˜OLšœ˜Lšœœœ#ž˜NLšœ˜—Lš =™=LšœO˜OLšœ(˜(Lš œœœœž/˜PLšœ˜ —Lš ™šœœœž ˜ALšœ@˜@Lš œœœœ( ˜YLšœœ:˜PL˜—Lš£/™/šœœœ˜Lšœ˜Lšœ"ž4˜VLšœI˜IL˜—Lš‘"™"Lšœ˜šœœœ˜/Lšœ ˜ šœž7˜KLšœ˜Lšœ˜Lš œ œœœœœ ˜kL˜—Lšœ˜—LšœH˜HLšœW˜WLšœ#˜#Lšœ6žœ6˜‰Lšœ7žœK˜œLšœž˜5Lšœ ˜L˜—š‘œ˜0Lš œœœ œœ™-Lšœœœ˜Lš œ œœ œœ˜0Lšœœœ˜1Lšœœœ ˜Lšœœœ˜Lšœœ˜Lšœ3˜3Lšœ"œœ˜.šœP˜Pšœ!˜!Lšœ˜Lšœ)˜)Lšœž˜5Lšœœ˜Lšœ"ž,˜NLšœž˜*Lšœœœ˜Lšœ˜——šœ ˜Lšœ ˜ šœ ˜ šœ˜ Lšœ0˜4LšœG˜K—Lšœ˜—Lšœ$˜$Lšœ3˜3Lšœ,˜,Lšœ<˜