DIRECTORY
Atom USING [MakeAtom],
BasicTime USING [GMT, Now, OutOfRange, Period, Update],
CD USING [CreateDrawRef, Design, DrawProc, DrawRectProc, DrawRef, Instance, InstanceList, Layer, LayerKey, Orientation, original, Position, Rect, undefLayer],
CDBasics USING [BaseOfAnyRect, Intersection, NonEmpty, SizeOfRect],
CDDirectory USING [EachEntryAction, Enumerate],
CDColors USING [ColorTable, DisplayMode, DisplayType, globalColors],
CDCurves USING [CurvePtr],
CDInstances USING [NewInst],
CDOps USING [DrawDesign, InstList],
CDOrient USING [CreateTransform],
CDTexts USING [TextPtr],
CDValue USING [Fetch],
Checksum USING [ComputeChecksum],
CStitching USING [all, Area, ChangeEnumerateArea, ChangeRect, DumpCache, EnumerateArea, NewTesselation, RectProc, Region, ResetTesselation, Tesselation, Tile, TileProc],
FS USING [ComponentPositions, Error, ExpandName, Position],
HashTable USING [Create, EachPairAction, Fetch, GetSize, Insert, Key, Pairs, Table],
Imager USING [ClipRectangle, Color, ColorOperator, ConcatT, Context, ConstantColor, DoSave, Font, MaskRectangle, MaskStrokeTrajectory, Rectangle, ScaleT, SetColor, SetFont, SetPriorityImportant, SetStrokeEnd, SetStrokeWidth, SetXY, ShowRope, StrokeEnd, TranslateT, VEC],
ImagerBrick USING [Brick, BrickRep],
ImagerColor USING [ColorFromRGB, RGB],
ImagerColorPrivate USING [ComponentFromColor],
ImagerColorOperator USING [ColorOperator, RGBLinearColorModel],
ImagerFont USING [Modify],
ImagerInterpress USING [Close, Create, DeclareColor, DeclareColorOperator, DeclareFont, DoPage, Ref],
ImagerPDPublic USING [Toner],
ImagerTransformation USING [Invert, Transformation],
Interpress USING [classAppearanceError, classAppearanceWarning, classComment, classMasterError, classMasterWarning, LogProc],
IO USING [atom, int, PutFR1, real, time],
MessageWindow USING [Append, Blink, Clear],
Nectarine USING [],
NodeStyle USING [FontFace],
NodeStyleFont USING [FontFromStyleParams],
PeachPrint USING [DoPeachPrintCommand, PupAborted],
PrincOpsUtils USING [],
PrintFileConvert USING [InterpressToPD, ParamsFromPrinterType, PDParams, ProgressProc],
Process USING [CheckForAbort, Detach, priorityBackground, SetPriority],
Real USING [Fix, Float],
RefTab USING [Create, Delete, EachPairAction, Fetch, Insert, Pairs, Ref],
Rope USING [Cat, Equal, Fetch, IsEmpty, Length, Replace, ROPE, SkipTo, Substr],
TerminalIO USING [TOS, WriteF, WriteInt, WriteRope],
UserProfile USING [Boolean, CallWhenProfileChanges, ProfileChangedProc, Token];
NectarineImpl: CEDAR PROGRAM
IMPORTS Atom, BasicTime, CD, CDBasics, CDColors, CDDirectory, CDInstances, CDOps, CDOrient, CDValue, Checksum, CStitching, FS, HashTable, Imager, ImagerColor, ImagerColorPrivate, ImagerColorOperator, ImagerFont, ImagerInterpress, ImagerTransformation, IO, MessageWindow, NodeStyleFont, PeachPrint, PrintFileConvert, Process, Real, RefTab, Rope, TerminalIO, UserProfile
EXPORTS Nectarine ~ BEGIN
OPEN Real;
break: SIGNAL = CODE;		-- for debugging
invalidPrinter: PUBLIC SIGNAL = CODE;
communicationsFailure: PUBLIC SIGNAL = CODE;
tooComplex: PUBLIC SIGNAL = CODE;
Font: TYPE = Imager.Font;
Color: TYPE = Imager.Color;
State: TYPE = REF StateRec;
StateRec: TYPE = RECORD [
previousColour: Color _ NIL,
previousStrokeWidth: REAL _ -1.0,
previousFont: Font _ NIL,
previousTextOrientation: CD.Orientation _ CD.original,
cardTile: CARD _ 0,	-- |{tile}|
startTime: BasicTime.GMT,
context: Imager.Context,
design: CD.Design,
interpress: ImagerInterpress.Ref,
tess: Tess,
abort: REF BOOL,
clip: BOOL _ FALSE,	-- Wysiwyg or selectedOnly
cdClip: CD.Rect,	-- Wysiwyg or selectedOnly
selectedOnly: BOOL,
band: REF CD.Rect _ NIL];
statistics: BOOL _ FALSE;
debug: BOOL _ FALSE;
remindFontConventions: BOOL _ TRUE;
risk: [0 .. 10) _ 2;	-- decrease if Nectarine runs out of VM.  More risk mean much more speed.  Geometric interpretation: consider a horizontal straight line through the design; you state that you have a rectangle only each risk l.  At zero risk, Nectarine uses only 14 MB of memory in the worst case.
Region: TYPE ~ LIST OF REF CStitching.Region;
Tess: TYPE ~ CStitching.Tesselation;
Tile: TYPE ~ CStitching.Tile;
empty: REF ~ NIL;
nothing: REF INT ~ NEW [INT];
StartDecomposition: PROC [state: State] RETURNS [dec: Tess] ~
{RETURN [CStitching.NewTesselation[stopFlag: state.abort]]};
FlushDecomposition: PROC [dec: Tess] ~ BEGIN
CStitching.ResetTesselation [dec]
END;	-- FlushDecomposition
PrintTile: CStitching.TileProc ~ BEGIN
state: State ~ NARROW [data];
b: Blend ~ NARROW [tile.value];
r: CD.Rect ~ CStitching.Area [tile];	-- not the area but the rectangle !
ChangeColour [state, b.blend];
state.context.MaskRectangle [ImagerRect [r]];
IF state.abort^ THEN ERROR ABORTED;
IF statistics THEN BEGIN
b.area _ b.area + (r.x2 - r.x1) * (r.y2 - r.y1);
state.cardTile _ SUCC [state.cardTile]
END
END;	-- PrintTile
PrintBand: PROC [state: State] ~ BEGIN
decomposition: Tess _ StartDecomposition [state];
gdr: CD.DrawRef ~ CD.CreateDrawRef [[]];
EnumerateGeometry: PROC ~ BEGIN
state.context.SetPriorityImportant [FALSE];	-- works for the devices at PARC today
decomposition.EnumerateArea [rect: CStitching.all, eachTile: PrintTile, data: state, skip: empty]
END;	-- EnumerateGeometry
Process.CheckForAbort [];	IF state.abort^ THEN ERROR ABORTED;
IF (state.clip OR (state.band # NIL)) THEN
gdr.interestClip _ IF (state.band = NIL) THEN state.cdClip
ELSE CDBasics.Intersection [state.cdClip, state.band^];
state.tess _ decomposition;
gdr.drawRect _ NewRect;	gdr.devicePrivate _ state;
IF state.selectedOnly THEN DrawSelection [state.design, gdr]
ELSE CDOps.DrawDesign [state.design, gdr];	-- pass 2
TerminalIO.WriteRope ["."];
BlendAllColours [];	TerminalIO.WriteRope ["."];	-- pass 3
state.previousColour _ NIL;	-- needed by Interpress
state.context.DoSave [EnumerateGeometry];	-- pass 4
FlushDecomposition [decomposition];
TerminalIO.WriteRope [". "];	-- state.tess _ decomposition _ NIL
END;	-- PrintBand
NewRect: CD.DrawRectProc ~ BEGIN
state: State ~ NARROW [pr.devicePrivate, State];
rect: CD.Rect _ IF (state.band = NIL) THEN r ELSE CDBasics.Intersection [r, state.band^];
IF (CDBasics.NonEmpty [rect]) THEN BEGIN
dec: Tess ~ state.tess;
InsertRect: CStitching.RectProc = BEGIN
WITH oldValue SELECT FROM
b: Blend => IF NOT b.flavours[l] THEN dec.ChangeRect [rect: rect, new: ColourTile [b, l]];
ENDCASE => BEGIN
b: Blend _ NEW [BlendRec];
dec.ChangeRect [rect: rect, new: ColourTile [b, l]]
END
END;	-- InsertRect
dec.ChangeEnumerateArea [rect: rect, eachRect: InsertRect, skip: nothing];
IF state.abort^ THEN ERROR ABORTED
END
END;	-- NewRect
DrawText: CD.DrawProc ~ BEGIN
state: State ~ NARROW [pr.devicePrivate];
context: Imager.Context ~ state.context;
text: CDTexts.TextPtr ~ NARROW [inst.ob.specificRef];
offset: Imager.VEC ~ text.cdFont.xy;
transf: ImagerTransformation.Transformation ~ CDOrient.CreateTransform [cellSize: inst.ob.size, cellInstOrient: orient, cellInstPos: pos];
invTransf: ImagerTransformation.Transformation ~ ImagerTransformation.Invert [transf];
Process.CheckForAbort [];	IF state.abort^ THEN ERROR ABORTED;
context.ConcatT [transf];	context.SetXY [offset];
ChangeColour [state, LayerColour [inst.ob.layer]];
ChangeFont [state, text.cdFont.font];
context.ShowRope [text.text];	context.ConcatT [invTransf]
END;	-- DrawText
DrawPath: CD.DrawProc ~ BEGIN
state: State ~ NARROW [pr.devicePrivate];
context: Imager.Context ~ state.context;
curve: CDCurves.CurvePtr ~ NARROW [inst.ob.specificRef];
transf: ImagerTransformation.Transformation ~ CDOrient.CreateTransform [cellSize: inst.ob.size, cellInstOrient: orient, cellInstPos: pos];
invTransf: ImagerTransformation.Transformation ~ ImagerTransformation.Invert [transf];
Process.CheckForAbort [];	IF state.abort^ THEN ERROR ABORTED;
context.ConcatT [transf];	-- context.SetXY [offset];
ChangeColour [state, LayerColour [inst.ob.layer]];
ChangeStrokeWidth [state, Float [curve.w]];
context.MaskStrokeTrajectory [curve.path];	context.ConcatT [invTransf]
END;	-- DrawPath
DrawObjectBorder: CD.DrawRectProc ~ BEGIN
state: State ~ NARROW [pr.devicePrivate, State];
pen: REAL ~ Float [state.design.technology.lambda / 4];
object, border: Imager.Rectangle;
Process.CheckForAbort [];	IF state.abort^ THEN ERROR ABORTED;
ChangeColour [state, black];
object _ ImagerRect [r];
object.x _ object.x - pen;	object.y _ object.y - pen;
object.w _ object.w + 2 * pen;	object.h _ object.h + 2 * pen;
border _ [x: object.x, y: object.y, w: object.w , h: pen];
state.context.MaskRectangle [border];
border _ [x: object.x, y: object.y, w: pen, h: object.h];
state.context.MaskRectangle [border];
border _ [x: object.x + object.w - pen, y: object.y, w: pen, h: object.h];
state.context.MaskRectangle [border];
border _ [x: object.x, y: object.y + object.h - pen, w: object.w, h: pen];
state.context.MaskRectangle [border]
END;	-- DrawObjectBorder
DrawObject: CD.DrawProc ~ BEGIN
Process.CheckForAbort [];
SELECT inst.ob.class.objectType FROM
$Text => DrawText [inst, pos, orient, pr];
$Spline0, $Line0, $Polygon0 => DrawPath [inst, pos, orient, pr];
ENDCASE =>  inst.ob.class.drawMe [inst, pos, orient, pr]
END;	-- DrawObject
DoInterpress: PUBLIC PROC [design: CD.Design, chipNDaleWindow: CD.Rect, clip, onlySel: BOOL _ FALSE, abortFlag: REF BOOL] RETURNS [masterName: Rope.ROPE, usedField: Imager.Rectangle] ~ BEGIN
interpress: ImagerInterpress.Ref;
state: State ~ NEW [StateRec];
rgbLinear: Imager.ColorOperator ~ ImagerColorOperator.RGBLinearColorModel [255];
medium: Imager.Rectangle ~ [x: 0.0, y: 0.0, w: 215.9, h: 279.4];	-- in mm
field: Imager.Rectangle ~ [x: medium.x + 10.0, y: medium.y + 10.0, w: medium.w - 20.0, h: medium.h - 20.0];	-- in mm
OpenIPMaster: PROC [] RETURNS [ImagerInterpress.Ref] ~ BEGIN
ENABLE {FS.Error => GOTO failure};
subDir: Rope.ROPE ~ "[]<>Temp>Nectarine>";	-- follows the religion
pos: FS.ComponentPositions;
ext: Rope.ROPE ~ ".dummy";	-- anything, just not to lose the dot
IF NOT design.name.IsEmpty[] THEN masterName _ design.name.Cat [ext]
ELSE BEGIN
cdName: Rope.ROPE ~ NARROW [CDValue.Fetch [design, $CDxLastFile]];
IF cdName.IsEmpty[] THEN masterName _ Rope.Cat ["UnnamedMaster", ext]
ELSE BEGIN
shortFName: Rope.ROPE;
[fullFName: masterName, cp: pos] _ FS.ExpandName [cdName, subDir];
shortFName _ masterName.Substr [start: pos.base.start, len: pos.base.length];
masterName _ shortFName.Cat [ext]
END
END;
[fullFName: masterName, cp: pos] _ FS.ExpandName [masterName, subDir];
masterName _ masterName.Replace [pos.ext.start, pos.ext.length, "Interpress"];
RETURN [ImagerInterpress.Create [masterName]];
EXITS
failure => BEGIN
masterName _ "[]<>Temp>Nectarine>UnnamedMaster.Interpress";
RETURN [ImagerInterpress.Create [masterName]]
END
END;	-- OpenIPMaster
DrawToIP: PROC [context: Imager.Context] ~ BEGIN
tdr: CD.DrawRef ~ CD.CreateDrawRef [[]];
window: Imager.Rectangle ~ ImagerRect [chipNDaleWindow];	-- in the CG sense
ratioW, ratioH, y0: REAL;
iterations, bandSize: INT;	-- number and size of bands
chronos: BOOL;
lap, end: BasicTime.GMT;
EnumerateTextInDesign: PROC ~ BEGIN
state.context.SetPriorityImportant [TRUE];	-- see EnumerateGeometry
IF state.selectedOnly THEN DrawSelection [state.design, tdr]
ELSE CDOps.DrawDesign [state.design, tdr]
END;	-- EnumerateTextInDesign
state.context _ context;	state.clip _ clip;	state.selectedOnly _ onlySel;
state.cdClip _ chipNDaleWindow;
SetLayerColourTable [];
ratioW _ field.w / window.w;	ratioH _ field.h / window.h;
usedField.x _ field.x;	usedField.y _ field.y;	-- in mm
IF ratioH < ratioW THEN
{usedField.w _ window.w * ratioH;	usedField.h _ field.h}
ELSE {usedField.w _ field.w;	usedField.h _ window.h * ratioW};
y0 _ 0.0;
context.TranslateT [[field.x, y0 + field.y]];  context.ScaleT [MIN [ratioW, ratioH]];
context.TranslateT [[-window.x, -window.y]];
IF statistics THEN CleanColourTable [state];
state.startTime _ BasicTime.Now [];
IF clip THEN context.ClipRectangle [window];	-- global to context !!!
bandSize _ (1000000 * (risk+1)) / Fix[window.w / design.technology.lambda];
IF bandSize < 4 * design.technology.lambda THEN SIGNAL tooComplex;
iterations _ Fix [window.h] / bandSize;	-- "zero relative" !
IF debug THEN BEGIN
TerminalIO.WriteRope [" there will be "];
TerminalIO.WriteInt [iterations];	TerminalIO.WriteRope [" reiterations "]
END
ELSE TerminalIO.WriteInt [iterations];
IF ((iterations = 0) AND (NOT state.clip)) THEN PrintBand [state]	-- shortcut
ELSE BEGIN
halftime: INT ~ iterations / 2;
currentBand: REF CD.Rect ~ NEW [CD.Rect _ chipNDaleWindow];
state.band _ currentBand;
chronos _ iterations > 5;
FOR b: INT DECREASING IN [0 .. iterations] DO
currentBand.y1 _ chipNDaleWindow.y1 + b * bandSize;
currentBand.y2 _ MIN [chipNDaleWindow.y2, currentBand.y1 + bandSize];
IF chronos THEN BEGIN
fudge: INT ~ 8;
IF (b = iterations - 3) THEN lap _ BasicTime.Now [];
IF (b = iterations - 4) THEN BEGIN
duration: INT ~ BasicTime.Period [lap, BasicTime.Now[]];
end _ BasicTime.Update [lap, fudge * duration * (b + 2) !
BasicTime.OutOfRange => GOTO endless]; 
TerminalIO.WriteF ["\nInterpress master will be ready ca. %g\n", IO.time [end]];
chronos _ FALSE
END
END;
PrintBand [state];
IF (b = halftime) AND (iterations > 10) THEN BEGIN
fudge: INT ~ 3;	-- more than 2 because of memory fragmentation
duration: INT ~ BasicTime.Period [state.startTime, BasicTime.Now[]];
end _ BasicTime.Update [state.startTime, fudge * duration !
BasicTime.OutOfRange => GOTO endless]; 
TerminalIO.WriteF ["\nInterpress master will be ready ca. %g\n", IO.time [end]]
END
ENDLOOP;
state.band _ NIL
END;
IF (state.tess # NIL) THEN {CStitching.DumpCache []; state.tess _ NIL};
context.SetStrokeEnd [square];
IF clip THEN tdr.interestClip _ chipNDaleWindow;
tdr.drawChild _ DrawObject;
tdr.drawOutLine _ DrawObjectBorder;	tdr.borders _ TRUE;
tdr.devicePrivate _ state;
state.previousColour _ NIL;	-- needed by Interpress
state.previousStrokeWidth _ -1.0;	-- needed by Interpress
context.DoSave [EnumerateTextInDesign];  TerminalIO.WriteRope [".   "];	-- pass 5
TerminalIO.WriteRope [TimeToRope [state.startTime, BasicTime.Now[]]];
TerminalIO.WriteRope ["\n"];
EXITS
endless => BEGIN
TerminalIO.WriteRope [" Would not terminate before 2036.\n"];
MessageWindow.Clear [];
MessageWindow.Append ["Nectarine would not terminate before 2036"];
MessageWindow.Blink [];
SIGNAL tooComplex
END
END;	-- DrawToIP
Action: PROC [] ~ BEGIN
DeclareColours: HashTable.EachPairAction ~ BEGIN
blendRec: Blend ~ NARROW [value];
IF (blendRec.blend # NIL) THEN interpress.DeclareColor [blendRec.blend];
RETURN [FALSE]
END;
DeclareFonts: RefTab.EachPairAction ~
{interpress.DeclareFont [NARROW [val,Font]]; RETURN [FALSE]};
ListFonts: RefTab.EachPairAction ~
{TerminalIO.WriteRope [NARROW[val,Font].name]; TerminalIO.WriteRope ["\n"];
RETURN [FALSE]};
state.interpress _ interpress _ OpenIPMaster [];
TerminalIO.WriteRope [Rope.Cat ["Producing Interpress master ", masterName, "\n"]];
interpress.DeclareColorOperator [rgbLinear];
[] _ colourTable.Pairs [DeclareColours];	-- this is a terrible hack, since the colours in the table are those from the previuos run. A request to provide a clean solution has been filed with the Imaging People.
UpdateFontMap [state];	-- pass 1
[] _ fontMap.Pairs [DeclareFonts];	TerminalIO.WriteRope [". "];
IF debug THEN BEGIN
TerminalIO.WriteRope ["\nThe following fonts are in the preamble:\n"];
[] _ fontMap.Pairs [ListFonts]
END;
interpress.DoPage [action: DrawToIP, scale: 0.001];
interpress.Close [];
IF (statistics OR debug) THEN ListColourTable [state];
TerminalIO.WriteRope [Rope.Cat ["Interpress master ", masterName, " is ready.\n"]]
END;	-- Action
state.design _ design;
state.abort _ IF abortFlag # NIL THEN abortFlag ELSE NEW [BOOL _ FALSE];
Action []	-- fork
END;	-- DoInterpress
DrawSelection: PROC [design: CD.Design, d: CD.DrawRef] ~ BEGIN
FOR all: CD.InstanceList _ CDOps.InstList [design], all.rest WHILE all # NIL DO
IF all.first.selected THEN d.drawChild [all.first, all.first.location, all.first.orientation, d]
ENDLOOP
END;	-- DrawSelection
EnumerateObjects: PROC [design: CD.Design, d: CD.DrawRef] ~ BEGIN
DoObject: CDDirectory.EachEntryAction ~ BEGIN
i: CD.Instance ~ CDInstances.NewInst [ob];
d.drawChild [i, [0,0], 0, d]
END;	-- DoObject
[] _ CDDirectory.Enumerate [design, DoObject]
END;	-- EnumerateObjects
ChangeColour: PROC [state: State, colour: Color] ~ INLINE BEGIN
context: Imager.Context ~ state.context;
a: ImagerColor.RGB ~ RGBFromColour [colour];
b: ImagerColor.RGB ~ RGBFromColour [state.previousColour];
IF (a.R # b.R) OR (a.G # b.G) OR (a.B # b.B) OR (state.previousColour = NIL) THEN BEGIN
context.SetColor [colour];	state.previousColour _ colour
END
END;	-- ChangeColour
ChangeStrokeWidth: PROC [state: State, w: REAL] ~ INLINE BEGIN
context: Imager.Context ~ state.context;
IF (w < 0) OR (w # state.previousStrokeWidth) THEN BEGIN
context.SetStrokeWidth [w];	state.previousStrokeWidth _ w
END
END;	-- ChangeStrokeWidth
ChangeFont: PROC [state: State, skFont: Font] ~ INLINE BEGIN
context: Imager.Context ~ state.context;
IF (skFont # state.previousFont) THEN BEGIN
context.SetFont [NARROW [fontMap.Fetch[skFont].val, Font]];
state.previousFont _ skFont
END
END;	-- ChangeFont
LogInterpress: Interpress.LogProc ~ BEGIN
TerminalIO.WriteRope [SELECT class FROM
Interpress.classMasterError => "Master Error: ",
Interpress.classMasterWarning => "Master Warning: ",
Interpress.classAppearanceError => "Appearance Error: ",
Interpress.classAppearanceWarning => "Appearance Warning: ",
Interpress.classComment => "Comment: ",
ENDCASE => IO.PutFR1 ["Class %g error: ", IO.int [class]]];
TerminalIO.WriteRope [explanation];	TerminalIO.WriteRope [" . . . \n"]
END;	-- LogInterpress
ProgressLog: PrintFileConvert.ProgressProc ~ BEGIN
IF begin THEN TerminalIO.WriteRope [IO.PutFR1 ["[%g", IO.int [page]]]
ELSE TerminalIO.WriteRope ["] "]
END;	-- ProgressLog
Bitset: TYPE ~ PACKED ARRAY CD.Layer OF BOOLEAN _ ALL [FALSE];
BlendKey: TYPE ~ REF Bitset;
Blend: TYPE ~ REF BlendRec;
BlendRec: TYPE ~ RECORD [count: CD.Layer _ 0,
flavours: Bitset,
blend: Color _ black,
area: CARD _ 0];
colourTable: HashTable.Table ~ HashTable.Create [557, Match, Hash];	-- or 997
layerColorTable: ARRAY CD.Layer OF Color;	-- must be set for each task
ColourTile: PROC [old: Blend, l: CD.Layer] RETURNS [new: Blend] ~ BEGIN
key: BlendKey ~ NEW [Bitset _ old.flavours];
key[l] _ TRUE;
new _ NARROW [colourTable.Fetch[key].value, Blend];
IF (new = NIL) THEN BEGIN
copy: Blend _ NEW [BlendRec _ [flavours: old.flavours]];
copy.count _ SUCC [old.count];
copy.flavours[l] _ TRUE;
new _ copy;
IF NOT colourTable.Insert [key, copy] THEN ERROR
END
END;	-- ColourTile
black: Color ~ ImagerColor.ColorFromRGB [[0.0, 0.0, 0.0]];
blue: Color ~ ImagerColor.ColorFromRGB [[0.0, 0.0, 1.0]];
blackRGB: ImagerColor.RGB ~ [0.0, 0.0, 0.0];
yellowRGB: ImagerColor.RGB ~ [1.0, 1.0, 0.0];
magentaRGB: ImagerColor.RGB ~ [1.0, 0.0, 1.0];
cyan: Color ~ ImagerColor.ColorFromRGB [[0.0, 1.0, 1.0]];
lightYellow: Color ~ ImagerColor.ColorFromRGB [[6.0/7.0, 6.0/7.0, 3.0/7.0]];
lightMagenta: Color ~ ImagerColor.ColorFromRGB [[5.0/7.0, 0.0, 5.0/7.0]];
BlendColours: HashTable.EachPairAction ~ BEGIN
components: Blend ~ NARROW [value];
n: REAL _ Float [components.count];
comp: PACKED ARRAY CD.Layer OF BOOLEAN _ components.flavours;
mix: ImagerColor.RGB _ blackRGB;
IF (components.blend # black) THEN RETURN [FALSE];	-- caching across sessions
SELECT n FROM
0 => ERROR;	-- should never have been allocated
1 => BEGIN
i: CD.Layer _ 0;
WHILE NOT comp[i] DO i _ SUCC [i] ENDLOOP;
components.blend _ LayerColour [i]
END;
ENDCASE => BEGIN
poly, diff, met, met2, cut, cut2, well: CD.Layer _ 0;
FOR i: CD.Layer IN CD.Layer DO
IF comp[i] THEN SELECT CD.LayerKey[i] FROM
$pol => poly _ i;
$ndif, $pdif => diff _ i;
$met => met _ i;
$met2 => met2 _ i;
$nwel => well _ i;
$cut => cut _ i;
$cut2 => {cut _ i; cut2 _ i};
ENDCASE => NULL
ENDLOOP;
IF (cut # 0) THEN components.blend _ IF (cut2 # 0) THEN blue ELSE black
ELSE BEGIN	-- Assume: all other colours have the same weight.
IF (poly # 0) AND (diff # 0) THEN BEGIN	-- Handle gates.
mix _ yellowRGB;	n _ n - 1.0;
comp[poly] _ comp[diff] _ FALSE
END;
IF (poly # 0) AND (met # 0) AND (diff = 0) THEN BEGIN	-- Handle metal over poly.
mix _ magentaRGB;	n _ n - 1.0;
comp[poly] _ comp[met] _ FALSE
END;
FOR i: CD.Layer IN CD.Layer DO	-- Compute mean colour.
IF comp[i] THEN BEGIN
v: ImagerColor.RGB ~ RGBFromColour [LayerColour[i]];
mix.R _ mix.R + v.R;	mix.G _ mix.G + v.G;	mix.B _ mix.B + v.B
END
ENDLOOP;
IF (met2 # 0) THEN BEGIN	-- make metal-2 transparent
mix.R _ mix.R - 4.0/7.0;	mix.B _ mix.B - 4.0/7.0;	n _ n - 4.0/7.0
END;
IF (well # 0) THEN BEGIN	-- make wells transparent
mix.R _ mix.R - 5.0/7.0;	mix.G _ mix.G - 5.0/7.0;	n _ n - 5.0/7.0;
mix.B _ mix.B - (3.0/7.0 * 2.0/7.0)	-- take out well lightener
END;
mix.R _ mix.R / n;	mix.G _ mix.G / n;	mix.B _ mix.B / n;
components.blend _ ImagerColor.ColorFromRGB [mix]
END
END;
RETURN [FALSE]
END;	-- BlendColours
LayerColour: PROC [l: CD.Layer] RETURNS [Color] ~ INLINE BEGIN
RETURN [layerColorTable[l]]
END;	-- LayerColour
SetLayerColourTable: PROC ~ BEGIN
FOR i: CD.Layer IN CD.Layer DO
SELECT CD.LayerKey[i] FROM
$nwel => layerColorTable[i] _ lightYellow;
$met => layerColorTable[i] _cyan;
$met2 => layerColorTable[i] _ lightMagenta;
ENDCASE => layerColorTable[i] _ CDColors.globalColors[bit8][normal].cols[i]
ENDLOOP
END;	-- SetLayerColourTable
BlendAllColours: PROC ~ BEGIN
[] _ colourTable.Pairs [BlendColours]
END;	-- BlendAllColours
Hash: PROC [k: HashTable.Key] RETURNS [CARDINAL] ~ BEGIN
TRUSTED BEGIN
RETURN [Checksum.ComputeChecksum [0, SIZE [BlendKey], LOOPHOLE [k]]]
END
END;	-- Hash
Match: PROC [a, b: HashTable.Key] RETURNS [BOOL] ~ BEGIN
k1: BlendKey ~ NARROW [a, BlendKey]; k2: BlendKey ~ NARROW [b, BlendKey];
RETURN [(k1^ = k2^)]
END;	-- Match
fontMap: RefTab.Ref ~ RefTab.Create [];	-- global
fontPrefix: ATOM ~ Atom.MakeAtom ["xerox/pressfonts/"];
visitedCells: RefTab.Ref;
DrawFilter: CD.DrawProc ~ BEGIN
SELECT inst.ob.class.objectType FROM
$Text => FindFont [inst, pos, orient, pr];
$Cell =>
IF visitedCells.Insert [inst.ob, $hack] THEN inst.ob.class.drawMe [inst, pos, orient, pr];
ENDCASE => NULL
END;	-- DrawFilter
FindFont: CD.DrawProc ~ BEGIN
text: CDTexts.TextPtr ~ NARROW [inst.ob.specificRef];
font: Font ~ text.cdFont.font;
IF NOT fontMap.Fetch[font].found THEN [] _ fontMap.Insert [font, Mapping [font]]
END;	-- FindFont
UpdateFontMap: PROC [state: State] ~ BEGIN
tdr: CD.DrawRef ~ CD.CreateDrawRef [[]];
Evict: RefTab.EachPairAction ~ {[] _ visitedCells.Delete [key];  RETURN [FALSE]};
remindFontConventions _ TRUE;
tdr.drawChild _ DrawFilter;	tdr.devicePrivate _ state;
IF state.selectedOnly THEN DrawSelection [state.design, tdr]
ELSE BEGIN
visitedCells _ RefTab.Create [557];
EnumerateObjects [state.design, tdr];
[] _ visitedCells.Pairs [Evict];	visitedCells _ NIL
END
END;	-- UpdateFontMap
Mapping: PROC [sk: Font] RETURNS [mr: Font] ~ BEGIN
shortFName, subDir, fullFName, family, attributes: Rope.ROPE;
cp: FS.ComponentPositions;
sizePos, facePos: INTEGER;
face: NodeStyle.FontFace _ Regular;
size: REAL;
[fullFName, cp] _ FS.ExpandName [name: sk.name];
subDir _ fullFName.Substr [start: cp.subDirs.start, len: cp.subDirs.length];
SELECT TRUE FROM
subDir.Equal ["Xerox>PressFonts", FALSE] => BEGIN
IF remindFontConventions THEN BEGIN
TerminalIO.WriteRope ["Nectarine takes care of all the font substitutions.  You can use the strike fonts for the layout.\n"];
remindFontConventions _ FALSE
END;
mr _ sk
END;
subDir.Equal ["Xerox>TiogaFonts", FALSE] => BEGIN
shortFName _ fullFName.Substr [start: cp.base.start, len: cp.base.length];
sizePos _ shortFName.SkipTo [0, "0123456789"];
attributes _ shortFName.Substr [sizePos, shortFName.Length[]-sizePos];
facePos _ attributes.SkipTo [0, "bBiI"];
size _ (ORD [attributes.Fetch[0]] - ORD ['0]);
FOR i: INT IN [1 .. facePos) DO
size _ size * 10.0 + (ORD [attributes.Fetch[i]] - ORD ['0])
ENDLOOP;
IF (facePos # attributes.Length[]) THEN BEGIN
it: BOOL ~ (attributes.SkipTo [0, "iI"] # attributes.Length[]);
b: BOOL ~ (attributes.SkipTo [0, "bB"] # attributes.Length[]);
SELECT TRUE FROM
it AND b => face _ BoldItalic;
it AND NOT b => face _ Italic;
NOT it AND b => face _ Bold;
ENDCASE => ERROR
END;
family _ shortFName.Substr [0, sizePos];
mr _ NodeStyleFont.FontFromStyleParams [prefix: fontPrefix, family: Atom.MakeAtom[family], face: face, size: size, alphabets: CapsAndLower];
mr _ ImagerFont.Modify [mr, sk.charToClient]
END;
ENDCASE => BEGIN
TerminalIO.WriteRope [Rope.Cat [fullFName, "font class", subDir, " unknown, not substituted.\n"]];
mr _ sk
END
END;	-- Mapping
ImagerRect: PROC [r: CD.Rect] RETURNS [Imager.Rectangle] ~ BEGIN
base: CD.Position ~ CDBasics.BaseOfAnyRect [r];
size: CD.Position ~ CDBasics.SizeOfRect [r];
RETURN [[Float[base.x], Float[base.y], Float[size.x], Float[size.y]]]
END;	-- ImagerRect
ImagerVec: PROC [p: CD.Position] RETURNS [Imager.VEC] ~ BEGIN
RETURN [[Float[p.x], Float[p.y]]]
END;	-- ImagerVec
RGBFromColour: PROC [c: Color] RETURNS [rgb: ImagerColor.RGB] ~ INLINE BEGIN
WITH c SELECT FROM
constant: Imager.ConstantColor => BEGIN
rgb.R _ ImagerColorPrivate.ComponentFromColor [constant, $Red];
rgb.G _ ImagerColorPrivate.ComponentFromColor [constant, $Green];
rgb.B _ ImagerColorPrivate.ComponentFromColor [constant, $Blue]
END;
ENDCASE => rgb _ [0.0, 0.0, 0.0];
RETURN [rgb]
END;	-- RGBFromColour
PeachProcess: PROC [masterName, peachName: Rope.ROPE, printerKey: ATOM, copies: INT] ~ BEGIN
ENABLE {PeachPrint.PupAborted => GOTO failure};
serverName: Rope.ROPE;
FillSample: PROC [s: ImagerBrick.Brick, a, b, c, d: REAL] ~ BEGIN
IF (s.size # 4 )THEN ERROR;
s.sSize _ 2;	s.fSize _ 2;	s.phase _ 0;	s.u _ 0;	s.v _ 0;
s.samples[0] _ a;	s.samples[1] _ b;
s.samples[2] _ c;	s.samples[3] _ d
END;	-- FillSample
TRUSTED {Process.SetPriority [Process.priorityBackground]};
SELECT printerKey FROM
$NVersatec => BEGIN
par: PrintFileConvert.PDParams _ PrintFileConvert.ParamsFromPrinterType [$versatec];
scale: REAL ~ (25.4 * par.pageFSize) / 215.9;	-- medium size in mm
serverName _ UserProfile.Token ["Nectarine.Versatec", "Sleepy"];
PrintFileConvert.InterpressToPD [inputName: masterName, outputName: peachName, params: par, sx: scale, sy: scale, logProc: LogInterpress, progressProc: ProgressLog]
END;
$NColorVersatec, $NPeachExpand => BEGIN
par: PrintFileConvert.PDParams _ PrintFileConvert.ParamsFromPrinterType [$colorVersatec];
scale: REAL ~ (25.4 * par.pageFSize) / 215.9;	-- medium size in mm
brickC: ImagerBrick.Brick _ NEW [ImagerBrick.BrickRep[4]];
brickM: ImagerBrick.Brick _ NEW [ImagerBrick.BrickRep[4]];
brickY: ImagerBrick.Brick _ NEW [ImagerBrick.BrickRep[4]];
serverName _ IF (printerKey = $NColorVersatec) THEN
UserProfile.Token ["Nectarine.ColorVersatec", "Sleepy"]
ELSE UserProfile.Token ["Nectarine.PeachExpand", "Bennington"];
FillSample [brickC, 0.2, 0.8, 0.6, 0.4];
FillSample [brickM, 0.6, 0.4, 0.2, 0.8];
FillSample [brickY, 0.2, 0.6, 0.8, 0.4];
par.bricks [cyan] _ brickC;
par.bricks [magenta] _ brickM;
par.bricks [yellow] _ brickY;
PrintFileConvert.InterpressToPD [inputName: masterName, outputName: peachName, params: par, sx: scale, sy: scale, logProc: LogInterpress, progressProc: ProgressLog]
END;
$NBw400 => BEGIN
par: PrintFileConvert.PDParams _ PrintFileConvert.ParamsFromPrinterType [$bw400];
serverName _ UserProfile.Token ["Nectarine.Bw400", "MtFuji"];
PrintFileConvert.InterpressToPD [inputName: masterName, outputName: peachName, params: par, sx: 1.3, sy: 1.3, logProc: LogInterpress, progressProc: ProgressLog]
END;
$NColor400 => BEGIN
par: PrintFileConvert.PDParams _ PrintFileConvert.ParamsFromPrinterType [$color400];
par.ppd _ 4.0;
serverName _ UserProfile.Token ["Nectarine.Color400", "MtFuji"];
PrintFileConvert.InterpressToPD [inputName: masterName, outputName: peachName, params: par, sx: 1.3, sy: 1.3, logProc: LogInterpress, progressProc: ProgressLog]
END;
$NRaven300 => serverName _ UserProfile.Token ["Nectarine.Raven300", "Quoth"];
ENDCASE => NULL;	-- can never happen
TerminalIO.WriteRope [Rope.Cat ["Sending ", peachName, " to ", serverName, "\n."]];
PeachPrint.DoPeachPrintCommand [serverName, peachName, TerminalIO.TOS[], FALSE, copies];
IF (printerKey = $NPeachExpand) THEN BEGIN
pos: FS.ComponentPositions ~ FS.ExpandName[peachName].cp;
server2Name: Rope.ROPE ~ UserProfile.Token ["Nectarine.ColorVersatec", "Sleepy"];
simpleName: Rope.ROPE ~ peachName.Substr [pos.base.start, pos.base.length];
peachName _ Rope.Cat ["[", serverName, "]<Cedar>PD>", simpleName, "-1.PD"];
TerminalIO.WriteRope [Rope.Cat ["Sending ", peachName, " to ", server2Name, "\n."]];
PeachPrint.DoPeachPrintCommand [server2Name, peachName, TerminalIO.TOS[], FALSE, copies]
END;
EXITS
failure => BEGIN
TerminalIO.WriteRope [Rope.Cat ["Communications failure. File saved on ", peachName, "for manual retry.\n"]];
MessageWindow.Clear [];
MessageWindow.Append ["Nectarine: Peach communications failure"];
MessageWindow.Blink []
END
END;	-- PeachProcess
Print: PUBLIC PROC [masterName: Rope.ROPE, printerKey: ATOM, copies: INT _ 1] RETURNS [peachName: Rope.ROPE] ~ BEGIN
IF (masterName = NIL) THEN TerminalIO.WriteRope ["Produce an Interpress master first.\n"]
ELSE BEGIN
pos: FS.ComponentPositions ~ FS.ExpandName[masterName].cp;
SELECT printerKey FROM
$NVersatec, $NColorVersatec, $NBw400, $NColor400, $NPeachExpand =>
peachName _ masterName.Replace [pos.ext.start, pos.ext.length, "PD"];
$NRaven300 => peachName _ masterName;	-- understands Interpress
ENDCASE => SIGNAL invalidPrinter;
Process.CheckForAbort [];
TRUSTED BEGIN
Process.Detach [FORK PeachProcess [masterName, peachName, printerKey, copies]]
END;
TerminalIO.WriteRope ["Peach printing process forked off.\n"]
END
END;	-- Print
GetStatisticsToggle: UserProfile.ProfileChangedProc ~ BEGIN
statistics _ UserProfile.Boolean [key: "Nectarine.Statistics"]
END;
ListColourTable: PROC [state: State] ~ BEGIN
totalArea: REAL _ 0.0;	-- It is the way it is because of numerical stability.
ComputeArea: HashTable.EachPairAction ~ BEGIN
data: Blend ~ NARROW [value];
totalArea _ totalArea + Float [data.area]
END;	-- ComputeArea
ListEntry: HashTable.EachPairAction ~ BEGIN
data: Blend ~ NARROW [value];
comp: ImagerColor.RGB ~ RGBFromColour [data.blend];
IF totalArea = 0.0 THEN totalArea _ 1.0;
TerminalIO.WriteF ["%g\t%g\t%g\t\t%g\t", IO.real[comp.R], IO.real[comp.G], IO.real[comp.B], IO.real[Float[data.area]/totalArea]];
FOR i: CD.Layer IN CD.Layer DO
IF data.flavours[i] THEN TerminalIO.WriteF ["  %g", IO.atom [CD.LayerKey[i]]]
ENDLOOP;
TerminalIO.WriteRope ["\n"]
END;	-- ListEntry
TerminalIO.WriteF ["Statistical data gathered by Nectarine:\n\tSize of color table: %g; number of tiles: %g\n\tColor (R, G, B), relative area and layers\n", IO.int [colourTable.GetSize[]], IO.int [state.cardTile]];
[] _ colourTable.Pairs [ComputeArea];
IF debug THEN BEGIN
[] _ colourTable.Pairs [ListEntry];
TerminalIO.WriteRope ["Colors with null area were intermediate.\n"]
END
END;	-- ListColourTable
CleanColourTable: PROC [state: State] ~ BEGIN
ResetArea: HashTable.EachPairAction ~ {rec: Blend ~ NARROW [value]; rec.area _ 0};
[] _ colourTable.Pairs [ResetArea];  state.cardTile _ 0
END;	-- CleanColourTable
TimeToRope: PROC [from, to: BasicTime.GMT] RETURNS [time: Rope.ROPE] ~ BEGIN
tmp: Rope.ROPE;
sec: INT = BasicTime.Period [from, to];
min: INT = sec / 60;
h: INT = min / 60;
tmp _ IO.PutFR1 [value: IO.int [h]];
time _ SELECT h FROM
= 0 => "00",
< 10 => Rope.Cat ["0", tmp],
ENDCASE => tmp;
tmp _ IO.PutFR1 [value: IO.int [min MOD 60]];
time _ Rope.Cat [time, ":", SELECT min FROM
= 0 => "00",
< 10 => Rope.Cat ["0", tmp],
ENDCASE => tmp];
tmp _ IO.PutFR1 [value: IO.int [sec MOD 60]];
time _ Rope.Cat [time, ":", SELECT sec FROM
= 0 => "00",
< 10 => Rope.Cat ["0", tmp],
ENDCASE => tmp]
END;	-- TimeToRope
UserProfile.CallWhenProfileChanges [GetStatisticsToggle]
END.
��l��NectarineImpl.mesa
Copyright c 1986 by Xerox Corporation.  All rights reserved.
Giordano Bruno Beretta, April 11, 1986 7:57:41 pm PST
gbb August 21, 1986 6:10:29 pm PDT

Implements an alternate way to produce Interpress masters from ChipNDale drawings.  The difference is in the user interface.  It is similar to the one in programs by Imaging Folks, and it is simpler to use for casual users.
Fuzzless and sweeter than peaches (Suzanne Williams)
Implementation note on clipping:  If bands have to be created because of the size of the design, true clipping to bands must be done when traversing the design.  The penalty on the corner stitched data structure may be swallowed, since it is an overnight job anyway.  However, leaving clipping to the Imager, you will have all those rectangles in the Interpress master with their multiciplity.  A large disk can hold only about 90% of a thing like the Cross-RAM, and every single file on your disk will have been flushed off when you come in in the morning.
If you insist on leaving the clipping to the imager, then you must be very careful deciding where to place it.  The reason is that clipping in the Imager is relative, and therefore the window must be specified inside Do-Save-Simple-Body, in order not to disturb the global clipping window.  The places would be EnumerateGeometry and EnumerateTextInDesign.
Geometry
Does what FreeTesselation supposedly did once upon a time.
PROC [tile: REF Tile, data: REF]
Prints a band.  If there is only one band and no clipping is necessary, setting clip to false will make it faster.
[r: Rect, l: Layer, pr: DrawRef]
Note that merging works correctly because of the use of the colour table.
[plane: REF Tesselation, rect: Rect, oldValue: REF, data: REF]
Annotation
[inst: CD.Instance, pos: CD.Position, orient: CD.Orientation, pr: CD.DrawRef]
[inst: CD.Instance, pos: CD.Position, orient: CD.Orientation, pr: CD.DrawRef]
[r: Rect, l: Layer, pr: DrawRef]
The border is drawn outside the cell, since this is the way they are used by Rick Barth, currently the only creator of documents using boxes.
South:
West:
East:
North:
[inst: Instance, pos: Position, orient: Orientation, pr: REF DrawInformation]
$FilledCurve0 =>
The procedure for rectangles is called through the recursion step.
Interpress
Produces an Interpress master of the design.  The master is scaled such that it fits a whole page.  chipNDaleWindow is either the bounding box of the design or a window in it.  In the latter case, clip must be set to TRUE, and objects completetly outside the window will be ommitted from the Interpress master (because of things like mitering, actual clipping can be performed only when a bitmap is created).
The usedField is specified in millimeters.  It is useful for subsequent processing of the Interpress master as long as this field cannot be specified in the preamble of Interpress masters themselves.
If onlySel is true, only the selected object are included in the Interpress master.
May return signal tooComplex if it is believed that there might be too many rectangles in a horizontal cross section.  The used criterion is the width of the design; if you do not agree, use the Interpreter to increase the risk.
Creates the interpress master.
Called back by the Interpress machinery.
Preview considers the top of the page to be most important, because we write text from top to bottom.  Also designers want have images to be flush to the top of the field, so they can use the bottom of the medium for hand-annotations.  Unfortunately, this causes a severe problem when producing a PD file.  In fact there is said to be a hack fixing a hard bug in the Peach software.  This hack is said to be a white rectangle at the lower left corner of the medium.  On the Versatec this means that with every image in landscape format you would get meters of white paper.  This is why images are positioned in the lower left corner of the field.
y0 _ IF ratioH < ratioW THEN 0.0 ELSE field.h - window.h * ratioW;
Rectangles:
Magic numbers: Assume 14 MB of memory may be used.  Each tile requires 7 words of storage, hence 106 tiles can be stored.  In the current worst case, a die is 10 mm wide.  If a gate can be 2 mm long, in the worst case there is a rectangle each mm.
The intersection of the current band with the clipping window is performed by PrintBand.  The field state.cdClip is assigned earlier.
Produce bands from high to low y-coordinate values in order to avoid paging in succeeding software.
The first bands are not typical, because they are not dense.
Text:
Does it at background priority.
TRUSTED {Process.SetPriority [Process.priorityBackground]};
Produce preamble.
Create a table of the fonts and them in the preamble.
Produce the page.  All coordinates will be in millimeters.
Close.
Same as CDOps.DrawDesign, but visits only the selected objects.
Same as CDOps.DrawDesign, but visits objects only once.
PROC [name: Rope.ROPE, ob: CD.Object] RETURNS [quit: BOOL_FALSE]
At this point we know that only one colour representation is used.  Must be fast as a bullet.
w < 0 means that it has not yet been set in this body.  Must be fast as a bullet.
Must be fast as a bullet
Called for errors during interpress execution.  [class: INT, code: ATOM, explanation: ROPE]
[begin: BOOL, page: INT]
Color Blending
Data is global
Sets up a blending record for a tile.  Must be fast as a bullet.
Takes the layers covering a tile and blend an RBG-colour out of them.
Find exception layers.
Cuts always win.
Reinitialize mix by yellow and eliminate poly and diff.
Ensure that only one colour representation is used.
Spread out hues & make "more subtractive".
The logarithm of the number of colours is two, that of the rectangles is six.
PROC [Key] RETURNS [CARDINAL]
HashTable.EqualProc
Conversions
Data is global
[inst: Instance, pos: Position, orient: Orientation, pr: REF DrawInformation]
There is no facility offered by ChipNDale to visit only a cell without recursing to its subcells, so here is a homebrew hack.
[inst: Instance, pos: Position, orient: Orientation, pr: REF DrawInformation]
The map is global, because fonts rarely change across designs.
DrawDesign is an overkill, which easily takes 20 minutes on the CrossRAM.  There is no facility offered by ChipNDale to visit only a cell without recursing to its subcells, so here is a homebrew hack.
Translates from strike to spline fonts.
Construct the old style name:
Find the size and face from the old style name:
Compute the size (assume: there always is a size):
Determine the face:
CdPos: PROC [v: Imager.VEC] RETURNS [CD.Position] ~ BEGIN
RETURN [[Round[v.x], Round[v.y]]]
END;	-- CdPos
Assume that LayerColour had previously been called.
Printing
This is a mess.  The religion asks me to propagate the error I get from PeachPrint to my client.  However, PeachPrint just sits there until all printing is done or aborts locking up ChipNDale.  Therefore, until PeachPrint is not fixed and forks off a process by its own, I do it myself and swallow that bloody event.
Should be in Cedar.
Medium size in inches: 40" X 40".  Exact scale: 4.705883
Medium size in inches: 40" X 40".  Exact scale: 4.705883
Use the following three statements to obtain very fast colors:
Or use the following statement to obtain quality colors (rotated screens):
par.ppd _ 2.0;
Medium size in inches: 11" X 14".  Exact scale: 1.294118
Medium size in inches: 11" X 14".  Exact scale: 1.294118
SIGNAL communicationsFailure
Produces (if necessary) a PD file from an Interpress master and ships it to the printer.  Valid printer keys are $NVersatec, $NColorVersatec, $NBw400, $NColor400, $NRaven300.  May return signals invalidPrinter and communicationsFailure.
Statistics
Lists the statistics on the colour table.
We initialize only the area so as to cache colour blendings across sessions.
Although the INT returned BasicTime.Period is the same as GMT and might hence be loopholed to use IO.time from Conversions, the latter uses BasicTime.Unpack which allows only values that give a valid date.
Initialization
Ê"î��˜�codešœ™Kšœ
Ïmœ1™<Kšœ5™5K™"—K™�™ßIquote™4—code2šÏk	˜	Kšœžœ˜Kšœ
žœžœ#˜7Kšžœžœ–˜žKšœ	žœ5˜CKšœžœ˜/Kšœ	žœ6˜DKšœ	žœ˜Kšœžœ˜Kšœžœ˜#Kšœ	žœ˜!Kšœžœ˜Kšœžœ	˜Kšœ	žœ˜!Kšœžœ™˜©Kšžœžœ3˜;Kšœ
žœE˜TKšœžœýžœ˜ŽKšœžœ˜$Kšœžœžœ˜&Kšœžœ˜.Kšœžœ&˜?Kšœžœ
˜KšœžœO˜eKšœžœ	˜Kšœžœ˜4Kšœžœm˜}Kšžœžœ!˜)Kšœžœ˜+Kšœ
žœ˜Kšœ
žœ˜Kšœžœ˜*Kšœžœ#˜3Kšœžœ˜KšœžœA˜WKšœžœ:˜GKšœžœ˜Kšœžœ=˜IKšœžœ/žœ˜OKšœžœžœ˜4Kšœžœ>˜O—MšÐln
œžœž˜Mšžœžœ`žœžœr˜ðMšžœ
ž˜šžœ˜
IunitšÏbœŽ™­Kšœ·Ïeœ¡œ™ãNšœžœžœÏc˜'Kšœžœžœžœ˜%Kšœžœžœžœ˜,Kšœžœžœžœ˜!Nšœžœ˜Kšœžœ˜Nšœžœžœ
˜Kš-œ
žœžœžœžœžœžœžœžœ¢œžœ#žœ>žœžœžœžœ¢œžœ¢œžœžœžœžœ˜×Nšœžœžœ˜Kšœžœžœ˜Nšœžœžœ˜#Nšœ¢ËÐce¢Ðcg¢G˜­—head™Mš	œžœžœžœžœ˜-Kšœžœ˜$Kšœžœ˜Kšœžœžœ˜Kš	œ	žœžœžœžœ˜šÏnœžœžœ˜=Kšœžœ5˜<—š¥œžœž˜,Kšœ
¡œ!™:Kšœ!˜!Kšžœ¢˜—š¥	œž˜&Kšžœžœ
žœ™ Kšœžœ˜Kšœžœ˜Kšœžœ ¢#˜HNšœ˜Kšœ-˜-Kšžœžœžœžœ˜#šžœžœž˜Kšœ0˜0Kšœžœ˜&Kšž˜—Kšžœ¢	˜—š¥	œžœž˜&KšœP¡œ¡œ™rKšœ1˜1Kšœžœžœ˜(š¥œžœž˜Kšœ$žœ¢&˜RKšœa˜aKšžœ¢˜—Nš	œžœžœžœžœ˜=šžœ
žœžœž˜*Kš	œžœžœžœžœ3˜r—Kšœ˜Kšœ2˜2Kšžœžœ"˜<Kšžœ'¢Ðcl˜4Kšœ˜Kšœ0¢¦˜9Kšœžœ¢˜3Kšœ*¢¦˜3Kšœ#˜#Kšœ¢#˜@Kšžœ¢˜—š¥œžœž˜ Kšœ ™ Kšœžœ˜0Kšœžœžœžœžœžœ(˜Yšžœžœž˜(KšœI™IKšœ˜š¥
œž˜'Kšœžœ$žœžœ™>šžœ
žœž˜Kšœžœžœžœ5˜Zšžœž˜Kšœžœ˜Kšœ3˜3Kšž˜——Kšžœ¢
˜—NšœJ˜JKšžœžœžœž˜"Kšž˜—Kšžœ¢˜——™
š¥œžœž˜Kš	œžœžœžœžœ	™MKšœžœ˜)Kšœ(˜(Kšœžœ˜5Kšœžœ˜$KšœŠ˜ŠKšœV˜VNš	œžœžœžœžœ˜=Kšœ1˜1Kšœ2˜2Kšœ%˜%Kšœ9˜9Kšžœ¢˜—š¥œžœž˜Kš	œžœžœžœžœ	™MKšœžœ˜)Kšœ(˜(Kšœžœ˜8KšœŠ˜ŠKšœV˜VNš	œžœžœžœžœ˜=Nšœ¢˜4Kšœ2˜2Kšœ+˜+KšœF˜FKšžœ¢˜—š¥œžœž˜)Kšœ ™ K™Kšœžœ˜0Kšœžœ.˜7Kšœ!˜!Kš	œžœžœžœžœ˜=Kšœ˜Kšœ˜Kšœ™Kšœ5˜5Kšœ=˜=Kšœ:˜:Kšœ%˜%Kšœ™Kšœ9˜9Kšœ%˜%Kšœ™KšœJ˜JKšœ%˜%Kšœ™KšœJ˜JKšœ$˜$Kšžœ¢˜—š¥
œžœž˜Kšœ9žœ™MKšœ˜šžœž˜$Kšœ*˜*Kšœ@˜@K™K™BKšžœ1˜8—Kšžœ¢
˜——™
š¥œžœžœ
žœžœžœžœ
žœžœžœžœ!ž˜¾Kšœd¡œR¡œžœ»™˜Kšœ¡	œº™ÇKšœ¡œI™SKšœ¡
œÃ¡œ™äKšœ!˜!Kšœžœ˜KšœP˜PKšœA¢˜IKšœl¢˜tš¥œžœžœž˜<K™Kšžœžœ
žœ
˜"Kšœ
žœ¢˜BKšœžœ˜Kšœ
žœ
¢%˜@Nšžœžœžœ#˜Dšžœž˜
Kšœ
žœžœ'˜BKšžœžœ-˜Ešžœž˜
Kšœžœ˜Kšœ#žœ˜BKšœM˜MKšœ!˜!Kšž˜—Kšžœ˜—Kšœ#žœ!˜FKšœN˜NKšžœ(˜.šž˜šœž˜Kšœ;˜;Kšžœ'˜-Kšž˜——Kšžœ¢˜—š¥œžœž˜0K™(Kšœžœžœ˜(Kšœ9¢˜KKšœžœ˜Kšœžœ¢˜6Kšœ	žœ˜Kšœžœ˜š¥œžœž˜#Kšœ$žœ¢˜CKšžœžœ"˜<Kšžœ%˜)Kšžœ¢˜—Nšœ+Ðbxœ˜IKšœ˜Nšœ˜Kšœ9˜9Kšœ.¢˜6šžœž˜Kšœ8˜8—Kšžœ:˜>šœ©žœÛ™†Kšœžœžœžœ™B—Kšœ	˜	Kšœ?žœ˜UKšœ,˜,Kšžœžœ˜,Kšœ#˜#Kšžœžœ!¢˜EN™KšœcÏuœ[Ïgœ4©œ™÷KšœK˜KKšžœ(žœžœ˜BKšœ(¢˜<šžœžœž˜Kšœ)˜)KšœI˜IKšž˜—Kšžœ"˜&Kš	žœžœžœžœ¢˜Mšžœž˜
Kšœ
žœ˜Kš	œ
žœžœžœžœ˜;KšœN£	œ
¡œ™…Kšœ˜Kšœ˜š	žœžœž
œžœž˜-K™cKšœ3˜3Kšœžœ1˜Ešžœ	žœž˜K™<Kšœžœ˜Kšžœžœ˜4šžœžœž˜"Kšœ
žœ+˜8KšœRžœ˜aKšœAžœ
˜PKšœ
ž˜Kšž˜—Kšžœ˜—Kšœ˜šžœžœžœž˜2Kšœžœ¢.˜>Kšœ
žœ7˜DKšœTžœ˜cKšœAžœ˜OKšž˜—Kšžœ˜—Kšœ
ž˜Kšžœ˜—Kšžœžœžœ(žœ˜GN™Kšœ˜Kšžœžœ$˜0Kšœ˜Kšœ2žœ˜7Kšœ˜Kšœžœ¢˜3Kšœ"¢˜9KšœH¢¦˜QKšœE˜EKšœ˜šž˜šœž˜Kšœ=˜=Kšœ˜KšœC˜CKšœ˜Kšžœ˜Kšž˜——Kšžœ¢˜—š¥œžœž˜K™š¥œž˜0Kšœžœ	˜!Kšžœžœžœ*˜HKšžœžœ˜Kšžœ˜—š¥œ˜%Kšœžœ
žœžœ˜=—š¥	œ˜"Kšœžœ.˜KKšžœžœ˜—Nšžœ4™;Kšœ0˜0KšœS˜SN™Kšœ,˜,Kšœ)¢©˜ÒK™5Kšœ¢¦˜ Kšœ?˜?šžœžœž˜KšœF˜FKšœ˜Kšžœ˜—N™:K•StartOfExpansionI[self: ImagerInterpress.Ref, action: PROC [...], scale: REAL _ 1.0]šœ3˜3N™Kšœ˜Kšžœ
žœžœ˜6KšœR˜RKšžœ¢	˜—Nšœ˜Kšœžœ
žœžœžœžœžœžœ˜HNšœ
¢˜Kšžœ¢˜—š	¥
œžœ
žœžœž˜>Kšœ?™?š	žœžœ2žœžœž˜OJšžœžœF˜`Jšž˜—Kšžœ¢
˜—š	¥œžœ
žœžœž˜AKšœ7™7š¥œ ž˜-Kš
žœ
žœžœ	žœž
œ™@Kšœžœ%˜*Kšœ˜Kšžœ¢˜—Kšœžœ˜-Kšžœ¢˜—š¥œžœ!žœž˜?K™]Kšœ(˜(Kšœžœ˜,Kšœžœ(˜:š
žœ
žœ
žœ
žœžœžœž˜WKšœ8˜8Kšž˜—Kšžœ¢˜—š	¥œžœžœžœž˜>MšœQ™QKšœ(˜(šžœ	žœ!žœž˜8Kšœ9˜9Kšž˜—Kšžœ¢˜—š¥
œžœ žœž˜<Kšœ™Kšœ(˜(šžœžœž˜+Kšœžœ$˜;Kšœ˜Kšž˜—Kšžœ¢
˜—š¥
œž˜)Kš¢-œžœžœžœ™[Kšœžœžœ„žœžœžœ˜çKšœF˜FKšžœ¢˜—š¥œ"ž˜2Kšœžœžœ™Kšžœžœžœžœ
˜EKšžœ˜ Kšžœ¢˜——™O™Mšœžœžœžœžœžœžœžœžœ˜>Kšœ
žœžœ˜Kšœžœžœ
˜Kš	œ
žœžœ	žœ:žœ˜fMšœD¢	˜MMšœžœžœžœ¢˜Fš	¥
œžœžœžœž˜GK™@Kšœžœ˜,Kšœ	žœ˜Kšœžœ'˜3šžœžœžœž˜Kšœžœ'˜8Kšœ
žœ
˜Kšœžœ˜Kšœ˜Kšžœžœ žœž˜0Kšž˜—Kšžœ¢
˜—Mšœ:˜:Kšœ9˜9Kšœžœ˜,Kšœžœ˜-Kšœžœ˜.Kšœ9˜9KšœL˜LKšœI˜Iš¥œž˜.Kšœ.žœ™EKšœžœ	˜#Kšœžœ˜#Kšœžœžœžœžœžœ˜=Kšœžœ˜ Nš	žœžœžœžœ¢˜Mšžœž˜
Kšœžœ¢#˜/šœž˜
Kšœžœ˜Kš
žœžœ	žœžœžœ˜*Kšœ"˜"Kšžœ˜—šžœž˜Kšœ(žœ˜5K™š	žœžœžœžœž˜š	žœ	žœžœžœ
ž˜*Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšžœž˜—Kšžœ˜—K™Kš
žœ
žœžœžœžœ˜Gšžœžœ¢2˜=š	žœžœžœžœ¢˜8Kšœ7™7Kšœ˜Kšœž˜Kšžœ˜—šžœžœžœžœžœ¢˜PKšœ˜Kšœž˜Kšžœ˜—šžœžœžœžœžœ¢˜6šžœ	žœž˜Kšœžœ"˜4Kšœ=˜=Kšž˜—Kšžœ˜—šžœžœžœ¢˜4KšœA˜AKšžœ˜—šžœžœžœ¢˜2KšœB˜BKšœ>˜>Kšžœ˜—Kšœ8˜8Kšœ1˜1Kšž˜—Kšž˜—Kšžœžœ˜—Kšžœ¢˜—š¥œžœžœžœžœž˜>K™3Kšžœ˜Kšžœ¢˜—š¥œžœž˜!J™*š	žœžœžœžœž˜šžœžœ
ž˜Kšœ*˜*Kšœ!˜!Kšœ+˜+KšžœD˜K—Kšž˜—Kšžœ¢˜—š¥œžœž˜K™MKšœ%˜%Kšžœ¢˜—š	¥œžœžœžœž˜8Kšžœžœžœ™šžœž˜
Kšžœžœ
žœ˜DKšž˜—Kšžœ¢˜—š	¥œžœžœžœž˜8Mšœ™Kšœžœžœ˜IKšžœ˜Kšžœ¢˜
——™O™Kšœ(¢	˜1Kšœžœ'˜7Kšœ˜š¥
œžœž˜Kšœ9žœ™Mšžœž˜$Kšœ*˜*šœ˜K™}Kšžœ%žœ.˜Z—Kšžœž˜—Kšžœ¢
˜—š¥œžœž˜Kšœ9žœ™MKšœžœ˜5Kšœ˜Kšžœžœžœ+˜PKšžœ¢˜—š¥
œžœž˜*K™>Kšœžœžœ˜(Kš¥œ<žœžœ˜QNšœžœ˜Kšœ6˜6Kšžœžœ"˜<šžœž˜
K™ÈKšœ#˜#Kšœ%˜%Kšœ0ž˜3Kšž˜—Kšžœ¢
˜—š¥œžœžœž˜3K™'Kšœ8žœ˜=Kšœžœ˜Kšœžœ˜Kšœ#˜#Kšœžœ˜Nšœžœ˜0KšœL˜Lšžœžœž˜šœ"žœž˜1šžœžœž˜#Kšœ}˜}Kšœž˜Kšžœ˜—K˜Kšžœ˜—šœ"žœž˜1K™KšœJ˜JK™/Kšœ.˜.KšœF˜FKšœ(˜(K™2Kšœžœžœ˜.šžœžœžœž˜Kšœžœžœ˜;Kšžœ˜—K™šžœ žœž˜-Kšœžœ7˜?Kšœžœ7˜>šžœžœž˜Kšœžœ˜Kšœžœžœ˜Kšžœžœ˜Kšžœž˜—Kšžœ˜—Kšœ(˜(KšœŒ˜ŒKšœ,˜,Kšžœ˜—šžœž˜Kšœb˜bK˜Kšž˜——Kšžœ¢˜—š	¥
œžœžœžœž˜@Kšœžœ'˜/Kšœžœ$˜,Kšžœ?˜EKšžœ¢
˜—š¥	œžœžœžœ	žœž˜=Kšžœ˜!Kšžœ¢˜—š¥œžœžœžœžœ
ž™9Kšžœ™!Kšžœ¢™
—š¥
œžœžœžœžœž˜LKšœ¡œ™3šžœž˜šœ"ž˜'Kšœ?˜?KšœA˜AKšœ?˜?Kšžœ˜—Kšžœ˜!—Kšžœ˜Kšžœ¢˜——™š¥œžœžœžœ
žœž˜\Kšœ¼™¼Kšžœžœ
˜/Kšœžœ˜š¥
œžœ$žœž˜AK™Kšžœžœžœ˜Kšœ8˜8Kšœ#˜#Kšœ"˜"Kšžœ¢
˜—Nšžœ4˜;šžœž˜šœž˜KšœT˜TKšœžœ#¢˜BKšœœ™8Kšœ@˜@Kšœ¤˜¤Kšžœ˜—šœ"ž˜'KšœY˜Yšœžœ#¢˜BKšœœ™8—Kšœžœ˜:Kšœžœ˜:Kšœžœ˜:šœ
žœžœ8˜kKšžœ;˜?—Kšœ(˜(Kšœ(˜(Kšœ(˜(K™>Kšœ˜Kšœ˜Kšœ˜K™JKšœ™Kšœ¤˜¤Kšžœ˜—šœž˜KšœQ˜QKšœ=˜=Kšœ¢œœ¢œ™8Kšœ ˜ Kšžœ˜—šœž˜KšœT˜TKšœ˜Kšœ@˜@Kšœ¢œœ¢œ™8Kšœ ˜ Kšžœ˜—KšœM˜MKšžœžœ¢˜$—KšœS˜SKšœBžœžœ
˜Xšžœžœž˜*Kšœžœžœ˜9Kšœžœ;˜QKšœžœ6˜KKšœK˜KKšœT˜TKšœCžœžœ	˜XKšžœ˜—šž˜šœž˜Kšœm˜mKšœ˜KšœA˜AKšœ˜Kšžœ™Kšž˜——Kšžœ¢˜—š¥œžœžœžœžœ
žœžœžœž˜tKš	œžœU¡<œ¡œ¡œ™ìNšžœžœžœ?˜Yšžœž˜
Kšœžœžœ˜:šžœž˜Kšœˆ˜ˆKšœ&¢˜?Kšžœžœ˜!—Kšœ˜šžœž˜
Kšœžœ:˜NKšžœ˜—Kšœ=˜=Kšž˜—Kšžœ¢˜
——™
š¥œ#ž˜;Mšœ>˜>Mšžœ˜—š¥œžœž˜,K™)Kšœžœ¢6˜Mš¥œž˜-Kšœžœ	˜Kšœ)˜)Kšžœ¢˜—š¥	œž˜+Kšœžœ	˜Kšœžœ˜3Kšžœžœ˜(Kš	œ)žœžœžœžœ#˜š	žœžœžœžœž˜Kšžœžœžœžœ˜MKšžœ˜—Kšœ˜Kšžœ¢˜—Nšœžœžœ˜ÖNšœ%˜%šžœžœž˜Kšœ#˜#KšœC˜CKšž˜—Kšžœ¢˜—š¥œžœž˜-K™LMš¥	œ+žœ˜RKšœ7˜7Kšžœ¢˜—š¥
œžœžœžœ
žœž˜LKšœ
Ðekœ
¡œªœ%ª¡œ¡œ¡œ1™ÍKšœ
žœ˜Kšœžœ˜'Kšœžœ˜Kšœžœ˜Nšœžœžœ
˜$Kšœžœžœ+žœ˜NNšœžœžœ
žœ˜-Kšœžœžœ+žœ	˜fNšœžœžœ
žœ˜-Kšœžœžœ+žœ˜eKšžœ¢
˜——™Mšœ8˜8—Mšžœ˜—�…—����{Ö��¾0��