1 Unit JcMaster;
2 
3 { This file contains master control logic for the JPEG compressor.
4   These routines are concerned with parameter validation, initial setup,
5   and inter-pass control (determining the number of passes and the work
6   to be done in each pass). }
7 
8 { Original: jcmaster.c ; Copyright (C) 1991-1997, Thomas G. Lane. }
9 
10 interface
11 
12 {$I jconfig.inc}
13 
14 uses
15   jmorecfg,
16   jinclude,
17   jdeferr,
18   jerror,
19   jutils,
20   jpeglib;
21 
22 
23 { Initialize master compression control. }
24 
25 {GLOBAL}
26 procedure jinit_c_master_control (cinfo : j_compress_ptr;
27                                   transcode_only : boolean);
28 
29 implementation
30 
31 { Private state }
32 
33 type
34   c_pass_type = (
35         main_pass,              { input data, also do first output step }
36         huff_opt_pass,          { Huffman code optimization pass }
37         output_pass             { data output pass }
38                 );
39 
40 type
41   my_master_ptr = ^my_comp_master;
42   my_comp_master = record
43     pub : jpeg_comp_master;     { public fields }
44 
45     pass_type : c_pass_type;    { the type of the current pass }
46 
47     pass_number : int;          { # of passes completed }
48     total_passes : int;         { total # of passes needed }
49 
50     scan_number : int;          { current index in scan_info[] }
51   end;
52 
53 
54 { Support routines that do various essential calculations. }
55 
56 {LOCAL}
57 procedure initial_setup (cinfo : j_compress_ptr);
58 { Do computations that are needed before master selection phase }
59 var
60   ci : int;
61   compptr : jpeg_component_info_ptr;
62   samplesperrow : long;
63   jd_samplesperrow : JDIMENSION;
64 begin
65 
66   { Sanity check on image dimensions }
67   if (cinfo^.image_height <= 0) or (cinfo^.image_width <= 0) or
68      (cinfo^.num_components <= 0) or (cinfo^.input_components <= 0) then
69     ERREXIT(j_common_ptr(cinfo), JERR_EMPTY_IMAGE);
70 
71   { Make sure image isn't bigger than I can handle }
72   if ( long(cinfo^.image_height) > long(JPEG_MAX_DIMENSION)) or
73       ( long(cinfo^.image_width) > long(JPEG_MAX_DIMENSION)) then
74     ERREXIT1(j_common_ptr(cinfo), JERR_IMAGE_TOO_BIG,
75                                   uInt(JPEG_MAX_DIMENSION));
76 
77   { Width of an input scanline must be representable as JDIMENSION. }
78   samplesperrow := long (cinfo^.image_width) * long (cinfo^.input_components);
79   jd_samplesperrow := JDIMENSION (samplesperrow);
80   if ( long(jd_samplesperrow) <> samplesperrow) then
81     ERREXIT(j_common_ptr(cinfo), JERR_WIDTH_OVERFLOW);
82 
83   { For now, precision must match compiled-in value... }
84   if (cinfo^.data_precision <> BITS_IN_JSAMPLE) then
85     ERREXIT1(j_common_ptr(cinfo), JERR_BAD_PRECISION, cinfo^.data_precision);
86 
87   { Check that number of components won't exceed internal array sizes }
88   if (cinfo^.num_components > MAX_COMPONENTS) then
89     ERREXIT2(j_common_ptr(cinfo), JERR_COMPONENT_COUNT, cinfo^.num_components,
90              MAX_COMPONENTS);
91 
92   { Compute maximum sampling factors; check factor validity }
93   cinfo^.max_h_samp_factor := 1;
94   cinfo^.max_v_samp_factor := 1;
95   compptr := jpeg_component_info_ptr(cinfo^.comp_info);
96   for ci := 0 to pred(cinfo^.num_components) do
97   begin
98     if (compptr^.h_samp_factor<=0) or (compptr^.h_samp_factor>MAX_SAMP_FACTOR)
99     or (compptr^.v_samp_factor<=0) or (compptr^.v_samp_factor>MAX_SAMP_FACTOR) then
100       ERREXIT(j_common_ptr(cinfo), JERR_BAD_SAMPLING);
101     { MAX }
102     if cinfo^.max_h_samp_factor > compptr^.h_samp_factor then
103       cinfo^.max_h_samp_factor := cinfo^.max_h_samp_factor
104     else
105       cinfo^.max_h_samp_factor := compptr^.h_samp_factor;
106     { MAX }
107     if cinfo^.max_v_samp_factor > compptr^.v_samp_factor then
108       cinfo^.max_v_samp_factor := cinfo^.max_v_samp_factor
109     else
110       cinfo^.max_v_samp_factor := compptr^.v_samp_factor;
111     Inc(compptr);
112   end;
113 
114   { Compute dimensions of components }
115   compptr := jpeg_component_info_ptr(cinfo^.comp_info);
116   for ci := 0 to pred(cinfo^.num_components) do
117   begin
118     { Fill in the correct component_index value; don't rely on application }
119     compptr^.component_index := ci;
120     { For compression, we never do DCT scaling. }
121     compptr^.DCT_scaled_size := DCTSIZE;
122     { Size in DCT blocks }
123     compptr^.width_in_blocks := JDIMENSION (
124       jdiv_round_up(long (cinfo^.image_width) * long (compptr^.h_samp_factor),
125                     long (cinfo^.max_h_samp_factor * DCTSIZE)) );
126     compptr^.height_in_blocks := JDIMENSION (
127       jdiv_round_up(long (cinfo^.image_height) * long (compptr^.v_samp_factor),
128                     long (cinfo^.max_v_samp_factor * DCTSIZE)) );
129     { Size in samples }
130     compptr^.downsampled_width := JDIMENSION (
131       jdiv_round_up(long(cinfo^.image_width) * long(compptr^.h_samp_factor),
132                     long(cinfo^.max_h_samp_factor)) );
133     compptr^.downsampled_height := JDIMENSION (
134       jdiv_round_up(long (cinfo^.image_height) * long(compptr^.v_samp_factor),
135                     long (cinfo^.max_v_samp_factor)) );
136     { Mark component needed (this flag isn't actually used for compression) }
137     compptr^.component_needed := TRUE;
138     Inc(compptr);
139   end;
140 
141   { Compute number of fully interleaved MCU rows (number of times that
142     main controller will call coefficient controller). }
143 
144   cinfo^.total_iMCU_rows := JDIMENSION (
145     jdiv_round_up(long (cinfo^.image_height),
146                   long (cinfo^.max_v_samp_factor*DCTSIZE)) );
147 end;
148 
149 
150 {$ifdef C_MULTISCAN_FILES_SUPPORTED}
151 
152 {LOCAL}
153 procedure validate_script (cinfo : j_compress_ptr);
154 { Verify that the scan script in cinfo^.scan_info[] is valid; also
155   determine whether it uses progressive JPEG, and set cinfo^.progressive_mode. }
156 type
157   IntRow = array[0..DCTSIZE2-1] of int;
158   introw_ptr = ^IntRow;
159 var
160   {const}scanptr : jpeg_scan_info_ptr;
161   scanno, ncomps, ci, coefi, thisi : int;
162   Ss, Se, Ah, Al : int;
163   component_sent : array[0..MAX_COMPONENTS-1] of boolean;
164 {$ifdef C_PROGRESSIVE_SUPPORTED}
165   last_bitpos_int_ptr : int_ptr;
166   last_bitpos_ptr : introw_ptr;
167   last_bitpos : array[0..MAX_COMPONENTS-1] of IntRow;
168   { -1 until that coefficient has been seen; then last Al for it }
169   { The JPEG spec simply gives the ranges 0..13 for Ah and Al, but that
170     seems wrong: the upper bound ought to depend on data precision.
171     Perhaps they really meant 0..N+1 for N-bit precision.
172     Here we allow 0..10 for 8-bit data; Al larger than 10 results in
173     out-of-range reconstructed DC values during the first DC scan,
174     which might cause problems for some decoders. }
175 {$ifdef BITS_IN_JSAMPLE_IS_8}
176 const
177   MAX_AH_AL = 10;
178 {$else}
179 const
180   MAX_AH_AL = 13;
181 {$endif}
182 {$endif}
183 begin
184 
185   if (cinfo^.num_scans <= 0) then
186     ERREXIT1(j_common_ptr(cinfo), JERR_BAD_SCAN_SCRIPT, 0);
187 
188   { For sequential JPEG, all scans must have Ss=0, Se=DCTSIZE2-1;
189     for progressive JPEG, no scan can have this. }
190 
191   scanptr := cinfo^.scan_info;
192   if (scanptr^.Ss <> 0) or (scanptr^.Se <> DCTSIZE2-1) then
193   begin
194 {$ifdef C_PROGRESSIVE_SUPPORTED}
195     cinfo^.progressive_mode := TRUE;
196     last_bitpos_int_ptr := @(last_bitpos[0][0]);
197     for ci := 0 to pred(cinfo^.num_components) do
198       for coefi := 0 to pred(DCTSIZE2) do
199       begin
200         last_bitpos_int_ptr^ := -1;
201         Inc(last_bitpos_int_ptr);
202       end;
203 {$else}
204     ERREXIT(j_common_ptr(cinfo), JERR_NOT_COMPILED);
205 {$endif}
206   end
207   else
208   begin
209     cinfo^.progressive_mode := FALSE;
210     for ci := 0 to pred(cinfo^.num_components) do
211       component_sent[ci] := FALSE;
212   end;
213 
214   for scanno := 1 to cinfo^.num_scans do
215   begin
216     { Validate component indexes }
217     ncomps := scanptr^.comps_in_scan;
218     if (ncomps <= 0) or (ncomps > MAX_COMPS_IN_SCAN) then
219       ERREXIT2(j_common_ptr(cinfo), JERR_COMPONENT_COUNT, ncomps, MAX_COMPS_IN_SCAN);
220     for ci := 0 to pred(ncomps) do
221     begin
222       thisi := scanptr^.component_index[ci];
223       if (thisi < 0) or (thisi >= cinfo^.num_components) then
224         ERREXIT1(j_common_ptr(cinfo), JERR_BAD_SCAN_SCRIPT, scanno);
225       { Components must appear in SOF order within each scan }
226       if (ci > 0) and (thisi <= scanptr^.component_index[ci-1]) then
227         ERREXIT1(j_common_ptr(cinfo), JERR_BAD_SCAN_SCRIPT, scanno);
228     end;
229     { Validate progression parameters }
230     Ss := scanptr^.Ss;
231     Se := scanptr^.Se;
232     Ah := scanptr^.Ah;
233     Al := scanptr^.Al;
234     if (cinfo^.progressive_mode) then
235     begin
236 {$ifdef C_PROGRESSIVE_SUPPORTED}
237       if (Ss < 0) or (Ss >= DCTSIZE2) or (Se < Ss) or (Se >= DCTSIZE2) or
238          (Ah < 0) or (Ah > MAX_AH_AL) or (Al < 0) or (Al > MAX_AH_AL) then
239         ERREXIT1(j_common_ptr(cinfo), JERR_BAD_PROG_SCRIPT, scanno);
240 
241       if (Ss < 0) or (Ss >= DCTSIZE2) or (Se < Ss) or (Se >= DCTSIZE2)
242        or (Ah < 0) or (Ah > MAX_AH_AL) or (Al < 0) or (Al > MAX_AH_AL) then
243         ERREXIT1(j_common_ptr(cinfo), JERR_BAD_PROG_SCRIPT, scanno);
244       if (Ss = 0) then
245       begin
246         if (Se <> 0) then       { DC and AC together not OK }
247           ERREXIT1(j_common_ptr(cinfo), JERR_BAD_PROG_SCRIPT, scanno);
248       end
249       else
250       begin
251         if (ncomps <> 1) then  { AC scans must be for only one component }
252           ERREXIT1(j_common_ptr(cinfo), JERR_BAD_PROG_SCRIPT, scanno);
253       end;
254       for ci := 0 to pred(ncomps) do
255       begin
256         last_bitpos_ptr := @( last_bitpos[scanptr^.component_index[ci]]);
257         if (Ss <> 0) and (last_bitpos_ptr^[0] < 0) then { AC without prior DC scan }
258           ERREXIT1(j_common_ptr(cinfo), JERR_BAD_PROG_SCRIPT, scanno);
259         for coefi := Ss to Se do
260         begin
261           if (last_bitpos_ptr^[coefi] < 0) then
262           begin
263             { first scan of this coefficient }
264             if (Ah <> 0) then
265               ERREXIT1(j_common_ptr(cinfo), JERR_BAD_PROG_SCRIPT, scanno);
266           end
267           else
268           begin
269             { not first scan }
270             if (Ah <> last_bitpos_ptr^[coefi]) or (Al <> Ah-1) then
271               ERREXIT1(j_common_ptr(cinfo), JERR_BAD_PROG_SCRIPT, scanno);
272           end;
273           last_bitpos_ptr^[coefi] := Al;
274         end;
275       end;
276 {$endif}
277     end
278     else
279     begin
280       { For sequential JPEG, all progression parameters must be these: }
281       if (Ss <> 0) or (Se <> DCTSIZE2-1) or (Ah <> 0) or (Al <> 0) then
282         ERREXIT1(j_common_ptr(cinfo), JERR_BAD_PROG_SCRIPT, scanno);
283       { Make sure components are not sent twice }
284       for ci := 0 to pred(ncomps) do
285       begin
286         thisi := scanptr^.component_index[ci];
287         if (component_sent[thisi]) then
288           ERREXIT1(j_common_ptr(cinfo), JERR_BAD_SCAN_SCRIPT, scanno);
289         component_sent[thisi] := TRUE;
290       end;
291     end;
292     Inc(scanptr);
293   end;
294 
295   { Now verify that everything got sent. }
296   if (cinfo^.progressive_mode) then
297   begin
298 {$ifdef C_PROGRESSIVE_SUPPORTED
299     { For progressive mode, we only check that at least some DC data
300       got sent for each component; the spec does not require that all bits
301       of all coefficients be transmitted.  Would it be wiser to enforce
302       transmission of all coefficient bits?? }
303 
304     for ci := 0 to pred(cinfo^.num_components) do
305     begin
306       if (last_bitpos[ci][0] < 0) then
307         ERREXIT(j_common_ptr(cinfo), JERR_MISSING_DATA);
308     end;
309 {$endif}
310   end
311   else
312   begin
313     for ci := 0 to pred(cinfo^.num_components) do
314     begin
315       if (not component_sent[ci]) then
316         ERREXIT(j_common_ptr(cinfo), JERR_MISSING_DATA);
317     end;
318   end;
319 end;
320 
321 {$endif} { C_MULTISCAN_FILES_SUPPORTED }
322 
323 
324 {LOCAL}
325 procedure select_scan_parameters (cinfo : j_compress_ptr);
326 { Set up the scan parameters for the current scan }
327 var
328   master : my_master_ptr;
329   {const} scanptr : jpeg_scan_info_ptr;
330   ci : int;
331 var
332   comp_infos : jpeg_component_info_list_ptr;
333 begin
334 {$ifdef C_MULTISCAN_FILES_SUPPORTED}
335   if (cinfo^.scan_info <> NIL) then
336   begin
337     { Prepare for current scan --- the script is already validated }
338     master := my_master_ptr (cinfo^.master);
339     scanptr := cinfo^.scan_info;
340     Inc(scanptr, master^.scan_number);
341 
342     cinfo^.comps_in_scan := scanptr^.comps_in_scan;
343     comp_infos := cinfo^.comp_info;
344     for ci := 0 to pred(scanptr^.comps_in_scan) do
345     begin
346       cinfo^.cur_comp_info[ci] :=
347         @(comp_infos^[scanptr^.component_index[ci]]);
348     end;
349     cinfo^.Ss := scanptr^.Ss;
350     cinfo^.Se := scanptr^.Se;
351     cinfo^.Ah := scanptr^.Ah;
352     cinfo^.Al := scanptr^.Al;
353   end
354   else
355 {$endif}
356   begin
357     { Prepare for single sequential-JPEG scan containing all components }
358     if (cinfo^.num_components > MAX_COMPS_IN_SCAN) then
359       ERREXIT2(j_common_ptr(cinfo), JERR_COMPONENT_COUNT, cinfo^.num_components,
360                MAX_COMPS_IN_SCAN);
361     cinfo^.comps_in_scan := cinfo^.num_components;
362     comp_infos := cinfo^.comp_info;
363     for ci := 0 to pred(cinfo^.num_components) do
364     begin
365       cinfo^.cur_comp_info[ci] := @(comp_infos^[ci]);
366     end;
367     cinfo^.Ss := 0;
368     cinfo^.Se := DCTSIZE2-1;
369     cinfo^.Ah := 0;
370     cinfo^.Al := 0;
371   end;
372 end;
373 
374 
375 {LOCAL}
376 procedure per_scan_setup (cinfo : j_compress_ptr);
377 { Do computations that are needed before processing a JPEG scan }
378 { cinfo^.comps_in_scan and cinfo^.cur_comp_info[] are already set }
379 var
380   ci, mcublks, tmp : int;
381   compptr : jpeg_component_info_ptr;
382   nominal : long;
383 begin
384   if (cinfo^.comps_in_scan = 1) then
385   begin
386 
387     { Noninterleaved (single-component) scan }
388     compptr := cinfo^.cur_comp_info[0];
389 
390     { Overall image size in MCUs }
391     cinfo^.MCUs_per_row := compptr^.width_in_blocks;
392     cinfo^.MCU_rows_in_scan := compptr^.height_in_blocks;
393 
394     { For noninterleaved scan, always one block per MCU }
395     compptr^.MCU_width := 1;
396     compptr^.MCU_height := 1;
397     compptr^.MCU_blocks := 1;
398     compptr^.MCU_sample_width := DCTSIZE;
399     compptr^.last_col_width := 1;
400     { For noninterleaved scans, it is convenient to define last_row_height
401       as the number of block rows present in the last iMCU row. }
402 
403     tmp := int (compptr^.height_in_blocks mod compptr^.v_samp_factor);
404     if (tmp = 0) then
405       tmp := compptr^.v_samp_factor;
406     compptr^.last_row_height := tmp;
407 
408     { Prepare array describing MCU composition }
409     cinfo^.blocks_in_MCU := 1;
410     cinfo^.MCU_membership[0] := 0;
411 
412   end
413   else
414   begin
415 
416     { Interleaved (multi-component) scan }
417     if (cinfo^.comps_in_scan <= 0) or
418        (cinfo^.comps_in_scan > MAX_COMPS_IN_SCAN) then
419       ERREXIT2(j_common_ptr(cinfo), JERR_COMPONENT_COUNT,
420         cinfo^.comps_in_scan,  MAX_COMPS_IN_SCAN);
421 
422     { Overall image size in MCUs }
423     cinfo^.MCUs_per_row := JDIMENSION (
424       jdiv_round_up( long (cinfo^.image_width),
425                      long (cinfo^.max_h_samp_factor*DCTSIZE)) );
426     cinfo^.MCU_rows_in_scan := JDIMENSION (
427       jdiv_round_up( long (cinfo^.image_height),
428                      long (cinfo^.max_v_samp_factor*DCTSIZE)) );
429 
430     cinfo^.blocks_in_MCU := 0;
431 
432     for ci := 0 to pred(cinfo^.comps_in_scan) do
433     begin
434       compptr := cinfo^.cur_comp_info[ci];
435       { Sampling factors give # of blocks of component in each MCU }
436       compptr^.MCU_width := compptr^.h_samp_factor;
437       compptr^.MCU_height := compptr^.v_samp_factor;
438       compptr^.MCU_blocks := compptr^.MCU_width * compptr^.MCU_height;
439       compptr^.MCU_sample_width := compptr^.MCU_width * DCTSIZE;
440       { Figure number of non-dummy blocks in last MCU column & row }
441       tmp := int (compptr^.width_in_blocks mod compptr^.MCU_width);
442       if (tmp = 0) then
443         tmp := compptr^.MCU_width;
444       compptr^.last_col_width := tmp;
445       tmp := int (compptr^.height_in_blocks mod compptr^.MCU_height);
446       if (tmp = 0) then
447         tmp := compptr^.MCU_height;
448       compptr^.last_row_height := tmp;
449       { Prepare array describing MCU composition }
450       mcublks := compptr^.MCU_blocks;
451       if (cinfo^.blocks_in_MCU + mcublks > C_MAX_BLOCKS_IN_MCU) then
452         ERREXIT(j_common_ptr(cinfo), JERR_BAD_MCU_SIZE);
453       while (mcublks > 0) do
454       begin
455         Dec(mcublks);
456         cinfo^.MCU_membership[cinfo^.blocks_in_MCU] := ci;
457         Inc(cinfo^.blocks_in_MCU);
458       end;
459     end;
460 
461   end;
462 
463   { Convert restart specified in rows to actual MCU count. }
464   { Note that count must fit in 16 bits, so we provide limiting. }
465   if (cinfo^.restart_in_rows > 0) then
466   begin
467     nominal := long(cinfo^.restart_in_rows) * long(cinfo^.MCUs_per_row);
468     if nominal < long(65535) then
469       cinfo^.restart_interval := uInt (nominal)
470     else
471       cinfo^.restart_interval := long(65535);
472   end;
473 end;
474 
475 
476 { Per-pass setup.
477   This is called at the beginning of each pass.  We determine which modules
478   will be active during this pass and give them appropriate start_pass calls.
479   We also set is_last_pass to indicate whether any more passes will be
480   required. }
481 
482 {METHODDEF}
483 procedure prepare_for_pass (cinfo : j_compress_ptr); far;
484 var
485   master : my_master_ptr;
486 var
487   fallthrough : boolean;
488 begin
489   master := my_master_ptr (cinfo^.master);
490   fallthrough := true;
491 
492   case (master^.pass_type) of
493   main_pass:
494     begin
495       { Initial pass: will collect input data, and do either Huffman
496         optimization or data output for the first scan. }
497       select_scan_parameters(cinfo);
498       per_scan_setup(cinfo);
499       if (not cinfo^.raw_data_in) then
500       begin
501         cinfo^.cconvert^.start_pass (cinfo);
502         cinfo^.downsample^.start_pass (cinfo);
503         cinfo^.prep^.start_pass (cinfo, JBUF_PASS_THRU);
504       end;
505       cinfo^.fdct^.start_pass (cinfo);
506       cinfo^.entropy^.start_pass (cinfo, cinfo^.optimize_coding);
507       if master^.total_passes > 1 then
508         cinfo^.coef^.start_pass (cinfo, JBUF_SAVE_AND_PASS)
509       else
510         cinfo^.coef^.start_pass (cinfo, JBUF_PASS_THRU);
511       cinfo^.main^.start_pass (cinfo, JBUF_PASS_THRU);
512       if (cinfo^.optimize_coding) then
513       begin
514         { No immediate data output; postpone writing frame/scan headers }
515         master^.pub.call_pass_startup := FALSE;
516       end
517       else
518       begin
519         { Will write frame/scan headers at first jpeg_write_scanlines call }
520         master^.pub.call_pass_startup := TRUE;
521       end;
522     end;
523 {$ifdef ENTROPY_OPT_SUPPORTED}
524   huff_opt_pass,
525   output_pass:
526     begin
527       if (master^.pass_type = huff_opt_pass) then
528       begin
529         { Do Huffman optimization for a scan after the first one. }
530         select_scan_parameters(cinfo);
531         per_scan_setup(cinfo);
532         if (cinfo^.Ss <> 0) or (cinfo^.Ah = 0) or (cinfo^.arith_code) then
533         begin
534           cinfo^.entropy^.start_pass (cinfo, TRUE);
535           cinfo^.coef^.start_pass (cinfo, JBUF_CRANK_DEST);
536           master^.pub.call_pass_startup := FALSE;
537           fallthrough := false;
538         end;
539         { Special case: Huffman DC refinement scans need no Huffman table
540           and therefore we can skip the optimization pass for them. }
541         if fallthrough then
542         begin
543           master^.pass_type := output_pass;
544           Inc(master^.pass_number);
545           {FALLTHROUGH}
546         end;
547       end;
548 {$else}
549   output_pass:
550     begin
551 {$endif}
552       if fallthrough then
553       begin
554         { Do a data-output pass. }
555         { We need not repeat per-scan setup if prior optimization pass did it. }
556         if (not cinfo^.optimize_coding) then
557         begin
558           select_scan_parameters(cinfo);
559           per_scan_setup(cinfo);
560         end;
561         cinfo^.entropy^.start_pass (cinfo, FALSE);
562         cinfo^.coef^.start_pass (cinfo, JBUF_CRANK_DEST);
563         { We emit frame/scan headers now }
564         if (master^.scan_number = 0) then
565           cinfo^.marker^.write_frame_header (cinfo);
566         cinfo^.marker^.write_scan_header (cinfo);
567         master^.pub.call_pass_startup := FALSE;
568       end;
569     end;
570   else
571     ERREXIT(j_common_ptr(cinfo), JERR_NOT_COMPILED);
572   end;
573 
574   master^.pub.is_last_pass := (master^.pass_number = master^.total_passes-1);
575 
576   { Set up progress monitor's pass info if present }
577   if (cinfo^.progress <> NIL) then
578   begin
579     cinfo^.progress^.completed_passes := master^.pass_number;
580     cinfo^.progress^.total_passes := master^.total_passes;
581   end;
582 end;
583 
584 
585 { Special start-of-pass hook.
586   This is called by jpeg_write_scanlines if call_pass_startup is TRUE.
587   In single-pass processing, we need this hook because we don't want to
588   write frame/scan headers during jpeg_start_compress; we want to let the
589   application write COM markers etc. between jpeg_start_compress and the
590   jpeg_write_scanlines loop.
591   In multi-pass processing, this routine is not used. }
592 
593 {METHODDEF}
594 procedure pass_startup (cinfo : j_compress_ptr); far;
595 begin
596   cinfo^.master^.call_pass_startup := FALSE; { reset flag so call only once }
597 
598   cinfo^.marker^.write_frame_header (cinfo);
599   cinfo^.marker^.write_scan_header (cinfo);
600 end;
601 
602 
603 { Finish up at end of pass. }
604 
605 {METHODDEF}
606 procedure finish_pass_master (cinfo : j_compress_ptr); far;
607 var
608   master : my_master_ptr;
609 begin
610   master := my_master_ptr (cinfo^.master);
611 
612   { The entropy coder always needs an end-of-pass call,
613     either to analyze statistics or to flush its output buffer. }
614   cinfo^.entropy^.finish_pass (cinfo);
615 
616   { Update state for next pass }
617   case (master^.pass_type) of
618   main_pass:
619     begin
620       { next pass is either output of scan 0 (after optimization)
621         or output of scan 1 (if no optimization). }
622 
623       master^.pass_type := output_pass;
624       if (not cinfo^.optimize_coding) then
625         Inc(master^.scan_number);
626     end;
627   huff_opt_pass:
628     { next pass is always output of current scan }
629     master^.pass_type := output_pass;
630   output_pass:
631     begin
632       { next pass is either optimization or output of next scan }
633       if (cinfo^.optimize_coding) then
634         master^.pass_type := huff_opt_pass;
635       Inc(master^.scan_number);
636     end;
637   end;
638 
639   Inc(master^.pass_number);
640 end;
641 
642 
643 { Initialize master compression control. }
644 
645 {GLOBAL}
646 procedure jinit_c_master_control (cinfo : j_compress_ptr;
647                                   transcode_only : boolean);
648 var
649   master : my_master_ptr;
650 begin
651   master := my_master_ptr(
652       cinfo^.mem^.alloc_small (j_common_ptr(cinfo), JPOOL_IMAGE,
653                                   SIZEOF(my_comp_master)) );
654   cinfo^.master := jpeg_comp_master_ptr(master);
655   master^.pub.prepare_for_pass := prepare_for_pass;
656   master^.pub.pass_startup := pass_startup;
657   master^.pub.finish_pass := finish_pass_master;
658   master^.pub.is_last_pass := FALSE;
659 
660   { Validate parameters, determine derived values }
661   initial_setup(cinfo);
662 
663   if (cinfo^.scan_info <> NIL) then
664   begin
665 {$ifdef C_MULTISCAN_FILES_SUPPORTED}
666     validate_script(cinfo);
667 {$else}
668     ERREXIT(j_common_ptr(cinfo), JERR_NOT_COMPILED);
669 {$endif}
670   end
671   else
672   begin
673     cinfo^.progressive_mode := FALSE;
674     cinfo^.num_scans := 1;
675   end;
676 
677   if (cinfo^.progressive_mode) then  {  TEMPORARY HACK ??? }
678     cinfo^.optimize_coding := TRUE;  { assume default tables no good for progressive mode }
679 
680   { Initialize my private state }
681   if (transcode_only) then
682   begin
683     { no main pass in transcoding }
684     if (cinfo^.optimize_coding) then
685       master^.pass_type := huff_opt_pass
686     else
687       master^.pass_type := output_pass;
688   end
689   else
690   begin
691     { for normal compression, first pass is always this type: }
692     master^.pass_type := main_pass;
693   end;
694   master^.scan_number := 0;
695   master^.pass_number := 0;
696   if (cinfo^.optimize_coding) then
697     master^.total_passes := cinfo^.num_scans * 2
698   else
699     master^.total_passes := cinfo^.num_scans;
700 end;
701 
702 end.
703