ShapeUtilitiesImpl.mesa
Copyright © 1984, 1986 by Xerox Corporation. All rights reserved.
Last Edited by: Crow, March 11, 1989 3:37:26 pm PST
DIRECTORY
Atom     USING [ GetPropFromList, PutPropOnList, PropList ],
Real     USING [ Fix, Round ],
Basics     USING [ BITOR, BITAND ],
BasicTime   USING [ PulsesToSeconds, GetClockPulses ],
Rope     USING [ ROPE, Cat ],
Convert    USING [ RopeFromReal ],
ScanConvert   USING [ justNoticeable ],
G3dVector USING [ Add, Cross, Dot, Length, Mul, Normalize ],
G3dMatrix USING [ Mul, Transform, TransformVec ],
G3dPlane USING [ DistanceToPoint ],
ThreeDBasics  USING [ AllOut, ClipState, Context, Error, FacingDir,
         IntegerSequence, NatSequence, NoneOut, OutCode, Patch,
         PatchSequence, PtrPatchSequence, PtrPatch,
         RealSequence, RGB, RegisterShadingClass,
         RegisterSurfaceType, ScaleAndAddXfm,
         ShadingClass, ShadingSequence, ShadingValue, ShapeClass,
         ShapeInstance, ShapeSequence, ShapeProc, SixSides, Triple,
         TripleSequence, Vertex, VertexInfo, VertexInfoProc,
         VertexInfoSequence, VertexSequence, Xfm3D ],
SurfaceRender  USING [ OutputPolygon, RopeDisplay, ValidatePolyhedron,
         ValidateRopeShape ],
ShapeUtilities  USING [ ShapePatch ];
ShapeUtilitiesImpl: CEDAR MONITOR
IMPORTS Atom, Basics, BasicTime, Convert, G3dPlane, G3dMatrix, Real, Rope, SurfaceRender, ThreeDBasics, G3dVector
EXPORTS ShapeUtilities
~ BEGIN
Internal Declarations
Context: TYPE ~ ThreeDBasics.Context;
RGB: TYPE ~ ThreeDBasics.RGB;          --  [ r, g, b: REAL];
SixSides: TYPE ~ ThreeDBasics.SixSides;
ScaleAndAddXfm: TYPE ~ ThreeDBasics.ScaleAndAddXfm;
OutCode: TYPE ~ ThreeDBasics.OutCode;
NoneOut: OutCode ~ ThreeDBasics.NoneOut;
AllOut: OutCode ~ ThreeDBasics.AllOut;
Xfm3D: TYPE ~ ThreeDBasics.Xfm3D;
Triple: TYPE ~ ThreeDBasics.Triple;
TripleSequence: TYPE ~ ThreeDBasics.TripleSequence;
NatSequence: TYPE ~ ThreeDBasics.NatSequence;
IntegerSequence: TYPE ~ ThreeDBasics.IntegerSequence;
RealSequence: TYPE ~ ThreeDBasics.RealSequence;
ShapeInstance: TYPE ~ ThreeDBasics.ShapeInstance;
FacingDir: TYPE ~ ThreeDBasics.FacingDir;
Patch: TYPE ~ ThreeDBasics.Patch;
PatchSequence: TYPE ~ ThreeDBasics.PatchSequence;
PtrPatch: TYPE ~ ThreeDBasics.PtrPatch;
PtrPatchSequence: TYPE ~ ThreeDBasics.PtrPatchSequence;
ShapePatch: TYPE ~ ShapeUtilities.ShapePatch;
Vertex: TYPE ~ ThreeDBasics.Vertex;
VertexSequence: TYPE ~ ThreeDBasics.VertexSequence;
VertexInfo: TYPE ~ ThreeDBasics.VertexInfo;
VertexInfoSequence: TYPE ~ ThreeDBasics.VertexInfoSequence;
VertexInfoProc: TYPE ~ ThreeDBasics.VertexInfoProc;
ShadingValue: TYPE ~ ThreeDBasics.ShadingValue;
ShadingSequence: TYPE ~ ThreeDBasics.ShadingSequence;
ShapeClass: TYPE ~ ThreeDBasics.ShapeClass;
ShadingClass: TYPE ~ ThreeDBasics.ShadingClass;
ShapeProc: TYPE ~ ThreeDBasics.ShapeProc;  -- PROC[ Context, ShapeInstance ]
LORA: TYPE ~ LIST OF REF ANY;
Renamed Procedures
Transform: PROC[p: Triple, mat: Xfm3D] RETURNS[Triple] ~ G3dMatrix.Transform;
TransformVec: PROC[vec: Triple, mat: Xfm3D] RETURNS[Triple] ~
                  G3dMatrix.TransformVec;
GetProp: PROC [propList: Atom.PropList, prop: REF ANY] RETURNS [REF ANY] ~
                     Atom.GetPropFromList;
PutProp: PROC [propList: Atom.PropList, prop: REF ANY, val: REF ANY]
   RETURNS
