⭐ 欢迎来到虫虫下载站! | 📦 资源下载 📁 资源专辑 ℹ️ 关于我们
⭐ 虫虫下载站

📄 jchuff.pas

📁 DELPHI版的JPEG文件解码源程序
💻 PAS
📖 第 1 页 / 共 3 页
字号:
Unit JcHuff;

{ This file contains Huffman entropy encoding routines.

  Much of the complexity here has to do with supporting output suspension.
  If the data destination module demands suspension, we want to be able to
  back up to the start of the current MCU.  To do this, we copy state
  variables into local working storage, and update them back to the
  permanent JPEG objects only upon successful completion of an MCU. }

{ Original: jchuff.c; Copyright (C) 1991-1997, Thomas G. Lane. }

interface

{$I jconfig.inc}

uses
  jmorecfg, { longptr definition missing }
  jpeglib,
  jdeferr,
  jerror,
  jutils,
  jinclude,
  jcomapi;

{ The legal range of a DCT coefficient is
   -1024 .. +1023  for 8-bit data;
  -16384 .. +16383 for 12-bit data.
  Hence the magnitude should always fit in 10 or 14 bits respectively. }


{$ifdef BITS_IN_JSAMPLE_IS_8}
const
  MAX_COEF_BITS = 10;
{$else}
const
  MAX_COEF_BITS = 14;
{$endif}

{ Derived data constructed for each Huffman table }
{ Declarations shared with jcphuff.c }
type
  c_derived_tbl_ptr = ^c_derived_tbl;
  c_derived_tbl = record
    ehufco : array[0..256-1] of uInt;	{ code for each symbol }
    ehufsi : array[0..256-1] of byte;   { length of code for each symbol }
    { If no code has been allocated for a symbol S, ehufsi[S] contains 0 }
  end;
{ for JCHUFF und JCPHUFF }
type
  TLongTable = array[0..256] of long;
  TLongTablePtr = ^TLongTable;

{ Compute the derived values for a Huffman table.
  Note this is also used by jcphuff.c. }

{GLOBAL}
procedure jpeg_make_c_derived_tbl (cinfo : j_compress_ptr;
                                   isDC : boolean;
                                   tblno : int;
			           var pdtbl : c_derived_tbl_ptr);

{ Generate the optimal coding for the given counts, fill htbl.
  Note this is also used by jcphuff.c. }

{GLOBAL}
procedure jpeg_gen_optimal_table (cinfo : j_compress_ptr;
                                  htbl : JHUFF_TBL_PTR;
                                  var freq : TLongTable);  { Nomssi }

{ Module initialization routine for Huffman entropy encoding. }

{GLOBAL}
procedure jinit_huff_encoder (cinfo : j_compress_ptr);

implementation

{ Expanded entropy encoder object for Huffman encoding.

  The savable_state subrecord contains fields that change within an MCU,
  but must not be updated permanently until we complete the MCU. }

