Merge from mainline (167278:168000).
[official-gcc/graphite-test-results.git] / gcc / ada / g-debpoo.adb
blobef7ce9e3dbd3e8667ae195da41ef9353905538db
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- G N A T . D E B U G _ P O O L S --
6 -- --
7 -- B o d y --
8 -- --
9 -- Copyright (C) 1992-2009, Free Software Foundation, Inc. --
10 -- --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 3, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. --
17 -- --
18 -- As a special exception under Section 7 of GPL version 3, you are granted --
19 -- additional permissions described in the GCC Runtime Library Exception, --
20 -- version 3.1, as published by the Free Software Foundation. --
21 -- --
22 -- You should have received a copy of the GNU General Public License and --
23 -- a copy of the GCC Runtime Library Exception along with this program; --
24 -- see the files COPYING3 and COPYING.RUNTIME respectively. If not, see --
25 -- <http://www.gnu.org/licenses/>. --
26 -- --
27 -- GNAT was originally developed by the GNAT team at New York University. --
28 -- Extensive contributions were provided by Ada Core Technologies Inc. --
29 -- --
30 ------------------------------------------------------------------------------
32 with Ada.Exceptions.Traceback;
33 with GNAT.IO; use GNAT.IO;
35 with System.Address_Image;
36 with System.Memory; use System.Memory;
37 with System.Soft_Links; use System.Soft_Links;
39 with System.Traceback_Entries; use System.Traceback_Entries;
41 with GNAT.HTable;
42 with GNAT.Traceback; use GNAT.Traceback;
44 with Ada.Unchecked_Conversion;
46 package body GNAT.Debug_Pools is
48 Default_Alignment : constant := Standard'Maximum_Alignment;
49 -- Alignment used for the memory chunks returned by Allocate. Using this
50 -- value guarantees that this alignment will be compatible with all types
51 -- and at the same time makes it easy to find the location of the extra
52 -- header allocated for each chunk.
54 Max_Ignored_Levels : constant Natural := 10;
55 -- Maximum number of levels that will be ignored in backtraces. This is so
56 -- that we still have enough significant levels in the tracebacks returned
57 -- to the user.
59 -- The value 10 is chosen as being greater than the maximum callgraph
60 -- in this package. Its actual value is not really relevant, as long as it
61 -- is high enough to make sure we still have enough frames to return to
62 -- the user after we have hidden the frames internal to this package.
64 ---------------------------
65 -- Back Trace Hash Table --
66 ---------------------------
68 -- This package needs to store one set of tracebacks for each allocation
69 -- point (when was it allocated or deallocated). This would use too much
70 -- memory, so the tracebacks are actually stored in a hash table, and
71 -- we reference elements in this hash table instead.
73 -- This hash-table will remain empty if the discriminant Stack_Trace_Depth
74 -- for the pools is set to 0.
76 -- This table is a global table, that can be shared among all debug pools
77 -- with no problems.
79 type Header is range 1 .. 1023;
80 -- Number of elements in the hash-table
82 type Tracebacks_Array_Access
83 is access GNAT.Traceback.Tracebacks_Array;
85 type Traceback_Kind is (Alloc, Dealloc, Indirect_Alloc, Indirect_Dealloc);
87 type Traceback_Htable_Elem;
88 type Traceback_Htable_Elem_Ptr
89 is access Traceback_Htable_Elem;
91 type Traceback_Htable_Elem is record
92 Traceback : Tracebacks_Array_Access;
93 Kind : Traceback_Kind;
94 Count : Natural;
95 Total : Byte_Count;
96 Next : Traceback_Htable_Elem_Ptr;
97 end record;
99 -- Subprograms used for the Backtrace_Htable instantiation
101 procedure Set_Next
102 (E : Traceback_Htable_Elem_Ptr;
103 Next : Traceback_Htable_Elem_Ptr);
104 pragma Inline (Set_Next);
106 function Next
107 (E : Traceback_Htable_Elem_Ptr) return Traceback_Htable_Elem_Ptr;
108 pragma Inline (Next);
110 function Get_Key
111 (E : Traceback_Htable_Elem_Ptr) return Tracebacks_Array_Access;
112 pragma Inline (Get_Key);
114 function Hash (T : Tracebacks_Array_Access) return Header;
115 pragma Inline (Hash);
117 function Equal (K1, K2 : Tracebacks_Array_Access) return Boolean;
118 -- Why is this not inlined???
120 -- The hash table for back traces
122 package Backtrace_Htable is new GNAT.HTable.Static_HTable
123 (Header_Num => Header,
124 Element => Traceback_Htable_Elem,
125 Elmt_Ptr => Traceback_Htable_Elem_Ptr,
126 Null_Ptr => null,
127 Set_Next => Set_Next,
128 Next => Next,
129 Key => Tracebacks_Array_Access,
130 Get_Key => Get_Key,
131 Hash => Hash,
132 Equal => Equal);
134 -----------------------
135 -- Allocations table --
136 -----------------------
138 type Allocation_Header;
139 type Allocation_Header_Access is access Allocation_Header;
141 type Traceback_Ptr_Or_Address is new System.Address;
142 -- A type that acts as a C union, and is either a System.Address or a
143 -- Traceback_Htable_Elem_Ptr.
145 -- The following record stores extra information that needs to be
146 -- memorized for each block allocated with the special debug pool.
148 type Allocation_Header is record
149 Allocation_Address : System.Address;
150 -- Address of the block returned by malloc, possibly unaligned
152 Block_Size : Storage_Offset;
153 -- Needed only for advanced freeing algorithms (traverse all allocated
154 -- blocks for potential references). This value is negated when the
155 -- chunk of memory has been logically freed by the application. This
156 -- chunk has not been physically released yet.
158 Alloc_Traceback : Traceback_Htable_Elem_Ptr;
159 -- ??? comment required
161 Dealloc_Traceback : Traceback_Ptr_Or_Address;
162 -- Pointer to the traceback for the allocation (if the memory chunk is
163 -- still valid), or to the first deallocation otherwise. Make sure this
164 -- is a thin pointer to save space.
166 -- Dealloc_Traceback is also for blocks that are still allocated to
167 -- point to the previous block in the list. This saves space in this
168 -- header, and make manipulation of the lists of allocated pointers
169 -- faster.
171 Next : System.Address;
172 -- Point to the next block of the same type (either allocated or
173 -- logically freed) in memory. This points to the beginning of the user
174 -- data, and does not include the header of that block.
175 end record;
177 function Header_Of (Address : System.Address)
178 return Allocation_Header_Access;
179 pragma Inline (Header_Of);
180 -- Return the header corresponding to a previously allocated address
182 function To_Address is new Ada.Unchecked_Conversion
183 (Traceback_Ptr_Or_Address, System.Address);
185 function To_Address is new Ada.Unchecked_Conversion
186 (System.Address, Traceback_Ptr_Or_Address);
188 function To_Traceback is new Ada.Unchecked_Conversion
189 (Traceback_Ptr_Or_Address, Traceback_Htable_Elem_Ptr);
191 function To_Traceback is new Ada.Unchecked_Conversion
192 (Traceback_Htable_Elem_Ptr, Traceback_Ptr_Or_Address);
194 Header_Offset : constant Storage_Count :=
195 Default_Alignment *
196 ((Allocation_Header'Size / System.Storage_Unit
197 + Default_Alignment - 1) / Default_Alignment);
198 -- Offset of user data after allocation header
200 Minimum_Allocation : constant Storage_Count :=
201 Default_Alignment - 1 + Header_Offset;
202 -- Minimal allocation: size of allocation_header rounded up to next
203 -- multiple of default alignment + worst-case padding.
205 -----------------------
206 -- Local subprograms --
207 -----------------------
209 function Find_Or_Create_Traceback
210 (Pool : Debug_Pool;
211 Kind : Traceback_Kind;
212 Size : Storage_Count;
213 Ignored_Frame_Start : System.Address;
214 Ignored_Frame_End : System.Address) return Traceback_Htable_Elem_Ptr;
215 -- Return an element matching the current traceback (omitting the frames
216 -- that are in the current package). If this traceback already existed in
217 -- the htable, a pointer to this is returned to spare memory. Null is
218 -- returned if the pool is set not to store tracebacks. If the traceback
219 -- already existed in the table, the count is incremented so that
220 -- Dump_Tracebacks returns useful results. All addresses up to, and
221 -- including, an address between Ignored_Frame_Start .. Ignored_Frame_End
222 -- are ignored.
224 function Output_File (Pool : Debug_Pool) return File_Type;
225 pragma Inline (Output_File);
226 -- Returns file_type on which error messages have to be generated for Pool
228 procedure Put_Line
229 (File : File_Type;
230 Depth : Natural;
231 Traceback : Tracebacks_Array_Access;
232 Ignored_Frame_Start : System.Address := System.Null_Address;
233 Ignored_Frame_End : System.Address := System.Null_Address);
234 -- Print Traceback to File. If Traceback is null, print the call_chain
235 -- at the current location, up to Depth levels, ignoring all addresses
236 -- up to the first one in the range:
237 -- Ignored_Frame_Start .. Ignored_Frame_End
239 package Validity is
240 function Is_Valid (Storage : System.Address) return Boolean;
241 pragma Inline (Is_Valid);
242 -- Return True if Storage is the address of a block that the debug pool
243 -- has under its control, in which case Header_Of may be used to access
244 -- the associated allocation header.
246 procedure Set_Valid (Storage : System.Address; Value : Boolean);
247 pragma Inline (Set_Valid);
248 -- Mark the address Storage as being under control of the memory pool
249 -- (if Value is True), or not (if Value is False).
250 end Validity;
252 use Validity;
254 procedure Set_Dead_Beef
255 (Storage_Address : System.Address;
256 Size_In_Storage_Elements : Storage_Count);
257 -- Set the contents of the memory block pointed to by Storage_Address to
258 -- the 16#DEADBEEF# pattern. If Size_In_Storage_Elements is not a multiple
259 -- of the length of this pattern, the last instance may be partial.
261 procedure Free_Physically (Pool : in out Debug_Pool);
262 -- Start to physically release some memory to the system, until the amount
263 -- of logically (but not physically) freed memory is lower than the
264 -- expected amount in Pool.
266 procedure Allocate_End;
267 procedure Deallocate_End;
268 procedure Dereference_End;
269 -- These procedures are used as markers when computing the stacktraces,
270 -- so that addresses in the debug pool itself are not reported to the user.
272 Code_Address_For_Allocate_End : System.Address;
273 Code_Address_For_Deallocate_End : System.Address;
274 Code_Address_For_Dereference_End : System.Address;
275 -- Taking the address of the above procedures will not work on some
276 -- architectures (HPUX and VMS for instance). Thus we do the same thing
277 -- that is done in a-except.adb, and get the address of labels instead
279 procedure Skip_Levels
280 (Depth : Natural;
281 Trace : Tracebacks_Array;
282 Start : out Natural;
283 Len : in out Natural;
284 Ignored_Frame_Start : System.Address;
285 Ignored_Frame_End : System.Address);
286 -- Set Start .. Len to the range of values from Trace that should be output
287 -- to the user. This range of values excludes any address prior to the
288 -- first one in Ignored_Frame_Start .. Ignored_Frame_End (basically
289 -- addresses internal to this package). Depth is the number of levels that
290 -- the user is interested in.
292 ---------------
293 -- Header_Of --
294 ---------------
296 function Header_Of (Address : System.Address)
297 return Allocation_Header_Access
299 function Convert is new Ada.Unchecked_Conversion
300 (System.Address, Allocation_Header_Access);
301 begin
302 return Convert (Address - Header_Offset);
303 end Header_Of;
305 --------------
306 -- Set_Next --
307 --------------
309 procedure Set_Next
310 (E : Traceback_Htable_Elem_Ptr;
311 Next : Traceback_Htable_Elem_Ptr)
313 begin
314 E.Next := Next;
315 end Set_Next;
317 ----------
318 -- Next --
319 ----------
321 function Next
322 (E : Traceback_Htable_Elem_Ptr) return Traceback_Htable_Elem_Ptr is
323 begin
324 return E.Next;
325 end Next;
327 -----------
328 -- Equal --
329 -----------
331 function Equal (K1, K2 : Tracebacks_Array_Access) return Boolean is
332 use Ada.Exceptions.Traceback;
333 begin
334 return K1.all = K2.all;
335 end Equal;
337 -------------
338 -- Get_Key --
339 -------------
341 function Get_Key
342 (E : Traceback_Htable_Elem_Ptr) return Tracebacks_Array_Access
344 begin
345 return E.Traceback;
346 end Get_Key;
348 ----------
349 -- Hash --
350 ----------
352 function Hash (T : Tracebacks_Array_Access) return Header is
353 Result : Integer_Address := 0;
355 begin
356 for X in T'Range loop
357 Result := Result + To_Integer (PC_For (T (X)));
358 end loop;
360 return Header (1 + Result mod Integer_Address (Header'Last));
361 end Hash;
363 -----------------
364 -- Output_File --
365 -----------------
367 function Output_File (Pool : Debug_Pool) return File_Type is
368 begin
369 if Pool.Errors_To_Stdout then
370 return Standard_Output;
371 else
372 return Standard_Error;
373 end if;
374 end Output_File;
376 --------------
377 -- Put_Line --
378 --------------
380 procedure Put_Line
381 (File : File_Type;
382 Depth : Natural;
383 Traceback : Tracebacks_Array_Access;
384 Ignored_Frame_Start : System.Address := System.Null_Address;
385 Ignored_Frame_End : System.Address := System.Null_Address)
387 procedure Print (Tr : Tracebacks_Array);
388 -- Print the traceback to standard_output
390 -----------
391 -- Print --
392 -----------
394 procedure Print (Tr : Tracebacks_Array) is
395 begin
396 for J in Tr'Range loop
397 Put (File, "0x" & Address_Image (PC_For (Tr (J))) & ' ');
398 end loop;
399 Put (File, ASCII.LF);
400 end Print;
402 -- Start of processing for Put_Line
404 begin
405 if Traceback = null then
406 declare
407 Tr : aliased Tracebacks_Array (1 .. Depth + Max_Ignored_Levels);
408 Start, Len : Natural;
410 begin
411 Call_Chain (Tr, Len);
412 Skip_Levels (Depth, Tr, Start, Len,
413 Ignored_Frame_Start, Ignored_Frame_End);
414 Print (Tr (Start .. Len));
415 end;
417 else
418 Print (Traceback.all);
419 end if;
420 end Put_Line;
422 -----------------
423 -- Skip_Levels --
424 -----------------
426 procedure Skip_Levels
427 (Depth : Natural;
428 Trace : Tracebacks_Array;
429 Start : out Natural;
430 Len : in out Natural;
431 Ignored_Frame_Start : System.Address;
432 Ignored_Frame_End : System.Address)
434 begin
435 Start := Trace'First;
437 while Start <= Len
438 and then (PC_For (Trace (Start)) < Ignored_Frame_Start
439 or else PC_For (Trace (Start)) > Ignored_Frame_End)
440 loop
441 Start := Start + 1;
442 end loop;
444 Start := Start + 1;
446 -- Just in case: make sure we have a traceback even if Ignore_Till
447 -- wasn't found.
449 if Start > Len then
450 Start := 1;
451 end if;
453 if Len - Start + 1 > Depth then
454 Len := Depth + Start - 1;
455 end if;
456 end Skip_Levels;
458 ------------------------------
459 -- Find_Or_Create_Traceback --
460 ------------------------------
462 function Find_Or_Create_Traceback
463 (Pool : Debug_Pool;
464 Kind : Traceback_Kind;
465 Size : Storage_Count;
466 Ignored_Frame_Start : System.Address;
467 Ignored_Frame_End : System.Address) return Traceback_Htable_Elem_Ptr
469 begin
470 if Pool.Stack_Trace_Depth = 0 then
471 return null;
472 end if;
474 declare
475 Trace : aliased Tracebacks_Array
476 (1 .. Integer (Pool.Stack_Trace_Depth) + Max_Ignored_Levels);
477 Len, Start : Natural;
478 Elem : Traceback_Htable_Elem_Ptr;
480 begin
481 Call_Chain (Trace, Len);
482 Skip_Levels (Pool.Stack_Trace_Depth, Trace, Start, Len,
483 Ignored_Frame_Start, Ignored_Frame_End);
485 -- Check if the traceback is already in the table
487 Elem :=
488 Backtrace_Htable.Get (Trace (Start .. Len)'Unrestricted_Access);
490 -- If not, insert it
492 if Elem = null then
493 Elem := new Traceback_Htable_Elem'
494 (Traceback => new Tracebacks_Array'(Trace (Start .. Len)),
495 Count => 1,
496 Kind => Kind,
497 Total => Byte_Count (Size),
498 Next => null);
499 Backtrace_Htable.Set (Elem);
501 else
502 Elem.Count := Elem.Count + 1;
503 Elem.Total := Elem.Total + Byte_Count (Size);
504 end if;
506 return Elem;
507 end;
508 end Find_Or_Create_Traceback;
510 --------------
511 -- Validity --
512 --------------
514 package body Validity is
516 -- The validity bits of the allocated blocks are kept in a has table.
517 -- Each component of the hash table contains the validity bits for a
518 -- 16 Mbyte memory chunk.
520 -- The reason the validity bits are kept for chunks of memory rather
521 -- than in a big array is that on some 64 bit platforms, it may happen
522 -- that two chunk of allocated data are very far from each other.
524 Memory_Chunk_Size : constant Integer_Address := 2 ** 24; -- 16 MB
525 Validity_Divisor : constant := Default_Alignment * System.Storage_Unit;
527 Max_Validity_Byte_Index : constant :=
528 Memory_Chunk_Size / Validity_Divisor;
530 subtype Validity_Byte_Index is Integer_Address
531 range 0 .. Max_Validity_Byte_Index - 1;
533 type Byte is mod 2 ** System.Storage_Unit;
535 type Validity_Bits is array (Validity_Byte_Index) of Byte;
537 type Validity_Bits_Ref is access all Validity_Bits;
538 No_Validity_Bits : constant Validity_Bits_Ref := null;
540 Max_Header_Num : constant := 1023;
542 type Header_Num is range 0 .. Max_Header_Num - 1;
544 function Hash (F : Integer_Address) return Header_Num;
546 package Validy_Htable is new GNAT.HTable.Simple_HTable
547 (Header_Num => Header_Num,
548 Element => Validity_Bits_Ref,
549 No_Element => No_Validity_Bits,
550 Key => Integer_Address,
551 Hash => Hash,
552 Equal => "=");
553 -- Table to keep the validity bit blocks for the allocated data
555 function To_Pointer is new Ada.Unchecked_Conversion
556 (System.Address, Validity_Bits_Ref);
558 procedure Memset (A : Address; C : Integer; N : size_t);
559 pragma Import (C, Memset, "memset");
561 ----------
562 -- Hash --
563 ----------
565 function Hash (F : Integer_Address) return Header_Num is
566 begin
567 return Header_Num (F mod Max_Header_Num);
568 end Hash;
570 --------------
571 -- Is_Valid --
572 --------------
574 function Is_Valid (Storage : System.Address) return Boolean is
575 Int_Storage : constant Integer_Address := To_Integer (Storage);
577 begin
578 -- The pool only returns addresses aligned on Default_Alignment so
579 -- anything off cannot be a valid block address and we can return
580 -- early in this case. We actually have to since our data structures
581 -- map validity bits for such aligned addresses only.
583 if Int_Storage mod Default_Alignment /= 0 then
584 return False;
585 end if;
587 declare
588 Block_Number : constant Integer_Address :=
589 Int_Storage / Memory_Chunk_Size;
590 Ptr : constant Validity_Bits_Ref :=
591 Validy_Htable.Get (Block_Number);
592 Offset : constant Integer_Address :=
593 (Int_Storage -
594 (Block_Number * Memory_Chunk_Size)) /
595 Default_Alignment;
596 Bit : constant Byte :=
597 2 ** Natural (Offset mod System.Storage_Unit);
598 begin
599 if Ptr = No_Validity_Bits then
600 return False;
601 else
602 return (Ptr (Offset / System.Storage_Unit) and Bit) /= 0;
603 end if;
604 end;
605 end Is_Valid;
607 ---------------
608 -- Set_Valid --
609 ---------------
611 procedure Set_Valid (Storage : System.Address; Value : Boolean) is
612 Int_Storage : constant Integer_Address := To_Integer (Storage);
613 Block_Number : constant Integer_Address :=
614 Int_Storage / Memory_Chunk_Size;
615 Ptr : Validity_Bits_Ref := Validy_Htable.Get (Block_Number);
616 Offset : constant Integer_Address :=
617 (Int_Storage - (Block_Number * Memory_Chunk_Size)) /
618 Default_Alignment;
619 Bit : constant Byte :=
620 2 ** Natural (Offset mod System.Storage_Unit);
622 begin
623 if Ptr = No_Validity_Bits then
625 -- First time in this memory area: allocate a new block and put
626 -- it in the table.
628 if Value then
629 Ptr := To_Pointer (Alloc (size_t (Max_Validity_Byte_Index)));
630 Validy_Htable.Set (Block_Number, Ptr);
631 Memset (Ptr.all'Address, 0, size_t (Max_Validity_Byte_Index));
632 Ptr (Offset / System.Storage_Unit) := Bit;
633 end if;
635 else
636 if Value then
637 Ptr (Offset / System.Storage_Unit) :=
638 Ptr (Offset / System.Storage_Unit) or Bit;
640 else
641 Ptr (Offset / System.Storage_Unit) :=
642 Ptr (Offset / System.Storage_Unit) and (not Bit);
643 end if;
644 end if;
645 end Set_Valid;
647 end Validity;
649 --------------
650 -- Allocate --
651 --------------
653 procedure Allocate
654 (Pool : in out Debug_Pool;
655 Storage_Address : out Address;
656 Size_In_Storage_Elements : Storage_Count;
657 Alignment : Storage_Count)
659 pragma Unreferenced (Alignment);
660 -- Ignored, we always force 'Default_Alignment
662 type Local_Storage_Array is new Storage_Array
663 (1 .. Size_In_Storage_Elements + Minimum_Allocation);
665 type Ptr is access Local_Storage_Array;
666 -- On some systems, we might want to physically protect pages against
667 -- writing when they have been freed (of course, this is expensive in
668 -- terms of wasted memory). To do that, all we should have to do it to
669 -- set the size of this array to the page size. See mprotect().
671 P : Ptr;
673 Current : Byte_Count;
674 Trace : Traceback_Htable_Elem_Ptr;
676 begin
677 <<Allocate_Label>>
678 Lock_Task.all;
680 -- If necessary, start physically releasing memory. The reason this is
681 -- done here, although Pool.Logically_Deallocated has not changed above,
682 -- is so that we do this only after a series of deallocations (e.g loop
683 -- that deallocates a big array). If we were doing that in Deallocate,
684 -- we might be physically freeing memory several times during the loop,
685 -- which is expensive.
687 if Pool.Logically_Deallocated >
688 Byte_Count (Pool.Maximum_Logically_Freed_Memory)
689 then
690 Free_Physically (Pool);
691 end if;
693 -- Use standard (i.e. through malloc) allocations. This automatically
694 -- raises Storage_Error if needed. We also try once more to physically
695 -- release memory, so that even marked blocks, in the advanced scanning,
696 -- are freed.
698 begin
699 P := new Local_Storage_Array;
701 exception
702 when Storage_Error =>
703 Free_Physically (Pool);
704 P := new Local_Storage_Array;
705 end;
707 Storage_Address :=
708 To_Address
709 (Default_Alignment *
710 ((To_Integer (P.all'Address) + Default_Alignment - 1)
711 / Default_Alignment)
712 + Integer_Address (Header_Offset));
713 -- Computation is done in Integer_Address, not Storage_Offset, because
714 -- the range of Storage_Offset may not be large enough.
716 pragma Assert ((Storage_Address - System.Null_Address)
717 mod Default_Alignment = 0);
718 pragma Assert (Storage_Address + Size_In_Storage_Elements
719 <= P.all'Address + P'Length);
721 Trace := Find_Or_Create_Traceback
722 (Pool, Alloc, Size_In_Storage_Elements,
723 Allocate_Label'Address, Code_Address_For_Allocate_End);
725 pragma Warnings (Off);
726 -- Turn warning on alignment for convert call off. We know that in fact
727 -- this conversion is safe since P itself is always aligned on
728 -- Default_Alignment.
730 Header_Of (Storage_Address).all :=
731 (Allocation_Address => P.all'Address,
732 Alloc_Traceback => Trace,
733 Dealloc_Traceback => To_Traceback (null),
734 Next => Pool.First_Used_Block,
735 Block_Size => Size_In_Storage_Elements);
737 pragma Warnings (On);
739 -- Link this block in the list of used blocks. This will be used to list
740 -- memory leaks in Print_Info, and for the advanced schemes of
741 -- Physical_Free, where we want to traverse all allocated blocks and
742 -- search for possible references.
744 -- We insert in front, since most likely we'll be freeing the most
745 -- recently allocated blocks first (the older one might stay allocated
746 -- for the whole life of the application).
748 if Pool.First_Used_Block /= System.Null_Address then
749 Header_Of (Pool.First_Used_Block).Dealloc_Traceback :=
750 To_Address (Storage_Address);
751 end if;
753 Pool.First_Used_Block := Storage_Address;
755 -- Mark the new address as valid
757 Set_Valid (Storage_Address, True);
759 if Pool.Low_Level_Traces then
760 Put (Output_File (Pool),
761 "info: Allocated"
762 & Storage_Count'Image (Size_In_Storage_Elements)
763 & " bytes at 0x" & Address_Image (Storage_Address)
764 & " (physically:"
765 & Storage_Count'Image (Local_Storage_Array'Length)
766 & " bytes at 0x" & Address_Image (P.all'Address)
767 & "), at ");
768 Put_Line (Output_File (Pool), Pool.Stack_Trace_Depth, null,
769 Allocate_Label'Address,
770 Code_Address_For_Deallocate_End);
771 end if;
773 -- Update internal data
775 Pool.Allocated :=
776 Pool.Allocated + Byte_Count (Size_In_Storage_Elements);
778 Current := Pool.Allocated -
779 Pool.Logically_Deallocated -
780 Pool.Physically_Deallocated;
782 if Current > Pool.High_Water then
783 Pool.High_Water := Current;
784 end if;
786 Unlock_Task.all;
788 exception
789 when others =>
790 Unlock_Task.all;
791 raise;
792 end Allocate;
794 ------------------
795 -- Allocate_End --
796 ------------------
798 -- DO NOT MOVE, this must be right after Allocate. This is similar to what
799 -- is done in a-except, so that we can hide the traceback frames internal
800 -- to this package
802 procedure Allocate_End is
803 begin
804 <<Allocate_End_Label>>
805 Code_Address_For_Allocate_End := Allocate_End_Label'Address;
806 end Allocate_End;
808 -------------------
809 -- Set_Dead_Beef --
810 -------------------
812 procedure Set_Dead_Beef
813 (Storage_Address : System.Address;
814 Size_In_Storage_Elements : Storage_Count)
816 Dead_Bytes : constant := 4;
818 type Data is mod 2 ** (Dead_Bytes * 8);
819 for Data'Size use Dead_Bytes * 8;
821 Dead : constant Data := 16#DEAD_BEEF#;
823 type Dead_Memory is array
824 (1 .. Size_In_Storage_Elements / Dead_Bytes) of Data;
825 type Mem_Ptr is access Dead_Memory;
827 type Byte is mod 2 ** 8;
828 for Byte'Size use 8;
830 type Dead_Memory_Bytes is array (0 .. 2) of Byte;
831 type Dead_Memory_Bytes_Ptr is access Dead_Memory_Bytes;
833 function From_Ptr is new Ada.Unchecked_Conversion
834 (System.Address, Mem_Ptr);
836 function From_Ptr is new Ada.Unchecked_Conversion
837 (System.Address, Dead_Memory_Bytes_Ptr);
839 M : constant Mem_Ptr := From_Ptr (Storage_Address);
840 M2 : Dead_Memory_Bytes_Ptr;
841 Modulo : constant Storage_Count :=
842 Size_In_Storage_Elements mod Dead_Bytes;
843 begin
844 M.all := (others => Dead);
846 -- Any bytes left (up to three of them)
848 if Modulo /= 0 then
849 M2 := From_Ptr (Storage_Address + M'Length * Dead_Bytes);
851 M2 (0) := 16#DE#;
852 if Modulo >= 2 then
853 M2 (1) := 16#AD#;
855 if Modulo >= 3 then
856 M2 (2) := 16#BE#;
857 end if;
858 end if;
859 end if;
860 end Set_Dead_Beef;
862 ---------------------
863 -- Free_Physically --
864 ---------------------
866 procedure Free_Physically (Pool : in out Debug_Pool) is
867 type Byte is mod 256;
868 type Byte_Access is access Byte;
870 function To_Byte is new Ada.Unchecked_Conversion
871 (System.Address, Byte_Access);
873 type Address_Access is access System.Address;
875 function To_Address_Access is new Ada.Unchecked_Conversion
876 (System.Address, Address_Access);
878 In_Use_Mark : constant Byte := 16#D#;
879 Free_Mark : constant Byte := 16#F#;
881 Total_Freed : Storage_Count := 0;
883 procedure Reset_Marks;
884 -- Unmark all the logically freed blocks, so that they are considered
885 -- for physical deallocation
887 procedure Mark
888 (H : Allocation_Header_Access; A : System.Address; In_Use : Boolean);
889 -- Mark the user data block starting at A. For a block of size zero,
890 -- nothing is done. For a block with a different size, the first byte
891 -- is set to either "D" (in use) or "F" (free).
893 function Marked (A : System.Address) return Boolean;
894 -- Return true if the user data block starting at A might be in use
895 -- somewhere else
897 procedure Mark_Blocks;
898 -- Traverse all allocated blocks, and search for possible references
899 -- to logically freed blocks. Mark them appropriately
901 procedure Free_Blocks (Ignore_Marks : Boolean);
902 -- Physically release blocks. Only the blocks that haven't been marked
903 -- will be released, unless Ignore_Marks is true.
905 -----------------
906 -- Free_Blocks --
907 -----------------
909 procedure Free_Blocks (Ignore_Marks : Boolean) is
910 Header : Allocation_Header_Access;
911 Tmp : System.Address := Pool.First_Free_Block;
912 Next : System.Address;
913 Previous : System.Address := System.Null_Address;
915 begin
916 while Tmp /= System.Null_Address
917 and then Total_Freed < Pool.Minimum_To_Free
918 loop
919 Header := Header_Of (Tmp);
921 -- If we know, or at least assume, the block is no longer
922 -- referenced anywhere, we can free it physically.
924 if Ignore_Marks or else not Marked (Tmp) then
926 declare
927 pragma Suppress (All_Checks);
928 -- Suppress the checks on this section. If they are overflow
929 -- errors, it isn't critical, and we'd rather avoid a
930 -- Constraint_Error in that case.
931 begin
932 -- Note that block_size < zero for freed blocks
934 Pool.Physically_Deallocated :=
935 Pool.Physically_Deallocated -
936 Byte_Count (Header.Block_Size);
938 Pool.Logically_Deallocated :=
939 Pool.Logically_Deallocated +
940 Byte_Count (Header.Block_Size);
942 Total_Freed := Total_Freed - Header.Block_Size;
943 end;
945 Next := Header.Next;
947 if Pool.Low_Level_Traces then
948 Put_Line
949 (Output_File (Pool),
950 "info: Freeing physical memory "
951 & Storage_Count'Image
952 ((abs Header.Block_Size) + Minimum_Allocation)
953 & " bytes at 0x"
954 & Address_Image (Header.Allocation_Address));
955 end if;
957 System.Memory.Free (Header.Allocation_Address);
958 Set_Valid (Tmp, False);
960 -- Remove this block from the list
962 if Previous = System.Null_Address then
963 Pool.First_Free_Block := Next;
964 else
965 Header_Of (Previous).Next := Next;
966 end if;
968 Tmp := Next;
970 else
971 Previous := Tmp;
972 Tmp := Header.Next;
973 end if;
974 end loop;
975 end Free_Blocks;
977 ----------
978 -- Mark --
979 ----------
981 procedure Mark
982 (H : Allocation_Header_Access;
983 A : System.Address;
984 In_Use : Boolean)
986 begin
987 if H.Block_Size /= 0 then
988 To_Byte (A).all := (if In_Use then In_Use_Mark else Free_Mark);
989 end if;
990 end Mark;
992 -----------------
993 -- Mark_Blocks --
994 -----------------
996 procedure Mark_Blocks is
997 Tmp : System.Address := Pool.First_Used_Block;
998 Previous : System.Address;
999 Last : System.Address;
1000 Pointed : System.Address;
1001 Header : Allocation_Header_Access;
1003 begin
1004 -- For each allocated block, check its contents. Things that look
1005 -- like a possible address are used to mark the blocks so that we try
1006 -- and keep them, for better detection in case of invalid access.
1007 -- This mechanism is far from being fool-proof: it doesn't check the
1008 -- stacks of the threads, doesn't check possible memory allocated not
1009 -- under control of this debug pool. But it should allow us to catch
1010 -- more cases.
1012 while Tmp /= System.Null_Address loop
1013 Previous := Tmp;
1014 Last := Tmp + Header_Of (Tmp).Block_Size;
1015 while Previous < Last loop
1016 -- ??? Should we move byte-per-byte, or consider that addresses
1017 -- are always aligned on 4-bytes boundaries ? Let's use the
1018 -- fastest for now.
1020 Pointed := To_Address_Access (Previous).all;
1021 if Is_Valid (Pointed) then
1022 Header := Header_Of (Pointed);
1024 -- Do not even attempt to mark blocks in use. That would
1025 -- screw up the whole application, of course.
1027 if Header.Block_Size < 0 then
1028 Mark (Header, Pointed, In_Use => True);
1029 end if;
1030 end if;
1032 Previous := Previous + System.Address'Size;
1033 end loop;
1035 Tmp := Header_Of (Tmp).Next;
1036 end loop;
1037 end Mark_Blocks;
1039 ------------
1040 -- Marked --
1041 ------------
1043 function Marked (A : System.Address) return Boolean is
1044 begin
1045 return To_Byte (A).all = In_Use_Mark;
1046 end Marked;
1048 -----------------
1049 -- Reset_Marks --
1050 -----------------
1052 procedure Reset_Marks is
1053 Current : System.Address := Pool.First_Free_Block;
1054 Header : Allocation_Header_Access;
1055 begin
1056 while Current /= System.Null_Address loop
1057 Header := Header_Of (Current);
1058 Mark (Header, Current, False);
1059 Current := Header.Next;
1060 end loop;
1061 end Reset_Marks;
1063 -- Start of processing for Free_Physically
1065 begin
1066 Lock_Task.all;
1068 if Pool.Advanced_Scanning then
1070 -- Reset the mark for each freed block
1072 Reset_Marks;
1074 Mark_Blocks;
1075 end if;
1077 Free_Blocks (Ignore_Marks => not Pool.Advanced_Scanning);
1079 -- The contract is that we need to free at least Minimum_To_Free bytes,
1080 -- even if this means freeing marked blocks in the advanced scheme
1082 if Total_Freed < Pool.Minimum_To_Free
1083 and then Pool.Advanced_Scanning
1084 then
1085 Pool.Marked_Blocks_Deallocated := True;
1086 Free_Blocks (Ignore_Marks => True);
1087 end if;
1089 Unlock_Task.all;
1091 exception
1092 when others =>
1093 Unlock_Task.all;
1094 raise;
1095 end Free_Physically;
1097 ----------------
1098 -- Deallocate --
1099 ----------------
1101 procedure Deallocate
1102 (Pool : in out Debug_Pool;
1103 Storage_Address : Address;
1104 Size_In_Storage_Elements : Storage_Count;
1105 Alignment : Storage_Count)
1107 pragma Unreferenced (Alignment);
1109 Header : constant Allocation_Header_Access :=
1110 Header_Of (Storage_Address);
1111 Valid : Boolean;
1112 Previous : System.Address;
1114 begin
1115 <<Deallocate_Label>>
1116 Lock_Task.all;
1117 Valid := Is_Valid (Storage_Address);
1119 if not Valid then
1120 Unlock_Task.all;
1121 if Pool.Raise_Exceptions then
1122 raise Freeing_Not_Allocated_Storage;
1123 else
1124 Put (Output_File (Pool),
1125 "error: Freeing not allocated storage, at ");
1126 Put_Line (Output_File (Pool), Pool.Stack_Trace_Depth, null,
1127 Deallocate_Label'Address,
1128 Code_Address_For_Deallocate_End);
1129 end if;
1131 elsif Header.Block_Size < 0 then
1132 Unlock_Task.all;
1133 if Pool.Raise_Exceptions then
1134 raise Freeing_Deallocated_Storage;
1135 else
1136 Put (Output_File (Pool),
1137 "error: Freeing already deallocated storage, at ");
1138 Put_Line (Output_File (Pool), Pool.Stack_Trace_Depth, null,
1139 Deallocate_Label'Address,
1140 Code_Address_For_Deallocate_End);
1141 Put (Output_File (Pool), " Memory already deallocated at ");
1142 Put_Line
1143 (Output_File (Pool), 0,
1144 To_Traceback (Header.Dealloc_Traceback).Traceback);
1145 Put (Output_File (Pool), " Memory was allocated at ");
1146 Put_Line (Output_File (Pool), 0, Header.Alloc_Traceback.Traceback);
1147 end if;
1149 else
1150 -- Some sort of codegen problem or heap corruption caused the
1151 -- Size_In_Storage_Elements to be wrongly computed.
1152 -- The code below is all based on the assumption that Header.all
1153 -- is not corrupted, such that the error is non-fatal.
1155 if Header.Block_Size /= Size_In_Storage_Elements then
1156 Put_Line (Output_File (Pool),
1157 "error: Deallocate size "
1158 & Storage_Count'Image (Size_In_Storage_Elements)
1159 & " does not match allocate size "
1160 & Storage_Count'Image (Header.Block_Size));
1161 end if;
1163 if Pool.Low_Level_Traces then
1164 Put (Output_File (Pool),
1165 "info: Deallocated"
1166 & Storage_Count'Image (Size_In_Storage_Elements)
1167 & " bytes at 0x" & Address_Image (Storage_Address)
1168 & " (physically"
1169 & Storage_Count'Image (Header.Block_Size + Minimum_Allocation)
1170 & " bytes at 0x" & Address_Image (Header.Allocation_Address)
1171 & "), at ");
1172 Put_Line (Output_File (Pool), Pool.Stack_Trace_Depth, null,
1173 Deallocate_Label'Address,
1174 Code_Address_For_Deallocate_End);
1175 Put (Output_File (Pool), " Memory was allocated at ");
1176 Put_Line (Output_File (Pool), 0, Header.Alloc_Traceback.Traceback);
1177 end if;
1179 -- Remove this block from the list of used blocks
1181 Previous :=
1182 To_Address (Header.Dealloc_Traceback);
1184 if Previous = System.Null_Address then
1185 Pool.First_Used_Block := Header_Of (Pool.First_Used_Block).Next;
1187 if Pool.First_Used_Block /= System.Null_Address then
1188 Header_Of (Pool.First_Used_Block).Dealloc_Traceback :=
1189 To_Traceback (null);
1190 end if;
1192 else
1193 Header_Of (Previous).Next := Header.Next;
1195 if Header.Next /= System.Null_Address then
1196 Header_Of
1197 (Header.Next).Dealloc_Traceback := To_Address (Previous);
1198 end if;
1199 end if;
1201 -- Update the header
1203 Header.all :=
1204 (Allocation_Address => Header.Allocation_Address,
1205 Alloc_Traceback => Header.Alloc_Traceback,
1206 Dealloc_Traceback => To_Traceback
1207 (Find_Or_Create_Traceback
1208 (Pool, Dealloc,
1209 Size_In_Storage_Elements,
1210 Deallocate_Label'Address,
1211 Code_Address_For_Deallocate_End)),
1212 Next => System.Null_Address,
1213 Block_Size => -Header.Block_Size);
1215 if Pool.Reset_Content_On_Free then
1216 Set_Dead_Beef (Storage_Address, -Header.Block_Size);
1217 end if;
1219 Pool.Logically_Deallocated :=
1220 Pool.Logically_Deallocated + Byte_Count (-Header.Block_Size);
1222 -- Link this free block with the others (at the end of the list, so
1223 -- that we can start releasing the older blocks first later on).
1225 if Pool.First_Free_Block = System.Null_Address then
1226 Pool.First_Free_Block := Storage_Address;
1227 Pool.Last_Free_Block := Storage_Address;
1229 else
1230 Header_Of (Pool.Last_Free_Block).Next := Storage_Address;
1231 Pool.Last_Free_Block := Storage_Address;
1232 end if;
1234 -- Do not physically release the memory here, but in Alloc.
1235 -- See comment there for details.
1237 Unlock_Task.all;
1238 end if;
1240 exception
1241 when others =>
1242 Unlock_Task.all;
1243 raise;
1244 end Deallocate;
1246 --------------------
1247 -- Deallocate_End --
1248 --------------------
1250 -- DO NOT MOVE, this must be right after Deallocate
1252 -- See Allocate_End
1254 -- This is making assumptions about code order that may be invalid ???
1256 procedure Deallocate_End is
1257 begin
1258 <<Deallocate_End_Label>>
1259 Code_Address_For_Deallocate_End := Deallocate_End_Label'Address;
1260 end Deallocate_End;
1262 -----------------
1263 -- Dereference --
1264 -----------------
1266 procedure Dereference
1267 (Pool : in out Debug_Pool;
1268 Storage_Address : Address;
1269 Size_In_Storage_Elements : Storage_Count;
1270 Alignment : Storage_Count)
1272 pragma Unreferenced (Alignment, Size_In_Storage_Elements);
1274 Valid : constant Boolean := Is_Valid (Storage_Address);
1275 Header : Allocation_Header_Access;
1277 begin
1278 -- Locking policy: we do not do any locking in this procedure. The
1279 -- tables are only read, not written to, and although a problem might
1280 -- appear if someone else is modifying the tables at the same time, this
1281 -- race condition is not intended to be detected by this storage_pool (a
1282 -- now invalid pointer would appear as valid). Instead, we prefer
1283 -- optimum performance for dereferences.
1285 <<Dereference_Label>>
1287 if not Valid then
1288 if Pool.Raise_Exceptions then
1289 raise Accessing_Not_Allocated_Storage;
1290 else
1291 Put (Output_File (Pool),
1292 "error: Accessing not allocated storage, at ");
1293 Put_Line (Output_File (Pool), Pool.Stack_Trace_Depth, null,
1294 Dereference_Label'Address,
1295 Code_Address_For_Dereference_End);
1296 end if;
1298 else
1299 Header := Header_Of (Storage_Address);
1301 if Header.Block_Size < 0 then
1302 if Pool.Raise_Exceptions then
1303 raise Accessing_Deallocated_Storage;
1304 else
1305 Put (Output_File (Pool),
1306 "error: Accessing deallocated storage, at ");
1307 Put_Line
1308 (Output_File (Pool), Pool.Stack_Trace_Depth, null,
1309 Dereference_Label'Address,
1310 Code_Address_For_Dereference_End);
1311 Put (Output_File (Pool), " First deallocation at ");
1312 Put_Line
1313 (Output_File (Pool),
1314 0, To_Traceback (Header.Dealloc_Traceback).Traceback);
1315 Put (Output_File (Pool), " Initial allocation at ");
1316 Put_Line
1317 (Output_File (Pool),
1318 0, Header.Alloc_Traceback.Traceback);
1319 end if;
1320 end if;
1321 end if;
1322 end Dereference;
1324 ---------------------
1325 -- Dereference_End --
1326 ---------------------
1328 -- DO NOT MOVE: this must be right after Dereference
1330 -- See Allocate_End
1332 -- This is making assumptions about code order that may be invalid ???
1334 procedure Dereference_End is
1335 begin
1336 <<Dereference_End_Label>>
1337 Code_Address_For_Dereference_End := Dereference_End_Label'Address;
1338 end Dereference_End;
1340 ----------------
1341 -- Print_Info --
1342 ----------------
1344 procedure Print_Info
1345 (Pool : Debug_Pool;
1346 Cumulate : Boolean := False;
1347 Display_Slots : Boolean := False;
1348 Display_Leaks : Boolean := False)
1351 package Backtrace_Htable_Cumulate is new GNAT.HTable.Static_HTable
1352 (Header_Num => Header,
1353 Element => Traceback_Htable_Elem,
1354 Elmt_Ptr => Traceback_Htable_Elem_Ptr,
1355 Null_Ptr => null,
1356 Set_Next => Set_Next,
1357 Next => Next,
1358 Key => Tracebacks_Array_Access,
1359 Get_Key => Get_Key,
1360 Hash => Hash,
1361 Equal => Equal);
1362 -- This needs a comment ??? probably some of the ones below do too???
1364 Data : Traceback_Htable_Elem_Ptr;
1365 Elem : Traceback_Htable_Elem_Ptr;
1366 Current : System.Address;
1367 Header : Allocation_Header_Access;
1368 K : Traceback_Kind;
1370 begin
1371 Put_Line
1372 ("Total allocated bytes : " &
1373 Byte_Count'Image (Pool.Allocated));
1375 Put_Line
1376 ("Total logically deallocated bytes : " &
1377 Byte_Count'Image (Pool.Logically_Deallocated));
1379 Put_Line
1380 ("Total physically deallocated bytes : " &
1381 Byte_Count'Image (Pool.Physically_Deallocated));
1383 if Pool.Marked_Blocks_Deallocated then
1384 Put_Line ("Marked blocks were physically deallocated. This is");
1385 Put_Line ("potentially dangerous, and you might want to run");
1386 Put_Line ("again with a lower value of Minimum_To_Free");
1387 end if;
1389 Put_Line
1390 ("Current Water Mark: " &
1391 Byte_Count'Image
1392 (Pool.Allocated - Pool.Logically_Deallocated
1393 - Pool.Physically_Deallocated));
1395 Put_Line
1396 ("High Water Mark: " &
1397 Byte_Count'Image (Pool.High_Water));
1399 Put_Line ("");
1401 if Display_Slots then
1402 Data := Backtrace_Htable.Get_First;
1403 while Data /= null loop
1404 if Data.Kind in Alloc .. Dealloc then
1405 Elem :=
1406 new Traceback_Htable_Elem'
1407 (Traceback => new Tracebacks_Array'(Data.Traceback.all),
1408 Count => Data.Count,
1409 Kind => Data.Kind,
1410 Total => Data.Total,
1411 Next => null);
1412 Backtrace_Htable_Cumulate.Set (Elem);
1414 if Cumulate then
1415 K := (if Data.Kind = Alloc then Indirect_Alloc
1416 else Indirect_Dealloc);
1418 -- Propagate the direct call to all its parents
1420 for T in Data.Traceback'First + 1 .. Data.Traceback'Last loop
1421 Elem := Backtrace_Htable_Cumulate.Get
1422 (Data.Traceback
1423 (T .. Data.Traceback'Last)'Unrestricted_Access);
1425 -- If not, insert it
1427 if Elem = null then
1428 Elem := new Traceback_Htable_Elem'
1429 (Traceback => new Tracebacks_Array'
1430 (Data.Traceback (T .. Data.Traceback'Last)),
1431 Count => Data.Count,
1432 Kind => K,
1433 Total => Data.Total,
1434 Next => null);
1435 Backtrace_Htable_Cumulate.Set (Elem);
1437 -- Properly take into account that the subprograms
1438 -- indirectly called might be doing either allocations
1439 -- or deallocations. This needs to be reflected in the
1440 -- counts.
1442 else
1443 Elem.Count := Elem.Count + Data.Count;
1445 if K = Elem.Kind then
1446 Elem.Total := Elem.Total + Data.Total;
1448 elsif Elem.Total > Data.Total then
1449 Elem.Total := Elem.Total - Data.Total;
1451 else
1452 Elem.Kind := K;
1453 Elem.Total := Data.Total - Elem.Total;
1454 end if;
1455 end if;
1456 end loop;
1457 end if;
1459 Data := Backtrace_Htable.Get_Next;
1460 end if;
1461 end loop;
1463 Put_Line ("List of allocations/deallocations: ");
1465 Data := Backtrace_Htable_Cumulate.Get_First;
1466 while Data /= null loop
1467 case Data.Kind is
1468 when Alloc => Put ("alloc (count:");
1469 when Indirect_Alloc => Put ("indirect alloc (count:");
1470 when Dealloc => Put ("free (count:");
1471 when Indirect_Dealloc => Put ("indirect free (count:");
1472 end case;
1474 Put (Natural'Image (Data.Count) & ", total:" &
1475 Byte_Count'Image (Data.Total) & ") ");
1477 for T in Data.Traceback'Range loop
1478 Put ("0x" & Address_Image (PC_For (Data.Traceback (T))) & ' ');
1479 end loop;
1481 Put_Line ("");
1483 Data := Backtrace_Htable_Cumulate.Get_Next;
1484 end loop;
1486 Backtrace_Htable_Cumulate.Reset;
1487 end if;
1489 if Display_Leaks then
1490 Put_Line ("");
1491 Put_Line ("List of not deallocated blocks:");
1493 -- Do not try to group the blocks with the same stack traces
1494 -- together. This is done by the gnatmem output.
1496 Current := Pool.First_Used_Block;
1497 while Current /= System.Null_Address loop
1498 Header := Header_Of (Current);
1500 Put ("Size: " & Storage_Count'Image (Header.Block_Size) & " at: ");
1502 for T in Header.Alloc_Traceback.Traceback'Range loop
1503 Put ("0x" & Address_Image
1504 (PC_For (Header.Alloc_Traceback.Traceback (T))) & ' ');
1505 end loop;
1507 Put_Line ("");
1508 Current := Header.Next;
1509 end loop;
1510 end if;
1511 end Print_Info;
1513 ------------------
1514 -- Storage_Size --
1515 ------------------
1517 function Storage_Size (Pool : Debug_Pool) return Storage_Count is
1518 pragma Unreferenced (Pool);
1519 begin
1520 return Storage_Count'Last;
1521 end Storage_Size;
1523 ---------------
1524 -- Configure --
1525 ---------------
1527 procedure Configure
1528 (Pool : in out Debug_Pool;
1529 Stack_Trace_Depth : Natural := Default_Stack_Trace_Depth;
1530 Maximum_Logically_Freed_Memory : SSC := Default_Max_Freed;
1531 Minimum_To_Free : SSC := Default_Min_Freed;
1532 Reset_Content_On_Free : Boolean := Default_Reset_Content;
1533 Raise_Exceptions : Boolean := Default_Raise_Exceptions;
1534 Advanced_Scanning : Boolean := Default_Advanced_Scanning;
1535 Errors_To_Stdout : Boolean := Default_Errors_To_Stdout;
1536 Low_Level_Traces : Boolean := Default_Low_Level_Traces)
1538 begin
1539 Pool.Stack_Trace_Depth := Stack_Trace_Depth;
1540 Pool.Maximum_Logically_Freed_Memory := Maximum_Logically_Freed_Memory;
1541 Pool.Reset_Content_On_Free := Reset_Content_On_Free;
1542 Pool.Raise_Exceptions := Raise_Exceptions;
1543 Pool.Minimum_To_Free := Minimum_To_Free;
1544 Pool.Advanced_Scanning := Advanced_Scanning;
1545 Pool.Errors_To_Stdout := Errors_To_Stdout;
1546 Pool.Low_Level_Traces := Low_Level_Traces;
1547 end Configure;
1549 ----------------
1550 -- Print_Pool --
1551 ----------------
1553 procedure Print_Pool (A : System.Address) is
1554 Storage : constant Address := A;
1555 Valid : constant Boolean := Is_Valid (Storage);
1556 Header : Allocation_Header_Access;
1558 begin
1559 -- We might get Null_Address if the call from gdb was done
1560 -- incorrectly. For instance, doing a "print_pool(my_var)" passes 0x0,
1561 -- instead of passing the value of my_var
1563 if A = System.Null_Address then
1564 Put_Line
1565 (Standard_Output, "Memory not under control of the storage pool");
1566 return;
1567 end if;
1569 if not Valid then
1570 Put_Line
1571 (Standard_Output, "Memory not under control of the storage pool");
1573 else
1574 Header := Header_Of (Storage);
1575 Put_Line (Standard_Output, "0x" & Address_Image (A)
1576 & " allocated at:");
1577 Put_Line (Standard_Output, 0, Header.Alloc_Traceback.Traceback);
1579 if To_Traceback (Header.Dealloc_Traceback) /= null then
1580 Put_Line (Standard_Output, "0x" & Address_Image (A)
1581 & " logically freed memory, deallocated at:");
1582 Put_Line
1583 (Standard_Output, 0,
1584 To_Traceback (Header.Dealloc_Traceback).Traceback);
1585 end if;
1586 end if;
1587 end Print_Pool;
1589 -----------------------
1590 -- Print_Info_Stdout --
1591 -----------------------
1593 procedure Print_Info_Stdout
1594 (Pool : Debug_Pool;
1595 Cumulate : Boolean := False;
1596 Display_Slots : Boolean := False;
1597 Display_Leaks : Boolean := False)
1599 procedure Stdout_Put (S : String);
1600 procedure Stdout_Put_Line (S : String);
1601 -- Wrappers for Put and Put_Line that ensure we always write to stdout
1602 -- instead of the current output file defined in GNAT.IO.
1604 procedure Internal is new Print_Info
1605 (Put_Line => Stdout_Put_Line,
1606 Put => Stdout_Put);
1608 ----------------
1609 -- Stdout_Put --
1610 ----------------
1612 procedure Stdout_Put (S : String) is
1613 begin
1614 Put_Line (Standard_Output, S);
1615 end Stdout_Put;
1617 ---------------------
1618 -- Stdout_Put_Line --
1619 ---------------------
1621 procedure Stdout_Put_Line (S : String) is
1622 begin
1623 Put_Line (Standard_Output, S);
1624 end Stdout_Put_Line;
1626 -- Start of processing for Print_Info_Stdout
1628 begin
1629 Internal (Pool, Cumulate, Display_Slots, Display_Leaks);
1630 end Print_Info_Stdout;
1632 ------------------
1633 -- Dump_Gnatmem --
1634 ------------------
1636 procedure Dump_Gnatmem (Pool : Debug_Pool; File_Name : String) is
1637 type File_Ptr is new System.Address;
1639 function fopen (Path : String; Mode : String) return File_Ptr;
1640 pragma Import (C, fopen);
1642 procedure fwrite
1643 (Ptr : System.Address;
1644 Size : size_t;
1645 Nmemb : size_t;
1646 Stream : File_Ptr);
1648 procedure fwrite
1649 (Str : String;
1650 Size : size_t;
1651 Nmemb : size_t;
1652 Stream : File_Ptr);
1653 pragma Import (C, fwrite);
1655 procedure fputc (C : Integer; Stream : File_Ptr);
1656 pragma Import (C, fputc);
1658 procedure fclose (Stream : File_Ptr);
1659 pragma Import (C, fclose);
1661 Address_Size : constant size_t :=
1662 System.Address'Max_Size_In_Storage_Elements;
1663 -- Size in bytes of a pointer
1665 File : File_Ptr;
1666 Current : System.Address;
1667 Header : Allocation_Header_Access;
1668 Actual_Size : size_t;
1669 Num_Calls : Integer;
1670 Tracebk : Tracebacks_Array_Access;
1671 Dummy_Time : Duration := 1.0;
1673 begin
1674 File := fopen (File_Name & ASCII.NUL, "wb" & ASCII.NUL);
1675 fwrite ("GMEM DUMP" & ASCII.LF, 10, 1, File);
1676 fwrite (Dummy_Time'Address, Duration'Max_Size_In_Storage_Elements, 1,
1677 File);
1679 -- List of not deallocated blocks (see Print_Info)
1681 Current := Pool.First_Used_Block;
1682 while Current /= System.Null_Address loop
1683 Header := Header_Of (Current);
1685 Actual_Size := size_t (Header.Block_Size);
1686 Tracebk := Header.Alloc_Traceback.Traceback;
1687 Num_Calls := Tracebk'Length;
1689 -- (Code taken from memtrack.adb in GNAT's sources)
1691 -- Logs allocation call using the format:
1693 -- 'A' <mem addr> <size chunk> <len backtrace> <addr1> ... <addrn>
1695 fputc (Character'Pos ('A'), File);
1696 fwrite (Current'Address, Address_Size, 1, File);
1697 fwrite (Actual_Size'Address, size_t'Max_Size_In_Storage_Elements, 1,
1698 File);
1699 fwrite (Dummy_Time'Address, Duration'Max_Size_In_Storage_Elements, 1,
1700 File);
1701 fwrite (Num_Calls'Address, Integer'Max_Size_In_Storage_Elements, 1,
1702 File);
1704 for J in Tracebk'First .. Tracebk'First + Num_Calls - 1 loop
1705 declare
1706 Ptr : System.Address := PC_For (Tracebk (J));
1707 begin
1708 fwrite (Ptr'Address, Address_Size, 1, File);
1709 end;
1710 end loop;
1712 Current := Header.Next;
1713 end loop;
1715 fclose (File);
1716 end Dump_Gnatmem;
1718 -- Package initialization
1720 begin
1721 Allocate_End;
1722 Deallocate_End;
1723 Dereference_End;
1724 end GNAT.Debug_Pools;