[Atom.PropList] ~ Atom.PutPropOnList;
Global Variables
nullPtr: INT ~ 0;    -- handy name for zero in sort sequences
nullTriple: Triple ← [0.0, 0.0, 0.0];
defaultWhite: RGB ← [1.0, 1.0, 1.0];
Caching Procedures
allocation avoidance structures - caches of peculiar data types
vertexStore: REF VertexInfoSequence ← NEW[ VertexInfoSequence[96] ]; -- Vertex Cache
vertexStoreLength: NAT ← 96;
vertexStorePtr: NAT ← 0;        -- place to return next free record
GetVertexInfo: PUBLIC ENTRY PROC[] RETURNS[REF VertexInfo] ~ {
ENABLE UNWIND => NULL;
vtx: REF VertexInfo;
IF vertexStorePtr = 0
THEN vtx ← NEW[VertexInfo]
ELSE {
vertexStorePtr ← vertexStorePtr - 1;
vtx ← vertexStore[vertexStorePtr];
vertexStore[vertexStorePtr] ← NIL;
};
vtx.aux ← vtx.props ← NIL;
RETURN[ vtx ];
};
ReleaseVertexInfo: PUBLIC ENTRY PROC[vtx: REF VertexInfo] ~ {
ENABLE UNWIND => NULL;
IF vertexStorePtr = vertexStoreLength THEN {
vertexStore ← NEW[ VertexInfoSequence[vertexStoreLength + 32] ];
vertexStoreLength ← vertexStoreLength + 32;
vertexStorePtr ← 0;
};
IF vertexStorePtr > 0 AND vertexStore[vertexStorePtr-1] = vtx
THEN SIGNAL ThreeDBasics.Error[[$MisMatch, "Double vertexInfo release"]]
ELSE vertexStore[vertexStorePtr] ← vtx;
vertexStorePtr ← vertexStorePtr + 1;
};
patchCache: REF PatchSequence ← NEW[ PatchSequence[16] ];  -- temps for clipping, etc.
patchCacheLength: NAT ← 16;
patchCachePtr: NAT ← 0;        -- place to return next free record
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;
};
IF patchCachePtr > 0 AND patchCache[patchCachePtr-1] = p
THEN SIGNAL ThreeDBasics.Error[[$MisMatch, "Double patch release"]]
ELSE patchCache[patchCachePtr] ← p;
patchCachePtr ← patchCachePtr + 1;
};
Utility Procedures
Sgn: PROCEDURE [number: REAL] RETURNS [INT] ~ INLINE {
IF number < 0. THEN RETURN[-1] ELSE RETURN[1];
};
Ceiling: PROC[number: REAL] RETURNS[result: INTEGER] ~ {
result ← Real.Round[number];
IF result < number THEN result ← result + 1;
};
ElapsedTime: PROC[startTime: REAL] RETURNS[Rope.ROPE] ~ {
timeX10: REAL ← 10.0 * (BasicTime.PulsesToSeconds[BasicTime.GetClockPulses[]] - startTime);
RETURN[ Rope.Cat[ Convert.RopeFromReal[ Real.Fix[timeX10] / 10.0 ], " secs. " ] ];
};
CurrentTime: PROC[] RETURNS[REAL] ~ {
RETURN[ BasicTime.PulsesToSeconds[BasicTime.GetClockPulses[]] ];
};
DiffPosns: PROC[vtx1, vtx2: REF Vertex] RETURNS[Triple] ~ {
RETURN[[vtx1.x - vtx2.x, vtx1.y - vtx2.y, vtx1.z - vtx2.z]] };
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 ← G3dVector.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]] ]
];
};
HoldEverything: PROCEDURE [] ~ {
ERROR ABORTED;
};
ShapePatchToPatch: PUBLIC PROC[context: REF Context, sPatch: REF ShapePatch]
       RETURNS
