📄 jquant1.pas
字号:
for i := 0 to pred(cinfo^.out_color_components) do
begin
{ fill in colormap entries for i'th color component }
nci := cquantize^.Ncolors[i]; { # of distinct values for this color }
blksize := blkdist div nci;
for j := 0 to pred(nci) do
begin
{ Compute j'th output value (out of nci) for component }
val := output_value(cinfo, i, j, nci-1);
{ Fill in all colormap entries that have this value of this component }
ptr := j * blksize;
while (ptr < total_colors) do
begin
{ fill in blksize entries beginning at ptr }
for k := 0 to pred(blksize) do
colormap^[i]^[ptr+k] := JSAMPLE(val);
Inc(ptr, blkdist);
end;
end;
blkdist := blksize; { blksize of this color is blkdist of next }
end;
{ Save the colormap in private storage,
where it will survive color quantization mode changes. }
cquantize^.sv_colormap := colormap;
cquantize^.sv_actual := total_colors;
end;
{ Create the color index table. }
{LOCAL}
procedure create_colorindex (cinfo : j_decompress_ptr);
var
cquantize : my_cquantize_ptr;
indexptr,
help_indexptr : JSAMPROW; { for negative offsets }
i,j,k, nci, blksize, val, pad : int;
begin
cquantize := my_cquantize_ptr (cinfo^.cquantize);
{ For ordered dither, we pad the color index tables by MAXJSAMPLE in
each direction (input index values can be -MAXJSAMPLE .. 2*MAXJSAMPLE).
This is not necessary in the other dithering modes. However, we
flag whether it was done in case user changes dithering mode. }
if (cinfo^.dither_mode = JDITHER_ORDERED) then
begin
pad := MAXJSAMPLE*2;
cquantize^.is_padded := TRUE;
end
else
begin
pad := 0;
cquantize^.is_padded := FALSE;
end;
cquantize^.colorindex := cinfo^.mem^.alloc_sarray
(j_common_ptr(cinfo), JPOOL_IMAGE,
JDIMENSION(MAXJSAMPLE+1 + pad),
JDIMENSION(cinfo^.out_color_components));
{ blksize is number of adjacent repeated entries for a component }
blksize := cquantize^.sv_actual;
for i := 0 to pred(cinfo^.out_color_components) do
begin
{ fill in colorindex entries for i'th color component }
nci := cquantize^.Ncolors[i]; { # of distinct values for this color }
blksize := blksize div nci;
{ adjust colorindex pointers to provide padding at negative indexes. }
if (pad <> 0) then
Inc(JSAMPLE_PTR(cquantize^.colorindex^[i]), MAXJSAMPLE);
{ in loop, val = index of current output value, }
{ and k = largest j that maps to current val }
indexptr := cquantize^.colorindex^[i];
val := 0;
k := largest_input_value(cinfo, i, 0, nci-1);
for j := 0 to MAXJSAMPLE do
begin
while (j > k) do { advance val if past boundary }
begin
Inc(val);
k := largest_input_value(cinfo, i, val, nci-1);
end;
{ premultiply so that no multiplication needed in main processing }
indexptr^[j] := JSAMPLE (val * blksize);
end;
{ Pad at both ends if necessary }
if (pad <> 0) then
begin
help_indexptr := indexptr;
{ adjust the help pointer to avoid negative offsets }
Dec(JSAMPLE_PTR(help_indexptr), MAXJSAMPLE);
for j := 1 to MAXJSAMPLE do
begin
{indexptr^[-j] := indexptr^[0];}
help_indexptr^[MAXJSAMPLE-j] := indexptr^[0];
indexptr^[MAXJSAMPLE+j] := indexptr^[MAXJSAMPLE];
end;
end;
end;
end;
{ Create an ordered-dither array for a component having ncolors
distinct output values. }
{LOCAL}
function make_odither_array (cinfo : j_decompress_ptr;
ncolors : int) : ODITHER_MATRIX_PTR;
var
odither : ODITHER_MATRIX_PTR;
j, k : int;
num, den : INT32;
begin
odither := ODITHER_MATRIX_PTR (
cinfo^.mem^.alloc_small(j_common_ptr(cinfo), JPOOL_IMAGE,
SIZEOF(ODITHER_MATRIX)));
{ The inter-value distance for this color is MAXJSAMPLE/(ncolors-1).
Hence the dither value for the matrix cell with fill order f
(f=0..N-1) should be (N-1-2*f)/(2*N) * MAXJSAMPLE/(ncolors-1).
On 16-bit-int machine, be careful to avoid overflow. }
den := 2 * ODITHER_CELLS * ( INT32(ncolors - 1));
for j := 0 to pred(ODITHER_SIZE) do
begin
for k := 0 to pred(ODITHER_SIZE) do
begin
num := ( INT32(ODITHER_CELLS-1 - 2*( int(base_dither_matrix[j][k]))))
* MAXJSAMPLE;
{ Ensure round towards zero despite C's lack of consistency
about rounding negative values in integer division... }
if num<0 then
odither^[j][k] := int (-((-num) div den))
else
odither^[j][k] := int (num div den);
end;
end;
make_odither_array := odither;
end;
{ Create the ordered-dither tables.
Components having the same number of representative colors may
share a dither table. }
{LOCAL}
procedure create_odither_tables (cinfo : j_decompress_ptr);
var
cquantize : my_cquantize_ptr;
odither : ODITHER_MATRIX_PTR;
i, j, nci : int;
begin
cquantize := my_cquantize_ptr (cinfo^.cquantize);
for i := 0 to pred(cinfo^.out_color_components) do
begin
nci := cquantize^.Ncolors[i]; { # of distinct values for this color }
odither := NIL; { search for matching prior component }
for j := 0 to pred(i) do
begin
if (nci = cquantize^.Ncolors[j]) then
begin
odither := cquantize^.odither[j];
break;
end;
end;
if (odither = NIL) then { need a new table? }
odither := make_odither_array(cinfo, nci);
cquantize^.odither[i] := odither;
end;
end;
{ Map some rows of pixels to the output colormapped representation. }
{METHODDEF}
procedure color_quantize (cinfo : j_decompress_ptr;
input_buf : JSAMPARRAY;
output_buf : JSAMPARRAY;
num_rows : int); far;
{ General case, no dithering }
var
cquantize : my_cquantize_ptr;
colorindex : JSAMPARRAY;
pixcode, ci : int; {register}
ptrin, ptrout : JSAMPLE_PTR; {register}
row : int;
col : JDIMENSION;
width : JDIMENSION;
nc : int; {register}
begin
cquantize := my_cquantize_ptr (cinfo^.cquantize);
colorindex := cquantize^.colorindex;
width := cinfo^.output_width;
nc := cinfo^.out_color_components;
for row := 0 to pred(num_rows) do
begin
ptrin := JSAMPLE_PTR(input_buf^[row]);
ptrout := JSAMPLE_PTR(output_buf^[row]);
for col := pred(width) downto 0 do
begin
pixcode := 0;
for ci := 0 to pred(nc) do
begin
Inc(pixcode, GETJSAMPLE(colorindex^[ci]^[GETJSAMPLE(ptrin^)]) );
Inc(ptrin);
end;
ptrout^ := JSAMPLE (pixcode);
Inc(ptrout);
end;
end;
end;
{METHODDEF}
procedure color_quantize3 (cinfo : j_decompress_ptr;
input_buf : JSAMPARRAY;
output_buf : JSAMPARRAY;
num_rows : int); far;
{ Fast path for out_color_components=3, no dithering }
var
cquantize : my_cquantize_ptr;
pixcode : int; {register}
ptrin, ptrout : JSAMPLE_PTR; {register}
colorindex0 : JSAMPROW;
colorindex1 : JSAMPROW;
colorindex2 : JSAMPROW;
row : int;
col : JDIMENSION;
width : JDIMENSION;
begin
cquantize := my_cquantize_ptr (cinfo^.cquantize);
colorindex0 := (cquantize^.colorindex)^[0];
colorindex1 := (cquantize^.colorindex)^[1];
colorindex2 := (cquantize^.colorindex)^[2];
width := cinfo^.output_width;
for row := 0 to pred(num_rows) do
begin
ptrin := JSAMPLE_PTR(input_buf^[row]);
ptrout := JSAMPLE_PTR(output_buf^[row]);
for col := pred(width) downto 0 do
begin
pixcode := GETJSAMPLE((colorindex0)^[GETJSAMPLE(ptrin^)]);
Inc(ptrin);
Inc( pixcode, GETJSAMPLE((colorindex1)^[GETJSAMPLE(ptrin^)]) );
Inc(ptrin);
Inc( pixcode, GETJSAMPLE((colorindex2)^[GETJSAMPLE(ptrin^)]) );
Inc(ptrin);
ptrout^ := JSAMPLE (pixcode);
Inc(ptrout);
end;
end;
end;
{METHODDEF}
procedure quantize_ord_dither (cinfo : j_decompress_ptr;
input_buf : JSAMPARRAY;
output_buf : JSAMPARRAY;
num_rows : int); far;
{ General case, with ordered dithering }
var
cquantize : my_cquantize_ptr;
input_ptr, {register}
output_ptr : JSAMPLE_PTR; {register}
colorindex_ci : JSAMPROW;
dither : ^ODITHER_vector; { points to active row of dither matrix }
row_index, col_index : int; { current indexes into dither matrix }
nc : int;
ci : int;
row : int;
col : JDIMENSION;
width : JDIMENSION;
var
pad_offset : int;
begin
cquantize := my_cquantize_ptr (cinfo^.cquantize);
nc := cinfo^.out_color_components;
width := cinfo^.output_width;
{ Nomssi: work around negative offset }
if my_cquantize_ptr (cinfo^.cquantize)^.is_padded then
pad_offset := MAXJSAMPLE
else
pad_offset := 0;
for row := 0 to pred(num_rows) do
begin
{ Initialize output values to 0 so can process components separately }
jzero_far( {far} pointer(output_buf^[row]),
size_t(width * SIZEOF(JSAMPLE)));
row_index := cquantize^.row_index;
for ci := 0 to pred(nc) do
begin
input_ptr := JSAMPLE_PTR(@ input_buf^[row]^[ci]);
output_ptr := JSAMPLE_PTR(output_buf^[row]);
colorindex_ci := cquantize^.colorindex^[ci];
{ Nomssi }
Dec(JSAMPLE_PTR(colorindex_ci), pad_offset);
dither := @(cquantize^.odither[ci]^[row_index]);
col_index := 0;
for col := pred(width) downto 0 do
begin
{ Form pixel value + dither, range-limit to 0..MAXJSAMPLE,
select output value, accumulate into output code for this pixel.
Range-limiting need not be done explicitly, as we have extended
the colorindex table to produce the right answers for out-of-range
inputs. The maximum dither is +- MAXJSAMPLE; this sets the
required amount of padding. }
Inc(output_ptr^,
colorindex_ci^[GETJSAMPLE(input_ptr^)+ pad_offset +
dither^[col_index]]);
Inc(output_ptr);
Inc(input_ptr, nc);
col_index := (col_index + 1) and ODITHER_MASK;
end;
end;
{ Advance row index for next row }
row_index := (row_index + 1) and ODITHER_MASK;
cquantize^.row_index := row_index;
end;
end;
{METHODDEF}
procedure quantize3_ord_dither (cinfo : j_decompress_ptr;
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -