-- CGBandDeviceImpl.mesa
-- Last changed by Ken Pier, July 11, 1983 6:03 pm
-- Last changed by Eric Bier,   November 16, 1982 4:07 pm

DIRECTORY
CGBandDevice,
GraphicsBasic USING [Box, Trap],
GraphicsColor USING [Color, ColorToIntensity, ColorToRGB, black, white],
CGBandStream USING[BandPrefix, BandIndex, BandStreamHandle,
OpenBand, PutBand, CloseBand],
CGBandFormat USING [ObjectRef, Object, objectSize, Run, runSize, LineRef, Line,
HeraldRef, HeraldObject, heraldObjectSize, EndRef, EndObject,
endObjectSize, TBrickRef, TBrickRep, tBrickSize],
CGBrick USING [BrickHandle, GetCurrentBrick, GetRow, GetCol, GetSize],
CGArea USING [Ref, Remove, Empty],
CGColor USING [GetStipple],
CGDevice USING [Ref, Rep],
CGMatrix USING [Ref, Make, Inv, InvRel],
CGScreen USING [Bits],
CGSource USING [Type, Ref],
CGStorage USING [qZone, pZone],
UnsafeStorage USING[GetSystemUZone],
Inline USING [LongNumber, LowByte, LongCOPY],
Environment USING[bitsPerWord],
CGFullSample USING [Pointer, SAMPLE, Table],
PressNetDefs USING [PrinterAttributes, GetPrinterAttributes],
Real USING [Fix, FixC, Float];