type
  savable_state = record
    put_buffer : INT32;		{ current bit-accumulation buffer }
    put_bits : int;		{ # of bits now in it }
    last_dc_val : array[0..MAX_COMPS_IN_SCAN-1] of int;
                                { last DC coef for each component }
  end;


type
  huff_entropy_ptr = ^huff_entropy_encoder;
  huff_entropy_encoder = record
    pub : jpeg_entropy_encoder; { public fields }

    saved : savable_state;	{ Bit buffer & DC state at start of MCU }

    { These fields are NOT loaded into local working state. }
    restarts_to_go : uInt;	{ MCUs left in this restart interval }
    next_restart_num : int;	{ next restart number to write (0-7) }

    { Pointers to derived tables (these workspaces have image lifespan) }
    dc_derived_tbls : array[0..NUM_HUFF_TBLS-1] of c_derived_tbl_ptr;
    ac_derived_tbls : array[0..NUM_HUFF_TBLS-1] of c_derived_tbl_ptr;

  {$ifdef ENTROPY_OPT_SUPPORTED} { Statistics tables for optimization }
    dc_count_ptrs : array[0..NUM_HUFF_TBLS-1] of TLongTablePtr;
    ac_count_ptrs : array[0..NUM_HUFF_TBLS-1] of TLongTablePtr;
  {$endif}
  end;



{ Working state while writing an MCU.
  This struct contains all the fields that are needed by subroutines. }

type
  working_state = record
    next_output_byte : JOCTETptr; { => next byte to write in buffer }
    free_in_buffer : size_t;	  { # of byte spaces remaining in buffer }
    cur : savable_state;	  { Current bit buffer & DC state }
    cinfo : j_compress_ptr;	  { dump_buffer needs access to this }
  end;


{ Forward declarations }
{METHODDEF}
function encode_mcu_huff (cinfo : j_compress_ptr;
                          const MCU_data : array of JBLOCKROW) : boolean; far;
                          forward;
{METHODDEF}
procedure finish_pass_huff (cinfo : j_compress_ptr); far; forward;
{$ifdef ENTROPY_OPT_SUPPORTED}
{METHODDEF}
function encode_mcu_gather (cinfo : j_compress_ptr;
                            const MCU_data: array of JBLOCKROW) : boolean;
                            far; forward;

{METHODDEF}
procedure finish_pass_gather (cinfo : j_compress_ptr); far; forward;
{$endif}


{ Initialize for a Huffman-compressed scan.
  If gather_statistics is TRUE, we do not output anything during the scan,
  just count the Huffman symbols used and generate Huffman code tables. }

{METHODDEF}
procedure start_pass_huff (cinfo : j_compress_ptr;
                           gather_statistics : boolean); far;
var
  entropy : huff_entropy_ptr;
  ci, dctbl, actbl : int;
  compptr : jpeg_component_info_ptr;
begin
  entropy := huff_entropy_ptr (cinfo^.entropy);

  if (gather_statistics) then
  begin
{$ifdef ENTROPY_OPT_SUPPORTED}
    entropy^.pub.encode_mcu := encode_mcu_gather;
    entropy^.pub.finish_pass := finish_pass_gather;
{$else}
    ERREXIT(j_common_ptr(cinfo), JERR_NOT_COMPILED);
{$endif}
  end
  else
  begin
    entropy^.pub.encode_mcu := encode_mcu_huff;
    entropy^.pub.finish_pass := finish_pass_huff;
  end;

  for ci := 0 to pred(cinfo^.comps_in_scan) do
  begin
    compptr := cinfo^.cur_comp_info[ci];
    dctbl := compptr^.dc_tbl_no;
    actbl := compptr^.ac_tbl_no;
    if (gather_statistics) then
    begin
{$ifdef ENTROPY_OPT_SUPPORTED}
      { Check for invalid table indexes }
      { (make_c_derived_tbl does this in the other path) }
      if (dctbl < 0) or (dctbl >= NUM_HUFF_TBLS) then
	ERREXIT1(j_common_ptr(cinfo), JERR_NO_HUFF_TABLE, dctbl);
      if (actbl < 0) or (actbl >= NUM_HUFF_TBLS) then
	ERREXIT1(j_common_ptr(cinfo), JERR_NO_HUFF_TABLE, actbl);
      { Allocate and zero the statistics tables }
      { Note that jpeg_gen_optimal_table expects 257 entries in each table! }
      if (entropy^.dc_count_ptrs[dctbl] = NIL) then
	entropy^.dc_count_ptrs[dctbl] := TLongTablePtr(
	  cinfo^.mem^.alloc_small (j_common_ptr(cinfo), JPOOL_IMAGE,
				      257 * SIZEOF(long)) );
      MEMZERO(entropy^.dc_count_ptrs[dctbl], 257 * SIZEOF(long));
      if (entropy^.ac_count_ptrs[actbl] = NIL) then
	entropy^.ac_count_ptrs[actbl] := TLongTablePtr(
	  cinfo^.mem^.alloc_small (j_common_ptr(cinfo), JPOOL_IMAGE,
				      257 * SIZEOF(long)) );
      MEMZERO(entropy^.ac_count_ptrs[actbl], 257 * SIZEOF(long));
{$endif}
    end
    else
    begin
      { Compute derived values for Huffman tables }
      { We may do this more than once for a table, but it's not expensive }
      jpeg_make_c_derived_tbl(cinfo, TRUE, dctbl,
			      entropy^.dc_derived_tbls[dctbl]);
      jpeg_make_c_derived_tbl(cinfo, FALSE, actbl,
			      entropy^.ac_derived_tbls[actbl]);
    end;
    { Initialize DC predictions to 0 }
    entropy^.saved.last_dc_val[ci] := 0;
  end;

  { Initialize bit buffer to empty }
  entropy^.saved.put_buffer := 0;
  entropy^.saved.put_bits := 0;

  { Initialize restart stuff }
  entropy^.restarts_to_go := cinfo^.restart_interval;
  entropy^.next_restart_num := 0;
end;


{ Compute the derived values for a Huffman table.
  This routine also performs some validation checks on the table.

  Note this is also used by jcphuff.c. }

{GLOBAL}
procedure jpeg_make_c_derived_tbl (cinfo : j_compress_ptr;
                                   isDC : boolean;
                                   tblno : int;
			           var pdtbl : c_derived_tbl_ptr);
var
  htbl : JHUFF_TBL_PTR;
  dtbl : c_derived_tbl_ptr;
  p, i, l, lastp, si, maxsymbol : int;
  huffsize : array[0..257-1] of byte;
  huffcode : array[0..257-1] of uInt;
  code : uInt;
begin
  { Note that huffsize[] and huffcode[] are filled in code-length order,
    paralleling the order of the symbols themselves in htbl->huffval[]. }

  { Find the input Huffman table }
  if (tblno < 0) or (tblno >= NUM_HUFF_TBLS) then
    ERREXIT1(j_common_ptr(cinfo), JERR_NO_HUFF_TABLE, tblno);
  if isDC then
    htbl := cinfo^.dc_huff_tbl_ptrs[tblno]
  else
    htbl := cinfo^.ac_huff_tbl_ptrs[tblno];
  if (htbl = NIL) then
    ERREXIT1(j_common_ptr(cinfo), JERR_NO_HUFF_TABLE, tblno);

  { Allocate a workspace if we haven't already done so. }
  if (pdtbl = NIL) then
    pdtbl := c_derived_tbl_ptr(
      cinfo^.mem^.alloc_small (j_common_ptr(cinfo), JPOOL_IMAGE,
				  SIZEOF(c_derived_tbl)) );
  dtbl := pdtbl;

  { Figure C.1: make table of Huffman code length for each symbol }

  p := 0;
  for l := 1 to 16 do
  begin
    i := int(htbl^.bits[l]);
    if (i < 0) and (p + i > 256) then	{ protect against table overrun }
      ERREXIT(j_common_ptr(cinfo), JERR_BAD_HUFF_TABLE);
    while (i > 0) do
    begin
      huffsize[p] := byte(l);
      Inc(p);
      Dec(i);
    end;
  end;
  huffsize[p] := 0;
  lastp := p;

  { Figure C.2: generate the codes themselves }
  { We also validate that the counts represent a legal Huffman code tree. }

  code := 0;
  si := huffsize[0];
  p := 0;
  while (huffsize[p] <> 0) do
  begin
    while (( int(huffsize[p]) ) = si) do
    begin
      huffcode[p] := code;
      Inc(p);
      Inc(code);
    end;
    { code is now 1 more than the last code used for codelength si; but
      it must still fit in si bits, since no code is allowed to be all ones. }

    if (INT32(code) >= (INT32(1) shl si)) then
      ERREXIT(j_common_ptr(cinfo), JERR_BAD_HUFF_TABLE);
    code := code shl 1;
    Inc(si);
  end;

  { Figure C.3: generate encoding tables }
  { These are code and size indexed by symbol value }

  { Set all codeless symbols to have code length 0;
    this lets us detect duplicate VAL entries here, and later
    allows emit_bits to detect any attempt to emit such symbols. }

  MEMZERO(@dtbl^.ehufsi, SIZEOF(dtbl^.ehufsi));

  { This is also a convenient place to check for out-of-range
    and duplicated VAL entries.  We allow 0..255 for AC symbols
    but only 0..15 for DC.  (We could constrain them further
    based on data depth and mode, but this seems enough.) }

  if isDC then
    maxsymbol := 15
  else
    maxsymbol := 255;

  for p := 0 to pred(lastp) do
  begin
    i := htbl^.huffval[p];
    if (i < 0) or (i > maxsymbol) or (dtbl^.ehufsi[i] <> 0) then
      ERREXIT(j_common_ptr(cinfo), JERR_BAD_HUFF_TABLE);
    dtbl^.ehufco[i] := huffcode[p];
    dtbl^.ehufsi[i] := huffsize[p];
  end;
end;


{ Outputting bytes to the file }


{LOCAL}
function dump_buffer (var state : working_state) : boolean;
{ Empty the output buffer; return TRUE if successful, FALSE if must suspend }
var
  dest : jpeg_destination_mgr_ptr;
begin
  dest := state.cinfo^.dest;

  if (not dest^.empty_output_buffer (state.cinfo)) then
  begin
    dump_buffer := FALSE;
    exit;
  end;
  { After a successful buffer dump, must reset buffer pointers }
  state.next_output_byte := dest^.next_output_byte;
  state.free_in_buffer := dest^.free_in_buffer;
  dump_buffer := TRUE;
end;


{ Outputting bits to the file }

{ Only the right 24 bits of put_buffer are used; the valid bits are
  left-justified in this part.  At most 16 bits can be passed to emit_bits
  in one call, and we never retain more than 7 bits in put_buffer
  between calls, so 24 bits are sufficient. }


{LOCAL}
function emit_bits (var state : working_state;
                    code : uInt;
                    size : int) : boolean;  {INLINE}
{ Emit some bits; return TRUE if successful, FALSE if must suspend }
var
  { This routine is heavily used, so it's worth coding tightly. }
  {register} put_buffer : INT32;

⌨️ 快捷键说明

复制代码 Ctrl + C
搜索代码 Ctrl + F
全屏模式 F11
切换主题 Ctrl + Shift + D
显示快捷键 ?
增大字号 Ctrl + =
减小字号 Ctrl + -