DIRECTORY Basics, ImagerColor USING [ColorOperator, PixelEncoding], ImagerColorPrivate USING [ApplyPixelEncoding, ColorOperatorClass, ColorOperatorClassRep, ColorOperatorCreateProc, ColorPoint, ColorSpace, ColorSpaceDimension, ColorTransform, DestroyColorPoint, GetPixelEncoding, MakeColorPoint, TranslateProc, TupleProc], ImagerColorTranslateWorks USING [ColorTransformAccelerator, ColorTransformAcceleratorRep, FastTranslateProc, FastTranslatePixelsProc], ImagerPixel USING [NewPixelMap, ObtainScratchPixels, PixelBuffer, PixelMap, PixelProc, PutPixels, ReleaseScratchPixels], ImagerPixelArray USING [GetPixels, MaxSampleValue, PixelArray], ImagerSample USING [PointerToSamples, RawSamples, SampleBuffer], Prop USING [PropList]; ImagerColorTranslateImpl: CEDAR MONITOR IMPORTS Basics, ImagerPixelArray, ImagerSample, ImagerPixel, ImagerColorPrivate EXPORTS ImagerColor, ImagerColorPrivate, ImagerColorTranslateWorks ~ BEGIN OPEN ImagerColorPrivate; SampleBuffer: TYPE ~ ImagerSample.SampleBuffer; ColorOperatorClassRep: PUBLIC TYPE ~ ImagerColorPrivate.ColorOperatorClassRep; PixelProc: TYPE ~ ImagerPixel.PixelProc; PixelArray: TYPE ~ ImagerPixelArray.PixelArray; PixelMap: TYPE ~ ImagerPixel.PixelMap; PixelBuffer: TYPE ~ ImagerPixel.PixelBuffer; ColorOperator: TYPE ~ ImagerColor.ColorOperator; FastTranslateProc: TYPE = ImagerColorTranslateWorks.FastTranslateProc; FastTranslatePixelsProc: TYPE = ImagerColorTranslateWorks.FastTranslatePixelsProc; ColorTransformAccelerator: TYPE = ImagerColorTranslateWorks.ColorTransformAccelerator; MakeAccelerator: PUBLIC PROC [slot: INT, name: ATOM, fastTranslate: FastTranslateProc ¬ NIL, fastTranslatePixels: FastTranslatePixelsProc ¬ NIL, propList: Prop.PropList ¬ NIL] RETURNS [ColorTransformAccelerator] = { RETURN [NEW[ImagerColorTranslateWorks.ColorTransformAcceleratorRep ¬ [slot: slot, name: name, fastTranslate: IF fastTranslate = NIL THEN GeneralTranslate ELSE fastTranslate, fastTranslatePixels: fastTranslatePixels, propList: propList]]] }; AcceleratorList: TYPE = LIST OF READONLY ColorTransformAccelerator; fallback: ColorTransformAccelerator = MakeAccelerator[ slot: LAST[INT], name: $Fallback, fastTranslatePixels: FallbackTranslatePixels ]; initialAccelerators: AcceleratorList = LIST[fallback]; accelerators: AcceleratorList ¬ initialAccelerators; -- Monitored RegisterAccelerator: PUBLIC ENTRY PROC [a: ColorTransformAccelerator] = { IF a # NIL THEN accelerators ¬ Insert[a, accelerators]; }; Insert: PROC [a: ColorTransformAccelerator, list: AcceleratorList] RETURNS [AcceleratorList] = { IF list = NIL THEN RETURN [LIST[a]] ELSE { oldSlot: INT = list.first.slot; SELECT a.slot FROM < oldSlot => RETURN [CONS[a, list]]; = oldSlot => RETURN [CONS[a, list.rest]]; ENDCASE => RETURN [CONS[list.first, Insert[a, list.rest]]]; }; }; Remove: PROC [list: AcceleratorList, slot: INT] RETURNS [new: AcceleratorList, a: ColorTransformAccelerator] = { IF list = NIL THEN RETURN [list, NIL]; IF list.first # NIL AND list.first.slot = slot THEN RETURN [list.rest, list.first]; [new, a] ¬ Remove[list.rest, slot]; new ¬ CONS[list.first, new]; }; UnregisterAccelerators: PUBLIC ENTRY PROC = { accelerators ¬ initialAccelerators }; RemoveAccelerator: PUBLIC ENTRY PROC [slot: INT] RETURNS [a: ColorTransformAccelerator] = { [accelerators, a] ¬ Remove[accelerators, slot]; }; GetAccelerators: PUBLIC ENTRY PROC RETURNS [AcceleratorList] = { RETURN [accelerators]; }; Translate: PUBLIC PROC [colorOperator: ColorOperator, transform: ColorTransform, pa: PixelArray] RETURNS [PixelMap] ~ { samplesPerPixelIn: NAT ~ pa.samplesPerPixel; maxIn: PixelProc ~ { RETURN [pa.MaxSampleValue[i]] }; maxOut: PixelProc ~ { RETURN [Fix[transform.rangeMax[i]+0.5]] }; FOR tail: AcceleratorList ¬ accelerators, tail.rest UNTIL tail = NIL DO a: ColorTransformAccelerator = tail.first; IF a.fastTranslate # NIL THEN { pm: PixelMap = a.fastTranslate[a, colorOperator, transform, pa]; IF pm # NIL THEN RETURN [pm] }; ENDLOOP; ERROR; }; TranslatePixels: PUBLIC PROC [colorOperator: ColorOperator, transform: ColorTransform, maxIn: PixelProc, translateAction: PROC [translate: TranslateProc]] ~ { FOR tail: AcceleratorList ¬ accelerators, tail.rest UNTIL tail = NIL DO a: ColorTransformAccelerator = tail.first; IF a.fastTranslatePixels # NIL AND a.fastTranslatePixels[a, colorOperator, transform, maxIn, translateAction].done THEN RETURN; ENDLOOP; ERROR; }; GeneralTranslate: PROC [self: ColorTransformAccelerator, colorOperator: ColorOperator, transform: ColorTransform, pa: PixelArray] RETURNS [PixelMap] = { maxIn: PixelProc ~ { RETURN [pa.MaxSampleValue[i]] }; pm: PixelMap ¬ NIL; translateAction: PROC [translate: TranslateProc] ~ { sSize: NAT = pa.sSize; fSize: NAT = pa.fSize; samplesPerPixelIn: NAT ~ pa.samplesPerPixel; pixelsIn: PixelBuffer ~ ImagerPixel.ObtainScratchPixels[samplesPerPixelIn, fSize]; samplesPerPixelOut: NAT ~ transform.rangeMax.dim; pixelsOut: PixelBuffer ~ ImagerPixel.ObtainScratchPixels[samplesPerPixelOut, fSize]; maxOut: PixelProc ~ { RETURN [Fix[transform.rangeMax[i]+0.5]] }; pm ¬ ImagerPixel.NewPixelMap[samplesPerPixelOut, [[0,0], [sSize, fSize]], maxOut]; FOR s: NAT IN [0..sSize) DO pa.GetPixels[s: s, f: 0, pixels: pixelsIn]; translate[pixelsIn: pixelsIn, pixelsOut: pixelsOut]; pm.PutPixels[initIndex: [s: s, f: 0], pixels: pixelsOut]; ENDLOOP; ImagerPixel.ReleaseScratchPixels[pixelsOut]; ImagerPixel.ReleaseScratchPixels[pixelsIn]; }; done: BOOL = self.fastTranslatePixels[self, colorOperator, transform, maxIn, translateAction]; IF done AND pm = NIL THEN ERROR; -- bug in fastTranslatePixels; it said it did something, but it didn't RETURN [pm]; }; Fix: PROC [real: REAL] RETURNS [INT] = INLINE { MCFix: PROC [real: REAL] RETURNS [INT] = TRUSTED MACHINE CODE { "(long int)*(float*)&" }; RETURN [MCFix[real]] }; FallbackTranslatePixels: PROC [self: ColorTransformAccelerator, colorOperator: ColorOperator, transform: ColorTransform, maxIn: PixelProc, translateAction: PROC [translate: TranslateProc]] RETURNS [done: BOOL ¬ TRUE] = { colorSpace: ColorSpace ~ transform.domain; dim: NAT ~ ColorSpaceDimension[colorSpace]; samplesPerPixelOut: NAT ~ transform.rangeMax.dim; vScratch: ColorPoint ¬ MakeColorPoint[dim]; dScratch: ColorPoint ¬ MakeColorPoint[samplesPerPixelOut]; pixelEncoding: ImagerColor.PixelEncoding ~ GetPixelEncoding[colorOperator]; SlowTranslate: TranslateProc ~ { v: ColorPoint ~ vScratch; d: ColorPoint ~ dScratch; class: ColorOperatorClass ~ colorOperator.class; FOR j: NAT IN [0..pixelsIn.length) DO pixelIn: TupleProc ~ { v: CARDINAL ¬ pixelsIn[i][j]; IF pixelEncoding = NIL THEN RETURN [v] ELSE { limit: CARDINAL = pixelEncoding[i].size-1; IF v > limit THEN v ¬ limit; RETURN [pixelEncoding[i][v]]; }; }; class.apply[colorOperator, pixelIn, colorSpace, v]; transform.proc[transform, v, d]; FOR i: NAT IN [0..samplesPerPixelOut) DO pixelsOut[i][j] ¬ Fix[d[i]+0.5]; ENDLOOP; ENDLOOP; }; translateAction[SlowTranslate]; dScratch ¬ DestroyColorPoint[dScratch]; vScratch ¬ DestroyColorPoint[vScratch]; }; InitOtherCases: PROC = { RegisterAccelerator[MakeAccelerator[slot: 1000, name: $OneDim, fastTranslatePixels: OneDimTranslate]]; RegisterAccelerator[MakeAccelerator[slot: 2000, name: $SmallTable, fastTranslatePixels: SmallTableTranslate]]; }; OneDimTranslate: PROC [self: ColorTransformAccelerator, colorOperator: ColorOperator, transform: ColorTransform, maxIn: PixelProc, translateAction: PROC [translate: TranslateProc]] RETURNS [BOOL] = { dimIn: NAT ~ colorOperator.samplesPerPixelIn; IF dimIn = 1 THEN { colorSpace: ColorSpace ~ transform.domain; dim: NAT ~ ColorSpaceDimension[colorSpace]; samplesPerPixelOut: NAT ~ transform.rangeMax.dim; pixelEncoding: ImagerColor.PixelEncoding ~ GetPixelEncoding[colorOperator]; maxIn0: CARDINAL ~ maxIn[0]; table: PixelBuffer ~ ImagerPixel.ObtainScratchPixels[samplesPerPixelOut, maxIn0+1]; TableTranslate: TranslateProc ~ TRUSTED { count: NAT ~ pixelsIn.length; FOR i: NAT IN [0..samplesPerPixelOut) DO samplesIn: SampleBuffer ~ pixelsIn[0]; samplesOut: SampleBuffer ~ pixelsOut[i]; samplesTable: SampleBuffer ~ table[i]; max: CARDINAL ~ samplesTable.length-1; pointerIn: LONG POINTER TO ImagerSample.RawSamples ¬ samplesIn.PointerToSamples[start: 0, count: count]; pointerOut: LONG POINTER TO ImagerSample.RawSamples ¬ samplesOut.PointerToSamples[start: 0, count: count]; pointerTable: LONG POINTER TO ImagerSample.RawSamples ¬ samplesTable.PointerToSamples[start: 0, count: max]; delta4: INT ~ SIZE[ImagerSample.RawSamples[4]]; delta1: INT ~ SIZE[ImagerSample.RawSamples[1]]; THROUGH [0..count/4) DO pointerOut[0] ¬ pointerTable[MIN[pointerIn[0], max]]; pointerOut[1] ¬ pointerTable[MIN[pointerIn[1], max]]; pointerOut[2] ¬ pointerTable[MIN[pointerIn[2], max]]; pointerOut[3] ¬ pointerTable[MIN[pointerIn[3], max]]; pointerIn ¬ pointerIn+delta4; pointerOut ¬ pointerOut+delta4; ENDLOOP; THROUGH [0..count MOD 4) DO pointerOut[0] ¬ pointerTable[MIN[pointerIn[0], max]]; pointerIn ¬ pointerIn+delta1; pointerOut ¬ pointerOut+delta1; ENDLOOP; ENDLOOP; }; d: ColorPoint ¬ MakeColorPoint[samplesPerPixelOut]; v: ColorPoint ¬ MakeColorPoint[dim]; class: ColorOperatorClass ~ colorOperator.class; FOR s0: CARDINAL IN [0..maxIn0] DO pixelIn: TupleProc ~ { check: [0..1) ~ i; RETURN [ApplyPixelEncoding[pixelEncoding, i, s0]]; }; class.apply[colorOperator, pixelIn, colorSpace, v]; transform.proc[transform, v, d]; FOR i: NAT IN [0..samplesPerPixelOut) DO table[i][s0] ¬ MAX[Fix[d[i]+0.5], 0]; ENDLOOP; ENDLOOP; translateAction[TableTranslate]; ImagerPixel.ReleaseScratchPixels[table]; v ¬ DestroyColorPoint[v]; d ¬ DestroyColorPoint[d]; RETURN[TRUE]; }; RETURN [FALSE] }; smallTableSize: NAT ¬ 2**13; SmallTableTranslate: PROC [self: ColorTransformAccelerator, colorOperator: ColorOperator, transform: ColorTransform, maxIn: PixelProc, translateAction: PROC [translate: TranslateProc]] RETURNS [BOOL] = { dimIn: NAT ~ colorOperator.samplesPerPixelIn; IF dimIn > 0 AND colorOperator.samplesPerPixelIn <= 4 THEN { colorSpace: ColorSpace ~ transform.domain; dim: NAT ~ ColorSpaceDimension[colorSpace]; samplesPerPixelOut: NAT ~ transform.rangeMax.dim; pixelEncoding: ImagerColor.PixelEncoding ~ GetPixelEncoding[colorOperator]; mask: ARRAY [0..4) OF CARDINAL ¬ ALL[0]; -- mask[i] = (2**packing[i])-1; mask[i] >= maxIn[i] packing: ARRAY [0..4) OF [0..32) ¬ ALL[0]; -- bits for each sample. tableSize: NAT ¬ 1; FOR i: NAT IN [0..dimIn) DO maxi: NAT ¬ maxIn[i]; bits: NAT ¬ 0; m: CARD ¬ 1; UNTIL m > maxi DO m ¬ 2*m; bits ¬ bits + 1 ENDLOOP; packing[i] ¬ bits; mask[i] ¬ m-1; IF tableSize > smallTableSize THEN { tableSize ¬ NAT.LAST; EXIT }; tableSize ¬ tableSize * m; ENDLOOP; IF tableSize <= smallTableSize THEN { InitMultiDimTable: PROC RETURNS [PixelBuffer] ~ { table: PixelBuffer ~ ImagerPixel.ObtainScratchPixels[samplesPerPixelOut, tableSize]; d: ColorPoint ¬ MakeColorPoint[samplesPerPixelOut]; v: ColorPoint ¬ MakeColorPoint[dim]; class: ColorOperatorClass ~ colorOperator.class; FOR packed: CARDINAL IN [0..tableSize) DO p: CARDINAL ¬ packed; s: ARRAY [0..4) OF CARDINAL; -- the unpacked samples. FOR i: NAT DECREASING IN [0..dimIn) DO s[i] ¬ Basics.BITAND[p, mask[i]]; p ¬ Basics.BITRSHIFT[p, packing[i]]; ENDLOOP; CHECKED { PixelIn: TupleProc ~ { RETURN [ApplyPixelEncoding[pixelEncoding, i, s[i]]] }; class.apply[colorOperator, PixelIn, colorSpace, v]; transform.proc[transform, v, d]; FOR i: NAT IN [0..samplesPerPixelOut) DO table[i][packed] ¬ MAX[Fix[d[i]+0.5], 0]; ENDLOOP; }; ENDLOOP; v ¬ DestroyColorPoint[v]; d ¬ DestroyColorPoint[d]; RETURN [table] }; PakNSav: UNSAFE PROC [buf: ImagerSample.SampleBuffer, p0, p1, p2, p3: POINTER TO ImagerSample.RawSamples] RETURNS [POINTER TO ImagerSample.RawSamples] ~ UNCHECKED { count: NAT ~ buf.length; packed: POINTER TO ImagerSample.RawSamples ~ buf.PointerToSamples[start: 0, count: count]; dimIn: NAT ~ colorOperator.samplesPerPixelIn; -- Get this as a local, for speed. b1: [0..32) ~ packing[1]; b2: [0..32) ~ packing[2]; b3: [0..32) ~ packing[3]; m0: CARDINAL ~ mask[0]; m1: CARDINAL ~ mask[1]; m2: CARDINAL ~ mask[2]; m3: CARDINAL ~ mask[3]; FOR j: NAT IN [0..count) DO s: CARDINAL ¬ Basics.BITAND[p0[0], m0]; p0 ¬ p0 + SIZE[WORD]; IF dimIn > 1 THEN { s ¬ Basics.BITLSHIFT[s, b1] + Basics.BITAND[p1[0], m1]; p1 ¬ p1 + SIZE[WORD]; s ¬ Basics.BITLSHIFT[s, b2] + Basics.BITAND[p2[0], m2]; p2 ¬ p2 + SIZE[WORD]; IF dimIn > 3 THEN { s ¬ Basics.BITLSHIFT[s, b3] + Basics.BITAND[p3[0], m3]; p3 ¬ p3 + SIZE[WORD]; }; }; packed[j] ¬ s; ENDLOOP; RETURN [packed]; }; table: PixelBuffer ~ InitMultiDimTable[]; MultiDimTableTranslate: TranslateProc ~ TRUSTED { count: NAT ~ pixelsIn.length; packedBuf: SampleBuffer ~ pixelsOut[samplesPerPixelOut-1]; -- Use the last output buffer as working space for the packed pixels. Be careful that this is the last buffer filled! check: [0..0] ~ packedBuf.length - count; packed: POINTER TO ImagerSample.RawSamples ~ PakNSav[packedBuf, PIn[0], PIn[1], PIn[2], PIn[3]]; PIn: UNSAFE PROC [i: INTEGER] RETURNS [POINTER TO ImagerSample.RawSamples] ~ UNCHECKED { IF i >= dimIn THEN i ¬ dimIn-1; IF i < 0 THEN RETURN [NIL]; RETURN [pixelsIn[i].PointerToSamples[start: 0, count: count]] }; FOR i: NAT IN [0..samplesPerPixelOut) DO samplesTable: SampleBuffer ~ table[i]; pointerTable: POINTER TO ImagerSample.RawSamples ¬ samplesTable.PointerToSamples[start: 0, count: tableSize]; pointerIn: POINTER TO ImagerSample.RawSamples ¬ packed; pointerOut: LONG POINTER TO ImagerSample.RawSamples ¬ pixelsOut[i].PointerToSamples[start: 0, count: count]; delta4: INT ~ SIZE[ImagerSample.RawSamples[4]]; delta1: INT ~ SIZE[ImagerSample.RawSamples[1]]; THROUGH [0..count/4) DO pointerOut[0] ¬ pointerTable[pointerIn[0]]; pointerOut[1] ¬ pointerTable[pointerIn[1]]; pointerOut[2] ¬ pointerTable[pointerIn[2]]; pointerOut[3] ¬ pointerTable[pointerIn[3]]; pointerIn ¬ pointerIn+delta4; pointerOut ¬ pointerOut+delta4; ENDLOOP; THROUGH [0..count MOD 4) DO pointerOut[0] ¬ pointerTable[pointerIn[0]]; pointerIn ¬ pointerIn+delta1; pointerOut ¬ pointerOut+delta1; ENDLOOP; ENDLOOP; }; translateAction[MultiDimTableTranslate]; ImagerPixel.ReleaseScratchPixels[table]; RETURN[TRUE]; }; }; RETURN [FALSE] }; InitOtherCases[]; END. InterpolationTable: TYPE ~ REF InterpolationTableRep; InterpolationTableRep: TYPE ~ RECORD [ encode: ARRAY [0..3) OF REF EncoderArray, gamutSamples: ARRAY [0..16) OF ARRAY [0..16) OF ARRAY [0..16) OF ColorCube ]; encodedUnit: CARD16 ~ 2**8; encodedMax: CARD16 ~ 2**12-1; EncoderArray: TYPE ~ RECORD [ min: REAL, max: REAL, s: PACKED SEQUENCE size: NAT OF [0..encodedMax] ]; ColorCube: TYPE ~ REF ColorCubeRep; ColorCubeRep: TYPE ~ RECORD [ base: ColorPoint, matrix: ARRAY [0..6) OF REF MatrixRep ]; MatrixRep: TYPE ~ RECORD [ SEQUENCE dim: NAT OF REF ARRAY [0..3) OF REAL ]; MakeInterpolationTable: PROC [colorOperator: ColorOperator, transform: ColorTransform, maxIn: PixelProc] RETURNS [InterpolationTable] ~ { colorSpace: ColorSpace ~ transform.domain; dim: NAT ~ ColorSpaceDimension[colorSpace]; samplesPerPixelOut: NAT ~ transform.rangeMax.dim; pixelEncoding: ImagerColor.PixelEncoding ~ GetPixelEncoding[colorOperator]; result: InterpolationTable ¬ NEW[InterpolationTableRep]; vScratch: ColorPoint ¬ MakeColorPoint[dim]; CornerIndex: TYPE ~ [0..8); d: ARRAY CornerIndex OF ColorPoint; BuildMatrix: PROC [ix1, ix2: CornerIndex] RETURNS [REF MatrixRep] ~ { ERROR; }; FOR i: NAT IN [0..8) DO d[i] ¬ MakeColorPoint[samplesPerPixelOut]; ENDLOOP; FOR i: NAT IN [0..colorOperator.samplesPerPixelIn) DO tableMin: REAL ¬ Real.LargestNumber; tableMax: REAL ¬ -Real.LargestNumber; sMax: NAT ~ maxIn[i]; encode: REF EncoderArray ¬ NEW[EncoderArray[sMax+1]]; IF pixelEncoding = NIL THEN { tableMin ¬ 0; tableMax ¬ sMax; } ELSE { FOR j: NAT IN [0..sMax] DO s: REAL ~ ApplyPixelEncoding[pixelEncoding, i, j]; IF s < tableMin THEN tableMin ¬ s; IF s > tableMax THEN tableMax ¬ s; ENDLOOP; }; IF tableMin < tableMax THEN { FOR j: NAT IN [0..sMax] DO s: REAL ~ ApplyPixelEncoding[pixelEncoding, i, j]; encode[j] ¬ RealInline.MCRound[((s-tableMin)/(tableMax-tableMin)) * encodedMax]; ENDLOOP; }; encode.min ¬ tableMin; encode.max ¬ tableMax; result.encode[i] ¬ encode; ENDLOOP; FOR xu: [0..16) IN [0..16) DO FOR yu: [0..16) IN [0..16) DO FOR zu: [0..16) IN [0..16) DO cc: ColorCube ~ NEW[ColorCubeRep]; FOR xf: [0..1] IN [0..1] DO FOR yf: [0..1] IN [0..1] DO FOR zf: [0..1] IN [0..1] DO pt: [0..8) ~ xf*4 + yf*2 + zf; v: ColorPoint ~ vScratch; pixelIn: TupleProc ~ { s: [0..encodedMax] ~ SELECT i FROM 0 => xu*encodedUnit+xf*(encodedUnit-1), 1 => yu*encodedUnit+yf*(encodedUnit-1), ENDCASE => zu*encodedUnit+zf*(encodedUnit-1); e: REF EncoderArray ~ result.encode[i]; RETURN [(REAL[s]/REAL[encodedMax])*(e.max-e.min) + e.min] }; class: ColorOperatorClass ~ colorOperator.class; class.apply[colorOperator, pixelIn, colorSpace, v]; transform.proc[transform, v, d[pt]]; ENDLOOP; ENDLOOP; ENDLOOP; cc.matrix[0] ¬ BuildMatrix[4,6]; cc.matrix[1] ¬ BuildMatrix[4,5]; cc.matrix[2] ¬ BuildMatrix[1,5]; cc.matrix[3] ¬ BuildMatrix[2,6]; cc.matrix[4] ¬ BuildMatrix[2,3]; cc.matrix[5] ¬ BuildMatrix[1,3]; cc.base ¬ d[0]; result.gamutSamples[xu][yu][zu] ¬ cc; d[0] ¬ MakeColorPoint[samplesPerPixelOut]; ENDLOOP; ENDLOOP; ENDLOOP; RETURN [result] }; ApplyInterpolation: PROC [interpolationTable: InterpolationTable, colorPoint: ColorPoint] RETURNS [result: ColorPoint] ~ { x: [0..encodedMax] ~ interpolationTable.encode[0][RealInline.MCRound[colorPoint[0]]]; y: [0..encodedMax] ~ interpolationTable.encode[1][RealInline.MCRound[colorPoint[1]]]; z: [0..encodedMax] ~ interpolationTable.encode[2][RealInline.MCRound[colorPoint[2]]]; colorCube: ColorCube ~ interpolationTable.gamutSamples[x/encodedUnit][y/encodedUnit][z/encodedUnit]; xr: [0..encodedUnit) ~ x MOD encodedUnit; yr: [0..encodedUnit) ~ y MOD encodedUnit; zr: [0..encodedUnit) ~ z MOD encodedUnit; index: [0..6) ~ IF xr > yr THEN ( IF xr > zr THEN (IF yr > zr THEN 0 ELSE 1) ELSE 2 ) ELSE ( IF xr > zr THEN 3 ELSE (IF yr > zr THEN 4 ELSE 5) ); matrix: REF MatrixRep ~ colorCube.matrix[index]; result ¬ MakeColorPoint[colorCube.base.dim]; FOR j: NAT IN [0..result.dim) DO v: REF ARRAY [0..3) OF REAL ~ matrix[j]; result[j] ¬ colorCube.base[j] + xr*v[0] + yr*v[1] + zr*v[2]; ENDLOOP; };  ImagerColorTranslateImpl.mesa Copyright Σ 1991, 1992, 1994 by Xerox Corporation. All rights reserved. Stone, June 25, 1985 5:15:17 pm PDT Michael Plass, February 23, 1994 10:52 am PST Copied Types Registration Dispatch Fallback cases This strange code conspires with c2c and the c compiler to make it possible to do the float-to-int conversion without a procedure call. It's not that the procedure call itself is that costly, but with the SPARC calling convention, it forces all of the floating point registers to memory. PROC [i: NAT] RETURNS [REAL]; Other cases This branch handles the case of a small total number of combinations - don't interpolate, just use a multi-dimensional table lookup. This loop computes tableSize and the mask and packing arrays. prevent overflow in tableSize computation Packs up the input samples into table indices. Unused: Body The parallipiped is split into 6 tets by subdividing it along the planes x=y, x=z, and y=z. Tetrahedron 0: x > y, x > z, y > z. Vertices are points [0,4,6,7]. Tetrahedron 1: x > y, x > z, y <= z. Vertices are points [0,4,5,7]. Tetrahedron 2: x > y, x <= z, y <= z. Vertices are points [0,1,5,7]. Tetrahedron 3: x <= y, x > z, y > z. Vertices are points [0,2,6,7]. Tetrahedron 4: x <= y, x <= z, y > z. Vertices are points [0,2,3,7]. Tetrahedron 5: x <= y, x <= z, y <= z. Vertices are points [0,1,3,7]. A cell can be subdivided into 5 tets, not 6: the beauty of the 6 tet subdivision is that the cutting planes are so simple that determining which tet a point is inside is very quick. ΚŸ•NewlineDelimiter –(cedarcode) style™code™Kšœ Οeœ<™GK™#K™-K™—šΟk ˜ K˜Kšœ žœ ˜1Kšœžœζ˜ώKšœžœg˜†Kšœ žœg˜xKšœžœ)˜?Kšœ žœ.˜@Kšœžœ ˜—K˜KšΟnœžœž˜'KšžœH˜OKšžœ;˜Bšœžœžœ˜ K˜—head™ Kšœžœ˜/Kšœžœžœ,˜NKšœ žœ˜(Kšœ žœ˜/Kšœ žœ˜&Kšœ žœ˜,Kšœžœ˜0K˜Kšœžœ/˜FKšœžœ5˜Ršœžœ7˜VK˜——™ šŸœžœžœžœžœ%žœ1žœžœžœ ˜ΧKš žœžœbžœžœžœžœO˜νKšœ˜K˜—š œžœžœžœžœ˜CK˜—˜6Kšœžœžœ@˜NKšœ˜K˜—šœ'žœ ˜6K˜—šœ5Οc ˜AK˜—šŸœžœžœžœ#˜IKšžœžœžœ(˜7Kšœ˜K˜—šŸœžœ7žœ˜`š žœžœžœžœžœžœ˜*Kšœ žœ˜šžœž˜Kšœ žœžœ ˜$Kšœ žœžœ˜)Kšžœžœžœ$˜;—Kšœ˜—Kšœ˜K˜—šŸœžœžœžœ9˜pKš žœžœžœžœžœ˜&Kš žœžœžœžœžœ˜SK˜#Kšœžœ˜Kšœ˜K˜—KšŸœžœžœžœ*˜Sš Ÿœžœžœžœžœžœ#˜[K˜/K˜—š Ÿœžœžœžœžœ˜@Kšžœ˜K˜K˜——™šŸ œžœžœKžœ˜wKšœžœ˜,Kšœžœ˜5Kšœžœ$˜@šžœ1žœžœž˜GK˜*šžœžœžœ˜K˜@Kšžœžœžœžœ˜K˜—Kšžœ˜—Kšžœ˜K˜K˜—šŸœžœžœ^žœ ˜žšžœ1žœžœž˜GK˜*šžœž˜KšžœP˜SKšžœžœ˜ —Kšžœ˜—Kšžœ˜Kšœ˜——™šŸœžœlžœ˜˜Kšœžœ˜5Kšœžœ˜šœžœ˜4Kšœžœ ˜Kšœžœ ˜Kšœžœ˜,K˜RKšœžœ˜1K˜TKšœžœ$˜@K˜Ršžœžœžœ ž˜K˜+Kšœ4˜4Kšœ9˜9Kšžœ˜—Kšœ,˜,Kšœ+˜+K˜—KšœžœT˜^Kš žœžœžœžœžœ F˜gKšžœ˜ Kšœ˜K˜—š Ÿœžœžœžœžœžžœ˜/K™ šŸŸœžœžœžœžœžœžœžœ˜?J˜Kšœ˜—Kšžœ˜K˜K˜—š Ÿœžœžœžœžœžœ˜άKšœ*˜*Kšœžœ#˜+Kšœžœ˜1Kšœ+˜+Kšœ:˜:K˜KšŸ œ˜!Kšœ˜Kšœ˜Kšœ0˜0šžœžœžœž˜%šœ˜Kšžœžœžœžœ™Kšœžœ˜šžœž˜Kšžœžœ˜šžœ˜Kšœžœ˜*Kšžœ žœ ˜Kšžœ˜Kšœ˜——Kšœ˜—K˜3Kšœ ˜ šžœžœžœž˜(K˜ Kšžœ˜—Kšžœ˜—Kšœ˜—Kšœ˜Kšœ'˜'Kšœ'˜'Kšœ˜——™ šŸœžœ˜K˜fK˜nKšœ˜K˜—š Ÿœžœžœžœžœ˜ΗKšœžœ#˜-šžœ žœ˜Kšœ*˜*Kšœžœ#˜+Kšœžœ˜1K˜KKšœžœ ˜KšœS˜SšŸœžœ˜)Kšœžœ˜šžœžœžœž˜(Kšœ&˜&Kšœ(˜(K˜&Kšœžœ˜&Kšœ žœžœžœN˜hKšœ žœžœžœO˜jKšœžœžœžœO˜lKšœžœžœ˜/Kšœžœžœ˜/šžœž˜Kšœžœ˜5Kšœžœ˜5Kšœžœ˜5Kšœžœ˜5Kšœ˜Kšœ˜Kšžœ˜—šžœ žœž˜Kšœžœ˜5Kšœ˜Kšœ˜Kšžœ˜—Kšžœ˜—K˜—Kšœ3˜3Kšœ$˜$Kšœ0˜0šžœžœžœ ž˜"šœ˜Kšœ˜Kšžœ,˜2Kšœ˜—Kšœ3˜3Kšœ ˜ šžœžœžœž˜(Kšœžœ˜%Kšžœ˜—Kšžœ˜—Kšœ ˜ Kšœ(˜(Kšœ˜Kšœ˜KšΠbkΟb‘’œ˜ Kšœ˜—Kšžœžœ˜K˜K˜—Kšœžœ ˜š Ÿœžœžœžœžœ˜ΛKšœžœ#˜-šžœ žœ&žœ˜