CGBandDeviceImpl: PROGRAM
IMPORTS CGArea, CGColor, CGBandStream, CGBrick, CGMatrix, CGScreen, CGStorage, Real,
UnsafeStorage, PressNetDefs, Inline, CGFullSample, GraphicsColor
EXPORTS CGBandDevice, GraphicsBasic = {
OPEN Area: CGArea, Brick: CGBrick, BDevice: CGBandDevice,
Device: CGDevice, Matrix: CGMatrix, Source: CGSource, BStream: CGBandStream,
BFormat: CGBandFormat, GB: GraphicsBasic, GC: GraphicsColor, Real;

DeviceObject: PUBLIC TYPE = CGDevice.Rep; -- exported to GraphicsBasic

dataZone: ZONE = CGStorage.qZone;
repZone: ZONE = CGStorage.qZone;
pZone: ZONE = CGStorage.pZone;
uZone: UNCOUNTED ZONE ← UnsafeStorage.GetSystemUZone[];
bitsPerWord: CARDINAL = Environment.bitsPerWord;
Byte: TYPE = [0..377B];

Error: SIGNAL = CODE;

Data: TYPE = REF DataRep;
DataRep: TYPE = RECORD [
base: LONG POINTER, -- base address of bitmap
raster: CARDINAL, -- bitmap words per line
lines: CARDINAL, -- bitmap lines
matrix: Matrix.Ref, -- virtual to device transformation matrix
htBrick: REF CGBrick.BrickHandle, -- for halftoning
bands: BDevice.BandRef --list of band parameters for each band
];


New: PUBLIC PROC[bDevice: BDevice.BandDevice] RETURNS[Device.Ref] = {

bCount: CARDINAL;
data: Data ← dataZone.NEW[DataRep ←
[ base: NIL, raster: 0, lines: 0, matrix: NIL, htBrick: NIL, bands: NIL]];
[base: data.base, raster: data.raster, height: data.lines,
matrix: data.matrix, bandCount: bCount] ← GetBParameters[bDevice];
data.htBrick ← CGBrick.GetCurrentBrick[]; oldBh ← NIL;
data.bands ← InitBands[data.lines, data.raster, bCount, bDevice];
RETURN[repZone.NEW[Device.Rep ← [
GetMatrix: GetMatrix, GetBounds: GetBounds, Show: Show,
GetRaster: GetRaster, data: data]]];
};

GetMatrix: SAFE PROC[self: Device.Ref] RETURNS[Matrix.Ref] = CHECKED {
data: Data ← NARROW[self.data];
RETURN[data.matrix];
};

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

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

Show: SAFE PROC[self: Device.Ref, area: Area.Ref, src: Source.Ref, map: Matrix.Ref] = TRUSTED {
data: Data ← NARROW[self.data];
UNTIL Area.Empty[area] DO
trap: GB.Trap ← Area.Remove[area];
ShowTrap[data,trap,src,map];
ENDLOOP;
};

Close: PUBLIC PROC[self: Device.Ref] = {
data: Data ← NARROW[self.data];
bands: BDevice.BandRef ← data.bands;
bcount: CARDINAL ← bands.count;
FOR bI: BStream.BandIndex IN [0..bcount) DO
BStream.PutBand[bands[bI].stream, endRef, BFormat.endObjectSize];
BStream.CloseBand[bands[bI].stream];--tho already closed, must release space
ENDLOOP;
};--Close

GetBParameters: PUBLIC PROC[b: BDevice.BandDevice]
RETURNS [base: LONG POINTER, raster,height: CARDINAL,
   matrix: Matrix.Ref,
   bandCount, brickloadSize, fontloadSize: CARDINAL ← 0] = {
pA: PressNetDefs.PrinterAttributes;
base ← NIL; --no direct screen refs for building bands
SELECT b FROM
screen => {
[ , raster, height] ← CGScreen.Bits[];
matrix ← Matrix.Make[[1,0,0,-1,0,height]];--y ← Height-y
bandCount ← 4;
};
hornet => {
pA ← PressNetDefs.GetPrinterAttributes[Stinger];
raster ← Real.FixC[((Real.Float[pA.resolutionB]*Real.Float[pA.scanLengthInches]/10)
     +bitsPerWord-1)/bitsPerWord];
height ← Real.FixC[Real.Float[pA.resolutionS]*8.5];
matrix ← Matrix.Make[[0, pA.resolutionB/72.0, pA.resolutionS/72.0, 0, 0, 0]];
bandCount ← 16;
};
platemaker => {
pA ← PressNetDefs.GetPrinterAttributes[DLP1];
raster ← Real.FixC[((Real.Float[pA.resolutionB]*Real.Float[pA.scanLengthInches]/10)
     +bitsPerWord-1)/bitsPerWord];
height ← Real.FixC[Real.Float[pA.resolutionS]*11.0];
matrix ← Matrix.Make[[pA.resolutionB/72.0, 0, 0, -pA.resolutionS/72.0, 0, height]];
bandCount ← 72;
};
ENDCASE => ERROR;
};

SetSeparation: PUBLIC PROC[s: BDevice.Separation] = {
colorSep ← s;
};


InitBands: PROC [lines, raster, bandCount: CARDINAL, bDevice: BDevice.BandDevice]
   RETURNS [bRef: BDevice.BandRef] = {

bandHeight: CARDINAL ← (lines + bandCount - 1)/bandCount;
bandName: LONG STRING = "PBAND."L;
heraldRef^ ← [mark: --Marker--, flags: [type: herald, rect: FALSE], band: ,--7777B
unused: , device: bDevice, bandCount: bandCount,
bandHeight: bandHeight, bandWidth: raster];
bRef ← repZone.NEW[BDevice.BandsRep[bandCount] ←
[count: bandCount, height: bandHeight, width: raster, list: ]];
FOR i: CARDINAL IN [0..bandCount) DO
bRef[i] ← [ymin: i*bandHeight, ymax: (i+1)*bandHeight,
stream: BStream.OpenBand[ bandName, i, overwrite]];
ENDLOOP;
--PBAND.0 ← herald record:
BStream.PutBand[bRef[0].stream, heraldRef, BFormat.heraldObjectSize];
--get a scanline buffer for "raster" words
lineRef ← uZone.NEW[Scanline[(raster+bitsPerWord-1)*bitsPerWord]];
--get a run buffer large enough for the max # of runs possible for this device
runsRef ← uZone.NEW[RunsBuffer[bandHeight]];

};--InitBands


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]] };

Frac: TYPE = Inline.LongNumber;
fscl: Frac = [num[lowbits: 0, highbits: 1]];

FixF: PROC[r: REAL] RETURNS[Frac] = INLINE {
RETURN[[li[Real.Fix[r*fscl.li]]]] };