[patch: REF Patch] ~ {
ptrPatch: REF PtrPatch ←
  NARROW
[sPatch.shape.surface, REF PtrPatchSequence][sPatch.patch];
auxData: REF ← GetProp[ sPatch.shape.shadingProps, $AuxiliaryVtxData ];
shapeColor: RGB ← sPatch.shape.shadingClass.color;
shapeTransmittance: REAL ← sPatch.shape.shadingClass.transmittance;
faceted: BOOLEAN ← sPatch.shape.shadingClass.shadingType = $Faceted
      AND sPatch.shape.class.type = $ConvexPolygon;
lines: BOOLEAN ← sPatch.shape.shadingClass.shadingType = $Lines
     OR sPatch.shape.shadingClass.shadingType = $HiddenLines;
patchInfo: REF ThreeDBasics.ShadingSequence ← sPatch.shape.shadingClass.patchShade;
coloredPatches: BOOLEANIF NOT faceted
THEN  GetProp[ sPatch.shape.fixedProps, $PatchColorsInFile ] # NIL
  OR
GetProp[ sPatch.shape.fixedProps, $PatchTransmittancesInFile ] # 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 ← sPatch.shape.class.type;    -- take type from class
patch.oneSided ← IF NOT ptrPatch.oneSided THEN FALSE ELSE (shapeTransmittance = 0.0);
patch.dir ← ptrPatch.dir;
Put shape & patch number on property list
patch.props ← PutProp[ ptrPatch.props, $Shape, sPatch.shape ];
patch.props ← PutProp[ patch.props, $PatchNo, NEW[NAT ← sPatch.patch] ];
FOR i: NAT IN [0..ptrPatch.nVtces) DO
j: NAT ← ptrPatch.vtxPtr[i];
patch[i].props ← patch.props;    -- pass info through in case needed
patch[i].coord ← sPatch.shape.vertex[j]^;
patch[i].shade ← sPatch.shape.shade[j]^;
IF auxData # NIL
THEN {
data: LORALIST[ auxData, NEW[INTEGER ← j] ];
patch[i] ← sPatch.shape.shadingClass.loadVtxAux[context, patch[i], data];
}
ELSE patch[i].aux ← NIL;
IF lines
THEN {            -- unshaded lines use shape color
patch[i].shade.er ← shapeColor.R;
patch[i].shade.eg ← shapeColor.G;
patch[i].shade.eb ← shapeColor.B;
}
ELSE IF patchInfo # NIL THEN IF faceted     -- shades for individual patches
THEN patch[i].shade ← patchInfo[sPatch.patch]^ -- faceted, take patch shade
ELSE IF coloredPatches THEN {    -- smooth, combine vtx and patch shades
patch[i].shade.r ← sPatch.shape.shade[j].r * patchInfo[sPatch.patch].r;
patch[i].shade.g ← sPatch.shape.shade[j].g * patchInfo[sPatch.patch].g;
patch[i].shade.b ← sPatch.shape.shade[j].b * patchInfo[sPatch.patch].b;
patch[i].shade.t ← sPatch.shape.shade[j].t * patchInfo[sPatch.patch].t;
patch[i] ← sPatch.shape.shadingClass.shadeVtx[
context, patch[i], sPatch.shape.shadingClass
];
};
ENDLOOP;
};
Procedures for Manipulating Shapes
InitClasses: PROC[] ~ {    -- register procedures for basic surface types
standardClass: ShapeClass ← [
type: $Light,
display: NIL,
displayPatch: NIL
];
defaultShadingClass: ShadingClass ← [  -- procs for standard shading (no texture)
type: $Default,
shadingType: $Faceted,
shadeVtx: ShadeVtx
];
ThreeDBasics.RegisterSurfaceType[standardClass, $Light]; -- placeholder class for light source
standardClass.type ← $ConvexPolygon;
standardClass.validate ← SurfaceRender.ValidatePolyhedron;
standardClass.displayPatch ← SurfaceRender.OutputPolygon;
ThreeDBasics.RegisterSurfaceType[standardClass, $ConvexPolygon]; -- ConvexPolygon procs
standardClass.type ← $RopeShape;
standardClass.validate ← SurfaceRender.ValidateRopeShape;
standardClass.displayPatch ← SurfaceRender.RopeDisplay;
ThreeDBasics.RegisterSurfaceType[standardClass, $RopeShape]; -- RopeShape procs
ThreeDBasics.RegisterShadingClass[defaultShadingClass, $Default];
defaultShadingClass.type ← $NoShading;
defaultShadingClass.shadingType ← $Faceted;
defaultShadingClass.shadeVtx ← NoShadeVtx;
ThreeDBasics.RegisterShadingClass[defaultShadingClass, $NoShading];
};
XfmToEyeSpace: PUBLIC PROC[context: REF Context, shape: REF ShapeInstance]
  RETURNS
