The dynamic stack usage engine has been rewritten to slightly simplify it. It now provides accurate results on machine where the stack base is known.
Tested on x86_64-pc-linux-gnu, committed on trunk 2011-08-04 Tristan Gingold <ging...@adacore.com> * s-tassta.adb (Task_Wrapper): Rewrite the dynamic stack usage part. * s-stausa.adb, s-stausa.ads: Major rewrite. Now provides accurate results if possible. * s-stusta.adb (Print): Adjust after changes in s-stausa. * gnat_ugn.texi: Update dynamic stack usage section.
Index: s-tassta.adb =================================================================== --- s-tassta.adb (revision 177283) +++ s-tassta.adb (working copy) @@ -1027,32 +1027,11 @@ Secondary_Stack : aliased SSE.Storage_Array (1 .. Secondary_Stack_Size); - pragma Warnings (Off); - -- Why are warnings being turned off here??? - Secondary_Stack_Address : System.Address := Secondary_Stack'Address; -- Address of secondary stack. In the fixed secondary stack case, this -- value is not modified, causing a warning, hence the bracketing with -- Warnings (Off/On). But why is so much *more* bracketed??? - Small_Overflow_Guard : constant := 12 * 1024; - -- Note: this used to be 4K, but was changed to 12K, since smaller - -- values resulted in segmentation faults from dynamic stack analysis. - - Big_Overflow_Guard : constant := 16 * 1024; - Small_Stack_Limit : constant := 64 * 1024; - -- ??? These three values are experimental, and seems to work on most - -- platforms. They still need to be analyzed further. They also need - -- documentation, what are they??? - - Size : Natural := - Natural (Self_ID.Common.Compiler_Data.Pri_Stack_Info.Size); - - Overflow_Guard : Natural; - -- Size of the overflow guard, used by dynamic stack usage analysis - - pragma Warnings (On); - SEH_Table : aliased SSE.Storage_Array (1 .. 8); -- Structured Exception Registration table (2 words) @@ -1116,7 +1095,6 @@ Self_ID.Common.Compiler_Data.Sec_Stack_Addr := Secondary_Stack'Address; SST.SS_Init (Secondary_Stack_Address, Integer (Secondary_Stack'Last)); - Size := Size - Natural (Secondary_Stack_Size); end if; if Use_Alternate_Stack then @@ -1136,24 +1114,64 @@ -- Initialize dynamic stack usage if System.Stack_Usage.Is_Enabled then - Overflow_Guard := - (if Size < Small_Stack_Limit - then Small_Overflow_Guard - else Big_Overflow_Guard); + declare + Guard_Page_Size : constant := 12 * 1024; + -- Part of the stack used as a guard page. This is an OS dependent + -- value, so we need to use the maximum. This value is only used + -- when the stack address is known, that is currently Windows. - STPO.Lock_RTS; - Initialize_Analyzer - (Self_ID.Common.Analyzer, - Self_ID.Common.Task_Image - (1 .. Self_ID.Common.Task_Image_Len), - Natural - (Self_ID.Common.Compiler_Data.Pri_Stack_Info.Size), - Size - Overflow_Guard, - SSE.To_Integer (Bottom_Of_Stack'Address), - SSE.To_Integer - (Self_ID.Common.Compiler_Data.Pri_Stack_Info.Limit)); - STPO.Unlock_RTS; - Fill_Stack (Self_ID.Common.Analyzer); + Small_Overflow_Guard : constant := 12 * 1024; + -- Note: this used to be 4K, but was changed to 12K, since + -- smaller values resulted in segmentation faults from dynamic + -- stack analysis. + + Big_Overflow_Guard : constant := 16 * 1024; + Small_Stack_Limit : constant := 64 * 1024; + -- ??? These three values are experimental, and seems to work on + -- most platforms. They still need to be analyzed further. They + -- also need documentation, what are they??? + + Pattern_Size : Natural := + Natural (Self_ID.Common.Compiler_Data.Pri_Stack_Info.Size); + -- Size of the pattern + + Stack_Base : Address; + -- Address of the base of the stack + begin + Stack_Base := Self_ID.Common.Compiler_Data.Pri_Stack_Info.Base; + if Stack_Base = Null_Address then + -- On many platforms, we don't know the real stack base + -- address. Estimate it using an address in the frame. + Stack_Base := Bottom_Of_Stack'Address; + + -- Also reduce the size of the stack to take into account the + -- secondary stack array declared in this frame. This is for + -- sure very conservative. + if not Parameters.Sec_Stack_Dynamic then + Pattern_Size := + Pattern_Size - Natural (Secondary_Stack_Size); + end if; + + -- Adjustments for inner frames + Pattern_Size := Pattern_Size - + (if Pattern_Size < Small_Stack_Limit + then Small_Overflow_Guard + else Big_Overflow_Guard); + else + -- Reduce by the size of the final guard page + Pattern_Size := Pattern_Size - Guard_Page_Size; + end if; + + STPO.Lock_RTS; + Initialize_Analyzer + (Self_ID.Common.Analyzer, + Self_ID.Common.Task_Image (1 .. Self_ID.Common.Task_Image_Len), + Natural (Self_ID.Common.Compiler_Data.Pri_Stack_Info.Size), + SSE.To_Integer (Stack_Base), + Pattern_Size); + STPO.Unlock_RTS; + Fill_Stack (Self_ID.Common.Analyzer); + end; end if; -- We setup the SEH (Structured Exception Handling) handler if supported Index: gnat_ugn.texi =================================================================== --- gnat_ugn.texi (revision 177383) +++ gnat_ugn.texi (working copy) @@ -17259,7 +17259,7 @@ columns: @noindent -Index | Task Name | Stack Size | Stack Usage [Value +/- Variation] +Index | Task Name | Stack Size | Stack Usage @noindent where: @@ -17277,8 +17277,7 @@ @item Stack Usage is the measure done by the stack analyzer. In order to prevent overflow, the stack is not entirely analyzed, and it's not possible to know exactly how -much has actually been used. The report thus contains the theoretical stack usage -(Value) and the possible variation (Variation) around this value. +much has actually been used. @end table Index: s-stausa.adb =================================================================== --- s-stausa.adb (revision 177274) +++ s-stausa.adb (working copy) @@ -6,7 +6,7 @@ -- -- -- B o d y -- -- -- --- Copyright (C) 2004-2010, Free Software Foundation, Inc. -- +-- Copyright (C) 2004-2011, Free Software Foundation, Inc. -- -- -- -- GNARL is free software; you can redistribute it and/or modify it under -- -- terms of the GNU General Public License as published by the Free Soft- -- @@ -93,76 +93,6 @@ -- | entry frame | ... | leaf frame | |####| -- +------------------------------------------------------------------+ - function Top_Slot_Index_In (Stack : Stack_Slots) return Integer; - -- Index of the stack Top slot in the Slots array, denoting the latest - -- possible slot available to call chain leaves. - - function Bottom_Slot_Index_In (Stack : Stack_Slots) return Integer; - -- Index of the stack Bottom slot in the Slots array, denoting the first - -- possible slot available to call chain entry points. - - function Push_Index_Step_For (Stack : Stack_Slots) return Integer; - -- By how much do we need to update a Slots index to Push a single slot on - -- the stack. - - function Pop_Index_Step_For (Stack : Stack_Slots) return Integer; - -- By how much do we need to update a Slots index to Pop a single slot off - -- the stack. - - pragma Inline_Always (Top_Slot_Index_In); - pragma Inline_Always (Bottom_Slot_Index_In); - pragma Inline_Always (Push_Index_Step_For); - pragma Inline_Always (Pop_Index_Step_For); - - ----------------------- - -- Top_Slot_Index_In -- - ----------------------- - - function Top_Slot_Index_In (Stack : Stack_Slots) return Integer is - begin - if System.Parameters.Stack_Grows_Down then - return Stack'First; - else - return Stack'Last; - end if; - end Top_Slot_Index_In; - - ---------------------------- - -- Bottom_Slot_Index_In -- - ---------------------------- - - function Bottom_Slot_Index_In (Stack : Stack_Slots) return Integer is - begin - if System.Parameters.Stack_Grows_Down then - return Stack'Last; - else - return Stack'First; - end if; - end Bottom_Slot_Index_In; - - ------------------------- - -- Push_Index_Step_For -- - ------------------------- - - function Push_Index_Step_For (Stack : Stack_Slots) return Integer is - pragma Unreferenced (Stack); - begin - if System.Parameters.Stack_Grows_Down then - return -1; - else - return +1; - end if; - end Push_Index_Step_For; - - ------------------------ - -- Pop_Index_Step_For -- - ------------------------ - - function Pop_Index_Step_For (Stack : Stack_Slots) return Integer is - begin - return -Push_Index_Step_For (Stack); - end Pop_Index_Step_For; - ------------------- -- Unit Services -- ------------------- @@ -175,9 +105,6 @@ Stack_Size_Str : constant String := "Stack Size"; Actual_Size_Str : constant String := "Stack usage"; - function Get_Usage_Range (Result : Task_Result) return String; - -- Return string representing the range of possible result of stack usage - procedure Output_Result (Result_Id : Natural; Result : Task_Result; @@ -194,7 +121,6 @@ ---------------- procedure Initialize (Buffer_Size : Natural) is - Bottom_Of_Stack : aliased Integer; Stack_Size_Chars : System.Address; begin @@ -204,9 +130,8 @@ Result_Array.all := (others => (Task_Name => (others => ASCII.NUL), - Variation => 0, Value => 0, - Max_Size => 0)); + Stack_Size => 0)); -- Set the Is_Enabled flag to true, so that the task wrapper knows that -- it has to handle dynamic stack analysis @@ -231,9 +156,8 @@ (Environment_Task_Analyzer, "ENVIRONMENT TASK", My_Stack_Size, - My_Stack_Size, - System.Storage_Elements.To_Integer (Bottom_Of_Stack'Address), - 0); + 0, + My_Stack_Size); Fill_Stack (Environment_Task_Analyzer); @@ -257,99 +181,78 @@ -- big, the more an "instrumentation threshold at writing" error is -- likely to happen. - Stack_Used_When_Filling : Integer; - Current_Stack_Level : aliased Integer; + Current_Stack_Level : aliased Integer; - Guard : constant Integer := 256; + Guard : constant := 256; -- Guard space between the Current_Stack_Level'Address and the last -- allocated byte on the stack. - begin - -- Easiest and most accurate method: the top of the stack is known. + if Parameters.Stack_Grows_Down then + if Analyzer.Stack_Base - Stack_Address (Analyzer.Pattern_Size) + > To_Stack_Address (Current_Stack_Level'Address) - Guard + then + -- No room for a pattern + Analyzer.Pattern_Size := 0; + return; + end if; - if Analyzer.Top_Pattern_Mark /= 0 then - Analyzer.Pattern_Size := - Stack_Size (Analyzer.Top_Pattern_Mark, - To_Stack_Address (Current_Stack_Level'Address)) - - Guard; + Analyzer.Pattern_Limit := Analyzer.Stack_Base + - Stack_Address (Analyzer.Pattern_Size); - if System.Parameters.Stack_Grows_Down then - Analyzer.Stack_Overlay_Address := - To_Address (Analyzer.Top_Pattern_Mark); - else - Analyzer.Stack_Overlay_Address := - To_Address (Analyzer.Top_Pattern_Mark - - Stack_Address (Analyzer.Pattern_Size)); + if Analyzer.Stack_Base > + To_Stack_Address (Current_Stack_Level'Address) - Guard + then + -- Reduce pattern size to prevent local frame overwrite + Analyzer.Pattern_Size := + Integer (To_Stack_Address (Current_Stack_Level'Address) - Guard + - Analyzer.Pattern_Limit); end if; - declare - Pattern : aliased Stack_Slots - (1 .. Analyzer.Pattern_Size / Bytes_Per_Pattern); - for Pattern'Address use Analyzer.Stack_Overlay_Address; - - begin - if System.Parameters.Stack_Grows_Down then - for J in reverse Pattern'Range loop - Pattern (J) := Analyzer.Pattern; - end loop; - - Analyzer.Bottom_Pattern_Mark := - To_Stack_Address (Pattern (Pattern'Last)'Address); - - else - for J in Pattern'Range loop - Pattern (J) := Analyzer.Pattern; - end loop; - - Analyzer.Bottom_Pattern_Mark := - To_Stack_Address (Pattern (Pattern'First)'Address); - end if; - end; - + Analyzer.Pattern_Overlay_Address := + To_Address (Analyzer.Pattern_Limit); else - -- Readjust the pattern size. When we arrive in this function, there - -- is already a given amount of stack used, that we won't analyze. - - Stack_Used_When_Filling := - Stack_Size (Analyzer.Bottom_Of_Stack, - To_Stack_Address (Current_Stack_Level'Address)); - - if Stack_Used_When_Filling > Analyzer.Pattern_Size then - - -- In this case, the known size of the stack is too small, we've - -- already taken more than expected, so there's no possible - -- computation - + if Analyzer.Stack_Base + Stack_Address (Analyzer.Pattern_Size) + < To_Stack_Address (Current_Stack_Level'Address) + Guard + then + -- No room for a pattern Analyzer.Pattern_Size := 0; - else - Analyzer.Pattern_Size := - Analyzer.Pattern_Size - Stack_Used_When_Filling; + return; end if; - declare - Stack : aliased Stack_Slots - (1 .. Analyzer.Pattern_Size / Bytes_Per_Pattern); + Analyzer.Pattern_Limit := Analyzer.Stack_Base + + Stack_Address (Analyzer.Pattern_Size); - begin - Stack := (others => Analyzer.Pattern); + if Analyzer.Stack_Base < + To_Stack_Address (Current_Stack_Level'Address) + Guard + then + -- Reduce pattern size to prevent local frame overwrite + Analyzer.Pattern_Size := Integer + (Analyzer.Pattern_Limit + - (To_Stack_Address (Current_Stack_Level'Address) + Guard)); + end if; - Analyzer.Stack_Overlay_Address := Stack'Address; - - if Analyzer.Pattern_Size /= 0 then - Analyzer.Bottom_Pattern_Mark := - To_Stack_Address - (Stack (Bottom_Slot_Index_In (Stack))'Address); - Analyzer.Top_Pattern_Mark := - To_Stack_Address - (Stack (Top_Slot_Index_In (Stack))'Address); - else - Analyzer.Bottom_Pattern_Mark := - To_Stack_Address (Stack'Address); - Analyzer.Top_Pattern_Mark := - To_Stack_Address (Stack'Address); - end if; - end; + Analyzer.Pattern_Overlay_Address := + To_Address (Analyzer.Pattern_Limit + - Stack_Address (Analyzer.Pattern_Size)); end if; + + -- Declare and fill the pattern buffer + declare + Pattern : aliased Stack_Slots + (1 .. Analyzer.Pattern_Size / Bytes_Per_Pattern); + for Pattern'Address use Analyzer.Pattern_Overlay_Address; + + begin + if System.Parameters.Stack_Grows_Down then + for J in reverse Pattern'Range loop + Pattern (J) := Analyzer.Pattern; + end loop; + else + for J in Pattern'Range loop + Pattern (J) := Analyzer.Pattern; + end loop; + end if; + end; end Fill_Stack; ------------------------- @@ -359,22 +262,20 @@ procedure Initialize_Analyzer (Analyzer : in out Stack_Analyzer; Task_Name : String; - My_Stack_Size : Natural; - Max_Pattern_Size : Natural; - Bottom : Stack_Address; - Top : Stack_Address; - Pattern : Unsigned_32 := 16#DEAD_BEEF#) + Stack_Size : Natural; + Stack_Base : Stack_Address; + Pattern_Size : Natural; + Pattern : Interfaces.Unsigned_32 := 16#DEAD_BEEF#) is begin -- Initialize the analyzer fields - Analyzer.Bottom_Of_Stack := Bottom; - Analyzer.Stack_Size := My_Stack_Size; - Analyzer.Pattern_Size := Max_Pattern_Size; - Analyzer.Pattern := Pattern; - Analyzer.Result_Id := Next_Id; - Analyzer.Task_Name := (others => ' '); - Analyzer.Top_Pattern_Mark := Top; + Analyzer.Stack_Base := Stack_Base; + Analyzer.Stack_Size := Stack_Size; + Analyzer.Pattern_Size := Pattern_Size; + Analyzer.Pattern := Pattern; + Analyzer.Result_Id := Next_Id; + Analyzer.Task_Name := (others => ' '); -- Compute the task name, and truncate if bigger than Task_Name_Length @@ -399,9 +300,9 @@ is begin if SP_Low > SP_High then - return Natural (SP_Low - SP_High + 4); + return Natural (SP_Low - SP_High); else - return Natural (SP_High - SP_Low + 4); + return Natural (SP_High - SP_Low); end if; end Stack_Size; @@ -417,10 +318,17 @@ -- likely to happen. Stack : Stack_Slots (1 .. Analyzer.Pattern_Size / Bytes_Per_Pattern); - for Stack'Address use Analyzer.Stack_Overlay_Address; + for Stack'Address use Analyzer.Pattern_Overlay_Address; begin - Analyzer.Topmost_Touched_Mark := Analyzer.Bottom_Pattern_Mark; + -- Value if the pattern was not modified + if Parameters.Stack_Grows_Down then + Analyzer.Topmost_Touched_Mark := + Analyzer.Pattern_Limit + Stack_Address (Analyzer.Pattern_Size); + else + Analyzer.Topmost_Touched_Mark := + Analyzer.Pattern_Limit - Stack_Address (Analyzer.Pattern_Size); + end if; if Analyzer.Pattern_Size = 0 then return; @@ -430,41 +338,28 @@ -- the bottom of it. The first index not equals to the patterns marks -- the beginning of the used stack. - declare - Top_Index : constant Integer := Top_Slot_Index_In (Stack); - Bottom_Index : constant Integer := Bottom_Slot_Index_In (Stack); - Step : constant Integer := Pop_Index_Step_For (Stack); - J : Integer; - - begin - J := Top_Index; - loop + if System.Parameters.Stack_Grows_Down then + for J in Stack'Range loop if Stack (J) /= Analyzer.Pattern then Analyzer.Topmost_Touched_Mark := To_Stack_Address (Stack (J)'Address); exit; end if; + end loop; - exit when J = Bottom_Index; - J := J + Step; + else + for J in reverse Stack'Range loop + if Stack (J) /= Analyzer.Pattern then + Analyzer.Topmost_Touched_Mark + := To_Stack_Address (Stack (J)'Address); + exit; + end if; end loop; - end; + + end if; end Compute_Result; --------------------- - -- Get_Usage_Range -- - --------------------- - - function Get_Usage_Range (Result : Task_Result) return String is - Variation_Used_Str : constant String := - Natural'Image (Result.Variation); - Value_Used_Str : constant String := - Natural'Image (Result.Value); - begin - return Value_Used_Str & " +/- " & Variation_Used_Str; - end Get_Usage_Range; - - --------------------- -- Output_Result -- --------------------- @@ -474,16 +369,16 @@ Max_Stack_Size_Len : Natural; Max_Actual_Use_Len : Natural) is - Result_Id_Str : constant String := Natural'Image (Result_Id); - My_Stack_Size_Str : constant String := Natural'Image (Result.Max_Size); - Actual_Use_Str : constant String := Get_Usage_Range (Result); + Result_Id_Str : constant String := Natural'Image (Result_Id); + Stack_Size_Str : constant String := Natural'Image (Result.Stack_Size); + Actual_Use_Str : constant String := Natural'Image (Result.Value); Result_Id_Blanks : constant String (1 .. Index_Str'Length - Result_Id_Str'Length) := (others => ' '); Stack_Size_Blanks : constant - String (1 .. Max_Stack_Size_Len - My_Stack_Size_Str'Length) := + String (1 .. Max_Stack_Size_Len - Stack_Size_Str'Length) := (others => ' '); Actual_Use_Blanks : constant @@ -496,7 +391,7 @@ Put (" | "); Put (Result.Task_Name); Put (" | "); - Put (Stack_Size_Blanks & My_Stack_Size_Str); + Put (Stack_Size_Blanks & Stack_Size_Str); Put (" | "); Put (Actual_Use_Blanks & Actual_Use_Str); New_Line; @@ -508,7 +403,7 @@ procedure Output_Results is Max_Stack_Size : Natural := 0; - Max_Actual_Use_Result_Id : Natural := Result_Array'First; + Max_Stack_Usage : Natural := 0; Max_Stack_Size_Len, Max_Actual_Use_Len : Natural := 0; Task_Name_Blanks : constant @@ -531,21 +426,18 @@ for J in Result_Array'Range loop exit when J >= Next_Id; - if Result_Array (J).Value > - Result_Array (Max_Actual_Use_Result_Id).Value - then - Max_Actual_Use_Result_Id := J; + if Result_Array (J).Value > Max_Stack_Usage then + Max_Stack_Usage := Result_Array (J).Value; end if; - if Result_Array (J).Max_Size > Max_Stack_Size then - Max_Stack_Size := Result_Array (J).Max_Size; + if Result_Array (J).Stack_Size > Max_Stack_Size then + Max_Stack_Size := Result_Array (J).Stack_Size; end if; end loop; Max_Stack_Size_Len := Natural'Image (Max_Stack_Size)'Length; - Max_Actual_Use_Len := - Get_Usage_Range (Result_Array (Max_Actual_Use_Result_Id))'Length; + Max_Actual_Use_Len := Natural'Image (Max_Stack_Usage)'Length; -- Display the output header. Blanks will be added in front of the -- labels if needed. @@ -599,37 +491,22 @@ ------------------- procedure Report_Result (Analyzer : Stack_Analyzer) is - Result : Task_Result := - (Task_Name => Analyzer.Task_Name, - Max_Size => Analyzer.Stack_Size, - Variation => 0, - Value => 0); - - Overflow_Guard : constant Integer := - Analyzer.Stack_Size - - Stack_Size (Analyzer.Top_Pattern_Mark, Analyzer.Bottom_Of_Stack); - Max, Min : Positive; - + Result : Task_Result := (Task_Name => Analyzer.Task_Name, + Stack_Size => Analyzer.Stack_Size, + Value => 0); begin if Analyzer.Pattern_Size = 0 then - -- If we have that result, it means that we didn't do any computation -- at all. In other words, we used at least everything (and possibly -- more). - Min := Analyzer.Stack_Size - Overflow_Guard; - Max := Analyzer.Stack_Size; + Result.Value := Analyzer.Stack_Size; else - Min := - Stack_Size - (Analyzer.Topmost_Touched_Mark, Analyzer.Bottom_Of_Stack); - Max := Min + Overflow_Guard; + Result.Value := Stack_Size (Analyzer.Topmost_Touched_Mark, + Analyzer.Stack_Base); end if; - Result.Value := (Max + Min) / 2; - Result.Variation := (Max - Min) / 2; - if Analyzer.Result_Id in Result_Array'Range then -- If the result can be stored, then store it in Result_Array @@ -641,7 +518,7 @@ declare Result_Str_Len : constant Natural := - Get_Usage_Range (Result)'Length; + Natural'Image (Result.Value)'Length; Size_Str_Len : constant Natural := Natural'Image (Analyzer.Stack_Size)'Length; Index: s-stausa.ads =================================================================== --- s-stausa.ads (revision 177274) +++ s-stausa.ads (working copy) @@ -6,7 +6,7 @@ -- -- -- S p e c -- -- -- --- Copyright (C) 2004-2010, Free Software Foundation, Inc. -- +-- Copyright (C) 2004-2011, Free Software Foundation, Inc. -- -- -- -- GNARL is free software; you can redistribute it and/or modify it under -- -- terms of the GNU General Public License as published by the Free Soft- -- @@ -57,11 +57,8 @@ -- Amount of stack used. The value is calculated on the basis of the -- mechanism used by GNAT to allocate it, and it is NOT a precise value. - Variation : Natural; - -- Possible variation in the amount of used stack. The real stack usage - -- may vary in the range Value +/- Variation - - Max_Size : Natural; + Stack_Size : Natural; + -- Size of the stack end record; type Result_Array_Type is array (Positive range <>) of Task_Result; @@ -91,8 +88,9 @@ -- begin -- Initialize_Analyzer (A, -- "Task t", + -- A_Storage_Size, + -- 0, -- A_Storage_Size - A_Guard, - -- A_Guard -- To_Stack_Address (Bottom_Of_Stack'Address)); -- Fill_Stack (A); -- Some_User_Code; @@ -115,7 +113,9 @@ -- before the call to the instrumentation procedure. -- Strategy: The user of this package should measure the bottom of stack - -- before the call to Fill_Stack and pass it in parameter. + -- before the call to Fill_Stack and pass it in parameter. The impact + -- is very minor unless the stack used is very small, but in this case + -- you aren't very interested by the figure. -- Instrumentation threshold at writing: @@ -212,32 +212,29 @@ -- the memory will look like that: -- -- Stack growing - -- -----------------------------------------------------------------------> - -- |<---------------------->|<----------------------------------->| - -- | Stack frame | Memory filled with Analyzer.Pattern | - -- | of Fill_Stack | | - -- | (deallocated at | | - -- | the end of the call) | | - -- ^ | ^ - -- Analyzer.Bottom_Of_Stack | Analyzer.Top_Pattern_Mark - -- ^ - -- Analyzer.Bottom_Pattern_Mark + -- ----------------------------------------------------------------------> + -- |<--------------------->|<----------------------------------->| + -- | Stack frames to | Memory filled with Analyzer.Pattern | + -- | Fill_Stack | | + -- ^ | ^ + -- Analyzer.Stack_Base | Analyzer.Pattern_Limit + -- ^ + -- Analyzer.Pattern_Limit +/- Analyzer.Pattern_Size -- procedure Initialize_Analyzer (Analyzer : in out Stack_Analyzer; Task_Name : String; - My_Stack_Size : Natural; - Max_Pattern_Size : Natural; - Bottom : Stack_Address; - Top : Stack_Address; + Stack_Size : Natural; + Stack_Base : Stack_Address; + Pattern_Size : Natural; Pattern : Interfaces.Unsigned_32 := 16#DEAD_BEEF#); -- Should be called before any use of a Stack_Analyzer, to initialize it. -- Max_Pattern_Size is the size of the pattern zone, might be smaller than - -- the full stack size in order to take into account e.g. the secondary - -- stack and a guard against overflow. The actual size taken will be - -- readjusted with data already used at the time the stack is actually - -- filled. + -- the full stack size Stack_Size in order to take into account e.g. the + -- secondary stack and a guard against overflow. The actual size taken + -- will be readjusted with data already used at the time the stack is + -- actually filled. Is_Enabled : Boolean := False; -- When this flag is true, then stack analysis is enabled @@ -253,16 +250,14 @@ -- Stack growing -- -----------------------------------------------------------------------> -- |<---------------------->|<-------------->|<--------->|<--------->| - -- | Stack frame | Array of | used | Memory | - -- | of Compute_Result | Analyzer.Probe | during | filled | - -- | (deallocated at | elements | the | with | - -- | the end of the call) | | execution | pattern | - -- | ^ | | | - -- | Bottom_Pattern_Mark | | | + -- | Stack frames | Array of | used | Memory | + -- | to Compute_Result | Analyzer.Probe | during | filled | + -- | | elements | the | with | + -- | | | execution | pattern | -- | | | -- |<----------------------------------------------------> | -- Stack used ^ - -- Top_Pattern_Mark + -- Pattern_Limit procedure Report_Result (Analyzer : Stack_Analyzer); -- Store the results of the computation in memory, at the address @@ -288,6 +283,10 @@ Task_Name : String (1 .. Task_Name_Length); -- Name of the task + Stack_Base : Stack_Address; + -- Address of the base of the stack, as given by the caller of + -- Initialize_Analyzer. + Stack_Size : Natural; -- Entire size of the analyzed stack @@ -297,23 +296,16 @@ Pattern : Pattern_Type; -- Pattern used to recognize untouched memory - Bottom_Pattern_Mark : Stack_Address; - -- Bound of the pattern area on the stack closest to the bottom + Pattern_Limit : Stack_Address; + -- Bound of the pattern area farthest to the base - Top_Pattern_Mark : Stack_Address; - -- Topmost bound of the pattern area on the stack - Topmost_Touched_Mark : Stack_Address; -- Topmost address of the pattern area whose value it is pointing -- at has been modified during execution. If the systematic error are -- compensated, it is the topmost value of the stack pointer during -- the execution. - Bottom_Of_Stack : Stack_Address; - -- Address of the bottom of the stack, as given by the caller of - -- Initialize_Analyzer. - - Stack_Overlay_Address : System.Address; + Pattern_Overlay_Address : System.Address; -- Address of the stack abstraction object we overlay over a -- task's real stack, typically a pattern-initialized array. Index: s-stusta.adb =================================================================== --- s-stusta.adb (revision 177274) +++ s-stusta.adb (working copy) @@ -6,7 +6,7 @@ -- -- -- B o d y -- -- -- --- Copyright (C) 2009-2010, Free Software Foundation, Inc. -- +-- Copyright (C) 2009-2011, Free Software Foundation, Inc. -- -- -- -- GNAT is free software; you can redistribute it and/or modify it under -- -- terms of the GNU General Public License as published by the Free Soft- -- @@ -250,9 +250,8 @@ Obj.Task_Name (Obj.Task_Name'First .. Pos); begin Put_Line - ("| " & T_Name & " | " & Natural'Image (Obj.Max_Size) & - Natural'Image (Obj.Value) & " +/- " & - Natural'Image (Obj.Variation)); + ("| " & T_Name & " | " & Natural'Image (Obj.Stack_Size) & + Natural'Image (Obj.Value)); end; end Print;