ShowTrap: PROC [data: Data, trap: GB.Trap, src: Source.Ref, map: Matrix.Ref] = {
type: Source.Type ← src.type;
easy: BOOLEAN ← (SELECT type FROM
const, tile => TRUE, -- always easy
array => FALSE, -- never easy
proc => ERROR, --can't handle procs any more
ENDCASE => ERROR);
maskOnly: BOOLEAN ← src.bps=0;--kludge

yb,yt,yl,xl,xr, yStart, objHeight: CARDINAL ← 0;
rdxl,rdxr: REAL ← 0; -- left and right x increments
rsdx,rsdy: REAL ← 0; -- increments for source position
fsdx,fsdy: Frac; -- fractional versions of source position

fat: BOOLEAN ← src.fat;
rect: BOOLEANFALSE;
bps: CARDINAL = 8;--assumed for constant color trapezoids
maxSample: REAL = 255.0;--should be 2**bps
bSampPerWord: CARDINAL = bitsPerWord/bps;

hy: CARDINAL; -- index into halftone cBrick
lpx: CARDINAL ← 0;-- (L*px)

bands: BDevice.BandRef ← data.bands;
bandCount: CARDINAL ← bands.count;
bI: BStream.BandIndex ← 0;

DoHardLine: PROC[xmin,xmax,y: CARDINAL] = {
rsx,rsy: REAL; -- current source position

IF xmin>=xmax THEN RETURN; -- degenerate run
tPtr.count ← (xmax-xmin);

IF ~maskOnly THEN {
hy ← CGBrick.GetRow[bH, 0, y];
tPtr.bLine ← LOOPHOLE[cBrick+SIZE[NAT]+((L*hy)/bSampPerWord)]; --pointer to row of brick samples
tPtr.bi ← CGBrick.GetCol[bH, xmin, y]--+((L*hy) MOD bSampPerWord)--; -- starting x in brick
};
[[rsx,rsy]] ← Matrix.Inv[map,[xmin+0.5,y+0.5]];
tPtr.sx ← FixF[rsx].li; tPtr.sy ← FixF[rsy].li;
tPtr.sdx ← fsdx.li; tPtr.sdy ← fsdy.li;
CGFullSample.SAMPLE[tPtr];
BStream.PutBand[bands[bI].stream, lineRef, (tPtr.count+bitsPerWord-1)/bitsPerWord];
};--DoHardLine

DoRun: PROC[xmin, xmax: CARDINAL] = {
runsRef[runsIndex] ← [xmin: xmin, xmax: xmax];
runsIndex ← runsIndex+1;
};

-- main code for ShowTrap starts here
bH ← data.htBrick^;
IF bH#oldBh THEN {--prepare bricks
[L,p,D] ← CGBrick.GetSize[bH];--either cBrick or tBrick needs this
lpx ← L*p;
IF cBrick.size < lpx THEN {--need bigger brick buffers
uZone.FREE[@cBrick];
uZone.FREE[@tBrickTemp];
cBrick ← uZone.NEW[CBrick[lpx]];
tBrickTemp ← uZone.NEW[BFormat.TBrickRep[lpx]];
};--need bigger brick buffers
--fill in the scaled brick
FOR px: CARDINAL IN [0..p) DO
lpx ← L*px;
FOR lx: CARDINAL IN [0..L) DO
cBrick[lpx+lx] ← Inline.LowByte[Fix[maxSample*bH.cBrick[lpx+lx]]];
ENDLOOP;
ENDLOOP;
oldBh ← bH};--prepare bricks

--Initialize the nearly constant parts of the sample table if needed
IF ~easy THEN {
tPtr.dLine ← lineRef; --initialize scanline buffer
tPtr.sBase ← src.xbase; -- pointer to first word of source array
tPtr.sRast ← src.xrast; -- words per raster line in source array
tPtr.sh ← LAST[CARDINAL]; --large faked value
IF ~maskOnly THEN { --general array with source and brick
tPtr.bConst ← tPtr.sConst ← FALSE; tPtr.mConst ← TRUE;
tPtr.bw ← L; -- width of brick row, in samples
tPtr.size ← src.bps; -- sample size for source and brick
tPtr.sw ← src.xrast*(bitsPerWord/tPtr.size);
tPtr.function ← 14B; --opaque
}
ELSE { --mask only, no brick, use source like a mask
tPtr.bConst ← tPtr.mConst ← TRUE; tPtr.sConst ← FALSE;
tPtr.bValue ← 0; tPtr.size ← 1;
tPtr.sw ← src.xrast*bitsPerWord;
tPtr.function ← 3B; --transparent
};
};


