DIRECTORY Atom USING [MakeAtom], BasicTime USING [GMT, Now, OutOfRange, Period, ToNSTime, Update], CD USING [CreateDrawRef, Design, DrawProc, DrawRectProc, DrawRef, Instance, InstanceList, Layer, LayerKey, Number, Object, Position, Rect, undefLayer], CDBasics USING [BaseOfRect, ImagerTransform, Intersection, NonEmpty, SizeOfRect], CDDirectory USING [EachEntryAction, Enumerate], CDColors USING [ColorTable, DisplayMode, DisplayType, globalColors], CDCurves USING [CurveSpecific], CDInstances USING [NewInst], CDOps USING [DrawDesign, InstList], CDTexts USING [TextSpecific], CDValue USING [Fetch], Checksum USING [ComputeChecksum], CStitching USING [all, Area, ChangeEnumerateArea, ChangeRect, DumpCache, EnumerateArea, NewTesselation, RectProc, Region, ResetTesselation, Tesselation, Tile, TileProc], D2Orient USING [Orientation], FS USING [Close, ComponentPositions, Error, ExpandName, GetInfo, GetName, Open, OpenFile, Position, SetKeep], HashTable USING [Create, EachPairAction, Fetch, GetSize, Insert, Key, Pairs, Table], Imager USING [black, ClipRectangle, Color, ColorOperator, ConcatT, Context, ConstantColor, DoSave, Font, MaskFillTrajectory, MaskRectangle, MaskStrokeTrajectory, Rectangle, ScaleT, SetColor, SetFont, SetPriorityImportant, SetStrokeEnd, SetStrokeJoint, SetStrokeWidth, SetXY, ShowRope, StrokeEnd, StrokeJoint, Trans, TranslateT, VEC], ImagerBrick USING [Brick, BrickRep], ImagerColor USING [ColorFromRGB, RGB], ImagerColorPrivate USING [ComponentFromColor], ImagerColorOperator USING [ColorOperator, RGBLinearColorModel], ImagerExtras USING [MaskDashedStrokeTrajectory], ImagerFont USING [Modify], ImagerInterpress USING [Close, Create, DeclareColor, DeclareColorOperator, DeclareFont, DoPage, Ref], ImagerPath USING [LineToX, LineToY, MoveTo, Trajectory], ImagerPDPublic USING [Toner], ImagerTransformation USING [Cat, Create, Invert, Rotate, Scale2, Transformation, Translate], Interpress USING [classAppearanceError, classAppearanceWarning, classComment, classMasterError, classMasterWarning, LogProc], IO USING [atom, int, PutFR1, real, rope, 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], PrintingP4V3 USING [InterpressMasterStatus, SpoolingQueueFull, TransferError], -- Yuck ! Process USING [CheckForAbort, Detach, priorityBackground, SetPriority], Real USING [Fix, Float], RefTab USING [Create, Delete, EachPairAction, Fetch, GetSize, Insert, Pairs, Ref, Store], Rope USING [Cat, Equal, Fetch, IsEmpty, Length, Replace, ROPE, SkipTo, Substr], TerminalIO USING [CreateStream, PutF, PutRope], UserProfile USING [Boolean, CallWhenProfileChanges, ProfileChangedProc, Token], XNSPrintRequestManager USING [Context, GetDefaults, GetPrintRequestStatus, PrintFromFile, PrintRequest, RequestStatus, StatusChangedProc]; NectarineImpl: CEDAR PROGRAM IMPORTS Atom, BasicTime, CD, CDBasics, CDColors, CDDirectory, CDInstances, CDOps, CDValue, Checksum, CStitching, FS, HashTable, Imager, ImagerColor, ImagerColorPrivate, ImagerColorOperator, ImagerExtras, ImagerFont, ImagerInterpress, ImagerPath, ImagerTransformation, IO, MessageWindow, NodeStyleFont, PeachPrint, PrintFileConvert, PrintingP4V3, Process, Real, RefTab, Rope, TerminalIO, UserProfile, XNSPrintRequestManager EXPORTS Nectarine ~ BEGIN OPEN Real; break: SIGNAL = CODE; -- for debugging invalidPrinter: PUBLIC SIGNAL = CODE; communicationsFailure: PUBLIC SIGNAL = CODE; tooComplex: PUBLIC SIGNAL = CODE; layoutOnly: BOOL _ FALSE; -- faster and nicer plots setting this with the interpreter. Font: TYPE = Imager.Font; Color: TYPE = Imager.Color; Transformation: TYPE = ImagerTransformation.Transformation; State: TYPE = REF StateRec; StateRec: TYPE = RECORD [ previousColour: Color _ NIL, previousStrokeWidth: REAL _ -1.0, previousFont: Font _ NIL, previousTextOrientation: D2Orient.Orientation _ original, cardTile: CARD _ 0, -- |{tile}| startTime: BasicTime.GMT, context: Imager.Context, ipName: Rope.ROPE, 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, singleLayer: BOOL _ FALSE, -- only the layer of interset will be printed layerOfInterest: CD.Layer _ CD.undefLayer, isFirstPage, isLastPage: BOOL _ TRUE, band: REF CD.Rect _ NIL]; 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 mmXin: REAL ~ 25.4; statistics: BOOL _ FALSE; debug: BOOL _ FALSE; remindFontConventions: BOOL _ TRUE; risk: INT _ 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 PrintAlignedTile: CStitching.TileProc ~ BEGIN state: State ~ NARROW [data]; b: Blend ~ NARROW [tile.value]; r: CD.Rect ~ CStitching.Area [tile]; -- not the area but the rectangle ! ir: Imager.Rectangle ~ ImagerRect [r]; MaskAlignedRectangle: PROC ~ BEGIN state.context.SetXY [[ir.x, ir.y]]; state.context.Trans []; state.context.MaskRectangle [[0, 0, ir.w, ir.h]] END; -- MaskAlignedRectangle ChangeColour [state, b.blend]; state.context.DoSave [MaskAlignedRectangle]; IF state.abort^ THEN ERROR ABORTED; IF statistics THEN BEGIN l: CD.Number ~ state.design.technology.lambda; b.area _ b.area + ((r.x2 - r.x1) / l) * ((r.y2 - r.y1) / l); state.cardTile _ SUCC [state.cardTile] END END; -- PrintAlignedTile 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 l: CD.Number ~ state.design.technology.lambda; b.area _ b.area + ((r.x2 - r.x1) / l) * ((r.y2 - r.y1) / l); 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 IF layoutOnly THEN decomposition.EnumerateArea [rect: CStitching.all, eachTile: PrintTile, data: state, skip: empty] ELSE decomposition.EnumerateArea [rect: CStitching.all, eachTile: PrintAlignedTile, 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.PutRope ["."]; BlendAllColours []; TerminalIO.PutRope ["."]; -- pass 3 state.previousColour _ NIL; -- needed by Interpress state.context.DoSave [EnumerateGeometry]; -- pass 4 FlushDecomposition [decomposition]; TerminalIO.PutRope [". "]; -- state.tess _ decomposition _ NIL END; -- PrintBand NewRect: CD.DrawRectProc ~ BEGIN state: State ~ NARROW [pr.devicePrivate, State]; rect: CD.Rect; IF (state.singleLayer AND (l # state.layerOfInterest)) THEN RETURN; 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 mirrorY: Transformation ~ ImagerTransformation.Scale2 [[-1, 1]]; rot180: Transformation ~ ImagerTransformation.Rotate [180]; SpecialHack: PROC [obj: CD.Object, or: D2Orient.Orientation] RETURNS [t: Transformation] ~ BEGIN adjustX: Transformation ~ ImagerTransformation.Translate [[-(obj.bbox.x2 - obj.bbox.x1), 0]]; adjustXY: Transformation ~ ImagerTransformation.Translate [[-(obj.bbox.x2 - obj.bbox.x1), -(obj.bbox.y2 - obj.bbox.y1)]]; IF (obj.class.objectType # $FlipText) THEN ERROR; -- tocca ferro t _ SELECT or FROM mirrorX, rotate90X => adjustX.Cat [mirrorY], rotate180X, rotate270X => adjustXY.Cat [rot180, adjustX, mirrorY], rotate180, rotate90 => adjustXY.Cat [rot180], ENDCASE => ImagerTransformation.Create [1, 0, 0, 0, 1, 0] END; -- SpecialHack DrawText: CD.DrawProc ~ BEGIN state: State ~ NARROW [pr.devicePrivate]; context: Imager.Context ~ state.context; text: CDTexts.TextSpecific ~ NARROW [inst.ob.specific]; offset: Imager.VEC ~ text.cdFont.xy; transf, invTransf: Transformation; IF (state.singleLayer AND (inst.ob.layer # state.layerOfInterest)) THEN RETURN; IF state.abort^ THEN ERROR ABORTED; transf _ CDBasics.ImagerTransform [trans]; IF (inst.ob.class.objectType = $FlipText) THEN transf _ ImagerTransformation.Cat [SpecialHack [inst.ob, trans.orient], transf]; invTransf _ ImagerTransformation.Invert [transf]; 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.CurveSpecific ~ NARROW [inst.ob.specific]; transf: Transformation ~ CDBasics.ImagerTransform [trans]; invTransf: Transformation ~ ImagerTransformation.Invert [transf]; IF (state.singleLayer AND (inst.ob.layer # state.layerOfInterest)) THEN RETURN; 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 DrawArea: CD.DrawProc ~ BEGIN state: State ~ NARROW [pr.devicePrivate]; context: Imager.Context ~ state.context; curve: CDCurves.CurveSpecific ~ NARROW [inst.ob.specific]; transf: Transformation ~ CDBasics.ImagerTransform [trans]; invTransf: Transformation ~ ImagerTransformation.Invert [transf]; IF (state.singleLayer AND (inst.ob.layer # state.layerOfInterest)) THEN RETURN; IF state.abort^ THEN ERROR ABORTED; context.ConcatT [transf]; -- context.SetXY [offset]; ChangeColour [state, LayerColour [inst.ob.layer]]; ChangeStrokeWidth [state, Float [curve.w]]; context.MaskFillTrajectory [curve.path, TRUE]; context.ConcatT [invTransf] END; -- DrawArea DrawObjectBorder: CD.DrawRectProc ~ BEGIN state: State ~ NARROW [pr.devicePrivate, State]; pen: REAL ~ Float [state.design.technology.lambda]; halfPen: REAL ~ pen / 2.0; object: Imager.Rectangle ~ ImagerRect [r]; border: ImagerPath.Trajectory; IF state.abort^ THEN ERROR ABORTED; ChangeColour [state, black]; ChangeStrokeWidth [state, pen]; border _ ImagerPath.MoveTo [[object.x - halfPen, object.y - halfPen]]; border _ border.LineToX [object.x + object.w + halfPen]; -- South border _ border.LineToY [object.y + object.h + halfPen]; -- East border _ border.LineToX [object.x - halfPen]; -- North border _ border.LineToY [object.y - halfPen]; -- West state.context.MaskStrokeTrajectory [trajectory: border] END; -- DrawObjectBorder DrawDashedObjectBorder: CD.DrawRectProc ~ BEGIN state: State ~ NARROW [pr.devicePrivate, State]; pen: REAL ~ Float [state.design.technology.lambda / 2]; halfPen: REAL ~ pen / 2.0; object: Imager.Rectangle ~ ImagerRect [r]; border: ImagerPath.Trajectory; patternElements: NAT ~ 8; DotDotDotDash: PROC [i: NAT] RETURNS [REAL] ~ BEGIN pattern: ARRAY [0 .. patternElements) OF REAL ~ [0, 5*pen, 0, 5*pen, 0, 10*pen, 30*pen, 10*pen]; RETURN [pattern[i]] END; -- DotDotDotDash IF state.abort^ THEN ERROR ABORTED; ChangeColour [state, black]; ChangeStrokeWidth [state, pen]; border _ ImagerPath.MoveTo [[object.x - halfPen, object.y - halfPen]]; border _ border.LineToX [object.x + object.w + halfPen]; -- South border _ border.LineToY [object.y + object.h + halfPen]; -- East border _ border.LineToX [object.x - halfPen]; -- North border _ border.LineToY [object.y - halfPen]; -- West ImagerExtras.MaskDashedStrokeTrajectory [context: state.context, trajectory: border, offset: 0, length: 2*(object.w+object.h), patternLen: patternElements, pattern: DotDotDotDash] END; -- DrawDashedObjectBorder DrawObject: CD.DrawProc ~ BEGIN Process.CheckForAbort []; SELECT inst.ob.class.objectType FROM $Text, $RigidText, $FlipText => DrawText [inst, trans, pr]; $Spline0, $Line0 => DrawPath [inst, trans, pr]; $FilledCurve0, $Polygon0 => DrawArea [inst, trans, pr]; ENDCASE => inst.ob.class.drawMe [inst, trans, pr] END; -- DrawObject multipageHack: State _ NEW [StateRec]; DoInterpress: PUBLIC PROC [design: CD.Design, chipNDaleWindow: CD.Rect, clip, onlySel, singleLayer: BOOL _ FALSE, layer: CD.Layer _ CD.undefLayer, lambda: REAL _ 0.0, firstPage, lastPage: BOOL _ TRUE, abortFlag: REF BOOL] RETURNS [masterName: Rope.ROPE, usedField: Imager.Rectangle] ~ BEGIN interpress: ImagerInterpress.Ref; state: State; rgbLinear: Imager.ColorOperator ~ ImagerColorOperator.RGBLinearColorModel [255]; 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 IF state.selectedOnly THEN DrawSelection [state.design, tdr] ELSE CDOps.DrawDesign [state.design, tdr] END; -- EnumerateTextInDesign state.context _ context; 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]]; IF (lambda = 0.0) THEN context.ScaleT [MIN [ratioW, ratioH]] ELSE context.ScaleT [lambda / Float [design.technology.lambda]]; context.TranslateT [[-window.x, -window.y]]; context.SetStrokeJoint [mitered]; -- I hope that's faster for rectangles IF clip THEN context.ClipRectangle [window]; -- global to context !!! context.SetPriorityImportant [TRUE]; bandSize _ Fix [(1000000.0 * (risk+1)) / (window.w / design.technology.lambda)]; IF bandSize < 4 * design.technology.lambda THEN SIGNAL tooComplex; iterations _ Fix [window.h] / bandSize; -- "zero relative" ! IF (iterations > 5) THEN BEGIN TerminalIO.PutRope [" There will be "]; TerminalIO.PutRope [IO.PutFR1[value: IO.int[iterations]]]; TerminalIO.PutRope [" sets of 3 dots "] END ELSE {IF debug THEN TerminalIO.PutRope [IO.PutFR1[value: IO.int[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 + 1]; IF chronos THEN BEGIN fudge: INT ~ 8; IF (b = iterations - 3) THEN lap _ BasicTime.Now []; IF (b = iterations - 4) AND state.isLastPage THEN BEGIN duration: INT ~ BasicTime.Period [lap, BasicTime.Now[]]; end _ BasicTime.Update [lap, fudge * duration * (b + 2) ! BasicTime.OutOfRange => GOTO endless]; TerminalIO.PutF ["\nInterpress page will be ready ca. %g\n", IO.time [end]]; chronos _ FALSE END END; PrintBand [state]; IF (b = halftime) AND (iterations > 10) AND state.isLastPage 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.PutF ["\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 [round]; context.SetStrokeJoint [round]; IF clip THEN tdr.interestClip _ chipNDaleWindow; tdr.drawChild _ DrawObject; tdr.drawOutLine _ DrawObjectBorder; tdr.borders _ TRUE; tdr.selections _ FALSE; tdr.devicePrivate _ state; state.previousColour _ NIL; -- needed by Interpress state.previousStrokeWidth _ -1.0; -- needed by Interpress context.DoSave [EnumerateTextInDesign]; TerminalIO.PutRope [". "]; -- pass 5 EXITS endless => BEGIN ImportantMessage [" Nectarine would not terminate before 2036"]; SIGNAL tooComplex END END; -- DrawToIP Action: PROC [] ~ BEGIN DeclareColours: HashTable.EachPairAction ~ BEGIN blendRec: Blend ~ NARROW [value]; IF (blendRec.blend # NIL) THEN state.interpress.DeclareColor [blendRec.blend]; RETURN [FALSE] END; DeclareFonts: RefTab.EachPairAction ~ {state.interpress.DeclareFont [NARROW [val,Font]]; RETURN [FALSE]}; ListFonts: RefTab.EachPairAction ~ {TerminalIO.PutRope [NARROW[val,Font].name]; TerminalIO.PutRope ["\n"]; RETURN [FALSE]}; IF state.isFirstPage THEN BEGIN state.interpress _ interpress _ OpenIPMaster []; state.ipName _ masterName; TerminalIO.PutRope [Rope.Cat ["Producing Interpress master ", masterName, "\n"]]; state.interpress.DeclareColorOperator [rgbLinear]; IF (colourTable.GetSize[] + fontMap.GetSize[] < 50) THEN [] _ 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 IF (fontMap.GetSize[] < 50) THEN [] _ fontMap.Pairs [DeclareFonts]; TerminalIO.PutRope [". "]; IF debug THEN BEGIN TerminalIO.PutRope ["\nThe following fonts are in the preamble:\n"]; [] _ fontMap.Pairs [ListFonts] END END; TRUSTED {Process.SetPriority [Process.priorityBackground]}; state.interpress.DoPage [action: DrawToIP, scale: 0.001]; IF state.isLastPage THEN BEGIN state.interpress.Close []; FS.SetKeep [masterName, 3]; TerminalIO.PutRope [TimeToRope [state.startTime, BasicTime.Now[]]]; TerminalIO.PutRope ["\n"]; IF (statistics OR debug) THEN ListColourTable [state]; TerminalIO.PutRope [Rope.Cat ["Interpress master ", state.ipName, " is ready.\n"]] END END; -- Action IF firstPage THEN BEGIN multipageHack _ state _ NEW [StateRec]; state.design _ design; IF singleLayer THEN {state.singleLayer _ TRUE; state.layerOfInterest _ layer}; IF statistics THEN CleanColourTable [state]; state.abort _ IF abortFlag # NIL THEN abortFlag ELSE NEW [BOOL _ FALSE]; state.startTime _ BasicTime.Now [] END ELSE BEGIN state _ multipageHack; state.isFirstPage _ FALSE; state.previousColour _ NIL; state.previousStrokeWidth _ -1.0; state.previousFont _ NIL; state.previousTextOrientation _ original; masterName _ state.ipName END; state.clip _ clip; state.cdClip _ chipNDaleWindow; state.selectedOnly _ onlySel; state.isLastPage _ lastPage; 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.trans, 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], original], 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 IF (a.R = 0.0) AND (a.G = 0.0) AND (a.B = 0.0) THEN context.SetColor [blackBlack] ELSE 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 prFont: Font _ NARROW [fontMap.Fetch[skFont].val]; IF (prFont = NIL) THEN BEGIN prFont _ Mapping [skFont]; [] _ fontMap.Insert [skFont, prFont] END; context.SetFont [prFont]; state.previousFont _ skFont END END; -- ChangeFont LogInterpress: Interpress.LogProc ~ BEGIN TerminalIO.PutRope [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.PutRope [explanation]; TerminalIO.PutRope [" . . . \n"] END; -- LogInterpress ProgressLog: PrintFileConvert.ProgressProc ~ BEGIN IF begin THEN TerminalIO.PutRope [IO.PutFR1 ["[%g", IO.int [page]]] ELSE TerminalIO.PutRope ["] "] 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 _ NIL, 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]]; blackBlack: Color ~ Imager.black; blue: Color ~ ImagerColor.ColorFromRGB [[0.0, 0.0, 1.0]]; unColour: ImagerColor.RGB ~ [0.0, 0.0, 0.0]; doubleYellowRGB: ImagerColor.RGB ~ [2.0, 2.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 [[13.0/14.0, 13.0/14.0, 10.0/21.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 _ unColour; IF (components.blend # NIL) 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 _ doubleYellowRGB; 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; $cut => layerColorTable[i] _ black; $cut2 => layerColorTable[i] _ blue; 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, $RigidText, $FlipText => FindFont [inst, trans, pr]; $Cell => IF visitedCells.Insert [inst.ob, $hack] THEN inst.ob.class.drawMe [inst, trans, pr]; ENDCASE => NULL END; -- DrawFilter FindFont: CD.DrawProc ~ BEGIN text: CDTexts.TextSpecific ~ NARROW [inst.ob.specific]; 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; visitedCells _ RefTab.Create [557]; IF state.selectedOnly THEN DrawSelection [state.design, tdr] ELSE EnumerateObjects [state.design, tdr]; [] _ visitedCells.Pairs [Evict]; visitedCells _ NIL 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.PutRope ["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.PutRope [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.BaseOfRect [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 _ unColour; RETURN [rgb] END; -- RGBFromColour ImportantMessage: PROC [msg: Rope.ROPE] ~ BEGIN TerminalIO.PutRope [msg]; TerminalIO.PutRope ["\n"]; MessageWindow.Clear []; MessageWindow.Append [msg]; MessageWindow.Blink [] END; -- ImportantMessage XNSinfo: TYPE ~ RECORD [ c: XNSPrintRequestManager.Context, r: XNSPrintRequestManager.PrintRequest]; PrintRequest: TYPE ~ REF PrintRequestRec; PrintRequestRec: TYPE ~ RECORD [master: FS.OpenFile, fullName: Rope.ROPE, xns: REF XNSinfo]; submittedRequests: RefTab.Ref ~ RefTab.Create []; XNSfinalisation: XNSPrintRequestManager.StatusChangedProc ~ BEGIN TerminalIO.PutF ["%g completed with status %g.\n", IO.rope [request.fileName], IO.rope [request.lastStatus.statusMessage]]; ReportXNSprintingStatus END; -- XNSfinalisation ReportXNSprintingStatus: PUBLIC PROC ~ BEGIN obsolete: LIST OF PrintRequest; AnalyzeSubmitted: RefTab.EachPairAction ~ BEGIN req: PrintRequest _ NARROW [key]; status: XNSPrintRequestManager.RequestStatus ~ XNSPrintRequestManager.GetPrintRequestStatus [req.xns.r]; SELECT status.status FROM pending, inProgress, unknown, held => TerminalIO.PutF ["Status for %g: %g\n", IO.rope [req.xns.c.printObjectName], IO.rope [status.statusMessage]]; completed, completedWithWarning, aborted, canceled => BEGIN obsolete _ CONS [req, obsolete]; TerminalIO.PutF ["Status for %g: %g\n", IO.rope [req.xns.c.printObjectName], IO.rope [status.statusMessage]] END; rejected => ERROR; ENDCASE => ERROR END; -- AnalyzeSubmitted [] _ submittedRequests.Pairs [AnalyzeSubmitted]; FOR o: LIST OF PrintRequest _ obsolete, o.rest WHILE o # NIL DO [] _ submittedRequests.Delete [o.first]; o.first.master.Close -- unlock file ENDLOOP; END; -- ReportXNSprintingStatus PrintProcess: PROC [masterName, peachName: Rope.ROPE, printerKey: ATOM, copies: INT, doNotScale: BOOL, sizeHint: REF Imager.Rectangle _ NIL] ~ BEGIN currentRequest: PrintRequest _ NEW [PrintRequestRec]; {ENABLE BEGIN PeachPrint.PupAborted => GOTO failure; PrintingP4V3.SpoolingQueueFull => GOTO failure; PrintingP4V3.TransferError => GOTO failure END; serverName: Rope.ROPE; doNotSend: BOOL ~ (printerKey = $NRaven384) OR (printerKey = $NPlateMaker); deviceParameters: PrintFileConvert.PDParams; scale: REAL; 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 deviceParameters _ PrintFileConvert.ParamsFromPrinterType [$versatec]; IF (sizeHint # NIL) AND (sizeHint.h > sizeHint.w) THEN BEGIN scale _ (mmXin * deviceParameters.pageFSize) / sizeHint.w; IF (scale * sizeHint.h > 2000) THEN ImportantMessage [" Your plot will be longer than 2 metres. Printing anyway"] END ELSE scale _ (mmXin * deviceParameters.pageFSize) / field.w; serverName _ UserProfile.Token ["Nectarine.Versatec", "Sleepy"] END; $NColorVersatec, $NPeachExpand => BEGIN brickB: ImagerBrick.Brick _ NEW [ImagerBrick.BrickRep[4]]; brickC: ImagerBrick.Brick _ NEW [ImagerBrick.BrickRep[4]]; brickM: ImagerBrick.Brick _ NEW [ImagerBrick.BrickRep[4]]; brickY: ImagerBrick.Brick _ NEW [ImagerBrick.BrickRep[4]]; deviceParameters _ PrintFileConvert.ParamsFromPrinterType [$colorVersatec]; IF (sizeHint # NIL) AND (sizeHint.h > sizeHint.w) THEN BEGIN scale _ (mmXin * deviceParameters.pageFSize) / sizeHint.w; IF (scale * sizeHint.h > 2000) THEN ImportantMessage [" Your plot will be longer than 2 metres. Printing anyway"] END ELSE scale _ (mmXin * deviceParameters.pageFSize) / field.w; serverName _ IF (printerKey = $NColorVersatec) THEN UserProfile.Token ["Nectarine.ColorVersatec", "Sleepy"] ELSE UserProfile.Token ["Nectarine.PeachExpand", "Kearsarge"]; FillSample [brickB, 0.6, 0.4, 0.2, 0.8]; FillSample [brickC, 0.2, 0.8, 0.6, 0.4]; FillSample [brickM, 0.6, 0.4, 0.2, 0.8]; FillSample [brickY, 0.42, 0.15, 0.7, 0.3]; -- delicate ! deviceParameters.bricks [black] _ brickB; deviceParameters.bricks [cyan] _ brickC; deviceParameters.bricks [magenta] _ brickM; deviceParameters.bricks [yellow] _ brickY END; $NBw400 => BEGIN deviceParameters _ PrintFileConvert.ParamsFromPrinterType [$bw400]; scale _ (mmXin * deviceParameters.pageFSize) / field.w; serverName _ UserProfile.Token ["Nectarine.Bw400", "MtFuji"] END; $NColor400 => BEGIN deviceParameters _ PrintFileConvert.ParamsFromPrinterType [$color400]; deviceParameters.ppd _ 4.0; scale _ (mmXin * deviceParameters.pageFSize) / field.w; serverName _ UserProfile.Token ["Nectarine.Color400", "MtFuji"] END; $NPlateMaker => BEGIN deviceParameters _ PrintFileConvert.ParamsFromPrinterType [$plateMaker]; deviceParameters.tonerUniverse _ LIST [black, cyan, magenta, yellow]; scale _ 1.0 END; $NRaven300 => serverName _ UserProfile.Token ["Nectarine.Raven300", "Quoth"]; $NRaven384 => deviceParameters _ PrintFileConvert.ParamsFromPrinterType [$raven384]; ENDCASE => NULL; -- can never happen IF NOT doNotScale THEN scale _ 1.0; SELECT printerKey FROM $NRaven300 => NULL; $NRaven384 => BEGIN PrintFileConvert.InterpressToPD [inputName: masterName, outputName: peachName, params: deviceParameters, logProc: LogInterpress, progressProc: ProgressLog]; TerminalIO.PutRope [Rope.Cat ["PD file for Raven384 written on ", peachName, "\nuse TSetter to send it to a printer like Stinger.\n"]] END; $NPlateMaker => BEGIN tx: REAL ~ - (field.x * scale) / mmXin; ty: REAL ~ - (field.y * scale) / mmXin; separation: Rope.ROPE _ peachName.Cat ["-Black"]; deviceParameters.toners _ LIST [black]; PrintFileConvert.InterpressToPD [inputName: masterName, outputName: separation, params: deviceParameters, sx: scale, sy: scale, tx: tx, ty: ty, logProc: LogInterpress, progressProc: ProgressLog]; TerminalIO.PutRope [Rope.Cat ["Black separation written on ", separation, "\n"]]; separation _ peachName.Cat ["-Cyan"]; deviceParameters.toners _ LIST [cyan]; PrintFileConvert.InterpressToPD [inputName: masterName, outputName: separation, params: deviceParameters, sx: scale, sy: scale, tx: tx, ty: ty, logProc: LogInterpress, progressProc: ProgressLog]; TerminalIO.PutRope [Rope.Cat ["Cyan separation written on ", separation, "\n"]]; separation _ peachName.Cat ["-Magenta"]; deviceParameters.toners _ LIST [magenta]; PrintFileConvert.InterpressToPD [inputName: masterName, outputName: separation, params: deviceParameters, sx: scale, sy: scale, tx: tx, ty: ty, logProc: LogInterpress, progressProc: ProgressLog]; TerminalIO.PutRope [Rope.Cat ["Magenta separation written on ", separation, "\n"]]; separation _ peachName.Cat ["-Yellow"]; deviceParameters.toners _ LIST [yellow]; PrintFileConvert.InterpressToPD [inputName: masterName, outputName: separation, params: deviceParameters, sx: scale, sy: scale, tx: tx, ty: ty, logProc: LogInterpress, progressProc: ProgressLog]; TerminalIO.PutRope [Rope.Cat ["Yellow separation written on ", separation, "\n"]]; TerminalIO.PutRope ["Copy these files onto [Indigo]your name> and message Bridget Scamporrino . Please advise her that the separations are A size with a margin of 1 cm on each side.\n\n"] END; ENDCASE => BEGIN PrintFileConvert.InterpressToPD [inputName: masterName, outputName: peachName, params: deviceParameters, sx: scale, sy: scale, tx: - (field.x * scale) / mmXin, ty: - (field.y * scale) / mmXin, logProc: LogInterpress, progressProc: ProgressLog]; FS.SetKeep [peachName, 3] END; IF (NOT doNotSend) THEN BEGIN TerminalIO.PutRope [Rope.Cat ["Sending ", peachName, " to ", serverName, "\n."]]; IF printerKey = $NRaven300 THEN BEGIN pos: FS.ComponentPositions; currentRequest.xns _ NEW [XNSinfo]; currentRequest.xns.c _ XNSPrintRequestManager.GetDefaults [NIL]; currentRequest.master _ FS.Open [name: masterName, remoteCheck: FALSE]; currentRequest.fullName _ currentRequest.master.GetName.fullFName; -- to get the version number currentRequest.xns.c.printerName _ serverName; pos _ FS.ExpandName [currentRequest.fullName].cp; currentRequest.xns.c.printObjectName _ currentRequest.fullName.Substr[start: pos.base.start, len: pos.base.length].Cat["!",currentRequest.fullName.Substr[start: pos.ver.start, len: pos.ver.length]]; -- Sorry ! currentRequest.xns.c.printObjectCreateDate _ BasicTime.ToNSTime [currentRequest.master.GetInfo[].created]; currentRequest.xns.c.copyCount _ copies; currentRequest.xns.c.message _ Rope.Cat ["Nectarine for ", currentRequest.xns.c.message]; currentRequest.xns.r _ XNSPrintRequestManager.PrintFromFile [masterName, currentRequest.xns.c, XNSfinalisation]; [] _ submittedRequests.Store [currentRequest, NIL]; ReportXNSprintingStatus END ELSE PeachPrint.DoPeachPrintCommand [serverName, peachName, TerminalIO.CreateStream[], FALSE, copies] END; IF (printerKey = $NPeachExpand) THEN BEGIN pos: FS.ComponentPositions ~ FS.ExpandName[peachName].cp; server2Name: Rope.ROPE ~ UserProfile.Token ["Nectarine.ExpandedPeach", "Sleepy"]; simpleName: Rope.ROPE ~ peachName.Substr [pos.base.start, pos.base.length]; peachName _ Rope.Cat ["[", serverName, "]PD>", simpleName, "-1.PD"]; TerminalIO.PutRope [Rope.Cat ["Sending ", peachName, " to ", server2Name, "\n."]]; PeachPrint.DoPeachPrintCommand [server2Name, peachName, TerminalIO.CreateStream[], FALSE, copies] END; EXITS failure => BEGIN ImportantMessage [Rope.Cat ["Communications failure. File saved on ", peachName, " for manual retry."]]; END} END; -- PrintProcess Print: PUBLIC PROC [masterName: Rope.ROPE, printerKey: ATOM, copies: INT _ 1, doNotScale: BOOL _ FALSE, sizeHint: REF Imager.Rectangle _ NIL] RETURNS [peachName: Rope.ROPE] ~ BEGIN IF (masterName = NIL) THEN TerminalIO.PutRope ["Produce an Interpress master first.\n"] ELSE BEGIN pos: FS.ComponentPositions ~ FS.ExpandName[masterName].cp; SELECT printerKey FROM $NVersatec, $NColorVersatec, $NBw400, $NColor400, $NPeachExpand, $NPlateMaker, $NRaven384 => 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 PrintProcess [masterName, peachName, printerKey, copies, doNotScale, sizeHint]] END; TerminalIO.PutRope ["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.PutF ["%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.PutF [" %g", IO.atom [CD.LayerKey[i]]] ENDLOOP; TerminalIO.PutRope ["\n"] END; -- ListEntry TerminalIO.PutF ["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.PutRope ["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. RöNectarineImpl.mesa Copyright Ó 1986, 1987 by Xerox Corporation. All rights reserved. Giordano Bruno Beretta, April 11, 1986 7:57:41 pm PST gbb March 31, 1987 4:13:14 pm PST 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 (S. 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. [Artwork node; type 'ArtworkInterpress on' to command tool]  Insert caption here  Geometry Does what FreeTesselation supposedly did once upon a time. PROC [tile: REF Tile, data: REF] This version is much slower than PrintTile. It uses 4 additional operations and 12 additional bytes. This buys that all rectangles get aligned to pixels. This makes that all wires in schematics are printed with the same width. 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. state.context.SetPriorityImportant [FALSE]; -- works for the devices at PARC today The new Interpress to PD conversion software no longer allows to use this speed-up trick. [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 This is a special temporary hack that hacks out the transformation required to print the same thing as ChipNDale displays in the class $FlipText. [inst: CD.Instance, trans, pr: CD.DrawRef] [inst: CD.Instance, trans, pr: CD.DrawRef] [inst: CD.Instance, trans, 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. Convert the object border into an Imager trajectory. Draw it ! Note that the stroke ends and joints are round. [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. Convert the object border into an Imager trajectory. Draw it ! Note that the stroke ends and joints are round. DrawObjectBorder: CD.DrawRectProc ~ BEGIN [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. state: State ~ NARROW [pr.devicePrivate, State]; pen: REAL ~ Float [state.design.technology.lambda / 2]; object, border: Imager.Rectangle; Process.CheckForAbort []; IF state.abort^ THEN ERROR ABORTED; ChangeColour [state, black]; object _ ImagerRect [r]; South: 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]; West: border _ [x: object.x, y: object.y, w: pen, h: object.h]; state.context.MaskRectangle [border]; East: border _ [x: object.x + object.w - pen, y: object.y, w: pen, h: object.h]; state.context.MaskRectangle [border]; North: border _ [x: object.x, y: object.y + object.h - pen, w: object.w, h: pen]; state.context.MaskRectangle [border] END; -- DrawObjectBorder [inst: Instance, trans: Transformation, pr: REF DrawInformation] 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 millimetres. 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. If singleLayer is true, only objects in the layer layer are included in the Interpress master. If lambda = 0 then scale such that the window fills the field, else scale such that 1  will be lambda mm in the Interpress master. If not last page, the Interpress master is not closed, hence the next call of this procedure will add a page to the same master instead of creating a new document. 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. state.context.SetPriorityImportant [TRUE]; -- see EnumerateGeometry 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 metres 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; context.SetPriorityImportant [NOT layoutOnly]; There is a known bug in Tioga and Doug Wyatt has tried to look at it, but could not find a clue. It is not reproducible. The bug definitely is in Tioga, InterpressArtwork, or in the Imager and not in Nectarine, which only creates a vanilla Interpress artwork node. Rectangles: Magic numbers: Assume 14 MB of memory may be used. Each tile requires 16 words of storage (14 words for the tile and 2 words Cedar overhead), 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. In the average there are as many space tiles as there are colored tiles. 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: The stroke joint must be round, because a ChipNDale staightline segment [a, b] is made out of a spline [a, b, a'], where d (a, a') < e. Does it at background priority. Produce preamble. It is not possible to declare all colours in the preamble, because the size of the Interpress frame is 50 entries (this is defined in the Standard). Create a table of the fonts and them in the preamble. Produce the page. All coordinates will be in millimetres. Close. The keep of Interpress masters is 1. Unfortunately PeachPrint does not lock a file between the time it posts a request and the request is served. This can not only cause the files to get lost, but it may even hang some print servers. The solution implemented here, i.e., changing the keep to 3, it to be considered as a mild temporary hack until a proper solution becomes available in 3 weeks from the time these lines are written. Calling FS.SetKeep will have the side effect of deleting files that are obsolete relative to the new keep, even when the keep is not changed. 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. Draw black using the grey colour model, so that it is placed in the black colour separation. 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 This is nasty code. The trade off was between sort of a hack, 20 minutes of CPU on full chips, and this fix here. I wanted to find all fonts appearing in the design in order to declare them in the preamble. The most stupid thing somebody could do, would be to use a ChipNDale drawProc to visit all text objects [this can take 20 minutes of CPU]. In fact you only need to visit once every object. In ChipNDale you do this by enumerating the directory. Unfortunately ChipNDale has one object which is never in the directory, namely the root cell. In order to avoid the unesthetic special code for the root, the fonts used in the root object are not cached. In the normal case, no fonts are missed, because if there are non-cell objects in the root then usually they have some buddy inside an official cell. So all this was to justify why the print font can be L and has to be handled here at this stange place. All in all I don't care, so if you want to do something different just go ahead (the quickest would be to bypass the ChipNDale directory enumeration procedure and to do your own; this is easy if you use my table called visitedCells). 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. [key: Key, value: Value] RETURNS [quit: BOOLEAN _ FALSE] Find exception layers. Cuts always win. Reinitialize mix by yellow and eliminate poly and diff. Since gates are very important, they are given double weight. Ensure that only one colour representation is used. Spread out hues & make "more subtractive". In ChipNdale 23 cut (cut-2) was always black (blue), but in rel. 24 was displayed black (blue) and printed blue (green). 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, trans: Transformation, 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, trans: Transformation, 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. Writes a message in the ChipNDale terminal viewer and in the Message Window at the top of the LF screen and makes it blink. Printing PrintRequest: TYPE ~ REF RECORD [ context: Context, -- a copy of the ContextObject used to create this PrintRequestObject update: StatusChangedProc, distinguishedName: CHName.Name, requestID: Printing.RequestID, lastStatus: RequestStatus, attributes: Printing.PrintAttributes, options: Printing.PrintOptions, fileName: ROPE, ipMasterStream: IO.STREAM]; The file is opened until it is submitted in order to avoid its overwriting. PROC [request: PrintRequest] At this point, the file should be closed and the request removed from the submittedRequests queue. However, this procedure in reality is never called. Therefore, I do the clean-up in ReportXNSprintingStatus. Traverses Nectarine's private queues, updates them, and prints a status report. PROC [key: Key, val: Val] RETURNS [quit: BOOLEAN]; Display printer status. 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. If the image is in portrait format and the printer uses roll paper, the rectangle usedField from DoInterpress can be specified as a sizeHint to increase the scale so a to use the full roll width. Note: the origin in PDParams refers to the field, not to the medium. Should be in Cedar. Roll paper. Roll paper. Use the following three statements to obtain very fast colors: Or use the following statement to obtain quality colors (rotated screens): deviceParameters.ppd _ 2.0 Roll paper. Roll paper. Cut paper. Implementation notice: because of some possible arcane bug in the compiler, if the scales in x and y would have been first defined either as contants or variables, the compiler would set them to the value 0.0. Therefore you should not change the next line. scale _ MIN [(mmXin*deviceParameters.pageFSize)/field.w, (mmXin*deviceParameters.pageSSize)/field.h] The adjustement of the field to the left end of the printer head has to be scaled, because the field is included in the coordinates in the Interpress master. If the output is scaled to a fixed  value, then we simply overwrite the scale factor here. The keep of PD files is 1. Unfortunately PeachPrint does not lock a file between the time it posts a request and the request is served. This can not only cause the files to get lost, but it may even hang some print servers. The solution implemented here, i.e., changing the keep to 3, it to be considered as a mild temporary hack until a proper solution becomes available in 3 weeks from the time these lines are written. Calling FS.SetKeep will have the side effect of deleting files that are obsolete relative to the new keep, even when the keep is not changed. Prevent overwriting if the queue is full. SIGNAL communicationsFailure Produces (if necessary) a PD file from an Interpress master and ships it to the printer. Valid printer keys are $NVersatec, $NColorVersatec, $NPeachExpand, $NBw400, $NColor400, $NPlateMaker, $NRaven300, $NRaven384. May return signals invalidPrinter. If the image is in portrait format and the printer uses roll paper, the rectangle usedField from DoInterpress can be specified as a sizeHint to increase the scale so a to use the full roll width. If doNotScale then Print does not fit the field to the medium. 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 gbb September 4, 1986 1:49:44 pm PDT Made a change to avoid anti-aliasing. All rectangles are now printed with the lower left corner starting on a pixel. changes to: DIRECTORY, PrintAlignedTile, MaskAlignedRectangle (local of PrintAlignedTile), PrintTile, PrintBand, EnumerateGeometry (local of PrintBand) gbb September 4, 1986 5:51:47 pm PDT Changed the border of cells from a sequence of rectangles to a trajectory. changes to: DIRECTORY, IMPORTS, DrawObjectBorder, DotDotDotSpace (local of DrawObjectBorder), DrawObject gbb September 5, 1986 11:09:19 am PDT Added the parameter sizeHint to the print procedure. changes to: PeachProcess, Print gbb September 19, 1986 7:14:38 pm PDT Black toner for color Versatec had gone lost somewhen. changes to: PeachProcess gbb September 22, 1986 3:26:33 pm PDT Added capability to produce tone separations for PlateMaker. changes to: DIRECTORY, PeachProcess, Print gbb September 23, 1986 6:04:17 pm PDT Addded filled trajectories. changes to: DIRECTORY, DrawArea, DrawObjectBorder, DrawObject gbb September 24, 1986 3:47:17 pm PDT Fixed scaling for devices with cut paper. Changed colour model used to print black. Added 1 to the height of bands. changes to: DIRECTORY, DrawToIP (local of DoInterpress), black, unColour, BlendColours, PeachProcess. gbb September 25, 1986 8:00:34 pm PDT Bypassed an arcane bug in the compiler. changes to: PeachProcess: see implementation note. gbb October 2, 1986 1:01:19 pm PDT Introduced a mild temporary hack to fix a server locking problem until the new print server software becomes available in about three to four weeks. Finished adjusting and testing all the little details to print on Platemaker at 1200 lines per inch resolution. Instructions are written in the Terminal viewer. When submitting the separations, please advise the operator that the separations make use of the full device size. changes to: Action (local of DoInterpress), PeachProcess gbb October 7, 1986 3:36:11 pm PDT Tweeking the rendition of colours on the Versatec. changes to: PeachProcess gbb October 9, 1986 1:47:12 pm PDT Handle gracefully the limit of 50 entries in the Interpress frame. changes to: DIRECTORY, Action (local of DoInterpress) gbb December 5, 1986 1:48:47 pm PST Added Raven 384 printer changes to: PeachProcess, Print. gbb December 18, 1986 4:52:55 pm PST In ChipNdale 23 cut (cut-2) was always black (blue), but in rel. 24 was displayed black (blue) and printed blue (green). changes to: SetLayerColourTable: cut is forced to black and cut-2 to blue. gbb December 18, 1986 7:52:00 pm PST In mid-december 1986, the Interpress to PD software has changed, and the speed-up trick of turning off the Interpress imaging model for the tesselated geometry does no longer work. The new regime is: the imager priority is always set to important, but setting NectarineImpl.layoutOnly _ TRUE in the interpreter, the priority is turned off. In addition rectangles are no longer aligned to pixels, avoiding the white strikes. changes to: OPEN, EnumerateGeometry (local of PrintBand), EnumerateTextInDesign (local of DrawToIP, local of DoInterpress), DrawToIP (local of DoInterpress), BlendRec, BlendColours, SetLayerColourTable gbb December 24, 1986 10:33:00 am PST Since gates are very important, they are given double weight. changes to: doubleYellowRGB: doubled, BlendColours: double weight for gates. gbb February 2, 1987 6:02:40 pm PST Added the capability to print at a given scale, i.e., to define  in millimetres changes to: DoInterpress added parameter lambda, DrawToIP (local of DoInterpress): fixed scaling, Print: added parameter doNotScale. gbb February 6, 1987 1:20:30 pm PST Added XNS printing service. changes to: DIRECTORY, IMPORTS, submittedPrintRequests: interim, XNSwatch:interim, PrintProcess, Print. gbb February 7, 1987 6:56:46 pm PST Added queueing for XNS printing service. changes to: DIRECTORY, XNSinfo, PrintRequest, PrintRequestRec, pendingRequests, AnalyzeSubmitted (local of ReportXNSprintingStatus), Resubmit (local of ReportXNSprintingStatus), ReportXNSprintingStatus, PrintProcess gbb February 9, 1987 1:59:04 pm PST Added a watcher because this stuff does not work in the Cedar 6.1 version of XNS printing. changes to: DIRECTORY, PrintRequestRec, niceGuyQueueSize, XNSfinalisation, XNSwatcher, ReportXNSprintingStatus, Resubmit (local of ReportXNSprintingStatus), PrintProcess, UserProfile, TRUSTED gbb February 10, 1987 2:56:47 pm PST Added the ability to print only a single layer. changes to: OPEN, StateRec, NewRect, DrawText, DrawPath, DrawArea, DrawObjectBorder, DrawDashedObjectBorder, DoInterpress, DrawToIP (local of DoInterpress), Action (local of DoInterpress), DrawSelection, niceGuyQueueSize gbb March 16, 1987 3:22:03 pm PST Added capability to print multi-page documents for the Dragon documentation. changes to: StateRec, DoInterpress, DrawToIP (local of DoInterpress), Action (local of DoInterpress), PrintProcess gbb March 25, 1987 3:26:43 pm PST Changed scaling for Platemaker to be fixed to 1.0 instead of using Platemaker's device size. changes to: PrintProcess gbb March 31, 1987 4:12:04 pm PST Took out pending queue, because did never get notification from printer, hence locking up the transfer. Now everything is just shipped off to the printer. changes to: PrintRequestRec, submittedRequests, XNSfinalisation, AnalyzeSubmitted (local of ReportXNSprintingStatus), ReportXNSprintingStatus, PrintProcess, UserProfile Ê5ê˜codešœ™KšœB™BKšœ5™5K™!—K™™ßIquote™/—code2šÏk ˜ Kšœœ ˜Kšœ œœ-˜AKšœœ˜—Kšœ œC˜QKšœ œ˜/Kšœ œ6˜DKšœ œ˜Kšœ œ ˜Kšœœ˜#Kšœœ˜Kšœœ ˜Kšœ œ˜!Kšœ œ™˜©Kšœ œ˜Kšœœe˜mKšœ œE˜TKšœœ¼œ˜ÍKšœ œ˜$Kšœ œœ˜&Kšœœ˜.Kšœœ&˜?Kšœ œ˜0Kšœ œ ˜KšœœO˜eKšœ œ(˜8Kšœœ ˜KšœœB˜\Kšœ œm˜}Kšœœ'˜/Kšœœ˜+Kšœ œ˜Kšœ œ ˜Kšœœ˜*Kšœ œ#˜3Kšœœ˜KšœœA˜WKšœ œ=ÏcÐbc˜XKšœœ:˜GKšœœ˜KšœœM˜YKšœœ/œ˜OKšœ œ˜/Kšœ œ>˜OKšœœn˜Š—MšÐln œœ˜MšœœVœ™œ˜˜¦Mšœ ˜šœ˜ IunitšÏbœŽ™­Kšœ·Ïeœ¢œ™ãNšœœœž˜'Kšœœœœ˜%Kšœœœœ˜,Kšœ œœœ˜!Nšœ œœž<˜VNšœœ˜Kšœœ˜Kšœœ'˜;Nšœœœ ˜Kš9œ œœœœœFœž œœ(œ œ>œœœœžœœžœœœœž*œœ œ&œœœœœ˜‡NšœAž˜IKšœlž˜tI artworkFigure–G134.4084 mm topLeading 134.4084 mm topIndent 1.411111 mm bottomLeading •Bounds:0.0 mm xmin 0.0 mm ymin 144.2861 mm xmax 131.5861 mm ymax •Artwork Interpress• Interpress§Interpress/Xerox/3.0  f j k j¡¥“ÄWB ¤ ¨  9¡£C ¢ ¨ r jÄÔ_ ¤Ä¾ oÄÌÛˆ ¢ ¥ ¨¡¡¨ÄWB ¤ ¨ r jĆ  ¤ ¨ x j>Á‚ ¢ ¨Âሠ€ ¢ ¨¡¥“¢·“¢°“ȯ“ÅXeroxÅ PressFontsÅ Classic-mrr£¡ “º ¤ ” •  — x j#xŒ ¢ ¨š”™@Ž#(šŽ¡¸   :ð¡š  ð%¡š % :P¡š : P%¡š x jè$" ¢ ¨¡ ¤ ¨  ™Ìæ—Z¡¡¡¡™ k°$"™¤Ž#Œ$"¤#(#Œ#(¡’˜#ð"ÝŠÁmedium– x j„!4 ¢ ¨¡ ¤ ¨  ™Ìæ—Z¡¡¡¡™ kL!4™@Ž#(!4@ :#( :¡’˜#ŒïŠÁfield–ÅXeroxÅ PressFontsÅ Classic-mir£¡ “— ¤ ”¡•¡ —  ™,옠x j -´ ¢ ¨F £ ¨  ™Ìæ—Z¡¡¡¡™ k[.MŠÁy–  ™( Ž˜ x j(Ò  ¢ ¨Ÿ ¤ ¨  ™Ìæ—Z¡¡¡¡™ k)6^ŠÁx–  — x j¡ ¤ ¨Ÿ ¤Í £ ¥ ¨  ™Ìæ—Z¡¡¡¡™ kØØ ¬ ¬¡¹ # nŠÁ(0,0)–¡ — x j  H ¢ ¨¡ ¤ ¨  ™Ìæ—Z¡¡¡¡™ kh H™mŽ˜ x j : H ¢ ¨Ÿ ¤ ¨  ™Ìæ—Z¡¡¡¡™ kr H™mŽ˜Ñ ŠÁ mediumXSize– x j H  ¢ ¨ú £ ¨  ™Ìæ—Z¡¡¡¡™ k Hh™Þ˜ x j H% ¢ ¨F £ ¨  ™Ìæ—Z¡¡¡¡™ k H$T™Þ˜ ‡BŠ x jú £ ¨Á mediumYSize– k k k k é k é k gšÏn=Ïtœ¤™TKšœœ˜Nšœ œœ˜Kšœœœ˜Nšœœœ˜#NšœœžËÐcežÐcgžG˜§—head™Mš œœœœœ˜-Kšœœ˜$Kšœœ˜Kšœœœ˜Kš œ œœœœ˜š£œœœ˜=Kšœœ5˜<—š£œœ˜,Kšœ ¢œ!™:Kšœ!˜!Kšœž˜—š£œ˜-Kšœœ œ™ Kšœ!¢ œ»™åKšœœ˜Kšœ œ˜Kšœœ ž#˜HKšœ&˜&š£œœ˜"Kšœ;˜;Kšœ0˜0Kšœž˜—Nšœ˜Kšœ,˜,Kšœœœœ˜#šœ œ˜Kšœœ)˜.Kšœ<˜Kšœž ˜—š£œœ˜ Kšœ ™ Kšœœ˜0Kšœœ˜Kšœœœœ˜CKš œœœœœ(˜Pšœœ˜(KšœI™IKšœ˜š£ œ˜'Kšœœ$œœ™>šœ œ˜Kšœ œœœ5˜Zšœ˜Kšœ œ ˜Kšœ3˜3Kš˜——Kšœž ˜—NšœJ˜JKšœœœ˜"Kš˜—Kšœž˜——™ Mšœ@˜@Kšœ;˜;š £ œœœ#œ˜`Kšœ‘™‘Kšœ]˜]Kšœy˜yKšœ$œœž˜@šœœ˜Kšœ,˜,KšœB˜BKšœ-˜-Kšœ2˜9—Kšœž˜—š£œœ ˜Kšœœœ ™*Kšœœ˜)Kšœ(˜(Kšœœ˜7Kšœœ˜$Kšœ"˜"Nšœœ*œœ˜OKšœœœœ˜#Kšœ*˜*šœ'˜.KšœP˜P—Kšœ1˜1Kšœ1˜1Kšœ2˜2Kšœ%˜%Kšœ9˜9Kšœž˜—š£œœ ˜Kšœœœ ™*Kšœœ˜)Kšœ(˜(Kšœ œ˜:Kšœ:˜:KšœA˜ANšœœ*œœ˜OKšœœœœ˜#Nšœž˜4Kšœ2˜2Kšœ+˜+KšœF˜FKšœž ˜—š£œœ ˜Kšœœœ ™*Kšœœ˜)Kšœ(˜(Kšœ œ˜:Kšœ:˜:KšœA˜ANšœœ*œœ˜OKšœœœœ˜#Nšœž˜4Kšœ2˜2Kšœ+˜+Kšœ(œ˜JKšœž ˜—š£œœ˜)Kšœ ™ K™Kšœœ˜0Kšœœ*˜3Kšœ œ ˜Kšœ*˜*Kšœ˜Nšœœœœ˜#Kšœ<˜šœ©œÛ™†Kšœœœœ™B—Kšœ ˜ Kšœ-˜-Kšœœœ˜Kšœ œ7˜DKšœTœ ˜cKšœ?œ ˜MKš˜—Kšœ˜—Kšœ ˜Kšœ˜—Kšœœœ(œ˜GN™šœ=˜=Kšœ…©œ™‡—Kšœœ$˜0Kšœ˜Kšœ2œœ˜OKšœ˜Kšœœž˜3Kšœ"ž˜9KšœFž§˜Oš˜šœ ˜Kšœ@˜@Kšœ ˜Kš˜——Kšœž ˜—š£œœ˜K™š£œ˜0Kšœœ ˜!Kšœœœ0˜NKšœœ˜Kšœ˜—š£ œ˜%Kšœœ œœ˜C—š£ œ˜"Kšœœ,˜GKšœœ˜—šœœ˜Kšœ0˜0Kšœ˜KšœQ˜QN™Kšœ2˜2K™”šœ1˜8Kšœ)ž©˜Ò—K™5Kšœž§˜ Kšœœ#˜CKšœ˜šœœ˜KšœD˜DKšœ˜Kš˜—Kšœ˜—N™:Kšœ4˜;K•StartOfExpansionI[self: ImagerInterpress.Ref, action: PROC [...], scale: REAL _ 1.0]šœ9˜9N™šœœ˜Kšœ˜K™²Kšœ˜Kšœœƒ™KšœC˜CKšœ˜Kšœ œœ˜6KšœR˜RKš˜—Kšœž ˜—šœ œ˜Kšœœ#˜>Kšœ œœ!˜NKšœ œ˜,Kšœœ œœ œœœœ˜HKšœ"˜"Kš˜—šœ˜ Kšœ+œ˜1Kšœœ#˜=Kšœœ+˜CKšœ˜Kšœ˜—NšœÐbxœ˜2Kšœ:˜:Nšœ ž˜Kšœž˜—š £ œœ œ œ ˜>Kšœ?™?š œœ2œœ˜OJšœœ,˜FJš˜—Kšœž ˜—š £œœ œ œ ˜AKšœ7™7š£œ ˜-Kš œ œœ œ œ™@Kšœœ%˜*Kšœ%˜%Kšœž ˜—Kšœœ˜-Kšœž˜—š£ œœ!œ˜?K™]Kšœ(˜(Kšœœ˜,Kšœœ(˜:š œ œ œ œœœ˜WK™\Kšœ œ œ œ˜QKšœ˜Kšœ˜Kš˜—Kšœž˜—š £œœœœ˜>MšœQ™QKšœ(˜(šœ œ!œ˜8Kšœ9˜9Kš˜—Kšœž˜—š£ œœ œ˜Kšœ œœ˜Kšœœœ ˜Kš œ œœ œ-œœ˜dMšœDž ˜MMšœœœœž˜Fš £ œœœœ˜GK™@Kšœœ˜,Kšœ œ˜Kšœœ'˜3šœœœ˜Kšœœ'˜8Kšœ œ ˜Kšœœ˜Kšœ ˜ Kšœœ œ˜0Kš˜—Kšœž ˜—Mšœ:˜:Kšœ!˜!Kšœ9˜9Kšœœ˜,Kšœœ˜3Kšœœ˜.Kšœ9˜9KšœR˜RKšœI˜Iš£ œ˜.Kšœ.œ™EKšœœœœ™8Kšœœ ˜#Kšœœ˜#Kš œœœœœœ˜=Kšœœ ˜ Nš œœœœœž˜Kšœ˜ Kšœœž#˜/šœ˜ Kšœœ ˜Kš œœ œœœ˜*Kšœ"˜"Kšœ˜—šœ˜Kšœ(œ ˜5K™š œœœœ˜š œ œœœ ˜*Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜—Kšœ˜—K™Kš œ œœ œœ˜Gšœœž2˜=š œ œ œœž˜8Kšœu™uKšœ˜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šœz™zKšœ#˜#Kšœ#˜#KšœD˜K—Kš˜—Kšœž˜—š£œœ˜K™MKšœ%˜%Kšœž˜—š £œœœœ˜8Kšœœœ™šœ˜ Kšœœ œ˜DKš˜—Kšœž˜ —š £œœœœ˜8Mšœ™Kšœœœ˜IKšœ˜Kšœž˜ ——™ P™Kšœ(ž ˜1Kšœ œ'˜7Kšœ˜š£ œœ ˜Kšœ,œ™@šœ˜$Kšœ;˜;šœ˜K™}Kšœ%œ(˜T—Kšœ˜—Kšœž ˜—š£œœ ˜Kšœ,œ™@Kšœœ˜7Kšœ˜Kšœœœ+˜PKšœž ˜—š£ œœ˜*K™>Kšœœ œ˜(Kš£œ<œœ˜QNšœœ˜Kšœ6˜6Kšœ#˜#Kšœœ"˜<šœ&˜*K™ÈKšœ0˜3—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šœ`˜`K˜Kš˜——Kšœž˜—š £ œœœœ˜@Kšœœ$˜,Kšœœ$˜,Kšœ?˜EKšœž ˜—š £ œœœ œ œ˜=Kšœ˜!Kšœž ˜—š £œœ œœœ ™9Kšœ™!Kšœž™ —š £ œœ œœœ˜LKšœ ¢ œ™3šœ ˜šœ"˜'Kšœ?˜?KšœA˜AKšœ?˜?Kšœ˜—Kšœ˜—Kšœ˜ Kšœž˜—š£œœ œ˜/Kšœ^œ™{Kšœ4˜4KšœJ˜JKšœž˜——™Mšœ œœN˜dšœœœœ™!KšœžE™WKšœ™Kšœ™Kšœ™Kšœ™Kšœ%™%Kšœ™Kšœ œ™Kšœœœ™—Mšœœœ˜)š œœœ œœœ ˜\M™K—Mšœ1˜1š£œ-˜AKšœ™Kšœ3œœ*˜{KšœJ¢œ\¢œ™ÏK˜Kšœž˜—š£œœœ˜,K™OKšœ œœ˜š£œ˜/Kšœœœ™2Kšœœ˜!Kšœh˜hšœ˜šœ%˜%Kšœ(œ#œ˜m—šœ6˜;Kšœ œ˜ Kšœ(œ#œ˜lKšœ˜—Kšœ œ˜Kšœ˜—Kšœž˜—N™Kšœ0˜0š œœœ!œœ˜?Jšœ(˜(Ifilešœž˜#Jšœ˜—Kšœž˜—š£ œœœœ œœ œœ˜”Kšœ¼™¼MšœR¢ œ¢ œ¢œ7™ÃMšœ2¡œ™DKšœœ˜5šœœ˜ Kšœœ ˜&Kšœ"œ ˜/Kšœœ˜*Kšœ˜—Kšœœ˜Kšœ œœ˜KKšœ,˜,Kšœœ˜ š£ œœ$œ˜AK™Kšœœœ˜Kšœ8˜8Kšœ#˜#Kšœ"˜"Kšœž ˜—Nšœ4˜;šœ ˜šœ˜K™ KšœF˜Fš œ œœœ˜—Kšœ(˜(Kšœ(˜(Kšœ(˜(Kšœ+ž ˜8K™>Kšœ)˜)Kšœ(˜(Kšœ+˜+Kšœ)˜)K™JKšœ™Kšœ˜—šœ ˜K™ KšœC˜CKšœ7˜7Kšœ<˜˜>Mšœ˜—š£œœ˜,K™)Kšœ œž6˜Mš£ œ˜-Kšœœ ˜Kšœ)˜)Kšœž˜—š£ œ˜+Kšœœ ˜Kšœœ˜3Kšœœ˜(Kš œ'œœœœ#˜š œœœœ˜Kšœœœœ˜KKšœ˜—Kšœ˜Kšœž ˜—Nšœ›œœ˜ÔNšœ%˜%šœœ˜Kšœ#˜#KšœA˜AKš˜—Kšœž˜—š£œœ˜-K™LMš£ œ+œ˜RKšœ7˜7Kšœž˜—š £ œœœœ œ˜LKšœ Ðekœ ¢œ«œ%«¢œ¢ œ¢œ1™ÍKšœ œ˜Kšœœ˜'Kšœœ ˜Kšœœ ˜Nšœœœ ˜$Kšœœœ+œ˜NNšœœœ œ˜-Kšœœœ+œ ˜fNšœœœ œ˜-Kšœœœ+œ˜eKšœž ˜——™Mšœ8˜8—Mšœ˜™$K™uKšœ Ïr1œ¬)œ™——™$K™JKšœ ¬4œ¬ ™h—™%Kšœ¢œ™4Kšœ ¬™—™%K™6Kšœ ¬ ™—™%K™