G3dScanConvertImpl.mesa
Copyright © 1984 by Xerox Corporation. All rights reserved.
Frank Crow, November 3, 1989 4:17:06 pm PST
Scan conversion operations on pixel buffers. Expects input to be properly clipped.
Bloomenthal, February 21, 1989 11:32:14 pm PST
Glassner, September 10, 1989 6:32:34 pm PDT
DIRECTORY
Atom, Basics, Convert, G3dBasic, G3dEdgeBlt, G3dRender, G3dScanConvert, ImagerPixel, ImagerSample, PrincOps, PrincOpsUtils, Real, RealFns, Rope, SF, Terminal;
G3dScanConvertImpl: CEDAR MONITOR
IMPORTS Atom, Basics, Convert, G3dEdgeBlt, G3dRender, ImagerPixel, ImagerSample, PrincOpsUtils, Real, RealFns
EXPORTS G3dScanConvert
~ BEGIN
Type Definitions
LORA:      TYPE ~ LIST OF REF ANY;
RefSeq:      TYPE ~ G3dRender.RefSeq;
ROPE:      TYPE ~ Rope.ROPE;
LongNumber:   TYPE ~ Basics.LongNumber;
BytePair:     TYPE ~ Basics.BytePair;
SampleMap:    TYPE ~ ImagerSample.SampleMap;
EdgeDesc:    TYPE ~ G3dEdgeBlt.EdgeDesc;
EdgeSequence:   TYPE ~ G3dEdgeBlt.EdgeSequence;
RECORD [length: NAT ← 0, s: SEQUENCE maxLength: NAT OF G3dEdgeBlt.EdgeDesc ];
EdgeBltTable:   TYPE ~ G3dEdgeBlt.EdgeBltTable;
Context:     TYPE ~ G3dRender.Context;
RGB:      TYPE ~ G3dRender.RGB;    -- RECORD[ R, G, B: REAL]
RGBSequence:   TYPE ~ G3dRender.RGBSequence;
NatRGB:     TYPE ~ G3dRender.NatRGB;
NatRGBSequence:  TYPE ~ G3dRender.NatRGBSequence;
CtlPoint:     TYPE ~ G3dRender.CtlPoint;
CtlPtInfo:     TYPE ~ G3dRender.CtlPtInfo;
Pixel:      TYPE ~ G3dRender.Pixel;
PixelPart:     TYPE ~ G3dRender.PixelPart;
Box:      TYPE ~ SF.Box;
Pair:      TYPE ~ G3dRender.Pair;    -- RECORD[x, y: REAL]
IntegerPair:    TYPE ~ G3dRender.IntegerPair;  -- RECORD[x, y: INTEGER]
IntegerPairSequence: TYPE ~ G3dRender.IntegerPairSequence;
IntSequence:    TYPE ~ G3dRender.IntSequence;
IntSequenceRep:   TYPE ~ G3dBasic.IntSequenceRep;
RealSequence:   TYPE ~ G3dRender.RealSequence;
RealSequenceRep:  TYPE ~ G3dBasic.RealSequenceRep;
Patch:      TYPE ~ G3dRender.Patch;
Shape:      TYPE ~ G3dRender.Shape;
ShadingClass:   TYPE ~ G3dRender.ShadingClass;
Spot:      TYPE ~ G3dRender.Spot;
TextureFunction:  TYPE ~ G3dRender.TextureFunction;
TextureMap:    TYPE ~ G3dRender.TextureMap;
PixelBuffer:    TYPE ~ ImagerPixel.PixelBuffer;
PixelBufferProc:   TYPE ~ G3dScanConvert.PixelBufferProc;
LinkedPoly:    TYPE ~ RECORD [ lftVtces, rgtVtces: LIST OF CARD16 ];
Renamed Procedures
Round: PROC [REAL] RETURNS [INT] ~ Real.Round;
Fix: PROC [REAL] RETURNS [INT] ~ Real.Fix;
GetProp: PROC [propList: Atom.PropList, prop: REF ANY] RETURNS [REF ANY]
~ Atom.GetPropFromList;
Constants
constantBitBltTable: PrincOps.BitBltTable ← [   -- set up constant values in BitBlt tables
dst: [word: NULL, bit: 0], dstBpl: 0,
src: [word: NULL, bit: 0],
srcDesc: [gray[[yOffset: 0, widthMinusOne: 0, heightMinusOne: 0]]],
height: 1, width: 1,
flags: [direction: forward, disjoint: TRUE, disjointItems: TRUE, gray: TRUE, srcFunc: null, dstFunc: null]
];
longZero: LongNumber ~ [lc[0]];
longOne: LongNumber ~ [lc[1]];
ditherTable: ARRAY [0..4) OF ARRAY [0..4) OF NAT ~
             [[0,12,3,15], [8,4,11,7], [2,14,1,13], [10,6,9,5]];