FOR bI IN [0..bandCount) DO
IF SplitTrap[trap, bands[bI]] --writes the global lTrap--
THEN {--lTrap is in current band

-- compute yb (bottom of first scanline) and yt (top of last scanline)
IF fat THEN { yb𡤋ot[lTrap.ybot]; yt←Top[lTrap.ytop] }
ELSE { yb←Rnd[lTrap.ybot]; yt←Rnd[lTrap.ytop] };
IF yb<yt THEN yl←yt-1 -- yl is last line
ELSE { IF yb>yt OR fat THEN SIGNAL Error; GO TO exit };--skip this degenerate lTrap

-- ///////////////////////////////////////////////////////////////////////////////
rect ← objectRef.flags.rect ←
(lTrap.xbotL = lTrap.xtopL) AND (lTrap.xbotR = lTrap.xtopR);
objectRef.band ← bI;
yStart ← objectRef.yStart ← yb;
objHeight ← objectRef.height ← yt-yb;
-- //////////////////////////////////////////////////////////////////////////////

-- begin scan conversion; generate ALL runs first
runsIndex ← 0;
[[rsdx,rsdy]] ← Matrix.InvRel[map,[1,0]];
fsdx ← FixF[rsdx]; fsdy ← FixF[rsdy];
rdxl←(lTrap.xtopL-lTrap.xbotL); -- delta x, left
rdxr←(lTrap.xtopR-lTrap.xbotR); -- delta x, right
IF NOT(fat AND yb=yl) THEN {
rdy: REAL←lTrap.ytop-lTrap.ybot; -- delta y
rdxl←rdxl/rdy; rdxr←rdxr/rdy; -- dx/dy, left right
};
IF fat THEN {
rxlb,rxrb,rxlt,rxrt: REAL ← 0; -- x at bottom and top of current line
ltop: BOOLEAN ← rdxl<0; -- TRUE means leftmost x is at top of line
rtop: BOOLEAN ← rdxr>0; -- TRUE means rightmost x is at top of line
FOR y: CARDINAL IN[yb..yl] DO -- for each scan line
IF y=yb THEN { rxlb←lTrap.xbotL; rxrb←lTrap.xbotR } -- first line
ELSE { rxlb←rxlt; rxrb←rxrt }; -- successive lines
IF y=yl THEN { rxlt←lTrap.xtopL; rxrt←lTrap.xtopR } -- last line
ELSE IF y=yb THEN { -- first line, if yl>yb
d: REAL←(yb+1)-lTrap.ybot; -- distance to top of line
rxlt←rxlb+d*rdxl; rxrt←rxrb+d*rdxr;
}
ELSE { rxlt←rxlb+rdxl; rxrt←rxrb+rdxr }; -- middle lines
xl𡤋ot[IF ltop THEN rxlt ELSE rxlb];
xr←Top[IF rtop THEN rxrt ELSE rxrb];
IF xl<=xr THEN DoRun[xmin: xl, xmax: xr] ELSE ERROR; IF rect THEN EXIT;
ENDLOOP;
}
ELSE {
rxl,rxr: REAL ← 0; -- left and right x at middle of current line
FOR y: CARDINAL IN[yb..yl] DO -- for each scan line
IF y=yb THEN { -- first line
d: REAL←(yb+0.5)-lTrap.ybot; -- distance to middle of line
rxl←lTrap.xbotL+d*rdxl; rxr←lTrap.xbotR+d*rdxr;
  }
ELSE { rxl←rxl+rdxl; rxr←rxr+rdxr }; -- successive lines
xl←Rnd[rxl]; xr←Rnd[rxr];
IF xl<=xr THEN DoRun[xmin: xl, xmax: xr] ELSE ERROR; IF rect THEN EXIT;
ENDLOOP;
};

-- now generate the actual data for the runs

runsWords ← BFormat.runSize*runsIndex;
IF easy THEN { -- three cases for constant: all0, all1, threshold a brick if other
IF src.type = tile THEN {
tBrickTemp.L ← 16; tBrickTemp.p ← 16; tBrickTemp.D ← 0;
tBrickTemp.color ← LAST[CARDINAL];--unused
tBrickTemp.brickSize ← 256; tBrickWords ← BFormat.tBrickSize+16;
Inline.LongCOPY[to: @tBrickTemp.brick+1, from: src.xbase, nwords: 16];
objectRef.flags.type ← brick;  
}
ELSE IF src.color.tag = stipple THEN {
tBrickTemp.L ← 4; tBrickTemp.p ← 4; tBrickTemp.D ← 0;
tBrickTemp.color ← CGColor.GetStipple[src.color];
tBrickTemp.brickSize ← 16; tBrickWords ← BFormat.tBrickSize+1;
LOOPHOLE[@tBrickTemp.brick+1, LONG POINTER]^ ← tBrickTemp.color;
objectRef.flags.type ← brick;  
}
ELSE IF src.color = GC.black OR src.color = GC.white THEN
objectRef.flags.type ← IF src.color = GC.black THEN all1 ELSE all0
ELSE { -- intensity other than black or white
tBrickTemp.LL; tBrickTemp.p ← p; tBrickTemp.DD;
tBrickTemp.color ← FixC[maxSample*GetColorSep[src.color]];
tBrickTemp.brickSize ← L*p;
tBrickWords�ormat.tBrickSize+(tBrickTemp.brickSize+bitsPerWord-1)/bitsPerWord;
FOR px: CARDINAL IN [0..p) DO
lpx ← L*px;
FOR lx: CARDINAL IN [0..L) DO
tBrickTemp[lpx+lx] ← IF tBrickTemp.color >= Fix[maxSample*bH[lpx+lx]] THEN FALSE ELSE TRUE;
ENDLOOP;
ENDLOOP;
objectRef.flags.type ← brick;
};-- intenstiy other than black or white

--write out the completed Object (sans Runs)
BStream.PutBand[bands[bI].stream, objectRef, BFormat.objectSize];
BStream.PutBand[bands[bI].stream, runsRef, runsWords];--write runs
IF objectRef.flags.type = brick THEN
BStream.PutBand[bands[bI].stream, tBrickTemp, tBrickWords];--write tBrick
}--three easy cases

ELSE { -- hard case
  objectRef.flags.type ← bits;
  BStream.PutBand[bands[bI].stream, objectRef, BFormat.objectSize];--write object
BStream.PutBand[bands[bI].stream, runsRef, runsWords];--write out the runs
FOR rI: CARDINAL IN [0..objHeight) DO -- write out successive scanlines
runsIndex ← IF rect THEN 0 ELSE rI; -- must use (not band relative) y=yStart+rI
  DoHardLine[xmin: runsRef[runsIndex].xmin, xmax: runsRef[runsIndex].xmax, y: yStart+rI];
ENDLOOP;
  };-- hard case
EXITS
exit => NULL;
};--lTrap is in current band
ENDLOOP;-- end of [0..bcount) loop
};--ShowTrap

