-- CGBitmapDeviceImpl.mesa
-- Last changed by Doug Wyatt, December 1, 1983 1:11 pm
-- Last changed by Paul Rovner, August 10, 1983 11:29 am

DIRECTORY
Basics USING [DIVMOD, LongDivMod, LongMult],
CGArea USING [Empty, Ref, Remove],
CGBitmapDevice USING [], -- exports only
CGBitmapDeviceExtras USING [], -- exports only
CGColor USING [GetStipple],
CGDevice USING [Ref, Rep],
CGMatrix USING [Inv, InvRel, IsTrivial, Make, Ref],
CGSample USING [Flags, Sample0, Sample8, Table],
CGScreen USING [Bits],
CGSource USING [Mode, Ref, Type],
CGStorage USING [pZone, qZone],
GraphicsBasic USING [black, Box, Color, Trap, white],
GraphicsColor USING [ColorToIntensity],
PrincOps USING [BBTableSpace, BitBltTable, BitBltTablePtr],
PrincOpsUtils USING [AlignedBBTable, BITBLT],
Real USING [Fix, FixC, RoundC];

CGBitmapDeviceImpl: CEDAR PROGRAM
IMPORTS Basics, CGArea, CGColor, CGMatrix, CGSample, CGScreen, CGStorage,
GraphicsColor, PrincOpsUtils, Real
EXPORTS CGBitmapDevice, CGBitmapDeviceExtras = {
OPEN CGDevice, GraphicsBasic;

dataZone: ZONE = CGStorage.qZone;
repZone: ZONE = CGStorage.qZone;
brickZone: ZONE = CGStorage.pZone;

Error: SIGNAL = CODE;

Data: TYPE = REF DataRep;
DataRep: TYPE = RECORD [
baseref: REF, -- ref for bitmap (or NIL if screen)
base: LONG POINTER, -- base address of bitmap
rast: CARDINAL, -- bitmap words per line
lines: CARDINAL, -- bitmap lines
matrix: CGMatrix.Ref -- base transformation matrix
];

New: PUBLIC PROC[base: REF, raster, height: CARDINAL] RETURNS[Ref] = {
data: Data ← dataZone.NEW[DataRep ← [baseref: NIL, base: NIL, rast: 0, lines: 0, matrix: NIL]];
IF base=NIL THEN [base: data.base, raster: raster, height: height] ← CGScreen.Bits[]
ELSE { data.baseref ← base; data.base ← LOOPHOLE[base] };
data.rast ← raster; data.lines ← height;
data.matrix ← CGMatrix.Make[[1,0,0,-1,0,height]];
RETURN[repZone.NEW[Rep ← [
GetMatrix: GetMatrix, GetBounds: GetBounds, Show: Show,
GetRaster: GetRaster, MoveBlock: MoveBlock, data: data]]];
};

UnsafeNew: PUBLIC UNSAFE PROC[base: LONG POINTER, raster, height: CARDINAL] RETURNS[Ref] = {
data: Data ← dataZone.NEW[DataRep ← [baseref: NIL,
base: base, rast: raster, lines: height, matrix: NIL]];
data.matrix ← CGMatrix.Make[[1,0,0,-1,0,height]];
RETURN[repZone.NEW[Rep ← [
GetMatrix: GetMatrix, GetBounds: GetBounds, Show: Show,
GetRaster: GetRaster, MoveBlock: MoveBlock, data: data]]];
};

GetMatrix: PROC[self: Ref] RETURNS[CGMatrix.Ref] = {
data: Data ← NARROW[self.data];
RETURN[data.matrix];
};

GetBounds: PROC[self: Ref] RETURNS[Box] = {
data: Data ← NARROW[self.data];
w: CARDINAL ← 16*data.rast;
h: CARDINAL ← data.lines;
e: REAL = 0.1; -- small fudge factor
RETURN[[xmin: e, ymin: e, xmax: w-e, ymax: h-e]];
};

GetRaster: PROC[self: Ref] RETURNS[LONG POINTER,CARDINAL] = {
data: Data ← NARROW[self.data];
RETURN[data.base,data.rast];
};

Show: PROC[self: Ref, area: CGArea.Ref, src: CGSource.Ref, map: CGMatrix.Ref] = {
data: Data ← NARROW[self.data];
fat: BOOLEAN ← (src.fat AND src.type#array);
UNTIL CGArea.Empty[area] DO
trap: Trap ← CGArea.Remove[area];
IF trap.xbotL=trap.xtopL AND trap.xbotR=trap.xtopR THEN {
rect: Box ← [xmin: trap.xbotL, ymin: trap.ybot, xmax: trap.xbotR, ymax: trap.ytop];
ShowRect[data,rect,src,map] }
ELSE ShowTrap[data,trap,src,map];
ENDLOOP;
};

Bot: PROC[r: REAL] RETURNS[CARDINAL] = INLINE { RETURN[Real.FixC[r]] };
Top: PROC[r: REAL] RETURNS[CARDINAL] = INLINE { RETURN[Real.FixC[r]+1] };
Fix: PROC[r: REAL] RETURNS[CARDINAL] = INLINE { RETURN[Real.FixC[r]] };
Rnd: PROC[r: REAL] RETURNS[CARDINAL] = INLINE { RETURN[Real.FixC[r+.5]] };
RndI: PROC[r: REAL] RETURNS[INTEGER] = INLINE {
RETURN[Real.FixC[r+(LAST[INTEGER]+.5)]-LAST[INTEGER]] };
FixF: PROC[r: REAL] RETURNS[LONG INTEGER] = INLINE {
RETURN[Real.Fix[r*200000B]] };


Brick: TYPE = REF BrickRep;
BrickRep: TYPE = RECORD[w, h, d: CARDINAL, array: SEQUENCE size: CARDINAL OF CARDINAL];

brick3, brick4: Brick ← NIL;
currentBrick, defaultBrick: Brick ← NIL;

InitBricks: PROC = {
index3: ARRAY[0..9) OF NAT = [8,3,6,5,1,9,2,7,4];
index4: ARRAY[0..16) OF NAT = [09,13,08,04,14,07,03,10,06,02,11,15,01,12,16,05];
brick3 ← brickZone.NEW[BrickRep[9] ← [w: 3, h: 3, d: 0, array: ]];
FOR i: NAT IN[0..9) DO brick3[i] ← (255*index3[i]+5)/10 ENDLOOP;
brick4 ← brickZone.NEW[BrickRep[16] ← [w: 4, h: 4, d: 0, array: ]];
FOR i: NAT IN[0..16) DO brick4[i] ← (255*index4[i]+8)/17 ENDLOOP;
currentBrick ← defaultBrick ← brick3;
};

BadArgs: ERROR = CODE;

SetBrick: PUBLIC PROC[w, h, d: CARDINAL,
proc: PROC[i: CARDINAL] RETURNS[CARDINAL]] = {
IF w>0 AND h>0 AND d<w AND Basics.LongMult[w,h]<=LAST[CARDINAL] THEN {
size: CARDINAL ← w*h;
brick: Brick ← brickZone.NEW[BrickRep[size] ← [w: w, h: h, d: d, array: ]];
FOR i: NAT IN[0..size) DO brick[i] ← proc[i] ENDLOOP;
currentBrick ← brick }
ELSE ERROR BadArgs;
};

ResetBrick: PUBLIC PROC = { currentBrick ← defaultBrick };

Byte: TYPE = [0..256);

SetMap: PUBLIC PROC[proc: PROC[Byte] RETURNS[Byte]] = {
FOR i: Byte IN Byte DO defaultMap[i] ← proc[i] ENDLOOP;
};

black: CARDINAL = LAST[CARDINAL];

grayTable: ARRAY[0..16) OF CARDINAL ← [
000000B, 010421B, 021042B, 031463B, 042104B, 052525B, 063146B, 073567B,
104210B, 114631B, 125252B, 135673B, 146314B, 156735B, 167356B, 177777B];

GrayArray: TYPE = ARRAY [0..4) OF CARDINAL;

MakeGray: PROC[color: CARDINAL] RETURNS[GrayArray] = INLINE {
IF color=black THEN RETURN[ALL[black]] ELSE RETURN[MakeGrayProc[color]] };

MakeGrayProc: PROC[t: CARDINAL] RETURNS[GrayArray] = {
gray: GrayArray ← ALL[0];
IF t#0 THEN { temp: CARDINAL ← t;
FOR i: CARDINAL DECREASING IN[0..4) DO
gray[i] ← grayTable[temp MOD 16]; temp ← temp/16;
ENDLOOP; };
RETURN[gray];
};

ColorToStipple: PROC[color: GraphicsBasic.Color] RETURNS[CARDINAL] = INLINE {
IF color=GraphicsBasic.black THEN RETURN[177777B]
ELSE IF color=GraphicsBasic.white THEN RETURN[0]
ELSE IF color.tag=stipple THEN RETURN[CGColor.GetStipple[color]]
ELSE RETURN[ComputeStipple[color]] };

ComputeStipple: PROC[color: GraphicsBasic.Color] RETURNS[CARDINAL] = {
table: ARRAY [0..15] OF CARDINAL = [
177777B, 32767, 32735, 24543, 24415, 23391, 23390, 23134,
23130, 6746, 6730, 2634, 2570, 2058, 2050, 0];
IF color.tag=stipple THEN RETURN[CGColor.GetStipple[color]]
ELSE { intensity: REAL ← GraphicsColor.ColorToIntensity[color];
i: [0..15] ← Real.RoundC[intensity*15]; RETURN[table[i]] };
};

nullBitBltTable: PrincOps.BitBltTable = [dst: [word: NIL, bit: 0], dstBpl: 0,
src: [word: NIL, bit: 0], srcDesc: [srcBpl[0]], width: 0, height: 0,
flags: [disjoint: TRUE, gray: TRUE, srcFunc: null, dstFunc: null]];

nullSampleFlags: CGSample.Flags = [function: 0,
mConst: FALSE, bConst: FALSE, sConst: FALSE, useMap: FALSE, size: 0];
nullSampleTable: CGSample.Table = [flags: nullSampleFlags,
count: 0, bValue: 0, sValue: 0, dLine: NIL, mLine: NIL, di: 0, mi: 0, map: NIL,
bLine: NIL, bi: 0, bw: 0, sBase: NIL, sRast: 0, sw: 0, sh: 0, sox: 0, soy: 0,
sx: 0, sy: 0, sdx: 0, sdy: 0];

MapArray: TYPE = ARRAY[0..256) OF CARDINAL;
defaultMap: REF MapArray ← InitDefaultMap[];
InitDefaultMap: PROC RETURNS[REF MapArray] = {
map: REF MapArray ← repZone.NEW[MapArray];
FOR i: NAT IN[0..256) DO map[i] ← i ENDLOOP;
RETURN[map] };

ShowRect: PROC[data: Data, rect: Box, src: CGSource.Ref, map: CGMatrix.Ref] = {
type: CGSource.Type ← src.type;
mode: CGSource.Mode ← src.mode;
easy: BOOLEAN ← (SELECT type FROM
const, tile => TRUE, -- always easy
array => (CGMatrix.IsTrivial[map] AND src.bps<2), -- bitmap is easy
proc => FALSE, -- never easy
ENDCASE => ERROR);
fat: BOOLEAN ← (src.fat AND type#array);
xmin, xmax, ymin, ymax: CARDINAL ← 0;
dbase: LONG POINTER ← data.base;
drast: CARDINAL ← data.rast;
IF fat THEN {
xmin ← Bot[rect.xmin]; xmax ← Top[rect.xmax];
ymin ← Bot[rect.ymin]; ymax ← Top[rect.ymax];
}
ELSE {
xmin ← Rnd[rect.xmin]; xmax ← Rnd[rect.xmax];
ymin ← Rnd[rect.ymin]; ymax ← Rnd[rect.ymax];
};
IF NOT(xmin<xmax AND ymin<ymax) THEN RETURN; -- nothing to do
IF easy THEN TRUSTED {
bbspace: PrincOps.BBTableSpace;
bb: PrincOps.BitBltTablePtr ← PrincOpsUtils.AlignedBBTable[@bbspace];
gray: ARRAY [0..4) OF CARDINAL;
color: CARDINAL ← ColorToStipple[src.color];
bb^ ← nullBitBltTable;
bb.flags.dstFunc ← (SELECT mode FROM transparent => or, invert => xor, ENDCASE => null);
bb.dst.word ← dbase + Basics.LongMult[ymin, drast] + xmin/16;
bb.dst.bit ← xmin MOD 16; bb.dstBpl ← drast*16;
SELECT type FROM
const => { yOffset: [0..4) ← ymin MOD 4;
bb.srcDesc.gray ← [yOffset: 0, widthMinusOne: 0, heightMinusOne: 3];
bb.srcDesc.gray.yOffset ← yOffset;
bb.src.word ← @gray + yOffset; bb.src.bit ← xmin MOD 16;
gray ← MakeGray[color];
};
tile => { yOffset: [0..16) ← ymin MOD 16;
bb.srcDesc.gray ← [yOffset: 0, widthMinusOne: 0, heightMinusOne: 15];
bb.srcDesc.gray.yOffset ← yOffset;
bb.src.word ← src.xbase + yOffset; bb.src.bit ← xmin MOD 16;
-- weird "transparent white" semantics for McGregor's grey text hack:
IF mode=transparent AND color=0 THEN {
bb.flags.srcFunc ← complement; bb.flags.dstFunc ← and };
};
array => {
-- map transforms source coordinates to device coordinates
-- Since this is an easy case, we know map is a simple translation;
-- so subtracting map's translation elements will take us from device to source
sxmin: CARDINAL ← Real.FixC[xmin+0.5-map.m.e];
symin: CARDINAL ← Real.FixC[ymin+0.5-map.m.f];
sbase: LONG POINTER ← src.xbase;
srast: CARDINAL ← src.xrast;
bb.flags.gray ← FALSE;
IF (src.bps>0)=(color>0) THEN bb.flags.srcFunc ← complement;
bb.src.word ← sbase + Basics.LongMult[symin,srast] + sxmin/16;
bb.src.bit ← sxmin MOD 16;
bb.srcDesc.srcBpl ← srast*16;
};
ENDCASE => ERROR;
bb.width ← xmax - xmin; bb.height ← ymax - ymin;
PrincOpsUtils.BITBLT[bb];
}
ELSE TRUSTED {
table: CGSample.Table ← nullSampleTable;
rsx, rsy, rsdx, rsdy: REAL;
y: CARDINAL ← ymin;
[[rsdx,rsdy]] ← CGMatrix.InvRel[map,[1,0]];
table.sdx ← FixF[rsdx]; table.sdy ← FixF[rsdy];
table.sBase ← src.xbase; table.sRast ← src.xrast;
table.dLine ← dbase+Basics.LongMult[drast, ymin];
table.di ← xmin; table.count ← xmax-xmin;
IF src.bps=8 THEN {
brick: Brick ← currentBrick;
bbase: LONG POINTER ← @brick[0];
bw, bh, bd, be, br, bx, by: CARDINAL;
bw ← brick.w; bh ← brick.h; bd ← brick.d;
be ← (IF bd=0 THEN 0 ELSE bw-bd);
[quotient: br, remainder: by] ← Basics.DIVMOD[y, bh];
bx ← Basics.LongDivMod[Basics.LongMult[br, be], bw].remainder;
table.bLine ← bbase + by*bw; table.bw ← bw;
table.bi ← (xmin+bx) MOD bw;
table.map ← LOOPHOLE[defaultMap];
DO
[[rsx,rsy]] ← CGMatrix.Inv[map,[xmin+0.5,y+0.5]];
table.sx ← FixF[rsx]; table.sy ← FixF[rsy];
CGSample.Sample8[@table, mode];
IF (y ← y+1)=ymax THEN EXIT;
table.dLine ← table.dLine+drast;
IF (by ← by+1)=bh THEN { by ← 0; table.bLine ← bbase;
IF bx<bd THEN bx ← bx+be ELSE bx ← bx-bd;
table.bi ← (xmin+bx) MOD bw }
ELSE table.bLine ← table.bLine+bw;
ENDLOOP;
}
ELSE IF src.bps=0 THEN {
DO
[[rsx,rsy]] ← CGMatrix.Inv[map,[xmin+0.5,y+0.5]];
table.sx ← FixF[rsx]; table.sy ← FixF[rsy];
CGSample.Sample0[@table, mode];
IF (y ← y+1)=ymax THEN EXIT;
table.dLine ← table.dLine+drast;
ENDLOOP;
}
ELSE NULL;
};
};

ShowTrap: PROC[data: Data, trap: Trap, src: CGSource.Ref, map: CGMatrix.Ref] = TRUSTED {
type: CGSource.Type ← src.type;
mode: CGSource.Mode ← src.mode;
color: CARDINAL ← ColorToStipple[src.color];
ymin, ymax, xmin, xmax, y: CARDINAL;
xL, xR, dxL, dxR, dy, fy: REAL;
dline: LONG POINTER; -- destination line for current y
drast: CARDINAL; -- destination raster width (in words)

IF src.fat AND type#array THEN { ShowFatTrap[data, trap, src]; RETURN };
ymin ← Rnd[trap.ybot]; ymax ← Rnd[trap.ytop];
IF NOT ymax>ymin THEN { IF ymin>ymax THEN SIGNAL Error; RETURN }; -- nothing to do
dy ← trap.ytop-trap.ybot; -- delta y
dxL ← (trap.xtopL-trap.xbotL)/dy; -- dx/dy, left
dxR ← (trap.xtopR-trap.xbotR)/dy; -- dx/dy, right
fy ← (ymin+0.5)-trap.ybot; -- distance to middle of first line
xL ← trap.xbotL+fy*dxL; xR ← trap.xbotR+fy*dxR; -- left and right x at middle of current line
y ← ymin; drast ← data.rast; dline ← data.base + Basics.LongMult[y, drast];
SELECT type FROM
const, tile => {
bbspace: PrincOps.BBTableSpace;
bb: PrincOps.BitBltTablePtr ← PrincOpsUtils.AlignedBBTable[@bbspace];
gray: ARRAY [0..4) OF CARDINAL; -- gray pattern, if type=const
pbase: LONG POINTER; -- pattern base address
ph, py: CARDINAL; -- pattern height and current line
bb^ ← nullBitBltTable;
bb.dstBpl ← drast*16; bb.height ← 1; bb.flags.gray ← TRUE;
bb.flags.dstFunc ← (SELECT mode FROM transparent => or, invert => xor, ENDCASE => null);
IF type=const THEN { pbase ← @gray; ph ← 4; gray ← MakeGray[color] }
ELSE { pbase ← src.xbase; ph ← 16;
-- weird "transparent white" semantics for McGregor's grey text hack:
IF mode=transparent AND color=0 THEN {
bb.flags.srcFunc ← complement; bb.flags.dstFunc ← and };
};
py ← y MOD ph; bb.src.word ← pbase + py;
bb.srcDesc.gray ← [yOffset: py, widthMinusOne: 0, heightMinusOne: ph-1];
DO xmin ← Rnd[xL]; xmax ← Rnd[xR];
IF xmin<xmax THEN {
bb.dst.word ← dline + xmin/16; bb.dst.bit ← xmin MOD 16;
bb.src.bit ← bb.dst.bit; bb.width ← xmax-xmin;
PrincOpsUtils.BITBLT[bb] };
IF (y ← y+1)=ymax THEN EXIT;
xL ← xL+dxL; xR ← xR+dxR; -- update left and right x
dline ← dline + drast; -- bump destination line
IF (py ← py+1)=ph THEN { bb.src.word ← pbase; py ← 0 }
ELSE bb.src.word ← bb.src.word + 1; -- bump pattern line
ENDLOOP;
};
array => IF CGMatrix.IsTrivial[map] AND src.bps=0 THEN { -- easy array
bbspace: PrincOps.BBTableSpace;
bb: PrincOps.BitBltTablePtr ← PrincOpsUtils.AlignedBBTable[@bbspace];
tx, ty: INTEGER;
sline: LONG POINTER;
srast: CARDINAL;
bb^ ← nullBitBltTable;
bb.dstBpl ← drast*16; bb.height ← 1; bb.flags.gray ← FALSE;
bb.flags.dstFunc ← (SELECT mode FROM transparent => or, invert => xor, ENDCASE => null);
IF color=0 THEN { bb.flags.srcFunc ← complement;
IF mode=transparent THEN bb.flags.dstFunc ← and };
-- The matrix 'map' transforms source coordinates to device coordinates.
-- Here we know map is a simple translation, so subtracting its translation
-- elements will take us from device to source coordinates.
tx ← RndI[map.m.e]; ty ← RndI[map.m.f];
srast ← src.xrast; sline ← src.xbase + Basics.LongMult[(ymin-ty), srast];
bb.srcDesc.srcBpl ← srast*16;
DO xmin ← Rnd[xL]; xmax ← Rnd[xR];
IF xmin<xmax THEN { sxmin: CARDINAL ← xmin-tx;
bb.dst.word ← dline + xmin/16; bb.dst.bit ← xmin MOD 16;
bb.src.word ← sline + sxmin/16; bb.src.bit ← sxmin MOD 16;
bb.width ← xmax-xmin;
PrincOpsUtils.BITBLT[bb] };
IF (y ← y+1)=ymax THEN EXIT;
xL ← xL+dxL; xR ← xR+dxR; -- update left and right x
dline ← dline+drast; -- bump destination line
sline ← sline+srast; -- bump source line
ENDLOOP;
}
ELSE { -- hard array
table: CGSample.Table ← nullSampleTable;
sx, sy, sdx, sdy: REAL;
[[sdx, sdy]] ← CGMatrix.InvRel[map, [1,0]];
table.sdx ← FixF[sdx]; table.sdy ← FixF[sdy];
table.sBase ← src.xbase; table.sRast ← src.xrast;
IF src.bps=8 THEN {
brick: Brick ← currentBrick;
bbase: LONG POINTER ← @brick[0];
bw, bh, bd, be, br, bx, by: CARDINAL;
bw ← brick.w; bh ← brick.h; bd ← brick.d;
be ← (IF bd=0 THEN 0 ELSE bw-bd);
[quotient: br, remainder: by] ← Basics.DIVMOD[y, bh];
bx ← Basics.LongDivMod[Basics.LongMult[br, be], bw].remainder;
table.bLine ← bbase + by*bw; table.bw ← bw;
table.map ← LOOPHOLE[defaultMap];
DO xmin ← Rnd[xL]; xmax ← Rnd[xR];
IF xmin<xmax THEN {
[[sx, sy]] ← CGMatrix.Inv[map, [xmin+0.5, y+0.5]];
table.sx ← FixF[sx]; table.sy ← FixF[sy];
table.bi ← (xmin+bx) MOD bw;
table.dLine ← dline; table.di ← xmin;
table.count ← xmax-xmin;
CGSample.Sample8[@table, mode];
};
IF (y ← y+1)=ymax THEN EXIT;
xL ← xL+dxL; xR ← xR+dxR; -- update left and right x
dline ← dline+drast; -- bump destination line
IF (by ← by+1)=bh THEN { by ← 0; table.bLine ← bbase;
IF bx<bd THEN bx ← bx+be ELSE bx ← bx-bd }
ELSE table.bLine ← table.bLine+bw; -- bump brick line
ENDLOOP;
}
ELSE IF src.bps=0 THEN {
DO xmin ← Rnd[xL]; xmax ← Rnd[xR];
IF xmin<xmax THEN {
[[sx, sy]] ← CGMatrix.Inv[map, [xmin+0.5, y+0.5]];
table.sx ← FixF[sx]; table.sy ← FixF[sy];
table.dLine ← dline; table.di ← xmin;
table.count ← xmax-xmin;
CGSample.Sample0[@table, mode];
};
IF (y ← y+1)=ymax THEN EXIT;
xL ← xL+dxL; xR ← xR+dxR; -- update left and right x
dline ← dline+drast; -- bump destination line
ENDLOOP;
}
ELSE NULL;
};
ENDCASE => ERROR; -- bad src.type
};

ShowFatTrap: PROC[data: Data, trap: Trap, src: CGSource.Ref] = TRUSTED {
type: CGSource.Type ← src.type;
mode: CGSource.Mode ← src.mode;
color: CARDINAL ← ColorToStipple[src.color];
ymin, ymax, ylast, xl, xr, y: CARDINAL;
dxL, dxR, xbL, xbR, xtL, xtR, dy, fy: REAL;
topL, topR: BOOLEAN;
dline: LONG POINTER; -- destination line for current y
drast: CARDINAL; -- destination raster width (in words)
bbspace: PrincOps.BBTableSpace;
bb: PrincOps.BitBltTablePtr ← PrincOpsUtils.AlignedBBTable[@bbspace];
gray: ARRAY [0..4) OF CARDINAL; -- gray pattern, if type=const
pbase: LONG POINTER; -- pattern base address
ph, py: CARDINAL; -- pattern height and current line

-- compute ymin (bottom of first scanline) and ymax (top of last scanline)
ymin ← Bot[trap.ybot]; ymax ← Top[trap.ytop];
IF NOT ymax>ymin THEN { SIGNAL Error; RETURN };
ylast ← ymax-1; -- ylast is last line
y ← ymin; drast ← data.rast; dline ← data.base + Basics.LongMult[y, drast];
bb^ ← nullBitBltTable;
bb.dstBpl ← drast*16; bb.height ← 1; bb.flags.gray ← TRUE;
bb.flags.dstFunc ← (SELECT mode FROM transparent => or, invert => xor, ENDCASE => null);
IF type=const THEN { pbase ← @gray; ph ← 4; gray ← MakeGray[color] }
ELSE { pbase ← src.xbase; ph ← 16 };
py ← y MOD ph; bb.src.word ← pbase + py;
bb.srcDesc.gray ← [yOffset: py, widthMinusOne: 0, heightMinusOne: ph-1];

xbL ← trap.xbotL; xbR ← trap.xbotR; -- bottom x
IF ylast>ymin THEN { -- more than one line
dy ← trap.ytop-trap.ybot; -- height of trapezoid
dxL ← (trap.xtopL-trap.xbotL)/dy; -- left dx/dy
dxR ← (trap.xtopR-trap.xbotR)/dy; -- right dx/dy
fy ← (ymin+1)-trap.ybot; -- distance to top of first line
xtL ← xbL+fy*dxL; xtR ← xbR+fy*dxR; -- top x
topL ← (dxL<0); -- TRUE means leftmost x is at top of line
topR ← (dxR>0); -- TRUE means rightmost x is at top of line
}
ELSE { -- exactly one line
xtL ← trap.xtopL; xtR ← trap.xtopR; -- top x
topL ← (xtL<xbL); -- TRUE means leftmost x is at top of line
topR ← (xtR>xbR); -- TRUE means rightmost x is at top of line
};

DO -- for each scan line
xl ← Bot[IF topL THEN xtL ELSE xbL];
xr ← Top[IF topR THEN xtR ELSE xbR];
IF xl<xr THEN {
bb.dst.word ← dline + xl/16; bb.dst.bit ← xl MOD 16;
bb.src.bit ← bb.dst.bit; bb.width ← xr-xl;
PrincOpsUtils.BITBLT[bb] };
IF (y ← y+1)=ymax THEN EXIT;
xbL ← xtL; xbR ← xtR; -- new bottom is previous top
IF y=ylast THEN { xtL ← trap.xtopL; xtR ← trap.xtopR } -- last line
ELSE { xtL ← xbL+dxL; xtR ← xbR+dxR }; -- middle lines
dline ← dline + drast; -- bump destination line
IF (py ← py+1)=ph THEN { bb.src.word ← pbase; py ← 0 }
ELSE bb.src.word ← bb.src.word + 1; -- bump pattern line
ENDLOOP;
};

MoveBlock: PROC[self: Ref, width, height, fromX, fromY, toX, toY: NAT] = {
data: Data ← NARROW[self.data];
wmax: CARDINAL ← 16*data.rast;
hmax: CARDINAL ← data.lines;
IF width>0 AND height>0 AND
fromX<wmax AND fromY<hmax AND toX<wmax AND toY<hmax THEN TRUSTED {
dbase: LONG POINTER ← data.base;
drast: CARDINAL ← data.rast;
sx: CARDINAL ← fromX;
sy: CARDINAL ← fromY;
dx: CARDINAL ← toX;
dy: CARDINAL ← toY;
w: CARDINALMIN[width, wmax-sx, wmax-dx];
h: CARDINALMIN[height, hmax-sy, hmax-dy];
bpl: INTEGER ← 16*drast;
bbspace: PrincOps.BBTableSpace;
bb: PrincOps.BitBltTablePtr ← PrincOpsUtils.AlignedBBTable[@bbspace];
bb^ ← nullBitBltTable;
bb.flags ← [direction: forward, disjoint: TRUE, disjointItems: TRUE,
gray: FALSE, srcFunc: null, dstFunc: null];
IF (sx+w)>dx AND (dx+w)>sx AND (sy+h)>dy AND (dy+h)>sy THEN {
bb.flags.disjoint ← FALSE; -- the rectangles overlap
IF dy=sy THEN bb.flags.disjointItems ← FALSE; -- so do the items
IF dy>sy OR (dy=sy AND dx>sx) THEN { -- reverse direction
bb.flags.direction ← backward; bpl ← -bpl;
sy ← sy + (h-1); dy ← dy + (h-1);
};
};
bb.dst.word ← dbase + Basics.LongMult[dy, drast] + dx/16; bb.dst.bit ← dx MOD 16;
bb.src.word ← dbase + Basics.LongMult[sy, drast] + sx/16; bb.src.bit ← sx MOD 16;
bb.dstBpl ← bb.srcDesc.srcBpl ← bpl;
bb.width ← w; bb.height ← h;
PrincOpsUtils.BITBLT[bb];
};
};

------ Initialization ------

InitBricks[];

}.