[ThreeDBasics.ClipState] ~ {
Transform Vertices and Centroid to Eye Space, calculate clip codes at vertices
ClipBoundingBall: PROC[] RETURNS[ThreeDBasics.ClipState] ~ {
Do gross clip test on bounding sphere, all in or all out allow rejection of entire object
clipFlag: BOOLEANFALSE;
FOR plane: SixSides IN SixSides DO
distance: REAL ← G3dPlane.DistanceToPoint[
[shape.centroid.ex, shape.centroid.ey, shape.centroid.ez],
context.clippingPlanes[plane]
];
IF distance < -shape.boundingRadius THEN RETURN[out]
ELSE IF distance < shape.boundingRadius THEN clipFlag ← TRUE;
ENDLOOP;
IF clipFlag THEN RETURN[clipped] ELSE RETURN[in];
};
xfm: Xfm3D ← G3dMatrix.Mul[shape.position, context.eyeSpaceXfm];
[[shape.centroid.ex, shape.centroid.ey, shape.centroid.ez]] ← Transform[
[shape.centroid.x, shape.centroid.y, shape.centroid.z],   -- Update shape centroid
xfm
];
shape.clipState ← ClipBoundingBall[];
IF shape.clipState # out THEN {-- run through vertices and shading and transform
andOfCodes: OutCode ← AllOut;     -- test for trivially out
orOfCodes: OutCode ← NoneOut;     -- test for trivially in
IF shape.vertex # NIL THEN FOR i: NAT IN [0..shape.vertex.length) DO
IF shape.vertex[i] # NIL THEN {
OPEN shape.vertex[i];
[ [ex, ey, ez] ] ← Transform[ [x, y, z] , xfm]; -- transform pts to eyespace
IF shape.clipState # in
THEN {
clip ← GetClipCodeForPt[ context, [ex, ey, ez] ];
orOfCodes ← LOOPHOLE[
Basics.BITOR[LOOPHOLE[orOfCodes], LOOPHOLE[ clip] ], OutCode];
andOfCodes ← LOOPHOLE[
Basics.BITAND[ LOOPHOLE[andOfCodes], LOOPHOLE[ clip] ], OutCode];
}
ELSE clip ← NoneOut;
};
ENDLOOP;
IF orOfCodes = NoneOut  THEN shape.clipState ← in
ELSE IF andOfCodes # NoneOut THEN shape.clipState ← out;
};
RETURN[shape.clipState];
};
XfmToDisplay: PUBLIC PROC[ context: REF Context, shape: REF ShapeInstance,
         getBox: BOOLFALSE ] ~ {
Transform all vertices for a shape from eyespace to display coordinates
xMin, yMin: REAL ← 32767.0;
xMax, yMax: REAL ← 0.0;
bboxNeeded: BOOLEAN ← context.antiAliasing OR getBox;
run through vertices and transform
IF shape.vertex # NIL THEN FOR i: NAT IN [0..shape.vertex.length) DO
IF shape.vertex[i] # NIL THEN {
OPEN shape.vertex[i];
IF clip = NoneOut THEN {
[ [sx, sy, sz] ] ← XfmTripleToDisplay[
pt: [ex, ey, ez],
xfm: context.eyeToNdc,
display: context.ndcToPixels,
offset: IF context.antiAliasing THEN .5 ELSE 0.0 -- nojaggy tiler offsets by 1/2 pixel
];
IF bboxNeeded THEN {
IF sx < xMin THEN xMin ← sx; IF sy < yMin THEN yMin ← sy;
IF sx > xMax THEN xMax ← sx; IF sy > yMax THEN yMax ← sy;
};
}
ELSE IF bboxNeeded THEN {
IF clip.left THEN xMin ← 0.0;  
IF clip.right THEN xMax ← context.viewPort.w;
IF clip.top THEN yMin ← 0.0;
IF clip.bottom THEN yMax ← context.viewPort.h;
};
};
ENDLOOP;
IF bboxNeeded THEN {
Expand extent by two pixels, NOTE!! this is not complete in the presence of clipping, doesn't pick up clipped vertices
xMin ← MAX[0.0, xMin-2.0]; xMax ← MIN[context.viewPort.w, xMax+2.0];
yMin ← MAX[0.0, yMin-2.0]; yMax ← MIN[context.viewPort.h, yMax+2.0];
shape.screenExtent ← [ min: [f: Real.Fix[xMin], s: Real.Fix[yMin]],
       max: [f: Ceiling[xMax], s: Ceiling[yMax]] ];
};
};
GetPolyInfo: PROC[context: REF Context, shape: REF ShapeInstance] ~ {
Compute Normals, Sum normals at polygon corners to get polygon normal
surface: REF PtrPatchSequence;
xfm: Xfm3D;
preNormaled: BOOLEAN ← GetProp[ shape.fixedProps, $PatchNormalsInFile] # NIL;
polyShade: REF ShadingSequence ← shape.shadingClass.patchShade;
IF shape.surface = NIL THEN RETURN;   -- not a shape (probably a light source)
IF shape.class.type # $ConvexPolygon THEN {
SIGNAL ThreeDBasics.Error[[$MisMatch, "Operation only for polygons"]];
RETURN[];
};
IF polyShade = NIL THEN {
polyShade ← NEW[ ShadingSequence[shape.numSurfaces] ];
polyShade.length ← shape.numSurfaces;
};
surface ← NARROW[shape.surface, REF PtrPatchSequence];
IF NOT shape.vtcesInValid THEN xfm ← G3dMatrix.Mul[shape.position, context.eyeSpaceXfm];
FOR i: NAT IN [0..shape.numSurfaces) DO
IF surface[i] # NIL THEN {
sumNmls: Triple ← [0., 0., 0.];
IF polyShade[i] = NIL THEN polyShade[i] ← NEW[ ThreeDBasics.ShadingValue ];
IF NOT preNormaled THEN {
FOR cVtx: NAT IN [0..surface[i].nVtces) DO
sumNmls ← G3dVector.Add[ sumNmls, GetNormal[shape.vertex, surface[i], cVtx] ];
ENDLOOP;
sumNmls ← G3dVector.Normalize[sumNmls];
polyShade[i].xn ← sumNmls.x;
polyShade[i].yn ← sumNmls.y;
polyShade[i].zn ← sumNmls.z;
IF NOT shape.vtcesInValid THEN { -- if vertices already transformed to eyespace
OPEN polyShade[i];          -- transform normal vectors
[ [exn, eyn, ezn] ] ← TransformVec[ [xn, yn, zn] , xfm];
};
};
};
ENDLOOP;
shape.shadingProps ← PutProp[shape.shadingProps, $PolygonInfoComputed, $ok];
};
GetPolyShades: 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;
shapeColor: RGB ← shape.shadingClass.color;
shapeTransmittance: REAL ← shape.shadingClass.transmittance;
polyShade: REF ShadingSequence ← shape.shadingClass.patchShade;
IF shape.class.type # $ConvexPolygon THEN RETURN; -- patches, etc. shaded after expansion
IF shape.surface = NIL OR shape.shadingClass.shadingType # $Faceted THEN {
SIGNAL ThreeDBasics.Error[[$Condition, "Data missing for faceted shading"]];
RETURN;
};
IF GetProp[ shape.shadingProps, $PolygonInfoComputed] = NIL THEN {
IF polyShade = NIL THEN {
polyShade ← NEW[ ShadingSequence[shape.numSurfaces] ];
polyShade.length ← shape.numSurfaces;
FOR i: NAT IN [0..shape.numSurfaces) DO
polyShade[i] ← NEW[ ShadingValue ];
ENDLOOP;
shape.shadingClass.patchShade ← polyShade;
};
GetPolyInfo[context, shape];
};
poly ← NARROW[ shape.surface, REF PtrPatchSequence ];
FOR i: NAT IN [0..shape.numSurfaces) DO
IF poly[i] # NIL THEN {
vtx: Vertex ← AverageVertices[poly[i]];
pt: VertexInfo ← [ vtx, polyShade[i]^, NIL ];
pt ← shape.shadingClass.shadeVtx[ context, pt, shape.shadingClass ]; -- calculate shade
polyShade[i].er ← pt.shade.er;
polyShade[i].eg ← pt.shade.eg;
polyShade[i].eb ← pt.shade.eb;
polyShade[i].et ← pt.shade.et;
};
ENDLOOP;
};
GetVtxNmls: PUBLIC PROC[context: REF Context, shape: REF ShapeInstance] ~ {
Sum normals for vertices given by adjacent polygon corners, only for polygons!
surface: REF PtrPatchSequence ← NARROW[shape.surface];
preNormaled: BOOLEAN ← GetProp[ shape.fixedProps, $VertexNormalsInFile ] # NIL;
IF shape.shade = NIL THEN {
shape.shade ← NEW[ ThreeDBasics.ShadingSequence[shape.vertex.length] ];
shape.shade.length ← shape.vertex.length;
};
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;  -- debugging aid
};
ENDLOOP;
IF NOT preNormaled THEN { -- get vertex normal
xfm: Xfm3D ← G3dMatrix.Mul[shape.position, context.eyeSpaceXfm];
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]] ← G3dVector.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];
IF G3dVector.Length[ [xn, yn, zn] ] > shape.boundingRadius * .0001
THEN {
[[xn, yn, zn]] ← G3dVector.Normalize[ [xn, yn, zn] ];
[[exn, eyn, ezn]] ← TransformVec[ [xn, yn, zn] , xfm];
}
ELSE {
[xn, yn, zn] ← [exn, eyn, ezn] ← nullTriple;
};
};
ENDLOOP;
};
shape.shadingProps ← PutProp[shape.shadingProps, $VtxInfoComputed, $ok];
};
GetVtxShades: PUBLIC PROC[ context: REF Context, shape: REF ShapeInstance] ~ {
tmpShininess: REAL;
IF shape.shadingClass # NIL THEN {  -- cache highlight power, no highlights here please
tmpShininess ← shape.shadingClass.shininess; shape.shadingClass.shininess ← 0.0;
};
IF shape.shade # NIL THEN FOR i: NAT IN [0..shape.shade.length) DO
IF shape.shade[i] # NIL THEN {
pt: VertexInfo ← [ coord: shape.vertex[i]^, shade: shape.shade[i]^ ];
pt ← shape.shadingClass.shadeVtx[context, pt, shape.shadingClass];
shape.shade[i].er ← pt.shade.er;
shape.shade[i].eg ← pt.shade.eg;
shape.shade[i].eb ← pt.shade.eb;
shape.shade[i].et ← pt.shade.et;
};
ENDLOOP;
IF shape.shadingClass # NIL THEN shape.shadingClass.shininess ← tmpShininess;
};
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[ G3dPlane.DistanceToPoint[
[vtx.ex, vtx.ey, vtx.ez],
context.clippingPlanes[side]
] ];
};
lastDist, dist: REAL; outCnt, last: NAT;
IF pIn.nVtces < 2 THEN RETURN[ pIn, pOut ]; -- return if degenerate (line needs 2)
outCnt ← 0;
IF pIn.type # $PolyLine 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 # $PolyLine) 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 pIn.vtx[i].aux # NIL AND pIn.vtx[last].aux # NIL
THEN {
data: LORALIST[
pIn.vtx[i].aux, pIn.vtx[last].aux, NEW[REAL ← a], NEW[REAL ← b]
];
pOut.vtx[outCnt] ← lerpProc[ context, 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
shape: REF ShapeInstance ← NARROW[ GetProp[poly.props, $Shape] ];
lerpProc: VertexInfoProc ← shape.shadingClass.lerpVtxAux;
orOfCodes: OutCode ← NoneOut;
poly2: REF Patch ← GetPatch[2 * poly.nVtces];  -- get temp patch, released below
IF poly.type # $ConvexPolygon AND poly.type # $PolyLine THEN {
SIGNAL ThreeDBasics.Error[[$Unimplemented, "Not clippable as polygon"]];
RETURN[ NIL ];
};
FOR i: NAT IN [0..poly.nVtces) DO
orOfCodes ← LOOPHOLE[
Basics.BITOR[LOOPHOLE[orOfCodes], LOOPHOLE[poly.vtx[i].coord.clip]],
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: OutCode ← NoneOut;
andOfCodes: OutCode ← AllOut;
FOR i: NAT IN [0..patch.nVtces) DO
orOfCodes ← LOOPHOLE[
Basics.BITOR[ LOOPHOLE[orOfCodes], LOOPHOLE[patch[i].coord.clip]],
OutCode];
andOfCodes ← LOOPHOLE[
Basics.BITAND[LOOPHOLE[andOfCodes], LOOPHOLE[patch[i].coord.clip]],
OutCode];
ENDLOOP;
IF andOfCodes # NoneOut
THEN patch.clipState ← out
ELSE IF orOfCodes = NoneOut
THEN patch.clipState ← in
ELSE patch.clipState ← clipped;
};
GetClipCodeForPt: PUBLIC PROC[context: REF Context, pt: Triple] RETURNS[clip: OutCode] ~ {
Compute outcode for one set of coordinates in eyespace
clip.bottom← G3dPlane.DistanceToPoint[ pt, context.clippingPlanes[Bottom]] < 0.;
clip.top ← G3dPlane.DistanceToPoint[ pt, context.clippingPlanes[Top] ] < 0.;
clip.left ← G3dPlane.DistanceToPoint[ pt, context.clippingPlanes[Left] ] < 0.;
clip.right ← G3dPlane.DistanceToPoint[ pt, context.clippingPlanes[Right] ] < 0.;
clip.near ← G3dPlane.DistanceToPoint[ pt, context.clippingPlanes[Near] ] < 0.;
clip.far ← G3dPlane.DistanceToPoint[ pt, context.clippingPlanes[Far] ] < 0.;
};
XfmPtToEyeSpace: PUBLIC PROC[context: REF Context, pt: Triple, xfm: Xfm3D ← NIL]
      RETURNS[Triple, OutCode] ~ {
 Transform Vertex to Eye Space
IF xfm = NIL THEN xfm ← context.eyeSpaceXfm;
pt ← Transform[ pt, xfm ];
RETURN[ pt, GetClipCodeForPt[context, pt] ];
};
XfmTripleToDisplay: PUBLIC PROC[pt: Triple, xfm, display: ScaleAndAddXfm, offset: REAL]
       RETURNS[result: Triple] ~ {
 Transform vertex from eyespace to display coordinates - local utility
aLilBit: REAL ← ScanConvert.justNoticeable * ScanConvert.justNoticeable;
IF pt.z <= 0.0 THEN {
SIGNAL ThreeDBasics.Error[[$MisMatch, "Negative depth"]];
pt.z ← .001;  -- fudge bad depths
};
result.x ← xfm.scaleX*pt.x/pt.z + xfm.addX;    -- convert to normalized display coords
result.y ← xfm.scaleY*pt.y/pt.z + xfm.addY;
result.z ← xfm.scaleZ/pt.z + xfm.addZ;
result.x ← display.scaleX * result.x + display.addX;  -- convert to screen coordinates
result.y ← display.scaleY * result.y + display.addY;
result.z ← display.scaleZ * result.z + display.addZ;
result.x ← result.x - offset;  -- nojaggy tiler offsets by 1/2 pixel and spreads out by 1
result.y ← result.y - offset;
RETURN [ result ];
};
XfmPtToDisplay: PUBLIC PROC[context: REF Context, pt: Triple,
          shape: REF ShapeInstance ← NIL]
       RETURNS[Triple] ~ {
 Transform vertex from eyespace to display coordinates
result: Triple ← XfmTripleToDisplay[
pt: pt,
xfm: context.eyeToNdc,
display: context.ndcToPixels,
offset: IF context.antiAliasing THEN .5 ELSE 0.0   -- nojaggy tiler offsets by 1/2 pixel
];
IF shape # NIL THEN {
xLo: NAT ← Real.Fix[ MAX[0.0, result.x - 2.0] ];
xHi: NAT ← Ceiling[ MIN[context.viewPort.w, result.x + 2.0] ];
yLo: NAT ← Real.Fix[ MAX[0.0, result.y - 2.0] ];
yHi: NAT ← Ceiling[ MIN[context.viewPort.h, result.y + 2.0] ];
IF shape.screenExtent.min.f > xLo THEN shape.screenExtent.min.f ← xLo;
IF shape.screenExtent.max.f < xHi THEN shape.screenExtent.max.f ← xHi;
IF shape.screenExtent.min.s > yLo THEN shape.screenExtent.min.s ← yLo;
IF shape.screenExtent.max.s < yHi THEN shape.screenExtent.max.s ← yHi;
};
RETURN [ result ];
};
Procedures for Shading Patches
BackFacing: PUBLIC PROC[ context: REF Context, 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 ← G3dVector.Normalize[G3dVector.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 ← G3dVector.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 (left-handed)
  ( 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] );
zNorm ← zNorm *Sgn[context.ndcToPixels.scaleY] *Sgn[context.ndcToPixels.scaleX];
Adjusts for flip in screen-space transform (ndcToPixels) in y and/or x
IF zNorm > 0 THEN RETURN[ back ] ELSE IF zNorm < 0 THEN RETURN[ front ];
ENDLOOP;
SIGNAL ThreeDBasics.Error[[$Condition, "Edges too small for stable arithmetic"]];
};
$Bezier    => { 
Backfacing test based on convex hull being hidden behind its base
SIGNAL ThreeDBasics.Error[[$Unimplemented, "Backfacing for patches not done"]];
};
ENDCASE => SIGNAL ThreeDBasics.Error[[$Unimplemented, "Unknown type"]];
RETURN[ undetermined ];
};
ShadePoly: PUBLIC PROC[ context: REF Context, poly: REF Patch] ~ {
shape: REF ShapeInstance ← NARROW[ GetProp[poly.props, $Shape] ];
IF shape.shadingClass.shadingType # $HiddenLines THEN FOR i: NAT IN [0..poly.nVtces) DO
IF shape.shadingClass.shadingType = $Faceted THEN { -- get 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 ]] ← G3dVector.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[i] ← shape.shadingClass.shadeVtx[ context, poly[i], shape.shadingClass ];
ENDLOOP;
};
GetAmbientLight: PROC[context: REF Context, normal: Triple] RETURNS[ambnt: RGB] ~ {
Get an ambient light value from the eyespace normal to the surface
IF context = NIL OR context.environment = NIL THEN RETURN[[.2, .2, .2]];
WITH GetProp[context.environment, $AmbientLight] SELECT FROM
clr: REF RGB => ambnt ← clr^;
light: REF ShapeInstance => {  -- light must be far away, treated as simple direction
dotNL: REAL ← G3dVector.Dot[
G3dVector.Normalize[ [light.centroid.ex, light.centroid.ey, light.centroid.ez] ],
G3dVector.Normalize[ normal ]
];
dotNL ← (dotNL + 1.0) / 2.0;   -- range ambient light over shadowed portions too
ambnt ← light.shadingClass.color;
ambnt.R ← ambnt.R*dotNL; ambnt.G ← ambnt.G*dotNL; ambnt.B ← ambnt.B*dotNL;
};
ENDCASE => ambnt ← [.2, .2, .2];
};
NoShadeVtx: ThreeDBasics.VertexInfoProc ~ {
shadingClass: REF ShadingClass ← NARROW[data];
shapeClr: RGBIF shadingClass # NIL THEN shadingClass.color ELSE defaultWhite;
shapeTrans: REALIF shadingClass # NIL THEN shadingClass.transmittance ELSE 0.0;
vtx.shade.er ← vtx.shade.r * shapeClr.R;
vtx.shade.eg ← vtx.shade.g * shapeClr.G;
vtx.shade.eb ← vtx.shade.b * shapeClr.B;
IF shapeTrans > 0.0 THEN {      -- compute transmittance if transparent
vtx.shade.et ← vtx.shade.t * shapeTrans;        -- Transmittance
vtx.shade.et ← MAX[0.0, MIN[vtx.shade.et, 1.]];
};
RETURN[vtx];  -- avoids shading calculations for background polygons, shadows, etc.
};
ShadeVtx: PUBLIC ThreeDBasics.VertexInfoProc ~ {
PROC[ context: REF Context, vtx: VertexInfo, data: REF ANYNIL ] RETURNS[VertexInfo]
Calculate shade at vertices of polygon
shadingClass: REF ShadingClass ← NARROW[data];
shapeClr: RGBIF shadingClass # NIL THEN shadingClass.color ELSE defaultWhite;
shapeTrans: REALIF shadingClass # NIL THEN shadingClass.transmittance ELSE 0.0;
shininess: REALIF shadingClass # NIL THEN shadingClass.shininess ELSE 0.0;
shinyPwr: NAT ← Real.Round[shininess];
partShiny: REAL ← 1.0;
toLightSrc, toEye: Triple;
dotNL, dotNE, sumHilite: REAL ← 0.0;
ambient, diffuse, specular, result: RGB ← [0.0, 0.0, 0.0];
vtxClr: RGB ← [vtx.shade.r * shapeClr.R, vtx.shade.g * shapeClr.G, vtx.shade.b * shapeClr.B];
IF vtx.props # NIL THEN {
ref: REF ← GetProp[vtx.props, $PartShiny];
IF ref # NIL THEN partShiny ← NARROW[ref, REF REAL]^;
};
toEye ← G3dVector.Normalize[[-vtx.coord.ex, -vtx.coord.ey, -vtx.coord.ez]]; -- direction to eye
[ [vtx.shade.exn, vtx.shade.eyn, vtx.shade.ezn] ] ← G3dVector.Normalize[
[vtx.shade.exn, vtx.shade.eyn, vtx.shade.ezn]    -- often not normalized
];
Get ambient component of light
ambient ← GetAmbientLight[ context, [vtx.shade.exn, vtx.shade.eyn, vtx.shade.ezn] ];
ambient.R ← ambient.R * vtxClr.R;
ambient.G ← ambient.G * vtxClr.G;
ambient.B ← ambient.B * vtxClr.B;
IF context.lightSources # NIL THEN FOR i: NAT IN [0..context.lightSources.length) DO
Do for each light source
lightClr: RGB ← context.lightSources[i].shadingClass.color;
Get Light Direction from Surface
toLightSrc ← G3dVector.Normalize[ [    -- vector to light source from surface vtx.
context.lightSources[i].centroid.ex - vtx.coord.ex,
context.lightSources[i].centroid.ey - vtx.coord.ey,
context.lightSources[i].centroid.ez - vtx.coord.ez
] ];
Get Light Strength
IF context.lightSources[i].orientation # [0.0, 0.0, 0.0] THEN {   -- spotlight, get direction
dotLS, intensity: REAL;
shineDirection: Triple ← TransformVec[ context.lightSources[i].orientation,
               context.eyeSpaceXfm ];
