ThreeDSurfacesImpl.mesa
Copyright © 1984, 1986 by Xerox Corporation. All rights reserved.
Last Edited by: Crow, December 16, 1986 5:00:42 pm PST
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
Internal Declarations
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 ]
Global Variables
allocation avoidance structures - caches of peculiar data types
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
Utility Procedures
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: BOOLEANIF 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 ANYLIST[ 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;
};
Procedures for Shape Description I/O
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;
Get Surface Type
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;
Get Vertices
{ 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 ];
};
Get Surface
{ keyWord: Rope.ROPEIF 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];
};
Find approximation to bounding sphere
{ 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: BOOLTRUE, normal, color, trans, texture, polyClr: BOOLFALSE] ~ {
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.ROPEIF shape.type = $ConvexPolygon THEN "Polygons" ELSE "Patches";
insideVisible: Rope.ROPEIF shape.insideVisible THEN " InsideVisible" ELSE NIL;
Header
stream.PutRope[ Rope.Cat[fileName, ".shape\n\n"] ];    -- write title on first line
stream.PutRope[ Rope.Cat["SurfaceType ~ ", surfaceType, insideVisible, "\n\n"] ]; -- surface
Vertices
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 ];
Surface
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];
};
Procedures for Transformations and Clipping
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 { 
Put out point if clip plane crossed
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 ANYLIST[
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;
};
Procedures for expansion to polygons
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: ATOMNIL, limit: REAL ← 0.0]
     RETURNS [REF ShapeInstance] ~ {
Expands a whole shape, calling procedures supplied by the surface type
RETURN[ ShapeDo[ context, shape, TRUE, limitType, limit ] ];
};
ShapeSubdivide: PUBLIC PROC[ context: REF Context, shape: REF ShapeInstance,
          limitType: ATOMNIL, limit: REAL ← 0.0]
      RETURNS [REF ShapeInstance] ~ {
Subdivide a whole shape once, calling procedures supplied by the surface type
RETURN[ ShapeDo[ context, shape, FALSE, limitType, limit ] ];
};
ExpandToLines: PROC[ context: REF Context, patch: REF Patch,
        action: PROC[context: REF Context, patch: REF Patch] ] ~ {
expand a patch into curved lines, pass them as "$Paths"
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
PROC[ context: REF Context, patch: REF Patch, limitType: ATOM, limit: REAL, action: PROC];
};
limitInPixels: REAL ← 2.0;
ExpandToConvexPolys: PROC[ context: REF Context, patch: REF Patch,
          action: PROC[context: REF Context, patch: REF Patch] ] ~ {
expand a patch into displayable polygons
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
PROC[ context: REF Context, patch: REF Patch, limitType: ATOM, limit: REAL, action: PROC];
};
RegisterSurfaceType: PUBLIC PROC[ context: REF Context,
           type: ATOM, procs: REF ThreeDSurfaces.PatchProcs ] ~ {
context.props ← Atom.PutPropOnList[context.props, type, procs];
};
Procedures for Shading
BackFacing: PUBLIC PROC[ poly: REF Patch, useEyeSpace: BOOLEANFALSE]
    RETURNS [FacingDir] ~ {
Assumes left-handed space (eye space or screen space)
SELECT poly.type FROM
$ConvexPolygon  => IF useEyeSpace
THEN {
Backfacing test based on first vertex and adjacent vertices
this: VertexInfo ← poly.vtx[0];
next: VertexInfo ← poly.vtx[1];
last: VertexInfo ← poly.vtx[2];
last: VertexInfo ← poly.vtx[poly.nVtces - 1];
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    => { 
Backfacing test based on convex hull being hidden behind its base
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: REALIF 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] ~ {
Calculate shades for Faceted shading (Used for quick display)
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: REALIF 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] ~ {
Compute Normals, Sum normals at polygon corners to get polygon normal
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] ~ {
Sum normals for vertices given by adjacent polygon corners, only for polygons!
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
};
Procedures for Sorting and Display
LoadSortSequence: PUBLIC PROC[ context: REF Context, sortOrder: LIST OF REF ANYNIL ]
      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: BOOLEANFALSE;
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: BOOLEANFALSE ] ~ {
ShowPatch: PROC[p: REF ThreeDSurfaces.ShapePatch] ~{
patch: REF Patch ← ShapePatchToPatch[ context, p ];
OutputPatch[ context, patch ];
};
time: REAL ← CurrentTime[];
log: IO.STREAMNARROW[ Atom.GetPropFromList[context.props, $Log] ];
timing: Rope.ROPE;
shape: REF ThreeDBasics.ShapeSequence ← context.shapes;

IF shape = NIL THEN RETURN[];
Get Everything (including light centroids) into eyespace
FOR i: NAT IN [0.. shape.length) DO
IF Atom.GetPropFromList[shape[i].props, $Hidden] = NIL OR shape[i].type = $Light
THEN IF shape[i].vtcesInValid THEN { 
shape[i].clipState ← ThreeDScenes.XfmToEyeSpace[ context, shape[i] ];
IF shape[i].clipState # out THEN ThreeDScenes.XfmToDisplay[context, shape[i] ];
};
ENDLOOP;
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] ~ {
Make a polygon for each edge and tile it
baseRadius: REAL ← .003;
limit: NATIF 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] ~ { 
Unclipped shape output
ax, ay, bx, by: NAT;
color: SampleSet ← ShapetoColorBytes[context, s];
usingImager: BOOLEANFALSE;
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: NATIF 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: BOOLEANFALSE;
{ 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: NATIF patch.type = $Path THEN patch.nVtces - 1 ELSE patch.nVtces;
FOR j: NAT IN [0..limit] DO
i: NATIF 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: NATIF patch.type = $Path THEN patch.nVtces - 1 ELSE patch.nVtces;
FOR j: NAT IN [0..limit] DO
i: NATIF 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.