1 Unit JMemMgr;
2 
3 { This file contains the JPEG system-independent memory management
4   routines.  This code is usable across a wide variety of machines; most
5   of the system dependencies have been isolated in a separate file.
6   The major functions provided here are:
7     * pool-based allocation and freeing of memory;
8     * policy decisions about how to divide available memory among the
9       virtual arrays;
10     * control logic for swapping virtual arrays between main memory and
11       backing storage.
12   The separate system-dependent file provides the actual backing-storage
13   access code, and it contains the policy decision about how much total
14   main memory to use.
15   This file is system-dependent in the sense that some of its functions
16   are unnecessary in some systems.  For example, if there is enough virtual
17   memory so that backing storage will never be used, much of the virtual
18   array control logic could be removed.  (Of course, if you have that much
19   memory then you shouldn't care about a little bit of unused code...) }
20 
21 { Original : jmemmgr.c ; Copyright (C) 1991-1997, Thomas G. Lane. }
22 
23 interface
24 
25 {$I jconfig.inc}
26 
27 uses
28    jmorecfg,
29    jinclude,
30    jdeferr,
31    jerror,
32    jpeglib,
33    jutils,
34 {$IFDEF VER70}
35 {$ifndef NO_GETENV}
36    Dos,                         { DOS unit should declare getenv() }
37                                 { function GetEnv(name : string) : string; }
38 {$endif}
39    jmemdos;                     { import the system-dependent declarations }
40 {$ELSE}
41    jmemnobs;
42   {$DEFINE NO_GETENV}
43 {$ENDIF}
44 
45 { Memory manager initialization.
46   When this is called, only the error manager pointer is valid in cinfo! }
47 
48 {GLOBAL}
49 procedure jinit_memory_mgr (cinfo : j_common_ptr);
50 
51 implementation
52 
53 
54 { Some important notes:
55     The allocation routines provided here must never return NIL.
56     They should exit to error_exit if unsuccessful.
57 
58     It's not a good idea to try to merge the sarray and barray routines,
59     even though they are textually almost the same, because samples are
60     usually stored as bytes while coefficients are shorts or ints.  Thus,
61     in machines where byte pointers have a different representation from
62     word pointers, the resulting machine code could not be the same.  }
63 
64 
65 { Many machines require storage alignment: longs must start on 4-byte
66   boundaries, doubles on 8-byte boundaries, etc.  On such machines, malloc()
67   always returns pointers that are multiples of the worst-case alignment
68   requirement, and we had better do so too.
69   There isn't any really portable way to determine the worst-case alignment
70   requirement.  This module assumes that the alignment requirement is
71   multiples of sizeof(ALIGN_TYPE).
72   By default, we define ALIGN_TYPE as double.  This is necessary on some
73   workstations (where doubles really do need 8-byte alignment) and will work
74   fine on nearly everything.  If your machine has lesser alignment needs,
75   you can save a few bytes by making ALIGN_TYPE smaller.
76   The only place I know of where this will NOT work is certain Macintosh
77   680x0 compilers that define double as a 10-byte IEEE extended float.
78   Doing 10-byte alignment is counterproductive because longwords won't be
79   aligned well.  Put "#define ALIGN_TYPE long" in jconfig.h if you have
80   such a compiler. }
81 
82 {$ifndef ALIGN_TYPE} { so can override from jconfig.h }
83 type
84   ALIGN_TYPE = double;
85 {$endif}
86 
87 
88 { We allocate objects from "pools", where each pool is gotten with a single
89   request to jpeg_get_small() or jpeg_get_large().  There is no per-object
90   overhead within a pool, except for alignment padding.  Each pool has a
91   header with a link to the next pool of the same class.
92   Small and large pool headers are identical except that the latter's
93   link pointer must be FAR on 80x86 machines.
94   Notice that the "real" header fields are union'ed with a dummy ALIGN_TYPE
95   field.  This forces the compiler to make SIZEOF(small_pool_hdr) a multiple
96   of the alignment requirement of ALIGN_TYPE. }
97 
98 type
99   small_pool_ptr = ^small_pool_hdr;
100   small_pool_hdr = record
101   case byte of
102     0:(hdr : record
103                next : small_pool_ptr;   { next in list of pools }
104                bytes_used : size_t;     { how many bytes already used within pool }
105                bytes_left : size_t;     { bytes still available in this pool }
106              end);
107     1:(dummy : ALIGN_TYPE);             { included in union to ensure alignment }
108   end; {small_pool_hdr;}
109 
110 type
111   large_pool_ptr = ^large_pool_hdr; {FAR}
112   large_pool_hdr = record
113   case byte of
114     0:(hdr : record
115                next : large_pool_ptr;   { next in list of pools }
116                bytes_used : size_t;     { how many bytes already used within pool }
117                bytes_left : size_t;     { bytes still available in this pool }
118              end);
119     1:(dummy : ALIGN_TYPE);             { included in union to ensure alignment }
120   end; {large_pool_hdr;}
121 
122 
123 { Here is the full definition of a memory manager object. }
124 
125 type
126   my_mem_ptr = ^my_memory_mgr;
127   my_memory_mgr = record
128     pub : jpeg_memory_mgr;      { public fields }
129 
130     { Each pool identifier (lifetime class) names a linked list of pools. }
131     small_list : array[0..JPOOL_NUMPOOLS-1] of small_pool_ptr ;
132     large_list : array[0..JPOOL_NUMPOOLS-1] of large_pool_ptr ;
133 
134     { Since we only have one lifetime class of virtual arrays, only one
135       linked list is necessary (for each datatype).  Note that the virtual
136       array control blocks being linked together are actually stored somewhere
137       in the small-pool list. }
138 
139     virt_sarray_list : jvirt_sarray_ptr;
140     virt_barray_list : jvirt_barray_ptr;
141 
142     { This counts total space obtained from jpeg_get_small/large }
143     total_space_allocated : long;
144 
145     { alloc_sarray and alloc_barray set this value for use by virtual
146       array routines. }
147 
148     last_rowsperchunk : JDIMENSION;     { from most recent alloc_sarray/barray }
149   end; {my_memory_mgr;}
150 
151   {$ifndef AM_MEMORY_MANAGER}   { only jmemmgr.c defines these }
152 
153 { The control blocks for virtual arrays.
154   Note that these blocks are allocated in the "small" pool area.
155   System-dependent info for the associated backing store (if any) is hidden
156   inside the backing_store_info struct. }
157 type
158   jvirt_sarray_control = record
159     mem_buffer : JSAMPARRAY;    { => the in-memory buffer }
160     rows_in_array : JDIMENSION; { total virtual array height }
161     samplesperrow : JDIMENSION; { width of array (and of memory buffer) }
162     maxaccess : JDIMENSION;     { max rows accessed by access_virt_sarray }
163     rows_in_mem : JDIMENSION;   { height of memory buffer }
164     rowsperchunk : JDIMENSION;  { allocation chunk size in mem_buffer }
165     cur_start_row : JDIMENSION; { first logical row # in the buffer }
166     first_undef_row : JDIMENSION;       { row # of first uninitialized row }
167     pre_zero : boolean;         { pre-zero mode requested? }
168     dirty : boolean;            { do current buffer contents need written? }
169     b_s_open : boolean;         { is backing-store data valid? }
170     next : jvirt_sarray_ptr;    { link to next virtual sarray control block }
171     b_s_info : backing_store_info;      { System-dependent control info }
172   end;
173 
174   jvirt_barray_control = record
175     mem_buffer : JBLOCKARRAY;   { => the in-memory buffer }
176     rows_in_array : JDIMENSION; { total virtual array height }
177     blocksperrow : JDIMENSION;  { width of array (and of memory buffer) }
178     maxaccess : JDIMENSION;     { max rows accessed by access_virt_barray }
179     rows_in_mem : JDIMENSION;   { height of memory buffer }
180     rowsperchunk : JDIMENSION;  { allocation chunk size in mem_buffer }
181     cur_start_row : JDIMENSION; { first logical row # in the buffer }
182     first_undef_row : JDIMENSION;       { row # of first uninitialized row }
183     pre_zero : boolean;         { pre-zero mode requested? }
184     dirty : boolean;            { do current buffer contents need written? }
185     b_s_open : boolean;         { is backing-store data valid? }
186     next : jvirt_barray_ptr;    { link to next virtual barray control block }
187     b_s_info : backing_store_info;      { System-dependent control info }
188   end;
189   {$endif}  { AM_MEMORY_MANAGER}
190 
191 {$ifdef MEM_STATS}              { optional extra stuff for statistics }
192 
193 {LOCAL}
194 procedure print_mem_stats (cinfo : j_common_ptr; pool_id : int);
195 var
196   mem : my_mem_ptr;
197   shdr_ptr : small_pool_ptr;
198   lhdr_ptr : large_pool_ptr;
199 begin
200   mem := my_mem_ptr (cinfo^.mem);
201 
202   { Since this is only a debugging stub, we can cheat a little by using
203     fprintf directly rather than going through the trace message code.
204     This is helpful because message parm array can't handle longs. }
205 
206   WriteLn(output, 'Freeing pool ', pool_id,', total space := ',
207            mem^.total_space_allocated);
208 
209   lhdr_ptr := mem^.large_list[pool_id];
210   while (lhdr_ptr <> NIL) do
211   begin
212     WriteLn(output, '  Large chunk used ',
213             long (lhdr_ptr^.hdr.bytes_used));
214     lhdr_ptr := lhdr_ptr^.hdr.next;
215   end;
216 
217   shdr_ptr := mem^.small_list[pool_id];
218 
219   while (shdr_ptr <> NIL) do
220   begin
221     WriteLn(output, '  Small chunk used ',
222                     long (shdr_ptr^.hdr.bytes_used), ' free ',
223                     long (shdr_ptr^.hdr.bytes_left) );
224     shdr_ptr := shdr_ptr^.hdr.next;
225   end;
226 end;
227 
228 {$endif} { MEM_STATS }
229 
230 
231 {LOCAL}
232 procedure out_of_memory (cinfo : j_common_ptr; which : int);
233 { Report an out-of-memory error and stop execution }
234 { If we compiled MEM_STATS support, report alloc requests before dying }
235 begin
236 {$ifdef MEM_STATS}
237   cinfo^.err^.trace_level := 2; { force self_destruct to report stats }
238 {$endif}
239   ERREXIT1(cinfo, JERR_OUT_OF_MEMORY, which);
240 end;
241 
242 
243 { Allocation of "small" objects.
244 
245   For these, we use pooled storage.  When a new pool must be created,
246   we try to get enough space for the current request plus a "slop" factor,
247   where the slop will be the amount of leftover space in the new pool.
248   The speed vs. space tradeoff is largely determined by the slop values.
249   A different slop value is provided for each pool class (lifetime),
250   and we also distinguish the first pool of a class from later ones.
251   NOTE: the values given work fairly well on both 16- and 32-bit-int
252   machines, but may be too small if longs are 64 bits or more. }
253 
254 const
255   first_pool_slop : array[0..JPOOL_NUMPOOLS-1] of size_t  =
256         (1600,                  { first PERMANENT pool }
257         16000);                 { first IMAGE pool }
258 
259 const
260   extra_pool_slop : array[0..JPOOL_NUMPOOLS-1] of size_t =
261         (0,                     { additional PERMANENT pools }
262         5000);                  { additional IMAGE pools }
263 
264 const
265   MIN_SLOP = 50;                { greater than 0 to avoid futile looping }
266 
267 
268 {METHODDEF}
alloc_smallnull269 function alloc_small (cinfo : j_common_ptr;
270                       pool_id : int;
271                       sizeofobject : size_t) : pointer; far;
272 type
273   byteptr = ^byte;
274 { Allocate a "small" object }
275 var
276   mem : my_mem_ptr;
277   hdr_ptr, prev_hdr_ptr : small_pool_ptr;
278   data_ptr : byteptr;
279   odd_bytes, min_request, slop : size_t;
280 begin
281   mem := my_mem_ptr (cinfo^.mem);
282 
283   { Check for unsatisfiable request (do now to ensure no overflow below) }
284   if (sizeofobject > size_t(MAX_ALLOC_CHUNK-SIZEOF(small_pool_hdr))) then
285     out_of_memory(cinfo, 1);    { request exceeds malloc's ability }
286 
287   { Round up the requested size to a multiple of SIZEOF(ALIGN_TYPE) }
288   odd_bytes := sizeofobject mod SIZEOF(ALIGN_TYPE);
289   if (odd_bytes > 0) then
290     Inc(sizeofobject, SIZEOF(ALIGN_TYPE) - odd_bytes);
291 
292   { See if space is available in any existing pool }
293   if (pool_id < 0) or (pool_id >= JPOOL_NUMPOOLS) then
294     ERREXIT1(j_common_ptr(cinfo), JERR_BAD_POOL_ID, pool_id);   { safety check }
295   prev_hdr_ptr := NIL;
296   hdr_ptr := mem^.small_list[pool_id];
297   while (hdr_ptr <> NIL) do
298   begin
299     if (hdr_ptr^.hdr.bytes_left >= sizeofobject) then
300       break;                    { found pool with enough space }
301     prev_hdr_ptr := hdr_ptr;
302     hdr_ptr := hdr_ptr^.hdr.next;
303   end;
304 
305   { Time to make a new pool? }
306   if (hdr_ptr = NIL) then
307   begin
308     { min_request is what we need now, slop is what will be leftover }
309     min_request := sizeofobject + SIZEOF(small_pool_hdr);
310     if (prev_hdr_ptr = NIL) then        { first pool in class? }
311       slop := first_pool_slop[pool_id]
312     else
313       slop := extra_pool_slop[pool_id];
314     { Don't ask for more than MAX_ALLOC_CHUNK }
315     if (slop > size_t (MAX_ALLOC_CHUNK-min_request)) then
316       slop := size_t (MAX_ALLOC_CHUNK-min_request);
317     { Try to get space, if fail reduce slop and try again }
318     while TRUE do
319     begin
320       hdr_ptr := small_pool_ptr(jpeg_get_small(cinfo, min_request + slop));
321       if (hdr_ptr <> NIL) then
322         break;
323       slop := slop div 2;
324       if (slop < MIN_SLOP) then   { give up when it gets real small }
325         out_of_memory(cinfo, 2);  { jpeg_get_small failed }
326     end;
327     Inc(mem^.total_space_allocated, min_request + slop);
328     { Success, initialize the new pool header and add to end of list }
329     hdr_ptr^.hdr.next := NIL;
330     hdr_ptr^.hdr.bytes_used := 0;
331     hdr_ptr^.hdr.bytes_left := sizeofobject + slop;
332     if (prev_hdr_ptr = NIL) then       { first pool in class? }
333       mem^.small_list[pool_id] := hdr_ptr
334     else
335       prev_hdr_ptr^.hdr.next := hdr_ptr;
336   end;
337 
338   { OK, allocate the object from the current pool }
339   data_ptr := byteptr (hdr_ptr);
340   Inc(small_pool_ptr(data_ptr));  { point to first data byte in pool }
341   Inc(data_ptr, hdr_ptr^.hdr.bytes_used); { point to place for object }
342   Inc(hdr_ptr^.hdr.bytes_used, sizeofobject);
343   Dec(hdr_ptr^.hdr.bytes_left, sizeofobject);
344 
345   alloc_small := pointer(data_ptr);
346 end;
347 
348 
349 { Allocation of "large" objects.
350 
351   The external semantics of these are the same as "small" objects,
352   except that FAR pointers are used on 80x86.  However the pool
353   management heuristics are quite different.  We assume that each
354   request is large enough that it may as well be passed directly to
355   jpeg_get_large; the pool management just links everything together
356   so that we can free it all on demand.
357   Note: the major use of "large" objects is in JSAMPARRAY and JBLOCKARRAY
358   structures.  The routines that create these structures (see below)
359   deliberately bunch rows together to ensure a large request size. }
360 
361 {METHODDEF}
alloc_largenull362 function alloc_large (cinfo : j_common_ptr;
363                       pool_id : int;
364                       sizeofobject : size_t) : pointer; FAR;
365 { Allocate a "large" object }
366 var
367   mem : my_mem_ptr;
368   hdr_ptr : large_pool_ptr;
369   odd_bytes : size_t;
370 var
371   dest_ptr : large_pool_ptr;
372 begin
373   mem := my_mem_ptr (cinfo^.mem);
374 
375   { Check for unsatisfiable request (do now to ensure no overflow below) }
376   if (sizeofobject > size_t (MAX_ALLOC_CHUNK-SIZEOF(large_pool_hdr))) then
377     out_of_memory(cinfo, 3);    { request exceeds malloc's ability }
378 
379   { Round up the requested size to a multiple of SIZEOF(ALIGN_TYPE) }
380   odd_bytes := sizeofobject mod SIZEOF(ALIGN_TYPE);
381   if (odd_bytes > 0) then
382     Inc(sizeofobject, SIZEOF(ALIGN_TYPE) - odd_bytes);
383 
384   { Always make a new pool }
385   if (pool_id < 0) or (pool_id >= JPOOL_NUMPOOLS) then
386     ERREXIT1(cinfo, JERR_BAD_POOL_ID, pool_id); { safety check }
387 
388   hdr_ptr := large_pool_ptr (jpeg_get_large(cinfo, sizeofobject +
389                                             SIZEOF(large_pool_hdr)));
390   if (hdr_ptr = NIL) then
391     out_of_memory(cinfo, 4);    { jpeg_get_large failed }
392   Inc(mem^.total_space_allocated, sizeofobject + SIZEOF(large_pool_hdr));
393 
394   { Success, initialize the new pool header and add to list }
395   hdr_ptr^.hdr.next := mem^.large_list[pool_id];
396   { We maintain space counts in each pool header for statistical purposes,
397     even though they are not needed for allocation. }
398 
399   hdr_ptr^.hdr.bytes_used := sizeofobject;
400   hdr_ptr^.hdr.bytes_left := 0;
401   mem^.large_list[pool_id] := hdr_ptr;
402 
403   {alloc_large := pointerFAR (hdr_ptr + 1); - point to first data byte in pool }
404   dest_ptr := hdr_ptr;
405   Inc(large_pool_ptr(dest_ptr));
406   alloc_large := dest_ptr;
407 end;
408 
409 
410 { Creation of 2-D sample arrays.
411   The pointers are in near heap, the samples themselves in FAR heap.
412 
413   To minimize allocation overhead and to allow I/O of large contiguous
414   blocks, we allocate the sample rows in groups of as many rows as possible
415   without exceeding MAX_ALLOC_CHUNK total bytes per allocation request.
416   NB: the virtual array control routines, later in this file, know about
417   this chunking of rows.  The rowsperchunk value is left in the mem manager
418   object so that it can be saved away if this sarray is the workspace for
419   a virtual array. }
420 
421 {METHODDEF}
alloc_sarraynull422 function alloc_sarray (cinfo : j_common_ptr;
423                        pool_id : int;
424                        samplesperrow : JDIMENSION;
425                        numrows : JDIMENSION) : JSAMPARRAY; far;
426 { Allocate a 2-D sample array }
427 var
428   mem : my_mem_ptr;
429   the_result : JSAMPARRAY;
430   workspace : JSAMPROW;
431   rowsperchunk, currow, i : JDIMENSION;
432   ltemp : long;
433 begin
434   mem := my_mem_ptr(cinfo^.mem);
435 
436   { Calculate max # of rows allowed in one allocation chunk }
437   ltemp := (MAX_ALLOC_CHUNK-SIZEOF(large_pool_hdr)) div
438           (long(samplesperrow) * SIZEOF(JSAMPLE));
439   if (ltemp <= 0) then
440     ERREXIT(cinfo, JERR_WIDTH_OVERFLOW);
441   if (ltemp < long(numrows)) then
442     rowsperchunk := JDIMENSION (ltemp)
443   else
444     rowsperchunk := numrows;
445   mem^.last_rowsperchunk := rowsperchunk;
446 
447   { Get space for row pointers (small object) }
448   the_result := JSAMPARRAY (alloc_small(cinfo, pool_id,
449                                     size_t (numrows * SIZEOF(JSAMPROW))));
450 
451   { Get the rows themselves (large objects) }
452   currow := 0;
453   while (currow < numrows) do
454   begin
455     {rowsperchunk := MIN(rowsperchunk, numrows - currow);}
456     if rowsperchunk > numrows - currow then
457       rowsperchunk := numrows - currow;
458 
459     workspace := JSAMPROW (alloc_large(cinfo, pool_id,
460         size_t (size_t(rowsperchunk) * size_t(samplesperrow)
461                   * SIZEOF(JSAMPLE))) );
462     for i := pred(rowsperchunk) downto 0 do
463     begin
464       the_result^[currow] := workspace;
465       Inc(currow);
466       Inc(JSAMPLE_PTR(workspace), samplesperrow);
467     end;
468   end;
469 
470   alloc_sarray := the_result;
471 end;
472 
473 
474 { Creation of 2-D coefficient-block arrays.
475   This is essentially the same as the code for sample arrays, above. }
476 
477 {METHODDEF}
alloc_barraynull478 function alloc_barray (cinfo : j_common_ptr;
479                        pool_id : int;
480                        blocksperrow : JDIMENSION;
481                        numrows : JDIMENSION) : JBLOCKARRAY; far;
482 { Allocate a 2-D coefficient-block array }
483 var
484   mem : my_mem_ptr;
485   the_result : JBLOCKARRAY;
486   workspace : JBLOCKROW;
487   rowsperchunk, currow, i : JDIMENSION;
488   ltemp : long;
489 begin
490   mem := my_mem_ptr(cinfo^.mem);
491 
492   { Calculate max # of rows allowed in one allocation chunk }
493   ltemp := (MAX_ALLOC_CHUNK-SIZEOF(large_pool_hdr)) div
494           (long(blocksperrow) * SIZEOF(JBLOCK));
495   if (ltemp <= 0) then
496     ERREXIT(cinfo, JERR_WIDTH_OVERFLOW);
497   if (ltemp < long(numrows)) then
498     rowsperchunk := JDIMENSION (ltemp)
499   else
500     rowsperchunk := numrows;
501   mem^.last_rowsperchunk := rowsperchunk;
502 
503   { Get space for row pointers (small object) }
504   the_result := JBLOCKARRAY (alloc_small(cinfo, pool_id,
505                                      size_t (numrows * SIZEOF(JBLOCKROW))) );
506 
507   { Get the rows themselves (large objects) }
508   currow := 0;
509   while (currow < numrows) do
510   begin
511     {rowsperchunk := MIN(rowsperchunk, numrows - currow);}
512     if rowsperchunk > numrows - currow then
513       rowsperchunk := numrows - currow;
514 
515     workspace := JBLOCKROW (alloc_large(cinfo, pool_id,
516         size_t (size_t(rowsperchunk) * size_t(blocksperrow)
517                   * SIZEOF(JBLOCK))) );
518     for i := rowsperchunk downto 1 do
519     begin
520       the_result^[currow] := workspace;
521       Inc(currow);
522       Inc(JBLOCK_PTR(workspace), blocksperrow);
523     end;
524   end;
525 
526   alloc_barray := the_result;
527 end;
528 
529 
530 { About virtual array management:
531 
532   The above "normal" array routines are only used to allocate strip buffers
533   (as wide as the image, but just a few rows high).  Full-image-sized buffers
534   are handled as "virtual" arrays.  The array is still accessed a strip at a
535   time, but the memory manager must save the whole array for repeated
536   accesses.  The intended implementation is that there is a strip buffer in
537   memory (as high as is possible given the desired memory limit), plus a
538   backing file that holds the rest of the array.
539 
540   The request_virt_array routines are told the total size of the image and
541   the maximum number of rows that will be accessed at once.  The in-memory
542   buffer must be at least as large as the maxaccess value.
543 
544   The request routines create control blocks but not the in-memory buffers.
545   That is postponed until realize_virt_arrays is called.  At that time the
546   total amount of space needed is known (approximately, anyway), so free
547   memory can be divided up fairly.
548 
549   The access_virt_array routines are responsible for making a specific strip
550   area accessible (after reading or writing the backing file, if necessary).
551   Note that the access routines are told whether the caller intends to modify
552   the accessed strip; during a read-only pass this saves having to rewrite
553   data to disk.  The access routines are also responsible for pre-zeroing
554   any newly accessed rows, if pre-zeroing was requested.
555 
556   In current usage, the access requests are usually for nonoverlapping
557   strips; that is, successive access start_row numbers differ by exactly
558   num_rows := maxaccess.  This means we can get good performance with simple
559   buffer dump/reload logic, by making the in-memory buffer be a multiple
560   of the access height; then there will never be accesses across bufferload
561   boundaries.  The code will still work with overlapping access requests,
562   but it doesn't handle bufferload overlaps very efficiently. }
563 
564 
565 {METHODDEF}
request_virt_sarraynull566 function request_virt_sarray (cinfo : j_common_ptr;
567                               pool_id : int;
568                               pre_zero : boolean;
569                               samplesperrow : JDIMENSION;
570                               numrows : JDIMENSION;
571                               maxaccess : JDIMENSION) : jvirt_sarray_ptr; far;
572 { Request a virtual 2-D sample array }
573 var
574   mem : my_mem_ptr;
575   the_result : jvirt_sarray_ptr;
576 begin
577   mem := my_mem_ptr (cinfo^.mem);
578 
579   { Only IMAGE-lifetime virtual arrays are currently supported }
580   if (pool_id <> JPOOL_IMAGE) then
581     ERREXIT1(cinfo, JERR_BAD_POOL_ID, pool_id); { safety check }
582 
583   { get control block }
584   the_result := jvirt_sarray_ptr (alloc_small(cinfo, pool_id,
585                                   SIZEOF(jvirt_sarray_control)) );
586 
587   the_result^.mem_buffer := NIL;        { marks array not yet realized }
588   the_result^.rows_in_array := numrows;
589   the_result^.samplesperrow := samplesperrow;
590   the_result^.maxaccess := maxaccess;
591   the_result^.pre_zero := pre_zero;
592   the_result^.b_s_open := FALSE;        { no associated backing-store object }
593   the_result^.next := mem^.virt_sarray_list; { add to list of virtual arrays }
594   mem^.virt_sarray_list := the_result;
595 
596   request_virt_sarray := the_result;
597 end;
598 
599 
600 {METHODDEF}
request_virt_barraynull601 function request_virt_barray (cinfo : j_common_ptr;
602                               pool_id : int;
603                               pre_zero : boolean;
604                               blocksperrow : JDIMENSION;
605                               numrows : JDIMENSION;
606                               maxaccess : JDIMENSION) : jvirt_barray_ptr; far;
607 { Request a virtual 2-D coefficient-block array }
608 var
609   mem : my_mem_ptr;
610   the_result : jvirt_barray_ptr;
611 begin
612   mem := my_mem_ptr(cinfo^.mem);
613 
614   { Only IMAGE-lifetime virtual arrays are currently supported }
615   if (pool_id <> JPOOL_IMAGE) then
616     ERREXIT1(cinfo, JERR_BAD_POOL_ID, pool_id); { safety check }
617 
618   { get control block }
619   the_result := jvirt_barray_ptr(alloc_small(cinfo, pool_id,
620                                   SIZEOF(jvirt_barray_control)) );
621 
622   the_result^.mem_buffer := NIL;        { marks array not yet realized }
623   the_result^.rows_in_array := numrows;
624   the_result^.blocksperrow := blocksperrow;
625   the_result^.maxaccess := maxaccess;
626   the_result^.pre_zero := pre_zero;
627   the_result^.b_s_open := FALSE;        { no associated backing-store object }
628   the_result^.next := mem^.virt_barray_list; { add to list of virtual arrays }
629   mem^.virt_barray_list := the_result;
630 
631   request_virt_barray := the_result;
632 end;
633 
634 
635 {METHODDEF}
636 procedure realize_virt_arrays (cinfo : j_common_ptr); far;
637 { Allocate the in-memory buffers for any unrealized virtual arrays }
638 var
639   mem : my_mem_ptr;
640   space_per_minheight, maximum_space, avail_mem : long;
641   minheights, max_minheights : long;
642   sptr : jvirt_sarray_ptr;
643   bptr : jvirt_barray_ptr;
644 begin
645   mem := my_mem_ptr (cinfo^.mem);
646   { Compute the minimum space needed (maxaccess rows in each buffer)
647     and the maximum space needed (full image height in each buffer).
648     These may be of use to the system-dependent jpeg_mem_available routine. }
649 
650   space_per_minheight := 0;
651   maximum_space := 0;
652   sptr := mem^.virt_sarray_list;
653   while (sptr <> NIL) do
654   begin
655     if (sptr^.mem_buffer = NIL) then
656     begin { if not realized yet }
657       Inc(space_per_minheight, long(sptr^.maxaccess) *
658                              long(sptr^.samplesperrow) * SIZEOF(JSAMPLE));
659       Inc(maximum_space, long(sptr^.rows_in_array) *
660                        long(sptr^.samplesperrow) * SIZEOF(JSAMPLE));
661     end;
662     sptr := sptr^.next;
663   end;
664   bptr := mem^.virt_barray_list;
665   while (bptr <> NIL) do
666   begin
667     if (bptr^.mem_buffer = NIL) then
668     begin { if not realized yet }
669       Inc(space_per_minheight, long(bptr^.maxaccess) *
670                              long(bptr^.blocksperrow) * SIZEOF(JBLOCK));
671       Inc(maximum_space, long(bptr^.rows_in_array) *
672                        long(bptr^.blocksperrow) * SIZEOF(JBLOCK));
673     end;
674     bptr := bptr^.next;
675   end;
676 
677   if (space_per_minheight <= 0) then
678     exit;                       { no unrealized arrays, no work }
679 
680   { Determine amount of memory to actually use; this is system-dependent. }
681   avail_mem := jpeg_mem_available(cinfo, space_per_minheight, maximum_space,
682                                  mem^.total_space_allocated);
683 
684   { If the maximum space needed is available, make all the buffers full
685     height; otherwise parcel it out with the same number of minheights
686     in each buffer. }
687 
688   if (avail_mem >= maximum_space) then
689     max_minheights := long(1000000000)
690   else
691   begin
692     max_minheights := avail_mem div space_per_minheight;
693     { If there doesn't seem to be enough space, try to get the minimum
694       anyway.  This allows a "stub" implementation of jpeg_mem_available(). }
695     if (max_minheights <= 0) then
696       max_minheights := 1;
697   end;
698 
699   { Allocate the in-memory buffers and initialize backing store as needed. }
700 
701   sptr := mem^.virt_sarray_list;
702   while (sptr <> NIL) do
703   begin
704     if (sptr^.mem_buffer = NIL) then
705     begin { if not realized yet }
706       minheights := (long(sptr^.rows_in_array) - long(1)) div sptr^.maxaccess + long(1);
707       if (minheights <= max_minheights) then
708       begin
709         { This buffer fits in memory }
710         sptr^.rows_in_mem := sptr^.rows_in_array;
711       end
712       else
713       begin
714         { It doesn't fit in memory, create backing store. }
715         sptr^.rows_in_mem := JDIMENSION (max_minheights * sptr^.maxaccess);
716         jpeg_open_backing_store(cinfo,
717                                 @sptr^.b_s_info,
718                                 long(sptr^.rows_in_array) *
719                                 long(sptr^.samplesperrow) *
720                                 long(SIZEOF(JSAMPLE)));
721         sptr^.b_s_open := TRUE;
722       end;
723       sptr^.mem_buffer := alloc_sarray(cinfo, JPOOL_IMAGE,
724                                       sptr^.samplesperrow, sptr^.rows_in_mem);
725       sptr^.rowsperchunk := mem^.last_rowsperchunk;
726       sptr^.cur_start_row := 0;
727       sptr^.first_undef_row := 0;
728       sptr^.dirty := FALSE;
729     end;
730     sptr := sptr^.next;
731   end;
732 
733   bptr := mem^.virt_barray_list;
734   while (bptr <> NIL) do
735   begin
736     if (bptr^.mem_buffer = NIL) then
737     begin { if not realized yet }
738       minheights := (long(bptr^.rows_in_array) - long(1)) div bptr^.maxaccess + long(1);
739       if (minheights <= max_minheights) then
740       begin
741         { This buffer fits in memory }
742         bptr^.rows_in_mem := bptr^.rows_in_array;
743       end
744       else
745       begin
746         { It doesn't fit in memory, create backing store. }
747         bptr^.rows_in_mem := JDIMENSION (max_minheights * bptr^.maxaccess);
748         jpeg_open_backing_store(cinfo,
749                                 @bptr^.b_s_info,
750                                 long(bptr^.rows_in_array) *
751                                 long(bptr^.blocksperrow) *
752                                 long(SIZEOF(JBLOCK)));
753         bptr^.b_s_open := TRUE;
754       end;
755       bptr^.mem_buffer := alloc_barray(cinfo, JPOOL_IMAGE,
756                                       bptr^.blocksperrow, bptr^.rows_in_mem);
757       bptr^.rowsperchunk := mem^.last_rowsperchunk;
758       bptr^.cur_start_row := 0;
759       bptr^.first_undef_row := 0;
760       bptr^.dirty := FALSE;
761     end;
762     bptr := bptr^.next;
763   end;
764 end;
765 
766 
767 {LOCAL}
768 procedure do_sarray_io (cinfo : j_common_ptr;
769                         ptr : jvirt_sarray_ptr;
770                         writing : boolean);
771 { Do backing store read or write of a virtual sample array }
772 var
773   bytesperrow, file_offset, byte_count, rows, thisrow, i : long;
774 begin
775 
776   bytesperrow := long(ptr^.samplesperrow * SIZEOF(JSAMPLE));
777   file_offset := ptr^.cur_start_row * bytesperrow;
778   { Loop to read or write each allocation chunk in mem_buffer }
779   i := 0;
780   while i < long(ptr^.rows_in_mem) do
781   begin
782 
783     { One chunk, but check for short chunk at end of buffer }
784     {rows := MIN(long(ptr^.rowsperchunk), long(ptr^.rows_in_mem - i));}
785     rows := long(ptr^.rowsperchunk);
786     if rows > long(ptr^.rows_in_mem - i) then
787       rows := long(ptr^.rows_in_mem - i);
788     { Transfer no more than is currently defined }
789     thisrow := long (ptr^.cur_start_row) + i;
790     {rows := MIN(rows, long(ptr^.first_undef_row) - thisrow);}
791     if (rows > long(ptr^.first_undef_row) - thisrow) then
792       rows := long(ptr^.first_undef_row) - thisrow;
793     { Transfer no more than fits in file }
794     {rows := MIN(rows, long(ptr^.rows_in_array) - thisrow);}
795     if (rows > long(ptr^.rows_in_array) - thisrow) then
796       rows := long(ptr^.rows_in_array) - thisrow;
797 
798     if (rows <= 0) then        { this chunk might be past end of file! }
799       break;
800     byte_count := rows * bytesperrow;
801     if (writing) then
802       ptr^.b_s_info.write_backing_store (cinfo,
803                                         @ptr^.b_s_info,
804                                         pointer {FAR} (ptr^.mem_buffer^[i]),
805                                         file_offset, byte_count)
806     else
807       ptr^.b_s_info.read_backing_store (cinfo,
808                                         @ptr^.b_s_info,
809                                         pointer {FAR} (ptr^.mem_buffer^[i]),
810                                         file_offset, byte_count);
811     Inc(file_offset, byte_count);
812     Inc(i, ptr^.rowsperchunk);
813   end;
814 end;
815 
816 
817 {LOCAL}
818 procedure do_barray_io (cinfo : j_common_ptr;
819                        ptr : jvirt_barray_ptr;
820                        writing : boolean);
821 { Do backing store read or write of a virtual coefficient-block array }
822 var
823   bytesperrow, file_offset, byte_count, rows, thisrow, i : long;
824 begin
825   bytesperrow := long (ptr^.blocksperrow) * SIZEOF(JBLOCK);
826   file_offset := ptr^.cur_start_row * bytesperrow;
827   { Loop to read or write each allocation chunk in mem_buffer }
828   i := 0;
829   while (i < long(ptr^.rows_in_mem)) do
830   begin
831     { One chunk, but check for short chunk at end of buffer }
832     {rows := MIN(long(ptr^.rowsperchunk), long(ptr^.rows_in_mem - i));}
833     rows := long(ptr^.rowsperchunk);
834     if rows >long(ptr^.rows_in_mem - i) then
835       rows := long(ptr^.rows_in_mem - i);
836     { Transfer no more than is currently defined }
837     thisrow := long (ptr^.cur_start_row) + i;
838     {rows := MIN(rows, long(ptr^.first_undef_row - thisrow));}
839     if rows > long(ptr^.first_undef_row - thisrow) then
840       rows := long(ptr^.first_undef_row - thisrow);
841     { Transfer no more than fits in file }
842     {rows := MIN(rows, long (ptr^.rows_in_array - thisrow));}
843     if (rows > long (ptr^.rows_in_array - thisrow)) then
844       rows := long (ptr^.rows_in_array - thisrow);
845 
846     if (rows <= 0) then         { this chunk might be past end of file! }
847       break;
848     byte_count := rows * bytesperrow;
849     if (writing) then
850       ptr^.b_s_info.write_backing_store (cinfo,
851                                          @ptr^.b_s_info,
852                                          {FAR} pointer(ptr^.mem_buffer^[i]),
853                                           file_offset, byte_count)
854     else
855       ptr^.b_s_info.read_backing_store (cinfo,
856                                         @ptr^.b_s_info,
857                                         {FAR} pointer(ptr^.mem_buffer^[i]),
858                                         file_offset, byte_count);
859     Inc(file_offset, byte_count);
860     Inc(i, ptr^.rowsperchunk);
861   end;
862 end;
863 
864 
865 {METHODDEF}
access_virt_sarraynull866 function access_virt_sarray (cinfo : j_common_ptr;
867                              ptr : jvirt_sarray_ptr;
868                              start_row : JDIMENSION;
869                              num_rows : JDIMENSION;
870                              writable : boolean ) : JSAMPARRAY; far;
871 { Access the part of a virtual sample array starting at start_row }
872 { and extending for num_rows rows.  writable is true if  }
873 { caller intends to modify the accessed area. }
874 var
875   end_row : JDIMENSION;
876   undef_row : JDIMENSION;
877 var
878   bytesperrow : size_t;
879 var
880   ltemp : long;
881 begin
882   end_row := start_row + num_rows;
883   { debugging check }
884   if (end_row > ptr^.rows_in_array) or (num_rows > ptr^.maxaccess) or
885      (ptr^.mem_buffer = NIL) then
886     ERREXIT(cinfo, JERR_BAD_VIRTUAL_ACCESS);
887 
888   { Make the desired part of the virtual array accessible }
889   if (start_row < ptr^.cur_start_row) or
890      (end_row > ptr^.cur_start_row+ptr^.rows_in_mem) then
891   begin
892     if (not ptr^.b_s_open) then
893       ERREXIT(cinfo, JERR_VIRTUAL_BUG);
894     { Flush old buffer contents if necessary }
895     if (ptr^.dirty) then
896     begin
897       do_sarray_io(cinfo, ptr, TRUE);
898       ptr^.dirty := FALSE;
899     end;
900     { Decide what part of virtual array to access.
901       Algorithm: if target address > current window, assume forward scan,
902       load starting at target address.  If target address < current window,
903       assume backward scan, load so that target area is top of window.
904       Note that when switching from forward write to forward read, will have
905       start_row := 0, so the limiting case applies and we load from 0 anyway. }
906     if (start_row > ptr^.cur_start_row) then
907     begin
908       ptr^.cur_start_row := start_row;
909     end
910     else
911     begin
912       { use long arithmetic here to avoid overflow & unsigned problems }
913 
914 
915       ltemp := long(end_row) - long(ptr^.rows_in_mem);
916       if (ltemp < 0) then
917         ltemp := 0;             { don't fall off front end of file }
918       ptr^.cur_start_row := JDIMENSION(ltemp);
919     end;
920     { Read in the selected part of the array.
921       During the initial write pass, we will do no actual read
922       because the selected part is all undefined. }
923 
924     do_sarray_io(cinfo, ptr, FALSE);
925   end;
926   { Ensure the accessed part of the array is defined; prezero if needed.
927     To improve locality of access, we only prezero the part of the array
928     that the caller is about to access, not the entire in-memory array. }
929   if (ptr^.first_undef_row < end_row) then
930   begin
931     if (ptr^.first_undef_row < start_row) then
932     begin
933       if (writable) then        { writer skipped over a section of array }
934         ERREXIT(cinfo, JERR_BAD_VIRTUAL_ACCESS);
935       undef_row := start_row;   { but reader is allowed to read ahead }
936     end
937     else
938     begin
939       undef_row := ptr^.first_undef_row;
940     end;
941     if (writable) then
942       ptr^.first_undef_row := end_row;
943     if (ptr^.pre_zero) then
944     begin
945       bytesperrow := size_t(ptr^.samplesperrow) * SIZEOF(JSAMPLE);
946       Dec(undef_row, ptr^.cur_start_row); { make indexes relative to buffer }
947       Dec(end_row, ptr^.cur_start_row);
948       while (undef_row < end_row) do
949       begin
950         jzero_far({FAR} pointer(ptr^.mem_buffer^[undef_row]), bytesperrow);
951         Inc(undef_row);
952       end;
953     end
954     else
955     begin
956       if (not writable) then    { reader looking at undefined data }
957         ERREXIT(cinfo, JERR_BAD_VIRTUAL_ACCESS);
958     end;
959   end;
960   { Flag the buffer dirty if caller will write in it }
961   if (writable) then
962     ptr^.dirty := TRUE;
963   { Return address of proper part of the buffer }
964   access_virt_sarray := JSAMPARRAY(@ ptr^.mem_buffer^[start_row - ptr^.cur_start_row]);
965 end;
966 
967 
968 {METHODDEF}
access_virt_barraynull969 function access_virt_barray (cinfo : j_common_ptr;
970                              ptr : jvirt_barray_ptr;
971                              start_row : JDIMENSION;
972                              num_rows : JDIMENSION;
973                              writable : boolean) : JBLOCKARRAY; far;
974 { Access the part of a virtual block array starting at start_row }
975 { and extending for num_rows rows.  writable is true if  }
976 { caller intends to modify the accessed area. }
977 var
978   end_row : JDIMENSION;
979   undef_row : JDIMENSION;
980   ltemp : long;
981 var
982   bytesperrow : size_t;
983 begin
984   end_row := start_row + num_rows;
985 
986   { debugging check }
987   if (end_row > ptr^.rows_in_array) or (num_rows > ptr^.maxaccess) or
988      (ptr^.mem_buffer = NIL) then
989     ERREXIT(cinfo, JERR_BAD_VIRTUAL_ACCESS);
990 
991   { Make the desired part of the virtual array accessible }
992   if (start_row < ptr^.cur_start_row) or
993      (end_row > ptr^.cur_start_row+ptr^.rows_in_mem) then
994   begin
995     if (not ptr^.b_s_open) then
996       ERREXIT(cinfo, JERR_VIRTUAL_BUG);
997     { Flush old buffer contents if necessary }
998     if (ptr^.dirty) then
999     begin
1000       do_barray_io(cinfo, ptr, TRUE);
1001       ptr^.dirty := FALSE;
1002     end;
1003     { Decide what part of virtual array to access.
1004       Algorithm: if target address > current window, assume forward scan,
1005       load starting at target address.  If target address < current window,
1006       assume backward scan, load so that target area is top of window.
1007       Note that when switching from forward write to forward read, will have
1008       start_row := 0, so the limiting case applies and we load from 0 anyway. }
1009 
1010     if (start_row > ptr^.cur_start_row) then
1011     begin
1012       ptr^.cur_start_row := start_row;
1013     end
1014     else
1015     begin
1016       { use long arithmetic here to avoid overflow & unsigned problems }
1017 
1018       ltemp := long(end_row) - long(ptr^.rows_in_mem);
1019       if (ltemp < 0) then
1020         ltemp := 0;             { don't fall off front end of file }
1021       ptr^.cur_start_row := JDIMENSION (ltemp);
1022     end;
1023     { Read in the selected part of the array.
1024       During the initial write pass, we will do no actual read
1025       because the selected part is all undefined. }
1026 
1027     do_barray_io(cinfo, ptr, FALSE);
1028   end;
1029   { Ensure the accessed part of the array is defined; prezero if needed.
1030     To improve locality of access, we only prezero the part of the array
1031     that the caller is about to access, not the entire in-memory array. }
1032 
1033   if (ptr^.first_undef_row < end_row) then
1034   begin
1035     if (ptr^.first_undef_row < start_row) then
1036     begin
1037       if (writable) then        { writer skipped over a section of array }
1038         ERREXIT(cinfo, JERR_BAD_VIRTUAL_ACCESS);
1039       undef_row := start_row;   { but reader is allowed to read ahead }
1040     end
1041     else
1042     begin
1043       undef_row := ptr^.first_undef_row;
1044     end;
1045     if (writable) then
1046       ptr^.first_undef_row := end_row;
1047     if (ptr^.pre_zero) then
1048     begin
1049       bytesperrow := size_t (ptr^.blocksperrow) * SIZEOF(JBLOCK);
1050       Dec(undef_row, ptr^.cur_start_row); { make indexes relative to buffer }
1051       Dec(end_row, ptr^.cur_start_row);
1052       while (undef_row < end_row) do
1053       begin
1054         jzero_far({FAR}pointer(ptr^.mem_buffer^[undef_row]), bytesperrow);
1055         Inc(undef_row);
1056       end;
1057     end
1058     else
1059     begin
1060       if (not writable) then    { reader looking at undefined data }
1061         ERREXIT(cinfo, JERR_BAD_VIRTUAL_ACCESS);
1062     end;
1063   end;
1064   { Flag the buffer dirty if caller will write in it }
1065   if (writable) then
1066     ptr^.dirty := TRUE;
1067   { Return address of proper part of the buffer }
1068   access_virt_barray := JBLOCKARRAY(@ ptr^.mem_buffer^[start_row - ptr^.cur_start_row]);
1069 end;
1070 
1071 
1072 { Release all objects belonging to a specified pool. }
1073 
1074 {METHODDEF}
1075 procedure free_pool (cinfo : j_common_ptr; pool_id : int); far;
1076 var
1077   mem : my_mem_ptr;
1078   shdr_ptr : small_pool_ptr;
1079   lhdr_ptr : large_pool_ptr;
1080   space_freed : size_t;
1081 var
1082   sptr : jvirt_sarray_ptr;
1083   bptr : jvirt_barray_ptr;
1084 var
1085   next_lhdr_ptr : large_pool_ptr;
1086   next_shdr_ptr : small_pool_ptr;
1087 begin
1088   mem := my_mem_ptr(cinfo^.mem);
1089 
1090   if (pool_id < 0) or (pool_id >= JPOOL_NUMPOOLS) then
1091     ERREXIT1(cinfo, JERR_BAD_POOL_ID, pool_id); { safety check }
1092 
1093 {$ifdef MEM_STATS}
1094   if (cinfo^.err^.trace_level > 1) then
1095     print_mem_stats(cinfo, pool_id); { print pool's memory usage statistics }
1096 {$endif}
1097 
1098   { If freeing IMAGE pool, close any virtual arrays first }
1099   if (pool_id = JPOOL_IMAGE) then
1100   begin
1101     sptr := mem^.virt_sarray_list;
1102     while (sptr <> NIL) do
1103     begin
1104       if (sptr^.b_s_open) then
1105       begin     { there may be no backing store }
1106         sptr^.b_s_open := FALSE;        { prevent recursive close if error }
1107         sptr^.b_s_info.close_backing_store (cinfo, @sptr^.b_s_info);
1108       end;
1109       sptr := sptr^.next;
1110     end;
1111     mem^.virt_sarray_list := NIL;
1112     bptr := mem^.virt_barray_list;
1113     while (bptr <> NIL) do
1114     begin
1115       if (bptr^.b_s_open) then
1116       begin     { there may be no backing store }
1117         bptr^.b_s_open := FALSE;        { prevent recursive close if error }
1118         bptr^.b_s_info.close_backing_store (cinfo, @bptr^.b_s_info);
1119       end;
1120       bptr := bptr^.next;
1121     end;
1122     mem^.virt_barray_list := NIL;
1123   end;
1124 
1125   { Release large objects }
1126   lhdr_ptr := mem^.large_list[pool_id];
1127   mem^.large_list[pool_id] := NIL;
1128 
1129   while (lhdr_ptr <> NIL) do
1130   begin
1131     next_lhdr_ptr := lhdr_ptr^.hdr.next;
1132     space_freed := lhdr_ptr^.hdr.bytes_used +
1133                   lhdr_ptr^.hdr.bytes_left +
1134                   SIZEOF(large_pool_hdr);
1135     jpeg_free_large(cinfo, {FAR} pointer(lhdr_ptr), space_freed);
1136     Dec(mem^.total_space_allocated, space_freed);
1137     lhdr_ptr := next_lhdr_ptr;
1138   end;
1139 
1140   { Release small objects }
1141   shdr_ptr := mem^.small_list[pool_id];
1142   mem^.small_list[pool_id] := NIL;
1143 
1144   while (shdr_ptr <> NIL) do
1145   begin
1146     next_shdr_ptr := shdr_ptr^.hdr.next;
1147     space_freed := shdr_ptr^.hdr.bytes_used +
1148                   shdr_ptr^.hdr.bytes_left +
1149                   SIZEOF(small_pool_hdr);
1150     jpeg_free_small(cinfo, pointer(shdr_ptr), space_freed);
1151     Dec(mem^.total_space_allocated, space_freed);
1152     shdr_ptr := next_shdr_ptr;
1153   end;
1154 end;
1155 
1156 
1157 { Close up shop entirely.
1158   Note that this cannot be called unless cinfo^.mem is non-NIL. }
1159 
1160 {METHODDEF}
1161 procedure self_destruct (cinfo : j_common_ptr); far;
1162 var
1163   pool : int;
1164 begin
1165   { Close all backing store, release all memory.
1166     Releasing pools in reverse order might help avoid fragmentation
1167     with some (brain-damaged) malloc libraries. }
1168 
1169   for pool := JPOOL_NUMPOOLS-1 downto JPOOL_PERMANENT do
1170   begin
1171     free_pool(cinfo, pool);
1172   end;
1173 
1174   { Release the memory manager control block too. }
1175   jpeg_free_small(cinfo, pointer(cinfo^.mem), SIZEOF(my_memory_mgr));
1176   cinfo^.mem := NIL;            { ensures I will be called only once }
1177 
1178   jpeg_mem_term(cinfo);         { system-dependent cleanup }
1179 end;
1180 
1181 
1182 { Memory manager initialization.
1183   When this is called, only the error manager pointer is valid in cinfo! }
1184 
1185 {GLOBAL}
1186 procedure jinit_memory_mgr (cinfo : j_common_ptr);
1187 var
1188   mem : my_mem_ptr;
1189   max_to_use : long;
1190   pool : int;
1191   test_mac : size_t;
1192 {$ifndef NO_GETENV}
1193 var
1194   memenv : string;
1195   code : integer;
1196 {$endif}
1197 begin
1198   cinfo^.mem := NIL;            { for safety if init fails }
1199 
1200   { Check for configuration errors.
1201     SIZEOF(ALIGN_TYPE) should be a power of 2; otherwise, it probably
1202     doesn't reflect any real hardware alignment requirement.
1203     The test is a little tricky: for X>0, X and X-1 have no one-bits
1204     in common if and only if X is a power of 2, ie has only one one-bit.
1205     Some compilers may give an "unreachable code" warning here; ignore it. }
1206   if ((SIZEOF(ALIGN_TYPE) and (SIZEOF(ALIGN_TYPE)-1)) <> 0) then
1207     ERREXIT(cinfo, JERR_BAD_ALIGN_TYPE);
1208   { MAX_ALLOC_CHUNK must be representable as type size_t, and must be
1209     a multiple of SIZEOF(ALIGN_TYPE).
1210     Again, an "unreachable code" warning may be ignored here.
1211     But a "constant too large" warning means you need to fix MAX_ALLOC_CHUNK. }
1212 
1213   test_mac := size_t (MAX_ALLOC_CHUNK);
1214   if (long (test_mac) <> MAX_ALLOC_CHUNK) or
1215       ((MAX_ALLOC_CHUNK mod SIZEOF(ALIGN_TYPE)) <> 0) then
1216     ERREXIT(cinfo, JERR_BAD_ALLOC_CHUNK);
1217 
1218   max_to_use := jpeg_mem_init(cinfo); { system-dependent initialization }
1219 
1220   { Attempt to allocate memory manager's control block }
1221   mem := my_mem_ptr (jpeg_get_small(cinfo, SIZEOF(my_memory_mgr)));
1222 
1223   if (mem = NIL) then
1224   begin
1225     jpeg_mem_term(cinfo);       { system-dependent cleanup }
1226     ERREXIT1(cinfo, JERR_OUT_OF_MEMORY, 0);
1227   end;
1228 
1229   { OK, fill in the method pointers }
1230   mem^.pub.alloc_small := alloc_small;
1231   mem^.pub.alloc_large := alloc_large;
1232   mem^.pub.alloc_sarray := alloc_sarray;
1233   mem^.pub.alloc_barray := alloc_barray;
1234   mem^.pub.request_virt_sarray := request_virt_sarray;
1235   mem^.pub.request_virt_barray := request_virt_barray;
1236   mem^.pub.realize_virt_arrays := realize_virt_arrays;
1237   mem^.pub.access_virt_sarray := access_virt_sarray;
1238   mem^.pub.access_virt_barray := access_virt_barray;
1239   mem^.pub.free_pool := free_pool;
1240   mem^.pub.self_destruct := self_destruct;
1241 
1242   { Make MAX_ALLOC_CHUNK accessible to other modules }
1243   mem^.pub.max_alloc_chunk := MAX_ALLOC_CHUNK;
1244 
1245   { Initialize working state }
1246   mem^.pub.max_memory_to_use := max_to_use;
1247 
1248   for pool := JPOOL_NUMPOOLS-1 downto JPOOL_PERMANENT do
1249   begin
1250     mem^.small_list[pool] := NIL;
1251     mem^.large_list[pool] := NIL;
1252   end;
1253   mem^.virt_sarray_list := NIL;
1254   mem^.virt_barray_list := NIL;
1255 
1256   mem^.total_space_allocated := SIZEOF(my_memory_mgr);
1257 
1258   { Declare ourselves open for business }
1259   cinfo^.mem := @mem^.pub;
1260 
1261   { Check for an environment variable JPEGMEM; if found, override the
1262     default max_memory setting from jpeg_mem_init.  Note that the
1263     surrounding application may again override this value.
1264     If your system doesn't support getenv(), define NO_GETENV to disable
1265     this feature. }
1266 
1267 {$ifndef NO_GETENV}
1268   memenv := getenv('JPEGMEM');
1269   if (memenv <> '') then
1270   begin
1271     Val(memenv, max_to_use, code);
1272     if (Code = 0) then
1273     begin
1274       max_to_use := max_to_use * long(1000);
1275       mem^.pub.max_memory_to_use := max_to_use * long(1000);
1276     end;
1277   end;
1278 {$endif}
1279 
1280 end;
1281 
1282 end.
1283