DIRECTORY Atom USING [ GetPropFromList, PutPropOnList, PropList, DottedPair, DottedPairNode ], Real USING [ RoundC, Fix, FixI, FixC ], RealFns USING [ SqRt ], Basics USING [ BITOR, BITAND ], BasicTime USING [ PulsesToSeconds, GetClockPulses ], Rope USING [ ROPE, Cat , Find, Equal], Convert USING [ RopeFromReal, AtomFromRope ], IO USING [ Close, STREAM, PutRope ], FS USING [ StreamOpen ], Imager USING [ Context, MaskVectorI, SetStrokeWidth ], QuickViewer USING [ DrawInViewer ], Pixels USING [ GetSampleSet, SampleSet ], ScanConvert USING [ PutLine, justNoticeable ], Vector3d USING [ Dot, Triple, Quad, Normalize, Cross, Add ], Plane3d USING [ DistanceToPt ], ThreeDBasics USING [ AllOut, ClipState, Context, FacingDir, IntegerSequence, NatSequence, NatTable, NoneOut, OutCode, RealSequence, RGB, ShadingSequence, ShadingValue, ShapeInstance, ShapeSequence, ShapeProc, SixSides, Triple, TripleSequence, Vertex, VertexInfo, VertexInfoProc, VertexInfoSequence, VertexSequence ], ThreeDMisc USING [ CombineBoxes, GetMappedColor, GetBackgroundColor, SetRGBColor ], ThreeDScenes USING [ Error, GetShading, GetVtxShades, PutShading, ShadeVtx, XfmPtToDisplay, XfmToDisplay, XfmToEyeSpace ], Tilers USING [ PolygonTiler ], ThreeDSurfaces USING [ Patch, PatchProcs, PtrPatchSequence, PtrPatch, PatchSequence, SortSequence, ShapePatch ], ThreeDIO USING [ Error, Field, FieldSequence, ReadFields, WriteFields, ReadRope, ReadVertexInfoSequence, WriteVertexInfoSequence ]; ThreeDSurfacesImpl: CEDAR MONITOR IMPORTS Atom, BasicTime, Convert, Real, RealFns, Rope, IO, Basics, ThreeDScenes, Tilers, Vector3d, Plane3d, QuickViewer, ScanConvert, ThreeDMisc, Pixels, Imager, ThreeDIO, FS EXPORTS ThreeDSurfaces = BEGIN Context: TYPE ~ ThreeDBasics.Context; RGB: TYPE ~ ThreeDBasics.RGB; -- [ r, g, b: REAL]; SixSides: TYPE ~ ThreeDBasics.SixSides; Triple: TYPE ~ ThreeDBasics.Triple; TripleSequence: TYPE ~ ThreeDBasics.TripleSequence; NatSequence: TYPE ~ ThreeDBasics.NatSequence; IntegerSequence: TYPE ~ ThreeDBasics.IntegerSequence; RealSequence: TYPE ~ ThreeDBasics.RealSequence; SampleSet: TYPE ~ Pixels.SampleSet; ShapeInstance: TYPE ~ ThreeDBasics.ShapeInstance; FacingDir: TYPE ~ ThreeDBasics.FacingDir; Patch: TYPE ~ ThreeDSurfaces.Patch; PatchSequence: TYPE ~ ThreeDSurfaces.PatchSequence; PtrPatch: TYPE ~ ThreeDSurfaces.PtrPatch; PtrPatchSequence: TYPE ~ ThreeDSurfaces.PtrPatchSequence; ShapePatch: TYPE ~ ThreeDSurfaces.ShapePatch; Vertex: TYPE ~ ThreeDBasics.Vertex; VertexSequence: TYPE ~ ThreeDBasics.VertexSequence; VertexInfo: TYPE ~ ThreeDBasics.VertexInfo; VertexInfoSequence: TYPE ~ ThreeDBasics.VertexInfoSequence; ShadingValue: TYPE ~ ThreeDBasics.ShadingValue; ShadingSequence: TYPE ~ ThreeDBasics.ShadingSequence; ShapeProc: TYPE ~ ThreeDBasics.ShapeProc; -- PROC[ Context, ShapeInstance ] patchCache: REF PatchSequence _ NEW[ PatchSequence[16] ]; -- temps for clipping, etc. patchCacheLength: NAT _ 16; patchCachePtr: NAT _ 0; -- place to return next free record pixelBytes: SampleSet _ Pixels.GetSampleSet[1]; -- cache for pixel size nullPtr: INT ~ 0; -- handy name for zero in sort sequences Sqr: PROCEDURE [number: REAL] RETURNS [REAL] ~ INLINE { RETURN[number * number]; }; Sgn: PROCEDURE [number: REAL] RETURNS [REAL] ~ INLINE { IF number < 0. THEN RETURN[-1.] ELSE RETURN[1.]; }; ElapsedTime: PROC[startTime: REAL] RETURNS[Rope.ROPE] ~ { timeX10: REAL _ 10.0 * (BasicTime.PulsesToSeconds[BasicTime.GetClockPulses[]] - startTime); RETURN[ Rope.Cat[ Convert.RopeFromReal[ Real.FixC[timeX10] / 10.0 ], " secs. " ] ]; }; CurrentTime: PROC[] RETURNS[REAL] ~ { RETURN[ BasicTime.PulsesToSeconds[BasicTime.GetClockPulses[]] ]; }; GetPatch: PUBLIC ENTRY PROC[size: NAT] RETURNS[REF Patch] ~ { ENABLE UNWIND => NULL; p: REF Patch; IF patchCachePtr = 0 THEN p _ NEW[Patch[size]] ELSE { patchCachePtr _ patchCachePtr - 1; p _ patchCache[patchCachePtr]; patchCache[patchCachePtr] _ NIL; IF p.maxLength < size THEN p _ NEW[Patch[size]]; }; RETURN[ p ]; }; ReleasePatch: PUBLIC ENTRY PROC[p: REF Patch] ~ { ENABLE UNWIND => NULL; IF p = NIL THEN RETURN[]; IF patchCachePtr = patchCacheLength THEN { patchCache _ NEW[ PatchSequence[patchCacheLength + 2] ]; patchCacheLength _ patchCacheLength + 2; patchCachePtr _ 0; }; patchCache[patchCachePtr] _ p; patchCachePtr _ patchCachePtr + 1; }; DiffPosns: PROC[vtx1, vtx2: REF Vertex] RETURNS[Triple] ~ { RETURN[[vtx1.x - vtx2.x, vtx1.y - vtx2.y, vtx1.z - vtx2.z]] }; HoldEverything: PROCEDURE [] ~ { ERROR ABORTED; }; ShapetoColorBytes: PROC [context: REF Context, s: REF ShapeInstance] RETURNS[SampleSet] ~ { ref: REF ANY _ ThreeDScenes.GetShading[ s, $Color]; r, g, b: REAL; addOn: NAT _ 0; IF context.alphaBuffer THEN addOn _ addOn + 1; IF context.depthBuffer THEN addOn _ addOn + 1; IF ref # NIL THEN [r, g, b] _ NARROW[ ref, REF RGB]^ -- shape color ELSE IF context.renderMode # $Interpress THEN r _ g _ b _ 1.0 ELSE r _ g _ b _ 0.0; SELECT context.renderMode FROM -- convert color to byte sequence $Bitmap => { clr: RGB _ ThreeDMisc.GetBackgroundColor[context]; IF (clr.R + clr.G + clr.B) / 3 > 0.5 THEN pixelBytes[0] _ 255 ELSE pixelBytes[0] _ 0; -- ensure contrast with backgrnd }; $Dithered, $PseudoColor => { IF pixelBytes.length < 1+addOn THEN pixelBytes _ Pixels.GetSampleSet[1+addOn]; pixelBytes[0] _ ThreeDMisc.GetMappedColor[context, [r, g, b] ]; IF addOn > 0 THEN pixelBytes[1] _ 0; IF addOn > 1 THEN pixelBytes[2] _ 0; }; $Grey => { IF pixelBytes.length < 1+addOn THEN pixelBytes _ Pixels.GetSampleSet[1+addOn]; pixelBytes[0] _ Real.RoundC[255.0 * (r + g + b)/3 ]; IF addOn > 0 THEN pixelBytes[1] _ 0; IF addOn > 1 THEN pixelBytes[2] _ 0; }; $FullColor, $Dorado24, $Interpress => { IF pixelBytes.length < 3+addOn THEN pixelBytes _ Pixels.GetSampleSet[3+addOn]; pixelBytes[0] _ Real.RoundC[255.0 * r]; pixelBytes[1] _ Real.RoundC[255.0 * g]; pixelBytes[2] _ Real.RoundC[255.0 * b]; IF addOn > 0 THEN pixelBytes[3] _ 0; IF addOn > 1 THEN pixelBytes[4] _ 0; }; ENDCASE => SIGNAL ThreeDScenes.Error[[$Unimplemented, "Unknown renderMode"]]; RETURN[pixelBytes]; }; ShapePatchToPatch: PUBLIC PROC[context: REF Context, sPatch: REF ThreeDSurfaces.ShapePatch] RETURNS [patch: REF Patch] ~ { ptrPatch: REF PtrPatch _ NARROW[sPatch.shape.surface, REF PtrPatchSequence][sPatch.patch]; vertex: REF ThreeDBasics.VertexSequence _ sPatch.shape.vertex; shade: REF ThreeDBasics.ShadingSequence _ sPatch.shape.shade; shadingType: REF ANY _ ThreeDScenes.GetShading[ sPatch.shape, $Type ]; auxProc: REF ThreeDBasics.VertexInfoProc _ NARROW[ ThreeDScenes.GetShading[ sPatch.shape, $AuxLoad ] ]; faceted: BOOLEAN _ shadingType = $Faceted; lines: BOOLEAN _ shadingType = $Lines; patchInfo: REF ThreeDBasics.ShadingSequence _ NARROW[ ThreeDScenes.GetShading[ sPatch.shape, $PatchColors ] ]; coloredPatches: BOOLEAN _ IF patchInfo # NIL AND NOT faceted THEN ThreeDScenes.GetShading[ sPatch.shape, $PatchColorsInFile ] # NIL ELSE FALSE; IF ptrPatch.clipState = out THEN RETURN[NIL]; -- reject if outside frame patch _ GetPatch[2 * ptrPatch.nVtces]; -- get temp patch, released by OutputPatch patch.nVtces _ ptrPatch.nVtces; patch.clipState _ ptrPatch.clipState; patch.type _ ptrPatch.type; patch.oneSided _ ptrPatch.oneSided; patch.dir _ ptrPatch.dir; patch.props _ NIL; FOR list: Atom.PropList _ sPatch.shape.shadingProps, list.rest UNTIL list = NIL DO element: Atom.DottedPair _ NEW[Atom.DottedPairNode _ list.first^]; -- copy shading props patch.props _ CONS[element, patch.props]; ENDLOOP; patch.props _ Atom.PutPropOnList[ patch.props, $Shape, sPatch.shape ]; -- put on shape info FOR i: NAT IN [0..ptrPatch.nVtces) DO j: NAT _ ptrPatch.vtxPtr[i]; patch[i].coord _ vertex[j]^; patch[i].shade _ shade[j]^; IF auxProc # NIL THEN { data: LIST OF REF ANY _ LIST[ sPatch.shape.auxInfo, NEW[INTEGER _ j] ]; patch[i] _ auxProc^[context, NEW[ VertexInfo _ patch[i] ], data]^; }; IF lines THEN { -- lines use unshaded values patch[i].shade.er _ patch[i].shade.r; patch[i].shade.eg _ patch[i].shade.g; patch[i].shade.eb _ patch[i].shade.b; } ELSE IF patchInfo # NIL THEN -- shades for individual patches IF faceted THEN patch[i].shade _ patchInfo[sPatch.patch]^ ELSE IF coloredPatches THEN { patch[i].shade.er _ patch[i].shade.er * patchInfo[sPatch.patch].r; patch[i].shade.eg _ patch[i].shade.eg * patchInfo[sPatch.patch].g; patch[i].shade.eb _ patch[i].shade.eb * patchInfo[sPatch.patch].b; patch[i].shade.et _ patch[i].shade.et * patchInfo[sPatch.patch].t; IF context.alphaBuffer THEN { -- possible pixel by pixel shading patch[i].shade.r _ shade[j].r * patchInfo[sPatch.patch].r; patch[i].shade.g _ shade[j].g * patchInfo[sPatch.patch].g; patch[i].shade.b _ shade[j].b * patchInfo[sPatch.patch].b; patch[i].shade.t _ shade[j].t * patchInfo[sPatch.patch].t; }; }; ENDLOOP; }; ReadShape: PUBLIC PROC[shape: REF ShapeInstance, fileName: Rope.ROPE] ~ { stream: IO.STREAM _ FS.StreamOpen[ fileName: fileName ]; firstVtxNo: NAT _ 0; -- some files count from 0 some from 1 surfaceInfo: Rope.ROPE; surfaceInfo _ ThreeDIO.ReadRope[ stream, "SurfaceType", TRUE ! ThreeDIO.Error => CONTINUE ]; shape.type _ $ConvexPolygon; -- defaults shape.insideVisible _ FALSE; IF Rope.Find[surfaceInfo, "polygon", 0, FALSE] >= 0 THEN shape.type _ $ConvexPolygon; IF Rope.Find[surfaceInfo, "bezier", 0, FALSE] >= 0 THEN shape.type _ $Bezier; IF Rope.Find[surfaceInfo, "Inside", 0, FALSE] >= 0 THEN shape.insideVisible _ TRUE; IF Rope.Find[surfaceInfo, "CountFromOne", 0, FALSE] >= 0 THEN firstVtxNo _ 1; { vertices: REF VertexInfoSequence _ ThreeDIO.ReadVertexInfoSequence[stream, "Vertices"]; normalsRead, colorsRead, txtrRead, transRead: INT _ 0; auxInfo: REF TripleSequence _ NIL; shape.vertex _ NEW[ ThreeDBasics.VertexSequence[vertices.length] ]; shape.shade _ NEW[ ThreeDBasics.ShadingSequence[vertices.length] ]; IF vertices[0].aux # NIL THEN { auxInfo _ NEW[ TripleSequence[vertices.length] ]; auxInfo.length _ vertices.length; shape.auxInfo _ auxInfo; }; FOR i: NAT IN [0..vertices.length) DO shape.vertex[i] _ NEW[ ThreeDBasics.Vertex _ vertices[i].coord ]; shape.shade[i] _ NEW[ ThreeDBasics.ShadingValue _ vertices[i].shade ]; IF shape.shade[i].xn # 0.0 OR shape.shade[i].yn # 0.0 OR shape.shade[i].zn # 0.0 THEN normalsRead _ normalsRead + 1; IF shape.shade[i].r # 0.7 OR shape.shade[i].r # 0.7 OR shape.shade[i].r # 0.7 THEN colorsRead _ colorsRead + 1; IF shape.shade[i].t # 0.0 THEN transRead _ transRead + 1; IF vertices[i].aux # NIL THEN { auxInfo[i] _ NARROW[vertices[i].aux, REF Triple]^; txtrRead _ txtrRead + 1; }; ENDLOOP; IF normalsRead > vertices.length / 2 THEN ThreeDScenes.PutShading[ shape, $VertexNormalsInFile, $DoIt ]; IF colorsRead > vertices.length / 2 THEN ThreeDScenes.PutShading[ shape, $VertexColorsInFile, $DoIt ]; IF transRead > vertices.length / 2 THEN ThreeDScenes.PutShading[ shape, $VertexTransInFile, $DoIt ]; IF txtrRead > vertices.length / 2 THEN ThreeDScenes.PutShading[ shape, $VertexTextureInFile, $DoIt ]; ThreeDScenes.PutShading[shape, $Type, $Smooth ]; }; { keyWord: Rope.ROPE _ IF shape.type = $ConvexPolygon THEN "Polygons" ELSE "Patches"; fields: REF ThreeDIO.FieldSequence _ ThreeDIO.ReadFields[stream, keyWord]; GetPatchInfo: PROC[shape: REF ShapeInstance] RETURNS[p: REF ShadingSequence] ~ { p _ NARROW[ ThreeDScenes.GetShading[ shape, $PatchColors ] ]; IF p = NIL THEN { p _ NEW[ThreeDBasics.ShadingSequence[shape.numSurfaces] ]; FOR i: NAT IN [0..shape.numSurfaces) DO p[i] _ NEW[ThreeDBasics.ShadingValue]; ENDLOOP; }; }; shape.numSurfaces _ 0; FOR n: NAT IN [0..fields.length) DO patchInfo: REF ThreeDBasics.ShadingSequence; SELECT fields[n].type FROM integer => { intSeq: REF IntegerSequence _ NARROW[fields[n].sequence]; shape.numSurfaces _ intSeq.length; SELECT TRUE FROM Rope.Equal[fields[n].id, "index", FALSE] => {}; ENDCASE => { key: ATOM _ Convert.AtomFromRope[fields[n].id]; -- put on proplist ThreeDScenes.PutShading[ shape, key, intSeq ]; }; }; real => { realSeq: REF RealSequence _ NARROW[fields[n].sequence]; shape.numSurfaces _ realSeq.length; patchInfo _ GetPatchInfo[shape]; SELECT TRUE FROM Rope.Equal[fields[n].id, "trans", FALSE] => FOR i: NAT IN [0..realSeq.length) DO patchInfo[i].t _ realSeq[i]; ENDLOOP; ENDCASE => { key: ATOM _ Convert.AtomFromRope[fields[n].id]; -- put on proplist ThreeDScenes.PutShading[ shape, key, realSeq ]; }; }; triple => { tripleSeq: REF TripleSequence _ NARROW[fields[n].sequence]; shape.numSurfaces _ tripleSeq.length; patchInfo _ GetPatchInfo[shape]; SELECT TRUE FROM Rope.Equal[fields[n].id, "color", FALSE] => { FOR i: NAT IN [0..tripleSeq.length) DO patchInfo[i].r _ tripleSeq[i].x; patchInfo[i].g _ tripleSeq[i].y; patchInfo[i].b _ tripleSeq[i].z; ENDLOOP; ThreeDScenes.PutShading[ shape, $PatchColors, patchInfo ]; ThreeDScenes.PutShading[ shape, $PatchColorsInFile, $DoIt ]; ThreeDScenes.PutShading[shape, $Type, $Faceted ]; }; Rope.Equal[fields[n].id, "normal", FALSE] => { FOR i: NAT IN [0..tripleSeq.length) DO patchInfo[i].xn _ tripleSeq[i].x; patchInfo[i].yn _ tripleSeq[i].y; patchInfo[i].zn _ tripleSeq[i].z; ENDLOOP; ThreeDScenes.PutShading[ shape, $PatchColors, patchInfo ]; ThreeDScenes.PutShading[ shape, $PatchNormalsInFile, $DoIt ]; ThreeDScenes.PutShading[shape, $Type, $Faceted ]; }; ENDCASE => { key: ATOM _ Convert.AtomFromRope[fields[n].id]; -- put on proplist ThreeDScenes.PutShading[ shape, key, tripleSeq ]; }; }; nats => { -- get the surface elements surface: REF PtrPatchSequence; surfels: REF ThreeDBasics.NatTable _ NARROW[fields[n].sequence]; shape.numSurfaces _ surfels.length; shape.surface _ NEW[ PtrPatchSequence[shape.numSurfaces] ]; surface _ NARROW[shape.surface, REF PtrPatchSequence]; FOR i: NAT IN [0..shape.numSurfaces) DO IF surface[i] = NIL THEN surface[i] _ NEW[PtrPatch]; surface[i].vtxPtr _ NEW[NatSequence[surfels[i].length]]; surface[i].nVtces _ surfels[i].length; surface[i].type _ shape.type; surface[i].oneSided _ NOT shape.insideVisible; FOR j: NAT IN [0..surfels[i].length) DO surface[i].vtxPtr[j] _ surfels[i][j] - firstVtxNo; -- counting from zero ENDLOOP; ENDLOOP; }; ENDCASE => { key: ATOM _ Convert.AtomFromRope[fields[n].id]; -- put on proplist ThreeDScenes.PutShading[ shape, key, fields[n].sequence ]; }; ENDLOOP; IF ThreeDScenes.GetShading[ shape, $VertexNormalsInFile ] = NIL THEN GetVtxNormals[shape ! ThreeDScenes.Error => IF reason.code = $MisMatch THEN CONTINUE]; IF ThreeDScenes.GetShading[ shape, $PatchNormalsInFile ] = NIL AND ThreeDScenes.GetShading[ shape, $PatchColorsInFile ] # NIL THEN GetPolyNormals[shape ! ThreeDScenes.Error => IF reason.code = $MisMatch THEN CONTINUE]; }; { min, max: Triple; min _ max _ [shape.vertex[0].x, shape.vertex[0].y, shape.vertex[0].z]; FOR i: NAT IN (0..shape.vertex.length) DO -- get min and max in x, y, and z IF shape.vertex[i] # NIL THEN { IF shape.vertex[i].x < min.x THEN min.x _ shape.vertex[i].x ELSE IF shape.vertex[i].x > max.x THEN max.x _ shape.vertex[i].x; IF shape.vertex[i].y < min.y THEN min.y _ shape.vertex[i].y ELSE IF shape.vertex[i].y > max.y THEN max.y _ shape.vertex[i].y; IF shape.vertex[i].z < min.z THEN min.z _ shape.vertex[i].z ELSE IF shape.vertex[i].z > max.z THEN max.z _ shape.vertex[i].z; }; ENDLOOP; shape.centroid.x _ (min.x + max.x) / 2; -- get middle point in each coordinate shape.centroid.y _ (min.y + max.y) / 2; shape.centroid.z _ (min.z + max.z) / 2; shape.boundingRadius _ 0.; FOR i: NAT IN [0..shape.vertex.length) DO -- find radius radius: REAL _ RealFns.SqRt[ Sqr[shape.vertex[i].x - shape.centroid.x] + Sqr[shape.vertex[i].y - shape.centroid.y] + Sqr[shape.vertex[i].z - shape.centroid.z] ]; IF radius > shape.boundingRadius THEN shape.boundingRadius _ radius; ENDLOOP; }; }; CloneShape: PUBLIC PROC[newshape, oldShape: REF ShapeInstance] ~ { -- copy shape data newSurface, oldSurface: REF PtrPatchSequence; newshape.type _ oldShape.type; newshape.insideVisible _ oldShape.insideVisible; newshape.centroid _ oldShape.centroid; newshape.boundingRadius _ oldShape.boundingRadius; newshape.vertex _ NEW[ VertexSequence[oldShape.vertex.length] ]; newshape.shade _ NEW[ ShadingSequence[oldShape.shade.length] ]; FOR i: NAT IN [0..oldShape.vertex.length) DO -- copy vertices and shades newshape.vertex[i] _ NEW [ Vertex _ oldShape.vertex[i]^ ]; newshape.shade[i] _ NEW [ ShadingValue _ oldShape.shade[i]^ ]; ENDLOOP; newshape.numSurfaces _ oldShape.numSurfaces; newshape.surface _ NEW[ PtrPatchSequence[oldShape.numSurfaces] ]; newSurface _ NARROW[newshape.surface, REF PtrPatchSequence]; oldSurface _ NARROW[oldShape.surface, REF PtrPatchSequence]; FOR i: NAT IN [0..oldShape.numSurfaces) DO -- copy surface IF newSurface[i] = NIL THEN newSurface[i] _ NEW[PtrPatch]; newSurface[i].vtxPtr _ NEW[NatSequence[oldSurface[i].nVtces]]; newSurface[i].nVtces _ oldSurface[i].nVtces; newSurface[i].type _ oldSurface[i].type; newSurface[i].oneSided _ oldSurface[i].oneSided; FOR j: NAT IN [0..oldSurface[i].nVtces) DO newSurface[i].vtxPtr[j] _ oldSurface[i].vtxPtr[j]; ENDLOOP; ENDLOOP; newshape.shadingProps _ NIL; -- copy shading props FOR list: Atom.PropList _ oldShape.shadingProps, list.rest UNTIL list = NIL DO element: Atom.DottedPair _ NEW[Atom.DottedPairNode _ list.first^]; newshape.shadingProps _ CONS[element, newshape.shadingProps]; ENDLOOP; newshape.props _ NIL; -- copy general props FOR list: Atom.PropList _ oldShape.props, list.rest UNTIL list = NIL DO element: Atom.DottedPair _ NEW[Atom.DottedPairNode _ list.first^]; newshape.props _ CONS[element, newshape.props]; ENDLOOP; IF ThreeDScenes.GetShading[ newshape, $PatchColors ] # NIL THEN { -- copy facet info polyShades: REF ShadingSequence _ NARROW[ ThreeDScenes.GetShading[ newshape, $PatchColors ] ]; newpolyShades: REF ShadingSequence _ NEW[ ShadingSequence[ polyShades.length ] ]; FOR i: NAT IN [0..polyShades.length) DO newpolyShades[i] _ NEW[ShadingValue _ polyShades[i]^ ]; ENDLOOP; ThreeDScenes.PutShading[ newshape, $PatchColors, newpolyShades ] }; }; WriteShape: PUBLIC PROC[shape: REF ShapeInstance, fileName: Rope.ROPE, xyz: BOOL _ TRUE, normal, color, trans, texture, polyClr: BOOL _ FALSE] ~ { stream: IO.STREAM _ FS.StreamOpen[Rope.Cat[fileName, ".shape"], $create]; numFields: NAT _ 0; fields: REF ThreeDIO.FieldSequence _ NEW[ThreeDIO.FieldSequence[1]]; vertices: REF VertexInfoSequence _ NEW[ VertexInfoSequence[shape.vertex.length] ]; auxInfo: REF TripleSequence _ NARROW[shape.auxInfo]; surfaceType: Rope.ROPE _ IF shape.type = $ConvexPolygon THEN "Polygons" ELSE "Patches"; insideVisible: Rope.ROPE _ IF shape.insideVisible THEN " InsideVisible" ELSE NIL; stream.PutRope[ Rope.Cat[fileName, ".shape\n\n"] ]; -- write title on first line stream.PutRope[ Rope.Cat["SurfaceType ~ ", surfaceType, insideVisible, "\n\n"] ]; -- surface FOR i: NAT IN [0..shape.vertex.length) DO vertices[i] _ NEW[VertexInfo]; vertices[i].coord _ shape.vertex[i]^; vertices[i].shade _ shape.shade[i]^; IF auxInfo # NIL THEN vertices[i].aux _ NEW[ Triple _ auxInfo[i] ]; ENDLOOP; ThreeDIO.WriteVertexInfoSequence[ stream, "Vertices", vertices, xyz, normal, color, trans, texture ]; IF polyClr THEN { color: REF ShadingSequence _ NARROW[ ThreeDScenes.GetShading[shape, $PatchColors ] ]; tripleSeq: REF TripleSequence _ NEW[ TripleSequence[color.length] ]; tripleSeq.length _ color.length; FOR i: NAT IN [0..color.length) DO tripleSeq[i].x _ color[i].r; tripleSeq[i].y _ color[i].g; tripleSeq[i].z _ color[i].b; ENDLOOP; fields _ NEW[ThreeDIO.FieldSequence[2]]; fields[0] _ NEW[ThreeDIO.Field]; fields[0].sequence _ tripleSeq; fields[0].type _ triple; fields[0].id _ "rgbColor"; numFields _ 1; }; { surfels: REF ThreeDBasics.NatTable _ NEW[ThreeDBasics.NatTable[shape.numSurfaces] ]; patches: REF PtrPatchSequence _ NARROW[shape.surface, REF PtrPatchSequence]; FOR i: NAT IN [0..shape.numSurfaces) DO surfels[i] _ NEW[ NatSequence[patches[i].nVtces] ]; FOR j: NAT IN [0..patches[i].nVtces) DO surfels[i][j] _ patches[i].vtxPtr[j]; ENDLOOP; surfels[i].length _ patches[i].nVtces; ENDLOOP; surfels.length _ shape.numSurfaces; fields[numFields] _ NEW[ThreeDIO.Field]; fields[numFields].sequence _ surfels; fields[numFields].type _ nats; fields[numFields].id _ "vertices"; fields.length _ numFields + 1; }; ThreeDIO.WriteFields[stream, surfaceType, fields]; IO.Close[stream]; }; ClipPoly: PUBLIC PROC[ context: REF Context, poly: REF Patch] RETURNS [REF Patch] ~ { Clip: PROC[side: SixSides, pIn, pOut: REF Patch] RETURNS [REF Patch, REF Patch] = { Dist: PROC[side: SixSides, vtx: Vertex] RETURNS [REAL] = { -- + inside, - outside RETURN[ Plane3d.DistanceToPt[ [vtx.ex, vtx.ey, vtx.ez], context.clippingPlanes[side] ] ]; }; lastDist, dist: REAL; outCnt, last: NAT; IF pIn.nVtces < 3 THEN RETURN[ pIn, pOut ]; -- return if degenerate outCnt _ 0; IF pIn.type # $Path THEN { lastDist _ Dist[side, pIn.vtx[pIn.nVtces - 1].coord]; last _ pIn.nVtces - 1; }; IF pOut.maxLength < 2 * pIn.nVtces THEN pOut _ NEW[Patch[2 * pIn.nVtces]]; FOR i: NAT IN [0..pIn.nVtces) DO a, b: REAL; dist _ Dist[side, pIn.vtx[i].coord]; IF (i # 0 OR pIn.type # $Path) AND lastDist * dist < 0. THEN { b _ dist / (dist - lastDist); a _ 1.0 - b; pOut.vtx[outCnt].coord.x _ pIn.vtx[i].coord.x * a + pIn.vtx[last].coord.x * b; pOut.vtx[outCnt].coord.y _ pIn.vtx[i].coord.y * a + pIn.vtx[last].coord.y * b; pOut.vtx[outCnt].coord.z _ pIn.vtx[i].coord.z * a + pIn.vtx[last].coord.z * b; pOut.vtx[outCnt].coord.ex _ pIn.vtx[i].coord.ex * a + pIn.vtx[last].coord.ex * b; pOut.vtx[outCnt].coord.ey _ pIn.vtx[i].coord.ey * a + pIn.vtx[last].coord.ey * b; pOut.vtx[outCnt].coord.ez _ pIn.vtx[i].coord.ez * a + pIn.vtx[last].coord.ez * b; pOut.vtx[outCnt].shade.exn _ pIn.vtx[i].shade.exn*a + pIn.vtx[last].shade.exn*b; pOut.vtx[outCnt].shade.eyn _ pIn.vtx[i].shade.eyn*a + pIn.vtx[last].shade.eyn*b; pOut.vtx[outCnt].shade.ezn _ pIn.vtx[i].shade.ezn*a + pIn.vtx[last].shade.ezn*b; pOut.vtx[outCnt].shade.r _ pIn.vtx[i].shade.r * a + pIn.vtx[last].shade.r * b; pOut.vtx[outCnt].shade.g _ pIn.vtx[i].shade.g * a + pIn.vtx[last].shade.g * b; pOut.vtx[outCnt].shade.b _ pIn.vtx[i].shade.b * a + pIn.vtx[last].shade.b * b; pOut.vtx[outCnt].shade.t _ pIn.vtx[i].shade.t * a + pIn.vtx[last].shade.t * b; pOut.vtx[outCnt].shade.er _ pIn.vtx[i].shade.er * a + pIn.vtx[last].shade.er * b; pOut.vtx[outCnt].shade.eg _ pIn.vtx[i].shade.eg * a + pIn.vtx[last].shade.eg * b; pOut.vtx[outCnt].shade.eb _ pIn.vtx[i].shade.eb * a + pIn.vtx[last].shade.eb * b; pOut.vtx[outCnt].shade.et _ pIn.vtx[i].shade.et * a + pIn.vtx[last].shade.et * b; IF lerpProc # NIL THEN { data: LIST OF REF ANY _ LIST[ pIn.vtx[i].aux, pIn.vtx[last].aux, NEW[REAL _ a], NEW[REAL _ b] ]; pOut.vtx[outCnt] _ lerpProc[ context, NEW[VertexInfo _ pOut.vtx[outCnt]], data ]^; } ELSE pOut.vtx[outCnt].aux _ pIn.vtx[i].aux; outCnt _ outCnt + 1; }; IF dist >= 0. THEN { -- put out point if inside pOut.vtx[outCnt].coord.x _ pIn.vtx[i].coord.x; pOut.vtx[outCnt].coord.y _ pIn.vtx[i].coord.y; pOut.vtx[outCnt].coord.z _ pIn.vtx[i].coord.z; pOut.vtx[outCnt].coord.ex _ pIn.vtx[i].coord.ex; pOut.vtx[outCnt].coord.ey _ pIn.vtx[i].coord.ey; pOut.vtx[outCnt].coord.ez _ pIn.vtx[i].coord.ez; pOut.vtx[outCnt].shade.exn _ pIn.vtx[i].shade.exn; pOut.vtx[outCnt].shade.eyn _ pIn.vtx[i].shade.eyn; pOut.vtx[outCnt].shade.ezn _ pIn.vtx[i].shade.ezn; pOut.vtx[outCnt].shade.r _ pIn.vtx[i].shade.r; pOut.vtx[outCnt].shade.g _ pIn.vtx[i].shade.g; pOut.vtx[outCnt].shade.b _ pIn.vtx[i].shade.b; pOut.vtx[outCnt].shade.t _ pIn.vtx[i].shade.t; pOut.vtx[outCnt].shade.er _ pIn.vtx[i].shade.er; pOut.vtx[outCnt].shade.eg _ pIn.vtx[i].shade.eg; pOut.vtx[outCnt].shade.eb _ pIn.vtx[i].shade.eb; pOut.vtx[outCnt].shade.et _ pIn.vtx[i].shade.et; pOut.vtx[outCnt].aux _ pIn.vtx[i].aux; outCnt _ outCnt + 1; }; lastDist _ dist; last _ i; ENDLOOP; pOut.type _ pIn.type; pOut.oneSided _ pIn.oneSided; pOut.dir _ pIn.dir; pOut.nVtces _ outCnt; pOut.props _ pIn.props; RETURN [ pOut, pIn ]; }; -- end Clip Proc ref: REF ANY _ Atom.GetPropFromList[poly.props, $AuxLerp]; lerpProc: ThreeDBasics.VertexInfoProc _ NIL; orOfCodes: ThreeDBasics.OutCode _ ThreeDBasics.NoneOut; poly2: REF Patch _ GetPatch[2 * poly.nVtces]; -- get temp patch, released below IF poly.type # $ConvexPolygon AND poly.type # $Path THEN SIGNAL ThreeDScenes.Error[[$Unimplemented, "Not clippable"]]; IF ref # NIL -- get proc for interpolating auxiliary vtx info THEN lerpProc _ NARROW[ref, REF ThreeDBasics.VertexInfoProc]^; FOR i: NAT IN [0..poly.nVtces) DO orOfCodes _ LOOPHOLE[ Basics.BITOR[LOOPHOLE[orOfCodes], LOOPHOLE[poly.vtx[i].coord.clip]], ThreeDBasics.OutCode]; ENDLOOP; IF orOfCodes.near THEN [poly, poly2] _ Clip[ Near, poly, poly2]; IF orOfCodes.far THEN [poly, poly2] _ Clip[ Far, poly, poly2]; IF orOfCodes.left THEN [poly, poly2] _ Clip[ Left, poly, poly2]; IF orOfCodes.right THEN [poly, poly2] _ Clip[ Right, poly, poly2]; IF orOfCodes.bottom THEN [poly, poly2] _ Clip[Bottom, poly, poly2]; IF orOfCodes.top THEN [poly, poly2] _ Clip[ Top, poly, poly2]; ReleasePatch[poly2]; -- done with temp patch RETURN[ poly ]; }; GetPatchClipState: PUBLIC PROC[ patch: REF Patch] ~ { orOfCodes: ThreeDBasics.OutCode _ ThreeDBasics.NoneOut; andOfCodes: ThreeDBasics.OutCode _ ThreeDBasics.AllOut; FOR i: NAT IN [0..patch.nVtces) DO orOfCodes _ LOOPHOLE[ Basics.BITOR[ LOOPHOLE[orOfCodes], LOOPHOLE[patch[i].coord.clip]], ThreeDBasics.OutCode]; andOfCodes _ LOOPHOLE[ Basics.BITAND[LOOPHOLE[andOfCodes], LOOPHOLE[patch[i].coord.clip]], ThreeDBasics.OutCode]; ENDLOOP; IF andOfCodes # ThreeDBasics.NoneOut THEN patch.clipState _ out ELSE IF orOfCodes = ThreeDBasics.NoneOut THEN patch.clipState _ in ELSE patch.clipState _ clipped; }; GetPtrPatchClipState: PROC[ shape: REF ShapeInstance, patch: REF PtrPatch] ~ { orOfCodes: ThreeDBasics.OutCode _ ThreeDBasics.NoneOut; andOfCodes: ThreeDBasics.OutCode _ ThreeDBasics.AllOut; FOR j: NAT IN [0..patch.nVtces) DO k: NAT _ patch.vtxPtr[j]; orOfCodes _ LOOPHOLE[ Basics.BITOR[ LOOPHOLE[orOfCodes], LOOPHOLE[shape.vertex[k].clip]], ThreeDBasics.OutCode]; andOfCodes _ LOOPHOLE[ Basics.BITAND[LOOPHOLE[andOfCodes], LOOPHOLE[shape.vertex[k].clip]], ThreeDBasics.OutCode]; ENDLOOP; IF andOfCodes # ThreeDBasics.NoneOut THEN patch.clipState _ out ELSE IF orOfCodes = ThreeDBasics.NoneOut THEN patch.clipState _ in ELSE patch.clipState _ clipped; }; ShapeDo: PROC[ context: REF Context, shape: REF ShapeInstance, fullExpand: BOOLEAN, limitType: ATOM, limit: REAL] RETURNS [REF ShapeInstance] ~ { MakeRoom: PROC [] ~ { -- ensure enough space for storing expanded shape IF vertex = NIL -- first we attempt to guess at how much space will be needed THEN vertex _ NEW[ VertexSequence[newPts.length * shape.numSurfaces] ] ELSE IF vertex.length < newPts.length + ptIndex -- then we expand as needed THEN { vertex2: REF VertexSequence; IF vertex.length * 2 > LAST[NAT] THEN SIGNAL ThreeDScenes.Error[[$Unimplemented, "Sequence too long (Dragon needed)"]]; vertex2 _ NEW[ VertexSequence[vertex.length*2] ]; FOR i: NAT IN [0..vertex.length) DO -- copy old sequence IF vertex[i] # NIL THEN vertex2[i] _ NEW[ Vertex _ vertex[i]^ ] ELSE vertex2[i] _ NEW[ Vertex ]; ENDLOOP; vertex _ vertex2; }; IF shade = NIL -- first we attempt to guess at how much space will be needed THEN shade _ NEW[ ShadingSequence[newPts.length * shape.numSurfaces] ] ELSE IF shade.length < newPts.length + ptIndex -- then we expand as needed THEN { shade2: REF ShadingSequence _ NEW[ ShadingSequence[vertex.length*2] ]; FOR i: NAT IN [0..shade.length) DO -- copy old sequence IF shade[i] # NIL THEN shade2[i] _ NEW[ ShadingValue _ shade[i]^ ] ELSE shade2[i] _ NEW[ ShadingValue ]; ENDLOOP; shade _ shade2; }; IF surface = NIL -- first we attempt to guess at how much space will be needed THEN surface _ NEW[ PtrPatchSequence[newPatches.length * shape.numSurfaces] ] ELSE IF surface.length < newPatches.length + patchIndex -- then we expand as needed THEN { surface2: REF PtrPatchSequence; IF surface.length * 2 > LAST[NAT] THEN SIGNAL ThreeDScenes.Error[[$Unimplemented, "Sequence too long (Dragon needed)"]]; surface2 _ NEW[ PtrPatchSequence[surface.length*2] ]; FOR i: NAT IN [0..surface.length) DO -- copy old sequence IF surface[i] # NIL THEN surface2[i] _ NEW[ PtrPatch _ surface[i]^ ] ELSE surface2[i] _ NEW[ PtrPatch ]; ENDLOOP; surface _ surface2; }; }; patch: REF PtrPatchSequence _ NARROW[ shape.surface ]; vertex: REF ThreeDBasics.VertexSequence; shade: REF ThreeDBasics.ShadingSequence; surface: REF PtrPatchSequence; patchInfo: REF ThreeDBasics.ShadingSequence _ NARROW[ ThreeDScenes.GetShading[ shape, $PatchColors ] ]; newPts: REF ThreeDBasics.VertexInfoSequence; newPatches: REF PtrPatchSequence; ptIndex, patchIndex: INT _ 0; class: REF ThreeDSurfaces.PatchProcs _ NARROW[ Atom.GetPropFromList[context.props, patch[0].type] ]; IF class = NIL THEN ERROR ThreeDScenes.Error[[$MisMatch, "No class registered"]]; IF fullExpand AND class.expand = NIL THEN ERROR ThreeDScenes.Error[[$MisMatch, "No expand Proc"]]; IF NOT fullExpand AND class.subdivide = NIL THEN ERROR ThreeDScenes.Error[[$MisMatch, "No subdivide Proc"]]; FOR pNum: NAT IN [0..shape.numSurfaces) DO IF fullExpand -- expand patch THEN [newPts, newPatches] _ class.expand[shape, patch[pNum], limitType, limit] ELSE [newPts, newPatches] _ class.subdivide[shape, patch[pNum], limitType, limit]; MakeRoom[]; -- get storage space for expanded shape FOR i: NAT IN [0..newPts.length) DO -- copy the vertices into the whole vertex[i+ptIndex] _ NEW[ ThreeDBasics.Vertex ]; vertex[i+ptIndex]^ _ newPts[i].coord; shade[i+ptIndex] _ NEW[ ThreeDBasics.ShadingValue ]; shade[i+ptIndex]^ _ newPts[i].shade; IF patchInfo # NIL THEN { shade[i+ptIndex].r _ shade[i+ptIndex].r * patchInfo[pNum].r; shade[i+ptIndex].g _ shade[i+ptIndex].g * patchInfo[pNum].g; shade[i+ptIndex].b _ shade[i+ptIndex].b * patchInfo[pNum].b; }; ENDLOOP; FOR i: NAT IN [0..newPatches.length) DO -- copy the polygons into the whole surface[i+patchIndex].vtxPtr _ NEW[ NatSequence[newPatches[i].nVtces] ]; FOR j: NAT IN [0..newPatches[i].nVtces) DO surface[i+patchIndex].vtxPtr[j] _ newPatches[i].vtxPtr[j] + ptIndex; ENDLOOP; surface[i+patchIndex].type _ newPatches[i].type; surface[i+patchIndex].oneSided _ newPatches[i].oneSided; surface[i+patchIndex].dir _ newPatches[i].dir; surface[i+patchIndex].nVtces _ newPatches[i].nVtces; surface[i+patchIndex].clipState _ newPatches[i].clipState; surface[i+patchIndex].props _ newPatches[i].props; ENDLOOP; ptIndex _ ptIndex + newPts.length; -- update the indices patchIndex _ patchIndex + newPatches.length; ENDLOOP; IF fullExpand THEN shape.type _ $ConvexPolygon; -- set type to polygons if fully expanded shape.vertex _ vertex; -- point the shape at the new data shape.shade _ shade; shape.surface _ surface; shape.numSurfaces _ surface.length; ThreeDScenes.PutShading[ shape, $PatchColors, NIL ]; shape.shadingInValid _ TRUE; shape.vtcesInValid _ TRUE; RETURN[shape]; }; ShapeExpand: PUBLIC PROC[ context: REF Context, shape: REF ShapeInstance, limitType: ATOM _ NIL, limit: REAL _ 0.0] RETURNS [REF ShapeInstance] ~ { RETURN[ ShapeDo[ context, shape, TRUE, limitType, limit ] ]; }; ShapeSubdivide: PUBLIC PROC[ context: REF Context, shape: REF ShapeInstance, limitType: ATOM _ NIL, limit: REAL _ 0.0] RETURNS [REF ShapeInstance] ~ { RETURN[ ShapeDo[ context, shape, FALSE, limitType, limit ] ]; }; ExpandToLines: PROC[ context: REF Context, patch: REF Patch, action: PROC[context: REF Context, patch: REF Patch] ] ~ { class: REF ThreeDSurfaces.PatchProcs _ NARROW[ Atom.GetPropFromList[context.props, patch.type] ]; IF class = NIL THEN ERROR ThreeDScenes.Error[[$MisMatch, "No class registered"]]; class.displayLines[context, patch, NIL, 0.0, action]; -- expand to default limit and display }; limitInPixels: REAL _ 2.0; ExpandToConvexPolys: PROC[ context: REF Context, patch: REF Patch, action: PROC[context: REF Context, patch: REF Patch] ] ~ { class: REF ThreeDSurfaces.PatchProcs _ NARROW[ Atom.GetPropFromList[context.props, patch.type] ]; IF class = NIL THEN ERROR ThreeDScenes.Error[[$MisMatch, "No class registered"]]; IF context.alphaBuffer THEN class.display[context, patch, NIL, 0.0, action] -- expand to maximum and display ELSE class.display[context, patch, NIL, limitInPixels, action]; -- expand for quick display }; RegisterSurfaceType: PUBLIC PROC[ context: REF Context, type: ATOM, procs: REF ThreeDSurfaces.PatchProcs ] ~ { context.props _ Atom.PutPropOnList[context.props, type, procs]; }; BackFacing: PUBLIC PROC[ poly: REF Patch, useEyeSpace: BOOLEAN _ FALSE] RETURNS [FacingDir] ~ { SELECT poly.type FROM $ConvexPolygon => IF useEyeSpace THEN { this: VertexInfo _ poly.vtx[0]; next: VertexInfo _ poly.vtx[1]; last: VertexInfo _ poly.vtx[2]; direction: Triple _ Vector3d.Normalize[Vector3d.Cross[ [next.coord.ex - this.coord.ex, next.coord.ey - this.coord.ey, next.coord.ez - this.coord.ez], [last.coord.ex - this.coord.ex, last.coord.ey - this.coord.ey, last.coord.ez - this.coord.ez] ] ]; dotDir: REAL _ Vector3d.Dot[[this.coord.ex, this.coord.ey, this.coord.ez] , direction]; IF dotDir > 0.0 THEN RETURN[back] ELSE IF dotDir < 0.0 THEN RETURN[front]; } ELSE { -- do check in image space, rejecting eensy polygon edges s: REAL _ 1.0 / ScanConvert.justNoticeable; -- scales visible feature size to 1 FOR i: NAT IN [0..poly.nVtces) DO this: VertexInfo _ poly.vtx[i]; next: VertexInfo _ poly.vtx[(i+1) MOD poly.nVtces]; last: VertexInfo _ poly.vtx[(i+poly.nVtces-1) MOD poly.nVtces]; zNorm: INT _ -- integer computation of z-coord of normal ( Real.Fix[s*next.coord.sx - s*this.coord.sx] ) * ( Real.Fix[s*last.coord.sy - s*this.coord.sy] ) - ( Real.Fix[s*next.coord.sy - s*this.coord.sy] ) * ( Real.Fix[s*last.coord.sx - s*this.coord.sx] ); IF zNorm > 0 THEN RETURN[ back ] ELSE IF zNorm < 0 THEN RETURN[ front ]; ENDLOOP; SIGNAL ThreeDScenes.Error[[$Condition, "Edges too small for stable arithmetic"]]; }; $Bezier => { SIGNAL ThreeDScenes.Error[[$Unimplemented, "Backfacing for patches not done"]]; }; ENDCASE => SIGNAL ThreeDScenes.Error[[$Unimplemented, "Unknown type"]]; RETURN[ undetermined ]; }; ShadePoly: PUBLIC PROC[ context: REF Context, poly: REF Patch] ~ { ref: REF _ Atom.GetPropFromList[poly.props, $Shininess]; shininess: REAL _ IF ref # NIL THEN NARROW[ref, REF REAL]^ ELSE 0.0; shading: REF ANY _ Atom.GetPropFromList[ poly.props, $Type ]; FOR i: NAT IN [0..poly.nVtces) DO IF shading = $Faceted THEN { -- calculate normals from vertex coords lVtx: NAT _ (i + poly.nVtces - 1) MOD poly.nVtces; nVtx: NAT _ (i + 1) MOD poly.nVtces; [[ poly[i].shade.exn, poly[i].shade.eyn, poly[i].shade.ezn ]] _ Vector3d.Cross[ [ poly[nVtx].coord.ex - poly[i].coord.ex, -- in eyespace, so do left-handed poly[nVtx].coord.ey - poly[i].coord.ey, poly[nVtx].coord.ez - poly[i].coord.ez ], [ poly[lVtx].coord.ex - poly[i].coord.ex, poly[lVtx].coord.ey - poly[i].coord.ey, poly[lVtx].coord.ez - poly[i].coord.ez ] ]; }; [[poly.vtx[i].shade.er, poly.vtx[i].shade.eg, poly.vtx[i].shade.eb], poly.vtx[i].shade.et] _ ThreeDScenes.ShadeVtx[context, poly[i], 0.0]; ENDLOOP; }; GetShades: PUBLIC PROC[context: REF Context, shape: REF ShapeInstance] ~ { AverageVertices: PROC[poly: REF PtrPatch] RETURNS[vtx: Vertex] ~ { FOR i: NAT IN [0..poly.nVtces) DO addVtx: Vertex _ shape.vertex[poly.vtxPtr[i]]^; vtx.x _ vtx.x + addVtx.x; vtx.y _ vtx.y + addVtx.y; vtx.z _ vtx.z + addVtx.z; vtx.ex _ vtx.ex + addVtx.ex; vtx.ey _ vtx.ey + addVtx.ey; vtx.ez _ vtx.ez + addVtx.ez; vtx.sx _ vtx.sx + addVtx.sx; vtx.sy _ vtx.sy + addVtx.sy; vtx.sz _ vtx.sz + addVtx.sz; vtx.clip _ LOOPHOLE[ Basics.BITOR[ LOOPHOLE[vtx.clip], LOOPHOLE[addVtx.clip] ], ThreeDBasics.OutCode]; ENDLOOP; vtx.x _ vtx.x/poly.nVtces; vtx.y _ vtx.y/poly.nVtces; vtx.z _ vtx.z/poly.nVtces; vtx.ex _ vtx.ex/poly.nVtces; vtx.ey _ vtx.ey/poly.nVtces; vtx.ez _ vtx.ez/poly.nVtces; vtx.sx _ vtx.sx/poly.nVtces; vtx.sy _ vtx.sy/poly.nVtces; vtx.sz _ vtx.sz/poly.nVtces; }; poly: REF PtrPatchSequence; polyShades: REF ThreeDBasics.ShadingSequence _ NARROW[ ThreeDScenes.GetShading[ shape, $PatchColors ] ]; ref: REF _ Atom.GetPropFromList[shape.shadingProps, $Shininess]; shininess: REAL _ IF ref # NIL THEN NARROW[ref, REF REAL]^ ELSE 0.0; IF shape.surface = NIL OR polyShades = NIL OR ThreeDScenes.GetShading[shape, $Type] # $Faceted THEN { SIGNAL ThreeDScenes.Error[[$Condition, "Data missing for faceted shading"]]; RETURN; }; poly _ NARROW[ shape.surface, REF PtrPatchSequence ]; FOR i: NAT IN [0..poly.length) DO IF poly[i] # NIL THEN { vtx: Vertex _ AverageVertices[poly[i]]; pt: VertexInfo _ [ vtx, polyShades[i]^, NIL ]; IF polyShades[i] = NIL THEN polyShades[i] _ NEW[ ThreeDBasics.ShadingValue ]; [[polyShades[i].er, polyShades[i].eg, polyShades[i].eb], polyShades[i].et] _ ThreeDScenes.ShadeVtx[context, pt, shininess]; -- calculate shade }; ENDLOOP; ThreeDScenes.PutShading[ shape, $PatchColors, polyShades ] }; GetNormal: PROC[vertex: REF ThreeDBasics.VertexSequence, poly: REF PtrPatch, cVtx: NAT] RETURNS[normal: Triple] ~ { lVtx: NAT _ (cVtx + poly.nVtces - 1) MOD poly.nVtces; nVtx: NAT _ (cVtx + 1) MOD poly.nVtces; normal _ Vector3d.Cross[ -- in object space so do right-handed DiffPosns[ vertex[poly.vtxPtr[lVtx]], vertex[poly.vtxPtr[cVtx]] ], DiffPosns[ vertex[poly.vtxPtr[nVtx]], vertex[poly.vtxPtr[cVtx]] ] ]; }; GetPolyNormals: PUBLIC PROC[shape: REF ShapeInstance] ~ { surface: REF PtrPatchSequence; patchInfo: REF ThreeDBasics.ShadingSequence _ NARROW[ ThreeDScenes.GetShading[ shape, $PatchColors ] ]; IF shape.type # $ConvexPolygon THEN SIGNAL ThreeDScenes.Error[[$MisMatch, "Operation only for polygons"]]; IF shape.surface = NIL THEN RETURN; -- not a shape (probably a light source) surface _ NARROW[shape.surface, REF PtrPatchSequence]; IF patchInfo = NIL THEN patchInfo _ NEW[ ThreeDBasics.ShadingSequence[shape.numSurfaces] ]; FOR i: NAT IN [0..patchInfo.length) DO IF surface[i] # NIL THEN { sumNmls: Triple _ [0., 0., 0.]; FOR cVtx: NAT IN [0..surface[i].nVtces) DO sumNmls _ Vector3d.Add[ sumNmls, GetNormal[shape.vertex, surface[i], cVtx] ]; ENDLOOP; sumNmls _ Vector3d.Normalize[sumNmls]; IF patchInfo[i] = NIL THEN patchInfo[i] _ NEW[ ThreeDBasics.ShadingValue ]; patchInfo[i].xn _ sumNmls.x; patchInfo[i].yn _ sumNmls.y; patchInfo[i].zn _ sumNmls.z; }; ENDLOOP; ThreeDScenes.PutShading[ shape, $PatchColors, patchInfo ]; shape.vtcesInValid _ TRUE; -- make sure eye-space normals correct }; GetVtxNormals: PUBLIC PROC[shape: REF ShapeInstance] ~ { surface: REF PtrPatchSequence _ NARROW[shape.surface]; IF shape.type # $ConvexPolygon THEN SIGNAL ThreeDScenes.Error[[$MisMatch, "Operation only for polygons"]]; IF ThreeDScenes.GetShading[shape, $VertexNormalsInFile] # NIL THEN SIGNAL ThreeDScenes.Error[[$MisMatch, "Normals already fixed"]]; IF shape.shade = NIL OR shape.shade.length # shape.vertex.length THEN { shape.shade _ NEW[ ThreeDBasics.ShadingSequence[shape.vertex.length] ]; IF ThreeDScenes.GetShading[ shape, $Type ] = NIL OR ThreeDScenes.GetShading[ shape, $Type ] = $Faceted THEN ThreeDScenes.PutShading[ shape, $Type, $Smooth]; }; FOR i: NAT IN [0..shape.vertex.length) DO IF shape.shade[i] = NIL THEN shape.shade[i] _ NEW[ ThreeDBasics.ShadingValue ]; shape.shade[i].xn _ shape.shade[i].yn _ shape.shade[i].zn _ 0.0; ENDLOOP; FOR i: NAT IN [0..shape.numSurfaces) DO -- get normals at vertices, add to earlier ones IF surface[i] # NIL THEN FOR cVtx: NAT IN [0..surface[i].nVtces) DO OPEN shape.shade[surface[i].vtxPtr[cVtx]]; cornerNormal: Triple _ GetNormal[ shape.vertex, surface[i], cVtx ]; [[xn, yn, zn]] _ Vector3d.Add[ cornerNormal, [xn, yn, zn]]; ENDLOOP; ENDLOOP; FOR i: NAT IN [0..shape.shade.length) DO IF shape.shade[i] # NIL THEN { OPEN shape.shade[i]; [[xn, yn, zn]] _ Vector3d.Normalize[ [xn, yn, zn] ]; }; ENDLOOP; shape.vtcesInValid _ TRUE; -- make sure eye-space normals correct }; LoadSortSequence: PUBLIC PROC[ context: REF Context, sortOrder: LIST OF REF ANY _ NIL ] RETURNS[LIST OF REF ANY] ~ { awayness: REF ThreeDBasics.RealSequence; buckets: REF ThreeDSurfaces.SortSequence; sortKey: REF ThreeDBasics.NatSequence; shape: REF ThreeDBasics.ShapeSequence _ context.shapes; patchCount: CARDINAL _ 0; bucketListPtr: INT _ 1; -- start bucket count at 1 to allow use of zero as null minDepth: REAL _ context.yonLimit; maxDepth: REAL _ context.hitherLimit; zScale: REAL _ 1.; NewSortOrder: PROC[] ~ { awayness _ NEW[ThreeDBasics.RealSequence[patchCount+1]]; buckets _ NEW[ThreeDSurfaces.SortSequence[patchCount+1]]; sortKey _ NEW[ThreeDBasics.NatSequence[context.depthResolution]]; }; FOR i: NAT IN [0.. shape.length) DO -- get minimum and maximum depth and patch count IF shape[i] # NIL AND Atom.GetPropFromList[shape[i].props, $Hidden] = NIL THEN IF shape[i].clipState # out AND shape[i].surface # NIL THEN { radius: REAL _ shape[i].boundingRadius; IF shape[i].centroid.ez - radius < minDepth THEN minDepth _ shape[i].centroid.ez - radius; IF shape[i].centroid.ez + radius > maxDepth THEN maxDepth _ shape[i].centroid.ez + radius; patchCount _ patchCount + shape[i].numSurfaces; }; ENDLOOP; minDepth _ MAX[minDepth, 0]; -- nothing allowed behind the eyepoint IF (maxDepth - minDepth) > 0. THEN zScale _ (context.depthResolution - 1) / (maxDepth - minDepth); IF sortOrder = NIL THEN NewSortOrder[] ELSE { awayness _ NARROW[sortOrder.first]; buckets _ NARROW[sortOrder.rest.first]; sortKey _ NARROW[sortOrder.rest.rest.first]; }; IF awayness.length < patchCount OR sortKey.length < context.depthResolution THEN NewSortOrder[]; -- get new storage if sizes have expanded FOR i: NAT IN [0..sortKey.length) DO sortKey[i] _ nullPtr; ENDLOOP; -- clear sort structure FOR s: NAT IN [0.. shape.length) DO -- Enter patches (by z-centroid) in bucket lists IF shape[s] # NIL AND Atom.GetPropFromList[shape[s].props, $Hidden] = NIL AND shape[s].clipState # out AND shape[s].surface # NIL THEN { patch: REF PtrPatchSequence _ NARROW[shape[s].surface]; FOR i: NAT IN [0..shape[s].numSurfaces) DO IF patch[i] # NIL THEN { IF shape[s].clipState = in THEN patch[i].clipState _ in -- unclipped, inside ELSE IF shape[s].clipState = clipped THEN GetPtrPatchClipState[ shape[s], patch[i] ] -- evaluate clipping tags ELSE patch[i].clipState _ out; IF patch[i].clipState # out THEN { -- can't be proven not visible neg, pos: BOOLEAN _ FALSE; dirSum: REAL _ 0.0; zNear: REAL _ maxDepth; iz: INT; FOR j: NAT IN [0..patch[i].nVtces) DO -- get minimum z-coordinate zNear _ MIN[zNear, shape[s].vertex[patch[i].vtxPtr[j]].ez]; ENDLOOP; iz _ Real.FixI[zScale *(zNear - minDepth)]; -- get corresponding bucket address IF iz < 0 THEN iz _ 0; -- clip at zero IF patch[i].type = $ConvexPolygon THEN -- normals valid only for polygons FOR k: NAT IN [0..patch[i].nVtces) DO j: NAT _ patch[i].vtxPtr[k]; dir: REAL _ Vector3d.Dot[ -- normal front or back facing? [shape[s].vertex[j].ex, shape[s].vertex[j].ey, shape[s].vertex[j].ez], [shape[s].shade[j].exn, shape[s].shade[j].eyn, shape[s].shade[j].ezn] ]; IF dir > 0.0 THEN pos _ TRUE ELSE IF dir < 0.0 THEN neg _ TRUE; dirSum _ dirSum + dir; -- sum normals to characterize orientation ENDLOOP; IF pos AND NOT neg THEN patch[i].dir _ back ELSE IF neg AND NOT pos THEN patch[i].dir _ front ELSE patch[i].dir _ undetermined; IF NOT (patch[i].oneSided AND patch[i].dir = back) THEN { -- will be displayed bkt, bckPtr, nxtPtr: INT _ nullPtr; IF context.alphaBuffer THEN dirSum _ -dirSum; -- reverse sort order bkt _ sortKey[iz]; WHILE bkt # nullPtr AND awayness[bkt] > dirSum DO bckPtr _ bkt; -- find right place in ordered chain bkt _ buckets[bkt].next; ENDLOOP; IF bckPtr = nullPtr THEN { nxtPtr _ bkt; sortKey[iz] _ bucketListPtr; } -- head of chain ELSE { -- reset links in chain buckets[bckPtr].next _ bucketListPtr; nxtPtr _ bkt; }; bkt _ bucketListPtr; buckets[bkt] _ NEW[ShapePatch]; buckets[bkt].next _ nxtPtr; -- null if first thing in bucket buckets[bkt].shape _ shape[s]; buckets[bkt].patch _ i; awayness[bkt] _ dirSum; bucketListPtr _ bucketListPtr + 1; }; }; }; ENDLOOP; }; ENDLOOP; RETURN[ LIST[awayness, buckets, sortKey] ]; }; GetDepths: PROC[ context: REF Context] ~ { shape: REF ThreeDBasics.ShapeSequence _ context.shapes; minDepth: REAL _ context.yonLimit; maxDepth: REAL _ context.hitherLimit; zScale: REAL _ 1.; FOR i: NAT IN [0.. shape.length) DO -- get minimum and maximum depth IF shape[i] # NIL AND Atom.GetPropFromList[shape[i].props, $Hidden] = NIL THEN IF shape[i].clipState # out AND shape[i].surface # NIL THEN { radius: REAL _ shape[i].boundingRadius; IF shape[i].centroid.ez - radius < minDepth THEN minDepth _ shape[i].centroid.ez - radius; IF shape[i].centroid.ez + radius > maxDepth THEN maxDepth _ shape[i].centroid.ez + radius; }; ENDLOOP; minDepth _ MAX[minDepth, context.hitherLimit]; -- nothing allowed behind the eyepoint IF (maxDepth - minDepth) > 0. THEN zScale _ (context.depthResolution - 1) / (maxDepth - minDepth); 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 { patch: REF PtrPatchSequence _ NARROW[shape[s].surface]; FOR i: NAT IN [0..shape[s].numSurfaces) DO IF patch[i] # NIL THEN IF shape[s].clipState = in THEN { -- unclipped, inside FOR j: NAT IN [0..patch[i].nVtces) DO shape[s].vertex[patch[i].vtxPtr[j]].sz _ zScale * (shape[s].vertex[patch[i].vtxPtr[j]].ez - minDepth); ENDLOOP; patch[i].clipState _ in; } ELSE IF shape[s].clipState = clipped THEN -- clipped, ensure positive result FOR j: NAT IN [0..patch[i].nVtces) DO shape[s].vertex[patch[i].vtxPtr[j]].sz _ MAX[ 0.0, zScale * (shape[s].vertex[patch[i].vtxPtr[j]].ez - minDepth) ]; ENDLOOP; ENDLOOP; }; ENDLOOP; }; currentColor: SampleSet; -- global color for line drawings currentShape: REF ShapeInstance; UpdateShapeCache: PROC[context: REF Context, shape: REF ShapeInstance] ~ { currentShape _ shape; IF Atom.GetPropFromList[shape.shadingProps, $Type ] = $Lines THEN currentColor _ ShapetoColorBytes[context, shape]; }; DoBackToFront: PUBLIC PROC[ context: REF Context, sortInfo: LIST OF REF ANY, action: PROC[REF ThreeDSurfaces.ShapePatch] ] ~ { sortKey: REF ThreeDBasics.NatSequence _ NARROW[sortInfo.rest.rest.first]; buckets: REF ThreeDSurfaces.SortSequence _ NARROW[sortInfo.rest.first]; FOR i: NAT DECREASING IN [0..context.depthResolution) DO j: NAT _ sortKey[i]; WHILE j # nullPtr DO IF buckets[j].shape # currentShape THEN UpdateShapeCache[context, buckets[j].shape]; action[buckets[j]]; -- call back with next polygon in order j _ buckets[j].next; ENDLOOP; ENDLOOP; ThreeDMisc.CombineBoxes[context]; -- get combined bounding box on scene }; DoFrontToBack: PUBLIC PROC[ context: REF Context, sortInfo: LIST OF REF ANY, action: PROC[REF ThreeDSurfaces.ShapePatch] ] ~ { sortKey: REF ThreeDBasics.NatSequence _ NARROW[sortInfo.rest.rest.first]; buckets: REF ThreeDSurfaces.SortSequence _ NARROW[sortInfo.rest.first]; FOR i: NAT IN [0..context.depthResolution) DO j: NAT _ sortKey[i]; WHILE j # nullPtr DO IF buckets[j].shape # currentShape THEN UpdateShapeCache[context, buckets[j].shape]; action[buckets[j]]; -- call back with next polygon in order j _ buckets[j].next; ENDLOOP; ENDLOOP; ThreeDMisc.CombineBoxes[context]; -- get combined bounding box on scene }; DoForPatches: PUBLIC PROC[ context: REF Context, set: REF ThreeDBasics.ShapeSequence, patchAction: PROC[REF ThreeDSurfaces.ShapePatch], shapeAction: PROC[REF ThreeDBasics.ShapeInstance] _ NIL ] ~ { FOR s: NAT IN [0..set.length) DO IF Atom.GetPropFromList[set[s].props, $Hidden] = NIL THEN { IF set[s].clipState = in AND set[s].type = $ConvexPolygon AND shapeAction # NIL THEN shapeAction[set[s]] ELSE IF set[s].clipState # out AND set[s].surface # NIL THEN { patch: REF PtrPatchSequence _ NARROW[set[s].surface]; currentColor _ ShapetoColorBytes[context, set[s]]; -- set color for shape FOR i: NAT IN [0..set[s].numSurfaces) DO IF patch[i] # NIL THEN { IF set[s].clipState = in THEN patch[i].clipState _ in -- unclipped, inside ELSE IF set[s].clipState = clipped THEN GetPtrPatchClipState[ set[s], patch[i] ] ELSE patch[i].clipState _ out; IF patch[i].clipState # out THEN patchAction[NEW[ ShapePatch _ [set[s], i, 0] ]]; }; ENDLOOP; }; }; ENDLOOP; }; ShowObjects: PUBLIC PROC[ context: REF Context, frontToBack: BOOLEAN _ FALSE ] ~ { ShowPatch: PROC[p: REF ThreeDSurfaces.ShapePatch] ~{ patch: REF Patch _ ShapePatchToPatch[ context, p ]; OutputPatch[ context, patch ]; }; time: REAL _ CurrentTime[]; log: IO.STREAM _ NARROW[ Atom.GetPropFromList[context.props, $Log] ]; timing: Rope.ROPE; shape: REF ThreeDBasics.ShapeSequence _ context.shapes; IF shape = NIL THEN RETURN[]; 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; timing _ Rope.Cat[ "Xforms: ", ElapsedTime[time] ]; time _ CurrentTime[]; FOR i: NAT IN [0.. shape.length) DO -- now, get it shaded IF shape[i].shadingInValid AND (shape[i].clipState # out) AND Atom.GetPropFromList[shape[i].props, $Hidden] = NIL THEN { shadingType: REF ANY _ ThreeDScenes.GetShading[ shape[i], $Type ]; IF shadingType = $Faceted THEN GetShades[ context, shape[i] ] ELSE IF shadingType = $Smooth OR shadingType = $Lines THEN ThreeDScenes.GetVtxShades[ context, shape[i] ] ELSE [] _ NARROW[shadingType, REF ShapeProc][ context, shape[i] ]; -- use proc }; ENDLOOP; timing _ Rope.Cat[ timing, " Shading: ", ElapsedTime[time] ]; time _ CurrentTime[]; IF context.depthBuffer THEN { GetDepths[context]; DoForPatches[context, context.shapes, ShowPatch]; } ELSE { context.sortSequence _ LoadSortSequence[context, NARROW[context.sortSequence] ]; timing _ Rope.Cat[ timing, " Sort: ", ElapsedTime[time] ]; time _ CurrentTime[]; IF frontToBack THEN DoFrontToBack[context, NARROW[context.sortSequence], ShowPatch] ELSE DoBackToFront[context, NARROW[context.sortSequence], ShowPatch]; }; IF log # NIL THEN log.PutRope[ Rope.Cat[ timing, " Scanout: ", ElapsedTime[time] ] ]; }; ShowWireFrameObjects: PUBLIC PROC[context: REF Context ] ~ { ShowPatch: PROC[p: REF ThreeDSurfaces.ShapePatch] ~{ patch: REF Patch _ ShapePatchToPatch[ context, p ]; OutputPatchEdges[ context, patch ]; }; ShowShape: PROC[s: REF ThreeDBasics.ShapeInstance] ~{ OutputShapeLines[ context, s ]; }; shape: REF ThreeDBasics.ShapeSequence _ context.shapes; IF shape = NIL THEN RETURN[]; FOR i: NAT IN [0.. shape.length) DO IF Atom.GetPropFromList[shape[i].props, $Hidden] = NIL AND shape[i].vtcesInValid THEN { shape[i].clipState _ ThreeDScenes.XfmToEyeSpace[ context, shape[i] ]; IF shape[i].clipState # out THEN ThreeDScenes.XfmToDisplay[context, shape[i] ]; }; ENDLOOP; IF context.alphaBuffer THEN DoForPatches[context, context.shapes, ShowPatch] ELSE DoForPatches[context, context.shapes, ShowPatch, ShowShape]; ThreeDMisc.CombineBoxes[context]; -- get combined bounding box on scene }; EdgesToPolygons: PROC[context: REF Context, patch: REF Patch] ~ { baseRadius: REAL _ .003; limit: NAT _ IF patch.type = $Path THEN patch.nVtces - 1 ELSE patch.nVtces; MakeEdge: PROC[pt1, pt2: VertexInfo, edge: REF Patch] ~ { dirX, dirY, mag, offSetX1, offSetY1, offSetX2, offSetY2: REAL; dirX _ pt2.coord.ex - pt1.coord.ex; -- get unit vector in edge direction dirY _ pt2.coord.ey - pt1.coord.ey; mag _ RealFns.SqRt[ Sqr[dirX] + Sqr[dirY] ]; IF mag < ScanConvert.justNoticeable THEN RETURN[]; -- quit if too short to be seen dirX _ dirX / mag; dirY _ dirY / mag; offSetX1 _ dirX * baseRadius; offSetY1 _ dirY * baseRadius; offSetX2 _ dirX * baseRadius; offSetY2 _ dirY * baseRadius; FOR i: NAT IN [0..3) DO edge[i] _ pt1; ENDLOOP; FOR i: NAT IN [3..6) DO edge[i] _ pt2; ENDLOOP; edge[0].coord.ex _ edge[0].coord.ex+offSetY1; edge[0].coord.ey _ edge[0].coord.ey-offSetX1; edge[1].coord.ex _ edge[1].coord.ex-offSetX1; edge[1].coord.ey _ edge[1].coord.ey-offSetY1; edge[2].coord.ex _ edge[2].coord.ex-offSetY1; edge[2].coord.ey _ edge[2].coord.ey+offSetX1; edge[3].coord.ex _ edge[3].coord.ex-offSetY2; edge[3].coord.ey _ edge[3].coord.ey+offSetX2; edge[4].coord.ex _ edge[4].coord.ex+offSetX2; edge[4].coord.ey _ edge[4].coord.ey+offSetY2; edge[5].coord.ex _ edge[5].coord.ex+offSetY2; edge[5].coord.ey _ edge[5].coord.ey-offSetX2; IF edge.clipState = in THEN FOR i: NAT IN [0..6) DO OPEN edge[i].coord; shape: REF ShapeInstance _ IF context.alphaBuffer THEN NARROW[ Atom.GetPropFromList[patch.props, $Shape] ] ELSE NIL; [[sx, sy, sz]] _ ThreeDScenes.XfmPtToDisplay[ context, shape, [ex, ey, ez] ]; ENDLOOP; OutputPatch[context, edge]; }; FOR i: NAT IN [0..limit) DO edge: REF Patch _ GetPatch[6]; -- will be released by OutputPatch edge.type _ $ConvexPolygon; edge.nVtces _ 6; edge.oneSided _ patch.oneSided; edge.dir _ patch.dir; edge.clipState _ patch.clipState; edge.props _ Atom.PutPropOnList[ NIL, $Type, $Smooth ]; MakeEdge[ patch[i], patch[(i+1) MOD patch.nVtces], edge ]; ENDLOOP; ReleasePatch[patch]; -- end of the line for this patch }; ImagerLine: PROC[ context: REF Context, ax, ay, bx, by: INTEGER, color: SampleSet] ~ { DoLine: PROC[imagerCtx: Imager.Context] ~ { ThreeDMisc.SetRGBColor[imagerCtx, [color[0]/255.0, color[1]/255.0, color[2]/255.0] ]; Imager.MaskVectorI[ imagerCtx, ax, ay, bx, by ]; }; IF context.renderMode = $Interpress THEN { imagerCtx: Imager.Context _ NARROW[Atom.GetPropFromList[context.props, $ImagerCtx]]; Imager.SetStrokeWidth[ imagerCtx, 1.0 ]; DoLine[ imagerCtx ]; } ELSE QuickViewer.DrawInViewer[ NARROW[context.viewer], DoLine ]; }; OutputShapeLines: PUBLIC PROC[context: REF Context, s: REF ThreeDBasics.ShapeInstance] ~ { ax, ay, bx, by: NAT; color: SampleSet _ ShapetoColorBytes[context, s]; usingImager: BOOLEAN _ FALSE; patches: REF PtrPatchSequence; IF s.surface = NIL THEN RETURN; IF context.renderMode = $Dithered THEN usingImager _ TRUE; patches _ NARROW[s.surface, REF PtrPatchSequence]; FOR i: NAT IN [0..s.numSurfaces) DO IF patches[i].type # $ConvexPolygon THEN SIGNAL ThreeDScenes.Error[[$MisMatch, "Operation only for convex polygons"]] ELSE FOR j: NAT IN [0..patches[i].nVtces] DO k: NAT _ IF j = patches[i].nVtces THEN 0 ELSE j; bx _ Real.RoundC[s.vertex[patches[i].vtxPtr[k]].sx]; by _ Real.RoundC[s.vertex[patches[i].vtxPtr[k]].sy]; IF j > 0 THEN IF NOT usingImager THEN ScanConvert.PutLine[ context.display, [ax, ay], [bx, by], color ] ELSE ImagerLine[ context, ax, ay, bx, by, color ]; ax _ bx; ay _ by; ENDLOOP; IF context.stopMe THEN HoldEverything[]; -- shut down if stop signal received ENDLOOP; }; OutputPatchEdges: PUBLIC PROC[context: REF Context, patch: REF Patch] ~ { usingImager: BOOLEAN _ FALSE; { IF patch = NIL OR patch.clipState = out THEN GO TO CleanUp; -- reject if outside frame IF patch.type # $ConvexPolygon AND patch.type # $Path -- expand to curves THEN { ExpandToLines[context, patch, OutputPatchEdges]; RETURN[]; }; IF context.alphaBuffer -- antialiased THEN { EdgesToPolygons[context, patch]; RETURN[]; }; IF context.renderMode = $Dithered OR context.renderMode = $Interpress THEN usingImager _ TRUE; IF patch.clipState = in THEN { ax, ay, bx, by: NAT; limit: NAT _ IF patch.type = $Path THEN patch.nVtces - 1 ELSE patch.nVtces; FOR j: NAT IN [0..limit] DO i: NAT _ IF j = patch.nVtces THEN 0 ELSE j; bx _ Real.RoundC[patch[i].coord.sx]; by _ Real.RoundC[patch[i].coord.sy]; IF j > 0 THEN IF NOT usingImager THEN ScanConvert.PutLine[ context.display, [ax, ay], [bx, by], currentColor ] ELSE ImagerLine[ context, ax, ay, bx, by, currentColor ]; ax _ bx; ay _ by; ENDLOOP; } ELSE IF patch.clipState = clipped THEN { patch _ ClipPoly[ context, patch ]; IF patch.nVtces > 2 OR ( patch.type = $Path AND patch.nVtces > 1 ) THEN { ax, ay, bx, by: NAT; shape: REF ShapeInstance _ IF context.alphaBuffer THEN NARROW[ Atom.GetPropFromList[patch.props, $Shape] ] ELSE NIL; limit: NAT _ IF patch.type = $Path THEN patch.nVtces - 1 ELSE patch.nVtces; FOR j: NAT IN [0..limit] DO i: NAT _ IF j = patch.nVtces THEN 0 ELSE j; x, y, z: REAL; [[x, y, z]] _ ThreeDScenes.XfmPtToDisplay[ context, shape, [patch[i].coord.ex, patch[i].coord.ey, patch[i].coord.ez] ]; bx _ Real.RoundC[x]; by _ Real.RoundC[y]; IF j > 0 THEN IF NOT usingImager THEN ScanConvert.PutLine[ context.display, [ax,ay], [bx,by], currentColor ] ELSE ImagerLine[ context, ax, ay, bx, by, currentColor ]; ax _ bx; ay _ by; ENDLOOP; }; }; EXITS CleanUp => NULL; }; ReleasePatch[patch]; IF context.stopMe THEN HoldEverything[]; -- shut down if stop signal received }; OutputPatch: PUBLIC PROC[context: REF Context, patch: REF Patch] ~ { { IF patch = NIL OR patch.clipState = out THEN GO TO CleanUp; -- reject if outside frame IF Atom.GetPropFromList[patch.props, $Type ] = $Lines THEN { OutputPatchEdges[context, patch]; -- sorted, anti-aliased line drawings, patch lines RETURN[]; }; IF patch.type # $ConvexPolygon -- catch unexpanded patches, etc. THEN { ExpandToConvexPolys[context, patch, OutputPatch]; RETURN; }; IF patch.clipState = clipped THEN { patch _ ClipPoly[context, patch]; IF patch.nVtces > 2 THEN { shape: REF ShapeInstance _ IF context.alphaBuffer THEN NARROW[ Atom.GetPropFromList[patch.props, $Shape] ] ELSE NIL; FOR i: NAT IN [0..patch.nVtces) DO OPEN patch[i].coord; [[sx, sy, sz]] _ ThreeDScenes.XfmPtToDisplay[context, shape, [ex, ey, ez]]; ENDLOOP; }; }; IF patch.nVtces > 2 THEN { IF patch.dir = undetermined THEN patch.dir _ BackFacing[ patch ! ThreeDScenes.Error => IF reason.code = $Condition THEN GO TO GiveUp ]; IF patch.dir = front THEN Tilers.PolygonTiler[context, patch] ELSE IF patch.oneSided -- backfacing!! THEN RETURN[] -- Reject if closed surface ELSE { ref: REF ANY _ Atom.GetPropFromList[patch.props, $ShadeVtx]; FOR i: NAT IN [0..patch.nVtces) DO -- recalculate shading for back side patch[i].shade.exn _ -patch[i].shade.exn; -- reverse normals patch[i].shade.eyn _ -patch[i].shade.eyn; patch[i].shade.ezn _ -patch[i].shade.ezn; IF ref = NIL -- use standard shading proc THEN [ [patch[i].shade.er, patch[i].shade.eg, patch[i].shade.eb], patch[i].shade.et ] _ ThreeDScenes.ShadeVtx[ context, patch[i], 0.0 ] ELSE { -- call custom shader shadeVtx: REF ThreeDBasics.VertexInfoProc _ NARROW[ref]; patch[i] _ shadeVtx^[context, NEW[VertexInfo _ patch[i]], patch.props]^; }; ENDLOOP; FOR i: NAT IN [0..patch.nVtces/2) DO -- reorder to keep clockwise on display tempVtx: VertexInfo _ patch[i]; patch[i] _ patch[patch.nVtces-1 - i]; patch[patch.nVtces-1 - i] _ tempVtx; ENDLOOP; Tilers.PolygonTiler[context, patch] }; EXITS GiveUp => NULL }; EXITS CleanUp => NULL; }; ReleasePatch[patch]; IF context.stopMe THEN HoldEverything[]; -- shut down if stop signal received }; END. 4ThreeDSurfacesImpl.mesa Copyright c 1984, 1986 by Xerox Corporation. All rights reserved. Last Edited by: Crow, December 16, 1986 5:00:42 pm PST Internal Declarations Global Variables allocation avoidance structures - caches of peculiar data types Utility Procedures Procedures for Shape Description I/O Get Surface Type Get Vertices Get Surface Find approximation to bounding sphere Header Vertices Surface Procedures for Transformations and Clipping Put out point if clip plane crossed Procedures for expansion to polygons Expands a whole shape, calling procedures supplied by the surface type Subdivide a whole shape once, calling procedures supplied by the surface type expand a patch into curved lines, pass them as "$Paths" PROC[ context: REF Context, patch: REF Patch, limitType: ATOM, limit: REAL, action: PROC]; expand a patch into displayable polygons PROC[ context: REF Context, patch: REF Patch, limitType: ATOM, limit: REAL, action: PROC]; Procedures for Shading Assumes left-handed space (eye space or screen space) Backfacing test based on first vertex and adjacent vertices last: VertexInfo _ poly.vtx[poly.nVtces - 1]; Backfacing test based on convex hull being hidden behind its base Calculate shades for Faceted shading (Used for quick display) Compute Normals, Sum normals at polygon corners to get polygon normal Sum normals for vertices given by adjacent polygon corners, only for polygons! Procedures for Sorting and Display Get Everything (including light centroids) into eyespace Make a polygon for each edge and tile it Unclipped shape output Ê>’˜Iheadšœ™šœ Ïmœ7™BJšœ6™6J˜šÏk ˜ Jšœ žœS˜aJšœ žœ˜+Jšœ žœ ˜Jšœ žœžœžœ˜#Jšœ žœ%˜6Jšœ žœžœ˜*Jšœ žœ ˜0Jšžœžœ žœ ˜)Idefaultšœžœžœ ˜Lšœ žœ*˜9Jšœžœ˜%Jšœ žœ˜-Jšœžœ˜0Jšœ žœ.˜?Jšœ žœ˜"JšœžœÎ˜áJšœ žœL˜^Jšœžœq˜„Jšœ žœ˜"Jšœžœe˜zJšœ žœ~˜—J˜—head2šœžœž˜!Iašžœ¦˜®Nšžœ˜J˜Jšœž˜J˜—head3šÏb™Jšœ žœ˜%Jšžœžœžœ Ïc˜Jšžœžœžœ˜Lšœžœ˜ šžœ˜Lšžœžœ ˜šžœž˜Lšœ"˜"Lšœ˜Lšœžœ˜ Lšžœžœžœ˜2L˜——Lšžœ˜ Lšœ˜—š¡ œžœžœ ˜1Jšžœžœžœ˜Lšžœžœžœžœ˜šžœ"žœ˜*Lšœ žœ(˜8Lšœ(˜(Lšœ˜Lšœ˜—Lšœ˜Lšœ"˜"Lšœ˜—š¡ œžœ žœ žœ ˜;Jšžœ8˜>J˜—š¡œž œ˜!Nšžœžœ˜J˜J˜—š ¡œžœ žœ žœžœ˜dNšœžœžœ'˜3Lšœ žœ˜Lšœžœ˜Lšžœžœ˜.Lšžœžœ˜.šžœžœ˜ Lš žœ žœžœžœ ˜=Lšžœžœ"žœžœ˜T—šžœžœ !˜Gšœ ˜ Jšœžœ*˜2šžœ#˜%Jšžœžœ  ˜Q—Jšœ˜—šœ˜Jšžœžœ+˜NJšœ?˜?Jšžœ žœžœ žœ˜LJšœ˜—šœ ˜ Jšžœžœ+˜NJšœ4˜4Jšžœ žœžœ žœ˜LJ˜—šœ(˜(Jšžœžœ+˜NJšœ'˜'Jšœ'˜'Jšœ'˜'Jšžœ žœžœ žœ˜LJšœ˜—Jšžœžœ<˜N—Jšžœ ˜Jšœ˜—š ¡œž œ žœžœžœ žœ ˜ŽJšœ žœ ž œžœ!˜]Nšœžœ3˜>Jšœžœ3˜=Jšœ žœ2˜FJšœ žœ(žœ6˜pJšœ žœ˜*Jšœžœ˜&šœ žœ žœ˜6Jšœ6˜6Jšœ˜—š œžœžœ žœžœžœ ˜=Jšžœ?ž˜FJšžœžœ˜ —J˜Jš žœžœžœžœ ˜NJšœ) *˜SJšœ ˜ Jšœ&˜&Jšœ˜Jšœ#˜#Jšœ˜Jšœžœ˜šžœ<žœžœž˜RJšœžœ$ ˜XJšœžœ˜)Jšžœ˜—JšœF ˜\šžœžœžœž˜%Jšœžœ˜Jšœ˜Jšœ˜šžœ žœžœ˜Jšœžœžœžœžœžœžœžœ˜GJšœžœ"˜BJ˜—šžœžœ ˜8Jšœ&˜&Lšœ%˜%Lšœ%˜%Lšœ˜—šžœ žœ   ˜Ešžœ˜ Jšžœ*˜.šžœžœžœ˜JšœC˜CLšœB˜BLšœB˜BLšœC˜Cšžœžœ "˜BLšœ:˜:Jšœ:˜:Jšœ:˜:Jšœ:˜:J˜—J˜———Jšžœ˜—Jšœ˜——šŸ$™$š¡ œž œžœžœ˜IJšœžœžœ'˜8Lšœ žœ &˜CLšœž˜LšŸ™Lšœ8žœ žœ˜gLšœ3˜3Lšœž˜L˜Lšžœ&žœžœ˜ULšžœ%žœžœ˜NLšžœ%žœžœžœ˜Tšžœ+žœžœ˜ML˜—J™JšŸ ™ šœ žœJ˜ZJšœ.žœ˜6Jšœ žœžœ˜"Jšœžœ1˜CLšœžœ2˜Cšžœžœžœ˜Jšœ žœ$˜1Jšœ!˜!Jšœ˜J˜—šžœžœžœž˜%Jšœžœ,˜AJšœžœ2˜Fšžœžœžœ˜PJšžœ˜#—šžœžœžœ˜MJšžœ˜!—Jšžœžœ˜9šžœžœžœ˜Jšœ žœžœ&˜NJ˜—Jšžœ˜—šžœ#˜%Jšžœ@˜D—šžœ"˜$Jšžœ?˜C—šžœ!˜#Jšžœ>˜B—šžœ ˜"Jšžœ@˜D—Jšœ0˜0J˜—J˜JšŸ ™ š œžœžœžœ žœ ˜VJšœžœ?˜Jš ¡ œžœžœžœžœ˜PJšœžœ3˜=šžœžœžœ˜Jšœžœ3˜:šžœžœžœžœ˜(Jšœžœ˜'Jšžœ˜—J˜—Jšœ˜—Jšœ˜šžœžœžœž˜#Jšœ žœ˜,šžœž˜šœ ˜ Jšœžœžœ˜9Jšœ"˜"šžœžœž˜Jšœ"žœ˜/šžœ˜ Jšœžœ( ˜CJšœ.˜.Jšœ˜——Jšœ˜—šœ ˜ Jšœ žœžœ˜7Jšœ#˜#Jšœ ˜ šžœžœž˜šœ"žœ˜,Jš žœžœžœžœ žœ˜L—šžœ˜ Jšœžœ( ˜CJšœ/˜/Jšœ˜——Jšœ˜—šœ ˜ Jšœ žœžœ˜;Jšœ%˜%Jšœ ˜ šžœžœž˜šœ"žœ˜.šžœžœžœžœ˜(Jšœ$˜$Jšœ#˜#Jšœ ˜ Jšžœ˜—Jšœ:˜:Jšœ<˜Jšžœ˜ —Jšœ,˜,Lšœžœžœ,˜BNšœ žœžœ˜Jšœ,˜,Jšœ(˜(Jšœ0˜0šžœžœžœž˜*Jšœ2˜2Jšžœ˜—Jšžœ˜ —Jšœžœ  ˜;šžœ8žœžœž˜NJšœžœ$˜BJšœžœ!˜=Jšžœ˜—Jšœžœ ˜7šžœ1žœžœž˜GJšœžœ$˜BJšœžœ˜/Jšžœ˜—šžœ5žœžœ ˜Tšœ žœžœ˜)Jšœ1˜1Jšœ˜—Jšœžœžœ)˜Qšžœžœžœž˜'Jšœžœ!˜7Jšžœ˜—Jšœ@˜@Jšœ˜—Jšœ˜—š¡ œž œžœž œžœžœ*žœžœ˜˜Jšœžœžœ8˜IJšœ žœ˜Jšœžœžœ˜DJšœ žœžœ,˜RJšœ žœžœ˜4Jš œžœžœžœ žœ ˜Wš œžœžœžœžœžœ˜QJšŸ™—Jšœ7 ˜SšœR  ˜\JšŸ™—šžœžœžœž˜)Jšœžœ ˜Jšœ%˜%Jšœ$˜$Jšžœ žœžœžœ˜CJšžœ˜—šœq˜qJšŸ™—šžœ žœ˜Jšœžœžœ2˜UJšœ žœžœ!˜DJšœ ˜ šžœžœžœž˜#Jšœ@žœž˜^Jšžœ˜—Jšœ žœ˜(Jšœ žœ˜ Jšœ˜Jšœ˜Jšœ˜Jšœ˜Jšœ˜—šœ žœžœ,˜WLšœ žœžœžœ˜Lšžœžœžœž˜'Lšœ žœ#˜3šžœžœžœž˜'Jšœ%˜%Jšžœ˜—Jšœ&˜&Jšžœ˜—Jšœ#˜#Jšœžœ˜(Jšœ%˜%Jšœ˜Jšœ"˜"Jšœ˜Jšœ˜—Jšœ2˜2Jšžœ˜Jšœ ˜——šŸ+™+š¡œžœžœ žœžœ žœžœ ˜Yš ¡œžœžœžœžœžœ ˜Tš ¡œžœžœžœ ˜Ršžœ˜Nšœ˜Nšœ˜Nšœ˜—Nšœ˜—Nšœžœžœ˜+Pšžœžœžœ ˜CN˜ šžœžœ˜Nšœ5˜5Nšœ˜N˜—Nšžœ!žœžœ˜Jšžœžœžœž˜ Nšœžœ˜ Nšœ$˜$šžœžœžœžœ˜?Nš #™#Nšœ-˜-NšœN˜NNšœN˜NNšœN˜NNšœQ˜QNšœQ˜QNšœQ˜QNšœP˜PNšœP˜PNšœP˜PNšœN˜NNšœN˜NNšœN˜NNšœN˜NNšœQ˜QNšœQ˜QNšœQ˜QNšœQ˜Qšžœ žœžœ˜š œžœžœžœžœžœ˜Nš œ#žœžœžœžœ˜@Nšœ˜—Nšœ&žœ)˜RN˜Nšžœ'˜+—N˜N˜—šžœ žœ ˜4Nšœ.˜.Nšœ.˜.Nšœ.˜.Nšœ0˜0Nšœ0˜0Nšœ0˜0Nšœ2˜2Nšœ2˜2Nšœ2˜2Nšœ.˜.Nšœ.˜.Nšœ.˜.Nšœ.˜.Nšœ0˜0Nšœ0˜0Nšœ0˜0Nšœ0˜0Nšœ&˜&N˜N˜—Nšœ˜Nšžœ˜—Nšœ˜Nšœ˜Jšœ˜N˜Nšœ˜Nšžœ˜Nšœ ˜—Pšœžœžœ.˜:Lšœ(žœ˜,Lšœ7˜7Jšœžœ% !˜PJ˜šžœžœ˜4Jšžœžœ7˜B—šžœžœ  0˜FJšžœ žœžœ˜>—šžœžœžœžœ˜"šœ žœ˜Jšœžœžœ žœ˜DJšœ˜—Jšžœ˜—Jšžœžœ,˜EJšžœžœ-˜GJšžœžœ.˜HJšžœžœ-˜FJšžœžœ+˜CJšžœžœ,˜EJšœ ˜3Jšžœ ˜N˜—š¡œžœžœ žœ ˜5Jšœ;˜;Jšœ8˜8šžœžœžœž˜"šœ žœ˜Jšœžœž œ žœ˜BJšœ˜—šœ žœ˜Jšœžœžœžœ˜CJšœ˜—Jšžœ˜—šžœ#˜%Jšžœ˜šžœžœ"˜)Jšžœ˜Jšžœ˜——L˜—š¡œžœ žœžœ˜NJšœ;˜;Jšœ8˜8šžœžœžœž˜"Jšœžœ˜šœ žœ˜Jšœžœž œ žœ˜CJšœ˜—šœ žœ˜Jšœžœžœžœ˜DJšœ˜—Jšžœ˜—šžœ#˜%Jšžœ˜šžœžœ"˜)Jšžœ˜Jšžœ˜——L˜——šŸ$™$š¡œžœ žœžœžœžœ žœžœžœ˜¢codeš¡œžœ  1˜Hšžœ žœ =˜QNšžœ žœ5˜Fšžœžœ* ˜Lšžœ˜Nšœ žœ˜šžœžœžœ˜!NšžœžœV˜a—Nšœ žœ$˜1š žœžœžœžœ ˜<šžœ žœ˜Nšžœžœ˜-Nšžœžœ ˜!—Nšžœ˜—Nšœ˜N˜———šžœ žœ =˜PNšžœ žœ6˜Fšžœžœ) ˜Kšžœ˜Nšœžœžœ%˜Fš žœžœžœžœ ˜;šžœ žœ˜Nšžœ žœ˜1Nšžœžœ˜&—Nšžœ˜—Nšœ˜N˜———šžœ žœ =˜RNšžœ žœ;˜Mšžœžœ1 ˜Sšžœ˜Nšœ žœ˜šžœžœžœ˜"NšžœžœV˜a—Nšœ žœ'˜5š žœžœžœžœ ˜=šžœžœ˜Nšžœžœ˜1Nšžœžœ ˜$—Nšžœ˜—Nšœ˜N˜———Q˜—Nšœžœžœ˜6Nšœžœ˜(Nšœžœ˜(Nšœ žœ˜šœ žœ žœ˜5Jšœ.˜.Jšœ˜—Nšœžœ!˜,Nšœ žœ˜!Nšœžœ˜NšœžœžœD˜qNšžœ žœžœžœ8˜Qšžœ žœžœ˜%Nšžœžœ3˜=—šžœžœ žœžœ˜,Nšžœžœ6˜@—N˜šžœžœžœž˜*šžœ ˜.NšžœJ˜NNšžœN˜R—Nšœ '˜=š žœžœžœžœ #˜LNšœžœ˜/Nšœ%˜%Nšœžœ˜4Nšœ$˜$šžœ žœžœ˜Nšœ<˜Nšœ,˜,Nšžœ˜—Nšžœ žœ )˜ZNšœ  "˜BNšœ˜Nšœ˜Nšœ#˜#Jšœ.žœ˜4Nšœž˜Nšœž˜Nšžœ˜N˜—š¡ œžœžœ žœžœ&žœžœ žœžœžœ˜¤N™FNšžœžœ˜Jšžœžœ:˜E—šžœžœžœ*žœ˜GJšœžœ7˜Hšžœ.žœžœ4˜lJšžœ1˜5—J˜—šžœžœžœžœ˜*Jšžœžœžœžœ˜OJšœB˜BJšžœ˜ —š žœžœžœžœ 0˜\šžœžœžœžœžœžœžœ˜DJšžœ'˜+JšœC˜CJšœ;˜;Jšžœ˜—Jšžœ˜ —šžœžœžœžœ˜)šžœžœžœ˜Jšžœ˜Jšœ4˜4Jšœ˜—Jšžœ˜—Jšœžœ -˜HJ˜——šŸ"™"š¡œžœžœ žœž œžœžœ žœž œžœ˜{Nšœ žœ˜(Nšœ žœ˜)Nšœ žœ˜&Nšœžœ-˜7Nšœ žœ˜Nšœžœ 7˜QNšœ žœ˜"Nšœ žœ˜%Nšœžœ˜š¡ œžœ˜Lšœ žœ*˜8Nšœ žœ,˜9Nšœ žœ4˜AN˜—š žœžœžœžœ 0˜Tš žœ žœžœ1žœž˜Nšžœžœžœžœ˜=Nšœžœ˜'Nšžœ*˜,Nšœžœ*˜/šžœ)˜+Nšžœ*˜.—Nšœ/˜/N˜——Nšžœ˜—Nšœ žœ &˜Gšžœ˜Nšžœ@˜D—šžœ žœ˜Lšžœ˜šžœ˜Nšœ žœ˜#Nšœ žœ˜'Nšœ žœ˜,Nšœ˜——šžœžœ*˜MLšžœ )˜D—Lš žœžœžœžœžœ ˜]š žœžœžœžœ 4˜Yšžœžœžœ1žœžœžœžœ˜–Jšœžœžœ˜7šžœžœžœžœ˜+šžœ žœžœ˜šžœ˜Jšžœ  ˜8šžœžœ˜%Jšžœ, ˜JLšžœ˜——šžœžœ ˜FJšœ žœžœ˜Jšœžœ˜Jšœžœ˜Jšœžœ˜šžœžœžœž ˜DJšœžœ0˜;Jšžœ˜—Jšœ, #˜OJšžœžœ ˜,šžœ žœ "˜Jšžœžœžœž˜%Jšœžœ˜šœžœ ˜=JšœF˜FJšœE˜EJ˜—Jšžœ žœžœžœžœ žœžœ˜?Jšœ *˜BJšžœ˜——šžœžœžœžœ˜+š žœžœžœžœžœ˜1Jšžœ˜"——š žœžœžœžœ ˜NJšœžœ ˜#Jšžœžœ ˜DJšœž˜šžœžœžœ˜2Jšœ $˜8Jšœ˜Jšžœ˜—šžœ˜Jšžœ5 ˜Išžœ ˜+Jšœ7˜7Jšœ˜——Jšœ˜Jšœžœ ˜Jšœ  ˜?Jšœ"˜"Jšœ˜Jšœ˜Jšœ"˜"Jšœ˜—J˜—Jšœ˜—Jšžœ˜Jšœ˜——Nšžœ˜—Nšžœžœ˜+Nšœ˜N˜—š¡ œžœ žœ ˜*Nšœžœ-˜7Nšœ žœ˜"Nšœ žœ˜%Nšœžœ˜š žœžœžœžœ  ˜Dš žœ žœžœ1žœž˜Nšžœžœžœžœ˜=Nšœžœ˜'Nšžœ*˜,Nšœžœ*˜/šžœ)˜+Nšžœ*˜.—N˜——Nšžœ˜—Nšœ žœ! &˜Ušžœ˜Nšžœ@˜D—šžœžœžœž˜#š žœ žœžœ1žœž˜Nšžœžœžœžœ˜>Jšœžœžœ˜7šžœžœžœžœ˜+šžœ žœž˜šžœ˜šžœ  ˜"šžœžœžœžœ˜&Jšœi˜iJšžœ˜ —Jšœ˜J˜—šžœžœžœ "˜Lšžœžœžœžœ˜&šœ)žœ˜-Jšœ˜Jšœ<˜˜B—Jšœ$ %˜IJšœ˜J˜—š¡œžœ žœžœ ˜AJ™(Jšœ žœ˜Jš œžœžœžœžœ˜Kš¡œžœžœ ˜9Jšœ9žœ˜>Jšœ( $œ˜PJšœ#˜#Jšœ,˜,Jšžœ"žœžœ ˜TJšœ.˜.Jšœ<˜Jšœ)˜)Jšœ)˜)šžœžœ  ˜3JšžœŠ˜Žšžœ  ˜%Jšœ žœžœ˜9Jšœžœ'˜HJ˜——Jšžœ˜—š žœžœžœžœ '˜MJšœ˜Jšœ%˜%Jšœ$˜$Jšžœ˜—Jšœ#˜#Jšœ˜———Jšžœ ž˜J˜—Lšžœ žœ˜L˜—Lšœ˜Jšžœžœ $˜NJ˜J˜J˜—J˜—Jšžœ˜—…—é¶.|