spotSpread: NAT ← Real.Fix[ context.lightSources[i].shadingClass.shininess ];
dotLS ← -G3dVector.Dot[toLightSrc, shineDirection];
IF dotLS > 0. THEN {        -- compute spotlight factor
binaryCount: NAT ← spotSpread;
intensity ← 1.;
WHILE binaryCount > 0 DO    -- compute power by repeated squares
IF (binaryCount MOD 2) = 1 THEN intensity ← intensity*dotLS;
dotLS ← dotLS*dotLS;
binaryCount ← binaryCount/2;
ENDLOOP;
}
ELSE intensity ← 0.;
IF intensity < ScanConvert.justNoticeable THEN LOOP; -- no effect, skip this light 
lightClr.R ← lightClr.R*intensity;
lightClr.G ← lightClr.G*intensity;
lightClr.B ← lightClr.B*intensity;
};
Get Basic Lambertian Shade
dotNL ← G3dVector.Dot[toLightSrc, [vtx.shade.exn, vtx.shade.eyn, vtx.shade.ezn]];
IF dotNL <= 0. THEN LOOP;       -- surface faces away from light, skip
diffuse.R ← (1. - ambient.R) * dotNL * lightClr.R * vtxClr.R; -- surface facing the light
diffuse.G ← (1. - ambient.G) * dotNL * lightClr.G * vtxClr.G;
diffuse.B ← (1. - ambient.B) * dotNL * lightClr.B * vtxClr.B;
Get Highlight Contribution
IF shinyPwr > 0 AND partShiny > 0.0 THEN {   -- compute Phong specular component
pctHilite: REAL ← 0.0;
halfWay: Triple ← G3dVector.Normalize[  -- normalized average of vectors
G3dVector.Mul[ G3dVector.Add[toEye, toLightSrc], 0.5 ]
];
dotNormHalfWay: REAL ← G3dVector.Dot[ -- cos angle betw. normal and average
[vtx.shade.exn, vtx.shade.eyn, vtx.shade.ezn],
halfWay
];
IF dotNormHalfWay > 0. THEN {
binaryCount: NAT ← shinyPwr;
pctHilite ← partShiny;
WHILE binaryCount > 0 DO    -- compute power by repeated squares
IF (binaryCount MOD 2) = 1 THEN pctHilite ← pctHilite*dotNormHalfWay;
dotNormHalfWay ← dotNormHalfWay*dotNormHalfWay;
binaryCount ← binaryCount/2;
ENDLOOP;
IF pctHilite < 0.0 OR pctHilite > 1.0
THEN SIGNAL ThreeDBasics.Error[[$MisMatch, "Highlight error"]];
};
Add in Highlight, based on headroom left after diffuse and ambient light included
specular.R ← (1.0 - diffuse.R - ambient.R) * pctHilite * lightClr.R;
specular.G ← (1.0 - diffuse.G - ambient.G) * pctHilite * lightClr.G;
specular.B ← (1.0 - diffuse.B - ambient.B) * pctHilite * lightClr.B;
sumHilite ← sumHilite + pctHilite;
};
Accumulate diffuse and specular contributions from each light
result.R ← result.R + diffuse.R + specular.R;
result.G ← result.G + diffuse.G + specular.G;
result.B ← result.B + diffuse.B + specular.B;
ENDLOOP;        -- end loop for each light source
result.R ← result.R + ambient.R;   -- add in ambient light
result.G ← result.G + ambient.G;
result.B ← result.B + ambient.B;
vtx.shade.er ← MAX[0.0, MIN[result.R, 1.]];
vtx.shade.eg ← MAX[0.0, MIN[result.G, 1.]];
vtx.shade.eb ← MAX[0.0, MIN[result.B, 1.]];
IF shapeTrans > 0.0
THEN {      -- compute transmittance if transparent
Transmittance is cosine of angle between to eye and normal (modified for effect)
dotNE ← G3dVector.Dot[toEye, [vtx.shade.exn, vtx.shade.eyn, vtx.shade.ezn]];
dotNE ← 1.0 - ABS[dotNE]; dotNE ← 1.0 - (dotNE * dotNE); -- invert, square, invert
vtx.shade.et ← dotNE * vtx.shade.t * shapeTrans; -- Transmittance as seen from eyepoint
vtx.shade.et ← MIN[1.0 - sumHilite, vtx.shade.et];   -- make highlights more opaque
vtx.shade.et ← MAX[0.0, MIN[vtx.shade.et, 1.]];
}
ELSE vtx.shade.et ← 0.0;
RETURN[vtx];
};
InitClasses[];
END.