DIRECTORY Atom, Commander, Convert, FS, Imager, ImagerColorOperator, ImagerFont, ImagerFontFilter, ImagerInterpress, ImagerPD, ImagerPixelArray, ImagerPress, ImagerToJaM, ImagerTransformation, ImagerSmooth, PixelMapOps, ImagerPixelMap, Interpress, IO, Process, Real, Rope, ShowPress; PrintFileConvertImpl: CEDAR PROGRAM IMPORTS Atom, Commander, Convert, FS, Imager, ImagerColorOperator, ImagerFont, ImagerFontFilter, ImagerInterpress, ImagerPD, ImagerPixelArray, ImagerPress, ImagerToJaM, ImagerTransformation, Interpress, ImagerSmooth, PixelMapOps, ImagerPixelMap, IO, Process, Real, Rope, ShowPress ~ BEGIN ROPE: TYPE ~ Rope.ROPE; ActionProc: TYPE ~ PROC [inputName: ROPE, outputName: ROPE, cmd: Commander.Handle, cmds: IO.STREAM]; Log: Interpress.LogProc ~ { cmd: Commander.Handle ~ NARROW[master.logData]; msg: IO.STREAM ~ cmd.out; msg.PutRope[ SELECT class FROM masterError => "Master Error: ", masterWarning => "Master Warning: ", appearanceError => "Appearance Error: ", appearanceWarning => "Appearance Warning: ", comment => "Comment: ", ENDCASE => NIL ]; msg.PutRope[explanation]; msg.PutRope[" . . . "]; }; InterpressToAISAction: ActionProc = { AColor: TYPE = {red, green, blue}; aA: ARRAY AColor OF ATOM = [$Red, $Green, $Blue]; om: Interpress.OpenMaster; sPixelsPerInch, fPixelsPerInch: REAL _ 72.0; sPixelsPerInchI, fPixelsPerInchI: INT; pixelMap: ImagerPixelMap.PixelMap; context: Imager.Context; gray: BOOL _ FALSE; complaint: ROPE; UNTIL IO.EndOf[self: cmds] DO { token: ROPE ~ GetCmdToken[cmds]; IF token=NIL THEN LOOP; SELECT TRUE FROM Rope.Equal[token, "gray", FALSE] => gray _ TRUE; Rope.Equal[token, "ppi:", FALSE] => sPixelsPerInch _ fPixelsPerInch _ Convert.RealFromRope[r: GetCmdToken[cmds] ! Convert.Error => {cmd.out.PutRope["\nIllegal value for ppi.\n"]; GOTO Fail}]; Rope.Equal[token, "sppi:", FALSE] => sPixelsPerInch _ Convert.RealFromRope[r: GetCmdToken[cmds] ! Convert.Error => {complaint _ "\nIllegal value for sppi.\n"; GOTO Fail}]; Rope.Equal[token, "fppi:", FALSE] => fPixelsPerInch _ Convert.RealFromRope[r: GetCmdToken[cmds] ! Convert.Error => {complaint _ "\nIllegal value for fppi.\n"; GOTO Fail}]; ENDCASE => {complaint _ Rope.Cat["\nUnrecognized token: ", token, "\n"]; GOTO Fail}; EXITS Fail => Complain[complaint] } ENDLOOP; om _ Interpress.Open[inputName, Log, cmd]; sPixelsPerInchI _ Real.RoundLI[sPixelsPerInch]; fPixelsPerInchI _ Real.RoundLI[fPixelsPerInch]; pixelMap _ ImagerPixelMap.Create[3, [0, 0, 11*sPixelsPerInchI, (85*fPixelsPerInchI)/10]]; context _ ImagerSmooth.Create[pixelMap: pixelMap, component: $Intensity, viewToPixel: ImagerSmooth.LikeScreen[11*sPixelsPerInchI], initialScale: fPixelsPerInch/0.0254, change: NIL, changeData: NIL, cacheFonts: TRUE, surfaceUnitsPerPixel: 5]; IF gray THEN { -- Intensity map Process.CheckForAbort[]; cmd.out.PutF["[%g", IO.int[1]]; ImagerPixelMap.Fill[dest: pixelMap, area: [0, 0, 10000, 10000], value: 377B]; Interpress.DoPage[master: om, context: context, page: 1]; PixelMapOps.StoreAIS[Rope.Cat[outputName, ".ais"], [pixelMap, FALSE, NIL]]; cmd.out.PutRope["] "]; } ELSE FOR i: AColor IN AColor DO Process.CheckForAbort[]; cmd.out.PutF["[%g", IO.refAny[aA[i]]]; ImagerPixelMap.Fill[dest: pixelMap, area: [0, 0, 10000, 10000], value: 377B]; ImagerSmooth.SetComponent[context, aA[i]]; Interpress.DoPage[master: om, context: context, page: 1]; PixelMapOps.StoreAIS[Rope.Cat[outputName, "-", Atom.GetPName[aA[i]], ".ais"], [pixelMap, FALSE, NIL]]; cmd.out.PutRope["] "]; ENDLOOP; }; PressToInterpressAction: ActionProc ~ { version: ROPE ~ GetCmdToken[cmds]; verbose: ROPE ~ GetCmdToken[cmds]; header: ROPE ~ IF Rope.Size[version] = 3 AND Rope.Fetch[version, 1] = '. THEN Rope.Cat["Interpress/Xerox/", version, " "] ELSE NIL; showPress: ShowPress.Handle ~ ShowPress.Open[inputName]; interpress: ImagerInterpress.Ref _ ImagerInterpress.Create[outputName, header]; xc: BOOL _ Rope.Size[version] = 3 AND Rope.Fetch[version, 0] < '3; FOR i: INT IN [1..showPress.lastPart) DO Paint: PROC [context: Imager.Context] ~ { cmd.out.PutF["[%g", IO.int[i]]; IF xc THEN context _ FontTranslator[context, version, cmd, verbose.Equal["verbose", FALSE]]; Imager.SetPriorityImportant[context, TRUE]; ShowPress.DrawPressPage[context: context, show: showPress, pageNumber: i]; cmd.out.PutRope["] "]; }; Process.CheckForAbort[]; ImagerInterpress.DoPage[self: interpress, action: Paint, scale: 1.0E-5]; ENDLOOP; ImagerInterpress.Close[interpress]; }; inch: REAL ~ 0.0254; headerSampled: ROPE _ "Interpress/Xerox/3.0 "; aisMargin: REAL _ 0.25*inch; pageWidth: REAL _ 8.5*inch; pageHeight: REAL _ 11*inch; captionFont: ROPE _ "xerox/pressfonts/helvetica-mir"; captionLoc: Imager.VEC ~ [72, 9]; FileChoice: PROC [r: Rope.ROPE, a: ARRAY [0..3) OF Rope.ROPE] RETURNS [result: Rope.ROPE _ NIL] ~ { FOR i: NAT IN [0..3) DO IF a[i] # NIL THEN { name: ROPE ~ Rope.Cat[r, "-", a[i], ".ais"]; result _ FS.FileInfo[name ! FS.Error => {IF error.code = $unknownFile THEN CONTINUE}].fullFName; IF result# NIL THEN RETURN; }; ENDLOOP; }; GetColorNames: PROC [name: Rope.ROPE] RETURNS [ok: BOOL, red, grn, blu: Rope.ROPE] ~ { red _ FileChoice[name, ["red", "r", NIL]]; IF red = NIL THEN { ok _ FALSE; RETURN}; grn _ FileChoice[name, ["grn", "green", "g"]]; IF grn = NIL THEN { ok _ FALSE; RETURN}; blu _ FileChoice[name, ["blu", "blue", "b"]]; ok _ blu # NIL; }; ColorAISToInterpressCommand: Commander.CommandProc ~ { red, grn, blu: ROPE; interpress: ImagerInterpress.Ref; pa: Imager.PixelArray; maxSample: CARDINAL; rect: Imager.Rectangle; scale: REAL; Paint: PROC [context: Imager.Context] ~ { Caption: PROC ~ { Imager.ScaleT[context, inch/72]; Imager.SetFont[context, ImagerFont.Scale[ImagerFont.Find[captionFont], 9]]; Imager.SetXY[context, [72, 9]]; Imager.ShowRope[context, cmd.commandLine]; }; Imager.SetPriorityImportant[context, TRUE]; Imager.DoSave[context, Caption]; Imager.TranslateT[context, [pageWidth*0.5, pageHeight*0.5]]; Imager.ScaleT[context, scale]; Imager.TranslateT[context, [-(rect.x+rect.w*0.5), -(rect.y+rect.h*0.5)]]; Imager.SetSampledColor[context: context, pa: pa, m: NIL, colorOperator: ImagerColorOperator.RGBLinearColorModel[maxSample]]; Imager.MaskRectangle[context, rect]; }; stream: IO.STREAM _ IO.RIS[cmd.commandLine]; outputName: ROPE _ GetCmdToken[stream]; secondTokenIndex: INT _ IO.GetIndex[stream]; gets: ROPE _ GetCmdToken[stream]; ok: BOOL _ FALSE; inputName: ROPE _ NIL; IF NOT gets.Equal["_"] THEN { inputName _ outputName; outputName _ NIL; stream.SetIndex[secondTokenIndex]; } ELSE {inputName _ GetCmdToken[stream]}; IF inputName = NIL THEN RETURN[result: $Failure, msg: cmd.procData.doc]; [ok, red, grn, blu] _ GetColorNames[inputName ! FS.Error => { IF error.group = user THEN {result _ $Failure; msg _ error.explanation; GOTO Quit} }]; IF NOT ok THEN RETURN[result: $Failure, msg: "Could not find one or more of the input files\n"]; IF outputName = NIL THEN { outputName _ MakeOutputName[inputName, cmd.procData.doc]; }; cmd.out.PutF["Reading\n %g\n %g\n %g . . . ", IO.rope[red], IO.rope[grn], IO.rope[blu]]; pa _ ImagerPixelArray.Join3AIS[red, grn, blu]; maxSample _ ImagerPixelArray.MaxSampleValue[pa, 0]; rect _ ImagerTransformation.TransformRectangle[pa.m, [0, 0, pa.sSize, pa.fSize]]; scale _ MIN[(pageWidth-2*aisMargin)/rect.w, (pageHeight-2*aisMargin)/rect.h]; interpress _ ImagerInterpress.Create[outputName, headerSampled]; ImagerInterpress.DeclarePixelArray[interpress, pa]; ImagerInterpress.DoPage[self: interpress, action: Paint, scale: 1.0]; ImagerInterpress.Close[interpress]; outputName _ FindFullName[outputName]; cmd.out.PutRope["\n "]; cmd.out.PutRope[outputName]; cmd.out.PutRope[" written.\n"]; EXITS Quit => NULL }; AISToInterpressAction: ActionProc ~ { interpress: ImagerInterpress.Ref _ ImagerInterpress.Create[outputName, headerSampled]; pa: Imager.PixelArray _ ImagerPixelArray.FromAIS[inputName]; maxSample: CARDINAL ~ ImagerPixelArray.MaxSampleValue[pa, 0]; rect: Imager.Rectangle _ ImagerTransformation.TransformRectangle[pa.m, [0, 0, pa.sSize, pa.fSize]]; scale: REAL _ MIN[(pageWidth-2*aisMargin)/rect.w, (pageHeight-2*aisMargin)/rect.h]; Paint: PROC [context: Imager.Context] ~ { Caption: PROC ~ { Imager.ScaleT[context, inch/72]; Imager.SetFont[context, ImagerFont.Scale[ImagerFont.Find[captionFont], 9]]; Imager.SetXY[context, [72, 9]]; Imager.ShowRope[context, cmd.commandLine]; }; Imager.SetPriorityImportant[context, TRUE]; Imager.DoSave[context, Caption]; Imager.TranslateT[context, [pageWidth*0.5, pageHeight*0.5]]; Imager.ScaleT[context, scale]; Imager.TranslateT[context, [-(rect.x+rect.w*0.5), -(rect.y+rect.h*0.5)]]; Imager.SetSampledColor[context: context, pa: pa, m: NIL, colorOperator: ImagerColorOperator.GrayLinearColorModel[maxSample, 0, maxSample]]; Imager.MaskRectangle[context, rect]; }; cmd.out.PutF["[%g", IO.int[1]]; ImagerInterpress.DeclarePixelArray[interpress, pa]; ImagerInterpress.DoPage[self: interpress, action: Paint, scale: 1.0]; cmd.out.PutRope["] "]; ImagerInterpress.Close[interpress]; }; InterpressToPressAction: ActionProc ~ { interpress: Interpress.OpenMaster ~ Interpress.Open[inputName, Log, cmd]; context: Imager.Context ~ ImagerPress.SimpleCreate[fileName: outputName, printerType: press]; FOR i: INT IN [1..interpress.pages] DO Process.CheckForAbort[]; cmd.out.PutF["[%g", IO.int[i]]; Interpress.DoPage[master: interpress, context: context, page: i]; cmd.out.PutRope["] "]; IF i # interpress.pages THEN ImagerPress.NewPage[context]; ENDLOOP; ImagerPress.Close[context]; }; InterpressToJaMAction: ActionProc ~ { interpress: Interpress.OpenMaster ~ Interpress.Open[inputName, Log, cmd]; stream: IO.STREAM ~ FS.StreamOpen[outputName, $create]; context: Imager.Context ~ ImagerToJaM.Create[stream]; stream.PutRope["% Produced from "]; stream.PutRope[inputName]; stream.PutRope["\n"]; FOR i: INT IN [1..interpress.pages] DO Process.CheckForAbort[]; stream.PutF["%% Page %g\n", IO.int[i]]; Interpress.DoPage[master: interpress, context: context, page: i]; ENDLOOP; ImagerToJaM.Close[context]; }; printerTypeNames: ARRAY ImagerPD.PrinterType OF ROPE _ [ nil: NIL, raven300: "raven300", raven384: "raven384", o3: NIL, plateMaker: "plateMaker", o5: NIL, puffin: "puffin", colorVersatec: "colorVersatec", versatec: "versatec", color400: "color400", c150: "c150", d4020: "d4020", bw400: "bw400", o13: NIL, o14: NIL, o15: NIL ]; printerTypePPD: ARRAY ImagerPD.PrinterType OF REAL _ [ nil: 5, raven300: 6, raven384: 6, o3: 5, plateMaker: 9, o5: 5, puffin: 6, colorVersatec: 5, versatec: 5, color400: 7, c150: 4, d4020: 4, bw400: 7, o13: 5, o14: 5, o15: 5 ]; PrinterTypeFromRope: PROC [rope: ROPE] RETURNS [ImagerPD.PrinterType] ~ { FOR p: ImagerPD.PrinterType IN ImagerPD.PrinterType DO IF Rope.Equal[rope, printerTypeNames[p], FALSE] THEN RETURN [p]; ENDLOOP; RETURN [nil]; }; Rev: PROC [list: ImagerPD.Toners] RETURNS [ImagerPD.Toners] ~ { l1, l2, l3: ImagerPD.Toners _ NIL; IF list = NIL THEN RETURN[NIL]; l3 _ list; UNTIL (l1 _ l3) = NIL DO l3 _ l3.rest; l1.rest _ l2; l2 _ l1; ENDLOOP; RETURN[l2]; }; InterpressToPDAction: ActionProc ~ { deviceCodeRope: ROPE ~ GetCmdToken[cmds]; printerType: ImagerPD.PrinterType ~ PrinterTypeFromRope[deviceCodeRope]; r: REAL _ 0.0; tok: ROPE _ NIL; Err: PROC ~ { IF tok#NIL THEN Complain[Rope.Concat["Unknown keyword: ", tok]] ELSE Complain["Malformed command"]; }; tx, ty: REAL _ 0.0; scale: REAL _ 1.0; toners: ImagerPD.Toners _ NIL; tonerUniverse: ImagerPD.Toners _ NIL; ppd: REAL _ -1.0; skipPages: INT _ 0; nPages: INT _ INT.LAST; tok _ GetCmdToken[cmds]; DO SELECT TRUE FROM Rope.Equal[tok, "black", FALSE] => { toners _ CONS[black, toners]; }; Rope.Equal[tok, "cyan", FALSE] => { toners _ CONS[cyan, toners]; }; Rope.Equal[tok, "magenta", FALSE] => { toners _ CONS[magenta, toners]; }; Rope.Equal[tok, "yellow", FALSE] => { toners _ CONS[yellow, toners]; }; ENDCASE => EXIT; tok _ GetCmdToken[cmds]; ENDLOOP; toners _ Rev[toners]; IF Rope.Equal[tok, "of", FALSE] THEN { tok _ GetCmdToken[cmds]; SELECT TRUE FROM Rope.Equal[tok, "3", FALSE] => { tonerUniverse _ LIST[cyan, magenta, yellow]; }; Rope.Equal[tok, "4", FALSE] => { tonerUniverse _ LIST[black, cyan, magenta, yellow]; }; ENDCASE => Err[]; tok _ GetCmdToken[cmds]; }; IF tok # NIL THEN { r _ RealFromRope[tok]; tok _ GetCmdToken[cmds]; SELECT TRUE FROM Rope.Equal[tok, "ppd", FALSE] => {ppd _ r; r _ GetReal[cmds]; tok _ GetCmdToken[cmds]}; ENDCASE => NULL; SELECT TRUE FROM Rope.Equal[tok, "in", FALSE] => { tx _ r; ty _ GetReal[cmds]; tok _ GetCmdToken[cmds]; IF Rope.Equal[tok, "in", FALSE] AND Rope.Equal[tok _ GetCmdToken[cmds], "translate", FALSE] THEN {r _ GetReal[cmds]; tok _ GetCmdToken[cmds]} ELSE Err[]; }; ENDCASE => NULL; SELECT TRUE FROM Rope.Equal[tok, "scale", FALSE] => {scale _ r; r _ GetReal[cmds]; tok _ GetCmdToken[cmds]}; ENDCASE => NULL; SELECT TRUE FROM Rope.Equal[tok, "skipPages", FALSE] => {skipPages _ Real.Round[r]; r _ GetReal[cmds]; tok _ GetCmdToken[cmds]}; ENDCASE => NULL; SELECT TRUE FROM Rope.Equal[tok, "nPages", FALSE] => {nPages _ Real.Round[r]; r _ GetReal[cmds]; tok _ GetCmdToken[cmds]}; tok = NIL => NULL; ENDCASE => Err[]; }; IF printerType = nil THEN { cmd.out.PutRope["Unknown printer type: "]; cmd.out.PutRope[deviceCodeRope]; cmd.out.PutChar['\n]; cmd.out.PutRope["Valid types are: "]; FOR p: ImagerPD.PrinterType IN ImagerPD.PrinterType DO cmd.out.PutRope[printerTypeNames[p]]; cmd.out.PutChar[' ]; ENDLOOP; cmd.out.PutChar['\n]; ERROR ABORTED; } ELSE { realPPD: REAL ~ IF ppd > 0 THEN ppd ELSE printerTypePPD[printerType]; interpress: Interpress.OpenMaster ~ Interpress.Open[inputName, Log, cmd]; pd: ImagerPD.PD _ ImagerPD.CreateFromPrinterType[outputName, printerType, toners, tonerUniverse, realPPD]; nPages _ MIN[nPages, interpress.pages-skipPages]; FOR i: INT IN [skipPages..skipPages+nPages) DO action: PROC [context: Imager.Context] ~ { IF tx#0.0 OR ty#0.0 THEN { Imager.TranslateT[context, [tx*0.0254, ty*0.0254]]; }; IF scale#1.0 THEN { IF scale=-1 THEN Imager.Scale2T[context, [-1.0, 1.0]] ELSE Imager.ScaleT[context, scale]; }; Interpress.DoPage[master: interpress, context: context, page: i+1]; }; cmd.out.PutF[" [%g", IO.int[i+1]]; ImagerPD.DoPage[pd: pd, action: action, pixelUnits: FALSE]; cmd.out.PutChar[']]; ENDLOOP; cmd.out.PutChar[' ]; ImagerPD.Close[pd]; }; }; FontTranslator: PROC [c: Imager.Context, version: ROPE, cmd: Commander.Handle, verbose: BOOL] RETURNS [context: Imager.Context] ~ { fontMap: ImagerFontFilter.FontMap _ xc1map; RETURN [ImagerFontFilter.FilterFonts[c, fontMap, cmd, verbose]]; }; CH: PROC [char: CHAR] RETURNS [WORD] ~ INLINE {RETURN [ORD[char]]}; XC: PROC [set: [0..256), code: [0..256)] RETURNS [WORD] ~ {RETURN [set*256+code]}; C1: PROC [char: CHAR, set: [0..256), code: [0..256)] RETURNS [ImagerFontFilter.CharRangeMap] ~ { RETURN [[bc: CH[char], ec: CH[char], newbc: XC[set, code]]] }; classicModernEtAl: LIST OF ROPE _ LIST["Classic", "Modern"]; timesRomanEtAl: LIST OF LIST OF ROPE _ LIST[LIST["TimesRoman", "Classic"], LIST["Helvetica", "Modern"], LIST["Gacha", "XeroxBook"], LIST["Tioga", "Classic"], LIST["Laurel", "Classic"]]; mrrEtAl: LIST OF ROPE _ LIST["-mrr", "-mir-italic", "-bir-bold-italic", "-brr-bold"]; alphaMap: ImagerFontFilter.CharacterCodeMap ~ LIST [ [bc: CH[' ], ec: CH['~], newbc: CH[' ]] ]; mathMap: ImagerFontFilter.CharacterCodeMap _ LIST [ C1['c, 0, 323B], C1['r, 0, 322B] ]; oisMap: ImagerFontFilter.CharacterCodeMap _ LIST [ [bc: CH['a], ec: CH['~], newbc: CH['a]], [bc: CH['.], ec: CH[']], newbc: CH['.]], [bc: CH['%], ec: CH[',], newbc: CH['%]], [bc: CH['-], ec: CH['-], newbc: XC[357B, 42B]], [bc: CH[' ], ec: CH['!], newbc: CH[' ]], [bc: CH['\"], ec: CH['\"], newbc: XC[0, 271B]], [bc: CH['#], ec: CH['#], newbc: CH['#]], [bc: CH['$], ec: CH['$], newbc: XC[0, 244B]], [bc: CH['^], ec: CH['^], newbc: XC[0, 255B]], [bc: CH['_], ec: CH['_], newbc: XC[0, 254B]], C1['\030, 357B, 45B], C1['\267, 357B, 146B], C1['\265, 41B, 172B], C1['\140, 0, 140B], C1[', 357B, 064B], C1[', 357B, 065B], ]; xc1map: ImagerFontFilter.FontMap _ MakeXC1map[]; MakeXC1map: PROC RETURNS [f: ImagerFontFilter.FontMap] ~ { Enter: PROC [e: ImagerFontFilter.FontMapEntry] ~ {f _ CONS[e, f]}; FOR family: LIST OF ROPE _ classicModernEtAl, family.rest UNTIL family = NIL DO FOR face: LIST OF ROPE _ mrrEtAl, face.rest UNTIL face = NIL DO Enter[[ inputName: Rope.Cat["Xerox/Pressfonts/", family.first, face.first.Substr[0, 4]], output: LIST[[newName: Rope.Cat["Xerox/xc1-1-1/", family.first, face.first.Substr[4]], charMap: oisMap]] ]]; ENDLOOP; ENDLOOP; FOR family: LIST OF LIST OF ROPE _ timesRomanEtAl, family.rest UNTIL family = NIL DO FOR face: LIST OF ROPE _ mrrEtAl, face.rest UNTIL face = NIL DO Enter[[ inputName: Rope.Cat["Xerox/Pressfonts/", family.first.first, face.first.Substr[0, 4]], output: LIST[[newName: Rope.Cat["Xerox/xc1-1-1/", family.first.rest.first, face.first.Substr[4]], charMap: oisMap]], warn: TRUE ]]; ENDLOOP; ENDLOOP; Enter[[ inputName: "Xerox/Pressfonts/Logo-mrr", output: LIST[[newName: "Xerox/xc1-1-1/Logotypes-Xerox", charMap: alphaMap]] ]]; Enter[[ inputName: "Xerox/Pressfonts/Math-mrr", output: LIST[[newName: "Xerox/xc1-1-1/Modern", charMap: mathMap]] ]]; Enter[[ inputName: "Xerox/Pressfonts/Math-mir", output: LIST[[newName: "Xerox/xc1-1-1/Modern-italic", charMap: mathMap]] ]]; }; FindFullName: PROC [inputName: ROPE] RETURNS [ROPE] ~ { fullFName: ROPE _ NIL; fullFName _ FS.FileInfo[inputName].fullFName; RETURN [fullFName] }; CmdTokenBreak: PROC [char: CHAR] RETURNS [IO.CharClass] = { IF char = '_ THEN RETURN [break]; IF char = ' OR char = '\t OR char = ', OR char = '; OR char = '\n THEN RETURN [sepr]; RETURN [other]; }; GetCmdToken: PROC [stream: IO.STREAM] RETURNS [rope: ROPE] = { rope _ NIL; rope _ stream.GetTokenRope[CmdTokenBreak ! IO.EndOfStream => CONTINUE].token; }; RealFromRope: PROC [rope: ROPE] RETURNS [real: REAL] = { oops: BOOL _ FALSE; real _ Convert.RealFromRope[rope ! Convert.Error => {oops _ TRUE; CONTINUE}]; IF oops THEN {oops _ FALSE; real _ Convert.IntFromRope[rope ! Convert.Error => {oops _ TRUE; CONTINUE}]}; IF oops THEN Complain[Rope.Concat["Number expected: ", rope]]; }; GetReal: PROC [stream: IO.STREAM] RETURNS [real: REAL _ 0.0] = { tokenKind: IO.TokenKind _ tokenEOF; rope: ROPE _ NIL; [tokenKind: tokenKind, token: rope] _ stream.GetCedarTokenRope[ ! IO.EndOfStream => CONTINUE; IO.Error => Complain["Number expected"]; ]; SELECT tokenKind FROM tokenDECIMAL => real _ Convert.IntFromRope[rope]; tokenREAL => real _ Convert.RealFromRope[rope]; tokenEOF => real _ -0.0; ENDCASE => Complain[Rope.Concat["Number expected: ", rope]]; }; Complain: ERROR [complaint: ROPE] ~ CODE; MakeOutputName: PROC [inputName: ROPE, doc: ROPE] RETURNS [ROPE] ~ { start: INT _ Rope.Index[s1: doc, s2: " to "]+4; end: INT _ Rope.Index[s1: doc, pos1: start, s2: " "]; cp: FS.ComponentPositions; isAIS: BOOL _ Rope.Equal[Rope.Substr[doc, start, end-start], "ais", FALSE]; [inputName, cp] _ FS.ExpandName[inputName]; RETURN [Rope.Cat[ Rope.Substr[inputName, cp.base.start, cp.base.length], IF isAIS THEN NIL ELSE ".", IF isAIS THEN NIL ELSE Rope.Substr[doc, start, end-start] ]] }; Command: Commander.CommandProc ~ { refAction: REF ActionProc ~ NARROW[cmd.procData.clientData]; stream: IO.STREAM _ IO.RIS[cmd.commandLine]; outputName: ROPE _ GetCmdToken[stream]; secondTokenIndex: INT _ IO.GetIndex[stream]; gets: ROPE _ GetCmdToken[stream]; inputName: ROPE _ NIL; IF NOT gets.Equal["_"] THEN { inputName _ outputName; outputName _ NIL; stream.SetIndex[secondTokenIndex]; } ELSE {inputName _ GetCmdToken[stream]}; IF inputName = NIL THEN RETURN[result: $Failure, msg: cmd.procData.doc]; inputName _ FindFullName[inputName ! FS.Error => { IF error.group = user THEN {result _ $Failure; msg _ error.explanation; GOTO Quit} }]; IF outputName = NIL THEN { outputName _ MakeOutputName[inputName, cmd.procData.doc]; }; cmd.out.PutRope["Reading "]; cmd.out.PutRope[inputName]; cmd.out.PutRope[" . . . "]; refAction^[inputName, outputName, cmd, stream ! Complain => {result _ $Failure; msg _ complaint; GOTO Quit}]; outputName _ FindFullName[outputName ! FS.Error => { outputName _ "Output file(s)"; CONTINUE}; ]; cmd.out.PutRope[outputName]; cmd.out.PutRope[" written.\n"]; EXITS Quit => NULL }; Commander.Register["PressToInterpress", Command, "Convert Press file to Interpress (output _ input [version])\n", NEW[ActionProc _ PressToInterpressAction]]; Commander.Register["AISToInterpress", Command, "Convert AIS file to Interpress (output _ input)\n", NEW[ActionProc _ AISToInterpressAction]]; Commander.Register["ColorAISToInterpress", Command, "Convert Color AIS file to Interpress (output _ input)\n", NEW[ActionProc _ AISToInterpressAction]]; Commander.Register["InterpressToPress", Command, "Convert Interpress file to Press (output _ input)\n", NEW[ActionProc _ InterpressToPressAction]]; Commander.Register["InterpressToJaM", Command, "Convert Interpress file to JaM (output _ input)\n", NEW[ActionProc _ InterpressToJaMAction]]; Commander.Register["InterpressToPD", Command, "Convert' Interpress file to PD (output _ input printerType {black | cyan | magenta | yellow} [of (3 | 4)] [ ppd] [ in in translate] [ scale] [ skipPages] [ nPages])\n", NEW[ActionProc _ InterpressToPDAction]]; Commander.Register["ColorAISToInterpress", ColorAISToInterpressCommand, "Convert Color AIS files to Interpress (output _ inputRoot)\n"]; Commander.Register["InterpressToAIS", Command, "Convert Interpress file to AIS (outputRoot _ input) {Gray} {ppi: }\n", NEW[ActionProc _ InterpressToAISAction]]; END. DPrintFileConvertImpl.mesa Copyright c 1984, 1985 by Xerox Corporation. All rights reserved. Michael Plass, October 29, 1985 9:04:51 am PST Tim Diebert: February 18, 1986 10:36:06 am PST Pier, December 17, 1985 10:21:47 am PST Eric Nickell February 12, 1986 1:23:48 pm PST Rick Beach, February 19, 1986 1:01:28 pm PST สA˜codešœ™Kšœ ฯmœ7™BK™.K™.K™'K™-K™,—K˜Kšฯk œžœาžœ!˜›K˜Kšะlnœžœž˜#Kšžœžœาžœ ˜˜Kšœž˜K˜šžœžœžœ˜K˜—š œ žœžœ žœžœžœžœ˜dK˜—šœ˜Kšœžœ˜/Kšœžœžœ ˜šœ ˜ šžœž˜Kšœ ˜ Kšœ$˜$Kšœ(˜(Kšœ,˜,Kšœ˜Kšžœž˜—K˜—Kšœ˜Kšœ˜Kšœ˜K˜—šฯnœ˜%Jšœžœ˜"Jšœžœžœžœ˜1Kšœ˜Jšœ žœ˜,Jšœ"žœ˜&Jšœ"˜"Kšœ˜Kšœžœžœ˜Kšœ žœ˜J˜•StartOfExpansion[self: STREAM]šžœžœžœ˜K–\[base: ROPE, start: INT _ 0, len: INT _ 2147483647, translator: Rope.TranslatorType]šœžœ˜ Kšžœžœžœžœ˜šžœžœž˜Kšœžœ žœ˜0K– [r: ROPE]šœžœ”žœ˜ฟK– [r: ROPE]šœžœžœ˜ซK– [r: ROPE]šœžœžœ˜ซKšžœCžœ˜U—Kšžœ˜!Kšœžœ˜ —J˜Kšœ*˜*Jšœ/˜/Jšœ/˜/JšœY˜YKšœฐžœžœžœ˜๑J˜šžœžœฯc˜J˜Kšœžœ ˜K–[dest: ImagerPixelMap.PixelMap, area: ImagerPixelMap.DeviceRectangle, value: CARDINAL, function: ImagerPixelMap.Function]šœM˜MKšœ9˜9Jšœ>žœžœ˜KK˜Jšœ˜—šžœžœ žœž˜K˜Kšœžœ˜&K–[dest: ImagerPixelMap.PixelMap, area: ImagerPixelMap.DeviceRectangle, value: CARDINAL, function: ImagerPixelMap.Function]šœM˜MKšœ*˜*Kšœ9˜9JšœYžœžœ˜fK˜Jšžœ˜—Kšœ˜K˜—š œ˜'Kšœ žœ˜"Kšœ žœ˜"Kš œžœžœžœžœ-žœžœ˜ƒKšœ8˜8KšœO˜OKšœžœžœ˜Bšžœžœžœž˜(š œžœ˜)Kšœžœ ˜KšžœžœJžœ˜\Kšœ%žœ˜+KšœJ˜JK˜Kšœ˜—K˜KšœH˜HKšžœ˜—Kšœ#˜#Kšœ˜K˜—Kšœžœ ˜Kšœžœ˜.Kšœ žœ ˜Kšœ žœ ˜Kšœ žœ ˜Kšœ žœ$˜5šœžœ ˜!K˜—š   œžœ žœžœžœžœ˜=Kšžœžœžœ˜%šžœžœžœž˜šžœžœžœ˜Kšœžœ"˜,Kš œ žœžœ žœžœžœ ˜`Kšžœ žœžœžœ˜Kšœ˜—Kšžœ˜—K˜—K˜š ะbn œžœ žœžœžœžœ˜VKšœ$žœ˜*Kš žœžœžœžœžœ˜(Kšœ.˜.Kš žœžœžœžœžœ˜(Kšœ-˜-Kšœ žœ˜K˜K˜—š œ˜6Kšœžœ˜Kšœ!˜!Kšœ˜Kšœ žœ˜K˜Kšœžœ˜ š œžœ˜)š œžœ˜Kšœ ˜ KšœK˜KKšœ˜Kšœ*˜*Kšœ˜—Kšœ%žœ˜+Kšœ ˜ Kšœ<˜K– "cedar" stylešœžœ˜ K– "cedar" stylešœ+žœžœ˜MKšœ˜K˜—– "cedar" styleš   œžœžœžœžœ˜8K– "cedar" stylešœžœžœ˜K– "cedar" stylešœ<žœžœ˜MK– "cedar" styleš žœžœ žœ=žœžœ˜iK– "cedar" stylešžœžœ2˜>Kšœ˜K˜—– "cedar" styleš  œžœ žœžœžœžœ ˜@K– "cedar" stylešœ žœ˜#K– "cedar" stylešœžœžœ˜– "cedar" stylešœA˜AK– "cedar" stylešžœžœ˜K– "cedar" stylešžœ&˜(K– "cedar" stylešœ˜—šžœ ž˜Kšœ1˜1Kšœ/˜/Kšœ˜Kšžœ5˜<—Kšœ˜K˜—šœ žœ žœžœ˜)K˜—š  œžœ žœžœžœžœ˜DKšœžœ%˜/Kšœžœ-˜5Kšœžœ˜Kšœžœ9žœ˜KKšœžœ˜+šžœ ˜Kšœ6˜6Kšžœžœžœžœ˜Kšžœžœžœžœ#˜9Kšœ˜—Kšœ˜K˜—š œ˜"Kšœ žœžœ˜