DIRECTORY Atom USING [ PropList, GetPropFromList, PutPropOnList ], Real USING [ FixI, Float, RoundI, RoundC, FixC, LargestNumber ], RealFns USING [ SqRt, Power], Imager USING [ Context, PathProc, MaskFill, SetColor ], ImagerColor USING [ ColorFromRGB ], ImagerPixelMap USING [ PixelMap ], Vector3d USING [ Normalize, Mul, Add ], QuickViewer USING [ DrawInViewer ], Pixels USING [ GetSampleSet, PixelBuffer, SampleSet, SampleSetSequence ], ScanConvert USING [ Spot, IntPairSequence, GetColorProc, ConstantPoly, SmoothPoly, ShinyPoly, SpotSequence, justNoticeable, PutSpot, Extend ], ThreeDBasics USING [ Context, Pair, PatchProc, RealSequence, RGB, ShadingValue, Triple, Vertex, VertexInfo, VtxToRealSeqProc ], ThreeDScenes USING [ GetShading, ShadeVtx, ShadingProcs], ThreeDSurfaces USING [ Patch ], ThreeDMisc USING [ GetMappedColor ], TextureMaps USING [ GetTxtrAt, TextureMap ], Tilers USING [ LerpVtx, LerpVtxSequence, FancyPatch ]; TilersImpl: CEDAR MONITOR IMPORTS Real, Imager, ImagerColor, QuickViewer, RealFns, ThreeDMisc, ScanConvert, Vector3d, Atom, Pixels, ThreeDScenes, TextureMaps EXPORTS Tilers = BEGIN TilersError: PUBLIC SIGNAL [reason: ATOM] ~ CODE; RGB: TYPE ~ ThreeDBasics.RGB; Pair: TYPE ~ ThreeDBasics.Pair; -- RECORD [ x, y: REAL]; Triple: TYPE ~ ThreeDBasics.Triple; -- RECORD [ x, y, z: REAL]; SampleSet: TYPE ~ Pixels.SampleSet; Patch: TYPE ~ ThreeDSurfaces.Patch; ColorPrimary: TYPE ~ { red, green, blue, grey }; PixelMap: TYPE ~ ImagerPixelMap.PixelMap; BooleanSequence: TYPE ~ RECORD [ length: NAT, s: SEQUENCE maxLength: NAT OF BOOLEAN ]; RealSequence: TYPE ~ ThreeDBasics.RealSequence; Vertex: TYPE ~ ThreeDBasics.Vertex; VertexInfo: TYPE ~ ThreeDBasics.VertexInfo; LerpVtx: TYPE ~ Tilers.LerpVtx; LerpVtxSequence: TYPE ~ Tilers.LerpVtxSequence; FancyPatch: TYPE ~ Tilers.FancyPatch; EdgeBlock: TYPE ~ RECORD [ moreVertical: BOOLEAN, start, end: REAL, x, y, xIncr, yIncr: REAL, val, incr: REF RealSequence ]; ScanSegment: TYPE ~ RECORD [ start, end: REAL, coverage, cvrgIncr: REAL, lMask, rMask: CARDINAL, val, yIncr, xIncrVal, xIncrForY: REF RealSequence ]; ScanSegSequence: TYPE ~ RECORD [ length: NAT, segs: SEQUENCE maxLength: NAT OF REF ScanSegment ]; IntPolySequence: TYPE ~ RECORD [ length: NAT, polys: SEQUENCE maxLength: NAT OF REF ScanConvert.IntPairSequence ]; SpotSeqSequence: TYPE ~ RECORD [ length: NAT, s: SEQUENCE maxLength: NAT OF REF ScanConvert.SpotSequence ]; HilitSeqs: TYPE ~ RECORD [ -- reflection vectors and light source flags for hilites refls: REF RealSequence, flags: REF BooleanSequence ]; HilitSeqsSequence: TYPE ~ RECORD [ length: NAT, s: SEQUENCE maxLength: NAT OF REF HilitSeqs ]; tblLngth: NAT ~ 256; justNoticeable: REAL ~ ScanConvert.justNoticeable; -- 0.02 recurseLimit: NAT _ 32; -- limits recursion in fancy tiler weight: ARRAY [0..tblLngth] OF REAL; -- filter table pixelBytesCache: REF Pixels.SampleSetSequence _ NEW[ Pixels.SampleSetSequence[2] ]; pixelBytesCacheLength: NAT _ 2; pixelBytesCachePtr: NAT _ 0; -- place to return next free record intPolyCache: REF IntPolySequence _ NEW[ IntPolySequence[2] ]; -- for constant tiler intPolyCacheLength: NAT _ 2; intPolyCachePtr: NAT _ 0; scanSegCache: REF ScanSegSequence _ NEW[ ScanSegSequence[2] ]; -- for ShowSteepTrap scanSegCacheLength: NAT _ 2; scanSegCachePtr: NAT _ 0; spotSeqCache: REF SpotSeqSequence _ NEW[ SpotSeqSequence[2] ]; -- for smooth tiler spotSeqCacheLength: NAT _ 2; spotSeqCachePtr: NAT _ 0; hilitSeqCache: REF HilitSeqsSequence _ NEW[ HilitSeqsSequence[2] ]; -- for hilites hilitSeqCacheLength: NAT _ 2; hilitSeqCachePtr: NAT _ 0; vertexCache: REF LerpVtxSequence _ NEW[ LerpVtxSequence[2] ]; -- for hilites vertexCacheLength: NAT _ 2; vertexCachePtr: NAT _ 0; GetPixelBytes: ENTRY PROC[size: NAT] RETURNS[SampleSet] ~ { ENABLE UNWIND => NULL; s: SampleSet; IF pixelBytesCachePtr = 0 THEN s _ Pixels.GetSampleSet[size] ELSE { pixelBytesCachePtr _ pixelBytesCachePtr - 1; s _ pixelBytesCache[pixelBytesCachePtr]; pixelBytesCache[pixelBytesCachePtr] _ NIL; IF s.maxLength < size THEN s _ Pixels.GetSampleSet[size]; }; RETURN[ s ]; }; ReleasePixelBytes: ENTRY PROC[s: SampleSet] ~ { ENABLE UNWIND => NULL; IF pixelBytesCachePtr = pixelBytesCacheLength THEN { pixelBytesCache _ NEW[ Pixels.SampleSetSequence[pixelBytesCacheLength + 2] ]; pixelBytesCacheLength _ pixelBytesCacheLength + 2; pixelBytesCachePtr _ 0; }; pixelBytesCache[pixelBytesCachePtr] _ s; pixelBytesCachePtr _ pixelBytesCachePtr + 1; }; GetScanSeg: ENTRY PROC[size: NAT] RETURNS[REF ScanSegment] ~ { ENABLE UNWIND => NULL; seg: REF ScanSegment; IF scanSegCachePtr = 0 THEN seg _ NEW[ ScanSegment ] ELSE { scanSegCachePtr _ scanSegCachePtr - 1; seg _ scanSegCache[scanSegCachePtr]; scanSegCache[scanSegCachePtr] _ NIL; }; IF seg.val = NIL OR seg.val.maxLength < size THEN { seg.val _ NEW[ RealSequence[size] ]; seg.yIncr _ NEW[ RealSequence[size] ]; seg.xIncrVal _ NEW[ RealSequence[size] ]; seg.xIncrForY _ NEW[ RealSequence[size] ]; }; RETURN[ seg ]; }; ReleaseScanSeg: ENTRY PROC[s: REF ScanSegment] ~ { ENABLE UNWIND => NULL; IF scanSegCachePtr = scanSegCacheLength THEN { scanSegCache _ NEW[ ScanSegSequence[scanSegCacheLength + 2] ]; scanSegCacheLength _ scanSegCacheLength + 2; scanSegCachePtr _ 0; }; scanSegCache[scanSegCachePtr] _ s; scanSegCachePtr _ scanSegCachePtr + 1; }; GetSpotSeq: ENTRY PROC[size: NAT] RETURNS[REF ScanConvert.SpotSequence] ~ { ENABLE UNWIND => NULL; s: REF ScanConvert.SpotSequence; IF spotSeqCachePtr = 0 THEN s _ NEW[ ScanConvert.SpotSequence[size] ] ELSE { spotSeqCachePtr _ spotSeqCachePtr - 1; s _ spotSeqCache[spotSeqCachePtr]; spotSeqCache[spotSeqCachePtr] _ NIL; IF s.maxLength < size THEN s _ NEW[ ScanConvert.SpotSequence[size] ]; }; RETURN[ s ]; }; ReleaseSpotSeq: ENTRY PROC[s: REF ScanConvert.SpotSequence] ~ { ENABLE UNWIND => NULL; IF spotSeqCachePtr = spotSeqCacheLength THEN { spotSeqCache _ NEW[ SpotSeqSequence[spotSeqCacheLength + 2] ]; spotSeqCacheLength _ spotSeqCacheLength + 2; spotSeqCachePtr _ 0; }; spotSeqCache[spotSeqCachePtr] _ s; spotSeqCachePtr _ spotSeqCachePtr + 1; }; GetHilitSeqs: ENTRY PROC[reflSize, flagSize: NAT] RETURNS[REF HilitSeqs] ~ { ENABLE UNWIND => NULL; s: REF HilitSeqs; IF hilitSeqCachePtr = 0 THEN { s _ NEW[ HilitSeqs ]; s.refls _ NEW[ RealSequence[reflSize] ]; s.flags _ NEW[ BooleanSequence[flagSize] ]; } ELSE { hilitSeqCachePtr _ hilitSeqCachePtr - 1; s _ hilitSeqCache[hilitSeqCachePtr]; hilitSeqCache[hilitSeqCachePtr] _ NIL; IF s.refls.maxLength < reflSize THEN s.refls _ NEW[ RealSequence[reflSize] ]; IF s.flags.maxLength < flagSize THEN s.flags _ NEW[ BooleanSequence[flagSize] ]; }; RETURN[ s ]; }; ReleaseHilitSeqs: ENTRY PROC[s: REF HilitSeqs] ~ { ENABLE UNWIND => NULL; IF hilitSeqCachePtr = hilitSeqCacheLength THEN { hilitSeqCache _ NEW[ HilitSeqsSequence[hilitSeqCacheLength + 2] ]; hilitSeqCacheLength _ hilitSeqCacheLength + 2; hilitSeqCachePtr _ 0; }; hilitSeqCache[hilitSeqCachePtr] _ s; hilitSeqCachePtr _ hilitSeqCachePtr + 1; }; GetVertex: ENTRY PROC[size: NAT] RETURNS[REF LerpVtx] ~ { ENABLE UNWIND => NULL; vtx: REF LerpVtx; IF vertexCachePtr = 0 THEN vtx _ NEW[ LerpVtx ] ELSE { vertexCachePtr _ vertexCachePtr - 1; vtx _ vertexCache[vertexCachePtr]; vertexCache[vertexCachePtr] _ NIL; }; IF vtx.val = NIL OR vtx.val.maxLength < size THEN vtx.val _ NEW[ RealSequence[size] ]; RETURN[ vtx ]; }; ReleaseVertex: ENTRY PROC[vtx: REF LerpVtx] ~ { ENABLE UNWIND => NULL; IF vertexCachePtr = vertexCacheLength THEN { vertexCache _ NEW[ LerpVtxSequence[vertexCacheLength + 2] ]; vertexCacheLength _ vertexCacheLength + 2; vertexCachePtr _ 0; }; vertexCache[vertexCachePtr] _ vtx; vertexCachePtr _ vertexCachePtr + 1; }; 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.]; }; Ceiling: PROC[ in: REAL ] RETURNS[ out: INTEGER ] ~ { out _ Real.RoundI[in]; IF Real.Float[out] < in THEN out _ out + 1; }; Floor: PROC[ in: REAL ] RETURNS[ out: INTEGER ] ~ { out _ Real.RoundI[in]; IF Real.Float[out] > in THEN out _ out - 1; }; Init: PROC[] ~ { FOR i: NAT IN [0..tblLngth/2] DO t: REAL _ i * 1.0 / (tblLngth/2); weight[i] _ Sqr[t] / 2.; weight[i + tblLngth/2] _ 1. - Sqr[1. - t] / 2.; ENDLOOP; }; DupLerpVtx: PROC[vtx: LerpVtx] RETURNS[newVtx: LerpVtx] ~ { newVtx.x _ vtx.x; newVtx.y _ vtx.y; newVtx.val _ NEW[RealSequence[vtx.val.length]]; FOR i: NAT IN [0..vtx.val.length) DO newVtx.val[i] _ vtx.val[i] ENDLOOP; newVtx.val.length _ vtx.val.length; }; DupEdgeBlock: PROC[srce: EdgeBlock] RETURNS[dest : EdgeBlock] ~ { dest.moreVertical _ srce.moreVertical; dest.start _ srce.start; dest.end _ srce.end; dest.x _ srce.x; dest.xIncr _ srce.xIncr; dest.y _ srce.y; dest.yIncr _ srce.yIncr; dest.val _ NEW[RealSequence[srce.val.length]]; dest.val.length _ srce.val.length; FOR i: NAT IN [0..srce.val.length) DO dest.val[i] _ srce.val[i] ENDLOOP; dest.incr _ NEW[RealSequence[srce.incr.length]]; dest.incr.length _ srce.incr.length; FOR i: NAT IN [0..srce.incr.length) DO dest.incr[i] _ srce.incr[i] ENDLOOP; }; GetLerpedVals: ThreeDBasics.VtxToRealSeqProc ~ { IF dest = NIL OR dest.maxLength < 9 THEN dest _ NEW[ RealSequence[9] ]; -- leave room dest[0] _ source.shade.er; dest[1] _ source.shade.eg; dest[2] _ source.shade.eb; dest[3] _ source.shade.et; dest.length _ 4; RETURN [dest]; }; GetLerpedValsForHighLights: ThreeDBasics.VtxToRealSeqProc ~ { IF dest = NIL OR dest.maxLength < 15 THEN dest _ NEW[ RealSequence[15] ]; -- leave room dest[0] _ source.shade.r; dest[1] _ source.shade.g; dest[2] _ source.shade.b; dest[3] _ source.shade.t; dest[4] _ source.shade.exn; dest[5] _ source.shade.eyn; dest[6] _ source.shade.ezn; dest[7] _ source.coord.ex; dest[8] _ source.coord.ey; dest[9] _ source.coord.ez; dest.length _ 10; RETURN [dest]; }; RecoverColor: ScanConvert.GetColorProc ~ { IF Atom.GetPropFromList[spot.props, $TextureMap] # NIL THEN spot _ TextureMaps.GetTxtrAt[spot]; IF Atom.GetPropFromList[spot.props, $HltPwr] # NIL THEN spot _ AddHighlight[spot]; RETURN[ [ R: spot.val[0], G: spot.val[1], B: spot.val[2] ], spot.val[3] ]; }; AddHighlight: PUBLIC PROC[spot: ScanConvert.Spot] RETURNS[ScanConvert.Spot] ~ { context: REF ThreeDBasics.Context _ NARROW[ Atom.GetPropFromList[spot.props, $Context] ]; ref: REF _ Atom.GetPropFromList[spot.props, $HltPwr]; shininess: REAL _ IF ref # NIL THEN NARROW[ref, REF REAL]^ ELSE 0.0; pt: VertexInfo; pt.coord.ex _ spot.val[7]; pt.coord.ey _ spot.val[8]; pt.coord.ez _ spot.val[9]; pt.shade.exn _ spot.val[4]; pt.shade.eyn _ spot.val[5]; pt.shade.ezn _ spot.val[6]; pt.shade.r _ spot.val[0]; pt.shade.g _ spot.val[1]; pt.shade.b _ spot.val[2]; pt.shade.t _ spot.val[3]; [ [spot.val[0], spot.val[1], spot.val[2]], spot.val[3] ] _ ThreeDScenes.ShadeVtx[ context, pt, shininess]; RETURN[spot]; }; PolygonTiler: PUBLIC PROC[context: REF ThreeDBasics.Context, poly: REF Patch] ~ { shadingType: REF ANY _ Atom.GetPropFromList[poly.props, $Type ]; IF context.alphaBuffer THEN { tilingProc: REF ANY _ Atom.GetPropFromList[poly.props, $Tiler ]; IF tilingProc = NIL THEN FancyTiler[context, poly] -- standard anti-aliasing tiler ELSE [] _ NARROW[tilingProc, REF ThreeDBasics.PatchProc]^[context, poly]; -- other } ELSE IF Atom.GetPropFromList[poly.props, $Shininess ] # NIL THEN ShinyTiler[context, poly] -- highlight tiler ELSE SELECT shadingType FROM $Faceted => IF NOT context.depthBuffer THEN ConstantTiler[context, poly] ELSE SmoothTiler[context, poly]; ENDCASE => SmoothTiler[context, poly]; -- default is smooth shading }; ConstantTiler: PUBLIC PROC[ context: REF ThreeDBasics.Context, poly: REF Patch] ~ { pixelBytes: SampleSet _ GetPixelBytes[3]; intPoly: REF ScanConvert.SpotSequence _ GetSpotSeq[poly.nVtces]; SELECT context.renderMode FROM $Dithered, $Bitmap, $Interpress => { -- use Imager in these modes Path: Imager.PathProc ~ { moveTo[[ poly.vtx[poly.nVtces-1].coord.sx, poly.vtx[poly.nVtces-1].coord.sy ]]; FOR i: NAT IN [0..poly.nVtces) DO lineTo[[ poly.vtx[i].coord.sx, poly.vtx[i].coord.sy ]]; ENDLOOP; }; DoFill: PROC[ imagerCtx: Imager.Context ] ~ { Imager.SetColor[ imagerCtx, ImagerColor.ColorFromRGB[ [ poly.vtx[0].shade.er, poly.vtx[0].shade.eg, poly.vtx[0].shade.eb ] ] ]; Imager.MaskFill[imagerCtx, Path]; }; IF context.renderMode = $Interpress THEN DoFill[ NARROW[ Atom.GetPropFromList[context.props, $ImagerCtx] ] ] ELSE QuickViewer.DrawInViewer[ NARROW[context.viewer], DoFill ]; RETURN; }; $PseudoColor => { pixelBytes[0] _ ThreeDMisc.GetMappedColor[ context, [poly.vtx[0].shade.er, poly.vtx[0].shade.eg, poly.vtx[0].shade.eb] ]; pixelBytes.length _ 1; }; $Grey => { pixelBytes[0] _ Real.RoundC[ (poly.vtx[0].shade.er + poly.vtx[0].shade.eg + poly.vtx[0].shade.eb)/3 ]; pixelBytes.length _ 1; }; $FullColor, $Dorado24 => { pixelBytes[0] _ Real.RoundC[poly.vtx[0].shade.er * 255.0]; pixelBytes[1] _ Real.RoundC[poly.vtx[0].shade.eg * 255.0]; pixelBytes[2] _ Real.RoundC[poly.vtx[0].shade.eb * 255.0]; pixelBytes.length _ 3; }; ENDCASE => TilersError[$BadRenderMode]; FOR i: CARDINAL IN [0..poly.nVtces) DO intPoly[i].x _ Real.FixC[poly.vtx[i].coord.sx]; intPoly[i].y _ Real.FixC[poly.vtx[i].coord.sy]; ENDLOOP; intPoly.length _ poly.nVtces; ScanConvert.ConstantPoly[context.display, pixelBytes, intPoly]; ReleasePixelBytes[pixelBytes]; }; SmoothTiler: PUBLIC PROC[ context: REF ThreeDBasics.Context, poly: REF Patch] ~ { spotSeq: REF ScanConvert.SpotSequence _ GetSpotSeq[poly.nVtces]; zScale: NAT _ LAST[NAT] / context.depthResolution; addOn: NAT _ IF context.depthBuffer THEN 1 ELSE 0; spotSeq.length _ poly.nVtces; FOR i: NAT IN [0..poly.nVtces) DO SELECT context.renderMode FROM $Grey => { IF spotSeq[i].val = NIL OR spotSeq[i].val.maxLength < 1+addOn THEN spotSeq[i].val _ NEW[RealSequence[1]]; spotSeq[i].val[0] _ (poly.vtx[i].shade.er + poly.vtx[i].shade.eg + poly.vtx[i].shade.eb) / 3; spotSeq[i].val.length _ 1+addOn; }; $Dithered, $PseudoColor, $FullColor, $Dorado24 => { IF spotSeq[i].val = NIL OR spotSeq[i].val.maxLength < 3+addOn THEN spotSeq[i].val _ NEW[RealSequence[3+addOn]]; spotSeq[i].val[0] _ poly.vtx[i].shade.er; spotSeq[i].val[1] _ poly.vtx[i].shade.eg; spotSeq[i].val[2] _ poly.vtx[i].shade.eb; spotSeq[i].val.length _ 3+addOn; }; ENDCASE => TilersError[$BadRenderMode]; IF context.depthBuffer THEN spotSeq[i].val[spotSeq[i].val.length-1] _ Real.FixC[poly.vtx[i].coord.sz * zScale]; spotSeq[i].x _ Real.FixC[poly.vtx[i].coord.sx]; spotSeq[i].y _ Real.FixC[poly.vtx[i].coord.sy]; ENDLOOP; ScanConvert.SmoothPoly[context.display, spotSeq, context.renderMode]; ReleaseSpotSeq[spotSeq]; }; ShinyTiler: PUBLIC PROC[context: REF ThreeDBasics.Context, poly: REF Patch] ~ { spotSeq: REF ScanConvert.SpotSequence; zScale: NAT _ LAST[NAT] / context.depthResolution; addOn: NAT _ IF context.depthBuffer THEN 1 ELSE 0; hiliteInfo: REF HilitSeqs; idealReflSeq: REF RealSequence; lightFlags: REF BooleanSequence; shininess: REAL _ NARROW[Atom.GetPropFromList[poly.props, $Shininess], REF REAL]^; shinyPwr: NAT _ Real.RoundC[shininess]; normalInfoLength, nmlCnt, hltCnt: NAT _ 0; IF context.renderMode = $Bitmap THEN TilersError[$BadRenderMode]; hiliteInfo _ GotAHilite[context, poly, shininess]; -- do we have a possible highlight? IF hiliteInfo = NIL THEN { -- no highlight IF Atom.GetPropFromList[poly.props, $Type ] = $Faceted THEN IF NOT context.depthBuffer THEN ConstantTiler[context, poly] ELSE SmoothTiler[context, poly] ELSE SmoothTiler[context, poly]; RETURN[]; }; spotSeq _ GetSpotSeq[poly.nVtces]; idealReflSeq _ hiliteInfo.refls; -- got a highlight, lets do it! lightFlags _ hiliteInfo.flags; FOR j: NAT IN [0 .. context.lights.length) DO -- figure storage needed for extra normal info IF lightFlags[j] THEN normalInfoLength _ normalInfoLength + 5; ENDLOOP; FOR i: NAT IN [0..poly.nVtces) DO -- get storage for each vertex in turn IF spotSeq[i].val = NIL OR spotSeq[i].val.maxLength < 3 + normalInfoLength + addOn THEN spotSeq[i].val _ NEW[RealSequence[3 + normalInfoLength + addOn]]; spotSeq[i].val[0] _ poly.vtx[i].shade.er * 255.0; spotSeq[i].val[1] _ poly.vtx[i].shade.eg * 255.0; spotSeq[i].val[2] _ poly.vtx[i].shade.eb * 255.0; spotSeq[i].x _ Real.FixC[poly.vtx[i].coord.sx]; spotSeq[i].y _ Real.FixC[poly.vtx[i].coord.sy]; spotSeq[i].val.length _ 3 + normalInfoLength + addOn; IF context.depthBuffer THEN spotSeq[i].val[spotSeq[i].val.length-1] _ Real.FixC[poly.vtx[i].coord.sz * zScale]; ENDLOOP; spotSeq.length _ poly.nVtces; FOR j: NAT IN [0..context.lights.length) DO -- pick up info for each highlight-causing light IF lightFlags[j] THEN { FOR i: NAT IN [0..poly.nVtces) DO outBase: NAT _ 3 + hltCnt*5; -- r, g, b + 5 per highlight inBase: NAT _ (j * 5 * poly.nVtces) + (i * 5); FOR k: NAT IN [0..5) DO spotSeq[i].val[outBase+k] _ 256.0 * idealReflSeq[inBase + k]; ENDLOOP; ENDLOOP; hltCnt _ hltCnt + 1; }; ENDLOOP; ScanConvert.ShinyPoly[context.display, spotSeq, shinyPwr, context.renderMode]; ReleaseHilitSeqs[hiliteInfo]; ReleaseSpotSeq[spotSeq]; }; defaultHiliteState: BOOL _ FALSE; -- Kludge of the day PhongShadeAllPolygons: PUBLIC PROC ~ {defaultHiliteState _ TRUE}; PhongShadeOnlyHighLightedPolygons: PUBLIC PROC ~ {defaultHiliteState _ FALSE}; GotAHilite: PROC[context: REF ThreeDBasics.Context, poly: REF Patch, shininess: REAL] RETURNS[REF HilitSeqs ] ~ { XfmNormal: PROC[light: Vertex, vtx: VertexInfo] RETURNS[ Triple ] ~ { toLightSrc: Triple _ Vector3d.Normalize[ -- normalized direction to light [ light.ex - vtx.coord.ex, light.ey - vtx.coord.ey, light.ez - vtx.coord.ez ] ]; toEye: Triple _ Vector3d.Normalize[ -- normalized direction to eye [ -vtx.coord.ex, -vtx.coord.ey, -vtx.coord.ez ] ]; idealRefl: Triple _ Vector3d.Mul[ Vector3d.Add[toLightSrc, toEye], 0.5 ]; hypotA: REAL _ RealFns.SqRt[ Sqr[idealRefl.x] + Sqr[idealRefl.z] ]; -- rotate about y cosA: REAL _ idealRefl.z / hypotA; sinA: REAL _ idealRefl.x / hypotA; hypotB: REAL _ RealFns.SqRt[ Sqr[idealRefl.y] + Sqr[hypotA] ]; -- rotate about x cosB: REAL _ hypotA / hypotB; sinB: REAL _ idealRefl.y / hypotB; tx: REAL _ cosA*vtx.shade.exn - sinA*vtx.shade.ezn; ty: REAL _ vtx.shade.eyn; tz: REAL _ sinA*vtx.shade.exn + cosA*vtx.shade.ezn; RETURN[ Vector3d.Normalize[ [x: tx, y: cosB*ty - sinB*tz, z: sinB*ty + cosB*tz] ] ]; }; gotAHilite: BOOLEAN _ defaultHiliteState; seqLength: NAT _ (poly.nVtces*5) * context.lights.length; hilitInfo: REF HilitSeqs _ GetHilitSeqs[seqLength, context.lights.length]; idealReflSeq: REF RealSequence _ hilitInfo.refls; lightFlags: REF BooleanSequence _ hilitInfo.flags; lightFlags.length _ context.lights.length; FOR j: NAT IN [0..context.lights.length) DO lightClr: RGB _ NARROW[ThreeDScenes.GetShading[ context.lights[j], $Color], REF RGB ]^; minX, minY: REAL _ Real.LargestNumber; maxX, maxY: REAL _ -Real.LargestNumber; FOR i: NAT IN [0..poly.nVtces) DO -- get bounding box on highlight reflection vectors reflVec: Triple _ XfmNormal[ context.lights[j].centroid, poly[i] ]; base: NAT _ (j * 5 * poly.nVtces) + (i * 5); minX _ MIN[minX, reflVec.x]; maxX _ MAX[maxX, reflVec.x]; minY _ MIN[minY, reflVec.y]; maxY _ MAX[maxY, reflVec.y]; idealReflSeq[base ] _ reflVec.x; idealReflSeq[base+1] _ reflVec.y; idealReflSeq[base+2] _ lightClr.R; idealReflSeq[base+3] _ lightClr.G; idealReflSeq[base+4] _ lightClr.B; idealReflSeq.length _ base+5; ENDLOOP; minX _ IF Sgn[minX] # Sgn[maxX] THEN 0.0 ELSE MIN[ABS[minX], ABS[maxX]]; minY _ IF Sgn[minY] # Sgn[maxY] THEN 0.0 ELSE MIN[ABS[minY], ABS[maxY]]; IF RealFns.Power[ MAX[ 0.0, 1.0 - Sqr[minX] - Sqr[minY] ], shininess ] > justNoticeable THEN { gotAHilite _ TRUE; lightFlags[j] _ TRUE; } ELSE lightFlags[j] _ FALSE; ENDLOOP; IF NOT gotAHilite THEN { ReleaseHilitSeqs[hilitInfo]; hilitInfo _ NIL; }; RETURN[hilitInfo]; }; FancyTiler: PUBLIC PROC[context: REF ThreeDBasics.Context, poly: REF Patch] ~ { getVtxProc: ThreeDBasics.VtxToRealSeqProc _ NIL; getColorProc: ScanConvert.GetColorProc _ NIL; LerpVtxFromVtx: PROC[vtx: VertexInfo, fancy: BOOL] RETURNS[LerpVtx] ~ { lerpVtx: LerpVtx _ [vtx.coord.sx, vtx.coord.sy, NIL]; lerpVtx.val _ IF fancy THEN GetLerpedValsForHighLights[dest: lerpVtx.val, source: vtx] ELSE GetLerpedVals[dest: lerpVtx.val, source: vtx]; RETURN[lerpVtx]; }; AddTextureCoords: PROC[vtx: LerpVtx, addVtx: VertexInfo] RETURNS[LerpVtx] ~ { IF vtx.val.maxLength < vtx.val.length+2 THEN vtx.val _ ScanConvert.Extend[vtx.val, vtx.val.length+2]; vtx.val[vtx.val.length ] _ NARROW[addVtx.aux, REF Triple].x; vtx.val[vtx.val.length+1] _ NARROW[addVtx.aux, REF Triple].y; vtx.val.length _ vtx.val.length+2; RETURN [vtx]; }; AdjustTexture: PROC[poly: REF Patch] ~ { maxXtxtr, maxYtxtr, minXtxtr, minYtxtr: REAL _ 0.0; FOR i: CARDINAL IN [0..poly.nVtces) DO -- find maximum txtr: REF Triple _ NARROW[poly[i].aux]; IF maxXtxtr < txtr.x THEN maxXtxtr _ txtr.x; IF maxYtxtr < txtr.y THEN maxYtxtr _ txtr.y; ENDLOOP; FOR i: CARDINAL IN [0..poly.nVtces) DO -- push small ones beyond maximum txtr: REF Triple _ NARROW[poly[i].aux]; WHILE maxXtxtr - txtr.x > .5 DO txtr.x _ txtr.x + 1.0; ENDLOOP; WHILE maxYtxtr - txtr.y > .5 DO txtr.y _ txtr.y + 1.0; ENDLOOP; ENDLOOP; minXtxtr _ maxXtxtr; minYtxtr _ maxYtxtr; FOR i: CARDINAL IN [0..poly.nVtces) DO -- find minimum txtr: REF Triple _ NARROW[poly[i].aux]; IF minXtxtr > txtr.x THEN minXtxtr _ txtr.x; IF minYtxtr > txtr.y THEN minYtxtr _ txtr.y; ENDLOOP; minXtxtr _ Real.Float[Real.FixI[minXtxtr]]; minYtxtr _ Real.Float[Real.FixI[minYtxtr]]; FOR i: CARDINAL IN [0..poly.nVtces) DO -- adjust everything to minima under 1.0 txtr: REF Triple _ NARROW[poly[i].aux]; txtr.x _ txtr.x - minXtxtr; txtr.y _ txtr.y - minYtxtr; ENDLOOP; }; keepYIncrements, shadingPerPixel, textureMapping: BOOLEAN _ FALSE; spot: ScanConvert.Spot; fancyPoly: REF FancyPatch _ NEW[ FancyPatch[poly.nVtces] ]; shininess: REF REAL; ref: REF _ Atom.GetPropFromList[poly.props, $ShadingProcs]; IF ref # NIL THEN [getVtxProc, getColorProc] _ NARROW[ ref, REF ThreeDScenes.ShadingProcs]^; IF getColorProc # NIL THEN shadingPerPixel _ TRUE -- custom shading, must use raw surface color ELSE getColorProc _ RecoverColor; -- default shading IF NOT context.alphaBuffer THEN SIGNAL TilersError[$NoAlphaBuffer]; shininess _ NARROW[Atom.GetPropFromList[poly.props, $Shininess], REF REAL]; IF shininess # NIL AND shininess^ > 0.0 THEN { hilitInfo: REF HilitSeqs _ GotAHilite[context, poly, shininess^]; IF hilitInfo # NIL THEN { spot.props _ Atom.PutPropOnList[spot.props, $HltPwr, shininess]; keepYIncrements _ TRUE; shadingPerPixel _ TRUE; ReleaseHilitSeqs[hilitInfo]; }; }; ref _ Atom.GetPropFromList[poly.props, $TextureMap]; IF ref # NIL THEN { spot.props _ Atom.PutPropOnList[ spot.props, $TextureMap, ref ]; IF NARROW[ref, REF TextureMaps.TextureMap].type = $Bump THEN IF NOT shadingPerPixel THEN { IF shininess = NIL THEN shininess _ NEW[REAL _ 0.0]; spot.props _ Atom.PutPropOnList[spot.props, $HltPwr, shininess]; shadingPerPixel _ TRUE; -- change shading mode for bump mapping }; keepYIncrements _ TRUE; textureMapping _ TRUE; AdjustTexture[poly]; -- fix texture seams }; spot.proc _ getColorProc; -- set up remaining spot fields IF keepYIncrements THEN spot.props _ Atom.PutPropOnList[ spot.props, $KeepYIncrements, $DoIt ]; spot.props _ Atom.PutPropOnList[spot.props, $Context, context]; -- pass context. spot.props _ Atom.PutPropOnList[spot.props, $ShapeShadingProps, poly.props ]; -- pass props FOR i: NAT IN [0..poly.nVtces) DO -- convert vertices to lerp fancyPoly[i] _ LerpVtxFromVtx[poly[i], shadingPerPixel]; ENDLOOP; IF textureMapping THEN { -- add texture coordinates FOR i: NAT IN [0..poly.nVtces) DO fancyPoly[i] _ AddTextureCoords[ fancyPoly[i], poly[i] ]; ENDLOOP; spot.props _ Atom.PutPropOnList[ -- store texture coord position marker spot.props, $MapVals, NEW[ NAT _ fancyPoly[0].val.length - 2 ] ]; }; IF getVtxProc # NIL THEN FOR i: CARDINAL IN [0..poly.nVtces) DO -- for custom shading fancyPoly[i].val _ getVtxProc[ dest: fancyPoly[i].val, source: poly[i] ]; ENDLOOP; fancyPoly.spot _ spot; RealFancyTiler[context, fancyPoly]; -- now go tile it }; RealFancyTiler: PUBLIC PROC[context: REF ThreeDBasics.Context, poly: REF FancyPatch] ~ { least, top, bottom: REAL; lEdge, rEdge: EdgeBlock; vtxCount, lVtx, rVtx, nxtlVtx, nxtrVtx, nVtcesMinusOne: NAT; leftVtxNeeded, rightVtxNeeded: BOOLEAN; least _ poly.vtx[0].y; nxtlVtx _ 0; FOR i: CARDINAL IN [1..poly.length) DO -- find bottom vertex IF poly.vtx[i].y < least THEN { least _ poly[i].y; nxtlVtx _ i; }; ENDLOOP; nxtrVtx _ nxtlVtx; -- set pointers to bottom vertex leftVtxNeeded _ rightVtxNeeded _ TRUE; nVtcesMinusOne _ poly.length - 1; vtxCount _ 1; WHILE vtxCount < poly.length DO -- Do until all vertices reached IF leftVtxNeeded THEN { -- work around left side lVtx _ nxtlVtx; nxtlVtx _ (nxtlVtx + 1) MOD poly.length; lEdge _ MakeEdge[poly[lVtx], poly[nxtlVtx]]; leftVtxNeeded _ FALSE; }; IF rightVtxNeeded THEN { -- work around right side rVtx _ nxtrVtx; nxtrVtx _ (nxtrVtx + nVtcesMinusOne) MOD poly.length; rEdge _ MakeEdge[poly[rVtx], poly[nxtrVtx]]; rightVtxNeeded _ FALSE; }; IF poly[nxtlVtx].y < poly[nxtrVtx].y THEN { top _ poly[nxtlVtx].y; -- next left vertex reached leftVtxNeeded _ TRUE; vtxCount _ vtxCount + 1; } ELSE { top _ poly[nxtrVtx].y; -- next right vertex reached rightVtxNeeded _ TRUE; vtxCount _ vtxCount + 1; }; bottom _ MAX[poly[lVtx].y, poly[rVtx].y]; ShowFancyTrap[ context, poly, bottom, top, lEdge, rEdge ! TilersError => IF reason = $DeepRecursionInTiler THEN CONTINUE]; ENDLOOP; }; MakeEdge: PROC[vtx1, vtx2: LerpVtx] RETURNS[edge: EdgeBlock] ~ { length: REAL; edge.val _ NEW[ RealSequence[vtx1.val.length] ]; edge.incr _ NEW[ RealSequence[vtx1.val.length] ]; IF ABS[vtx2.y - vtx1.y] >= ABS[vtx2.x - vtx1.x] THEN { length _ vtx2.y - vtx1.y; edge.start _ MIN[vtx1.y, vtx2.y]; edge.end _ MAX[vtx1.y, vtx2.y]; edge.moreVertical _ TRUE; } ELSE { length _ vtx2.x - vtx1.x; edge.start _ MIN[vtx1.x, vtx2.x]; edge.end _ MAX[vtx1.x, vtx2.x]; edge.moreVertical _ FALSE; }; IF ABS[length] < justNoticeable THEN length _ 1.; -- prevent divide errors edge.x _ vtx1.x; edge.xIncr _ (vtx2.x - vtx1.x) / length; edge.y _ vtx1.y; edge.yIncr _ (vtx2.y - vtx1.y) / length; FOR i: NAT IN [0..vtx1.val.length) DO edge.val[i] _ vtx1.val[i]; edge.incr[i] _ (vtx2.val[i] - vtx1.val[i]) / length; ENDLOOP; edge.val.length _ edge.incr.length _ vtx1.val.length; RETURN[edge]; }; EvalEdgeAt: PROC[vtx: LerpVtx, edge: EdgeBlock, position: REAL] RETURNS[LerpVtx] ~ { pos, dist: REAL; IF vtx.val = NIL OR vtx.val.maxLength < edge.val.length THEN vtx.val _ NEW[ RealSequence[edge.val.length] ]; IF position > edge.end THEN pos _ edge.end -- keep values between vertex values ELSE IF position < edge.start THEN pos _ edge.start ELSE pos _ position; dist _ IF edge.moreVertical THEN pos - edge.y ELSE pos - edge.x; vtx.x _ edge.x + edge.xIncr * dist; vtx.y _ edge.y + edge.yIncr * dist; FOR i: NAT IN [0..edge.val.length) DO vtx.val[i] _ edge.val[i] + edge.incr[i] * dist; ENDLOOP; vtx.val.length _ edge.val.length; RETURN[vtx]; }; EvalCvrgeAt: PROC[ start, end, position: REAL] RETURNS[ cvrge: REAL, mask: CARDINAL] ~ { rCoverage, rUnCoverage: REAL; lCoverage: REAL _ position - start; IF lCoverage >= 1. THEN lCoverage _ 2.0 -- fully covered ELSE IF lCoverage > -1.0 THEN lCoverage _ 1.0 + lCoverage -- partially covered ELSE lCoverage _ 0.; lCoverage _ weight[Real.FixI[ tblLngth/2 * lCoverage ]]; rCoverage _ end - position; IF rCoverage >= 1. THEN rCoverage _ 2.0 -- fully covered ELSE IF rCoverage > -1.0 THEN rCoverage _ 1.0 + rCoverage -- partially covered ELSE rCoverage _ 0.; rUnCoverage _ weight[Real.FixI[ tblLngth/2 * (2.0 - rCoverage) ]]; -- weight uncovered part cvrge _ lCoverage - rUnCoverage; -- l - r is total coverage mask _ 0; -- not yet implemented }; MakeScanSeg: PROC[seg: REF ScanSegment, lEdge, rEdge: EdgeBlock, position: REAL, increments: BOOLEAN] RETURNS[REF ScanSegment] ~ { length, lCvrge, rCvrge: REAL; lVtx: REF LerpVtx _ GetVertex[lEdge.val.length]; rVtx: REF LerpVtx _ GetVertex[lEdge.val.length]; lVtx^ _ EvalEdgeAt[lVtx^, lEdge, position]; rVtx^ _ EvalEdgeAt[rVtx^, rEdge, position]; IF lEdge.moreVertical -- horizontal scan segment THEN { length _ rVtx.x - lVtx.x; seg.start _ lVtx.x; seg.end _ rVtx.x; } ELSE { -- vertical scan segment length _ rVtx.y - lVtx.y; seg.start _ lVtx.y; seg.end _ rVtx.y; }; IF ABS[length] > justNoticeable THEN { -- long enough to show up [lCvrge, seg.lMask] _ EvalCvrgeAt[lEdge.start, lEdge.end, position]; [rCvrge, seg.rMask] _ EvalCvrgeAt[rEdge.start, rEdge.end, position]; seg.coverage _ lCvrge; seg.cvrgIncr _ (rCvrge - lCvrge) / length; FOR i: NAT IN [0..lEdge.val.length) DO seg.val[i] _ lVtx.val[i]; seg.xIncrVal[i] _ (rVtx.val[i] - lVtx.val[i]) / length; -- x-increments ENDLOOP; seg.val.length _ seg.xIncrVal.length _ lEdge.val.length; IF increments THEN { FOR i: NAT IN [0..lEdge.val.length) DO seg.yIncr[i] _ lEdge.incr[i]; -- yincrements seg.xIncrForY[i] _ (rEdge.incr[i] - lEdge.incr[i]) / length; -- x-incrs for yincrs ENDLOOP; seg.yIncr.length _ seg.xIncrForY.length _ lEdge.val.length; }; IF seg.val[0] < 0.0 THEN SIGNAL TilersError[$NegativeColor]; }; ReleaseVertex[lVtx]; ReleaseVertex[rVtx]; RETURN[seg]; }; EvalScanSegAt: PROC[spot: ScanConvert.Spot, seg: REF ScanSegment, position: REAL] RETURNS[REAL, ScanConvert.Spot] ~ { pos, dist, coverage: REAL; mask: CARDINAL; IF spot.val = NIL OR spot.val.maxLength < seg.val.length THEN { spot.val _ NEW[ RealSequence[seg.val.length] ]; spot.yIncr _ NEW[ RealSequence[seg.val.length] ]; spot.xIncr _ NEW[ RealSequence[seg.val.length] ]; }; IF position > seg.end THEN pos _ seg.end -- keep values between vertex values ELSE IF position < seg.start THEN pos _ seg.start ELSE pos _ position; dist _ pos - seg.start; FOR i: NAT IN [0..seg.val.length) DO -- load up spot values spot.val[i] _ seg.val[i] + seg.xIncrVal[i] * dist; spot.yIncr[i] _ seg.yIncr[i] + seg.xIncrForY[i] * dist; ENDLOOP; spot.xIncr _ seg.xIncrVal; -- use x increments as is spot.val.length _ spot.yIncr.length _ spot.xIncr.length _ seg.val.length; [coverage, mask] _ EvalCvrgeAt[seg.start, seg.end, position]; coverage _ coverage * (seg.coverage + seg.cvrgIncr * dist); RETURN[coverage, spot]; }; ShowFancyTrap: PROC[ context: REF ThreeDBasics.Context, inPoly: REF FancyPatch, bottom, top: REAL, lEdge, rEdge: EdgeBlock] ~ { GetXcoordAt: PROC[edge: EdgeBlock, yPos: REAL] RETURNS [REAL] ~ { dist: REAL _ yPos - edge.y; RETURN [ edge.x + dist / edge.yIncr ]; }; spot: ScanConvert.Spot _ inPoly.spot; tEdge, bEdge, midlEdge, midrEdge: EdgeBlock; leftTopVtx, leftBotVtx, rightTopVtx, rightBotVtx, vtx0, vtx1, vtx2, vtx3, vertex: LerpVtx; sideways, midSection: BOOLEAN _ TRUE; toughCase: BOOLEAN _ FALSE; a, b: REAL; -- parameters for defining 45 degree lines IF bottom + justNoticeable >= top THEN RETURN[]; -- too thin to affect image midlEdge _ DupEdgeBlock[lEdge]; -- copy sides for possible later use midrEdge _ DupEdgeBlock[rEdge]; FOR i: NAT IN [0..midlEdge.val.length) DO midlEdge.val[i] _ lEdge.val[i]; midlEdge.incr[i] _ lEdge.incr[i]; midrEdge.val[i] _ rEdge.val[i]; midrEdge.incr[i] _ rEdge.incr[i]; ENDLOOP; IF NOT (lEdge.moreVertical AND rEdge.moreVertical) THEN { -- get corners IF lEdge.moreVertical THEN { leftTopVtx _ EvalEdgeAt[leftTopVtx, lEdge, top]; leftBotVtx _ EvalEdgeAt[leftBotVtx, lEdge, bottom]; } ELSE { topX: REAL _ GetXcoordAt[lEdge, top]; botX: REAL _ GetXcoordAt[lEdge, bottom]; leftTopVtx _ EvalEdgeAt[leftTopVtx, lEdge, topX]; leftBotVtx _ EvalEdgeAt[leftBotVtx, lEdge, botX]; }; IF rEdge.moreVertical THEN { rightTopVtx _ EvalEdgeAt[rightTopVtx, rEdge, top]; rightBotVtx _ EvalEdgeAt[rightBotVtx, rEdge, bottom]; } ELSE { topX: REAL _ GetXcoordAt[rEdge, top]; botX: REAL _ GetXcoordAt[rEdge, bottom]; rightTopVtx _ EvalEdgeAt[rightTopVtx, rEdge, topX]; rightBotVtx _ EvalEdgeAt[rightBotVtx, rEdge, botX]; }; IF rightTopVtx.x + justNoticeable < leftTopVtx.x OR rightBotVtx.x + justNoticeable < leftBotVtx.x THEN RETURN[]; -- twisted or backfacing }; IF NOT lEdge.moreVertical THEN IF lEdge.yIncr < 0. THEN { -- left edge is more horizontal, top vertex is leftmost tEdge _ MakeEdge[leftTopVtx, rightTopVtx]; bEdge _ DupEdgeBlock[lEdge]; IF leftBotVtx.x <= rightTopVtx.x THEN { -- easy case: right triangle containing whole left edge ShowSteepTrap[context, spot, leftTopVtx.x, leftBotVtx.x, bEdge, tEdge, sideways]; midlEdge _ MakeEdge[leftBotVtx, EvalEdgeAt[vertex, tEdge, leftBotVtx.x]]; } ELSE { -- right top is left of left bottom IF rEdge.moreVertical THEN { -- difficult case bot. more horz. top more vert. toughCase _ TRUE; ShowSteepTrap[context, spot, leftTopVtx.x, rightTopVtx.x, bEdge, tEdge, sideways]; vtx0 _ EvalEdgeAt[vtx0, bEdge, rightTopVtx.x]; --build new polygon vtx1 _ EvalEdgeAt[vtx1, rEdge, rightTopVtx.y]; vtx2 _ EvalEdgeAt[vtx2, rEdge, rightBotVtx.y]; vtx3 _ EvalEdgeAt[vtx3, bEdge, leftBotVtx.x]; a _ .707; b _ .707; -- test against negative 45 degree slope } ELSE { -- both more horz. do triangle then trapezoid ShowSteepTrap[context, spot, leftTopVtx.x, rightTopVtx.x, bEdge, tEdge, sideways]; ShowSteepTrap[context, spot, rightTopVtx.x, leftBotVtx.x, bEdge, rEdge, sideways]; midSection _ FALSE; }; }; } ELSE { -- left edge is more horizontal, bottom vertex is leftmost bEdge _ MakeEdge[leftBotVtx, rightBotVtx]; tEdge _ DupEdgeBlock[lEdge]; IF leftTopVtx.x <= rightBotVtx.x THEN { -- easy case: right triangle containing whole left edge ShowSteepTrap[context, spot, leftBotVtx.x, leftTopVtx.x, bEdge, tEdge, sideways]; midlEdge _ MakeEdge[leftTopVtx, EvalEdgeAt[vertex, bEdge, leftTopVtx.x]]; } ELSE { -- right bottom is left of left top IF rEdge.moreVertical THEN { -- difficult case bot. more vert. top more horz. toughCase _ TRUE; ShowSteepTrap[context, spot, leftBotVtx.x, rightBotVtx.x, bEdge, tEdge, sideways]; vtx0 _ EvalEdgeAt[vtx0, rEdge, rightBotVtx.y]; --build new polygon vtx1 _ EvalEdgeAt[vtx1, tEdge, rightBotVtx.x]; vtx2 _ EvalEdgeAt[vtx2, tEdge, leftTopVtx.x]; vtx3 _ EvalEdgeAt[vtx3, rEdge, rightTopVtx.y]; a _ -.707; b _ .707; -- test against positive 45 degree slope } ELSE { -- both more horz. do triangle then trapezoid ShowSteepTrap[context, spot, leftBotVtx.x, rightBotVtx.x, bEdge, tEdge, sideways]; ShowSteepTrap[context, spot, rightBotVtx.x, leftTopVtx.x, rEdge, tEdge, sideways]; midSection _ FALSE; }; }; }; IF NOT rEdge.moreVertical THEN IF rEdge.yIncr < 0. THEN { -- right edge is more horizontal, top vertex is leftmost bEdge _ MakeEdge[leftBotVtx, rightBotVtx]; tEdge _ DupEdgeBlock[rEdge]; IF leftBotVtx.x <= rightTopVtx.x THEN { -- easy case: right triangle containing whole right edge ShowSteepTrap[context, spot, rightTopVtx.x, rightBotVtx.x, bEdge, tEdge, sideways]; midrEdge _ MakeEdge[EvalEdgeAt[vertex, bEdge, rightTopVtx.x], rightTopVtx]; } ELSE { -- left bottom is right of right top IF lEdge.moreVertical THEN { -- difficult case bot. more vert. top more horz. toughCase _ TRUE; vtx0 _ EvalEdgeAt[vtx0, lEdge, rightTopVtx.y]; --build new polygon vtx1 _ EvalEdgeAt[vtx1, tEdge, rightTopVtx.x]; vtx2 _ EvalEdgeAt[vtx2, tEdge, leftBotVtx.x]; vtx3 _ EvalEdgeAt[vtx3, lEdge, leftBotVtx.y]; a _ .707; b _ .707; -- test against negative 45 degree slope }; ShowSteepTrap[context, spot, leftBotVtx.x, rightBotVtx.x, bEdge, tEdge, sideways]; }; } ELSE { -- right edge is more horizontal, bottom vertex is leftmost tEdge _ MakeEdge[leftTopVtx, rightTopVtx]; bEdge _ DupEdgeBlock[rEdge]; IF leftTopVtx.x <= rightBotVtx.x THEN { -- easy case: right triangle containing whole right edge ShowSteepTrap[context, spot, rightBotVtx.x, rightTopVtx.x, bEdge, tEdge, sideways]; midrEdge _ MakeEdge[rightBotVtx, EvalEdgeAt[vertex, tEdge, rightBotVtx.x]]; } ELSE { -- left top is right of right bottom IF lEdge.moreVertical THEN { -- difficult case bot. more vert. top more horz. toughCase _ TRUE; vtx0 _ EvalEdgeAt[vtx0, bEdge, rightBotVtx.x]; --build new polygon vtx1 _ EvalEdgeAt[vtx1, lEdge, rightBotVtx.y]; vtx2 _ EvalEdgeAt[vtx2, lEdge, leftTopVtx.y]; vtx3 _ EvalEdgeAt[vtx3, bEdge, leftTopVtx.x]; a _ -.707; b _ .707; -- test against positive 45 degree slope }; ShowSteepTrap[context, spot, leftTopVtx.x, rightTopVtx.x, bEdge, tEdge, sideways]; }; }; IF toughCase THEN { -- quadrilateral with top and bottom slopes on both sides of 45 deg. c, d1, d2, d3: REAL; -- evaluate area based on distance of vertices from 45 degree line c _ -(a * vtx0.x + b * vtx0.y); -- equation for line through vtx0 d1 _ a * vtx1.x + b * vtx1.y + c; -- distances of other vertices from line d2 _ a * vtx2.x + b * vtx2.y + c; d3 _ a * vtx3.x + b * vtx3.y + c; IF (top - bottom) * ( MAX[d1, d2, d3, 0.0] - MIN[d1, d2, d3, 0.0] ) / 2.0 < justNoticeable THEN RETURN[] -- estimated area too small to matter ELSE { poly: REF FancyPatch _ NEW[FancyPatch[4]]; poly.vtx[0] _ DupLerpVtx[vtx0]; poly.vtx[1] _ DupLerpVtx[vtx1]; poly.vtx[2] _ DupLerpVtx[vtx2]; poly.vtx[3] _ DupLerpVtx[vtx3]; poly.spot _ spot; poly.recurseLevel _ inPoly.recurseLevel + 1; IF poly.recurseLevel > recurseLimit THEN SIGNAL TilersError[$DeepRecursionInTiler]; RealFancyTiler[context, poly]; -- go draw it (recursively) }; } ELSE IF midSection THEN ShowSteepTrap[context, spot, bottom, top, midlEdge, midrEdge]; }; ShowSteepTrap: PROC[ context: REF ThreeDBasics.Context, spot: ScanConvert.Spot, bottom, top: REAL, lEdge, rEdge: EdgeBlock, sideways: BOOLEAN _ FALSE ] ~ { Swap: PROC[ref1, ref2: REF RealSequence] RETURNS [outRef1, outRef2: REF RealSequence] ~{ RETURN[ outRef1: ref2, outRef2: ref1 ]; }; shadingType: REF ANY _ Atom.GetPropFromList[ NARROW[ Atom.GetPropFromList[spot.props, $ShapeShadingProps], Atom.PropList ], $Type ]; scanSeg: REF ScanSegment _ GetScanSeg[lEdge.val.length]; writeOp: ATOM _ IF shadingType = $Lines THEN $WriteLineUnder ELSE $WriteUnder; lStartSave: REAL _ lEdge.start; lEndSave: REAL _ lEdge.end; -- save limits to restore later rStartSave: REAL _ rEdge.start; rEndSave: REAL _ rEdge.end; yLimit: INTEGER _ IF sideways THEN Ceiling[context.viewPort.w] ELSE Ceiling[context.viewPort.h]; xLimit: INTEGER _ IF sideways THEN Ceiling[context.viewPort.h] ELSE Ceiling[context.viewPort.w]; yIncrements: BOOLEAN _ FALSE; IF context.stopMe THEN RETURN; IF bottom + justNoticeable >= top THEN RETURN[]; -- too vertically thin to affect image IF Atom.GetPropFromList[spot.props, $KeepYIncrements] = $DoIt THEN yIncrements _TRUE; lEdge.start _ rEdge.start _ bottom; -- set edge limits for coverage calcs. lEdge.end _ rEdge.end _ top; FOR y: INTEGER IN [Floor[bottom]..Ceiling[top]] DO IF context.stopMe THEN RETURN; IF y < 0 OR y >= yLimit THEN LOOP; -- scissor off if out-of-bounds scanSeg _ MakeScanSeg[scanSeg, lEdge, rEdge, Real.Float[y], yIncrements]; IF scanSeg.end - scanSeg.start > justNoticeable THEN { -- if wide enough to affect image FOR x: INTEGER IN [Floor[scanSeg.start]..Ceiling[scanSeg.end]] DO IF x < 0 OR x >= xLimit THEN LOOP; -- scissor off if out-of-bounds [spot.coverage, spot] _ EvalScanSegAt[ spot, scanSeg, Real.Float[x] ]; IF sideways THEN { [spot.yIncr, spot.xIncr] _ Swap[spot.xIncr, spot.yIncr]; -- switch x and y spot.x _ y; spot.y _ x; } ELSE { spot.x _ x; spot.y _ y; }; ScanConvert.PutSpot[ context.display, spot, writeOp, context.renderMode ]; IF sideways THEN [spot.yIncr, spot.xIncr] _ Swap[spot.xIncr, spot.yIncr]; -- put back ENDLOOP; }; ENDLOOP; lEdge.start _ lStartSave; lEdge.end _ lEndSave; -- restore limits rEdge.start _ rStartSave; rEdge.end _ rEndSave; ReleaseScanSeg[scanSeg]; }; Init[]; END. €TilersImpl.mesa Last Edited by: Crow, December 16, 1986 4:01:33 pm PST Bloomenthal, January 19, 1987 5:36:29 pm PST Types RECORD [x, y: REAL, val: REF RealSequence]; RECORD [ length: NAT, s: SEQUENCE maxLength: NAT OF REF LerpVtx ]; RECORD [ recurseLevel: NAT _ 0, spot: ScanConvert.Spot, vtx: SEQUENCE length: NAT OF LerpVtx ]; Data Structure for trapezoid edges Global Constants Global Variables allocation avoidance structures - caches of peculiar data types Caching Procedures Utility procedures Calculates the integral over the left half of a pyramid function, equal to the left half of a parabolic window or B-spline basis function PROC[dest: REF RealSequence, source: VertexInfo] RETURNS[REF RealSequence]; PROC[dest: REF RealSequence, source: VertexInfo] RETURNS[REF RealSequence]; PROC[spot: Spot] RETURNS[RGB, REAL] Simple, Fast Tilers ShinyTiler for Phong shading and Highlight Utilities Transform the normal to a space in which a normal aligned with the z-axis would reflect the light straight into the eye gotAHilite: BOOLEAN _ FALSE; Get closest point to zero spanned in bounding box Anti-Aliasing Tiler for Fancier shading, etc. Get custom procedures for storing and extracting spot values Do we have a highlight? Do we have mapped texture? get trapezoid given by next higher vertex Get Pixel area coverage weighted by function stored in "weight" if left side more horizontal, check for slope, make top or bottom edge, do right triangle, do new left edge if right side more horizontal do likewise get triangle at right, if both horz. then left edge got middle trapezoid get triangle at right, if both horz. then left edge got middle trapezoid Do middle section Κ+&˜headšœ™Jšœ6™6Icode™,J˜šΟk ˜ Jšœ œ.˜=Jšœ œ6˜EJšœ œ˜!Jšœ œ+˜;Jšœœœ˜&Jšœœ˜$Jšœ œ˜+Jšœœ˜&Jšœ œ=˜NJšœœ‘˜₯Jšœœœ œI˜‹Jšœœ'˜;Jšœœ ˜!Jšœœ˜'Jšœœ˜/Jšœ œ*˜;—J˜—head2šœ œ˜Iašœ{˜ƒNšœ˜J˜Jšœ˜—head3šΟb™Jš œ œœ œœ˜1J˜Jšœœœ˜JšœœΟc˜AJšœœŸ˜FJšœ œ˜#Jšœœ˜#Jšœœ˜1Jšœ œ˜)Jšœœœ œœ œœœ˜VJšœœ˜/Jšœœ˜#Jšœ œ˜+šœ œ˜Jšœœœ™+—šœœ˜/Jš œ œœ œœœ ™B—šœ œ˜%Jš œœ.œ œœ ™j—˜J™"—šœ œœ˜Jšœœœ˜)Jšœœ˜Jšœ œ ˜Jšœ˜—šœ œœ˜Jšœ œ˜Jšœœ˜Jšœœ˜Jšœ!œ ˜1Jšœ˜—šœœœ˜ Jšœœ˜ Jš œœ œœœ ˜0Jšœ˜—šœœœ˜ Jšœœ˜ Jš œœ œœœ˜AJšœ˜—šœœœ˜ Jšœœ˜ Jš œœ œœœ˜:Jšœ˜—šœ œœŸ8˜UJšœœ˜Jšœœ˜Jšœ˜—šœœœ˜"Jšœœ˜ Jš œœ œœœ ˜+Jšœ˜—J˜—šž™Jšœ œ˜Jšœœ'Ÿ˜B—šž™Jšœœ Ÿ"˜@šœœœœŸ˜7Jšœ@™@—Jšœœœ ˜SJšœœ˜Jšœœ Ÿ$˜HJšœœœŸ˜TJšœœ˜JšœœŸ˜JšœœœŸ˜SJšœœ˜JšœœŸ˜JšœœœŸ˜RJšœœ˜JšœœŸ˜JšœœœŸ˜RJšœœ˜Jšœœ˜Jšœ œœŸ˜LJšœœ˜Jšœœ˜—šž™defaultš Οn œœœœœ˜Pšœ,˜,Pšœ˜Pšœ˜—Pšœ"˜"Pšœ&˜&Pšœ˜—P˜š   œœœœœœ˜LJšœœœ˜Pšœœ˜ šœ˜Pšœœ"˜/šœ˜Pšœ&˜&Pšœ"˜"Pšœ œ˜$Pšœœœ#˜GP˜——Pšœ˜ Pšœ˜—š œœœœ˜?Jšœœœ˜šœ&œ˜.Pšœœ,˜>Pšœ,˜,Pšœ˜Pšœ˜—Pšœ"˜"Pšœ&˜&Pšœ˜—š   œœœœ œœ˜SJšœœœ˜Pšœœ ˜šœ˜šœ˜Pšœœ˜Pšœ œ˜(Pšœ œ˜+P˜—šœ˜Pšœ(˜(Pšœ$˜$Pšœ"œ˜&Pšœœ œ˜OPšœœ œ˜RP˜——Pšœ˜ Pšœ˜—š œœœœ˜2Jšœœœ˜šœ(œ˜0Pšœœ/˜BPšœ.˜.Pšœ˜Pšœ˜—Pšœ$˜$Pšœ(˜(Pšœ˜—š   œœœœœœ ˜:Jšœœœ˜Pšœœ ˜šœ˜Pšœœ ˜šœ˜Pšœ$˜$Pšœ"˜"Pšœœ˜"P˜——Pš œ œœœ œ˜XPšœ˜Pšœ˜—š  œœœœ ˜/Jšœœœ˜šœ$œ˜,Pšœœ+˜Jšœœ˜+—Jšœb˜bJšœ ˜ Jšœ˜—šœ4˜4šœœœ$˜>Jšœœ˜1—Jšœ)˜)Jšœ)˜)Jšœ)˜)Jšœ ˜ Jšœ˜—Jšœ!˜(—šœ˜JšœT˜X—Jšœ/˜/Jšœ/˜/Jšœ˜—JšœE˜EJšœ˜J˜J˜——šž4™4š   œœœ œœ ˜OJšœ œ˜&Jšœœœœ˜2Jš œœœœœ˜2Jšœ œ ˜Jšœœ˜Jšœ œ˜ Jš œ œœ/œœ˜RJšœ œ˜'Jšœ"œ˜*Jšœœ˜AJšœ3Ÿ#˜Všœœœ Ÿ˜1šœ4˜6šœœœ˜ Jšœ˜"Jšœ˜—Jšœ˜#—Jšœ˜ Jšœ˜—Jšœ"˜"Jšœ&Ÿ˜EJšœ˜š œœœœŸ/˜]Jšœœ+˜@Jšœ˜—š œœœœŸ&˜Mšœœœ9˜SJšœœ-˜F—Jšœ1˜1Jšœ1˜1Jšœ1˜1Jšœ/˜/Jšœ/˜/Jšœ5˜5šœ˜JšœT˜X—Jšœ˜—Jšœ˜š œœœœŸ0˜\šœœ˜šœœœœ˜"Jšœ œŸ˜:Jšœœ#˜.šœœœ˜Jšœ=˜=Jšœ˜—Jšœ˜—Jšœ˜J˜—Jšœ˜—JšœN˜NJšœ˜Jšœ˜Jšœ˜J˜—JšœœœŸ˜9J™Jš œ œœ˜AJš !œ œœ˜NJ˜š  œœ œœœœœ˜wš  œœ!œ˜EJ™wšœ-Ÿ ˜MPšœP˜P—šœ)Ÿ˜GPšœ2˜2—JšœI˜IJšœœ8Ÿ˜UJšœœ"œ˜HJšœœ4Ÿ˜QJšœœœ˜CJšœœ+Ÿ˜4Jšœœ˜Jšœœ,˜4JšœP˜VJšœ˜—Jšœ œœ™Jšœ œ˜)Jšœ œ+˜9Jšœ œ<˜JJšœœ ˜1Jšœ œ#˜2J˜Jšœ*˜*šœœœ˜+Pš œ œœ6œœ˜WJšœ œ˜&Jšœ œ˜'š œœœœŸ3˜UPšœC˜CJšœœ#˜,Jšœœœ˜;Jšœœœ˜:Jšœ$˜$Jšœ!˜!Jšœ$˜$Jšœ%˜%Jšœ%˜%Jšœ˜Jšœ˜J™1—Jš œœœœœœœ˜HJš œœœœœœœ˜HšœœC˜XJšœœœ˜6Jšœœ˜—Jšœ˜—Jšœœ œ/œ˜PJšœ ˜Jšœ˜——šž-™-š   œœœ œœ ˜OJšœ,œ˜0Jšœ)œ˜-š œœœœ ˜GJšœ0œ˜5šœœ˜Jšœ;˜?Jšœ0˜4—Jšœ ˜Jšœ˜—š œœ#œ ˜Mšœ&˜(Jšœ9˜=—Jšœœ œ ˜>Jšœœ œ ˜=Jšœ"˜"Jšœ˜ Jšœ˜—š  œœœ ˜(Jšœ(œ˜3š œœœœŸ˜7Jšœœ œ˜'Jšœœ˜,Jšœœ˜,Jšœ˜ —š œœœœŸ!˜IJšœœ œ˜'Jšœœœ˜AJšœœœ˜AJšœ˜ —Jšœ,˜,š œœœœŸ˜7Jšœœ œ˜'Jšœœ˜,Jšœœ˜,Jšœ˜ —JšœZ˜Zš œœœœŸ(˜PJšœœ œ˜'Jšœ˜Jšœ˜Jšœ˜ —J˜—Jšœ2œœ˜BJšœ˜Jšœ œœ˜;šœ œœ˜J™<—Jšœœ3˜;šœœ˜ Jšœœœ˜O—šœœ˜JšœœŸ-˜MIshadingšœ"Ÿ˜8—J˜šœœœœ˜CJ™JšŸ™—Jšœ œ/œœ˜Kšœ œœ˜(šœ˜Jšœ œ4˜Bšœ œœ˜Jšœ@˜@Jšœœœ˜2Jšœ˜Jšœ˜—J˜—JšŸ™—Jšœ4˜4šœœœ˜JšœB˜Bšœœœ&œ˜=šœœœ˜Jš œ œœ œœ˜4Jšœ@˜@JšœœŸ'˜@J˜——Jšœœ˜Jšœœ˜JšœŸ˜/Jšœ˜—Jšœ$Ÿ˜Cšœ˜JšœH˜L—Jšœ@Ÿ˜PJšœNŸ ˜[š œœœœŸ˜KJšœ9˜9Jšœ˜—šœœ Ÿ˜:šœœœœ˜"Jšœ9˜9Jšœ˜—šœ%Ÿ&˜KJšœ ˜ Jšœ ˜ Jšœœ!˜)Jšœ˜—J˜—šœœœœœœœŸ˜UJšœJ˜JJšœ˜ —Jšœ˜Jšœ&Ÿ˜7Jšœ˜J˜—š  œœœ œœ˜YJšœœ˜Jšœ œ ˜Jšœ8œ˜=Jšœœ˜'Q˜'š œœœœŸ˜JJšœ˜Jšœ*˜.Jšœ˜ —Jšœ)Ÿ!˜JJšœ!œ˜'Jšœ!˜!J˜ šœœ Ÿ!˜JšœœŸ˜FJšœ)œ ˜9Jšœ,˜,Jšœœ˜J˜—šœœŸ˜GJšœ8œ ˜HJšœ,˜,Jšœœ˜J˜Jšœ)™)—šœ#œ˜-Jšœ!Ÿ˜Ÿ˜SJšœ˜Jšœ"˜&—PšœJ˜JJšœ œ:Ÿ ˜UJšœ˜—J˜—Jšœ˜—Jšœ2Ÿ˜CJšœ/˜/Jšœ˜J˜J˜—J˜—Jšœ˜—…—žJΠ