1 Unit JdColor;
2 
3 { This file contains output colorspace conversion routines. }
4 
5 { Original: jdcolor.c ; Copyright (C) 1991-1997, Thomas G. Lane. }
6 
7 interface
8 
9 {$I jconfig.inc}
10 
11 uses
12   jmorecfg,
13   jinclude,
14   jutils,
15   jdeferr,
16   jerror,
17   jpeglib;
18 
19 { Module initialization routine for output colorspace conversion. }
20 
21 {GLOBAL}
22 procedure jinit_color_deconverter (cinfo : j_decompress_ptr);
23 
24 implementation
25 
26 { Private subobject }
27 type
28   int_Color_Table = array[0..MAXJSAMPLE+1-1] of int;
29   int_table_ptr = ^int_Color_Table;
30   INT32_Color_Table = array[0..MAXJSAMPLE+1-1] of INT32;
31   INT32_table_ptr = ^INT32_Color_Table;
32 type
33   my_cconvert_ptr = ^my_color_deconverter;
34   my_color_deconverter = record
35     pub : jpeg_color_deconverter; { public fields }
36 
37     { Private state for YCC^.RGB conversion }
38     Cr_r_tab : int_table_ptr;   { => table for Cr to R conversion }
39     Cb_b_tab : int_table_ptr;   { => table for Cb to B conversion }
40     Cr_g_tab : INT32_table_ptr; { => table for Cr to G conversion }
41     Cb_g_tab : INT32_table_ptr; { => table for Cb to G conversion }
42   end;
43 
44 
45 
46 
47 {*************** YCbCr ^. RGB conversion: most common case *************}
48 
49 { YCbCr is defined per CCIR 601-1, except that Cb and Cr are
50   normalized to the range 0..MAXJSAMPLE rather than -0.5 .. 0.5.
51   The conversion equations to be implemented are therefore
52         R = Y                + 1.40200 * Cr
53         G = Y - 0.34414 * Cb - 0.71414 * Cr
54         B = Y + 1.77200 * Cb
55   where Cb and Cr represent the incoming values less CENTERJSAMPLE.
56   (These numbers are derived from TIFF 6.0 section 21, dated 3-June-92.)
57 
58   To avoid floating-point arithmetic, we represent the fractional constants
59   as integers scaled up by 2^16 (about 4 digits precision); we have to divide
60   the products by 2^16, with appropriate rounding, to get the correct answer.
61   Notice that Y, being an integral input, does not contribute any fraction
62   so it need not participate in the rounding.
63 
64   For even more speed, we avoid doing any multiplications in the inner loop
65   by precalculating the constants times Cb and Cr for all possible values.
66   For 8-bit JSAMPLEs this is very reasonable (only 256 entries per table);
67   for 12-bit samples it is still acceptable.  It's not very reasonable for
68   16-bit samples, but if you want lossless storage you shouldn't be changing
69   colorspace anyway.
70   The Cr=>R and Cb=>B values can be rounded to integers in advance; the
71   values for the G calculation are left scaled up, since we must add them
72   together before rounding. }
73 
74 const
75   SCALEBITS = 16;      { speediest right-shift on some machines }
76   ONE_HALF  = (INT32(1) shl (SCALEBITS-1));
77 
78 
79 { Initialize tables for YCC->RGB colorspace conversion. }
80 
81 {LOCAL}
82 procedure build_ycc_rgb_table (cinfo : j_decompress_ptr);
83 const
84   FIX_1_40200 = INT32(Round( 1.40200  * (1 shl SCALEBITS)));
85   FIX_1_77200 = INT32(Round( 1.77200  * (1 shl SCALEBITS)));
86   FIX_0_71414 = INT32(Round( 0.71414  * (1 shl SCALEBITS)));
87   FIX_0_34414 = INT32(Round( 0.34414  * (1 shl SCALEBITS)));
88 
89 var
90   cconvert : my_cconvert_ptr;
91   i : int;
92   x : INT32;
93 var
94   shift_temp : INT32;
95 begin
96   cconvert := my_cconvert_ptr (cinfo^.cconvert);
97 
98 
99   cconvert^.Cr_r_tab := int_table_ptr(
100     cinfo^.mem^.alloc_small ( j_common_ptr(cinfo), JPOOL_IMAGE,
101                                 (MAXJSAMPLE+1) * SIZEOF(int)) );
102   cconvert^.Cb_b_tab := int_table_ptr (
103     cinfo^.mem^.alloc_small ( j_common_ptr(cinfo), JPOOL_IMAGE,
104                                 (MAXJSAMPLE+1) * SIZEOF(int)) );
105   cconvert^.Cr_g_tab := INT32_table_ptr (
106     cinfo^.mem^.alloc_small ( j_common_ptr(cinfo), JPOOL_IMAGE,
107                                 (MAXJSAMPLE+1) * SIZEOF(INT32)) );
108   cconvert^.Cb_g_tab := INT32_table_ptr (
109     cinfo^.mem^.alloc_small ( j_common_ptr(cinfo), JPOOL_IMAGE,
110                                 (MAXJSAMPLE+1) * SIZEOF(INT32)) );
111 
112 
113   x := -CENTERJSAMPLE;
114   for i := 0 to MAXJSAMPLE do
115   begin
116     { i is the actual input pixel value, in the range 0..MAXJSAMPLE }
117     { The Cb or Cr value we are thinking of is x := i - CENTERJSAMPLE }
118     { Cr=>R value is nearest int to 1.40200 * x }
119 
120     shift_temp := FIX_1_40200  * x + ONE_HALF;
121     if shift_temp < 0 then  { SHIFT arithmetic RIGHT }
122       cconvert^.Cr_r_tab^[i] := int((shift_temp shr SCALEBITS)
123                              or ( (not INT32(0)) shl (32-SCALEBITS)))
124     else
125       cconvert^.Cr_r_tab^[i] := int(shift_temp shr SCALEBITS);
126 
127     { Cb=>B value is nearest int to 1.77200 * x }
128     shift_temp := FIX_1_77200  * x + ONE_HALF;
129     if shift_temp < 0 then   { SHIFT arithmetic RIGHT }
130       cconvert^.Cb_b_tab^[i] := int((shift_temp shr SCALEBITS)
131                                 or ( (not INT32(0)) shl (32-SCALEBITS)))
132     else
133       cconvert^.Cb_b_tab^[i] := int(shift_temp shr SCALEBITS);
134 
135     { Cr=>G value is scaled-up -0.71414 * x }
136     cconvert^.Cr_g_tab^[i] := (- FIX_0_71414 ) * x;
137     { Cb=>G value is scaled-up -0.34414 * x }
138     { We also add in ONE_HALF so that need not do it in inner loop }
139     cconvert^.Cb_g_tab^[i] := (- FIX_0_34414 ) * x + ONE_HALF;
140     Inc(x);
141   end;
142 end;
143 
144 
145 { Convert some rows of samples to the output colorspace.
146 
147   Note that we change from noninterleaved, one-plane-per-component format
148   to interleaved-pixel format.  The output buffer is therefore three times
149   as wide as the input buffer.
150   A starting row offset is provided only for the input buffer.  The caller
151   can easily adjust the passed output_buf value to accommodate any row
152   offset required on that side. }
153 
154 {METHODDEF}
155 procedure ycc_rgb_convert (cinfo : j_decompress_ptr;
156                            input_buf : JSAMPIMAGE;
157                            input_row : JDIMENSION;
158                            output_buf : JSAMPARRAY;
159                            num_rows : int); far;
160 var
161   cconvert : my_cconvert_ptr;
162   {register} y, cb, cr : int;
163   {register} outptr : JSAMPROW;
164   {register} inptr0, inptr1, inptr2 : JSAMPROW;
165   {register} col : JDIMENSION;
166   num_cols : JDIMENSION;
167   { copy these pointers into registers if possible }
168   {register} range_limit : range_limit_table_ptr;
169   {register} Crrtab : int_table_ptr;
170   {register} Cbbtab : int_table_ptr;
171   {register} Crgtab : INT32_table_ptr;
172   {register} Cbgtab : INT32_table_ptr;
173 var
174   shift_temp : INT32;
175 begin
176   cconvert := my_cconvert_ptr (cinfo^.cconvert);
177   num_cols := cinfo^.output_width;
178   range_limit := cinfo^.sample_range_limit;
179   Crrtab := cconvert^.Cr_r_tab;
180   Cbbtab := cconvert^.Cb_b_tab;
181   Crgtab := cconvert^.Cr_g_tab;
182   Cbgtab := cconvert^.Cb_g_tab;
183 
184   while (num_rows > 0) do
185   begin
186     Dec(num_rows);
187     inptr0 := input_buf^[0]^[input_row];
188     inptr1 := input_buf^[1]^[input_row];
189     inptr2 := input_buf^[2]^[input_row];
190     Inc(input_row);
191     outptr := output_buf^[0];
192     Inc(JSAMPROW_PTR(output_buf));
193     for col := 0 to pred(num_cols) do
194     begin
195       y  := GETJSAMPLE(inptr0^[col]);
196       cb := GETJSAMPLE(inptr1^[col]);
197       cr := GETJSAMPLE(inptr2^[col]);
198       { Range-limiting is essential due to noise introduced by DCT losses. }
199       outptr^[RGB_RED] :=   range_limit^[y + Crrtab^[cr]];
200       shift_temp := Cbgtab^[cb] + Crgtab^[cr];
201       if shift_temp < 0 then   { SHIFT arithmetic RIGHT }
202         outptr^[RGB_GREEN] := range_limit^[y + int((shift_temp shr SCALEBITS)
203                               or ( (not INT32(0)) shl (32-SCALEBITS)))]
204       else
205         outptr^[RGB_GREEN] := range_limit^[y + int(shift_temp shr SCALEBITS)];
206 
207       outptr^[RGB_BLUE] :=  range_limit^[y + Cbbtab^[cb]];
208       Inc(JSAMPLE_PTR(outptr), RGB_PIXELSIZE);
209     end;
210   end;
211 end;
212 
213 
214 {*************** Cases other than YCbCr -> RGB *************}
215 
216 
217 { Color conversion for no colorspace change: just copy the data,
218   converting from separate-planes to interleaved representation. }
219 
220 {METHODDEF}
221 procedure null_convert (cinfo : j_decompress_ptr;
222                         input_buf : JSAMPIMAGE;
223                         input_row : JDIMENSION;
224                         output_buf : JSAMPARRAY;
225                         num_rows : int); far;
226 var
227   {register} inptr,
228              outptr : JSAMPLE_PTR;
229   {register} count : JDIMENSION;
230   {register} num_components : int;
231   num_cols : JDIMENSION;
232   ci : int;
233 begin
234   num_components := cinfo^.num_components;
235   num_cols := cinfo^.output_width;
236 
237   while (num_rows > 0) do
238   begin
239     Dec(num_rows);
240     for ci := 0 to pred(num_components) do
241     begin
242       inptr := JSAMPLE_PTR(input_buf^[ci]^[input_row]);
243       outptr := JSAMPLE_PTR(@(output_buf^[0]^[ci]));
244 
245       for count := pred(num_cols) downto 0 do
246       begin
247         outptr^ := inptr^;      { needn't bother with GETJSAMPLE() here }
248         Inc(inptr);
249         Inc(outptr, num_components);
250       end;
251     end;
252     Inc(input_row);
253     Inc(JSAMPROW_PTR(output_buf));
254   end;
255 end;
256 
257 
258 { Color conversion for grayscale: just copy the data.
259   This also works for YCbCr -> grayscale conversion, in which
260   we just copy the Y (luminance) component and ignore chrominance. }
261 
262 {METHODDEF}
263 procedure grayscale_convert (cinfo : j_decompress_ptr;
264                              input_buf : JSAMPIMAGE;
265                              input_row : JDIMENSION;
266                              output_buf : JSAMPARRAY;
267                              num_rows : int); far;
268 begin
269   jcopy_sample_rows(input_buf^[0], int(input_row), output_buf, 0,
270                     num_rows, cinfo^.output_width);
271 end;
272 
273 { Convert grayscale to RGB: just duplicate the graylevel three times.
274   This is provided to support applications that don't want to cope
275   with grayscale as a separate case. }
276 
277 {METHODDEF}
278 procedure gray_rgb_convert (cinfo : j_decompress_ptr;
279                             input_buf : JSAMPIMAGE;
280                             input_row : JDIMENSION;
281                             output_buf : JSAMPARRAY;
282                             num_rows : int); far;
283 var
284   {register} inptr, outptr : JSAMPLE_PTR;
285   {register} col : JDIMENSION;
286   num_cols : JDIMENSION;
287 begin
288   num_cols := cinfo^.output_width;
289   while (num_rows > 0) do
290   begin
291     inptr := JSAMPLE_PTR(input_buf^[0]^[input_row]);
292     Inc(input_row);
293     outptr := JSAMPLE_PTR(@output_buf^[0]);
294     Inc(JSAMPROW_PTR(output_buf));
295     for col := 0 to pred(num_cols) do
296     begin
297       { We can dispense with GETJSAMPLE() here }
298       JSAMPROW(outptr)^[RGB_RED] := inptr^;
299       JSAMPROW(outptr)^[RGB_GREEN] := inptr^;
300       JSAMPROW(outptr)^[RGB_BLUE] := inptr^;
301       Inc(inptr);
302       Inc(outptr, RGB_PIXELSIZE);
303     end;
304     Dec(num_rows);
305   end;
306 end;
307 
308 
309 { Adobe-style YCCK -> CMYK conversion.
310   We convert YCbCr to R=1-C, G=1-M, and B=1-Y using the same
311   conversion as above, while passing K (black) unchanged.
312   We assume build_ycc_rgb_table has been called. }
313 
314 {METHODDEF}
315 procedure ycck_cmyk_convert (cinfo : j_decompress_ptr;
316                              input_buf : JSAMPIMAGE;
317                              input_row : JDIMENSION;
318                              output_buf : JSAMPARRAY;
319                              num_rows : int); far;
320 var
321   cconvert : my_cconvert_ptr;
322   {register} y, cb, cr : int;
323   {register} outptr : JSAMPROW;
324   {register} inptr0, inptr1, inptr2, inptr3 : JSAMPROW;
325   {register} col : JDIMENSION;
326   num_cols : JDIMENSION;
327   { copy these pointers into registers if possible }
328   {register} range_limit : range_limit_table_ptr;
329   {register} Crrtab : int_table_ptr;
330   {register} Cbbtab : int_table_ptr;
331   {register} Crgtab : INT32_table_ptr;
332   {register} Cbgtab : INT32_table_ptr;
333 var
334   shift_temp : INT32;
335 begin
336   cconvert := my_cconvert_ptr (cinfo^.cconvert);
337   num_cols := cinfo^.output_width;
338   { copy these pointers into registers if possible }
339   range_limit := cinfo^.sample_range_limit;
340   Crrtab := cconvert^.Cr_r_tab;
341   Cbbtab := cconvert^.Cb_b_tab;
342   Crgtab := cconvert^.Cr_g_tab;
343   Cbgtab := cconvert^.Cb_g_tab;
344 
345   while (num_rows > 0) do
346   begin
347     Dec(num_rows);
348     inptr0 := input_buf^[0]^[input_row];
349     inptr1 := input_buf^[1]^[input_row];
350     inptr2 := input_buf^[2]^[input_row];
351     inptr3 := input_buf^[3]^[input_row];
352     Inc(input_row);
353     outptr := output_buf^[0];
354     Inc(JSAMPROW_PTR(output_buf));
355     for col := 0 to pred(num_cols) do
356     begin
357       y  := GETJSAMPLE(inptr0^[col]);
358       cb := GETJSAMPLE(inptr1^[col]);
359       cr := GETJSAMPLE(inptr2^[col]);
360       { Range-limiting is essential due to noise introduced by DCT losses. }
361       outptr^[0] := range_limit^[MAXJSAMPLE - (y + Crrtab^[cr])];       { red }
362       shift_temp := Cbgtab^[cb] + Crgtab^[cr];
363       if shift_temp < 0 then
364         outptr^[1] := range_limit^[MAXJSAMPLE - (y + int(
365           (shift_temp shr SCALEBITS) or ((not INT32(0)) shl (32-SCALEBITS))
366                                                         ) )]
367       else
368         outptr^[1] := range_limit^[MAXJSAMPLE -             { green }
369                     (y + int(shift_temp shr SCALEBITS) )];
370       outptr^[2] := range_limit^[MAXJSAMPLE - (y + Cbbtab^[cb])];       { blue }
371       { K passes through unchanged }
372       outptr^[3] := inptr3^[col];       { don't need GETJSAMPLE here }
373       Inc(JSAMPLE_PTR(outptr), 4);
374     end;
375   end;
376 end;
377 
378 
379 { Empty method for start_pass. }
380 
381 {METHODDEF}
382 procedure start_pass_dcolor (cinfo : j_decompress_ptr); far;
383 begin
384   { no work needed }
385 end;
386 
387 
388 { Module initialization routine for output colorspace conversion. }
389 
390 {GLOBAL}
391 procedure jinit_color_deconverter (cinfo : j_decompress_ptr);
392 var
393   cconvert : my_cconvert_ptr;
394   ci : int;
395 begin
396   cconvert := my_cconvert_ptr (
397     cinfo^.mem^.alloc_small (j_common_ptr(cinfo), JPOOL_IMAGE,
398                                 SIZEOF(my_color_deconverter)) );
399   cinfo^.cconvert := jpeg_color_deconverter_ptr (cconvert);
400   cconvert^.pub.start_pass := start_pass_dcolor;
401 
402   { Make sure num_components agrees with jpeg_color_space }
403   case (cinfo^.jpeg_color_space) of
404   JCS_GRAYSCALE:
405     if (cinfo^.num_components <> 1) then
406       ERREXIT(j_common_ptr(cinfo), JERR_BAD_J_COLORSPACE);
407 
408   JCS_RGB,
409   JCS_YCbCr:
410     if (cinfo^.num_components <> 3) then
411       ERREXIT(j_common_ptr(cinfo), JERR_BAD_J_COLORSPACE);
412 
413   JCS_CMYK,
414   JCS_YCCK:
415     if (cinfo^.num_components <> 4) then
416       ERREXIT(j_common_ptr(cinfo), JERR_BAD_J_COLORSPACE);
417 
418   else                     { JCS_UNKNOWN can be anything }
419     if (cinfo^.num_components < 1) then
420       ERREXIT(j_common_ptr(cinfo), JERR_BAD_J_COLORSPACE);
421   end;
422 
423   { Set out_color_components and conversion method based on requested space.
424     Also clear the component_needed flags for any unused components,
425     so that earlier pipeline stages can avoid useless computation. }
426 
427   case (cinfo^.out_color_space) of
428   JCS_GRAYSCALE:
429     begin
430       cinfo^.out_color_components := 1;
431       if (cinfo^.jpeg_color_space = JCS_GRAYSCALE)
432         or (cinfo^.jpeg_color_space = JCS_YCbCr) then
433       begin
434         cconvert^.pub.color_convert := grayscale_convert;
435         { For color -> grayscale conversion, only the
436           Y (0) component is needed }
437         for ci := 1 to pred(cinfo^.num_components) do
438           cinfo^.comp_info^[ci].component_needed := FALSE;
439       end
440       else
441         ERREXIT(j_common_ptr(cinfo), JERR_CONVERSION_NOTIMPL);
442     end;
443 
444   JCS_RGB:
445     begin
446       cinfo^.out_color_components := RGB_PIXELSIZE;
447       if (cinfo^.jpeg_color_space = JCS_YCbCr) then
448       begin
449         cconvert^.pub.color_convert := ycc_rgb_convert;
450         build_ycc_rgb_table(cinfo);
451       end
452       else
453         if (cinfo^.jpeg_color_space = JCS_GRAYSCALE) then
454         begin
455           cconvert^.pub.color_convert := gray_rgb_convert;
456         end
457         else
458           if (cinfo^.jpeg_color_space = JCS_RGB) and (RGB_PIXELSIZE = 3) then
459           begin
460             cconvert^.pub.color_convert := null_convert;
461           end
462           else
463             ERREXIT(j_common_ptr(cinfo), JERR_CONVERSION_NOTIMPL);
464     end;
465 
466   JCS_CMYK:
467     begin
468       cinfo^.out_color_components := 4;
469       if (cinfo^.jpeg_color_space = JCS_YCCK) then
470       begin
471         cconvert^.pub.color_convert := ycck_cmyk_convert;
472         build_ycc_rgb_table(cinfo);
473       end
474       else
475         if (cinfo^.jpeg_color_space = JCS_CMYK) then
476         begin
477           cconvert^.pub.color_convert := null_convert;
478         end
479         else
480           ERREXIT(j_common_ptr(cinfo), JERR_CONVERSION_NOTIMPL);
481     end;
482 
483   else
484     begin { Permit null conversion to same output space }
485       if (cinfo^.out_color_space = cinfo^.jpeg_color_space) then
486       begin
487         cinfo^.out_color_components := cinfo^.num_components;
488         cconvert^.pub.color_convert := null_convert;
489       end
490       else                      { unsupported non-null conversion }
491         ERREXIT(j_common_ptr(cinfo), JERR_CONVERSION_NOTIMPL);
492     end;
493   end;
494 
495   if (cinfo^.quantize_colors) then
496     cinfo^.output_components := 1 { single colormapped output component }
497   else
498     cinfo^.output_components := cinfo^.out_color_components;
499 end;
500 
501 end.
502