SplitTrap: PROC [t: GB.Trap, band: BDevice.Band] RETURNS [BOOLEANTRUE] = {
--this proc takes a trapezoid and a band and "returns"
--the interesection of these in global lTrap

bymin: REAL ← band.ymin;--bottom line included in band
bymax: REAL ← band.ymax;--top line included in band
xbotL,xbotR,ybot,xtopL,xtopR,ytop: REAL;
maxratio: REAL;

--first case: t completely out of band
IF t.ytop < bymin OR t.ybot > bymax THEN RETURN[FALSE];

xbotL ← t.xbotL; xbotR ← t.xbotR; ybot ← t.ybot;
xtopL ← t.xtopL ; xtopR ← t.xtopR ; ytop ← t.ytop ;

--second case: t body in band, t top above band
IF ytop > bymax THEN {
lTrap.ytop ← bymax; -- band relative coordinate of top of band
maxratio ← (bymax-ybot)/(ytop-ybot);--zero denom blows up
lTrap.xtopR ← xbotR + maxratio*(xtopR-xbotR);
lTrap.xtopL ← xbotL + maxratio*(xtopL-xbotL);
}

ELSE {--third case: t top in band
lTrap.ytop ← ytop;
lTrap.xtopL ← xtopL;
lTrap.xtopR ← xtopR;
};

--fourth case: t bottom in band
IF ybot >= bymin THEN {
lTrap.ybot ← ybot;
lTrap.xbotL ← xbotL;
lTrap.xbotR ← xbotR;
}

ELSE { --fifth case: t bottom below band
lTrap.ybot ← bymin;
maxratio ← (bymin-ybot)/(ytop-ybot);--zero denom blows up
lTrap.xbotR ← xbotR + maxratio*(xtopR-xbotR);
lTrap.xbotL ← xbotL + maxratio*(xtopL-xbotL);
};
};--SplitTrap

GetColorSep: PROC [color: GC.Color] RETURNS [REAL] = {
SELECT colorSep FROM
red=> RETURN [GC.ColorToRGB[color].r];
green => RETURN [GC.ColorToRGB[color].g];
blue => RETURN [GC.ColorToRGB[color].b];
none => RETURN [GC.ColorToIntensity[color]];
ENDCASE => ERROR;
};