white: Pixel ~ [255, 255, 255, 0, 0];
Globals
numEdgeSequences: NAT ~ 6;
edgeSequenceCachePtr: NAT ← numEdgeSequences;
edgeSequenceCache: ARRAY [0..numEdgeSequences) OF REF EdgeSequence ← ALL[NIL];
statistics: BOOLEANFALSE;
polyCount, avePixelsPerPoly, aveScanSegLength, avePolyHeight: INT ← 0;
pixelsPerPolyHist: IntSequence;
scanSegLengthHist: IntSequence;
polyHeightHist: IntSequence;
useTextureCoords: BOOLEANFALSE;
Statistical Procedures
InitHistograms: PROCEDURE [maxScanSeg, maxHeight: NAT] ~ {
pixelsPerPolyHist ← NEW[ IntSequenceRep[maxScanSeg * maxHeight] ];
pixelsPerPolyHist.length ← maxScanSeg * maxHeight;
scanSegLengthHist ← NEW[ IntSequenceRep[maxScanSeg] ];
scanSegLengthHist.length ← maxScanSeg;
polyHeightHist ← NEW[ IntSequenceRep[maxHeight] ];
polyHeightHist.length ← maxHeight;
polyCount ← 0;
};
ClearHistograms: PROCEDURE [] ~ {
FOR i: NAT IN [0..pixelsPerPolyHist.length) DO pixelsPerPolyHist[i] ← 0; ENDLOOP;
FOR i: NAT IN [0..scanSegLengthHist.length) DO scanSegLengthHist[i] ← 0; ENDLOOP;
FOR i: NAT IN [0..polyHeightHist.length) DO polyHeightHist[i] ← 0; ENDLOOP;
polyCount ← 0;
};
ShowHistograms: PROCEDURE [context: Context] ~ {
ShowData: PROC[startWd, startHt: REAL, numbers: IntSequence, label: ROPE] ~ {
maxVal: INT ← 0;
lastJ: INT ← 0;
wSize: REAL ← context.viewPort.w;
FOR i: INT IN [0 .. numbers.length) DO
IF maxVal < numbers[i] THEN maxVal ← numbers[i];
ENDLOOP;
FOR i: INT IN [0 .. numbers.length) DO
numbers[i] ← Round[2048 * numbers[i] / maxVal]; -- scale to known max
ENDLOOP;
context.class.draw2DRope[ context, "0", [startWd -.025, startHt -.025], white, .025*wSize ];
context.class.draw2DRope[ context, Convert.RopeFromInt[maxVal],
        [startWd - .06, startHt + .2], white, .025*wSize ];
context.class.draw2DRope[ context, Convert.RopeFromInt[numbers.length],
        [startWd + 0.762, startHt - .025], white, .025*wSize ];
context.class.draw2DRope[context, label, [startWd + 0.1, startHt - .037], white, .025*wSize];
FOR i: INT IN [ 0 .. Round[wSize * 0.75] ) DO
s: REAL ← i / (wSize * 0.75);      -- pctge. across histogram
j: INT ← Fix[ numbers.length * s ];   -- index into histogram   
value: REAL ← numbers[j];
numVals: REAL ← 0;
IF j - lastJ > 1 THEN {
FOR k: INT IN (lastJ .. j) DO
value ← value + numbers[k]; IF numbers[k] > 0 THEN numVals ← numVals + 1;
ENDLOOP;
value ← value / MAX[numVals, 1];
};
s ← 0.75 * s;          -- distance normalized to 3/4 screen   
context.class.draw2DLine[ context,
   [startWd+s, startHt],
   [startWd+s, startHt + ( value / (4*2048) )],
   [255,255,255,0,0] ];
lastJ ← j;
ENDLOOP;
};
maxScanSeg, maxPolyHeight, maxPixelsPerPoly, total, count, largest: INT ← 0;
FOR i: NAT IN [0..pixelsPerPolyHist.length) DO
IF pixelsPerPolyHist[i] > maxPixelsPerPoly THEN maxPixelsPerPoly ← pixelsPerPolyHist[i];
total ← total + i * pixelsPerPolyHist[i];
IF pixelsPerPolyHist[i] > 0 THEN largest ← i
ENDLOOP;
pixelsPerPolyHist.length ← largest+1;
avePixelsPerPoly ← total / polyCount;
ShowData[0.125, 0.1, pixelsPerPolyHist, "Polygon size"];
total ← largest ← count ← 0;
FOR i: NAT IN [0..scanSegLengthHist.length) DO
IF scanSegLengthHist[i] > maxScanSeg THEN maxScanSeg ← scanSegLengthHist[i];
total ← total + i * scanSegLengthHist[i];
count ← count + scanSegLengthHist[i];
IF scanSegLengthHist[i] > 0 THEN largest ← i
ENDLOOP;
scanSegLengthHist.length ← largest+1;
aveScanSegLength ← total / count;
ShowData[0.125, 0.4, scanSegLengthHist, "Scan segment length"];
total ← largest ← count ← 0;
FOR i: NAT IN [0..polyHeightHist.length) DO
IF polyHeightHist[i] > maxPolyHeight THEN maxPolyHeight ← polyHeightHist[i];
total ← total + i * polyHeightHist[i];
count ← count + polyHeightHist[i];
IF polyHeightHist[i] > 0 THEN largest ← i
ENDLOOP;
polyHeightHist.length ← largest+1;
avePolyHeight ← total / count;
ShowData[0.125, 0.7, polyHeightHist, "Polygon height"];
};
Utility Procedures
Swap: PROCEDURE [first, second: INTEGER] RETURNS [INTEGER, INTEGER] = {
RETURN [second, first];
};
SGN: PROCEDURE [number: INTEGER] RETURNS [INTEGER] = INLINE {
Note! This returns zero if input is zero!!
IF number > 0 THEN RETURN[1] ELSE IF number < 0 THEN RETURN[-1] ELSE RETURN[0];
};
InlineIncr: PROC[edge: EdgeDesc, array: REF EdgeSequence ← NIL]
    RETURNS[EdgeDesc] ~ INLINE {
edge.val ← edge.val + edge.lngthIncr;
edge.bias ← edge.bias - 2*edge.hiccups;
IF edge.bias <= 0 THEN {
edge.val ← edge.val + edge.hicIncr;
edge.bias ← edge.bias + 2*edge.length;
};
edge.stepsLeft ← edge.stepsLeft - 1;
IF edge.stepsLeft <= 0        -- Get next linked edge if this one exhausted
THEN IF edge.nextEdge # 0 THEN edge ← array[edge.nextEdge];
RETURN[edge];
};
ShiftL: PROC [val: INTEGER, log2Scale: NAT] RETURNS [INTEGER]  -- shift left
= INLINE { RETURN[INTEGER[Basics.BITSHIFT[ LOOPHOLE[val], log2Scale ]]] };
ShiftR: PROC [val: INTEGER, log2Scale: NAT] RETURNS [INTEGER]  -- shift right  
= INLINE { RETURN[INTEGER[Basics.BITSHIFT[ LOOPHOLE[val], -INTEGER[log2Scale] ]]] };
SubPixel: PROC [position: INTEGER, log2Scale: NAT] RETURNS [INTEGER] ~ {
RETURN[INTEGER[Basics.BITAND[ position, ShiftL[1, log2Scale] - 1 ]]];
};
GetEdgeSeq: ENTRY PROC[length: NAT] RETURNS[REF EdgeSequence] ~ {
ENABLE UNWIND => NULL;
edges: REF EdgeSequence ← NIL;
IF edgeSequenceCachePtr > 0 THEN {
edgeSequenceCachePtr ← edgeSequenceCachePtr - 1;
edges ← edgeSequenceCache[edgeSequenceCachePtr];
edgeSequenceCache[edgeSequenceCachePtr] ← NIL;
};
IF edges = NIL OR length > edges.maxLength THEN edges ← NEW[ EdgeSequence[length] ];
edges.length ← length;
RETURN[ edges ];
};
ReleaseEdgeSeq: ENTRY PROC[edges: REF EdgeSequence] ~ {
ENABLE UNWIND => NULL;
IF edgeSequenceCachePtr < numEdgeSequences THEN {
edgeSequenceCache[edgeSequenceCachePtr] ← edges;
FOR i: NAT IN [0..edgeSequenceCachePtr) DO
IF edges = edgeSequenceCache[i] THEN
SIGNAL G3dRender.Error[$Fatal, "Multiple release of EdgeSeq"];
ENDLOOP;
edgeSequenceCachePtr ← edgeSequenceCachePtr + 1;
};
};
Sqr: PROCEDURE [number: INT16] RETURNS [INT32] ~ INLINE {
RETURN[ number * INT32[number] ]; };
Log2: PROC [n: INT] RETURNS [lg: NAT ← 0] ~ { -- finds log base 2 of input (from M. Plass)
nn: CARD32 ~ n;
k: CARD32 ← 1;
UNTIL k=0 OR k>= nn DO
lg ← lg + 1;
k ← k + k;
ENDLOOP;
};
Power: PUBLIC PROC[ value: CARD16, power: NAT] RETURNS[ result: CARD16 ] ~ {
binaryCount: NAT ← 2*power;   -- makes highlights same size as those by ShadePt
temp: CARD32 ← 65536;
val: CARD32 ← value;
IF power = 0 THEN RETURN[65535];
WHILE binaryCount > 0 DO   -- compute power by repeated squares
IF Basics.BITAND[binaryCount, 1] = 1 THEN temp ← Basics.HighHalf[temp * val];
val ← Basics.HighHalf[val * val];
binaryCount ← binaryCount/2;
ENDLOOP;
result ← temp;
};
SampleMapBase: PROC[samples: SampleMap] RETURNS[CARD32, WORD] ~ {
bytesPerLine: WORD; baseByteAddr: CARD32;
WITH samples SELECT FROM
raster: ImagerSample.RasterSampleMap => {
base: PrincOps.BitAddress ← ImagerSample.GetBase[raster];
baseByteAddr ← CARD32[ Basics.DoubleShift[LOOPHOLE[base.word], 1].li
       + Basics.BITSHIFT[base.bit, -3] ];
bytesPerLine ← Basics.BITSHIFT[ImagerSample.GetBitsPerLine[raster], -3];
};
ENDCASE => SIGNAL G3dRender.Error[$MisMatch, "only RasterSampleMaps here"];
RETURN[ baseByteAddr, bytesPerLine];
};
DoForPixelColors: PROC[ context: Context,
        action: PROC[dstAddr: CARD32, xStep, yStep: WORD, element: PixelPart]
       
] ~ {
base: CARD32; bpl: WORD; depth, alpha: REF NAT;
SELECT context.class.displayType FROM
$FullColor => {
[base, bpl] ← SampleMapBase[context.pixels[0]]; action[base, 1, bpl, r];
[base, bpl] ← SampleMapBase[context.pixels[1]]; action[base, 1, bpl, g];
[base, bpl] ← SampleMapBase[context.pixels[2]]; action[base, 1, bpl, b];
};
$PseudoColor, $Gray => {
[base, bpl] ← SampleMapBase[context.pixels[0]]; action[base, 1, bpl, r];
};
ENDCASE => SIGNAL G3dRender.Error[$MisMatch, "Unexpected display type"];
alpha ← NARROW[ GetProp[context.displayProps, $Alpha] ];
IF alpha # NIL THEN
{ [base, bpl] ← SampleMapBase[context.pixels[alpha^]]; action[base, 2, bpl, a]; };
depth ← NARROW[ GetProp[context.displayProps, $Depth] ];
IF depth # NIL THEN
{ [base, bpl] ← SampleMapBase[context.pixels[depth^]]; action[base, 2, bpl, z]; };
};
ShowCoords: PROC[poly: REF Patch] RETURNS[list: LIST OF REF IntegerPair] ~ {
FOR i: CARD16 DECREASING IN [0..poly.nVtces) DO
p: REF IntegerPair ← NEW[IntegerPair ← [Round[poly[i].coord.sx], Round[poly[i].coord.sy]]];
list ← CONS[p, list];
ENDLOOP;
RETURN[list];
};
MappedRGB: PUBLIC PROC[renderMode: ATOM, clr: RGB] RETURNS[NAT] ~ {
SELECT renderMode FROM 
$Dithered  => {
mapVal: NAT ← Fix[clr.R*4.999]*24
     + Fix[clr.G*5.999]*4
     + Fix[clr.B*3.999];
IF mapVal >= 60 THEN mapVal ← mapVal + 135;   -- move to top of map
RETURN[ mapVal ];
};
$PseudoColor => RETURN[
Fix[clr.R*5.999]*42 + Fix[clr.G*6.999]*6 + Fix[clr.B*5.999] + 2
];
ENDCASE  => SIGNAL G3dRender.Error[$MisMatch, "Bad Render Mode"];
RETURN[ 255 ];
};
RGBFromMap: PUBLIC PROC[renderMode: ATOM, value: NAT] RETURNS[RGB] ~ {
SELECT renderMode FROM
$Dithered  => {
IF value >= 60 THEN value ← value - 135;   -- move from top of map
value ← MIN[119, value];
RETURN[ [
R: (value / 24) / 5.0,
G: (value MOD 24) / 4 / 6.0,
B: (value MOD 4) / 4.0
] ];
};
$PseudoColor => {
value ← MIN[253, value] - 2;
RETURN[ [
R: (value / 42) / 6.0,
G: (value MOD 42) / 6 / 7.0,
B: (value MOD 6) / 6.0
] ];
};
ENDCASE  => SIGNAL G3dRender.Error[$MisMatch, "Bad Render Mode"];
RETURN[[255, 255, 255]];
};
Pixel Operations
DoWithPixels: PUBLIC PROC [ context: Context, start: IntegerPair, length: NAT,
         proc: PixelBufferProc ] ~ {
pixels: PixelBuffer ← ImagerPixel.ObtainScratchPixels[
context.pixels.samplesPerPixel, length
];
fMin: INTEGER ← context.pixels.box.min.f;
sMin: INTEGER ← context.pixels.box.min.s;
initIndex: SF.Vec ← [ f: MAX[fMin, start.x + fMin], s: start.y + sMin ];
delta: SF.Vec ← [ f: 1, s: 0 ];
ImagerPixel.GetPixels[             -- get pixels for segment
self: context.pixels, pixels: pixels,
initIndex: initIndex, delta: delta, count: length
];
proc[pixels];              -- call back with requested pixels
ImagerPixel.PutPixels[             -- return modified pixels
self: context.pixels, pixels: pixels,
initIndex: initIndex, delta: delta, count: length
];
ImagerPixel.ReleaseScratchPixels[pixels];
};
Write: PROC [ dstVal, srcVal: INT32 ] ~ INLINE {
dstAddr: LONG POINTERLOOPHOLE[Basics.DoubleShiftRight[LOOPHOLE[dstVal], 1]];
srcValue: BYTE ← LOOPHOLE[srcVal, LongNumber.bytes].ll; -- lo byte, lo half of long
IF Basics.DoubleAnd[LOOPHOLE[dstVal], longOne] # longZero -- lo byte? (right pixel)
THEN TRUSTED { LOOPHOLE[dstAddr^, BytePair].lowsrcValue; } -- right pixel
ELSETRUSTED { LOOPHOLE[dstAddr^, BytePair].high ← srcValue; }; -- left pixel
};
Dither: PROC [ dst, r, g, b, scanline: INT32 ] ~ {
Ordered dither for crude looks at full-color, $PseudoColor lookup table assumed
dstAddr: LONG POINTER TO INT16LOOPHOLE[Basics.DoubleShiftRight[LOOPHOLE[dst], 1]];
srcValue: BYTE;
red: INT16 ← LOOPHOLE[r, LongNumber.bytes].ll; -- lowest byte
grn: INT16 ← LOOPHOLE[g, LongNumber.bytes].ll; -- of longword
blu: INT16 ← LOOPHOLE[b, LongNumber.bytes].ll;
y: NAT ← Basics.BITAND[scanline, 3];
x: NAT ← Basics.BITAND[Basics.LowHalf[dst], 3];
threshold: NAT ← ditherTable[x][y];  -- calculate x and y table coordinates (4 x 4 table)
valR: NAT ← Basics.BITSHIFT[ Basics.BITSHIFT[red,2] + red, -4 ];  -- (red * 5) / 16
valG: NAT ← Basics.BITSHIFT[ Basics.BITSHIFT[grn,2] + Basics.BITSHIFT[grn,1], -4 ];
valB: NAT ← Basics.BITSHIFT[ Basics.BITSHIFT[blu,2] + blu, -4 ];  -- (blu * 5) / 16
val2R, val2G, val2B: NAT;
val2R ← Basics.BITSHIFT[valR,-4];           -- valR / 16
IF Basics.BITAND[valR,15] > threshold THEN val2R ← val2R + 1;  -- valr MOD 16
val2G ← Basics.BITSHIFT[valG,-4];
IF Basics.BITAND[valG,15] > threshold THEN val2G ← val2G + 1;
val2B ← Basics.BITSHIFT[valB,-4];
IF Basics.BITAND[valB,15] > threshold THEN val2B ← val2B + 1;
srcValue ← MIN[ 255,
Basics.BITSHIFT[val2R,5] + Basics.BITSHIFT[val2R,3] + Basics.BITSHIFT[val2R,1]
+ Basics.BITSHIFT[val2G,2] + Basics.BITSHIFT[val2G,1]
+ val2B + 2 ];     --val2R*42 + val2G*6 + val2B + 2
IF Basics.DoubleAnd[LOOPHOLE[dst], longOne] # longZero -- lo byte? (right pixel)
THEN TRUSTED { LOOPHOLE[dstAddr^, BytePair].lowsrcValue; } -- right pixel
ELSETRUSTED { LOOPHOLE[dstAddr^, BytePair].high ← srcValue; }; -- left pixel
};
Mat: PROC [ rDst, gDst, bDst, aDst, r, g, b, a: INT32 ] ~ {
};
DepthLess: PROC [ zDst, zSrc: INT32 ] RETURNS [ BOOLEAN ] ~ TRUSTED { -- INLINE
dstAddr: LONG POINTER TO CARD16LOOPHOLE[
Basics.DoubleShiftRight[LOOPHOLE[zDst], 1]];
IF dstAddr^ < LOOPHOLE[zSrc, LongNumber.pair].lo
THEN RETURN[FALSE]    -- old value closer
ELSE { dstAddr^ ← LOOPHOLE[zSrc, LongNumber.pair].lo; RETURN[TRUE]; };
};
Scan Conversion for Lines
PutLine: PUBLIC PROC [context: Context, p1, p2: IntegerPair, color1, color2: Pixel ] ~ {
DoLine: PROC[dstAddr: CARD32, xStep, yStep: WORD, element: PixelPart] ~ {
clrValue1: CARD16SELECT element FROM
r => color1[r], g => color1[g], b => color1[b],
a => color1[a], z => color1[z], ENDCASE => ERROR;
clrValue2: CARD16SELECT element FROM
r => color2[r], g => color2[g], b => color2[b],
a => color2[a], z => color2[z], ENDCASE => ERROR;
src, dst: G3dEdgeBlt.EdgeDesc;
dstAddr ← dstAddr + p1.y * INT[yStep] + p1.x; -- from base to line endpt
IF tall
THEN dst ← [ val: dstAddr, length: ABS[height], hiccups: ABS[width],
    lngthIncr: yStep * SGN[height], hicIncr: xStep * SGN[width] ]
ELSE dst ← [ val: dstAddr, length: ABS[width], hiccups: ABS[height],
    lngthIncr: xStep * SGN[width], hicIncr: yStep * SGN[height] ];
IF clrValue1 = clrValue2 OR dst.length = 0
THEN src ← [ val: clrValue1, length: 0, indirect: FALSE ] -- constant shade along line
ELSE {
clrDiff: INTEGERINTEGER[clrValue2] - INTEGER[clrValue1]; -- varying shade
src.val ← clrValue1;
src.length ← dst.length;
[src.lngthIncr, src.hiccups] ← Basics.DivMod[ABS[clrDiff], dst.length];
IF clrDiff < 0        -- color moving negatively?
THEN { src.lngthIncr ← -src.lngthIncr; src.hicIncr ← -1; }
ELSE src.hicIncr ← 1;
src.indirect ← FALSE;
};
G3dEdgeBlt.Blt[[dst, src]];      -- draw line including endpoints
};
box: Box ← context.pixels.box;
checkLimits: NAT;
tall: BOOLEANFALSE;
length, hiccups: NAT;
width: INTEGER ← p2.x - p1.x;
height: INTEGER ← p2.y - p1.y;
IF ABS[width] > ABS[height]
THEN { length ← ABS[width]; hiccups ← ABS[height]; tall ← FALSE; }
ELSE { length ← ABS[height]; hiccups ← ABS[width]; tall ← TRUE; };
box ← [ [0, 0], [box.max.s - box.min.s - 1, box.max.f - box.min.f - 1] ]; -- normalize box
checkLimits ← p1.x-box.min.f; checkLimits ← p2.x-box.min.f; -- raise bounds error if < 0
checkLimits ← p1.y-box.min.s; checkLimits ← p2.y-box.min.s;
checkLimits ← box.max.f-p1.x; checkLimits ← box.max.f-p2.x;
checkLimits ← box.max.s-p1.y; checkLimits ← box.max.s-p2.y;
DoForPixelColors[context, DoLine];
};
Scan Conversion for Convex Areas
MakeDstEdge: PROC[bot, top: CtlPoint, dstAddr: CARD32, xStep, yStep: WORD]
     RETURNS[edge: EdgeDesc] ~ {
Build destination address edge description
pLo: IntegerPair ← [ Round[bot.sx], Round[bot.sy] ];
pHi: IntegerPair ← [ Round[top.sx], Round[top.sy] ];
width: INTEGER ← pHi.x - pLo.x;
length: INTEGER ← pHi.y - pLo.y;
IF length <= 0 THEN { edge.length ← 0; RETURN[edge]; };
edge.val ← dstAddr + pLo.y * INT[yStep] + pLo.x * INT[xStep]; -- from base to edge bottom
edge.length ← length;
edge.hiccups ← ABS[width];
[edge.lngthIncr, edge.hiccups] ← Basics.DivMod[ABS[width], edge.length];
IF width < 0        -- x-position moving negatively?
THEN { edge.lngthIncr ← -edge.lngthIncr; edge.hicIncr ← -xStep; }
ELSE edge.hicIncr ← xStep;
edge.lngthIncr ← edge.lngthIncr * xStep + yStep; -- add in scanline to scanline step size
edge.bias ← edge.length;  -- initial bias to center hiccups
edge.stepsLeft ← edge.length;    -- set stepsLeft for count down
};
MakeSrcEdge: PROC[bot, top: CtlPtInfo, element: PixelPart]
     RETURNS[edge: EdgeDesc] ~ {
Build source value edge description
yStart: CARD16 ← Round[bot.coord.sy]; yEnd: CARD16 ← Round[top.coord.sy];
length: INTEGERINTEGER[yEnd] - INTEGER[yStart];
srcStart, srcEnd: CARD16;
width: INT16;
IF length <= 0 THEN { edge.length ← 0; RETURN[edge]; };
SELECT element FROM
r => { srcStart ← Fix[bot.shade.er * 255.0]; srcEnd ← Fix[top.shade.er * 255.0]; };
g => { srcStart ← Fix[bot.shade.eg * 255.0]; srcEnd ← Fix[top.shade.eg * 255.0]; };
b => { srcStart ← Fix[bot.shade.eb * 255.0]; srcEnd ← Fix[top.shade.eb * 255.0]; };
a => { srcStart ← Fix[bot.shade.et * 255.0]; srcEnd ← Fix[top.shade.et * 255.0]; };
z => { srcStart ← Round[bot.coord.sz];    srcEnd ← Round[top.coord.sz]; };
ENDCASE => ERROR;
width ← srcEnd - INT32[srcStart];
edge.val ← srcStart;         -- initial value
edge.length ← length;
edge.hiccups ← ABS[width];
[edge.lngthIncr, edge.hiccups] ← Basics.DivMod[ABS[width], edge.length];
IF width < 0        -- color moving negatively?
THEN { edge.lngthIncr ← -edge.lngthIncr; edge.hicIncr ← -1; }
ELSE edge.hicIncr ← 1;
edge.bias ← edge.length;  -- initial bias to center hiccups
edge.stepsLeft ← edge.length;    -- set stepsLeft for count down
};
LinkEdges: PROC [ poly: REF Patch, box: Box] RETURNS [LinkedPoly] ~ {
Link vertices into left side and right side chains
checkLimits: NAT;
lft, rgt: LIST OF CARD16NIL;
least, most: REAL ← poly[0].coord.sy; topVtx, botVtx, vtx: CARD16 ← 0;
box ← [ [0, 0], [box.max.s - box.min.s - 1, box.max.f - box.min.f - 1] ]; -- normalize box
FOR i: CARD16 IN [1..poly.nVtces) DO      -- find top and bottom vertex
p: IntegerPair ← [ Round[poly[i].coord.sx], Round[poly[i].coord.sy] ];
checkLimits ← p.y-box.min.s; checkLimits ← p.x-box.min.f;  -- check bounds
checkLimits ← box.max.s-p.y; checkLimits ← box.max.f-p.x;
IF poly[i].coord.sy < least THEN { least ← poly[i].coord.sy; botVtx ← i; }
ELSE IF poly[i].coord.sy > most THEN { most ← poly[i].coord.sy; topVtx ← i; };
ENDLOOP;
IF Fix[most] > Fix[least] THEN {
vtx ← topVtx; lft ← CONS[topVtx, lft];
WHILE vtx # botVtx DO           -- walk down left side
vtx ← vtx + 1; IF vtx = poly.nVtces THEN vtx ← 0;
lft ← CONS[ vtx, lft ];
ENDLOOP;
vtx ← topVtx; rgt ← CONS[topVtx, rgt];
WHILE vtx # botVtx DO           -- walk down right side
vtx ← IF vtx = 0 THEN poly.nVtces - 1 ELSE vtx - 1;
rgt ← CONS[vtx, rgt];
ENDLOOP;
};
RETURN[ [lft, rgt] ];
};
LinkDst: PROC[ dst: REF EdgeSequence, links: LIST OF CARD16, plygn: REF Patch,
     ptr, size: NAT, dstAddr: CARD32, xStep, yStep: WORD] ~ {
FOR list: LIST OF CARD16 ← links, list.rest UNTIL list.rest = NIL DO
dst[ptr] ← MakeDstEdge[
plygn[list.first].coord, plygn[list.rest.first].coord, dstAddr, xStep, yStep
];
IF dst[ptr].length > 0 THEN {
IF ptr - size >= 0 THEN dst[ptr-size].nextEdge ← ptr;  -- link to last edge
ptr ← ptr + size;
};
ENDLOOP;
};
LinkSrc: PROC[ src: REF EdgeSequence, links: LIST OF CARD16, plygn: REF Patch,
     ptr, size: NAT, element: PixelPart] ~ { 
FOR list: LIST OF CARD16 ← links, list.rest UNTIL list.rest = NIL DO
src[ptr] ← MakeSrcEdge[ plygn[list.first], plygn[list.rest.first], element ];
IF src[ptr].length > 0 THEN {
IF ptr - size >= 0 THEN src[ptr-size].nextEdge ← ptr;  -- link to last edge
ptr ← ptr + size;
};
ENDLOOP;
};
FastFlatTiler: PUBLIC PROC [context: Context, plygn: REF Patch, color: Pixel] ~ {
DoPoly: PROC[dstAddr: CARD32, xStep, yStep: WORD, element: PixelPart] ~ {
lft: REF EdgeSequence ← GetEdgeSeq[plygn.nVtces];
rgt: REF EdgeSequence ← GetEdgeSeq[plygn.nVtces];
clrValue: CARD16SELECT element FROM
r => color[r], g => color[g], b => color[b], z => color[z], ENDCASE => ERROR;
IF element # z         -- load high half of word to make brick for bitblt
THEN LOOPHOLE[clrValue, Basics.ShortNumber].hi ← clrValue;
LinkDst[lft, links.lftVtces, plygn, 0, 1, dstAddr, xStep, yStep]; -- chains for g3dEdgeBlt
LinkDst[rgt, links.rgtVtces, plygn, 0, 1, dstAddr, xStep, yStep];
IF lft[0].length # 0 AND rgt[0].length # 0 THEN TRUSTED {  -- not a zero-height poly
bb^ ← constantBitBltTable;     -- set up constant values in BitBlt table
bb.dstBpl ← Basics.BITSHIFT[yStep, 3];
bb.src.word ← @clrValue;
WHILE TRUE DO -- write scan segment with bitblt, then bump to next edge
width: INT16 ← rgt[0].val - lft[0].val;
IF width < 0 OR width > INT16[yStep] THEN width ← 0;  -- twisted polygon
bb.dst ← [word: LOOPHOLE[Basics.DoubleShiftRight[LOOPHOLE[lft[0].val], 1]],
   bit: Basics.BITSHIFT[ Basics.BITAND[ Basics.LowHalf[lft[0].val], 1], 3] ];
bb.width ← Basics.BITSHIFT[width + 1, 3];   -- convert from bytes to bits
PrincOpsUtils.BITBLT[bb];             -- do bitblt
lft[0] ← InlineIncr[lft[0], lft]; rgt[0] ← InlineIncr[rgt[0], rgt]; -- incr. edges
IF lft[0].stepsLeft = 0 OR rgt[0].stepsLeft = 0 THEN EXIT
ENDLOOP;
};
ReleaseEdgeSeq[lft]; ReleaseEdgeSeq[rgt];
};
links: LinkedPoly;
bbspace: PrincOps.BBTableSpace;         -- get BitBlt table
bb: PrincOps.BitBltTablePtr;
TRUSTED { bb ← PrincOpsUtils.AlignedBBTable[@bbspace]; };
SELECT context.class.displayType FROM
$PseudoColor =>
color[r] ← 42 * (color[r] * 6 / 256) + 6 * (color[g] * 7 / 256) + (color[b] * 6 / 256) +2;
$Gray => color[r] ← (color[r] + color[g] + color[b]) / 3;
ENDCASE;
links ← LinkEdges[ plygn, context.pixels.box ]; -- link vertices into left and right side chains
IF links.lftVtces # NIL THEN DoForPixelColors[context, DoPoly];
};
ScanPoly: PROC [context: Context, lftDst, lftSrc, rgtDst, rgtSrc: REF EdgeSequence,
     dstSize, srcSize, dstDpth, srcDpth, scanline: NAT,
     pixelProc: PROC[scanDst, scanSrc: REF EdgeSequence, scanline: NAT] ← NIL] ~ {
If not a zero-height poly then increment down edges and across scan segments
polyHeight, pixelCount: NAT ← 0;
dithering: BOOLEANIF context.class.displayType = $PseudoColor THEN TRUE ELSE FALSE;
clrsPerPixel: NATIF context.class.displayType = $FullColor THEN 3 ELSE 1;
scanSrc: REF EdgeSequence ← GetEdgeSeq[srcSize];
scanDst: REF EdgeSequence ← GetEdgeSeq[dstSize];
IF lftDst[0].length # 0 AND rgtDst[0].length # 0 THEN WHILE TRUE DO
segLength: INT16 ← rgtDst[0].val - lftDst[0].val + 1;
IF segLength <= 0 OR segLength > lftDst[0].lngthIncr THEN EXIT; -- twisted or backfacing
FOR i: NAT IN [0..dstSize) DO      -- build scan segment destinations
scanDst[i] ← [ val: lftDst[i].val, length: segLength, lngthIncr: ABS[lftDst[i].hicIncr] ];
scanDst[i].bias ← scanDst[i].stepsLeft ← segLength;
ENDLOOP;
FOR i: NAT IN [0..srcSize) DO      -- build scan segment sources
width: INT16 ← rgtSrc[i].val - lftSrc[i].val;
scanSrc[i] ← [val: lftSrc[i].val, length: segLength, indirect: FALSE ];
[scanSrc[i].lngthIncr, scanSrc[i].hiccups] ← Basics.DivMod[ABS[width], segLength];
IF width < 0          -- color/z moving negatively?
THEN { scanSrc[i].lngthIncr ← -scanSrc[i].lngthIncr; scanSrc[i].hicIncr ← -1; }
ELSE scanSrc[i].hicIncr ← 1;
scanSrc[i].bias ← scanSrc[i].stepsLeft ← segLength;
ENDLOOP;
IF statistics THEN {         -- gather statistics on polygon sizes
polyHeight ← polyHeight + 1;
pixelCount ← pixelCount + segLength;
IF CARD16[segLength] >= scanSegLengthHist.length
THEN segLength ← scanSegLengthHist.length - 1;  -- catch overflowing values
scanSegLengthHist[segLength] ← scanSegLengthHist[segLength] + 1; -- histogram
};
WHILE TRUE DO          -- Do scan segment, pixel by pixel
IF NOT context.depthBuffering
OR DepthLess[scanDst[dstDpth].val, scanSrc[srcDpth].val] THEN { -- test and put z
IF pixelProc # NIL
THEN { pixelProc[scanDst, scanSrc, scanline]; IF context.stopMe^ THEN RETURN; }
ELSE IF dithering
THEN Dither[
scanDst[0].val, scanSrc[0].val, scanSrc[1].val, scanSrc[2].val, scanline ]
ELSE FOR i: NAT IN[0..clrsPerPixel) DO
Write[scanDst[i].val, scanSrc[i].val];
ENDLOOP;
};
FOR i: NAT IN [0..srcSize) DO scanSrc[i] ← InlineIncr[scanSrc[i]]; ENDLOOP;
FOR i: NAT IN [0..dstSize) DO scanDst[i] ← InlineIncr[scanDst[i]]; ENDLOOP;
IF scanDst[0].stepsLeft = 0 THEN EXIT
ENDLOOP;
FOR i: NAT IN [0..srcSize) DO
lftSrc[i] ← InlineIncr[lftSrc[i], lftSrc]; rgtSrc[i] ← InlineIncr[rgtSrc[i], rgtSrc];
ENDLOOP;
FOR i: NAT IN [0..dstSize) DO
lftDst[i] ← InlineIncr[lftDst[i], lftDst]; rgtDst[i] ← InlineIncr[rgtDst[i], rgtDst];
ENDLOOP;
IF lftDst[0].stepsLeft = 0 OR rgtDst[0].stepsLeft = 0 THEN EXIT;
scanline ← scanline + 1;
ENDLOOP;
ReleaseEdgeSeq[scanSrc]; ReleaseEdgeSeq[scanDst];
IF statistics THEN {         -- gather statistics on polygon sizes
polyCount ← polyCount + 1;
IF polyHeight >= polyHeightHist.length THEN polyHeight ← polyHeightHist.length - 1;
polyHeightHist[polyHeight] ← polyHeightHist[polyHeight] + 1;
IF pixelCount >= pixelsPerPolyHist.length THEN pixelCount ← pixelsPerPolyHist.length - 1;
pixelsPerPolyHist[pixelCount] ← pixelsPerPolyHist[pixelCount] + 1;
};
};
LerpTiler: PUBLIC PROC [context: Context, plygn: REF Patch] ~ {
lftSrc, rgtSrc, lftDst, rgtDst: REF EdgeSequence ← NIL;
scanline, srcSize, dstSize, dstDpth, srcDpth, srcPos: NAT ← 0;
srcTmplate: Pixel ← IF context.class.displayType = $Gray THEN [1,0,0,0,0] ELSE [1,1,1,0,0];
dstTmplate: Pixel ← IF context.class.displayType = $FullColor THEN [1,1,1,0,0] ELSE [1,0,0,0,0];
dstBufPos: Pixel ← [0,1,2,0,0];
alpha: REF NATNARROW[ GetProp[context.displayProps, $Alpha]];
depth: REF NATNARROW[ GetProp[context.displayProps, $Depth]];
links: LinkedPoly;
IF alpha # NIL THEN { dstBufPos[a] ← alpha^; srcTmplate[a] ← dstTmplate[a] ← 2; };
IF depth # NIL THEN { dstBufPos[z] ← depth^; srcTmplate[z] ← dstTmplate[z] ← 2; };
FOR i: PixelPart IN PixelPart DO
IF srcTmplate[i] > 0 THEN srcSize ← srcSize + 1;
IF dstTmplate[i] > 0 THEN dstSize ← dstSize + 1;
ENDLOOP;
IF depth # NIL THEN { dstDpth ← dstSize-1; srcDpth ← srcSize-1; };
links ← LinkEdges[ plygn, context.pixels.box ]; -- link vertices into left and right side chains
IF links.lftVtces # NIL THEN {        -- if non-zero height
scanline ← Fix[plygn[links.lftVtces.first].coord.sy];    -- get first scanline
lftSrc ← GetEdgeSeq[srcSize*plygn.nVtces]; rgtSrc ← GetEdgeSeq[srcSize*plygn.nVtces];
lftDst ← GetEdgeSeq[dstSize*plygn.nVtces]; rgtDst ← GetEdgeSeq[dstSize*plygn.nVtces];
FOR i: PixelPart IN PixelPart DO    --Get Edge records for left and right sides
IF dstTmplate[i] > 0 THEN {
dstAddr, yStep: CARD32;
[dstAddr, yStep] ← SampleMapBase[context.pixels[dstBufPos[i]]];
LinkDst[ lftDst, links.lftVtces, plygn,
   dstBufPos[i], dstSize, dstAddr, dstTmplate[i], yStep ];
LinkDst[ rgtDst, links.rgtVtces, plygn,
   dstBufPos[i], dstSize, dstAddr, dstTmplate[i], yStep ];
};
IF srcTmplate[i] > 0 THEN {
LinkSrc[lftSrc, links.lftVtces, plygn, srcPos, srcSize, i ];
LinkSrc[rgtSrc, links.rgtVtces, plygn, srcPos, srcSize, i ];
srcPos ← srcPos + 1;
};
ENDLOOP;
ScanPoly[context, lftDst, lftSrc, rgtDst, rgtSrc, dstSize, srcSize, dstDpth, srcDpth, scanline];
ReleaseEdgeSeq[lftSrc]; ReleaseEdgeSeq[rgtSrc];
ReleaseEdgeSeq[lftDst]; ReleaseEdgeSeq[ rgtDst];
};
};
justNoticeable: NAT ~ Round[G3dScanConvert.justNoticeable * 65536];
spot: REF Spot ← NIL;
HiliteTiler: PUBLIC PROC [context: Context, plygn: REF Patch, shininess: NAT] ~ {
SimpleTexture: PROC[ red, grn, blu: CARD16, map: ImagerPixel.PixelMap, type: ATOM,
       ix, iy: INTEGER ]
     RETURNS [ newRed, newGrn, newBlu: CARD16 ] ~ {
GetTxtrAddress: PROC[buf: ImagerPixel.PixelMap, ix, iy: INTEGER]
RETURNS[ txtrX, txtrY: INTEGER ] ~ {
x: REAL ← 1.0 * ix / (LAST[NAT]/32);
y: REAL ← 1.0 * iy / (LAST[NAT]/32);
bufWidth: NAT ← buf.box.max.f - buf.box.min.f;
bufHeight: NAT ← buf.box.max.s - buf.box.min.s;
txtrX ← Fix[x * bufWidth] MOD bufWidth;
IF txtrX < 0 THEN txtrX ← txtrX + bufWidth;
txtrY ← Fix[y * bufHeight] MOD bufHeight;
IF txtrY < 0 THEN txtrY ← txtrY + bufHeight;
};
pixel: ImagerPixel.PixelBuffer ← ImagerPixel.ObtainScratchPixels[map.samplesPerPixel, 1];
x, y: INTEGER;
[x, y] ← GetTxtrAddress[map, ix, iy];
ImagerPixel.GetPixels[self: map, pixels: pixel, initIndex: [f: x, s: y+map.box.min.s], count: 1];
SELECT type FROM
$Color => {
red ← red * pixel[0][0] / 256;
grn ← grn * pixel[1][0] / 256;
blu ← blu * pixel[2][0] / 256;
};
$Intensity => {
red ← red * pixel[0][0] / 256;
grn ← grn * pixel[0][0] / 256;
blu ← blu * pixel[0][0] / 256;
};
ENDCASE  => SIGNAL G3dRender.Error[
$MisMatch, "Unknown texture type, or antialiasing needed"
];
ImagerPixel.ReleaseScratchPixels[pixel];
RETURN[red, grn, blu];
};
TextureFn: PROC[ red, grn, blu: CARD16, txtrFn: REF TextureFunction,
       x, y, z, dx, dy, dz: INT ]
     RETURNS [ newRed, newGrn, newBlu: CARD16 ] ~ {
dx, dy, dz: REAL ← 0;
IF spot = NIL THEN {
spot ← NEW[Spot];
spot.val ← NEW[RealSequenceRep[6]];   spot.val.length ← 6;
spot.yIncr ← NEW[RealSequenceRep[6]];  spot.yIncr.length ← 6;
spot.xIncr ← NEW[RealSequenceRep[6]];  spot.xIncr.length ← 6;
spot.yIncr[3] ← spot.yIncr[4] ← spot.yIncr[5] ← 0.0;
spot.xIncr[3] ← spot.xIncr[4] ← spot.xIncr[5] ← 0.0;
};
spot.val[0] ← red/255.0; spot.val[1] ← grn/255.0; spot.val[2] ← blu/255.0;
spot.val[3] ← 1.0 * x / (LAST[NAT]/32);  
spot.val[4] ← 1.0 * y / (LAST[NAT]/32);  
spot.val[5] ← 1.0 * z / (LAST[NAT]/32);
IF (lx # 0.0 OR ly # 0.0 OR lz # 0.0) THEN
{ dx ← ABS[spot.val[3] - lx]; dy ← ABS[spot.val[4] - ly]; dz ← ABS[spot.val[5] - lz]; };
lx ← spot.val[3]; ly ← spot.val[4]; lz ← spot.val[5];
spot.xIncr[3] ← (1.0 * dx / (LAST[NAT]/32)) / (LAST[NAT]/32); 
spot.xIncr[4] ← (1.0 * dy / (LAST[NAT]/32)) / (LAST[NAT]/32); 
spot.xIncr[5] ← (1.0 * dz / (LAST[NAT]/32)) / (LAST[NAT]/32);
txtrFn.proc[context, plygn.renderData.shadingClass, spot, txtrFn.props];
RETURN[
Real.Round[spot.val[0]*255], Real.Round[spot.val[1]*255], Real.Round[spot.val[2]*255]
];
};
Hilight: PROC[ scanDst, scanSrc: REF EdgeSequence, scanline: NAT ] ~ {
red, grn, blu: CARD16 ← 0;
hltRed, hltGrn, hltBlu: CARD16 ← 0;
reflStart: NAT ← srcSize - hltCnt * 2;
hltStart: NAT ← 0;
noticeableHilite: BOOLEANFALSE;
red ← scanSrc[0].val;
IF NOT gray THEN { -- if gray, scanSrc[1].val, scanSrc[2].val are not grn & blu
grn ← scanSrc[1].val;
blu ← scanSrc[2].val;
};
IF texture THEN {
WITH plygn.renderData.shadingClass.texture.first SELECT FROM  -- only one texture
txtrMap: REF TextureMap =>   -- modify with mapped texture
WITH txtrMap.pixels SELECT FROM
buf: ImagerPixel.PixelMap =>
[red, grn, blu] ← SimpleTexture[
red, grn, blu, buf, txtrMap.type,
scanSrc[reflStart-3].val, scanSrc[reflStart-2].val
];
ENDCASE => G3dRender.Error[$MisMatch, "Only simple mapped texture"];
txtrFn: REF TextureFunction => {    -- solid or other function-based texture
j: NAT ← reflStart-3; s: INTLAST[NAT]/32;
[red, grn, blu] ← TextureFn[
red, grn, blu, txtrFn,
scanSrc[j].val, scanSrc[j+1].val, scanSrc[j+2].val,
s*scanSrc[j].lngthIncr
  + s*(scanSrc[j].hicIncr * scanSrc[j].hiccups)/scanSrc[j].length,
s*scanSrc[j+1].lngthIncr
  + s*(scanSrc[j+1].hicIncr * scanSrc[j+1].hiccups)/scanSrc[j+1].length,
s*scanSrc[j+2].lngthIncr
  + s*(scanSrc[j+2].hicIncr * scanSrc[j+2].hiccups)/scanSrc[j+2].length
];
};
ENDCASE => SIGNAL G3dRender.Error[$Unimplemented, "Unexpected texture type"];
};
FOR i: NAT IN [hltStart..hltCnt) DO
j: NAT ← reflStart + i * 2;
sqrX: INT32 ← Sqr[ scanSrc[j].val*2 ];  -- scale to full card range from half integer
sqrY: INT32 ← Sqr[ scanSrc[j+1].val*2 ];
pctHilite: CARD32 ← Power[ 2 * Basics.HighHalf[LAST[INT32] - (sqrX+sqrY)], shininess ];
IF pctHilite > justNoticeable THEN { -- Scale light color by hilite strength
hltRed ← MIN[ hltRed + CARD32[Basics.HighHalf[pctHilite * lightColor[i].r]], 65535 ];
hltGrn ← MIN[ hltGrn + CARD32[Basics.HighHalf[pctHilite * lightColor[i].g]], 65535 ];
hltBlu ← MIN[ hltBlu + CARD32[Basics.HighHalf[pctHilite * lightColor[i].b]], 65535 ];
noticeableHilite ← TRUE;
};
ENDLOOP;
IF noticeableHilite THEN {
hltRed ← Basics.HighByte[hltRed];
hltGrn ← Basics.HighByte[hltGrn];
hltBlu ← Basics.HighByte[hltBlu];
IF gray THEN hltRed ← (hltRed + hltGrn + hltBlu) / 3;
red ← MIN[ red + Basics.HighByte[(255 - red) * 2 * hltRed], 255 ];
IF NOT gray THEN {
grn ← MIN[ grn + Basics.HighByte[(255 - grn) * 2 * hltGrn], 255 ];
blu ← MIN[ blu + Basics.HighByte[(255 - blu) * 2 * hltBlu], 255 ];
};
};
IF dithering
THEN Dither[ scanDst[0].val, red, grn, blu, scanline ]
ELSE IF gray
THEN Write[scanDst[0].val, red]
ELSE {
Write[scanDst[0].val, red]; Write[scanDst[1].val, grn]; Write[scanDst[2].val, blu];
};
};
lftSrc, rgtSrc, lftDst, rgtDst: REF EdgeSequence ← NIL;
scanline, srcSize, dstSize, dstDpth, srcDpth, srcPos: NAT ← 0;
lx, ly, lz: REAL ← 0.0;           -- for texture functions
srcTmplate: Pixel ← IF context.class.displayType = $Gray THEN [1,0,0,0,0] ELSE [1,1,1,0,0];
dstTmplate: Pixel ← IF context.class.displayType = $FullColor THEN [1,1,1,0,0] ELSE [1,0,0,0,0];
dstBufPos: Pixel ← [0,1,2,0,0];
alpha: REF NATNARROW[ GetProp[context.displayProps, $Alpha] ];
depth: REF NATNARROW[ GetProp[context.displayProps, $Depth] ];
dithering: BOOLEANIF context.class.displayType = $PseudoColor THEN TRUE ELSE FALSE;
gray: BOOLEANIF context.class.displayType = $Gray THEN TRUE ELSE FALSE;
texture: BOOLEANIF plygn.renderData.shadingClass.texture # NIL THEN TRUE ELSE FALSE;
lightColor: NatRGBSequence ← NARROW[ GetProp[plygn.props, $LightColors] ];
hltCnt: NATIF lightColor # NIL THEN lightColor.length ELSE 0;
links: LinkedPoly;
IF alpha # NIL THEN { dstBufPos[a] ← alpha^; srcTmplate[a] ← dstTmplate[a] ← 2; };
IF depth # NIL THEN { dstBufPos[z] ← depth^; srcTmplate[z] ← dstTmplate[z] ← 2; };
FOR i: PixelPart IN PixelPart DO
IF srcTmplate[i] > 0 THEN srcSize ← srcSize + 1;
IF dstTmplate[i] > 0 THEN dstSize ← dstSize + 1;
ENDLOOP;
IF depth # NIL THEN { dstDpth ← dstSize-1; srcDpth ← srcSize-1; };
IF texture THEN srcSize ← srcSize + 3;   -- make room for texure coordinates
srcSize ← srcSize + hltCnt * 2; -- reflection vector for each hilight-causing light source
links ← LinkEdges[ plygn, context.pixels.box ]; -- link vertices into left and right side chains
IF links.lftVtces # NIL THEN {        -- if non-zero height
scanline ← Fix[plygn[links.lftVtces.first].coord.sy];    -- get first scanline
lftSrc ← GetEdgeSeq[srcSize*plygn.nVtces]; rgtSrc ← GetEdgeSeq[srcSize*plygn.nVtces];
lftDst ← GetEdgeSeq[dstSize*plygn.nVtces]; rgtDst ← GetEdgeSeq[dstSize*plygn.nVtces];
FOR i: PixelPart IN PixelPart DO    --Get Edge records for left and right sides
IF dstTmplate[i] > 0 THEN {
dstAddr, yStep: CARD32;
[dstAddr, yStep] ← SampleMapBase[context.pixels[dstBufPos[i]]];
LinkDst[ lftDst, links.lftVtces, plygn,
   dstBufPos[i], dstSize, dstAddr, dstTmplate[i], yStep ];
LinkDst[ rgtDst, links.rgtVtces, plygn,
   dstBufPos[i], dstSize, dstAddr, dstTmplate[i], yStep ];
};
IF srcTmplate[i] > 0 THEN {
LinkSrc[lftSrc, links.lftVtces, plygn, srcPos, srcSize, i ];
LinkSrc[rgtSrc, links.rgtVtces, plygn, srcPos, srcSize, i ];
srcPos ← srcPos + 1;
};
ENDLOOP;
LinkAdditionalData[lftSrc, links.lftVtces, plygn, srcSize, hltCnt, texture ];
LinkAdditionalData[rgtSrc, links.rgtVtces, plygn, srcSize, hltCnt, texture ];
ScanPoly[
context, lftDst, lftSrc, rgtDst, rgtSrc, dstSize, srcSize, dstDpth, srcDpth, scanline, Hilight
];
ReleaseEdgeSeq[lftSrc]; ReleaseEdgeSeq[rgtSrc];
ReleaseEdgeSeq[lftDst]; ReleaseEdgeSeq[ rgtDst];
};
Remove prop to prevent highlights recurring after lights/surfaces have moved
plygn.props ← Atom.RemPropFromList[plygn.props, $LightColors];
};
LinkAdditionalData: PROC[ src: REF EdgeSequence, links: LIST OF CARD16, plygn: REF Patch,
         srcSize, hltCnt: NAT, texture: BOOL] ~ { 
BuildEdgeDesc: PROC[length: INT16, start, end: INT32] RETURNS [edge: EdgeDesc] ~ {
width: INT16 ← end - start;
edge.length ← length;
edge.val ← start;
edge.hiccups ← ABS[width];
[edge.lngthIncr, edge.hiccups] ← Basics.DivMod[ABS[width], edge.length];
IF width < 0          -- color (etc.) moving negatively?
THEN { edge.lngthIncr ← -edge.lngthIncr; edge.hicIncr ← -1; }
ELSE edge.hicIncr ← 1;
edge.bias ← edge.length;      -- initial bias to center hiccups
edge.stepsLeft ← edge.length;    -- set stepsLeft for count down
IF ptr-srcSize >= 0 THEN src[ptr-srcSize].nextEdge ← ptr; -- set ptr from last one
};
ptr: NAT ← srcSize - hltCnt*2;
FOR list: LIST OF CARD16 ← links, list.rest UNTIL list.rest = NIL DO
bot: CtlPtInfo ← plygn[list.first]; top: CtlPtInfo ← plygn[list.rest.first];
Get reflection vectors
srcStart: IntegerPairSequence ← IF hltCnt > 0 THEN NARROW[bot.data] ELSE NIL;
srcEnd: IntegerPairSequence ← IF hltCnt > 0 THEN NARROW[top.data] ELSE NIL;
yStart: CARD16 ← Round[bot.coord.sy]; yEnd: CARD16 ← Round[top.coord.sy];
length: INTEGERINTEGER[yEnd] - INTEGER[yStart];
IF length > 0 THEN {
IF texture THEN {
WITH plygn.renderData.shadingClass.texture.first SELECT FROM-- only one texture
txtrMap: REF TextureMap => {  -- modify with mapped texture
bigC: INT16LAST[NAT]/32;
ptr ← ptr - 3;
src[ptr] ← BuildEdgeDesc[
length, Round[bigC*bot.shade.txtrX], Round[bigC*top.shade.txtrX] ];
ptr ← ptr + 1;
src[ptr] ← BuildEdgeDesc[
length, Round[bigC*bot.shade.txtrY], Round[bigC*top.shade.txtrY] ];
ptr ← ptr + 1;
src[ptr] ← BuildEdgeDesc[ length, 0, 0 ]; -- filler to avoid bounds errors
ptr ← ptr + 1;
};
txtrFn: REF TextureFunction => {   -- solid or other function-based texture
bigC: INT16LAST[NAT]/32;
IF useTextureCoords
THEN {
ptr ← ptr - 3;
src[ptr] ← BuildEdgeDesc[
length, Round[bigC*bot.shade.txtrX], Round[bigC*top.shade.txtrX] ];
ptr ← ptr + 1;
src[ptr] ← BuildEdgeDesc[
length, Round[bigC*bot.shade.txtrY], Round[bigC*top.shade.txtrY] ];
ptr ← ptr + 1;
src[ptr] ← BuildEdgeDesc[ length, 0, 0 ]; -- filler to avoid bounds errors
ptr ← ptr + 1;
}
ELSE {
ptr ← ptr - 3;
src[ptr] ← BuildEdgeDesc[
length, Round[bigC*bot.coord.x], Round[bigC*top.coord.x] ];
ptr ← ptr + 1;
src[ptr] ← BuildEdgeDesc[
length, Round[bigC*bot.coord.y], Round[bigC*top.coord.y] ];
ptr ← ptr + 1;
src[ptr] ← BuildEdgeDesc[
length, Round[bigC*bot.coord.z], Round[bigC*top.coord.z] ];
ptr ← ptr + 1;
}
};
ENDCASE => SIGNAL G3dRender.Error[$Unimplemented, "Unexpected texture type"];
};
FOR i: NAT IN [0..hltCnt) DO    -- add in reflection vector for each highlight
src[ptr] ← BuildEdgeDesc[ length, srcStart[i].x, srcEnd[i].x ]; ptr ← ptr + 1;
src[ptr] ← BuildEdgeDesc[ length, srcStart[i].y, srcEnd[i].y ]; ptr ← ptr + 1;
ENDLOOP;
};
IF length > 0 THEN ptr ← ptr + srcSize - hltCnt*2;  -- skip over other data
ENDLOOP;
};
Image Manipulation
CheckLimits: PROC[] ~ {
};
ImageTransform: PROC[dst, src: SampleMap, dstPos: IntegerPair, theta, scale: REAL] ~ {
i: NAT ← 0;   -- loop index
dstEdge, srcEdge, dstStart, dstBias, srcStart: EdgeDesc;
srcAddr, dstAddr: CARD16;
srcBytesPerLine, dstBytesPerLine: WORD;
srcBox: Box ← ImagerSample.GetBox[src];
ebt: EdgeBltTable;
scaledWidth: NAT ← Round[scale * (srcBox.max.f - srcBox.min.f)];
scaledHeight: NAT ← Round[scale * (srcBox.max.s - srcBox.min.s)];
dstEdgeLength: CARD16 ← Round[RealFns.CosDeg[theta] * scaledWidth];
dstEdgeHiccups: CARD16 ← Round[RealFns.SinDeg[theta] * scaledWidth];
CheckLimits[]; -- ensure transformed image fits in target buffer, 0<theta<pi/4, .5<scale<1.5
[dstAddr, dstBytesPerLine] ← SampleMapBase[dst];
dstAddr ← dstAddr + dstPos.y * INT[dstBytesPerLine] + dstPos.x;
dstStart ← [   -- generates addresses walking down left edge of destination image
val: dstAddr,            -- start position for destination image
length: Round[RealFns.CosDeg[theta] * scaledHeight], -- left edge height, dst image
hiccups: Round[RealFns.SinDeg[theta] * scaledHeight], -- hiccups in left edge
lngthIncr: dstBytesPerLine,       -- vertical step to next scanline
hicIncr: 1,            -- horizontal step to next pixel
bias: Round[RealFns.CosDeg[theta] * scaledHeight] -- supply bias in lieu of G3dEdgeBlt
];
dstBias ← [ -- generates bias to correctly place first hiccup in image scanline-to-edge blt
val: 0,             -- initial bias is zero
length: dstStart.length,         -- height of left edge of dst image
hiccups: dstStart.hiccups,        -- hiccups in left edge
lngthIncr: 0,            -- no change until hiccup
hicIncr: -2 * dstEdgeHiccups,       -- increment to bias
bias: dstStart.bias - 2 * dstStart.hiccups    -- same as dstStart, off by one
];
[srcAddr, srcBytesPerLine] ← SampleMapBase[src];
srcStart ← [ -- walks down source image scanlines, skipping or replicating lines as needed
val: srcAddr,
length: srcBox.max.s - srcBox.min.s,     -- height of source image
hiccups: ABS[(srcBox.max.s - srcBox.min.s) - INTEGER[scaledHeight]], -- pixels to drop/add to scale down/up
lngthIncr: srcBytesPerLine,       -- vertical step to next scanline
hicIncr: IF scale > 1.0 THEN -srcBytesPerLine ELSE srcBytesPerLine, -- hiccup step
bias: srcBox.max.s - srcBox.min.s     -- supply bias since not using G3dEdgeBlt
];
dstEdge ← [  -- walks across destinatation image along slanted edge
val: dstStart.val,
length: dstEdgeLength,          -- horizontal dimension of edge
hiccups: dstEdgeHiccups,         -- vertical dimension of edge
lngthIncr: 1,             -- horizontal step to next pixel
hicIncr: -dstBytesPerLine,         -- vertical step to next pixel
bias: dstBias.val,            -- bias computed by dstBias
indirect: TRUE            -- incrementing addresses
];
srcEdge ← [ -- walks along scanline of source image, skipping or copying pixels as needed
val: srcStart.val,
length: srcBox.max.f - srcBox.min.f,        -- width of source image
hiccups: ABS[INTEGER[srcBox.max.f - srcBox.min.f] - scaledWidth], -- pixels to drop/add to scale down/up
lngthIncr: 1,            -- horizontal step to next pixel
hicIncr: IF scale > 1.0 THEN -1 ELSE 1,    -- hiccup step to next pixel
bias: 0,             -- will be supplied by G3dEdgeBlt
indirect: TRUE           -- incrementing addresses
];
ebt ← [dstEdge, srcEdge, [TRUE, FALSE] ];
WHILE i < dstStart.length DO
G3dEdgeBlt.Blt[ebt];
IF dstBias.val <= - dstEdgeLength   -- equals 0 after G3dEdgeBlt adds initial bias
THEN {  -- should be integrated better
dstBias.val ← dstBias.val + 2 * dstEdgeLength;   -- reset bias
dstStart.val ← dstStart.val - dstStart.lngthIncr;   -- move start position up one line    
}
ELSE i ← i+1;
ebt.dst.bias ← dstBias.val;       -- set up bias for distance to first hiccup
dstBias ← InlineIncr[dstBias];
dstStart ← InlineIncr[dstStart]; ebt.dst.val ← dstStart.val;
srcStart ← InlineIncr[srcStart]; ebt.src.val ← srcStart.val;
ENDLOOP;
};
END.