DEADSOFTWARE

hopefully no more windows
[d2df-editor.git] / src / lib / vampimg / JpegLib / imjdhuff.pas
1 unit imjdhuff;
3 { This file contains declarations for Huffman entropy decoding routines
4 that are shared between the sequential decoder (jdhuff.c) and the
5 progressive decoder (jdphuff.c). No other modules need to see these. }
7 { This file contains Huffman entropy decoding routines.
9 Much of the complexity here has to do with supporting input suspension.
10 If the data source module demands suspension, we want to be able to back
11 up to the start of the current MCU. To do this, we copy state variables
12 into local working storage, and update them back to the permanent
13 storage only upon successful completion of an MCU. }
15 { Original: jdhuff.h+jdhuff.c; Copyright (C) 1991-1997, Thomas G. Lane. }
19 interface
21 {$I imjconfig.inc}
23 uses
24 imjmorecfg,
25 imjinclude,
26 imjdeferr,
27 imjerror,
28 imjutils,
29 imjpeglib;
32 { Declarations shared with jdphuff.c }
36 { Derived data constructed for each Huffman table }
38 const
39 HUFF_LOOKAHEAD = 8; { # of bits of lookahead }
41 type
42 d_derived_tbl_ptr = ^d_derived_tbl;
43 d_derived_tbl = record
44 { Basic tables: (element [0] of each array is unused) }
45 maxcode : array[0..18-1] of INT32; { largest code of length k (-1 if none) }
46 { (maxcode[17] is a sentinel to ensure jpeg_huff_decode terminates) }
47 valoffset : array[0..17-1] of INT32; { huffval[] offset for codes of length k }
48 { valoffset[k] = huffval[] index of 1st symbol of code length k, less
49 the smallest code of length k; so given a code of length k, the
50 corresponding symbol is huffval[code + valoffset[k]] }
52 { Link to public Huffman table (needed only in jpeg_huff_decode) }
53 pub : JHUFF_TBL_PTR;
55 { Lookahead tables: indexed by the next HUFF_LOOKAHEAD bits of
56 the input data stream. If the next Huffman code is no more
57 than HUFF_LOOKAHEAD bits long, we can obtain its length and
58 the corresponding symbol directly from these tables. }
60 look_nbits : array[0..(1 shl HUFF_LOOKAHEAD)-1] of int;
61 { # bits, or 0 if too long }
62 look_sym : array[0..(1 shl HUFF_LOOKAHEAD)-1] of UINT8;
63 { symbol, or unused }
64 end;
66 { Fetching the next N bits from the input stream is a time-critical operation
67 for the Huffman decoders. We implement it with a combination of inline
68 macros and out-of-line subroutines. Note that N (the number of bits
69 demanded at one time) never exceeds 15 for JPEG use.
71 We read source bytes into get_buffer and dole out bits as needed.
72 If get_buffer already contains enough bits, they are fetched in-line
73 by the macros CHECK_BIT_BUFFER and GET_BITS. When there aren't enough
74 bits, jpeg_fill_bit_buffer is called; it will attempt to fill get_buffer
75 as full as possible (not just to the number of bits needed; this
76 prefetching reduces the overhead cost of calling jpeg_fill_bit_buffer).
77 Note that jpeg_fill_bit_buffer may return FALSE to indicate suspension.
78 On TRUE return, jpeg_fill_bit_buffer guarantees that get_buffer contains
79 at least the requested number of bits --- dummy zeroes are inserted if
80 necessary. }
83 type
84 bit_buf_type = INT32 ; { type of bit-extraction buffer }
85 const
86 BIT_BUF_SIZE = 32; { size of buffer in bits }
88 { If long is > 32 bits on your machine, and shifting/masking longs is
89 reasonably fast, making bit_buf_type be long and setting BIT_BUF_SIZE
90 appropriately should be a win. Unfortunately we can't define the size
91 with something like #define BIT_BUF_SIZE (sizeof(bit_buf_type)*8)
92 because not all machines measure sizeof in 8-bit bytes. }
94 type
95 bitread_perm_state = record { Bitreading state saved across MCUs }
96 get_buffer : bit_buf_type; { current bit-extraction buffer }
97 bits_left : int; { # of unused bits in it }
98 end;
100 type
101 bitread_working_state = record
102 { Bitreading working state within an MCU }
103 { current data source location }
104 { We need a copy, rather than munging the original, in case of suspension }
105 next_input_byte : JOCTETptr; { => next byte to read from source }
106 bytes_in_buffer : size_t; { # of bytes remaining in source buffer }
107 { Bit input buffer --- note these values are kept in register variables,
108 not in this struct, inside the inner loops. }
110 get_buffer : bit_buf_type; { current bit-extraction buffer }
111 bits_left : int; { # of unused bits in it }
112 { Pointer needed by jpeg_fill_bit_buffer }
113 cinfo : j_decompress_ptr; { back link to decompress master record }
114 end;
116 { Module initialization routine for Huffman entropy decoding. }
118 {GLOBAL}
119 procedure jinit_huff_decoder (cinfo : j_decompress_ptr);
121 {GLOBAL}
122 function jpeg_huff_decode(var state : bitread_working_state;
123 get_buffer : bit_buf_type; {register}
124 bits_left : int; {register}
125 htbl : d_derived_tbl_ptr;
126 min_bits : int) : int;
128 { Compute the derived values for a Huffman table.
129 Note this is also used by jdphuff.c. }
131 {GLOBAL}
132 procedure jpeg_make_d_derived_tbl (cinfo : j_decompress_ptr;
133 isDC : boolean;
134 tblno : int;
135 var pdtbl : d_derived_tbl_ptr);
137 { Load up the bit buffer to a depth of at least nbits }
139 function jpeg_fill_bit_buffer (var state : bitread_working_state;
140 get_buffer : bit_buf_type; {register}
141 bits_left : int; {register}
142 nbits : int) : boolean;
144 implementation
146 {$IFDEF MACRO}
148 { Macros to declare and load/save bitread local variables. }
149 {$define BITREAD_STATE_VARS}
150 get_buffer : bit_buf_type ; {register}
151 bits_left : int; {register}
152 br_state : bitread_working_state;
154 {$define BITREAD_LOAD_STATE(cinfop,permstate)}
155 br_state.cinfo := cinfop;
156 br_state.next_input_byte := cinfop^.src^.next_input_byte;
157 br_state.bytes_in_buffer := cinfop^.src^.bytes_in_buffer;
158 get_buffer := permstate.get_buffer;
159 bits_left := permstate.bits_left;
161 {$define BITREAD_SAVE_STATE(cinfop,permstate) }
162 cinfop^.src^.next_input_byte := br_state.next_input_byte;
163 cinfop^.src^.bytes_in_buffer := br_state.bytes_in_buffer;
164 permstate.get_buffer := get_buffer;
165 permstate.bits_left := bits_left;
168 { These macros provide the in-line portion of bit fetching.
169 Use CHECK_BIT_BUFFER to ensure there are N bits in get_buffer
170 before using GET_BITS, PEEK_BITS, or DROP_BITS.
171 The variables get_buffer and bits_left are assumed to be locals,
172 but the state struct might not be (jpeg_huff_decode needs this).
173 CHECK_BIT_BUFFER(state,n,action);
174 Ensure there are N bits in get_buffer; if suspend, take action.
175 val = GET_BITS(n);
176 Fetch next N bits.
177 val = PEEK_BITS(n);
178 Fetch next N bits without removing them from the buffer.
179 DROP_BITS(n);
180 Discard next N bits.
181 The value N should be a simple variable, not an expression, because it
182 is evaluated multiple times. }
185 {$define CHECK_BIT_BUFFER(state,nbits,action)}
186 if (bits_left < (nbits)) then
187 begin
188 if (not jpeg_fill_bit_buffer(&(state),get_buffer,bits_left,nbits)) then
189 begin
190 action;
191 exit;
192 end;
193 get_buffer := state.get_buffer;
194 bits_left := state.bits_left;
195 end;
198 {$define GET_BITS(nbits)}
199 Dec(bits_left, (nbits));
200 ( (int(get_buffer shr bits_left)) and ( pred(1 shl (nbits)) ) )
202 {$define PEEK_BITS(nbits)}
203 int(get_buffer shr (bits_left - (nbits))) and pred(1 shl (nbits))
205 {$define DROP_BITS(nbits)}
206 Dec(bits_left, nbits);
211 { Code for extracting next Huffman-coded symbol from input bit stream.
212 Again, this is time-critical and we make the main paths be macros.
214 We use a lookahead table to process codes of up to HUFF_LOOKAHEAD bits
215 without looping. Usually, more than 95% of the Huffman codes will be 8
216 or fewer bits long. The few overlength codes are handled with a loop,
217 which need not be inline code.
219 Notes about the HUFF_DECODE macro:
220 1. Near the end of the data segment, we may fail to get enough bits
221 for a lookahead. In that case, we do it the hard way.
222 2. If the lookahead table contains no entry, the next code must be
223 more than HUFF_LOOKAHEAD bits long.
224 3. jpeg_huff_decode returns -1 if forced to suspend. }
229 macro HUFF_DECODE(s,br_state,htbl,return FALSE,slowlabel);
230 label showlabel;
231 var
232 nb, look : int; {register}
233 begin
234 if (bits_left < HUFF_LOOKAHEAD) then
235 begin
236 if (not jpeg_fill_bit_buffer(br_state,get_buffer,bits_left, 0)) then
237 begin
238 decode_mcu := FALSE;
239 exit;
240 end;
241 get_buffer := br_state.get_buffer;
242 bits_left := br_state.bits_left;
243 if (bits_left < HUFF_LOOKAHEAD) then
244 begin
245 nb := 1;
246 goto slowlabel;
247 end;
248 end;
249 {look := PEEK_BITS(HUFF_LOOKAHEAD);}
250 look := int(get_buffer shr (bits_left - HUFF_LOOKAHEAD)) and
251 pred(1 shl HUFF_LOOKAHEAD);
253 nb := htbl^.look_nbits[look];
254 if (nb <> 0) then
255 begin
256 {DROP_BITS(nb);}
257 Dec(bits_left, nb);
259 s := htbl^.look_sym[look];
260 end
261 else
262 begin
263 nb := HUFF_LOOKAHEAD+1;
264 slowlabel:
265 s := jpeg_huff_decode(br_state,get_buffer,bits_left,htbl,nb));
266 if (s < 0) then
267 begin
268 result := FALSE;
269 exit;
270 end;
271 get_buffer := br_state.get_buffer;
272 bits_left := br_state.bits_left;
273 end;
274 end;
277 {$ENDIF} {MACRO}
279 { Expanded entropy decoder object for Huffman decoding.
281 The savable_state subrecord contains fields that change within an MCU,
282 but must not be updated permanently until we complete the MCU. }
284 type
285 savable_state = record
286 last_dc_val : array[0..MAX_COMPS_IN_SCAN-1] of int; { last DC coef for each component }
287 end;
290 type
291 huff_entropy_ptr = ^huff_entropy_decoder;
292 huff_entropy_decoder = record
293 pub : jpeg_entropy_decoder; { public fields }
295 { These fields are loaded into local variables at start of each MCU.
296 In case of suspension, we exit WITHOUT updating them. }
298 bitstate : bitread_perm_state; { Bit buffer at start of MCU }
299 saved : savable_state; { Other state at start of MCU }
301 { These fields are NOT loaded into local working state. }
302 restarts_to_go : uInt; { MCUs left in this restart interval }
304 { Pointers to derived tables (these workspaces have image lifespan) }
305 dc_derived_tbls : array[0..NUM_HUFF_TBLS] of d_derived_tbl_ptr;
306 ac_derived_tbls : array[0..NUM_HUFF_TBLS] of d_derived_tbl_ptr;
308 { Precalculated info set up by start_pass for use in decode_mcu: }
310 { Pointers to derived tables to be used for each block within an MCU }
311 dc_cur_tbls : array[0..D_MAX_BLOCKS_IN_MCU-1] of d_derived_tbl_ptr;
312 ac_cur_tbls : array[0..D_MAX_BLOCKS_IN_MCU-1] of d_derived_tbl_ptr;
313 { Whether we care about the DC and AC coefficient values for each block }
314 dc_needed : array[0..D_MAX_BLOCKS_IN_MCU-1] of boolean;
315 ac_needed : array[0..D_MAX_BLOCKS_IN_MCU-1] of boolean;
316 end;
320 { Initialize for a Huffman-compressed scan. }
322 {METHODDEF}
323 procedure start_pass_huff_decoder (cinfo : j_decompress_ptr);
324 var
325 entropy : huff_entropy_ptr;
326 ci, blkn, dctbl, actbl : int;
327 compptr : jpeg_component_info_ptr;
328 begin
329 entropy := huff_entropy_ptr (cinfo^.entropy);
331 { Check that the scan parameters Ss, Se, Ah/Al are OK for sequential JPEG.
332 This ought to be an error condition, but we make it a warning because
333 there are some baseline files out there with all zeroes in these bytes. }
335 if (cinfo^.Ss <> 0) or (cinfo^.Se <> DCTSIZE2-1) or
336 (cinfo^.Ah <> 0) or (cinfo^.Al <> 0) then
337 WARNMS(j_common_ptr(cinfo), JWRN_NOT_SEQUENTIAL);
339 for ci := 0 to pred(cinfo^.comps_in_scan) do
340 begin
341 compptr := cinfo^.cur_comp_info[ci];
342 dctbl := compptr^.dc_tbl_no;
343 actbl := compptr^.ac_tbl_no;
344 { Compute derived values for Huffman tables }
345 { We may do this more than once for a table, but it's not expensive }
346 jpeg_make_d_derived_tbl(cinfo, TRUE, dctbl,
347 entropy^.dc_derived_tbls[dctbl]);
348 jpeg_make_d_derived_tbl(cinfo, FALSE, actbl,
349 entropy^.ac_derived_tbls[actbl]);
350 { Initialize DC predictions to 0 }
351 entropy^.saved.last_dc_val[ci] := 0;
352 end;
354 { Precalculate decoding info for each block in an MCU of this scan }
355 for blkn := 0 to pred(cinfo^.blocks_in_MCU) do
356 begin
357 ci := cinfo^.MCU_membership[blkn];
358 compptr := cinfo^.cur_comp_info[ci];
359 { Precalculate which table to use for each block }
360 entropy^.dc_cur_tbls[blkn] := entropy^.dc_derived_tbls[compptr^.dc_tbl_no];
361 entropy^.ac_cur_tbls[blkn] := entropy^.ac_derived_tbls[compptr^.ac_tbl_no];
362 { Decide whether we really care about the coefficient values }
363 if (compptr^.component_needed) then
364 begin
365 entropy^.dc_needed[blkn] := TRUE;
366 { we don't need the ACs if producing a 1/8th-size image }
367 entropy^.ac_needed[blkn] := (compptr^.DCT_scaled_size > 1);
368 end
369 else
370 begin
371 entropy^.ac_needed[blkn] := FALSE;
372 entropy^.dc_needed[blkn] := FALSE;
373 end;
374 end;
376 { Initialize bitread state variables }
377 entropy^.bitstate.bits_left := 0;
378 entropy^.bitstate.get_buffer := 0; { unnecessary, but keeps Purify quiet }
379 entropy^.pub.insufficient_data := FALSE;
381 { Initialize restart counter }
382 entropy^.restarts_to_go := cinfo^.restart_interval;
383 end;
386 { Compute the derived values for a Huffman table.
387 This routine also performs some validation checks on the table.
389 Note this is also used by jdphuff.c. }
391 {GLOBAL}
392 procedure jpeg_make_d_derived_tbl (cinfo : j_decompress_ptr;
393 isDC : boolean;
394 tblno : int;
395 var pdtbl : d_derived_tbl_ptr);
396 var
397 htbl : JHUFF_TBL_PTR;
398 dtbl : d_derived_tbl_ptr;
399 p, i, l, si, numsymbols : int;
400 lookbits, ctr : int;
401 huffsize : array[0..257-1] of byte;
402 huffcode : array[0..257-1] of uInt;
403 code : uInt;
404 var
405 sym : int;
406 begin
407 { Note that huffsize[] and huffcode[] are filled in code-length order,
408 paralleling the order of the symbols themselves in htbl^.huffval[]. }
410 { Find the input Huffman table }
411 if (tblno < 0) or (tblno >= NUM_HUFF_TBLS) then
412 ERREXIT1(j_common_ptr(cinfo), JERR_NO_HUFF_TABLE, tblno);
413 if isDC then
414 htbl := cinfo^.dc_huff_tbl_ptrs[tblno]
415 else
416 htbl := cinfo^.ac_huff_tbl_ptrs[tblno];
417 if (htbl = NIL) then
418 ERREXIT1(j_common_ptr(cinfo), JERR_NO_HUFF_TABLE, tblno);
420 { Allocate a workspace if we haven't already done so. }
421 if (pdtbl = NIL) then
422 pdtbl := d_derived_tbl_ptr(
423 cinfo^.mem^.alloc_small (j_common_ptr(cinfo), JPOOL_IMAGE,
424 SIZEOF(d_derived_tbl)) );
425 dtbl := pdtbl;
426 dtbl^.pub := htbl; { fill in back link }
428 { Figure C.1: make table of Huffman code length for each symbol }
430 p := 0;
431 for l := 1 to 16 do
432 begin
433 i := int(htbl^.bits[l]);
434 if (i < 0) or (p + i > 256) then { protect against table overrun }
435 ERREXIT(j_common_ptr(cinfo), JERR_BAD_HUFF_TABLE);
436 while (i > 0) do
437 begin
438 huffsize[p] := byte(l);
439 Inc(p);
440 Dec(i);
441 end;
442 end;
443 huffsize[p] := 0;
444 numsymbols := p;
446 { Figure C.2: generate the codes themselves }
447 { We also validate that the counts represent a legal Huffman code tree. }
449 code := 0;
450 si := huffsize[0];
451 p := 0;
452 while (huffsize[p] <> 0) do
453 begin
454 while (( int (huffsize[p]) ) = si) do
455 begin
456 huffcode[p] := code;
457 Inc(p);
458 Inc(code);
459 end;
460 { code is now 1 more than the last code used for codelength si; but
461 it must still fit in si bits, since no code is allowed to be all ones. }
463 if (INT32(code) >= (INT32(1) shl si)) then
464 ERREXIT(j_common_ptr(cinfo), JERR_BAD_HUFF_TABLE);
466 code := code shl 1;
467 Inc(si);
468 end;
470 { Figure F.15: generate decoding tables for bit-sequential decoding }
472 p := 0;
473 for l := 1 to 16 do
474 begin
475 if (htbl^.bits[l] <> 0) then
476 begin
477 { valoffset[l] = huffval[] index of 1st symbol of code length l,
478 minus the minimum code of length l }
480 dtbl^.valoffset[l] := INT32(p) - INT32(huffcode[p]);
481 Inc(p, htbl^.bits[l]);
482 dtbl^.maxcode[l] := huffcode[p-1]; { maximum code of length l }
483 end
484 else
485 begin
486 dtbl^.maxcode[l] := -1; { -1 if no codes of this length }
487 end;
488 end;
489 dtbl^.maxcode[17] := long($FFFFF); { ensures jpeg_huff_decode terminates }
491 { Compute lookahead tables to speed up decoding.
492 First we set all the table entries to 0, indicating "too long";
493 then we iterate through the Huffman codes that are short enough and
494 fill in all the entries that correspond to bit sequences starting
495 with that code. }
497 MEMZERO(@dtbl^.look_nbits, SIZEOF(dtbl^.look_nbits));
499 p := 0;
500 for l := 1 to HUFF_LOOKAHEAD do
501 begin
502 for i := 1 to int (htbl^.bits[l]) do
503 begin
504 { l := current code's length, p := its index in huffcode[] & huffval[]. }
505 { Generate left-justified code followed by all possible bit sequences }
506 lookbits := huffcode[p] shl (HUFF_LOOKAHEAD-l);
507 for ctr := pred(1 shl (HUFF_LOOKAHEAD-l)) downto 0 do
508 begin
509 dtbl^.look_nbits[lookbits] := l;
510 dtbl^.look_sym[lookbits] := htbl^.huffval[p];
511 Inc(lookbits);
512 end;
513 Inc(p);
514 end;
515 end;
517 { Validate symbols as being reasonable.
518 For AC tables, we make no check, but accept all byte values 0..255.
519 For DC tables, we require the symbols to be in range 0..15.
520 (Tighter bounds could be applied depending on the data depth and mode,
521 but this is sufficient to ensure safe decoding.) }
523 if (isDC) then
524 begin
525 for i := 0 to pred(numsymbols) do
526 begin
527 sym := htbl^.huffval[i];
528 if (sym < 0) or (sym > 15) then
529 ERREXIT(j_common_ptr(cinfo), JERR_BAD_HUFF_TABLE);
530 end;
531 end;
532 end;
535 { Out-of-line code for bit fetching (shared with jdphuff.c).
536 See jdhuff.h for info about usage.
537 Note: current values of get_buffer and bits_left are passed as parameters,
538 but are returned in the corresponding fields of the state struct.
540 On most machines MIN_GET_BITS should be 25 to allow the full 32-bit width
541 of get_buffer to be used. (On machines with wider words, an even larger
542 buffer could be used.) However, on some machines 32-bit shifts are
543 quite slow and take time proportional to the number of places shifted.
544 (This is true with most PC compilers, for instance.) In this case it may
545 be a win to set MIN_GET_BITS to the minimum value of 15. This reduces the
546 average shift distance at the cost of more calls to jpeg_fill_bit_buffer. }
548 {$ifdef SLOW_SHIFT_32}
549 const
550 MIN_GET_BITS = 15; { minimum allowable value }
551 {$else}
552 const
553 MIN_GET_BITS = (BIT_BUF_SIZE-7);
554 {$endif}
557 {GLOBAL}
558 function jpeg_fill_bit_buffer (var state : bitread_working_state;
559 {register} get_buffer : bit_buf_type;
560 {register} bits_left : int;
561 nbits : int) : boolean;
562 label
563 no_more_bytes;
564 { Load up the bit buffer to a depth of at least nbits }
565 var
566 { Copy heavily used state fields into locals (hopefully registers) }
567 {register} next_input_byte : {const} JOCTETptr;
568 {register} bytes_in_buffer : size_t;
569 var
570 {register} c : int;
571 var
572 cinfo : j_decompress_ptr;
573 begin
574 next_input_byte := state.next_input_byte;
575 bytes_in_buffer := state.bytes_in_buffer;
576 cinfo := state.cinfo;
578 { Attempt to load at least MIN_GET_BITS bits into get_buffer. }
579 { (It is assumed that no request will be for more than that many bits.) }
580 { We fail to do so only if we hit a marker or are forced to suspend. }
582 if (cinfo^.unread_marker = 0) then { cannot advance past a marker }
583 begin
584 while (bits_left < MIN_GET_BITS) do
585 begin
586 { Attempt to read a byte }
587 if (bytes_in_buffer = 0) then
588 begin
589 if not cinfo^.src^.fill_input_buffer(cinfo) then
590 begin
591 jpeg_fill_bit_buffer := FALSE;
592 exit;
593 end;
594 next_input_byte := cinfo^.src^.next_input_byte;
595 bytes_in_buffer := cinfo^.src^.bytes_in_buffer;
596 end;
597 Dec(bytes_in_buffer);
598 c := GETJOCTET(next_input_byte^);
599 Inc(next_input_byte);
602 { If it's $FF, check and discard stuffed zero byte }
603 if (c = $FF) then
604 begin
605 { Loop here to discard any padding FF's on terminating marker,
606 so that we can save a valid unread_marker value. NOTE: we will
607 accept multiple FF's followed by a 0 as meaning a single FF data
608 byte. This data pattern is not valid according to the standard. }
610 repeat
611 if (bytes_in_buffer = 0) then
612 begin
613 if (not state.cinfo^.src^.fill_input_buffer (state.cinfo)) then
614 begin
615 jpeg_fill_bit_buffer := FALSE;
616 exit;
617 end;
618 next_input_byte := state.cinfo^.src^.next_input_byte;
619 bytes_in_buffer := state.cinfo^.src^.bytes_in_buffer;
620 end;
621 Dec(bytes_in_buffer);
622 c := GETJOCTET(next_input_byte^);
623 Inc(next_input_byte);
624 Until (c <> $FF);
626 if (c = 0) then
627 begin
628 { Found FF/00, which represents an FF data byte }
629 c := $FF;
630 end
631 else
632 begin
633 { Oops, it's actually a marker indicating end of compressed data.
634 Save the marker code for later use.
635 Fine point: it might appear that we should save the marker into
636 bitread working state, not straight into permanent state. But
637 once we have hit a marker, we cannot need to suspend within the
638 current MCU, because we will read no more bytes from the data
639 source. So it is OK to update permanent state right away. }
641 cinfo^.unread_marker := c;
642 { See if we need to insert some fake zero bits. }
643 goto no_more_bytes;
644 end;
645 end;
647 { OK, load c into get_buffer }
648 get_buffer := (get_buffer shl 8) or c;
649 Inc(bits_left, 8);
650 end { end while }
651 end
652 else
653 begin
654 no_more_bytes:
655 { We get here if we've read the marker that terminates the compressed
656 data segment. There should be enough bits in the buffer register
657 to satisfy the request; if so, no problem. }
659 if (nbits > bits_left) then
660 begin
661 { Uh-oh. Report corrupted data to user and stuff zeroes into
662 the data stream, so that we can produce some kind of image.
663 We use a nonvolatile flag to ensure that only one warning message
664 appears per data segment. }
666 if not cinfo^.entropy^.insufficient_data then
667 begin
668 WARNMS(j_common_ptr(cinfo), JWRN_HIT_MARKER);
669 cinfo^.entropy^.insufficient_data := TRUE;
670 end;
671 { Fill the buffer with zero bits }
672 get_buffer := get_buffer shl (MIN_GET_BITS - bits_left);
673 bits_left := MIN_GET_BITS;
674 end;
675 end;
677 { Unload the local registers }
678 state.next_input_byte := next_input_byte;
679 state.bytes_in_buffer := bytes_in_buffer;
680 state.get_buffer := get_buffer;
681 state.bits_left := bits_left;
683 jpeg_fill_bit_buffer := TRUE;
684 end;
687 { Out-of-line code for Huffman code decoding.
688 See jdhuff.h for info about usage. }
690 {GLOBAL}
691 function jpeg_huff_decode (var state : bitread_working_state;
692 {register} get_buffer : bit_buf_type;
693 {register} bits_left : int;
694 htbl : d_derived_tbl_ptr;
695 min_bits : int) : int;
696 var
697 {register} l : int;
698 {register} code : INT32;
699 begin
700 l := min_bits;
702 { HUFF_DECODE has determined that the code is at least min_bits }
703 { bits long, so fetch that many bits in one swoop. }
705 {CHECK_BIT_BUFFER(state, l, return -1);}
706 if (bits_left < l) then
707 begin
708 if (not jpeg_fill_bit_buffer(state, get_buffer, bits_left, l)) then
709 begin
710 jpeg_huff_decode := -1;
711 exit;
712 end;
713 get_buffer := state.get_buffer;
714 bits_left := state.bits_left;
715 end;
717 {code := GET_BITS(l);}
718 Dec(bits_left, l);
719 code := (int(get_buffer shr bits_left)) and ( pred(1 shl l) );
721 { Collect the rest of the Huffman code one bit at a time. }
722 { This is per Figure F.16 in the JPEG spec. }
724 while (code > htbl^.maxcode[l]) do
725 begin
726 code := code shl 1;
727 {CHECK_BIT_BUFFER(state, 1, return -1);}
728 if (bits_left < 1) then
729 begin
730 if (not jpeg_fill_bit_buffer(state, get_buffer, bits_left, 1)) then
731 begin
732 jpeg_huff_decode := -1;
733 exit;
734 end;
735 get_buffer := state.get_buffer;
736 bits_left := state.bits_left;
737 end;
739 {code := code or GET_BITS(1);}
740 Dec(bits_left);
741 code := code or ( (int(get_buffer shr bits_left)) and pred(1 shl 1) );
743 Inc(l);
744 end;
746 { Unload the local registers }
747 state.get_buffer := get_buffer;
748 state.bits_left := bits_left;
750 { With garbage input we may reach the sentinel value l := 17. }
752 if (l > 16) then
753 begin
754 WARNMS(j_common_ptr(state.cinfo), JWRN_HUFF_BAD_CODE);
755 jpeg_huff_decode := 0; { fake a zero as the safest result }
756 exit;
757 end;
759 jpeg_huff_decode := htbl^.pub^.huffval[ int (code + htbl^.valoffset[l]) ];
760 end;
763 { Figure F.12: extend sign bit.
764 On some machines, a shift and add will be faster than a table lookup. }
766 {$ifdef AVOID_TABLES}
768 #define HUFF_EXTEND(x,s) ((x) < (1<<((s)-1)) ? (x) + (((-1)<<(s)) + 1) : (x))
770 {$else}
772 {$define HUFF_EXTEND(x,s)
773 if (x < extend_test[s]) then
774 := x + extend_offset[s]
775 else
776 x;}
778 const
779 extend_test : array[0..16-1] of int = { entry n is 2**(n-1) }
780 ($0000, $0001, $0002, $0004, $0008, $0010, $0020, $0040,
781 $0080, $0100, $0200, $0400, $0800, $1000, $2000, $4000);
783 const
784 extend_offset : array[0..16-1] of int = { entry n is (-1 << n) + 1 }
785 (0, ((-1) shl 1) + 1, ((-1) shl 2) + 1, ((-1) shl 3) + 1, ((-1) shl 4) + 1,
786 ((-1) shl 5) + 1, ((-1) shl 6) + 1, ((-1) shl 7) + 1, ((-1) shl 8) + 1,
787 ((-1) shl 9) + 1, ((-1) shl 10) + 1, ((-1) shl 11) + 1,((-1) shl 12) + 1,
788 ((-1) shl 13) + 1, ((-1) shl 14) + 1, ((-1) shl 15) + 1);
790 {$endif} { AVOID_TABLES }
793 { Check for a restart marker & resynchronize decoder.
794 Returns FALSE if must suspend. }
796 {LOCAL}
797 function process_restart (cinfo : j_decompress_ptr) : boolean;
798 var
799 entropy : huff_entropy_ptr;
800 ci : int;
801 begin
802 entropy := huff_entropy_ptr (cinfo^.entropy);
804 { Throw away any unused bits remaining in bit buffer; }
805 { include any full bytes in next_marker's count of discarded bytes }
806 Inc(cinfo^.marker^.discarded_bytes, entropy^.bitstate.bits_left div 8);
807 entropy^.bitstate.bits_left := 0;
809 { Advance past the RSTn marker }
810 if (not cinfo^.marker^.read_restart_marker (cinfo)) then
811 begin
812 process_restart := FALSE;
813 exit;
814 end;
816 { Re-initialize DC predictions to 0 }
817 for ci := 0 to pred(cinfo^.comps_in_scan) do
818 entropy^.saved.last_dc_val[ci] := 0;
820 { Reset restart counter }
821 entropy^.restarts_to_go := cinfo^.restart_interval;
823 { Reset out-of-data flag, unless read_restart_marker left us smack up
824 against a marker. In that case we will end up treating the next data
825 segment as empty, and we can avoid producing bogus output pixels by
826 leaving the flag set. }
828 if (cinfo^.unread_marker = 0) then
829 entropy^.pub.insufficient_data := FALSE;
831 process_restart := TRUE;
832 end;
835 { Decode and return one MCU's worth of Huffman-compressed coefficients.
836 The coefficients are reordered from zigzag order into natural array order,
837 but are not dequantized.
839 The i'th block of the MCU is stored into the block pointed to by
840 MCU_data[i]. WE ASSUME THIS AREA HAS BEEN ZEROED BY THE CALLER.
841 (Wholesale zeroing is usually a little faster than retail...)
843 Returns FALSE if data source requested suspension. In that case no
844 changes have been made to permanent state. (Exception: some output
845 coefficients may already have been assigned. This is harmless for
846 this module, since we'll just re-assign them on the next call.) }
848 {METHODDEF}
849 function decode_mcu (cinfo : j_decompress_ptr;
850 var MCU_data : array of JBLOCKROW) : boolean;
851 label
852 label1, label2, label3;
853 var
854 entropy : huff_entropy_ptr;
855 {register} s, k, r : int;
856 blkn, ci : int;
857 block : JBLOCK_PTR;
858 {BITREAD_STATE_VARS}
859 get_buffer : bit_buf_type ; {register}
860 bits_left : int; {register}
861 br_state : bitread_working_state;
863 state : savable_state;
864 dctbl : d_derived_tbl_ptr;
865 actbl : d_derived_tbl_ptr;
866 var
867 nb, look : int; {register}
868 begin
869 entropy := huff_entropy_ptr (cinfo^.entropy);
871 { Process restart marker if needed; may have to suspend }
872 if (cinfo^.restart_interval <> 0) then
873 begin
874 if (entropy^.restarts_to_go = 0) then
875 if (not process_restart(cinfo)) then
876 begin
877 decode_mcu := FALSE;
878 exit;
879 end;
880 end;
882 { If we've run out of data, just leave the MCU set to zeroes.
883 This way, we return uniform gray for the remainder of the segment. }
885 if not entropy^.pub.insufficient_data then
886 begin
888 { Load up working state }
889 {BITREAD_LOAD_STATE(cinfo,entropy^.bitstate);}
890 br_state.cinfo := cinfo;
891 br_state.next_input_byte := cinfo^.src^.next_input_byte;
892 br_state.bytes_in_buffer := cinfo^.src^.bytes_in_buffer;
893 get_buffer := entropy^.bitstate.get_buffer;
894 bits_left := entropy^.bitstate.bits_left;
896 {ASSIGN_STATE(state, entropy^.saved);}
897 state := entropy^.saved;
899 { Outer loop handles each block in the MCU }
901 for blkn := 0 to pred(cinfo^.blocks_in_MCU) do
902 begin
903 block := JBLOCK_PTR(MCU_data[blkn]);
904 dctbl := entropy^.dc_cur_tbls[blkn];
905 actbl := entropy^.ac_cur_tbls[blkn];
907 { Decode a single block's worth of coefficients }
909 { Section F.2.2.1: decode the DC coefficient difference }
910 {HUFF_DECODE(s, br_state, dctbl, return FALSE, label1);}
911 if (bits_left < HUFF_LOOKAHEAD) then
912 begin
913 if (not jpeg_fill_bit_buffer(br_state,get_buffer,bits_left, 0)) then
914 begin
915 decode_mcu := False;
916 exit;
917 end;
918 get_buffer := br_state.get_buffer;
919 bits_left := br_state.bits_left;
920 if (bits_left < HUFF_LOOKAHEAD) then
921 begin
922 nb := 1;
923 goto label1;
924 end;
925 end;
926 {look := PEEK_BITS(HUFF_LOOKAHEAD);}
927 look := int(get_buffer shr (bits_left - HUFF_LOOKAHEAD)) and
928 pred(1 shl HUFF_LOOKAHEAD);
930 nb := dctbl^.look_nbits[look];
931 if (nb <> 0) then
932 begin
933 {DROP_BITS(nb);}
934 Dec(bits_left, nb);
936 s := dctbl^.look_sym[look];
937 end
938 else
939 begin
940 nb := HUFF_LOOKAHEAD+1;
941 label1:
942 s := jpeg_huff_decode(br_state,get_buffer,bits_left,dctbl,nb);
943 if (s < 0) then
944 begin
945 decode_mcu := FALSE;
946 exit;
947 end;
948 get_buffer := br_state.get_buffer;
949 bits_left := br_state.bits_left;
950 end;
952 if (s <> 0) then
953 begin
954 {CHECK_BIT_BUFFER(br_state, s, return FALSE);}
955 if (bits_left < s) then
956 begin
957 if (not jpeg_fill_bit_buffer(br_state,get_buffer,bits_left,s)) then
958 begin
959 decode_mcu := FALSE;
960 exit;
961 end;
962 get_buffer := br_state.get_buffer;
963 bits_left := br_state.bits_left;
964 end;
966 {r := GET_BITS(s);}
967 Dec(bits_left, s);
968 r := ( int(get_buffer shr bits_left)) and ( pred(1 shl s) );
970 {s := HUFF_EXTEND(r, s);}
971 if (r < extend_test[s]) then
972 s := r + extend_offset[s]
973 else
974 s := r;
975 end;
977 if (entropy^.dc_needed[blkn]) then
978 begin
979 { Convert DC difference to actual value, update last_dc_val }
980 ci := cinfo^.MCU_membership[blkn];
981 Inc(s, state.last_dc_val[ci]);
982 state.last_dc_val[ci] := s;
983 { Output the DC coefficient (assumes jpeg_natural_order[0] := 0) }
984 block^[0] := JCOEF (s);
985 end;
987 if (entropy^.ac_needed[blkn]) then
988 begin
990 { Section F.2.2.2: decode the AC coefficients }
991 { Since zeroes are skipped, output area must be cleared beforehand }
992 k := 1;
993 while (k < DCTSIZE2) do { Nomssi: k is incr. in the loop }
994 begin
995 {HUFF_DECODE(s, br_state, actbl, return FALSE, label2);}
996 if (bits_left < HUFF_LOOKAHEAD) then
997 begin
998 if (not jpeg_fill_bit_buffer(br_state,get_buffer,bits_left, 0)) then
999 begin
1000 decode_mcu := False;
1001 exit;
1002 end;
1003 get_buffer := br_state.get_buffer;
1004 bits_left := br_state.bits_left;
1005 if (bits_left < HUFF_LOOKAHEAD) then
1006 begin
1007 nb := 1;
1008 goto label2;
1009 end;
1010 end;
1011 {look := PEEK_BITS(HUFF_LOOKAHEAD);}
1012 look := int(get_buffer shr (bits_left - HUFF_LOOKAHEAD)) and
1013 pred(1 shl HUFF_LOOKAHEAD);
1015 nb := actbl^.look_nbits[look];
1016 if (nb <> 0) then
1017 begin
1018 {DROP_BITS(nb);}
1019 Dec(bits_left, nb);
1021 s := actbl^.look_sym[look];
1022 end
1023 else
1024 begin
1025 nb := HUFF_LOOKAHEAD+1;
1026 label2:
1027 s := jpeg_huff_decode(br_state,get_buffer,bits_left,actbl,nb);
1028 if (s < 0) then
1029 begin
1030 decode_mcu := FALSE;
1031 exit;
1032 end;
1033 get_buffer := br_state.get_buffer;
1034 bits_left := br_state.bits_left;
1035 end;
1037 r := s shr 4;
1038 s := s and 15;
1040 if (s <> 0) then
1041 begin
1042 Inc(k, r);
1043 {CHECK_BIT_BUFFER(br_state, s, return FALSE);}
1044 if (bits_left < s) then
1045 begin
1046 if (not jpeg_fill_bit_buffer(br_state,get_buffer,bits_left,s)) then
1047 begin
1048 decode_mcu := FALSE;
1049 exit;
1050 end;
1051 get_buffer := br_state.get_buffer;
1052 bits_left := br_state.bits_left;
1053 end;
1055 {r := GET_BITS(s);}
1056 Dec(bits_left, s);
1057 r := (int(get_buffer shr bits_left)) and ( pred(1 shl s) );
1059 {s := HUFF_EXTEND(r, s);}
1060 if (r < extend_test[s]) then
1061 s := r + extend_offset[s]
1062 else
1063 s := r;
1064 { Output coefficient in natural (dezigzagged) order.
1065 Note: the extra entries in jpeg_natural_order[] will save us
1066 if k >= DCTSIZE2, which could happen if the data is corrupted. }
1068 block^[jpeg_natural_order[k]] := JCOEF (s);
1069 end
1070 else
1071 begin
1072 if (r <> 15) then
1073 break;
1074 Inc(k, 15);
1075 end;
1076 Inc(k);
1077 end;
1078 end
1079 else
1080 begin
1082 { Section F.2.2.2: decode the AC coefficients }
1083 { In this path we just discard the values }
1084 k := 1;
1085 while (k < DCTSIZE2) do
1086 begin
1087 {HUFF_DECODE(s, br_state, actbl, return FALSE, label3);}
1088 if (bits_left < HUFF_LOOKAHEAD) then
1089 begin
1090 if (not jpeg_fill_bit_buffer(br_state,get_buffer,bits_left, 0)) then
1091 begin
1092 decode_mcu := False;
1093 exit;
1094 end;
1095 get_buffer := br_state.get_buffer;
1096 bits_left := br_state.bits_left;
1097 if (bits_left < HUFF_LOOKAHEAD) then
1098 begin
1099 nb := 1;
1100 goto label3;
1101 end;
1102 end;
1103 {look := PEEK_BITS(HUFF_LOOKAHEAD);}
1104 look := int(get_buffer shr (bits_left - HUFF_LOOKAHEAD)) and
1105 pred(1 shl HUFF_LOOKAHEAD);
1107 nb := actbl^.look_nbits[look];
1108 if (nb <> 0) then
1109 begin
1110 {DROP_BITS(nb);}
1111 Dec(bits_left, nb);
1113 s := actbl^.look_sym[look];
1114 end
1115 else
1116 begin
1117 nb := HUFF_LOOKAHEAD+1;
1118 label3:
1119 s := jpeg_huff_decode(br_state,get_buffer,bits_left,actbl,nb);
1120 if (s < 0) then
1121 begin
1122 decode_mcu := FALSE;
1123 exit;
1124 end;
1125 get_buffer := br_state.get_buffer;
1126 bits_left := br_state.bits_left;
1127 end;
1129 r := s shr 4;
1130 s := s and 15;
1132 if (s <> 0) then
1133 begin
1134 Inc(k, r);
1135 {CHECK_BIT_BUFFER(br_state, s, return FALSE);}
1136 if (bits_left < s) then
1137 begin
1138 if (not jpeg_fill_bit_buffer(br_state,get_buffer,bits_left,s)) then
1139 begin
1140 decode_mcu := FALSE;
1141 exit;
1142 end;
1143 get_buffer := br_state.get_buffer;
1144 bits_left := br_state.bits_left;
1145 end;
1147 {DROP_BITS(s);}
1148 Dec(bits_left, s);
1149 end
1150 else
1151 begin
1152 if (r <> 15) then
1153 break;
1154 Inc(k, 15);
1155 end;
1156 Inc(k);
1157 end;
1159 end;
1160 end;
1162 { Completed MCU, so update state }
1163 {BITREAD_SAVE_STATE(cinfo,entropy^.bitstate);}
1164 cinfo^.src^.next_input_byte := br_state.next_input_byte;
1165 cinfo^.src^.bytes_in_buffer := br_state.bytes_in_buffer;
1166 entropy^.bitstate.get_buffer := get_buffer;
1167 entropy^.bitstate.bits_left := bits_left;
1169 {ASSIGN_STATE(entropy^.saved, state);}
1170 entropy^.saved := state;
1172 end;
1174 { Account for restart interval (no-op if not using restarts) }
1175 Dec(entropy^.restarts_to_go);
1177 decode_mcu := TRUE;
1178 end;
1181 { Module initialization routine for Huffman entropy decoding. }
1183 {GLOBAL}
1184 procedure jinit_huff_decoder (cinfo : j_decompress_ptr);
1185 var
1186 entropy : huff_entropy_ptr;
1187 i : int;
1188 begin
1189 entropy := huff_entropy_ptr(
1190 cinfo^.mem^.alloc_small (j_common_ptr(cinfo), JPOOL_IMAGE,
1191 SIZEOF(huff_entropy_decoder)) );
1192 cinfo^.entropy := jpeg_entropy_decoder_ptr (entropy);
1193 entropy^.pub.start_pass := start_pass_huff_decoder;
1194 entropy^.pub.decode_mcu := decode_mcu;
1196 { Mark tables unallocated }
1197 for i := 0 to pred(NUM_HUFF_TBLS) do
1198 begin
1199 entropy^.dc_derived_tbls[i] := NIL;
1200 entropy^.ac_derived_tbls[i] := NIL;
1201 end;
1202 end;
1204 end.