-- START CODE

--brick storage
brickStartSize: CARDINAL = 100;--nominal size for bricks
CBrick: TYPE = RECORD[PACKED SEQUENCE size: NAT OF Byte];
cBrick: LONG POINTER TO CBrick ← uZone.NEW[CBrick[brickStartSize]];
tBrickTemp: BFormat.TBrickRef ← uZone.NEW[BFormat.TBrickRep[brickStartSize*bitsPerWord]];
tBrickWords: CARDINAL ← 0;--size of actual tBrick calculated

lTrap: REF GB.Trap ← repZone.NEW[GB.Trap ← [0,0,0,0,0,0, FALSE, FALSE]];
L,p: CARDINAL;--brick is L wide by p high
D: INTEGER ← 0;

heraldRef: BFormat.HeraldRef ← uZone.NEW[BFormat.HeraldObject]; --storage for herald obj
endRef: BFormat.EndRef ← uZone.NEW[BFormat.EndObject]; --initialized by this NEW call
objectRef: BFormat.ObjectRef ← uZone.NEW[BFormat.Object[1]]; --object head buffer

RunsBuffer: TYPE = RECORD[SEQUENCE COMPUTED CARDINAL OF BFormat.Run];
RunsRef: TYPE = LONG POINTER TO RunsBuffer;
runsRef: RunsRef ← NIL; -- initialized by InitBands
runsIndex: CARDINAL ← 0; -- runs buffer index
runsWords: CARDINAL ← 0; -- runsIndex*SIZE[Run]

Scanline: TYPE = BFormat.Line;
LineRef: TYPE = BFormat.LineRef;
lineRef: LineRef ← NIL; -- initialized by InitBands
lineIndex: CARDINAL ← 0;-- Scanline bit index

defaultTable: CGFullSample.Table ← [
function: 0, -- function
mConst: FALSE, -- mask value is constant
bConst: FALSE, -- brick value is constant
sConst: FALSE, -- source value is constant
useMap: FALSE, -- look up sample values in map
size: 0, -- sample size, for brick and source

count: 0, -- number of samples to process
bValue: 0, -- constant brick value, used if bConst=TRUE
sValue: 0, -- constant source value, used if sConst=TRUE

-- destination and mask information
dLine: NIL, -- pointer to row of destination bits
mLine: NIL, -- pointer to row of mask bits
di: 0, -- starting bit index in destination
mi: 0, -- starting bit index in mask

-- source to sample mapping table
map: NIL,

-- brick information
bLine: NIL, -- pointer to row of brick samples
bi: 0, -- starting sample index in brick
bw: 0, -- width of brick row, in samples

-- source information
sBase: NIL, -- pointer to first word of source array
sRast: 0, -- words per raster line in source array
sSpare: 0, -- not used
sw: 0, -- width of source, in samples
sh: 0, -- height of source, in lines
sox: 0, -- x offset of source, in samples
soy: 0, -- y offset of source, in lines
sx: 0, -- starting x position in source * 2^16
sy: 0, -- starting y position in source * 2^16
sdx: 0, -- increment to source x position * 2^16
sdy: 0 -- increment to source y position * 2^16
];

tPtr: CGFullSample.Pointer ← uZone.NEW[CGFullSample.Table ← defaultTable];
colorSep: BDevice.Separation ← none;
bH, oldBh: CGBrick.BrickHandle ← NIL;

}. -- CGBandDeviceImpl

LOG
--created 15-Feb-82 14:10:40 by Pier -- complete rewrite for new band file format
--changed to use LONG POINTERS instead of REFs, removed singleFile, 3/30/82
--swapped Heap with UnsafeStorage; NIL out all bases 5/3/82
--fixed bug in DLP bandcount, increasing from 32 to 72, 5/17/82
--fixed bug in SAMPLE setup when src.bps=0; eliminated MONITOR, 5/24/82
--changed to use color as defined in CGColor, 6/28/82
--upgrade to Cedar 3.2, 7/13/82
--upgrade to Cedar 3.3, added color separation kludge, September 18, 1982
--fixed bug in inverted tBricks, September 21, 1982 3:23 pm

Bier on October 11, 1982 11:02 am
Changed platemaker page size back to 11.0 and number of bands to 72.