DIRECTORY Process USING [ SecondsToTicks, Pause ], Basics USING [BITOR, BYTE], Atom USING [PutPropOnList, GetPropFromList, PropList], Real USING [FixI, Float], Terminal USING [Virtual, FrameBuffer, GetColorFrameBufferA, GetColorFrameBufferB, GetBWFrameBuffer, Current, ModifyColorFrame], QuickViewer USING [QuickView], ViewerClasses USING [Viewer], ViewerOps USING [OpenIcon], Imager USING [Context, Transformation, Rectangle], ImagerBackdoor USING [GetBounds, GetT], ImagerRasterPrivate USING [Data], ImagerPixelMap USING [DeviceRectangle], SampleMapOps USING [Create, SampleMap, SubMap, Transfer, GetSample, PutSample, Fill, FromVM, FromSubMap, Get, Put, Function, Buffer, ObtainBuffer, SampleMapRep], ImagerColor USING [RGB], Pixels USING [SubMapSequence, SampleSet, SubMap, SampleSetSequence, PixelBuffer, Extent, ErrorDesc]; PixelsImpl: CEDAR PROGRAM IMPORTS Basics, Atom, ImagerBackdoor, SampleMapOps, Real, Terminal, ViewerOps, Process EXPORTS Pixels ~ BEGIN OPEN Pixels; BYTE: TYPE ~ Basics.BYTE; RGB: TYPE ~ ImagerColor.RGB; SampleSet: TYPE ~ Pixels.SampleSet; SampleSetSequence: TYPE ~ Pixels.SampleSetSequence; SubMapSequence: TYPE ~ Pixels.SubMapSequence; PixelBuffer: TYPE ~ Pixels.PixelBuffer; Extent: TYPE ~ Pixels.Extent; PixelsError: PUBLIC SIGNAL [reason: Pixels.ErrorDesc] = CODE; SubMap: TYPE ~ Pixels.SubMap; SampleMap: TYPE ~ SampleMapOps.SampleMap; XfmMapPlace: PUBLIC PROC [ map: SubMap, x, y: INTEGER ] RETURNS [newX, newY: INTEGER] ~ { x _ map.df * (x + map.subMap.start.f); y _ MAX[0, INTEGER[map.subMap.size.s]-1 - y + map.subMap.start.s]; RETURN [ newX: x, newY: y ]; }; ByteAvrgWgtd: PUBLIC PROC[ b1, b2, wgt: BYTE ] RETURNS[ bOut: BYTE ] ~ { bOut _ ( CARDINAL[b1]*256 + CARDINAL[wgt]*CARDINAL[b2 - b1] ) / 256; bOut _ Basics.BITOR[ bOut, 1 ]; -- Von Neumann rounding }; SumLessProd: PUBLIC PROC[ b1, b2: BYTE ] RETURNS[ bOut: BYTE ] ~ { bOut _ ( CARDINAL[b1]*256 + CARDINAL[b2]*256 - CARDINAL[b2]*CARDINAL[b1] ) / 256; bOut _ Basics.BITOR[ bOut, 1 ]; -- Von Neumann rounding }; GetSampleSet: PUBLIC PROC[size: NAT] RETURNS[SampleSet] ~ { RETURN[ SampleMapOps.ObtainBuffer[size] ]; }; SampleMapFromFrameBuffer: PROC [frameBuffer: Terminal.FrameBuffer] RETURNS [SampleMap] ~ { RETURN [ SampleMapOps.FromVM[ fSize: frameBuffer.width, sSize: frameBuffer.height, bitsPerSample: frameBuffer.bitsPerPixel, vm: frameBuffer.vm ] ]; }; PositionFromProps: PROCEDURE [props: Atom.PropList] RETURNS [NAT] = { position: REF NAT _ NARROW[ Atom.GetPropFromList[props, $Alpha] ]; IF position = NIL THEN ERROR PixelsError[[$MisMatch, "Expected alpha buffer"]] ELSE RETURN[position^]; }; Swap: PROCEDURE [first, second: INTEGER] RETURNS [INTEGER, INTEGER] = { RETURN [second, first]; }; SGN: PROCEDURE [number: INTEGER] RETURNS [INTEGER] = INLINE { IF number >= 0 THEN RETURN[1] ELSE RETURN[-1]; }; Create: PUBLIC PROC [width, height: NAT, pixelSizes: SampleSet] RETURNS[ PixelBuffer ] ~ { buf: PixelBuffer; IF pixelSizes = NIL THEN SIGNAL PixelsError[[$Mismatch, "Pixel sizes needed"]]; buf.pixels _ NEW[SubMapSequence[pixelSizes.length] ]; FOR i: NAT IN [0..pixelSizes.length) DO IF pixelSizes[i] > 0 THEN buf.pixels[i].subMap.sampleMap _ SampleMapOps.Create[ fSize: width, sSize: height, bitsPerSample: pixelSizes[i] ]; buf.pixels[i].df _ 1; buf.pixels[i].subMap.start _ [0, 0]; buf.pixels[i].subMap.size _ [f: width, s: height]; ENDLOOP; buf.height _ height; buf.width _ width; buf.samplesPerPixel _ pixelSizes.length; RETURN [buf]; }; GetFromImagerContext: PUBLIC PROC [context: Imager.Context, alpha, depth: BOOLEAN] RETURNS[PixelBuffer, Imager.Rectangle] ~ { buf: PixelBuffer; bounds: Extent; noColor: BOOLEAN _ FALSE; newBds: Imager.Rectangle; xfm: Imager.Transformation; vt: Terminal.Virtual _ Terminal.Current[]; numMaps: NAT _ 0; WITH context.data SELECT FROM quickView: QuickViewer.QuickView => { viewer: ViewerClasses.Viewer _ quickView.viewer; WHILE viewer.parent # NIL DO viewer _ viewer.parent ENDLOOP; IF viewer.column # color THEN noColor _ TRUE; IF viewer.iconic THEN ViewerOps.OpenIcon[ viewer ]; }; imagerRaster: ImagerRasterPrivate.Data => { viewToDevice: Imager.Transformation _ imagerRaster.viewToDevice; viewClipBox: ImagerPixelMap.DeviceRectangle _ imagerRaster.viewClipBox; SELECT imagerRaster.device.class.type FROM $Bitmap => noColor _ TRUE; $GrayDisplay, $DitheredColorDisplay, $FullColorDisplay => noColor _ FALSE; ENDCASE => PixelsError[[$Unimplemented, "Unknown device type"]]; }; ENDCASE => PixelsError[[$Unimplemented, "Unknown Imager.Context.data type"]]; Process.Pause[ Process.SecondsToTicks[2] ]; -- pause for viewers to settle IF noColor THEN buf _ GetFromLF[vt, context] ELSE buf _ GetFromTerminal[vt, alpha, depth]; xfm _ ImagerBackdoor.GetT[context]; IF NOT xfm.integerTrans THEN SIGNAL PixelsError[[$Unimplemented, "Only translations allowed"]]; newBds _ ImagerBackdoor.GetBounds[context]; newBds.x _ newBds.x + xfm.tx; newBds.y _ newBds.y + xfm.ty; IF NOT noColor THEN { IF newBds.y < 29 THEN { newBds.y _ 0; newBds.h _ buf.height; }; -- ooh! yuk, horrible!! IF newBds.x < 5 THEN { newBds.x _ 0; newBds.w _ buf.width; }; -- junk!! bounds.x _ Real.FixI[ newBds.x ]; bounds.y _ MAX[ Real.FixI[ newBds.y ], 27 ]; -- 27 = viewer banner & menu, yuk!!! bounds.w _ MIN[buf.width - bounds.x, Real.FixI[newBds.w]]; bounds.h _ MIN[buf.height - bounds.y, Real.FixI[newBds.h]]; newBds _ [Real.Float[bounds.x], Real.Float[buf.height - (bounds.y + bounds.h)], -- right-side-up bounds Real.Float[bounds.w], Real.Float[bounds.h] ]; FOR i: NAT IN [0..buf.samplesPerPixel) DO buf.pixels[i].subMap.start _ [f: bounds.x, s: bounds.y]; buf.pixels[i].subMap.size _ [f: bounds.w, s: bounds.h]; ENDLOOP; }; buf.props _ Atom.PutPropOnList[ buf.props, $ImagerContext, context ]; -- store context buf.props _ Atom.PutPropOnList[ buf.props, $VirtualTerminal, vt ]; -- store terminal IF noColor THEN buf.props _ Atom.PutPropOnList[ buf.props, $RenderMode, $LF ]; RETURN [buf, newBds]; }; GetFromTerminal: PUBLIC PROC [vt: Terminal.Virtual, alpha, depth: BOOLEAN] RETURNS[PixelBuffer] ~ { fbA: Terminal.FrameBuffer _ vt.GetColorFrameBufferA[]; fbB: Terminal.FrameBuffer _ vt.GetColorFrameBufferB[]; map: NAT _ 0; buf: PixelBuffer; colorDepth: NAT _ 0; IF fbA = NIL THEN SIGNAL PixelsError[[$Mismatch, "No color display"]]; IF fbA # NIL THEN { map _ map + 1; IF fbA.bitsPerPixel > 8 THEN map _ map + 1; }; IF fbB # NIL THEN map _ map + 1; colorDepth _ map; IF alpha THEN map _ map + 1; IF depth THEN map _ map + 1; buf.pixels _ NEW[ SubMapSequence[map] ]; map _ 0; IF fbA.bitsPerPixel > 8 THEN { -- rg interleaved buffer, replicate sample map offset by one byte map _ map + 1; -- green map first ( low bytes ) buf.pixels[map].subMap.sampleMap _ SampleMapFromFrameBuffer[fbA]; buf.pixels[map].subMap.sampleMap.bitsPerSample _ 8; -- adjust to byte width samples buf.pixels[map].subMap.sampleMap.fSize _ buf.pixels[map].subMap.sampleMap.fSize * 2; buf.pixels[map-1] _ buf.pixels[map]; -- copy to get red map buf.pixels[map].subMap.sampleMap _ SampleMapOps.FromSubMap[ [ sampleMap: buf.pixels[map].subMap.sampleMap, start: [f: 1, s: 0] -- offset by one to get lower bytes ] ]; buf.pixels[map-1].df _ buf.pixels[map].df _ 2; buf.pixels[map-1].subMap.start _ buf.pixels[map].subMap.start _ [0, 0]; buf.pixels[map-1].subMap.size _ buf.pixels[map].subMap.size _ [f: fbA.width*2, s: fbA.height]; } ELSE { buf.pixels[map].subMap.sampleMap _ SampleMapFromFrameBuffer[fbA]; buf.pixels[map].df _ 1; buf.pixels[map].subMap.start _ [0, 0]; buf.pixels[map].subMap.size _ [f: fbA.width, s: fbA.height]; }; map _ map + 1; IF fbB # NIL THEN { buf.pixels[map].subMap.sampleMap _ SampleMapFromFrameBuffer[fbB]; buf.pixels[map].df _ 1; buf.pixels[map].subMap.start _ [0, 0]; buf.pixels[map].subMap.size _ [f: fbB.width, s: fbB.height]; map _ map + 1; }; IF alpha THEN { buf.pixels[colorDepth].subMap.sampleMap _ SampleMapOps.Create[ fSize: fbA.width, sSize: fbA.height, bitsPerSample: 8 ]; buf.pixels[colorDepth].df _ 1; buf.pixels[colorDepth].subMap.start _ [0, 0]; buf.pixels[colorDepth].subMap.size _ [f: fbA.width, s: fbA.height]; buf.props _ Atom.PutPropOnList[ buf.props, $Alpha, NEW[NAT _ colorDepth] ]; map _ map + 1; }; IF depth THEN { position: NAT _ IF alpha THEN colorDepth+1 ELSE colorDepth; buf.pixels[position].subMap.sampleMap _ SampleMapOps.Create[ fSize: fbA.width, sSize: fbA.height, bitsPerSample: 16 ]; buf.pixels[position].df _ 1; buf.pixels[position].subMap.start _ [0, 0]; buf.pixels[position].subMap.size _ [f: fbA.width, s: fbA.height]; buf.props _ Atom.PutPropOnList[ buf.props, $Depth, NEW[NAT _ position] ]; map _ map + 1; }; buf.samplesPerPixel _ map; buf.height _ fbA.height; buf.width _ fbA.width; buf.props _ Atom.PutPropOnList[ buf.props, $VirtualTerminal, vt ]; -- store terminal RETURN [buf]; }; GetFromLF: PROC [vt: Terminal.Virtual, context: Imager.Context] RETURNS[PixelBuffer] ~ { box: ImagerPixelMap.DeviceRectangle; fb: Terminal.FrameBuffer _ vt.GetBWFrameBuffer[]; buf: PixelBuffer; WITH context.data SELECT FROM quickView: QuickViewer.QuickView => { viewer: ViewerClasses.Viewer _ quickView.viewer; WHILE viewer.parent # NIL DO viewer _ viewer.parent ENDLOOP; box _ [ fMin: quickView.outer.wx + 2, sMin: fb.height - quickView.outer.wy - 2 - quickView.viewer.ch, fSize: quickView.viewer.cw, sSize: quickView.viewer.ch ]; }; imagerRaster: ImagerRasterPrivate.Data => { box _ imagerRaster.viewClipBox }; ENDCASE => PixelsError[[$Unimplemented, "Unknown Imager.Context.data type"]]; buf.pixels _ NEW[ SubMapSequence[1] ]; buf.pixels[0].subMap.sampleMap _ SampleMapFromFrameBuffer[fb]; buf.pixels[0].df _ 1; buf.pixels[0].subMap.start _ [ f: box.fMin, s: box.sMin ]; buf.pixels[0].subMap.size _ [f: box.fSize, s: box.sSize]; buf.samplesPerPixel _ 1; buf.height _ box.sSize; buf.width _ box.fSize; buf.props _ Atom.PutPropOnList[ buf.props, $VirtualTerminal, vt ]; -- store terminal RETURN [buf]; }; TerminalFromBuffer: PUBLIC PROC [buf: PixelBuffer] RETURNS[vt: Terminal.Virtual] ~ { RETURN[ NARROW[Atom.GetPropFromList[buf.props, $VirtualTerminal], Terminal.Virtual] ]; }; ImagerContextFromBuffer: PUBLIC PROC [buf: PixelBuffer, type: ATOM _ NIL] RETURNS[ctx: Imager.Context] ~ { ref: REF ANY _ Atom.GetPropFromList[buf.props, $ImagerContext]; IF ref # NIL THEN ctx _ NARROW[ref, Imager.Context] ELSE { kind: ATOM; ctx _ NIL; IF type # NIL THEN kind _ type ELSE SELECT buf.samplesPerPixel FROM 1, 2 => kind _ $Mapped; ENDCASE => kind _ $Color24; SELECT kind FROM $Gray => SIGNAL PixelsError[[$UnImplemented, "Grey display unsupported"]]; $Color24 => SIGNAL PixelsError[[$UnImplemented, "no 24-bit color"]]; ENDCASE => SIGNAL PixelsError[[$UnImplemented, "Unknown device type"]]; }; RETURN[ctx]; }; Fill: PUBLIC PROC [buf: PixelBuffer, pixel: SampleSet] ~ { DoIt: PROC[] ~ { Write[buf, [0, 0, buf.width, buf.height], pixel]; }; vt : Terminal.Virtual _ TerminalFromBuffer[buf]; IF pixel = NIL THEN { pixel _ GetSampleSet[buf.pixels.length]; FOR i: NAT IN [0..pixel.length) DO pixel[i] _ 0; ENDLOOP; }; IF vt # NIL THEN { n: NAT _ buf.samplesPerPixel - 1; Terminal.ModifyColorFrame[vt, DoIt, buf.pixels[n].subMap.start.f, buf.pixels[n].subMap.start.s, buf.pixels[n].subMap.start.f + buf.pixels[0].subMap.size.f, buf.pixels[n].subMap.start.s + buf.pixels[0].subMap.size.s ]; } ELSE DoIt[]; }; Transfer: PUBLIC PROC [dstBuf, srcBuf: PixelBuffer] ~ { numMaps: NAT _ MIN[ dstBuf.samplesPerPixel, srcBuf.samplesPerPixel+1 ]; DoIt: PROC[] ~ { FOR i: NAT IN [0 .. numMaps) DO heightDif: NAT _ MAX[ 0, INTEGER[dstBuf.pixels[i].subMap.size.s] - INTEGER[srcBuf.pixels[i].subMap.size.s] ]; IF dstBuf.pixels[i].df = 1 -- write only the first of a set of interleaved maps OR dstBuf.pixels[i].subMap.sampleMap.base.bit = 0 THEN SampleMapOps.Transfer[ dest: dstBuf.pixels[i].subMap.sampleMap, destStart: [ f: dstBuf.pixels[i].subMap.start.f * dstBuf.pixels[i].df, s: dstBuf.pixels[i].subMap.start.s + heightDif ], source: srcBuf.pixels[i].subMap ]; ENDLOOP; }; vt : Terminal.Virtual _ TerminalFromBuffer[dstBuf]; IF vt # NIL THEN { n: NAT _ dstBuf.samplesPerPixel - 1; Terminal.ModifyColorFrame[vt, DoIt, dstBuf.pixels[n].subMap.start.f, dstBuf.pixels[n].subMap.start.s, dstBuf.pixels[n].subMap.start.f + dstBuf.pixels[0].subMap.size.f, dstBuf.pixels[n].subMap.start.s + dstBuf.pixels[0].subMap.size.s ]; } ELSE DoIt[]; }; Copy: PUBLIC PROC [ destination, source: PixelBuffer, destArea, srcArea: Extent, op: ATOM _ $Write ] ~ { DoIt: PROC[] ~ { func: SampleMapOps.Function; SELECT op FROM $AND => func _ [ and, null]; $OR => func _ [ or, null]; $XOR => func _ [ xor, null]; ENDCASE => func _ [null, null]; IF destination.pixels = NIL OR source.pixels = NIL THEN SIGNAL PixelsError[[$Mismatch, "Buffer is nil"]]; SELECT op FROM $AND, $OR, $XOR, $Write => { srcArea.w _ MIN[ destArea.w, srcArea.w]; srcArea.h _ MIN[ destArea.h, srcArea.h]; FOR i: NAT IN [0..source.pixels.length) DO srcX, srcY, dstX, dstY: NAT; [srcX, srcY] _ XfmMapPlace[source.pixels[i], srcArea.x, srcArea.y + srcArea.h - 1]; [dstX, dstY] _ XfmMapPlace[destination.pixels[i], destArea.x, destArea.y + srcArea.h - 1]; IF destination.pixels[i].df = 1 -- copy only one from interleaved set OR destination.pixels[i].subMap.sampleMap.base.bit = 0 THEN SampleMapOps.Transfer[ dest: destination.pixels[i].subMap.sampleMap, destStart: [f: dstX, s: dstY], source: [ sampleMap: source.pixels[i].subMap.sampleMap, start: [f: srcX, s: srcY], size: [f: srcArea.w*source.pixels[i].df, s: srcArea.h] ], function: func ]; ENDLOOP; }; $WriteOver, $WriteUnder => { dstAlpha: NAT _ PositionFromProps[destination.props]; srcAlpha: NAT _ PositionFromProps[source.props]; srcSeg, dstSeg: REF SampleSetSequence _ NIL; FOR j: NAT IN [0 .. srcArea.h) DO srcSeg _ GetScanSeg[source, srcArea.x, j + srcArea.y, srcArea.w, srcSeg]; dstSeg _ GetScanSeg[destination, destArea.x, j + destArea.y, destArea.w, dstSeg]; FOR i: NAT IN [0 .. srcArea.w) DO samplesPerPixel: NAT _ MIN[srcSeg.length, dstSeg.length]; IF op = $WriteOver THEN { dstSeg[dstAlpha][i] _ SumLessProd[ dstSeg[dstAlpha][i], srcSeg[srcAlpha][i] ]; FOR k: NAT IN [0..samplesPerPixel) DO IF k # dstAlpha THEN dstSeg[k][i] _ ByteAvrgWgtd[ b1: dstSeg[k][i], b2: srcSeg[k][i], wgt: srcSeg[srcAlpha][i] ]; ENDLOOP; } ELSE IF op = $WriteUnder THEN { cvrge: NAT _ MIN[ srcSeg[srcAlpha][i], 255 - dstSeg[dstAlpha][i] ]; dstSeg[dstAlpha][i] _ dstSeg[dstAlpha][i] + cvrge; FOR k: NAT IN [0..samplesPerPixel) DO IF k # dstAlpha THEN dstSeg[k][i] _ dstSeg[k][i] + CARDINAL[cvrge * srcSeg[k][i]] / 256; ENDLOOP; }; ENDLOOP; PutScanSeg[destination, destArea.x, j + destArea.y, destArea.w, dstSeg]; ENDLOOP; }; ENDCASE => SIGNAL PixelsError[[$UnImplemented, "Unknown operation"]]; }; vt : Terminal.Virtual _ TerminalFromBuffer[destination]; IF vt # NIL THEN Terminal.ModifyColorFrame[vt, DoIt, destArea.x, destArea.y, destArea.x+destArea.w, destArea.y+destArea.h] ELSE DoIt[]; }; ShowOnImagerContext: PUBLIC PROC [context: Imager.Context, buf: PixelBuffer] ~ { SIGNAL PixelsError[[$Unimplemented, "Hasn't been written yet"]]; }; GetPixel: PUBLIC PROC [buf: PixelBuffer, x, y: NAT, pixel: SampleSet _ NIL] RETURNS[ SampleSet ] ~ { IF pixel = NIL OR pixel.maxLength < buf.samplesPerPixel THEN pixel _ GetSampleSet[buf.samplesPerPixel]; FOR i: NAT IN [0..buf.pixels.length) DO nx, ny: NAT; [nx, ny] _ XfmMapPlace[buf.pixels[i], x, y]; pixel[i] _ SampleMapOps.GetSample[ buf.pixels[i].subMap.sampleMap, [f: nx, s: ny] ] ENDLOOP; pixel.length _ buf.pixels.length; -- make sure length field is up to date RETURN [pixel]; }; PutPixel: PUBLIC PROC [ buf: PixelBuffer, x, y: NAT, pixel: SampleSet ] ~ { IF pixel = NIL OR pixel.length # buf.samplesPerPixel THEN SIGNAL PixelsError[[$Mismatch, "Pixel and buffer don't match"]]; FOR i: NAT IN [0..buf.pixels.length) DO nx, ny: NAT; [nx, ny] _ XfmMapPlace[buf.pixels[i], x, y]; SampleMapOps.PutSample[ buf.pixels[i].subMap.sampleMap, [f: nx, s: ny], pixel[i] ] ENDLOOP; }; GetScanSeg: PUBLIC PROC [ buf: PixelBuffer, x, y, length: NAT, pixels: REF SampleSetSequence _ NIL ] RETURNS[ REF SampleSetSequence ] ~ { IF pixels = NIL OR pixels.length # buf.samplesPerPixel THEN pixels _ NEW[ SampleSetSequence[buf.samplesPerPixel] ]; FOR i: NAT IN [0..buf.samplesPerPixel) DO nx, ny: NAT; IF pixels[i] = NIL OR pixels[i].length < length THEN pixels[i] _ GetSampleSet[length]; [nx, ny] _ XfmMapPlace[buf.pixels[i], x, y]; SampleMapOps.Get[ buffer: pixels[i], count: pixels[i].length, sampleMap: buf.pixels[i].subMap.sampleMap, f: nx, s: ny, df: buf.pixels[i].df ]; ENDLOOP; RETURN[pixels]; }; PutScanSeg: PUBLIC PROC [ buf: PixelBuffer, x, y, length: NAT, pixels: REF SampleSetSequence ] ~ { DoIt: PROC[] ~ { IF pixels = NIL OR pixels.length # buf.samplesPerPixel THEN SIGNAL PixelsError[[$Mismatch, "Pixel and buffer don't match"]]; FOR i: NAT IN [0..buf.samplesPerPixel) DO nx, ny: NAT; IF pixels[i] = NIL OR pixels[i].length < length THEN SIGNAL PixelsError[[$Mismatch, "Buffer has too few samples per pixel"]]; [nx, ny] _ XfmMapPlace[buf.pixels[i], x, y]; SampleMapOps.Put[ buffer: pixels[i], count: length, sampleMap: buf.pixels[i].subMap.sampleMap, f: nx, s: ny, df: buf.pixels[i].df ]; ENDLOOP; }; DoIt[]; }; dstPxl: SampleSet _ GetSampleSet[4]; srcPxl: SampleSet _ GetSampleSet[4]; -- for read-mod-write ops Write: PROC[ buf: PixelBuffer, area: Extent, pixel: SampleSet, func: SampleMapOps.Function _ [null, null] ] ~ { FOR i: NAT IN [0..buf.samplesPerPixel) DO x, y, w, h: NAT; [x, y] _ XfmMapPlace[ buf.pixels[i], area.x, area.y + area.h - 1 ]; -- upper left corner w _ MIN[ buf.pixels[i].subMap.sampleMap.fSize - x, area.w]; -- clip to map limits h _ MIN[ buf.pixels[i].subMap.sampleMap.sSize - y, area.h]; IF buf.pixels[i].df = 2 -- kludge for Dorado 24-bit color THEN IF buf.pixels[i].subMap.sampleMap.base.bit = 0 THEN { value: CARDINAL _ pixel[i] * 256 + pixel[i+1]; sampleMap: SampleMapOps.SampleMap _ NEW[SampleMapOps.SampleMapRep]; sampleMap^ _ buf.pixels[i].subMap.sampleMap^; sampleMap.bitsPerSample _ 16; sampleMap.fSize _ sampleMap.fSize / 2; x _ x / buf.pixels[i].df; -- correct for pixel size change SampleMapOps.Fill[ [sampleMap, [f: x, s: y], [f: w, s: h] ], value, func ]; } ELSE {} ELSE SampleMapOps.Fill[ -- case for continuous pixels dest: [ buf.pixels[i].subMap.sampleMap, [f: x, s: y], [f: w, s: h] ], value: pixel[i], function: func ]; ENDLOOP; }; WriteOver: PROC[ buf: PixelBuffer, area: Extent, pixel: SampleSet, alpha: NAT] ~ { scanSeg: REF SampleSetSequence _ NIL; FOR j: NAT IN [area.y..area.y+area.h) DO scanSeg _ GetScanSeg[buf, area.x, j, area.w, scanSeg]; FOR i: NAT IN [area.x..area.x+area.w) DO scanSeg[alpha][i] _ SumLessProd[ scanSeg[alpha][i], pixel[alpha] ]; FOR k: NAT IN [0..pixel.length) DO IF k # alpha THEN scanSeg[k][i] _ ByteAvrgWgtd[ b1: scanSeg[k][i], b2: pixel[k], wgt: pixel[alpha] ]; ENDLOOP; ENDLOOP; PutScanSeg[buf, area.x, j, area.w, scanSeg]; ENDLOOP; }; WriteUnder: PROC[ buf: PixelBuffer, area: Extent, pixel: SampleSet, alpha: NAT] ~ { scanSeg: REF SampleSetSequence _ NIL; FOR j: NAT IN [area.y..area.y+area.h) DO scanSeg _ GetScanSeg[buf, area.x, j, area.w, scanSeg]; FOR i: NAT IN [0..area.w) DO IF scanSeg[alpha][i] = 0 THEN { -- untouched pixel scanSeg[alpha][i] _ pixel[alpha]; FOR k: NAT IN [0..pixel.length) DO IF k # alpha THEN scanSeg[k][i] _ CARDINAL[pixel[alpha] * pixel[k]] / 255; -- alpha*new ENDLOOP; } ELSE IF scanSeg[alpha][i] < 255 THEN { -- used but not completely covered pixel cvrge: NAT _ MIN[ pixel[alpha], 255 - scanSeg[alpha][i] ]; -- < unused old alpha scanSeg[alpha][i] _ scanSeg[alpha][i] + cvrge; -- sum alphas (always < 256) FOR k: NAT IN [0..pixel.length) DO IF k # alpha THEN scanSeg[k][i] _ scanSeg[k][i] + CARDINAL[cvrge * pixel[k]] / 255; ENDLOOP; -- old + alpha*new }; ENDLOOP; PutScanSeg[buf, area.x, j, area.w, scanSeg]; ENDLOOP; }; PixelOp: PUBLIC PROC [ buf: PixelBuffer, area: Extent, pixel: SampleSet, op: ATOM _ $Write ] ~ { DoIt: PROC[] ~ { func: SampleMapOps.Function; SELECT op FROM $AND => func _ [ and, null]; $OR => func _ [ or, null]; $XOR => func _ [ xor, null]; ENDCASE => func _ [null, null]; IF pixel = NIL OR pixel.length < buf.samplesPerPixel THEN SIGNAL PixelsError[[$Mismatch, "Pixel and buffer don't match"]]; SELECT op FROM $AND, $OR, $XOR, $Write => Write[buf, area, pixel, func]; $WriteOver => { alpha: NAT _ PositionFromProps[buf.props]; SELECT pixel[alpha] FROM -- pixel[alpha] is coverage (alpha) 255 => Write[buf, area, pixel, func]; -- replacement if alpha saturated 0 => {}; -- no effect if alpha is zero ENDCASE => WriteOver[buf, area, pixel, alpha]; -- blend otherwise }; $WriteUnder => { alpha: NAT _ PositionFromProps[buf.props]; IF pixel[alpha] > 0 THEN WriteUnder[buf, area, pixel, alpha]; -- no-op if alpha zero }; ENDCASE => SIGNAL PixelsError[[$UnImplemented, "Unknown operation"]]; }; vt : Terminal.Virtual _ TerminalFromBuffer[buf]; IF vt # NIL THEN { xOffset: NAT _ buf.pixels[buf.samplesPerPixel-1].subMap.start.f; yOffset: NAT _ buf.pixels[buf.samplesPerPixel-1].subMap.start.s; Terminal.ModifyColorFrame[vt, DoIt, area.x + xOffset, area.y + yOffset, area.x+area.w + xOffset, area.y+area.h + yOffset]; } ELSE DoIt[]; }; GetValue: PUBLIC PROC [buf: PixelBuffer, x, y: NAT, map: NAT _ 0] RETURNS[ value: CARDINAL ] ~ { [x, y] _ XfmMapPlace[buf.pixels[map], x, y]; value _ SampleMapOps.GetSample[ buf.pixels[map].subMap.sampleMap, [f: x, s: y] ]; }; PutValue: PUBLIC PROC [ buf: PixelBuffer, x, y: NAT, value: CARDINAL, map: NAT _ 0 ] ~ { [x, y] _ XfmMapPlace[buf.pixels[map], x, y]; SampleMapOps.PutSample[ buf.pixels[map].subMap.sampleMap, [f: x, s: y] , value ]; }; ValueOp: PUBLIC PROC [ buf: PixelBuffer, area: Extent, value: CARDINAL, map: NAT _ 0, op: ATOM _ $Write ] ~ { func: SampleMapOps.Function; SELECT op FROM $AND => func _ [ and, null]; $OR => func _ [ or, null]; $XOR => func _ [ xor, null]; ENDCASE => func _ [null, null]; [area.x, area.y] _ XfmMapPlace[ buf.pixels[map], area.x, area.y + area.h - 1 ]; IF buf.pixels[map].df > 1 THEN area.x _ area.x / buf.pixels[map].df; SELECT op FROM $AND, $OR, $XOR, $Write => IF buf.pixels[map].df > 1 THEN { -- kludge for Dorado 24-bit color scanSeg: SampleSet _ GetSampleSet[area.w]; FOR x: NAT IN [0 .. area.w) DO scanSeg[x] _ value; ENDLOOP; FOR y: NAT IN [area.y.. area.y + area.h) DO SampleMapOps.Put[ buffer: scanSeg, count: area.w, sampleMap: buf.pixels[map].subMap.sampleMap, f: area.x, s: y, df: buf.pixels[map].df, function: func ]; ENDLOOP; } ELSE SampleMapOps.Fill[ dest: [buf.pixels[map].subMap.sampleMap, [f: area.x, s: area.y],[f: area.w, s: area.h]], value: value, function: func ]; ENDCASE => SIGNAL PixelsError[[$UnImplemented, "Operation not for single value"]]; }; END. ŽPixelsImpl.mesa Copyright c 1985 by Xerox Corporation. All rights reserved. Frank Crow, May 14, 1986 10:59:05 am PDT Fancy operations on two-dimensional arrays of pixels. ImagerDitheredDevice USING [ContextFromSampleMap], ImagerMappedDevice USING [ContextFromSampleMap], Type Definitions RECORD [ subMap: RECORD[sampleMap: SampleMap, start: CVEC _ [0,0], size: CVEC _ lastCVEC] ], df: NAT _ 1 ]; REF SampleMapRep: TYPE ~ RECORD [ It is unsafe for clients to alter these fields. sSize: NAT, -- number of scan lines fSize: NAT, -- number of samples per scan line bitsPerSample: [0..bitsPerWord], -- number of bits per sample base: PrincOps.BitAddress, -- starting bit address bitsPerLine: NAT, -- bits per scan line ref: REF -- for garbage collection ]; Utility Procedures Creation Operations Allocates bits and builds PixelBuffer record. Forces pixel buffer onto Imager context in those circumstances where it is possible NewBds needs to be the Imagers device bounds, not the client bounds!!! Makes pixel buffer out of terminal color display, if there is one PixelBuffer Operations Allows imager calls to act on your pixels Not yet implemented properly!! Convert sample maps to pixel map ImagerRaster.NewBitmapDevice[frame: ImagerPixelMap.PixelMap, pixelsPerInch: REAL _ 72] RETURNS [Device]; NewGrayDevice[terminal: Terminal.Virtual] RETURNS [Device]; NewColorMapDevice[terminal: Terminal.Virtual, bpp: NAT _ 8] RETURNS [Device]; NewColor24Device[terminal: Terminal.Virtual] RETURNS [Device]; ImagerRaster.Create[device: Device, pixelUnits: BOOL _ FALSE, fontCache: ImagerCache.Ref _ NIL, rastWeight: REAL _ 1.0, fontTuner: FontTuner _ NIL, class: REF Imager.ClassRep _ NIL ] RETURNS [Context]; mapList: LIST OF SampleMap _ NIL; $Dithered => ctx _ ImagerDitheredDevice.ContextFromSampleMap[ frame: buf.pixels[0], displayHeight: buf.height, pixelUnits: TRUE ]; $Mapped => ctx _ ImagerMappedDevice.ContextFromSampleMap[ frame: buf.pixels[0], displayHeight: buf.height, pixelUnits: TRUE ]; FOR i: NAT DECREASING IN [0..buf.pixels.length) DO mapList _ CONS[buf.pixels[i], mapList]; ENDLOOP; ImagerOps.ContextFromSampleMaps[mapList, NIL, kind]; -- unimplemented!! Clear pixels to specified pixel value Ensure that result fills the lower left corner of the destination area Puts pixels from displayMemory onto supplied context using Imager calls Pixel operations vt : Terminal.Virtual _ TerminalFromBuffer[buf]; IF pixels = NIL OR pixels.length # buf.samplesPerPixel THEN SIGNAL PixelsError[[$Mismatch, "Pixel and buffer don't match"]]; IF vt # NIL THEN Terminal.ModifyColorFrame[vt, DoIt, x, y, x+length, y+1] ELSE DoIt[]; sum alphas minus overlap estimate Visible value operations ΚŒ˜Ihead2šœ™šœ Οmœ1™˜>Ošœ˜šœ˜Ošœ ˜ Ošœ ˜ Ošœ˜—Ošœ=˜=Ošœ˜Ošœ˜Ošœ˜OšœEŸ˜VOšžœ˜ Ošœ˜——šœ™š œžœžœžœ˜TOšžœžœH˜VO˜—š  œžœžœžœžœžœ˜vO™IO™ OšœLžœžœ ™išœ;™;N™—šœM™MN™—šœ>™>N™—Ošœ  œžœžœžœžœžœ žœžœžœ ™ΙO˜Ošœžœžœ3˜?šžœžœ˜ Ošžœžœ˜&šžœ˜Ošœžœ˜ Ošœ žœžœ žœ™!Ošœžœ˜ šžœžœ˜Ošžœ ˜šžœžœž˜$Ošœ˜Ošžœ˜——šžœž˜Ošœ žœ;˜Lšœ=™=Ošœ™Ošœ™Ošœ ž™O™—šœ:™:Ošœ™Ošœ™Ošœ ž™O™—Ošœ žœ2˜EOšžœžœ6˜H—š žœžœž œžœžœ™3Ošœ žœ™)Ošžœ™—Ošœ)žœ Ÿ™GOšœ˜——Ošžœ˜ O˜—š œžœžœ)˜:O™%š œžœ˜Ošœ1˜1O˜—Ošœ0˜0šžœ žœžœ˜Ošœ(˜(Oš žœžœžœžœžœ˜;O˜—šžœžœ˜ šžœ˜Ošœžœ˜"šœ#˜#Ošœ˜Ošœ˜Ošœ;˜;Ošœ:˜:O˜—O˜—Ošžœ˜ —O˜—š œžœžœ"˜7Ošœ žœžœ6˜Hš œžœ˜šžœžœžœžœ˜ šœ žœžœ˜Ošž œ!˜+Ošœžœ!˜*Ošœ˜—šžœŸ5œžœ/˜ˆšžœ˜Ošœ(˜(šœ ˜ Ošœ9˜9Ošœ$žœ ˜.O˜—Ošœ ˜ Ošœ˜——Ošžœ˜—Ošœ˜—Ošœ3˜3šžœžœ˜ šžœ˜Ošœžœ˜%šœ#˜#Ošœ ˜ Ošœ ˜ OšœA˜AOšœ@˜@O˜—O˜—Ošžœ˜ —O˜—š œžœžœKžœ˜oš œžœ˜Ošœ˜šžœž˜Ošœ˜Ošœ˜Ošœ˜Ošžœ˜—šžœžœžœžœ˜3Ošžœžœ,˜7—šžœž˜šœ˜O™GOšœ žœ)žœ˜Tšžœžœžœžœ˜+Ošœžœ˜Ošœ\˜\Ošœf˜fšžœ!Ÿ)œžœ4˜„šžœ˜Ošœ-˜-Ošœ˜šœ ˜ Ošœ.˜.Ošœ˜Ošœ7˜7Ošœ˜—Ošœ˜Ošœ˜——Ošžœ˜—O˜—šœ˜Ošœ žœ)˜6Ošœ žœ$˜1Jšœžœžœ˜,šžœžœžœž˜!LšœI˜ILšœQ˜Qšžœžœžœž˜!Ošœžœžœ˜9šžœžœ˜OšœN˜Nš žœžœžœžœžœžœ˜;Ošœf˜fOšž˜—O˜—šžœžœžœ˜Ošœžœžœ3˜COšœ2˜2š žœžœžœžœžœžœ˜;Ošœžœ˜COšž˜—O˜—Ošžœ˜—LšœH˜HOšžœ˜—O˜—Ošžœžœ4˜E—O˜—Ošœ8˜8šžœžœ˜ Ošžœy˜}Ošžœ˜ —L˜—š œžœžœ0˜PO™GOšžœ:˜@Ošœ˜——™š Οbœžœžœžœžœžœ˜jšžœ žœžœ'˜8Ošžœ,˜0—šžœžœžœž˜'Ošœžœ˜ Ošœ,˜,OšœS˜SOšžœ˜—Ošœ$Ÿ'˜KOšžœ ˜Ošœ˜—š‘œžœžœžœ˜Kšžœ žœžœ$˜5Ošžœžœ;˜F—šžœžœžœž˜'Ošœžœ˜ Ošœ,˜,OšœR˜ROšžœ˜—L˜—š  œžœžœ#žœžœžœ žœžœ˜ššžœ žœžœ%˜7Lšžœ žœ,˜=—šžœžœžœž˜)Lšœžœ˜ Lšžœ žœžœžœ"˜VOšœ,˜,šœ˜Lšœ˜Lšœ˜Lšœ*˜*Lšœ˜Lšœ˜Lšœ˜Lšœ˜—Lšžœ˜—Lšžœ ˜Lšœ˜—š   œžœžœ#žœžœ˜lš œžœ˜šžœ žœžœ%˜7Lšžœžœ;˜F—šžœžœžœž˜)Lšœžœ˜ šžœ žœžœ˜0LšžœžœB˜M—Ošœ,˜,šœ˜Lšœ˜Lšœ˜Lšœ*˜*Lšœ˜Lšœ˜Lšœ˜Lšœ˜—Lšžœ˜—L˜—Ošœ0™0šžœ žœžœ%™7Lšžœžœ;™F—šžœžœ™ Ošžœ9™=Ošžœ™ —Lšœ˜Lšœ˜Ošœ%˜%Ošœ%Ÿ˜?—š œžœk˜všžœžœžœž˜)Ošœ˜OšœDŸ˜XOšœžœ5Ÿ˜ROšœžœ4˜;šžœŸ!˜Bšžœžœ-˜4šžœ˜Ošœžœ˜.Ošœ$žœ˜COšœ-˜-OšœG˜GOšœŸ"˜;OšœK˜KO˜—Ošžœ˜—šžœŸ˜