comp.lang.ada
 help / color / mirror / Atom feed
Search results ordered by [date|relevance]  view[summary|nested|Atom feed]
thread overview below | download mbox.gz: |
* Re: Custom Storage Pool questions
  @ 2021-10-02 23:19  4%               ` Jere
  0 siblings, 0 replies; 96+ results
From: Jere @ 2021-10-02 23:19 UTC (permalink / raw)


I was thinking more along the lines of adding a classwide operation on the 
root storage pool type.  That shouldn't change anyone's implementation
ideally.  Something like:

    -- Parameter is mode "in out" to allow for it to clear itself if the implementation
    -- so desires
    function Is_First_Allocation(Self : in out Root_Storage_Pool'Class) return Boolean;

Added to System.Storage_Pools.  Allow the implementation to implement it
however they like under the hood.  They could, for example, add a boolean
to the private part of the root storage pool and add a child function/package that 
sets it when the compiler implementation calls for the first allocation.  It can be 
implemented with a count.  I'm sure there are a plethora of ways.

Since the operation is classwide and it is optional, it wouldn't affect anyone's
existing storage pools.  it would basically just be there to give custom
storage pool designers a hook to know when it is portably safe to add
a custom header, regardless of the number of allocations an implementation
chooses to do.

It does place the burden on the compiler implementors to call it for the first
allocation, but I can't imagine that is a huge burden with today's IDE tools?

On Tuesday, September 28, 2021 at 12:42:16 AM UTC-4, Randy Brukardt wrote:
> "Jere" <> wrote in message
> news:6a073ced-4c3b-4e87...@googlegroups.com... 
> ...
> > We can't change the Allocate specification since it is what it is, but is 
> > there 
> > any consideration to adding functionality to the root storage pool type,
> We tried that as a solution for the user-defined dereference problem, and it 
> ended up going nowhere. Your problem is different but the issues of changing 
> the Storage_Pool spec remain. Not sure it could be made to work (one does 
> not want to force everyone to change their existing storage pools). 
> 
> Randy.

^ permalink raw reply	[relevance 4%]

* Re: Custom Storage Pool questions
  @ 2021-09-20 16:59  5%         ` Shark8
    1 sibling, 0 replies; 96+ results
From: Shark8 @ 2021-09-20 16:59 UTC (permalink / raw)


On Monday, September 20, 2021 at 12:48:21 AM UTC-6, briot.e wrote:
> > > If a compiler is allowed to break up an allocation into multiple 
> > > calls to Allocate (and of course Deallocate), how does one go about 
> > > enforcing that the user's header is only created once? 
> > I think one cannot enforce that, because the calls to Allocate do not 
> > indicate (with parameters) which set of calls concern the same object 
> > allocation.
> I think the only solution would be for this compiler to have another attribute similar to 'Storage_Pool, but that would define the pool for the descriptor: 
> 
> for X'Storage_Pool use Pool; 
> for X'Descriptor_Storage_Pool use Other_Pool; 
> 
> That way the user can decide when to add (or not) extra headers.
Hmmm, smells like a place to use generics and subpools; perhaps something like:

Generic
   Type Element(<>) is limited private;
   Type Descriptor(<>) is limited private;
   with Create( Item : Element ) return Descriptor;
Package Descriptor_Subpool is
   Type Pool_Type is new System.Storage_Pools.Subpools.Root_Storage_Pool_With_Subpools with private;
Private
   -- Element-subpool & descriptor-subpool defined here.
   -- Allocation of element also allocates Descriptor.
End Descriptor_Subpool;

Just top-of-the-head musings though.

^ permalink raw reply	[relevance 5%]

* Alignment issue
@ 2019-02-16 19:40  5% Simon Wright
  0 siblings, 0 replies; 96+ results
From: Simon Wright @ 2019-02-16 19:40 UTC (permalink / raw)


I have code like this (written while working on a StackOverflow
question), and GNAT ignores apparent alignment requests.

   with System.Storage_Pools;
   with System.Storage_Elements;
   package Alignment_Issue is

      type Data_Store is new System.Storage_Elements.Storage_Array
      with Alignment => 16;  --  Standard'Maximum_Alignment;

      type User_Pool (Size : System.Storage_Elements.Storage_Count)
         is  record
            Flag          : Boolean;
            Data          : Data_Store (1 .. Size);
         end record
      with Alignment => 16;  --  Standard'Maximum_Alignment;

   end Alignment_Issue;

(Standard'Maximum_Alignment is a GNAT special) and compiling with GNAT
CE 2018 (and other GNAT compilers) I see

   $ /opt/gnat-ce-2018/bin/gnatmake -c -u -f -gnatR alignment_issue.ads 
   gcc -c -gnatR alignment_issue.ads

   Representation information for unit Alignment_Issue (spec)
   ----------------------------------------------------------

   for Data_Store'Alignment use 16;
   for Data_Store'Component_Size use 8;

   for User_Pool'Object_Size use ??;
   for User_Pool'Value_Size use ??;
   for User_Pool'Alignment use 16;
   for User_Pool use record
      Size at 0 range  0 .. 63;
      Flag at 8 range  0 ..  7;
      Data at 9 range  0 .. ??;
   end record;

which means that GNAT has ignored the alignment specified for Data_Store
when setting up User_Pool.Data.

Is this expected? OK?

I found a workround of sorts:

   type Data_Store (Size : System.Storage_Elements.Storage_Count) is record
      Data : System.Storage_Elements.Storage_Array (1 .. Size);
   end record
   with Alignment => 16;  --  Standard'Maximum_Alignment;

   type User_Pool (Size : System.Storage_Elements.Storage_Count)
      is record
         Flag  : Boolean;
         Stack : Data_Store (Size);
      end record;

giving

   Representation information for unit Alignment_Issue (spec)
   ----------------------------------------------------------

   for Data_Store'Object_Size use ??;
   for Data_Store'Value_Size use ??;
   for Data_Store'Alignment use 16;
   for Data_Store use record
      Size at 0 range  0 .. 63;
      Data at 8 range  0 .. ??;
   end record;

   for User_Pool'Object_Size use ??;
   for User_Pool'Value_Size use ??;
   for User_Pool'Alignment use 16;
   for User_Pool use record
      Size  at  0 range  0 .. 63;
      Flag  at  8 range  0 ..  7;
      Stack at 16 range  0 .. ??;
   end record;

(but even then I see that Stack.Data is offset by 8 bytes because of the
discriminant)

^ permalink raw reply	[relevance 5%]

* Re: Memory pools
    2018-05-31 19:28  5% ` gorgelo
@ 2018-05-31 19:33  4% ` gorgelo
  1 sibling, 0 replies; 96+ results
From: gorgelo @ 2018-05-31 19:33 UTC (permalink / raw)


And to follow up on the naive benchmarks:
https://github.com/frol/completely-unscientific-benchmarks

Using the memory pool in the previous post it can be used to implement the Treap algorithm (after some minor modifications):

pragma Suppress (Tampering_Check);
-- Tampering checks are only for multi-task applications.
-- Since this application is single task we can safely
-- suppress tampering checks of the standard containers.
-- If performance is an issue, the Ada-Traits Containers may be used instead.

with System.Storage_Elements;
with System.Storage_Pools;
with Ada.Text_IO;
with Ada.Integer_Text_IO;
with Ada.Containers.Vectors;
with Ada.Unchecked_Deallocation;
with Ada.Numerics.Discrete_Random;

procedure Main is

   subtype Storage_Offset is System.Storage_Elements.Storage_Offset;
   subtype Storage_Count  is System.Storage_Elements.Storage_Count;
   subtype Storage_Array  is System.Storage_Elements.Storage_Array;

   subtype Root_Storage_Pool is System.Storage_Pools.Root_Storage_Pool;

   subtype Integer_Address is System.Storage_Elements.Integer_Address;

   subtype Count_Type is Ada.Containers.Count_Type;

   use type Count_Type;
   use type Storage_Offset;
   use type Integer_Address;

   procedure Put (Text : String) renames Ada.Text_IO.Put;

   procedure Put_Line (Text : String) renames Ada.Text_IO.Put_Line;

   procedure Put_Line (I : Integer) is
   begin
      Ada.Integer_Text_IO.Put (I, 0);
      Ada.Text_IO.New_Line;
   end Put_Line;

   procedure Put (I : Integer) is
   begin
      Ada.Integer_Text_IO.Put (I, 0);
   end Put;

   procedure Put (I : Storage_Offset) is
   begin
      Ada.Integer_Text_IO.Put (Integer (I), 0);
   end Put;

   function To_Integer (Value : System.Address) return Integer_Address
                        renames System.Storage_Elements.To_Integer;

   generic
      Slot_Size : Positive;
      -- Specifies the size of each slot in Storage Elements (bytes)
      -- Must be big enough to store any object one wishes to allocate
      -- inside the memory pool.

      MAX : Positive;
      -- Specifies the number of slots that will be allocated in an array
      -- from the heap every time more memory needs to be pre-allocated.

   package Arena_Pools is

      type Arena (<>) is new Root_Storage_Pool with private;

      function Make return Arena;

      overriding
      procedure Allocate
        (  Pool      : in out Arena;
           Address   : out System.Address;
           Size      : Storage_Count;
           Alignment : Storage_Count
          );

      overriding
      procedure Deallocate
        (  Pool      : in out Arena;
           Address   : System.Address;
           Size      : Storage_Count;
           Alignment : Storage_Count
          );

      overriding
      function Storage_Size (Pool : Arena) return Storage_Count;
      -- Approximation of how many Storage Elements (bytes)
      -- have been heap-allocated.

   private

      type Slot is record
         Elements : Storage_Array (1..Storage_Offset (Slot_Size));
      end record;

      subtype Slot_Index is Storage_Offset range 1.. Storage_Offset (MAX);

      type Slots_Array is array (Slot_Index) of Slot;

      subtype Free_Index is Integer range 1..MAX;
      -- This Integer type (32-bits) is created in order to not use the type
      -- Storage_Offset (64-bits) in the free indices vector.

      package Indices_Vector is new Ada.Containers.Vectors
        (Index_Type   => Positive,
         Element_Type => Free_Index,
         "="          => "=");

      type Slots_Envelope is record
         Items        : Slots_Array;
         Free_Indices : Indices_Vector.Vector;
      end record;

      type Slots_Envelope_Ptr is access all Slots_Envelope;

      package Envelope_Vectors is new Ada.Containers.Vectors
        (Index_Type   => Positive,
         Element_Type => Slots_Envelope_Ptr,
         "="          => "=");

      type Arena is new Root_Storage_Pool with record
         Index : Positive := 1;
         -- Indicates which array of slots to first search for a free index

         Envelopes : Envelope_Vectors.Vector;
      end record;

      overriding
      procedure Finalize (This : in out Arena);
      -- Deallocates all allocated memory from the heap

   end Arena_Pools;

   package body Arena_Pools is

      function Make return Slots_Envelope_Ptr is
         Envelope : Slots_Envelope_Ptr := new Slots_Envelope;
      begin
         Envelope.Free_Indices.Reserve_Capacity (Ada.Containers.Count_Type (MAX));
         for I in Slot_Index'Range loop
            Envelope.Free_Indices.Append (Free_Index (I));
         end loop;

         return Envelope;
      end Make;

      function Make return Arena is
         Envelope : Slots_Envelope_Ptr := Make;
      begin
         return This : Arena do
            This.Envelopes.Append (Envelope);
         end return;
      end Make;

      function Determine_Index (Pool    : Arena;
                                Address : System.Address) return Positive is
         Searched_For : Natural := 0;
         First_Address : System.Address;
         Last_Address  : System.Address;
      begin
         for I in Pool.Envelopes.First_Index..Pool.Envelopes.Last_Index loop
            First_Address := Pool.Envelopes (I).Items (1)'Address;
            Last_Address  := Pool.Envelopes (I).Items (Storage_Offset (MAX))'Address;
            if
              To_Integer (First_Address) <= To_Integer (Address) and
              To_Integer (Address)       <= To_Integer (Last_Address)
            then
               Searched_For := I;
               exit;
            end if;
         end loop;

         if Searched_For = 0 then
            raise Storage_Error;
         end if;

         return Searched_For;
      end Determine_Index;

      procedure Allocate
        (Pool      : in out Arena;
         Address   : out System.Address;
         Size      : Storage_Count;
         Alignment : Storage_Count)
      is
         Id : Slot_Index;
      begin
         if Pool.Envelopes (Pool.Index).Free_Indices.Length > 0 then
            Id := Slot_Index (Pool.Envelopes (Pool.Index).Free_Indices.Last_Element);
            Pool.Envelopes (Pool.Index).Free_Indices.Delete_Last;
         else
            declare
               Has_Found : Boolean := False;
            begin
               for I in Pool.Envelopes.First_Index .. Pool.Envelopes.Last_Index loop
                  if Pool.Envelopes (I).Free_Indices.Length > 0 then
                     Pool.Index := I;
                     Id := Slot_Index (Pool.Envelopes (Pool.Index).Free_Indices.Last_Element);
                     Pool.Envelopes (Pool.Index).Free_Indices.Delete_Last;
                     Has_Found := True;
                     exit;
                  end if;
               end loop;

               if not Has_Found then
                  declare
                     E : Slots_Envelope_Ptr := Make;
                  begin
                     Pool.Envelopes.Append (E);
                     Pool.Index := Pool.Envelopes.Last_Index;
                     Id := Slot_Index (Pool.Envelopes (Pool.Index).Free_Indices.Last_Element);
                     Pool.Envelopes (Pool.Index).Free_Indices.Delete_Last;
                  end;
               end if;
            end;
         end if;

         Address := Pool.Envelopes (Pool.Index).Items (Id).Elements'Address;
      end Allocate;

      procedure Deallocate (Pool      : in out Arena;
                            Address   : System.Address;
                            Size      : Storage_Count;
                            Alignment : Storage_Count)
      is
         I : constant Positive := Determine_Index (Pool, Address);

         First_Address : System.Address;
         Last_Address  : System.Address;

         Slot_Id : Slot_Index;

         D : Integer_Address;
      begin
         First_Address := Pool.Envelopes (I).Items (1)'Address;
         Last_Address  := Pool.Envelopes (I).Items (Storage_Offset (MAX))'Address;

         D := (To_Integer (Last_Address) - To_Integer (First_Address) + Integer_Address (Slot_Size)) / Integer_Address (MAX);

         Slot_Id := Slot_Index ((To_Integer (Address) + Integer_Address (Slot_Size) - To_Integer (First_Address))/ D);

         Pool.Envelopes (I).Free_Indices.Append (Free_Index (Slot_Id));
      end Deallocate;

      function Storage_Size (Pool : Arena) return Storage_Count is
         Result : Storage_Count := 0;
      begin
         for Envelope of Pool.Envelopes loop
            Result := Storage_Count (Slot_Size*MAX) + Storage_Count (Envelope.Free_Indices.Capacity * 4);
         end loop;

         return Result;
      end Storage_Size;

      procedure Free is new Ada.Unchecked_Deallocation (Object => Slots_Envelope,
                                                        Name   => Slots_Envelope_Ptr);

      procedure Finalize (This : in out Arena) is
      begin
         for Envelope of This.Envelopes loop
            Free (Envelope);
         end loop;
         This.Envelopes.Clear;
      end Finalize;

   end Arena_Pools;

   package Pools is new Arena_Pools (24, 200_000);

   Pool : Pools.Arena := Pools.Make;

   -- Here ends the definition of the Storage pool and here begins
   -- implementation of the algorithm.

   package Integer_Random is new Ada.Numerics.Discrete_Random (Integer);

   G : Integer_Random.Generator;

   type Node;
   type Node_Ptr is access all Node with
     Storage_Pool => Pool;

   type Node is record
      Left  : Node_Ptr;
      Right : Node_Ptr;
      X     : Integer := 0;
      Y     : Integer := Integer_Random.Random (G);
   end record with
     Size => 24*8;

   package Tree_Def is

      type Tree is tagged private;

      function Has_Value (T : in out Tree;
                          X : in     Integer) return Boolean;

      procedure Insert (T : in out Tree;
                        X : in     Integer);

      procedure Erase (T : in out Tree;
                       X : in     Integer);

   private

      function Merge (Lower   : Node_Ptr;
                      Greater : Node_Ptr) return Node_Ptr;

      function Merge (Lower   : Node_Ptr;
                      Equal   : Node_Ptr;
                      Greater : Node_Ptr) return Node_Ptr;

      procedure Split (Orig             : in     Node_Ptr;
                       Lower            : in out Node_Ptr;
                       Greater_Or_Equal : in out Node_Ptr;
                       Value            : in     Integer);

      procedure Split (Orig    : in     Node_Ptr;
                       Lower   : in out Node_Ptr;
                       Equal   : in out Node_Ptr;
                       Greater : in out Node_Ptr;
                       Value   : in     Integer);

      procedure Make_Node (Node :    out Node_Ptr;
                           X    : in     Integer);

      type Tree is tagged record
         Root: Node_Ptr := null;
      end record;

   end Tree_Def;

   package body Tree_Def is

      procedure Free is new Ada.Unchecked_Deallocation(Object => Node,
                                                       Name   => Node_Ptr);

      procedure Make_Node (Node :    out Node_Ptr;
                           X    : in     Integer) is
      begin
         Node := new Main.Node;
         Node.X := X;
         Node.Y := Integer_Random.Random (G);
      end Make_Node;

      procedure Delete_Node (Node : in out Node_Ptr) is
      begin
         if Node /= null then
            if Node.Left /= null then
               Delete_Node(Node.Left);
            end if;

            if Node.Right /= null then
               Delete_Node (Node.Right);
            end if;

            Free (Node);
         end if;
      end Delete_Node;

      function Merge (Lower   : Node_Ptr;
                      Greater : Node_Ptr) return Node_Ptr is
      begin
         if Lower = null then
            return Greater;
         end if;

         if Greater = null then
            return lower;
         end if;

         if Lower.Y < Greater.Y then
            Lower.Right := Merge (Lower.Right, Greater);
            return Lower;
         else
            Greater.Left := Merge (Lower, Greater.Left);
            return Greater;
         end if;
      end Merge;

      function Merge (Lower   : Node_Ptr;
                      Equal   : Node_Ptr;
                      Greater : Node_Ptr) return Node_Ptr is
      begin
         return Merge (Merge (Lower, Equal), Greater);
      end merge;

      procedure Split (Orig             : in     Node_Ptr;
                       Lower            : in out Node_Ptr;
                       Greater_Or_Equal : in out Node_Ptr;
                       Value            : in     Integer) is
      begin
         if Orig = null then
            Lower := null;
            Greater_Or_Equal := null;
            return;
         end if;
         if Orig.X < Value then
            Lower := Orig;
            Split (Lower.Right, Lower.Right, Greater_Or_Equal, Value);
         else
            Greater_Or_Equal := Orig;
            Split (Greater_Or_Equal.Left, Lower, Greater_Or_Equal.Left, Value);
         end if;
      end Split;

      procedure Split (Orig    : in     Node_Ptr;
                       Lower   : in out Node_Ptr;
                       Equal   : in out Node_Ptr;
                       Greater : in out Node_Ptr;
                       Value   : in     Integer)
      is
         Equal_Or_Greater: Node_Ptr;
      begin
         Split (Orig, Lower, Equal_Or_Greater, Value);
         Split (Equal_Or_Greater, Equal, Greater, Value + 1);
      end Split;

      function Has_Value (T : in out Tree;
                          X : in     Integer) return Boolean
      is
         Lower   : Node_Ptr;
         Equal   : Node_Ptr;
         Greater : Node_Ptr;

         Result : Boolean;
      begin
         Split (T.Root, Lower, Equal, Greater, X);
         Result := Equal /= null;
         T.Root := Merge (Lower, Equal, Greater);
         return Result;
      end Has_Value;

      procedure Insert (T : in out Tree;
                        X : in     Integer)
      is
         Lower   : Node_Ptr;
         Equal   : Node_Ptr;
         Greater : Node_Ptr;
      begin
         Split (T.Root, Lower, Equal, Greater, X);
         if Equal = null then
            Make_Node (Equal, X);
         end if;
         T.Root := Merge (Lower, Equal, Greater);
      end Insert;

      procedure Erase (T : in out Tree;
                       X : in     Integer) is
         Lower   : Node_Ptr;
         Equal   : Node_Ptr;
         Greater : Node_Ptr;
      begin
         Split (T.Root, Lower, Equal, Greater, X);
         T.Root := Merge (Lower, Greater);
         -- commenting out the following line
         -- doesn't seem to affect running time by much, if at all
         Delete_Node (Equal);
      end Erase;

   end Tree_Def;

   Tree    : Tree_Def.Tree;
   Current : Integer := 5;
   Result  : Integer := 0;
   Mode    : Integer;

begin
   Integer_Random.Reset (G);

   for I in 1..1_000_000 loop
      Mode := I mod 3;
      Current := (Current * 57 + 43) mod 10007;
      if Mode = 0 then
         Tree.Insert (Current);
      elsif Mode = 1 then
         Tree.Erase (Current);
      else
         Result := Result + (if Tree.Has_Value (Current) then 1 else 0);
      end if;
   end loop;
   Put_Line (Result);

end Main;

^ permalink raw reply	[relevance 4%]

* Re: Memory pools
  @ 2018-05-31 19:28  5% ` gorgelo
  2018-05-31 19:33  4% ` gorgelo
  1 sibling, 0 replies; 96+ results
From: gorgelo @ 2018-05-31 19:28 UTC (permalink / raw)


Here is an example of an unbounded storage pool that handles deallocations and is used for allocating 3 Integers inside it and then deallocating them:

with System.Storage_Elements;
with System.Storage_Pools;
with Ada.Text_IO;
with Ada.Integer_Text_IO;
with Ada.Containers.Vectors;
with Ada.Unchecked_Deallocation;

procedure Main is

   subtype Storage_Offset is System.Storage_Elements.Storage_Offset;
   subtype Storage_Count  is System.Storage_Elements.Storage_Count;
   subtype Storage_Array  is System.Storage_Elements.Storage_Array;

   subtype Root_Storage_Pool is System.Storage_Pools.Root_Storage_Pool;

   subtype Integer_Address is System.Storage_Elements.Integer_Address;

   use type Ada.Containers.Count_Type;
   use type Storage_Offset;
   use type Integer_Address;

   procedure Put (Text : String) renames Ada.Text_IO.Put;

   procedure Put_Line (Text : String) renames Ada.Text_IO.Put_Line;

   procedure Put_Line (I : Integer) is
   begin
      Ada.Integer_Text_IO.Put (I);
      Ada.Text_IO.New_Line;
   end Put_Line;

   procedure Put (I : Integer) is
   begin
      Ada.Integer_Text_IO.Put (I, 0);
   end Put;

   procedure Put (I : Storage_Offset) is
   begin
      Ada.Integer_Text_IO.Put (Integer (I), 0);
   end Put;

   function To_Integer (Value : System.Address) return Integer_Address
                        renames System.Storage_Elements.To_Integer;

   package Arena_Pools is

      type Arena (<>) is new Root_Storage_Pool with private;

      function Make return Arena;

      overriding
      procedure Allocate
        (  Pool      : in out Arena;
           Address   : out System.Address;
           Size      : Storage_Count;
           Alignment : Storage_Count
          );

      overriding
      procedure Deallocate
        (  Pool      : in out Arena;
           Address   : System.Address;
           Size      : Storage_Count;
           Alignment : Storage_Count
          );

      overriding
      function Storage_Size (Pool : Arena) return Storage_Count;
      -- Approximation of how many Storage Elements (bytes)
      -- have been heap-allocated.

   private

      Slot_Size : constant := 20;
      -- Specifies the size of each slot in Storage Elements (bytes)
      -- Must be big enough to store any object one wishes to allocate
      -- inside the memory pool.

      type Slot is record
         Elements : Storage_Array (1..Slot_Size);
      end record;

      MAX : constant := 200_000;
      -- Specifies the number of slots that will be allocated in an array
      -- from the heap every time more memory needs to be pre-allocated.

      subtype Slot_Index is Storage_Offset range 1..MAX;

      type Slots_Array is array (Slot_Index) of Slot;

      subtype Free_Index is Integer range 1..MAX;
      -- This Integer type (32-bits) is created in order to not use the type
      -- Storage_Offset (64-bits) in the free indices vector.

      package Indices_Vector is new Ada.Containers.Vectors
        (Index_Type   => Positive,
         Element_Type => Free_Index,
         "="          => "=");

      type Slots_Envelope is record
         Items        : Slots_Array;
         Free_Indices : Indices_Vector.Vector;
      end record;

      type Slots_Envelope_Ptr is access all Slots_Envelope;

      package Envelope_Vectors is new Ada.Containers.Vectors
        (Index_Type   => Positive,
         Element_Type => Slots_Envelope_Ptr,
         "="          => "=");

      type Arena is new Root_Storage_Pool with record
         Index : Positive := 1;
         -- Indicates which array of slots to first search for a free index

         Envelopes : Envelope_Vectors.Vector;
      end record;

      overriding
      procedure Finalize (This : in out Arena);
      -- Deallocates all allocated memory from the heap

   end Arena_Pools;

   package body Arena_Pools is

      function Make return Slots_Envelope_Ptr is
         Envelope : Slots_Envelope_Ptr := new Slots_Envelope;
      begin
         Envelope.Free_Indices.Reserve_Capacity (MAX);
         for I in Slot_Index'Range loop
            Envelope.Free_Indices.Append (Free_Index (I));
         end loop;

         return Envelope;
      end Make;

      function Make return Arena is
         Envelope : Slots_Envelope_Ptr := Make;
      begin
         return This : Arena do
            This.Envelopes.Append (Envelope);
         end return;
      end Make;

      function Determine_Index (Pool    : Arena;
                                Address : System.Address) return Positive is
         Searched_For : Natural := 0;
         First_Address : System.Address;
         Last_Address  : System.Address;
      begin
         for I in Pool.Envelopes.First_Index..Pool.Envelopes.Last_Index loop
            First_Address := Pool.Envelopes (I).Items (1)'Address;
            Last_Address  := Pool.Envelopes (I).Items (MAX)'Address;
            if
              To_Integer (First_Address) <= To_Integer (Address) and
              To_Integer (Address)       <= To_Integer (Last_Address)
            then
               Searched_For := I;
               exit;
            end if;
         end loop;

         if Searched_For = 0 then
            raise Storage_Error;
         end if;

         return Searched_For;
      end Determine_Index;

      procedure Allocate
        (Pool      : in out Arena;
         Address   : out System.Address;
         Size      : Storage_Count;
         Alignment : Storage_Count)
      is
         Id : Slot_Index;
      begin
         if Pool.Envelopes (Pool.Index).Free_Indices.Length > 0 then
            Id := Slot_Index (Pool.Envelopes (Pool.Index).Free_Indices.Last_Element);
            Pool.Envelopes (Pool.Index).Free_Indices.Delete_Last;
         else
            declare
               Has_Found : Boolean := False;
            begin
               for I in Pool.Envelopes.First_Index .. Pool.Envelopes.Last_Index loop
                  if Pool.Envelopes (I).Free_Indices.Length > 0 then
                     Pool.Index := I;
                     Id := Slot_Index (Pool.Envelopes (Pool.Index).Free_Indices.Last_Element);
                     Pool.Envelopes (Pool.Index).Free_Indices.Delete_Last;
                     Has_Found := True;
                     exit;
                  end if;
               end loop;

               if not Has_Found then
                  declare
                     E : Slots_Envelope_Ptr := Make;
                  begin
                     Pool.Envelopes.Append (E);
                     Pool.Index := Pool.Envelopes.Last_Index;
                     Id := Slot_Index (Pool.Envelopes (Pool.Index).Free_Indices.Last_Element);
                     Pool.Envelopes (Pool.Index).Free_Indices.Delete_Last;
                  end;
               end if;
            end;
         end if;

         Put ("Will allocate (array, slot) := (");
         Put (Pool.Index);
         Put (",");
         Put (Id);
         Put_Line (")");

         Address := Pool.Envelopes (Pool.Index).Items (Id).Elements'Address;
      end Allocate;

      procedure Deallocate (Pool      : in out Arena;
                            Address   : System.Address;
                            Size      : Storage_Count;
                            Alignment : Storage_Count)
      is
         I : constant Positive := Determine_Index (Pool, Address);

         First_Address : System.Address;
         Last_Address  : System.Address;

         Slot_Id : Slot_Index;

         D : Integer_Address;
      begin
         First_Address := Pool.Envelopes (I).Items (1)'Address;
         Last_Address  := Pool.Envelopes (I).Items (MAX)'Address;

         D := (To_Integer (Last_Address) - To_Integer (First_Address) + Slot_Size) / MAX;

         Slot_Id := Slot_Index ((To_Integer (Address) + Slot_Size - To_Integer (First_Address))/ D);

         Pool.Envelopes (I).Free_Indices.Append (Free_Index (Slot_Id));

         Put ("Deallocate (array, slot) := (");
         Put (I);
         Put (",");
         Put (Slot_Id);
         Put_Line (")");
      end Deallocate;

      function Storage_Size (Pool : Arena) return Storage_Count is
         Result : Storage_Count := 0;
      begin
         for Envelope of Pool.Envelopes loop
            Result := Slot_Size*MAX + Storage_Count (Envelope.Free_Indices.Capacity * 4);
         end loop;

         return Result;
      end Storage_Size;

      procedure Free is new Ada.Unchecked_Deallocation (Object => Slots_Envelope,
                                                        Name   => Slots_Envelope_Ptr);

      procedure Finalize (This : in out Arena) is
      begin
         for Envelope of This.Envelopes loop
            Free (Envelope);
         end loop;
         This.Envelopes.Clear;
         Put_Line ("Deallocated all heap-allocated memory");
      end Finalize;

   end Arena_Pools;

   Pool : Arena_Pools.Arena := Arena_Pools.Make;

   type Integer_Ptr is access Integer with
     Storage_Pool => Pool;

   procedure Free is new Ada.Unchecked_Deallocation (Object => Integer,
                                                     Name   => Integer_Ptr);

   X : Integer_Ptr := new Integer'(1);
   Y : Integer_Ptr := new Integer'(2);
   Z : Integer_Ptr := new Integer'(3);

begin
   Free (X);
   Free (Y);
   Free (Z);
   Put_Line ("Has allocated" & Pool.Storage_Size'Image & " bytes.");
end Main;

It has the following output:
Will allocate (array, slot) := (1,200000)
Will allocate (array, slot) := (1,199999)
Will allocate (array, slot) := (1,199998)
Deallocate (array, slot) := (1,200000)
Deallocate (array, slot) := (1,199999)
Deallocate (array, slot) := (1,199998)
Has allocated 4800000 bytes.
Deallocated all heap-allocated memory


The implementation is inspired from Rosetta stone Arena pools:
http://rosettacode.org/wiki/Arena_storage_pool#Ada

^ permalink raw reply	[relevance 5%]

* Re: two questions on allocators
  2018-02-23 22:30  5% ` Shark8
  2018-02-23 23:30  0%   ` Mehdi Saada
@ 2018-02-24 10:20  0%   ` AdaMagica
  1 sibling, 0 replies; 96+ results
From: AdaMagica @ 2018-02-24 10:20 UTC (permalink / raw)


Am Freitag, 23. Februar 2018 23:30:06 UTC+1 schrieb Shark8:
> The type of the allocator refers to a concrete instance of System.Storage_Pools.Root_Storage_Pool which can be associated with an access-type via pragma/aspect.

It has nothing to do with storage pools. It's a question of lifetime.

^ permalink raw reply	[relevance 0%]

* Re: two questions on allocators
  2018-02-23 22:30  5% ` Shark8
@ 2018-02-23 23:30  0%   ` Mehdi Saada
  2018-02-24 10:20  0%   ` AdaMagica
  1 sibling, 0 replies; 96+ results
From: Mehdi Saada @ 2018-02-23 23:30 UTC (permalink / raw)


> Finally, the phrase "new not null B" is in error, as you cannot say "new not null" in Ada.
Here's a simpler exemple ( I think I mixed up A and B, which made my statement meaningless):
type A is access INTEGER;
type B is access not null A;
Object_B : B := new A; --- **
allowed
type A is access INTEGER;
type B is access A;
Object_B : B := new not null A; -- illegal,
but wouldn't that be the same than * ?
Anyway, let's forget it.

> The type of the allocator refers to a concrete instance of System.Storage_Pools.Root_Storage_Pool
I remember... the pool, along with the data it contains shall not outlive its data's tag, makes sense.


^ permalink raw reply	[relevance 0%]

* Re: two questions on allocators
  @ 2018-02-23 22:30  5% ` Shark8
  2018-02-23 23:30  0%   ` Mehdi Saada
  2018-02-24 10:20  0%   ` AdaMagica
  0 siblings, 2 replies; 96+ results
From: Shark8 @ 2018-02-23 22:30 UTC (permalink / raw)


On Friday, February 23, 2018 at 1:42:14 PM UTC-7, Mehdi Saada wrote:
> 2.2/3: for an allocator with a subtype indication, the subtype indication shall not specify a null exclusion
> why 
> type A is access INTEGER;
> type B is access not null A; 
> type C is access B;
> Object_C : C := new B;
> is allowed, but not
> type A is access INTEGER;
> type B is access A; 
> type C is access B;
> Object_C : C := new not null B; ?? What's the difference ?

Lots.
In the first one, A is an access to an integer, B is an access to A (with null exclusion), and C is an access to B... so in C/C++ something like int*, int**, and int***, respectively.

The second is the same insofar as the C/C++ analog is concerned; but it's different in that B doesn't exclude Null.

Finally, the phrase "new not null B" is in error, as you cannot say "new not null" in Ada.


> If the designated type of the allocator is class-wide, the accessibility level of the type determined by the subtype_indication or qualified_expression shall not be statically deeper than that of the type of the allocator.
> 
> -> what means the last "type of the allocator" ? Is it the same than "designed type of the allocator" ?

The type of the allocator refers to a concrete instance of System.Storage_Pools.Root_Storage_Pool which can be associated with an access-type via pragma/aspect.

^ permalink raw reply	[relevance 5%]

* Re: Allocators design flaw
  2017-10-14 15:42  4%         ` Simon Wright
@ 2017-10-14 16:29  0%           ` Victor Porton
  0 siblings, 0 replies; 96+ results
From: Victor Porton @ 2017-10-14 16:29 UTC (permalink / raw)


Simon Wright wrote:

> Victor Porton <porton@narod.ru> writes:
> 
>> The Ada problem is that that _alloc_memory() cannot be integrated with
>> Ada allocators. The problem is that (in principle) Ada may request a
>> greater alignment than C ever has, and this way Ada allocators become
>> incompatible with C.
> 
> I just don't understand what the problem is.
> 
> If you declared an access type in Ada and invoked new, it's possible
> (really only in the context of the AI I referenced earlier) that the
> allocation might require an alignment greater than that required for the
> basic data. The AI's first example is
> 
>        type T is access String;
>        for T'Storage_Pool use ... ;
>        X : T := new String'("abc");

The trouble is as follows:

There is nothing in Ada standard to prevent the above "new" operator to 
request 256-byte alignment of the data. (Yes, I know this does not happen in 
practice, but it is not forbidden by the RM.)

If it requests such a great alignment by the C function *_alloc_memory() is 
able to do only 16-byte alignment, then my allocator would break the 
contract, that is allocate with lesser alignment than requested.

This could in principle lead to undefined behavior.

>     In the case of an access type whose designated subtype is an
>     unconstrained array subtype, some implementations prepend contiguous
>     dope information to the allocated array. String'Alignment is
>     typically 1. If the dope information contains values of the array
>     type's index type(s), then the alignment requirement of this dope
>     information might reasonably be that of the most strictly aligned
>     index type. The given example might be easier to implement if the
>     implementation were allowed to pass Integer'Alignment instead of
>     String'Alignment as the Alignment parameter in the call to Allocate
>     associated with the allocator.

The above quotation is unrelated.

> If you then called Unchecked_Deallocation, it would need to be aware of
> this extra dope information.

Again unrelated.

> But you don't propose to invoke new, which means that

Why? I do propose to invoke new.

> System.Storage_Pools.Allocate isn't going to be called. You're going to
> get C to allocate the memory as appropriate for whatever it contains,

What I want is to write Allocate in such a way that it could work calling 
the C allocating function.

> including any dope information, and if the Ada side gets to see its
> contents it will do so via appropriate representation clauses, which
> will explicitly include any dope information.
> 
> I agree that if the C side allocates the memory with an alignment that's
> incompatible with the contents of the struct then you'll have a problem,
> but I don't see how that could possibly be cured from the Ada side.

"C side" allocated memory compatible with every C struct. This is not the 
problem.

The problem that Ada may request a greater (a natural number of times) 
alignment and the C function cannot do what Ada requests.

-- 
Victor Porton - http://portonvictor.org

^ permalink raw reply	[relevance 0%]

* Re: Allocators design flaw
  @ 2017-10-14 15:42  4%         ` Simon Wright
  2017-10-14 16:29  0%           ` Victor Porton
  0 siblings, 1 reply; 96+ results
From: Simon Wright @ 2017-10-14 15:42 UTC (permalink / raw)


Victor Porton <porton@narod.ru> writes:

> The Ada problem is that that _alloc_memory() cannot be integrated with Ada 
> allocators. The problem is that (in principle) Ada may request a greater 
> alignment than C ever has, and this way Ada allocators become incompatible 
> with C.

I just don't understand what the problem is.

If you declared an access type in Ada and invoked new, it's possible
(really only in the context of the AI I referenced earlier) that the
allocation might require an alignment greater than that required for the
basic data. The AI's first example is

       type T is access String;
       for T'Storage_Pool use ... ;
       X : T := new String'("abc");

    In the case of an access type whose designated subtype is an
    unconstrained array subtype, some implementations prepend contiguous
    dope information to the allocated array. String'Alignment is
    typically 1. If the dope information contains values of the array
    type's index type(s), then the alignment requirement of this dope
    information might reasonably be that of the most strictly aligned
    index type. The given example might be easier to implement if the
    implementation were allowed to pass Integer'Alignment instead of
    String'Alignment as the Alignment parameter in the call to Allocate
    associated with the allocator.

If you then called Unchecked_Deallocation, it would need to be aware of
this extra dope information.

But you don't propose to invoke new, which means that
System.Storage_Pools.Allocate isn't going to be called. You're going to
get C to allocate the memory as appropriate for whatever it contains,
including any dope information, and if the Ada side gets to see its
contents it will do so via appropriate representation clauses, which
will explicitly include any dope information.

I agree that if the C side allocates the memory with an alignment that's
incompatible with the contents of the struct then you'll have a problem,
but I don't see how that could possibly be cured from the Ada side.

^ permalink raw reply	[relevance 4%]

* Re: Interest in standard smart pointers for Ada 2020
  @ 2017-09-01  9:05  5%   ` AdaMagica
  0 siblings, 0 replies; 96+ results
From: AdaMagica @ 2017-09-01  9:05 UTC (permalink / raw)


Am Donnerstag, 31. August 2017 17:17:12 UTC+2 schrieb Lucretia:
> I would add auto_ptr too, I've implemented one before, although I think Block_Pointer would be a better Ada name for it. Should be limited, initialised with extended return and frees the contents at the end of the block in which it was instantiated.

Sorry, I don't know much about C++.

But in Ada, you can add a size clause to an access type declaration. The whole thing is freed when the type goes out of scope.

Then there is System.Storage_Pools.

Isn't this what you request with an auto_ptr?


^ permalink raw reply	[relevance 5%]

* Re: T'Interface attribute
  2017-08-03  7:26  5%   ` Dmitry A. Kazakov
@ 2017-08-04 23:51  0%     ` Randy Brukardt
  0 siblings, 0 replies; 96+ results
From: Randy Brukardt @ 2017-08-04 23:51 UTC (permalink / raw)


"Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> wrote in message 
news:oluj7t$8uo$1@gioia.aioe.org...
> On 2017-08-03 06:46, Randy Brukardt wrote:
>> "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> wrote in message
>> news:olskua$1bfd$1@gioia.aioe.org...
>>> In order to reduce name space contamination I would propose attribute
>>> T'Interface which for any tagged type T would denote an interface type
>>> with all *new* primitive operations, e.g.
>>
>> Past experience say that such attributes (that is, those that designate 
>> some
>> sort of type or subtype) don't work out very well in Ada. For instance, 
>> we
>> considered T'Access in Ada 2005, but gave that up because of various
>> problems (and replaced with with anonymous access types, which are 
>> worse).
>> The worst problem was that there was no limit to the attribute, you could
>> write T'Access'Access'Access - and you can't prevent this since T could 
>> be a
>> generic formal type that itself is some T'Access.
>
> In this case generic would not be a problem because T must be tagged to 
> have T'Interface.
>
> As a side note, differently to 'Access, 'Length and actually 'Class, 
> 'Interface is idempotent:
>
>    T'Interface ::= T'Interface'Interface

Ada defines 'Class this way, too, I think in part to mitigate these 
problems.

The problem with formals is from the actual being T'Interface:

    generic
       type T is abstract tagged private;
    package Gen is
        procedure P (Item : in T'Interface);
    end Gen;

    package Inst is new Gen (Some_Tagged_Type'Interface);

The parameter of P is essentially Some_Tagged_Type'Interface'Interface.

>> Almost all Ada compilers materialize all Ada types in their symbol table, 
>> so
>> the effect of having a T'Interface would be that it would be 
>> automatically
>> declared for all tagged type declarations. Most Ada compilers also
>> materialize all of the primitive operations in their symbol table, so 
>> there
>> would be a large increase in memory usage and some time increase (all
>> lookups would have twice as many primitives to look through).
>
> This is an intended effect. Yes, there would likely be two tags for each 
> declared type.
>
> Which by the way will fix Ada.Streams and System.Storage_Pools design for 
> free. Since we will finally have:
>
>    Root_Stream_Type'Interface
>
> and
>
>    Root_Storage_Pool'Interface
>
> E.g.
>
>    type Serialized_Widget is
>       new Gtk_Widget_Record and Root_Stream_Type'Interface with private;

The problem with "fixing" Root_Stream_Type etc. is the "no hidden 
interfaces" rule. These types are often used in private derivations, and 
that is illegal for interfaces. (Attempts to weaken the "no hidden 
interfaces" rule have led to various definitional nightmares - it does not 
look likely. AI12-0023-1 discusses the latest attempts - it's still open but 
hasn't been discussed since Stockholm.)

That suggests a problem with this idea: effectivelly all types would have an 
associated interface. But interfaces can never be hidden (certainly not 
without restrictions as discussed in AI12-0023-1), so that would seem to 
imply that no hidden type derivations could occur. That would be a massive 
compatibility problem.

>> P.S. And as always, explain the problem to be solved as well as the 
>> possible
>> solution. That is always necessary to understand the value of a proposal.
>
> I have a design rule to have an explicit interface declared for each 
> tagged type. It saves much of redesign later.

I've generally materialized that as "the root of an abstraction should 
always be declared abstract".

>> P.P.S. I personally have never seen a real-world example where an 
>> interface
>> actually helps. There's lots and lots of book examples and show examples 
>> and
>> so on, but in practice you end up with only a single implementation so 
>> there
>> really is nothing gained by involving a lot of dispatching calls. Ergo, 
>> I'm
>> against anything (new) involving interfaces. YMMV.
>
> I have no idea how you manage keep Claw out of interfaces, really. 
> Multiple inheritance is a huge help and relief. I am using interfaces 
> extensively unless backward Ada 95 compatibility hinders me. E.g. in AICWL 
> all widget layers implement interfaces like Scalable_Layer, Gauge_Needle, 
> Waveform_Amplifier etc. It would not work otherwise.

In Claw, the only places that we got much benefit from OOP (beyond 
dispatching callbacks, the reason we used OOP in the first place) was in 
sharing implementations across related types. But that doesn't work for Ada 
interfaces, because you can't have any components in the type -- meaning 
that writing real implementations is impossible. One can use abstract types 
in this way (and we did so extensively).

We didn't find much use for dispatching (outside of the callbacks as 
previously mentioned; those only need to work on root types since they come 
directly from the message loop engine). If you don't need (or can use) 
dispatching, and since you can't use implementation inheritance, the use of 
interfaces buys nothing.

(Of course, we didn't have interfaces when Claw was designed, so it wasn't 
even an option. Perhaps we'd have done something differently had they been 
available -- but I doubt it.)

That pattern has persisted in pretty much all of my recent programs; I don't 
usually have very deep hierarchies and dispatching is limited to the root 
types (which I declare abstract for maximum sharing).

I realize other people end up with other patterns, but I'm not going to 
champion something I don't find useful. (I doubt I could do a good job of 
championing it anyway).

                                       Randy.



^ permalink raw reply	[relevance 0%]

* Re: T'Interface attribute
  @ 2017-08-03  7:26  5%   ` Dmitry A. Kazakov
  2017-08-04 23:51  0%     ` Randy Brukardt
  0 siblings, 1 reply; 96+ results
From: Dmitry A. Kazakov @ 2017-08-03  7:26 UTC (permalink / raw)


On 2017-08-03 06:46, Randy Brukardt wrote:
> "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> wrote in message
> news:olskua$1bfd$1@gioia.aioe.org...
>> In order to reduce name space contamination I would propose attribute
>> T'Interface which for any tagged type T would denote an interface type
>> with all *new* primitive operations, e.g.
> 
> Past experience say that such attributes (that is, those that designate some
> sort of type or subtype) don't work out very well in Ada. For instance, we
> considered T'Access in Ada 2005, but gave that up because of various
> problems (and replaced with with anonymous access types, which are worse).
> The worst problem was that there was no limit to the attribute, you could
> write T'Access'Access'Access - and you can't prevent this since T could be a
> generic formal type that itself is some T'Access.

In this case generic would not be a problem because T must be tagged to 
have T'Interface.

As a side note, differently to 'Access, 'Length and actually 'Class, 
'Interface is idempotent:

    T'Interface ::= T'Interface'Interface

> Almost all Ada compilers materialize all Ada types in their symbol table, so
> the effect of having a T'Interface would be that it would be automatically
> declared for all tagged type declarations. Most Ada compilers also
> materialize all of the primitive operations in their symbol table, so there
> would be a large increase in memory usage and some time increase (all
> lookups would have twice as many primitives to look through).

This is an intended effect. Yes, there would likely be two tags for each 
declared type.

Which by the way will fix Ada.Streams and System.Storage_Pools design 
for free. Since we will finally have:

    Root_Stream_Type'Interface

and

    Root_Storage_Pool'Interface

E.g.

    type Serialized_Widget is
       new Gtk_Widget_Record and Root_Stream_Type'Interface with private;

> P.S. And as always, explain the problem to be solved as well as the possible
> solution. That is always necessary to understand the value of a proposal.

I have a design rule to have an explicit interface declared for each 
tagged type. It saves much of redesign later.

> P.P.S. I personally have never seen a real-world example where an interface
> actually helps. There's lots and lots of book examples and show examples and
> so on, but in practice you end up with only a single implementation so there
> really is nothing gained by involving a lot of dispatching calls. Ergo, I'm
> against anything (new) involving interfaces. YMMV.

I have no idea how you manage keep Claw out of interfaces, really. 
Multiple inheritance is a huge help and relief. I am using interfaces 
extensively unless backward Ada 95 compatibility hinders me. E.g. in 
AICWL all widget layers implement interfaces like Scalable_Layer, 
Gauge_Needle, Waveform_Amplifier etc. It would not work otherwise.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de


^ permalink raw reply	[relevance 5%]

* Re: Is there a reason System.Storage_Pools isn't Pure?
  2017-04-22  5:02  8%         ` Randy Brukardt
@ 2017-04-22 17:18  8%           ` Shark8
  0 siblings, 0 replies; 96+ results
From: Shark8 @ 2017-04-22 17:18 UTC (permalink / raw)


On Friday, April 21, 2017 at 11:02:52 PM UTC-6, Randy Brukardt wrote:
> "Shark8" wrote in message 
> news:a498c0f6-11ae-4050-ade0-bc35c686dc1c...
> > On Wednesday, April 19, 2017 at 2:36:28 PM UTC-6, Randy Brukardt wrote:
> >>
> >> Your spec here doesn't have any way to put an element into the holder. 
> >> And
> >> that's where the trouble comes (especially for limited types!). Perhaps 
> >> you
> >> can figure it out (I haven't been able to). As it stands, your holder
> >> objects would have to have Has_Element = False. Not very useful. ;-)
> >
> > I should have known better than to type it on-the-fly.
> > Here's a different spec that actually does compile under GNAT, even though 
> > [AFACT] it shouldn't:
> 
> Right; it contains an assignment of a limited private type, which is, ummm, 
> surprising. :-)

For Replace_Element?
There's no assignment of a limited private type there, it's an assignment replacing the whole parameter "container", which is in this case an access type.
(Or do you mean in To_Holder?)

> 
> You probably could use a constructor allocator to do that in limited (pun 
> not intended) cases, but that would be a new object which couldn't exist 
> outside of the container. Might be useful in some cases...

Sounds like a good way to (e.g.) bind a value to a particular storage [sub]pool, IIUC.

^ permalink raw reply	[relevance 8%]

* Re: Is there a reason System.Storage_Pools isn't Pure?
  2017-04-20  0:12 12%       ` Shark8
@ 2017-04-22  5:02  8%         ` Randy Brukardt
  2017-04-22 17:18  8%           ` Shark8
  0 siblings, 1 reply; 96+ results
From: Randy Brukardt @ 2017-04-22  5:02 UTC (permalink / raw)


"Shark8" <onewingedshark@gmail.com> wrote in message 
news:a498c0f6-11ae-4050-ade0-bc35c686dc1c@googlegroups.com...
> On Wednesday, April 19, 2017 at 2:36:28 PM UTC-6, Randy Brukardt wrote:
>>
>> Your spec here doesn't have any way to put an element into the holder. 
>> And
>> that's where the trouble comes (especially for limited types!). Perhaps 
>> you
>> can figure it out (I haven't been able to). As it stands, your holder
>> objects would have to have Has_Element = False. Not very useful. ;-)
>
> I should have known better than to type it on-the-fly.
> Here's a different spec that actually does compile under GNAT, even though 
> [AFACT] it shouldn't:

Right; it contains an assignment of a limited private type, which is, ummm, 
surprising. :-)

You probably could use a constructor allocator to do that in limited (pun 
not intended) cases, but that would be a new object which couldn't exist 
outside of the container. Might be useful in some cases...

                       Randy.



^ permalink raw reply	[relevance 8%]

* Re: Is there a reason System.Storage_Pools isn't Pure?
  2017-04-19 20:36  8%     ` Randy Brukardt
@ 2017-04-20  0:12 12%       ` Shark8
  2017-04-22  5:02  8%         ` Randy Brukardt
  0 siblings, 1 reply; 96+ results
From: Shark8 @ 2017-04-20  0:12 UTC (permalink / raw)


On Wednesday, April 19, 2017 at 2:36:28 PM UTC-6, Randy Brukardt wrote:
> 
> Your spec here doesn't have any way to put an element into the holder. And 
> that's where the trouble comes (especially for limited types!). Perhaps you 
> can figure it out (I haven't been able to). As it stands, your holder 
> objects would have to have Has_Element = False. Not very useful. ;-)
> 
>                               Randy.

I should have known better than to type it on-the-fly.
Here's a different spec that actually does compile under GNAT, even though [AFACT] it shouldn't:

Pragma Ada_2012;
Pragma Assertion_Policy( Check );
Pragma SPARK_Mode( On );

Generic
    Type Element_Type(<>) is limited private;
Package Forth.Pure_Types.Pure_Holders with Pure, SPARK_Mode => On is
    Pragma Pure(Forth.Pure_Types.Pure_Holders);

    Type Holder is private;

    Function Has_Element (Container : Holder) return Boolean
      with Inline;

    Procedure Clear (Container : in out Holder)
      with Inline;

    Function Element (Container : Holder) return Element_Type
      with Inline,
	Pre     => Has_Element(Container)
		   or else raise Constraint_Error with "Container is empty.";

    Function To_Holder (Item : Element_Type) return Holder
      with Inline,
	Post    => Has_Element(To_Holder'Result);

    Procedure Replace_Element(Container : in out Holder; Item : Element_Type)
      with Inline;


Private
--      Pragma SPARK_Mode( OFF );

    Type Holder is access all Element_Type;
--      with Storage_Size => 0;

End Forth.Pure_Types.Pure_Holders;

---------------------------------------------------------------

Pragma Ada_2012;
Pragma Assertion_Policy( Check );

Package Body Forth.Pure_Types.Pure_Holders is

    Function Has_Element (Container : Holder) return Boolean is
      (Container /= Null);

    Procedure Clear (Container : in out Holder) is
	Procedure Unchecked_Deallocation(X : in out Holder)
	  with Import, Convention => Intrinsic;
    Begin
	Unchecked_Deallocation( Container );
    End Clear;

    Function Element (Container : Holder) return Element_Type is
      ( Container.All );

    Function To_Holder (Item : Element_Type) return Holder is
      ( New Element_Type'(Item) );

    Procedure Replace_Element(Container : in out Holder; Item : Element_Type) is
    Begin
	Clear( Container );
	Container:= To_Holder( Item );
    End Replace_Element;

End Forth.Pure_Types.Pure_Holders;

--------------

I've already got a Pure version of Storage_Pools (and Subpools) compiling too. (!) -- Of course I can't use an instance of them in a pure unit



----------------

Pragma Ada_2012;
Pragma Assertion_Policy( Check );

With
System.Storage_Pools;

Generic
    Type K(<>) is limited private;
    Pool : in out System.Storage_Pools.Root_Storage_Pool'Class;
Package Pool_Test with Pure is
    
    Type J is access all K
      with Storage_Pool => Pool;
    
End Pool_Test;


^ permalink raw reply	[relevance 12%]

* Re: Is there a reason System.Storage_Pools isn't Pure?
  2017-04-19  7:37  7%     ` Dmitry A. Kazakov
  2017-04-19 18:50  6%       ` Shark8
@ 2017-04-19 20:42  7%       ` Randy Brukardt
  1 sibling, 0 replies; 96+ results
From: Randy Brukardt @ 2017-04-19 20:42 UTC (permalink / raw)


"Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> wrote in message 
news:od743q$p4n$1@gioia.aioe.org...
...
> A lot of use cases conflated into single pragma Pure:
>
> 1. Value/object identity
> 2. Elaboration
> 3. Early evaluation (e.g. compile time, elaboration time)
>
> It must be reworked from the start, IMO.

More like abandoned. Our current thinking is to essentially replace it by 
specifications of the Global aspect (which is stricter, so the result can be 
usefully used in parallelism applications) and finer grained (so individual 
subprograms can each have appropriate settings, no more "everything in the 
package has to be the same").

That would leave the only real purposes of Pure to be distribution and 
elaboration; the former uses don't want access types at all, and the latter 
can be handled just using Preelaborate does the job. (Ergo: most of what was 
done to Pure in Ada 2005 was a mistake, an attempt to fix the muddled mess 
resulting in a bigger muddled mess.)

                                       Randy.



^ permalink raw reply	[relevance 7%]

* Re: Is there a reason System.Storage_Pools isn't Pure?
  2017-04-18 23:42  6%   ` Shark8
  2017-04-19  7:37  7%     ` Dmitry A. Kazakov
@ 2017-04-19 20:36  8%     ` Randy Brukardt
  2017-04-20  0:12 12%       ` Shark8
  1 sibling, 1 reply; 96+ results
From: Randy Brukardt @ 2017-04-19 20:36 UTC (permalink / raw)


"Shark8" <onewingedshark@gmail.com> wrote in message 
news:61e151c1-9fe6-4d32-8f13-d425bc41a616@googlegroups.com...
...
> What about a usable-for-anything holder? (In particular, I think that 
> Ada.Containers.Indefinite_Holders ought to be less restrictive than they 
> are.) We could have a Pure Indefinite_Holder with:
>
>    Generic
>      Type Element_Type(<>) is limited private;
>      -- Pure storage-pool as a parameter? a dependency?
>    Package Example with Pure, Spark_Mode => On is
>      Type Holder is private;
>      Function Has_Element( Container : Holder ) return Boolean;
>      Function Element( Container : Holder ) return Element_Type
>        with Pre => Has_Element( Container );
>      Procedure Clear( Container : in out Holder )
>        with Post => not Has_Element( Container );
>    Private
>      Pragma SPARK_Mode( Off );
>
>      Type is access Element_Type
>        with Storage_Size => 0; -- Pure pool storage to allow non-zero?
>
>      Function Has_Element( Container : Holder ) return Boolean is
>        (Container /= Null);
>      Function Has_Element( Container : Holder ) return Boolean is
>        (Container.All);
>    End Example;
>
> Or am I misunderstanding?

Your spec here doesn't have any way to put an element into the holder. And 
that's where the trouble comes (especially for limited types!). Perhaps you 
can figure it out (I haven't been able to). As it stands, your holder 
objects would have to have Has_Element = False. Not very useful. ;-)

                              Randy.
 


^ permalink raw reply	[relevance 8%]

* Re: Is there a reason System.Storage_Pools isn't Pure?
  2017-04-19 18:50  6%       ` Shark8
@ 2017-04-19 19:48  6%         ` Dmitry A. Kazakov
  0 siblings, 0 replies; 96+ results
From: Dmitry A. Kazakov @ 2017-04-19 19:48 UTC (permalink / raw)


On 2017-04-19 20:50, Shark8 wrote:
> On Wednesday, April 19, 2017 at 1:37:33 AM UTC-6, Dmitry A. Kazakov wrote:

>> No, so long you don't know what is in the memory. Even considering the
>> case of a shared [distributed] memory pool it cannot be pure.
>
> But of course you know what's in that memory: you put it there.
> [Well,  the compiler; and since accesses are typed of course we know what they
> are.] -- And a pool[-type] obviously can be pure, as it is only a
> definition, an interface, if you will.

OK, theoretically a pool type can be static. But instances cannot be, so 
it is not much use anyway.

>> E.g.
>> initialization of an object in the shared memory must be done only once,
>> which does not preclude binding of each shared copy/view, like mapping
>> pointers since copies may be located in different virtual address spaces.
>
> Huh?
> While 'pointer' and 'access' are forms of indirection, and
> conceptually the same an access is safer as there is no untyped access.
> Further, if we use the de facto standard that pointers are an integer
> (thanks C [/sarc]) then we can recognize that an access needn't be so
> restricted. Indeed there are cases where it *MUST* be more than an
> integer, like the case of an access to the value of an unconstrained
> array-type,as we *MUST* have the bounds.

I meant that you must relocate access types pointing inside the 
shared/distributed memory. It is no different to load-time relocation of 
shared libraries.

>>> What about a usable-for-anything holder?
>>
>> Huh, what about fixing initialization/fixed in the first place. We would
>> not need kludges like holders if any type could have proper constructor
>> and destructor, access types included.
>
> Perhaps, though maybe you should explain what a proper
> constructor/destructor is -- as I'm pretty sure that C++ style *isn't*
> what you have in mind.

In fact I do. C++ has constructors almost right. Ada has nothing but an 
ugly Ada.Finalization hack.

A user-defined constructor is an anonymous subroutine hooked at a 
definite stage of object's initialization. It cannot be called 
explicitly. It cannot be overridden. It is not a primitive operation. It 
can be safely rolled back on exception propagation.

> 1. Value/object identity? I'm not sure where you're getting that
> from., could you elaborate/explain?

There are things with and without identity. E.g. integer value has no 
identity. A task type value has. Stateful objects you refer below 
require identity, obviously. In "X has state S" X is the identity.

> 3. This is true; it would be nice to have a clear compile-time and
> elaboration-time distinction.
>
>> It must be reworked from the start, IMO.
>
> Perhaps, though it does quite well in enforcing a lack of state upon
> the compilation-unit; taken in that manner Pure does a good job as an
> indicator.

You mean immutability. Consider a generic unit parametrized by a 
constant value declaring things dependent on the constant. It has 
instances in different states which are pure (not in Ada sense AFAIK) 
but in the sense of being immutable.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de


^ permalink raw reply	[relevance 6%]

* Re: Is there a reason System.Storage_Pools isn't Pure?
  2017-04-19  7:37  7%     ` Dmitry A. Kazakov
@ 2017-04-19 18:50  6%       ` Shark8
  2017-04-19 19:48  6%         ` Dmitry A. Kazakov
  2017-04-19 20:42  7%       ` Randy Brukardt
  1 sibling, 1 reply; 96+ results
From: Shark8 @ 2017-04-19 18:50 UTC (permalink / raw)


On Wednesday, April 19, 2017 at 1:37:33 AM UTC-6, Dmitry A. Kazakov wrote:
> On 19/04/2017 01:42, Shark8 wrote:
> > On Tuesday, April 18, 2017 at 12:32:34 PM UTC-6, Randy Brukardt wrote:
> >> Originally, it was not Pure because it was a child of System, which was not
> >> Pure. So I can't find any discussion of the merits.
> >>
> >> However, Pure packages are automatically Remote_Types packages (that is,
> >> values of the type can be transmitted between partitions). We'd never want
> >> that to be the case with a storage pool, so there doesn't seem to be any
> >> point in it being Pure.
> >
> > Are we sure we'd never want that?
> > I imagine that would be an interesting way to do VMs -- essentially
> > transmitting the [contained] memory directly between partitions, right?
> 
> No, so long you don't know what is in the memory. Even considering the 
> case of a shared [distributed] memory pool it cannot be pure.

But of course you know what's in that memory: you put it there. [Well, the compiler; and since accesses are typed of course we know what they are.] -- And a pool[-type] obviously can be pure, as it is only a definition, an interface, if you will.

> E.g. 
> initialization of an object in the shared memory must be done only once, 
> which does not preclude binding of each shared copy/view, like mapping 
> pointers since copies may be located in different virtual address spaces.

Huh?
While 'pointer' and 'access' are forms of indirection, and conceptually the same an access is safer as there is no untyped access. Further, if we use the de facto standard that pointers are an integer (thanks C [/sarc]) then we can recognize that an access needn't be so restricted. Indeed there are cases where it *MUST* be more than an integer, like the case of an access to the value of an unconstrained array-type,as we *MUST* have the bounds.


> > What about a usable-for-anything holder?
> 
> Huh, what about fixing initialization/fixed in the first place. We would 
> not need kludges like holders if any type could have proper constructor 
> and destructor, access types included.

Perhaps, though maybe you should explain what a proper constructor/destructor is -- as I'm pretty sure that C++ style *isn't* what you have in mind.

> >> IMHO, Pure packages are too restricted to be useful (and not restricted
> >> enough to be useful when synchronization is involved); it makes sense for
> >> individual subprograms but not for an entire package. So I recommend only
> >> trying to make packages Preelaborated. (That's especially true in Ada 2012,
> >> where limited I/O is possible.) [Distribution might change this thinking;
> >> I'm only considering stand-alone programs that don't use Annex E.]
> >
> > That's probably truer than I'd like -- but I guess the question was
> > borne out of playing around w/ pure units and seeing how far I could
> > push the style-guide's instruction "Use pragma Pure where allowed."
> 
> A lot of use cases conflated into single pragma Pure:
> 
> 1. Value/object identity
> 2. Elaboration
> 3. Early evaluation (e.g. compile time, elaboration time)

1. Value/object identity? I'm not sure where you're getting that from., could you elaborate/explain?

3. This is true; it would be nice to have a clear compile-time and elaboration-time distinction.

> It must be reworked from the start, IMO.

Perhaps, though it does quite well in enforcing a lack of state upon the compilation-unit; taken in that manner Pure does a good job as an indicator.


^ permalink raw reply	[relevance 6%]

* Re: Is there a reason System.Storage_Pools isn't Pure?
  2017-04-18 23:42  6%   ` Shark8
@ 2017-04-19  7:37  7%     ` Dmitry A. Kazakov
  2017-04-19 18:50  6%       ` Shark8
  2017-04-19 20:42  7%       ` Randy Brukardt
  2017-04-19 20:36  8%     ` Randy Brukardt
  1 sibling, 2 replies; 96+ results
From: Dmitry A. Kazakov @ 2017-04-19  7:37 UTC (permalink / raw)


On 19/04/2017 01:42, Shark8 wrote:
> On Tuesday, April 18, 2017 at 12:32:34 PM UTC-6, Randy Brukardt wrote:
>> Originally, it was not Pure because it was a child of System, which was not
>> Pure. So I can't find any discussion of the merits.
>>
>> However, Pure packages are automatically Remote_Types packages (that is,
>> values of the type can be transmitted between partitions). We'd never want
>> that to be the case with a storage pool, so there doesn't seem to be any
>> point in it being Pure.
>
> Are we sure we'd never want that?
> I imagine that would be an interesting way to do VMs -- essentially
> transmitting the [contained] memory directly between partitions, right?

No, so long you don't know what is in the memory. Even considering the 
case of a shared [distributed] memory pool it cannot be pure. E.g. 
initialization of an object in the shared memory must be done only once, 
which does not preclude binding of each shared copy/view, like mapping 
pointers since copies may be located in different virtual address spaces.

> What about a usable-for-anything holder?

Huh, what about fixing initialization/fixed in the first place. We would 
not need kludges like holders if any type could have proper constructor 
and destructor, access types included.

>> IMHO, Pure packages are too restricted to be useful (and not restricted
>> enough to be useful when synchronization is involved); it makes sense for
>> individual subprograms but not for an entire package. So I recommend only
>> trying to make packages Preelaborated. (That's especially true in Ada 2012,
>> where limited I/O is possible.) [Distribution might change this thinking;
>> I'm only considering stand-alone programs that don't use Annex E.]
>
> That's probably truer than I'd like -- but I guess the question was
> borne out of playing around w/ pure units and seeing how far I could
> push the style-guide's instruction "Use pragma Pure where allowed."

A lot of use cases conflated into single pragma Pure:

1. Value/object identity
2. Elaboration
3. Early evaluation (e.g. compile time, elaboration time)

It must be reworked from the start, IMO.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de

^ permalink raw reply	[relevance 7%]

* Re: Is there a reason System.Storage_Pools isn't Pure?
  2017-04-18 18:32  6% ` Randy Brukardt
@ 2017-04-18 23:42  6%   ` Shark8
  2017-04-19  7:37  7%     ` Dmitry A. Kazakov
  2017-04-19 20:36  8%     ` Randy Brukardt
  0 siblings, 2 replies; 96+ results
From: Shark8 @ 2017-04-18 23:42 UTC (permalink / raw)


On Tuesday, April 18, 2017 at 12:32:34 PM UTC-6, Randy Brukardt wrote:
> Originally, it was not Pure because it was a child of System, which was not 
> Pure. So I can't find any discussion of the merits.
> 
> However, Pure packages are automatically Remote_Types packages (that is, 
> values of the type can be transmitted between partitions). We'd never want 
> that to be the case with a storage pool, so there doesn't seem to be any 
> point in it being Pure.

Are we sure we'd never want that?
I imagine that would be an interesting way to do VMs -- essentially transmitting the [contained] memory directly between partitions, right? -- so we could essentially solve the problems plaguing JavaScript/backend development (in theory) with this, right?


> Additionally, the Pure package rules assume that no storage pools can be 
> specified for access types (because there aren't rules banning that at 
> library-level, and there need to be such rules to prevent hidden state). 
> That could be changed, I suppose, but given that a Pure storage pool could 
> only be used for a local access type in a Pure package(something that mainly 
> exists in ACATS tests), it would be close to useless (or get used for 
> back-door state). Note that state has to be strictly prohibited as Pure 
> packages are replicated when used in a distributed system (thus each 
> partition would have different state, which wouldn't make sense).

What about a usable-for-anything holder? (In particular, I think that Ada.Containers.Indefinite_Holders ought to be less restrictive than they are.) We could have a Pure Indefinite_Holder with:

    Generic
      Type Element_Type(<>) is limited private;
      -- Pure storage-pool as a parameter? a dependency?
    Package Example with Pure, Spark_Mode => On is
      Type Holder is private;
      Function Has_Element( Container : Holder ) return Boolean;
      Function Element( Container : Holder ) return Element_Type
        with Pre => Has_Element( Container );
      Procedure Clear( Container : in out Holder )
        with Post => not Has_Element( Container );
    Private
      Pragma SPARK_Mode( Off );
      
      Type is access Element_Type
        with Storage_Size => 0; -- Pure pool storage to allow non-zero?
      
      Function Has_Element( Container : Holder ) return Boolean is
        (Container /= Null);
      Function Has_Element( Container : Holder ) return Boolean is
        (Container.All);
    End Example;

Or am I misunderstanding?

> IMHO, Pure packages are too restricted to be useful (and not restricted 
> enough to be useful when synchronization is involved); it makes sense for 
> individual subprograms but not for an entire package. So I recommend only 
> trying to make packages Preelaborated. (That's especially true in Ada 2012, 
> where limited I/O is possible.) [Distribution might change this thinking; 
> I'm only considering stand-alone programs that don't use Annex E.]

That's probably truer than I'd like -- but I guess the question was borne out of playing around w/ pure units and seeing how far I could push the style-guide's instruction "Use pragma Pure where allowed."
( https://en.wikibooks.org/wiki/Ada_Style_Guide/Print_version#Pragma_Pure )


^ permalink raw reply	[relevance 6%]

* Re: Is there a reason System.Storage_Pools isn't Pure?
  2017-04-18  6:31 14% Is there a reason System.Storage_Pools isn't Pure? Shark8
@ 2017-04-18 18:32  6% ` Randy Brukardt
  2017-04-18 23:42  6%   ` Shark8
  0 siblings, 1 reply; 96+ results
From: Randy Brukardt @ 2017-04-18 18:32 UTC (permalink / raw)


Originally, it was not Pure because it was a child of System, which was not 
Pure. So I can't find any discussion of the merits.

However, Pure packages are automatically Remote_Types packages (that is, 
values of the type can be transmitted between partitions). We'd never want 
that to be the case with a storage pool, so there doesn't seem to be any 
point in it being Pure.

Additionally, the Pure package rules assume that no storage pools can be 
specified for access types (because there aren't rules banning that at 
library-level, and there need to be such rules to prevent hidden state). 
That could be changed, I suppose, but given that a Pure storage pool could 
only be used for a local access type in a Pure package(something that mainly 
exists in ACATS tests), it would be close to useless (or get used for 
back-door state). Note that state has to be strictly prohibited as Pure 
packages are replicated when used in a distributed system (thus each 
partition would have different state, which wouldn't make sense).

IMHO, Pure packages are too restricted to be useful (and not restricted 
enough to be useful when synchronization is involved); it makes sense for 
individual subprograms but not for an entire package. So I recommend only 
trying to make packages Preelaborated. (That's especially true in Ada 2012, 
where limited I/O is possible.) [Distribution might change this thinking; 
I'm only considering stand-alone programs that don't use Annex E.]

                                  Randy.

"Shark8" <onewingedshark@gmail.com> wrote in message 
news:178b6fbc-229b-49fc-8ffb-a5797bfc335f@googlegroups.com...
> Looking at the specification for System.Storage_Pools [RM 13.11(5)] there 
> doesn't seem to be anything that requires the Preelaborate pragma... is 
> there any real reason that it wasn't made a Pure unit? 



^ permalink raw reply	[relevance 6%]

* Is there a reason System.Storage_Pools isn't Pure?
@ 2017-04-18  6:31 14% Shark8
  2017-04-18 18:32  6% ` Randy Brukardt
  0 siblings, 1 reply; 96+ results
From: Shark8 @ 2017-04-18  6:31 UTC (permalink / raw)


Looking at the specification for System.Storage_Pools [RM 13.11(5)] there doesn't seem to be anything that requires the Preelaborate pragma... is there any real reason that it wasn't made a Pure unit?


^ permalink raw reply	[relevance 14%]

* ANN: Deepend 3.4 Storage Pools
@ 2014-09-08  1:27  4% Brad Moore
  0 siblings, 0 replies; 96+ results
From: Brad Moore @ 2014-09-08  1:27 UTC (permalink / raw)


I am pleased to announce the availability of Deepend version 3.4.

Deepend is a suite of dynamic storage pools with subpool capabilities
for Ada 95, Ada 2005, and Ada 2012.
Bounded and unbounded storage pools types are provided.
Storage pools with subpool capabilities allow all objects in a subpool
to be reclaimed all at once, instead of requiring each object to be
individually reclaimed one at a time. Deepend storage pools provides a 
more efficient and safer scheme for storage management than relying on
the standard storage pool, and user calls to Unchecked_Deallocation.
In fact, Deepend can eliminate the need for Unchecked_Deallocations.
A Dynamic Pool may have any number of subpools.

Deepend can be downloaded from;
     https://sourceforge.net/projects/deepend/files/

Differences since last release include;

This is technically the first version of Deepend that compiles for Ada 
2012 and the GNAT GPL 2014 version of the compiler. In particular,

- The Pool parameter of the
   System.Storage_Pools.Subpools.Default_Subpool_For_Pool function was
   finalized to be an in out parameter for the Ada 2012 standard.
   This requires changes to the Deepend pools, since they override this
   function. In addition, the Ada 2005 and Ada 95 versions of Deepend
   also were modified to reflect this change. In Ada 95 and Ada 2005,
   functions cannot have in out parameters, so instead, the parameters
   were changed to be access parameters, so that the Ada 95 and Ada 2005
   version more closely matches the Ada 2012 version.
- In the Ada 2012 version, there were static_predicates defined for
   private declarations, which in fact needed to be dynamic_predicates.
   Since these were private declarations, the predicates were removed,
   since they weren't very useful since they were private declarations,
   and the need for dynamic checks for this was deemed as worthwhile.
- Removed workarounds for GNAT compiler bugs that were fixed in the
   GNAT GPL 2014 version of the compiler. In particular, the storage
   pools have default discriminants which now can be left unspecified
   to use the defaults.

Regards,
    Brad Moore


















^ permalink raw reply	[relevance 4%]

* Re: A simple question about the "new" allocator
  @ 2014-08-12 13:38  7%   ` G.B.
  0 siblings, 0 replies; 96+ results
From: G.B. @ 2014-08-12 13:38 UTC (permalink / raw)


On 12.08.14 09:35, Dmitry A. Kazakov wrote:
> On Mon, 11 Aug 2014 23:54:50 -0700 (PDT), NiGHTS wrote:
>
>> With all default configurations using a typical Ada compiler, will the following code run indefinitely without fail or will it eventually crash?
>>
>> procedure main is
>>
>>      Test : access Positive;
>>
>> begin
>>
>>      loop
>>          Test := new Positive;
>>      end loop;
>>
>> end main;
>>
>> If this does crash, what would be another way to write this program so
>> that it does not crash?
>>
>> I would prefer not to use Ada.Unchecked_Deallocation.
>
> Write a custom memory pool that does not allocate anything. Make Test a
> pointer to that pool.
>
> P.S. It might sound silly, but such pools are actually useful. When the
> object is already allocated and you want to initialize it and get a pointer
> to, one way to do that is using a fake allocator.

One such storage pool, tailored to the problem, and therefore likely
not applicable to every problem:

with System.Storage_Pools;
with System.Storage_Elements;

generic
    type T is private;
package My_Switching_Pool is

    pragma Preelaborate (My_Switching_Pool);

    use System;

    type Alternating_Pool
      is new Storage_Pools.Root_Storage_Pool with private;
    --  Provides storage for exactly two items of formal type `T`.

    overriding
    procedure Allocate
      (Pool                     : in out Alternating_Pool;
       Storage_Address          :    out Address;
       Size_In_Storage_Elements : in     Storage_Elements.Storage_Count;
       Alignment                : in     Storage_Elements.Storage_Count);
    --  makes the other of the two items available for storage

    overriding
    procedure Deallocate
      (Pool                     : in out Alternating_Pool;
       Storage_Address          : in     Address;
       Size_In_Storage_Elements : in     Storage_Elements.Storage_Count;
       Alignment                : in     Storage_Elements.Storage_Count);

    overriding
    function Storage_Size
      (Pool : Alternating_Pool) return Storage_Elements.Storage_Count;

private
    type Names is (Fst, Snd);
    type Pair is array (Names) of T;

    type Alternating_Pool
      is new Storage_Pools.Root_Storage_Pool with
       record
          In_Use : Names := Snd;
       end record;

    The_Data : Pair;

end My_Switching_Pool;

package body My_Switching_Pool is

    overriding
    procedure Allocate
      (Pool                     : in out Alternating_Pool;
       Storage_Address          :    out Address;
       Size_In_Storage_Elements : in     Storage_Elements.Storage_Count;
       Alignment                : in     Storage_Elements.Storage_Count)
    is
    begin
       -- switch components of `The_Data`
       Pool.In_Use := (if Pool.In_Use = Fst
                       then Snd
                       else Fst);
       Storage_Address := The_Data (Pool.In_Use)'Address;
    end Allocate;

    overriding
    procedure Deallocate
      (Pool                     : in out Alternating_Pool;
       Storage_Address          : in     Address;
       Size_In_Storage_Elements : in     Storage_Elements.Storage_Count;
       Alignment                : in     Storage_Elements.Storage_Count)
    is
    begin
       null;
    end Deallocate;

    overriding
    function Storage_Size
      (Pool : Alternating_Pool)
       return Storage_Elements.Storage_Count
    is
       use type Storage_Elements.Storage_Count;
    begin
       return Pair'Size / Storage_Elements.Storage_Element'Size;
    end Storage_Size;

end My_Switching_Pool;

with My_Switching_Pool;
procedure Main is

    package Two_Numbers is new My_Switching_Pool (T => Positive);

    The_Pool : Two_Numbers.Alternating_Pool;

    type Positive_Ptr is access Positive
       with Storage_Pool => The_Pool;

    Test : Positive_Ptr;

begin

    loop
       Test := new Positive;
    end loop;

end Main;


^ permalink raw reply	[relevance 7%]

* ANN: Deepend 3.0 Available for Ada 2012 and Ada 2005
@ 2012-07-04 15:04  4% Brad Moore
  0 siblings, 0 replies; 96+ results
From: Brad Moore @ 2012-07-04 15:04 UTC (permalink / raw)


I am pleased to announce the availability of Deepend 3.0.

Deepend is a dynamic storage pool with Subpool capabilities for Ada 2005
and Ada 2012 where all the objects in a subpool can be reclaimed all at
once, instead of requiring each object to be individually reclaimed one
at a time. A Dynamic Pool may have any number of subpools. If subpools
are not reclaimed prior to finalization of the pool, then they are
finalized when the pool is finalized.

Rather than deallocate items individually which is error prone and
susceptible to memory leaks and other memory issues, a subpool can be
freed all at once automatically when the pool object goes out of scope.

With this Storage pool, Unchecked_Deallocation is implemented as a No-Op
(null procedure), because it is not needed or intended to be used.

Subpool based storage management provides a safer means of memory
management, which can outperform other mechanisms for storage
reclamation including garbage collection.

Major differences in this release:

- Ada 2012 version is available which utilizes the new 
System.Storage_Pools.Subpools package defined in the Ada2012 standard.

- Ada 2012 version allows objects of unconstrained types, and objects 
that need finalization such as protected objects and controlled types
to be allocated to subpools. These objects are properly finalized when
the subpool is deallocated.

- Ada 2012 version uses other new features of the language, including
   in out parameters for function calls instead of access parameters,
   and provides a default discriminant for the Dynamic_Pool type. Pre
   and Post conditions are also used.

- The Storage_Size primitive is now implemented so that it reports the
amount of storage currently used

- The Binary_Tree benchmark that uses access type finalization was 
updated to use the Basic_Dynamic_Pools package instead of the 
Dynamic_Pools package, since that particular test does not use subpools.

The latest stable release and older releases may be downloaded from;

https://sourceforge.net/projects/deepend/files/



^ permalink raw reply	[relevance 4%]

* Is Storage Subpool Example tested?
@ 2012-04-25 21:18  5% ytomino
  0 siblings, 0 replies; 96+ results
From: ytomino @ 2012-04-25 21:18 UTC (permalink / raw)


Hello.

I'm trying to compile http://ada-auth.org/standards/12rm/html/RM-13-11-6.html , but there are some errors.

Perhaps, 

1. "use type System.Storage_Pools.Subpools.Subpool_Handle;" is missing.

2. 2nd parameter of Set_Pool_of_Subpool is "in out", but access value is given.

3. Downcast as MR_Subpool is missing in
> Result.Start := Pool.Next_Allocation;

4. ".Start" is missing in
> Pool.Next_Allocation := Pool.Markers(Pool.Current_Pool);

(And, I had to replace some 'Unchecked_Access to 'Unrestricted_Access, but this is GNAT's feature. I don't care it.)

BTW, Do you have a interesting idea to use subpools?
For instance, I like Matthew Heaney's System.Initialization. ( http://www.ada-auth.org/cgi-bin/cvsweb.cgi/ai05s/ai05-0001-1.txt?rev=1.17 )
It seems to be able to implement by user with subpool.

 P := System.Initialization.New_Object (Storage);

is able to be rewritten like below

 P := new (Make_Subpool_Using_Given_Address (Storage'Address)) Object_Type;

However, Delete_Object is difficult. :-)



^ permalink raw reply	[relevance 5%]

* Re: User Defined Storage Pool : Example
  @ 2011-01-22  9:47  4% ` anon
  0 siblings, 0 replies; 96+ results
From: anon @ 2011-01-22  9:47 UTC (permalink / raw)


-- referance delete for spacing


-- Found on www.adapower.com
--
-- http://www.adapower.com/index.php?Command=Class&ClassID=Advanced&CID=222
--
-- Files:
--        memory_management-test.adb
--        memory_management-support.ads
--        memory_management-support.adb
--        memory_management.ads
--        memory_management.adb
--
-- To compile and run:
-- 
--   >gnat make memory_management-test.adb
--   >memory_management-test

--
--  Memory Management with Storage Pools (Anh Vo)
--
--  Memory management can cause real headache due to memory leakage over 
--  time. That is, memory allocation is not properly deallocated after the 
--  call. When the memory runs out, the result could be catastrophic for 
--  some applications. This problem can be recued by garbage collector 
--  built-in the compiler such as Java. However, the cost of run-time 
--  overhead is high.
     
--  Here comes Ada 95 to the recue. How is it possible you may ask? Ah! 
--  Ada 95 provides a feature called Storage Pool. It allows the users 
--  have total control over the memory management. Best of all, it does 
--  not involve run-time overhead as garbage collector. When it is 
--  combined with controlled type, the memory leakage problem is history.
    
--  As shown in the test case, 100 storage elements were allocated 
--  initially. Then, these storage elements are reused again and again. It 
--  is pretty cool isn't it? Enjoy.
     

--------------------------------------------
-- File => memory_management-test.adb
--
with Ada.Finalization ;
with Ada.Text_Io ;
with Memory_Management.Support ;
     
procedure Memory_Management.Test is
    use Ada ;
    use Text_Io ;
     
begin
     
  Put_Line ("********* Memory Control Testing Starts **********") ;
   
  for Index in 1 .. 10 loop
    declare
      David_Botton : Support.General_Data ;
      Nick_Roberts : Support.General_Data ;
      Anh_Vo       : Support.General_Data ;
     
    begin
      David_Botton := ( Finalization.Controlled with
                         Id   => new Integer' ( 111 ), 
                         Name => new String' ( "David Botton" ) ) ;

      Nick_Roberts := ( Finalization.Controlled with
                          Id   => new Integer' ( 222 ), 
                          Name => new String' ( "Nick Roberts" ) ) ;

      Anh_Vo := ( Finalization.Controlled with
                    Id   => new Integer' ( 333 ),
                    Name => new String' ( "Anh Vo" ) ) ;
    end ;
  end loop ;
     
  Put_Line ( "Memory Management Test Passes" ) ;
     
exception
  when others =>
    Put_Line ( "Memory Management Test Fails" ) ;
     
end Memory_Management.Test ;


--------------------------------------------
-- File => memory_management-support.ads
--
with Ada.Finalization ;
     
package Memory_Management.Support is
     
  use Ada ;
     
  -- Adjust the storage size according to the application
  Big_Pool : User_Pool ( Size => 100 )  ;
     
  type Int_Acc is access Integer ;
    for Int_Acc'Storage_Pool use Big_Pool ;
     
  type Str_Acc is access all String ;
    for Str_Acc'Storage_Pool use Int_Acc'Storage_Pool ;
     
  type General_Data is new Finalization.Controlled 
         with record
                Id : Int_Acc ;
                Name : Str_Acc ;
              end record ;
     
  procedure Initialize ( Object : in out General_Data )  ;
     
  procedure Finalize ( Object : in out General_Data )  ;
     
end Memory_Management.Support ;
     

--------------------------------------------
-- File => memory_management-support.adb
--
with Ada.Unchecked_Deallocation ;
     
package body Memory_Management.Support is
     
  procedure Free is new Ada.Unchecked_Deallocation 
                                                 ( Integer, Int_Acc ) ;
  procedure Free is new Ada.Unchecked_Deallocation
                                                  ( String, Str_Acc ) ;
     
   procedure Initialize ( Object : in out General_Data ) is
     begin
       null ;
     end Initialize ;
     
  procedure Finalize ( Object : in out General_Data ) is
    begin
      Free ( Object.Id ) ;
      Free ( Object.Name ) ;
    end Finalize ;
     
end Memory_Management.Support ;
     
--------------------------------------------     
-- File => memory_management.ads
--
with System.Storage_Pools ;
with System.Storage_Elements ;
     
package Memory_Management is
     
    use System ;
    use Storage_Elements ;
    use Storage_Pools ;
     
  type User_Pool ( Size : Storage_Count ) is new
                                       Root_Storage_Pool with private ;
     
  procedure Allocate ( Pool                     : in out User_Pool ;
                       Storage_Address          :    out Address   ;
                       Size_In_Storage_Elements : in Storage_Count ;
                       Alignment                : in Storage_Count ) ;
     
  procedure Deallocate 
                      ( Pool                     : in out User_Pool ;
                        Storage_Address          : in     Address   ;
                        Size_In_Storage_Elements : in Storage_Count ;
                        Alignment                : in Storage_Count ) ;
     
  function Storage_Size ( Pool : in User_Pool ) 
               return Storage_Count ;
     
  -- Exeption declaration

  Memory_Exhausted : exception ;
     
  Item_Too_Big : exception ;
     
private
  type User_Pool ( Size : Storage_Count ) is new Root_Storage_Pool
           with record
                  Data       : Storage_Array ( 1 .. Size ) ;
                  Addr_Index : Storage_Count := 1 ;
                end record ;
     
end Memory_Management ;
     

--------------------------------------------     
-- File => memory_management.adb
--
with Ada.Exceptions ;
with Ada.Text_Io ;
with System ;
with System.Storage_Elements ;
with System.Address_To_Access_Conversions ;
     
package body Memory_Management is
     
    use Ada ;
    use Text_Io ;
    use System ;
    use Storage_Elements ;
    use type Storage_Count ;
     
  Package_Name : constant String := "Memory_Management." ;
     
    -- Used to turn on/off the debug information
  Debug_On : Boolean := True ; -- False ;
     
  type Holder is record
         Next_Address : Address := System.Null_Address ;
  end record ;
     
  package Addr_To_Acc is new Address_To_Access_Conversions ( Holder ) ;
     
  -- Keep track of the size of memory block for reuse
  Free_Storage_Keeper : array ( Storage_Count range 1 .. 100 )
          of Address := ( others => Null_Address ) ;
     
  procedure Display_Info ( Message       : string ; 
                           With_New_Line : Boolean := True ) is
    begin
      if Debug_On then
        if With_New_Line then
          Put_Line ( Message ) ;
        else
          Put ( Message ) ;
        end if ;
      end if ;
    end Display_Info ;
     

  procedure Allocate ( Pool                     : in out User_Pool ;
                       Storage_Address          :    out Address   ;
                       Size_In_Storage_Elements : in Storage_Count ;
                       Alignment                : in Storage_Count ) is
          
      Procedure_Name : constant String := "Allocate" ;
      Temp_Address   : Address  := Null_Address ;
      Marker         : Storage_Count ;
    begin
     
      Marker := ( Size_In_Storage_Elements + Alignment - 1 )
              / Alignment ;
     
      if Free_Storage_Keeper ( Marker ) /= Null_Address then
        Storage_Address := Free_Storage_Keeper ( Marker ) ;
        Free_Storage_Keeper (Marker) :=
        Addr_To_Acc.To_Pointer 
                ( Free_Storage_Keeper ( Marker ) ).Next_Address ;
      else
        Temp_Address := Pool.Data (Pool.Addr_Index)'Address ;
              
        Pool.Addr_Index := Pool.Addr_Index 
                         + Alignment 
                         * ( ( Size_In_Storage_Elements 
                               + Alignment - 1 ) 
                         / Alignment ) ;
     
        -- make sure memory is available as requested
        if Pool.Addr_Index > Pool.Size then
          Exceptions.Raise_Exception ( Storage_Error'Identity,
                                       "Storage exhausted in " 
                                       & Package_Name 
                                       & Procedure_Name ) ;
        else
          Storage_Address := Temp_Address ;
        end if ;
      end if ;
     
      Display_Info  ( "Address allocated from pool: "
                      & Integer_Address'Image 
                          ( To_Integer ( Storage_Address ) ) ) ;
   
      Display_Info ( "storage elements allocated from pool: "
                     & Storage_Count'Image 
                          ( Size_In_Storage_Elements ) ) ;
     
      Display_Info ( "Alignment in allocation operation: "
                     & Storage_Count'Image ( Alignment ) ) ;
   
    exception
      when Error : others => -- Object too big or memory exhausted
        Display_Info ( Exceptions.Exception_Information ( Error ) ) ;
        raise ;
     
    end Allocate ;


  procedure Deallocate 
                     ( Pool                     : in out User_Pool ;
                       Storage_Address          : in     Address   ;
                       Size_In_Storage_Elements : in Storage_Count ;
                       Alignment                : in Storage_Count ) is
          
      Marker : Storage_Count ;
     
    begin
     
      Marker := ( Size_In_Storage_Elements + Alignment - 1) 
              / Alignment ;
      Addr_To_Acc.To_Pointer ( Storage_Address ).Next_Address :=
                                     Free_Storage_Keeper ( Marker ) ;
      Free_Storage_Keeper ( Marker ) := Storage_Address ;
     
      Display_Info  ( "Address returned to pool: " 
                      & Integer_Address'Image 
                          ( To_Integer ( Storage_Address ) ) ) ;
     
      Display_Info ( "storage elements returned to pool: "
                     & Storage_Count'Image 
                         ( Size_In_Storage_Elements ) ) ;
     
      Display_Info ( "Alignment used in deallocation: "
                     & Storage_Count'Image ( Alignment ) ) ;
     
  end Deallocate ;
     
  function Storage_Size ( Pool : in User_Pool ) 
             return Storage_Count is
    begin
      return Pool.Size ;
    end Storage_Size ;
     
end Memory_Management ;




^ permalink raw reply	[relevance 4%]

* Re: put of access type
  @ 2009-08-21  1:20  4%             ` Adam Beneschan
  0 siblings, 0 replies; 96+ results
From: Adam Beneschan @ 2009-08-21  1:20 UTC (permalink / raw)


On Aug 20, 5:18 pm, "Randy Brukardt" <ra...@rrsoftware.com> wrote:
> "Martin Krischik" <krisc...@users.sourceforge.net> wrote in message
>
> news:4a8cea9c$1@news.post.ch...
>
>
>
>
>
> > Randy Brukardt schrieb:
> >> "Adam Beneschan" <a...@irvine.com> wrote in message
> >>news:c9aec6d6-4e9b-4bf6-9586-68a237175c9d@i18g2000pro.googlegroups.com...
> >> ...
> >>> Also, there's no rule saying that an access value has to be an address
> >>> at all.  It's certainly conceivable that an access value may be
> >>> implemented as a reference to some storage pool and an offset into
> >>> that pool, allowing for the possibility that the memory management
> >>> system may just decide to pick up the whole pool and move it to some
> >>> other address, without making any of the access values invalid.
>
> >> I think the Ada 95 definition of storage pools would make this
> >> implementation hard to make work. (Which is unfortunate, it would have
> >> worked fine in Ada 83).
>
> > It still works:
>
> I think you missed my point. The definition of the Allocate function for a
> storage pool returns an System.Address. Moreover, there is no notification
> when the access value returned from Allocate is dereferenced or converted to
> another access type. So if Allocate returns an offset rather than an
> address, the compiler generated code to implement .all and to implement
> conversions to anonymous access type is not going to take that into
> account -- it will think it received a System.Address. So this cannot work
> for any user-defined storage pool.

It could still work using a type like Martin suggested---as long as
the compiler sets up an access type with Pool_Access=False whenever it
is using a user-defined storage pool.  It would use Pool_Access=True
only for the default storage pool.  Yes, that makes it less useful.

More generally, though: My comment assumed that there would be a lot
of compiler support required for an access type that is implemented as
a pool reference plus an offset.  There's no reason that a compiler
that has this support couldn't also add its own rule that it supports
this kind of access type only for storage pools that are descendants
of System.Storage_Pools.Movable_Storage_Pools.-
 Root_Movable_Storage_Pool (with this last child package and type
being vendor-defined).  This type would contain additional operations
that the compiler would depend on to get things right; Allocate would
still return a System.Address, but some new operation defined for
Root_Movable_Storage_Pool would convert that address to an offset, and
the compiler would depend on that operation when setting up an access
type with Pool_Access=True.

A lot of work, certainly, and probably not worth the effort unless
some customer has special requirements.  But my original point wasn't
intended to suggest anything practical, but just to get people
thinking a bit about the *possibility* that an access type doesn't
need to be implemented as an address, and thus to start thinking about
things like that in more abstract ways instead of being tied to low-
level concepts that other languages sometimes make you think in.

                                       -- Adam




^ permalink raw reply	[relevance 4%]

* Re: GNAT on WinXP: System.OS_Lib.Spawn raises Program_Error
  2009-05-02 20:39  5%   ` anon
@ 2009-05-03  9:42  0%     ` Martin
  0 siblings, 0 replies; 96+ results
From: Martin @ 2009-05-03  9:42 UTC (permalink / raw)


On May 2, 9:39 pm, a...@anon.org (anon) wrote:
> Martin
>
> GNAT.OS_LIB existed in GNAT 3.15p  but since GNAT 2005 it have been
> moved to System.OS_LIB.  And the GNAT.OS_LIB just renames System.OS_LIB
> which makes this package a legacy for older projects and can be avoided for
> future use. It just causes more work for the compiler which increase the
> compile time.

Still there in the Win32 GPL 2008 edition.


> Plus, there are only 6 System files in the RM Ada standards:
>
>   0. System
>   1.   System.Address_To_Access_Conversions
>   2.   System.Machine_Code
>   3.   System.RPC
>   4.   System.Storage_Elements
>   5.   System.Storage_Pools
>
> All others System packages like all GNAT packages are non RM Ada
> standard package list. And any GNAT Ada programmer should know that.

You're assuming a level of knowledge that I don't find in the real
world.


> Adacore's annual or GNU quarterly update of GNAT is the Ada standard, for
> most people and schools, and very few programmers will use anything else.

I have no proof that 'very few programmers will use anything else' and
I suspect you don't either. I've used (professionally) 7 Ada compilers
that I can think of off the top of my head. And at least 1 more that
I've just on a personal level. That's not counting all the different
versions of each compiler separately.


> And any improvement that Adacore makes that is passed to GNU version will
> become to most programmers, additions to the Ada standards.  Just like a
> lot of programmers were using the Ada 2005 specs before they were approved
> in January, 2008.

GNAT extensions are not likely to become standard. Ada2005 specs were
_very_ likely to become standard.

Besides, I assume were all here in c.l.a. because we want to see
_more_ Ada in the world, so hopefully that means more people using all
Ada compilers and not just GNAT. We should be pointing out the 'right
thing to do' to all and let them make their minds up.


> Plus, "GNATLINK" uses "System.OS_LIB.spawn" to call the "gcc" compiler
> to compile the binder generated file.  If this was not OK, then why would
> Adacore or GNU use it?

Because AdaCore / GNU and certainly not going to port they're code to
a different compiler.


> And finally the RM allows the usages of additional System packages to be
> included in a standard.  System.OS_LIB is an "implementation-defined
> children of System" see, RM 13.7 (36),

The RM also allows the use of 'goto', are you advocating wide-spread
use of this facility too? Just because something is allowed does not
make it a 'good idea'.


> So you need to stop with the idea using non standard packages is a "bad
> idea". Plus, all that is needed is a few comments for future version of
> GNAT. And that because most programs written with GNAT will almost
> never be move from GNAT, so only updating comments are needed.

Sorry, that's just pants.

I just went though a porting exercise at work where a project was
looking to migrate from XD-Ada/68k to <some_other_Ada_product>/
PowerPC. One issue with XD-Ada based systems was that XD-Ada included
various non-standard extensions to package System - types of a known
size. This is the 2nd project I've seen that made _large_scale_ use of
these types throughout their code.

Perfectly avoidable (by defining types they know to match the size
required, perhaps even calling it 'Interfaces') or limiting the effect
by defining their own 'Project_System' package. The 1st option would
have involved 0 hours work the 2nd option a 2 minute job with minimal
source code files touched. In the end _dozens_ of files needed to be
modified and that incurs a lot more time (i.e. money) to check / re-
test.

Like I said - this is not the first time this has happened (and not
just with Ada - VC++ no hasn't come with <iostream.h>, only
<iostream>, since 2005 and I've seen projects which started post-98
when <iostream> was the standard header defined get bitten by this).

Cheers
-- Martin




^ permalink raw reply	[relevance 0%]

* Re: GNAT on WinXP: System.OS_Lib.Spawn raises Program_Error
  @ 2009-05-02 20:39  5%   ` anon
  2009-05-03  9:42  0%     ` Martin
  0 siblings, 1 reply; 96+ results
From: anon @ 2009-05-02 20:39 UTC (permalink / raw)


Martin

GNAT.OS_LIB existed in GNAT 3.15p  but since GNAT 2005 it have been 
moved to System.OS_LIB.  And the GNAT.OS_LIB just renames System.OS_LIB 
which makes this package a legacy for older projects and can be avoided for 
future use. It just causes more work for the compiler which increase the 
compile time.

Plus, there are only 6 System files in the RM Ada standards: 

  0. System
  1.   System.Address_To_Access_Conversions
  2.   System.Machine_Code
  3.   System.RPC
  4.   System.Storage_Elements
  5.   System.Storage_Pools

All others System packages like all GNAT packages are non RM Ada 
standard package list. And any GNAT Ada programmer should know that. 

Adacore's annual or GNU quarterly update of GNAT is the Ada standard, for 
most people and schools, and very few programmers will use anything else. 
And any improvement that Adacore makes that is passed to GNU version will 
become to most programmers, additions to the Ada standards.  Just like a 
lot of programmers were using the Ada 2005 specs before they were approved 
in January, 2008.

Plus, "GNATLINK" uses "System.OS_LIB.spawn" to call the "gcc" compiler 
to compile the binder generated file.  If this was not OK, then why would 
Adacore or GNU use it? 

And finally the RM allows the usages of additional System packages to be 
included in a standard.  System.OS_LIB is an "implementation-defined 
children of System" see, RM 13.7 (36),

So you need to stop with the idea using non standard packages is a "bad 
idea". Plus, all that is needed is a few comments for future version of 
GNAT. And that because most programs written with GNAT will almost 
never be move from GNAT, so only updating comments are needed.



In <923b28dd-46ee-40cb-b13e-5f8860405f22@r36g2000vbr.googlegroups.com>, Martin <martin.dowie@btopenworld.com> writes:
>On May 2, 5:16=A0am, a...@anon.org (anon) wrote:
>> First, in GNAT GPL 2008, GNAT.OS_LIB renames System.OS_LIB, so using
>> GNAT.OS_LIB would be a waste of time.
>
>Not entirely a waste, as using "GNAT.*" makes it explicit to anyone
>reading the code that this is a non-standard package being used. Using
>'System.OS_Lib' would give the erroneous impression to the casual
>reader that only standard language defined packages are being used and
>that there perhaps would be =A30.00 cost to compile it up using a
>different compiler.
>
>Using non-standard extensions to standard units is generally a
>_bad_idea_ but if it is unavoidable then it should be hidden in an
>abstration layer that you have control over.
>
>Cheers
>-- Martin
>




^ permalink raw reply	[relevance 5%]

* Re: Allocators and memory reclamation
  2008-01-28 22:27  4%   ` Maciej Sobczak
@ 2008-01-28 23:54  0%     ` Adam Beneschan
  0 siblings, 0 replies; 96+ results
From: Adam Beneschan @ 2008-01-28 23:54 UTC (permalink / raw)


On Jan 28, 2:27 pm, Maciej Sobczak <see.my.homep...@gmail.com> wrote:

> I understand that I can create my own pool with any behaviour I need.
> Let's try:
>
> with Ada.Text_IO;
> with Ada.Finalization;
> with System.Storage_Pools;
> with System.Storage_Elements;
>
> procedure Main is
>
>    use System.Storage_Pools;
>
>    -- used to acquire reference to the standard storage pool
>    type Integer_Ptr is access Integer;
>
>    procedure Test is
>
>       type My_Type is new Ada.Finalization.Controlled with null
> record;
>
>       procedure Finalize (T : in out My_Type) is
>       begin
>          Ada.Text_IO.Put_Line ("Finalize");
>       end Finalize;
>
>       use System;
>
>       type My_Pool_Type is new Root_Storage_Pool with null record;
>
>       procedure Allocate (Pool : in out My_Pool_Type;
>                           Storage_Address : out Address;
>                           Size_In_Storage_Elements : in
> Storage_Elements.Storage_Count;
>                           Alignment : in
> Storage_Elements.Storage_Count);
>       procedure Deallocate (Pool : in out My_Pool_Type;
>                             Storage_Address : in Address;
>                             Size_In_Storage_Elements : in
> Storage_Elements.Storage_Count;
>                             Alignment : in
> Storage_Elements.Storage_Count);
>       function Storage_Size (Pool : in My_Pool_Type) return
> Storage_Elements.Storage_Count;
>
>       procedure Allocate (Pool : in out My_Pool_Type;
>                           Storage_Address : out Address;
>                           Size_In_Storage_Elements : in
> Storage_Elements.Storage_Count;
>                           Alignment : in
> Storage_Elements.Storage_Count) is
>       begin
>          Allocate (Integer_Ptr'Storage_Pool, Storage_Address,
> Size_In_Storage_Elements, Alignment);
>          Ada.Text_IO.Put_Line ("allocating " &
>                                Storage_Elements.Storage_Count'Image
> (Size_In_Storage_Elements));
>       end Allocate;
>
>       procedure Deallocate (Pool : in out My_Pool_Type;
>                             Storage_Address : in Address;
>                             Size_In_Storage_Elements : in
> Storage_Elements.Storage_Count;
>                             Alignment : in
> Storage_Elements.Storage_Count) is
>       begin
>          Deallocate (Integer_Ptr'Storage_Pool, Storage_Address,
> Size_In_Storage_Elements, Alignment);
>          Ada.Text_IO.Put_Line ("deallocating");
>       end Deallocate;
>
>       function Storage_Size (Pool : in My_Pool_Type) return
> Storage_Elements.Storage_Count is
>       begin
>          return Storage_Size (Integer_Ptr'Storage_Pool);
>       end Storage_Size;
>
>       My_Pool : My_Pool_Type;
>
>       type My_Type_Ptr is access My_Type;
>       for My_Type_Ptr'Storage_Pool use My_Pool;
>
>       P : My_Type_Ptr;
>
>    begin
>       Ada.Text_IO.Put_Line ("starting to allocate objects");
>       P := new My_Type;
>       P := new My_Type;
>       Ada.Text_IO.Put_Line ("finished with objects and leaving the
> scope");
>    end Test;
>
> begin
>    Ada.Text_IO.Put_Line ("Running test");
>    Test;
>    Ada.Text_IO.Put_Line ("Test finished");
> end Main;
>
> (the code has lengthy lines and can get broken in your readers)
>
> In the above example I tried to create my own pool that is backed up
> by the standard pool acquired from some dummy access type. The new
> pool just forwards all primitive operations to the standard pool and
> prints some messages to see what's going on.
> It looks like I got it correctly, because it compiles and even works:
>
> Running Test
> Starting To Allocate Objects
> Allocating  12
> Allocating  12
> Finished With Objects And Leaving The Scope
> Finalize
> Finalize
> Test Finished
>
> I understand (now) that two objects are allocated with the help of my
> own pool. Since nobody deallocated explicitly (no
> Unchecked_Deallocation was used), the Deallocate procedure was not
> called and the memory is effectively leaked. I could have remembered
> the allocated addresses and deallocate the dangling blocks in the
> finalizer of my own pool (it is controlled after all) and this way the
> pool would guard the memory and prevent the leak. It didn't, so
> effectively there is a leak.
> More precisely, the allocated blocks come from the standard pool and
> they will be deallocated when the whole program will finish.
>
> The interesting part is that finalizers of My_Type were called and
> this is even before the pool gets finalized itself (I've checked it by
> overriding Finalize for My_Pool_Type). This is good, because after
> that only raw memory remained to be reclaimed.
> The question is - who called the finalizers of allocated objects? Any
> AARM paragraphs for this would be welcome.

As Randy pointed out, 7.6.1(11) is the key; it discusses when objects
created by an <allocator> are finalized.  It also says that those
objects are finalized in an arbitrary order.

>
> > > Another question relates to the order of finalizing objects. If the
> > > storage pool is torn down when the access type goes out of scope, is
> > > the order of finalizing objects guaranteed?
>
> > AFAIK, it is not. Why should it be?
>
> Why not? :-)
>
> If not, then there is additional (automatic) question: how can I make
> it guaranteed? Since finalizers seem to be called by some magic, then
> I don't think there is any way for me to influence the behaviour here
> - at least not by providing my own pool, which does not even get a
> chance to have anything to say on this subject.

I'm not completely clear on what you are trying to accomplish.  Are
you trying to ensure that if you allocate a number of objects of a
controlled type, then when those objects are finalized, you want them
to be finalized in a particular order, for example in the reverse
order in which you allocated them?

If this is what you want, you'll need to invent your own solution, but
I think it's doable.  I can envision an implementation where all the
allocated records of a type are linked together in a list; then when
one of these is finalized according to 7.6.1(11), the Finalize routine
recognizes this and finalizes *all* of the objects in the linked list,
perhaps setting a flag in the records to indicate that the
finalization took place.  Then when the other objects are finalized
according to 7.6.1(11), the Finalize routine would recognize that the
finalization has already been done, and do nothing.  If you do this,
you can certainly control the order in which allocated objects are
finalized.  But I think something like this has to be done.  There's
nothing in the language that I  know of to assert any control over the
order in which allocated objects are finalized.

>
> There is a related problem which I've found while playing with the
> above code example: I cannot have a pointer to the standard pool.
> In other words, this:
>
> type Pool_Ptr is access Root_Storage_Pool'Class;
> PP : Pool_Ptr := Integer'Storage_Pool'Access;
>
> is not possible, because the standard storage pool is not aliased.
> How can I get a reference to the standard pool so that I don't have to
> repeat the "Integer'Storage_Pool" million times?
> What about this:
>
> P : Root_Storage_Pool'Class := Integer_Ptr'Storage_Pool;
>
> I expect that P will be a reference to the standard pool, not its copy
> (it cannot be a copy, because Root_Storage_Pool is limited). Is this
> reasoning correct?

No.  Declaring an object of a limited type does *not* create a
reference; it creates an object.  Here, the compiler will think you're
trying to make a copy of a limited object, and it will complain.  Try
"renames".


> Last but not least: does AARM 13.11/20 mean that the above program is
> incorrect? How to implement it correctly, then?

You're probably OK in this particular case, since you're simply
passing through the arguments that the compiler is passing to another
Deallocate.  But the potential for trouble is that when the
implementation generates code for an <allocator> or for a call to an
Unchecked_Deallocation instance, it may do other things besides call
Allocate or Deallocate, and a direct call to Allocate or Deallocate
doesn't do those things.  It seems unlikely to me that, for an
implementation, those "other things" would do anything that involves
the storage pool, which means that this pass-through usage should be
fine.  But I could be wrong.

                                  -- Adam



^ permalink raw reply	[relevance 0%]

* Re: Allocators and memory reclamation
  @ 2008-01-28 22:27  4%   ` Maciej Sobczak
  2008-01-28 23:54  0%     ` Adam Beneschan
  0 siblings, 1 reply; 96+ results
From: Maciej Sobczak @ 2008-01-28 22:27 UTC (permalink / raw)


On 28 Sty, 16:15, "Dmitry A. Kazakov" <mail...@dmitry-kazakov.de>
wrote:

> The language does not prescribe the effect of a call to Deallocate on the
> program's environment.

I'm not interested in the interaction on this level.
I'm interested in the pattern of calls to Deallocate in the given
program.
My understanding, initially, was that Deallocate is called kind of
implicitly when the storage pool is torn down together with its
associated access type.
It does not seem to be the case, but the storage pool itself can keep
track of the allocated blocks and at the end do "something" with them.
For example, the storage pool might be based on static memory block
that just gives new addresses for each Allocate and have empty
Deallocate - a fairly compliant implementation. When the pool goes out
of scope, so does its memory.

I understood that the memory that was used by the pool is deallocated
even in the following simple case:

type Integer_Ptr is access Integer;

but the AARM claims it can be otherwise (that the memory might be
bound to library-level pool).

I understand that I can create my own pool with any behaviour I need.
Let's try:

with Ada.Text_IO;
with Ada.Finalization;
with System.Storage_Pools;
with System.Storage_Elements;

procedure Main is

   use System.Storage_Pools;

   -- used to acquire reference to the standard storage pool
   type Integer_Ptr is access Integer;

   procedure Test is

      type My_Type is new Ada.Finalization.Controlled with null
record;

      procedure Finalize (T : in out My_Type) is
      begin
         Ada.Text_IO.Put_Line ("Finalize");
      end Finalize;

      use System;

      type My_Pool_Type is new Root_Storage_Pool with null record;

      procedure Allocate (Pool : in out My_Pool_Type;
                          Storage_Address : out Address;
                          Size_In_Storage_Elements : in
Storage_Elements.Storage_Count;
                          Alignment : in
Storage_Elements.Storage_Count);
      procedure Deallocate (Pool : in out My_Pool_Type;
                            Storage_Address : in Address;
                            Size_In_Storage_Elements : in
Storage_Elements.Storage_Count;
                            Alignment : in
Storage_Elements.Storage_Count);
      function Storage_Size (Pool : in My_Pool_Type) return
Storage_Elements.Storage_Count;

      procedure Allocate (Pool : in out My_Pool_Type;
                          Storage_Address : out Address;
                          Size_In_Storage_Elements : in
Storage_Elements.Storage_Count;
                          Alignment : in
Storage_Elements.Storage_Count) is
      begin
         Allocate (Integer_Ptr'Storage_Pool, Storage_Address,
Size_In_Storage_Elements, Alignment);
         Ada.Text_IO.Put_Line ("allocating " &
                               Storage_Elements.Storage_Count'Image
(Size_In_Storage_Elements));
      end Allocate;

      procedure Deallocate (Pool : in out My_Pool_Type;
                            Storage_Address : in Address;
                            Size_In_Storage_Elements : in
Storage_Elements.Storage_Count;
                            Alignment : in
Storage_Elements.Storage_Count) is
      begin
         Deallocate (Integer_Ptr'Storage_Pool, Storage_Address,
Size_In_Storage_Elements, Alignment);
         Ada.Text_IO.Put_Line ("deallocating");
      end Deallocate;

      function Storage_Size (Pool : in My_Pool_Type) return
Storage_Elements.Storage_Count is
      begin
         return Storage_Size (Integer_Ptr'Storage_Pool);
      end Storage_Size;

      My_Pool : My_Pool_Type;

      type My_Type_Ptr is access My_Type;
      for My_Type_Ptr'Storage_Pool use My_Pool;

      P : My_Type_Ptr;

   begin
      Ada.Text_IO.Put_Line ("starting to allocate objects");
      P := new My_Type;
      P := new My_Type;
      Ada.Text_IO.Put_Line ("finished with objects and leaving the
scope");
   end Test;

begin
   Ada.Text_IO.Put_Line ("Running test");
   Test;
   Ada.Text_IO.Put_Line ("Test finished");
end Main;

(the code has lengthy lines and can get broken in your readers)

In the above example I tried to create my own pool that is backed up
by the standard pool acquired from some dummy access type. The new
pool just forwards all primitive operations to the standard pool and
prints some messages to see what's going on.
It looks like I got it correctly, because it compiles and even works:

Running Test
Starting To Allocate Objects
Allocating  12
Allocating  12
Finished With Objects And Leaving The Scope
Finalize
Finalize
Test Finished

I understand (now) that two objects are allocated with the help of my
own pool. Since nobody deallocated explicitly (no
Unchecked_Deallocation was used), the Deallocate procedure was not
called and the memory is effectively leaked. I could have remembered
the allocated addresses and deallocate the dangling blocks in the
finalizer of my own pool (it is controlled after all) and this way the
pool would guard the memory and prevent the leak. It didn't, so
effectively there is a leak.
More precisely, the allocated blocks come from the standard pool and
they will be deallocated when the whole program will finish.

The interesting part is that finalizers of My_Type were called and
this is even before the pool gets finalized itself (I've checked it by
overriding Finalize for My_Pool_Type). This is good, because after
that only raw memory remained to be reclaimed.
The question is - who called the finalizers of allocated objects? Any
AARM paragraphs for this would be welcome.

> > Another question relates to the order of finalizing objects. If the
> > storage pool is torn down when the access type goes out of scope, is
> > the order of finalizing objects guaranteed?
>
> AFAIK, it is not. Why should it be?

Why not? :-)

If not, then there is additional (automatic) question: how can I make
it guaranteed? Since finalizers seem to be called by some magic, then
I don't think there is any way for me to influence the behaviour here
- at least not by providing my own pool, which does not even get a
chance to have anything to say on this subject.


There is a related problem which I've found while playing with the
above code example: I cannot have a pointer to the standard pool.
In other words, this:

type Pool_Ptr is access Root_Storage_Pool'Class;
PP : Pool_Ptr := Integer'Storage_Pool'Access;

is not possible, because the standard storage pool is not aliased.
How can I get a reference to the standard pool so that I don't have to
repeat the "Integer'Storage_Pool" million times?
What about this:

P : Root_Storage_Pool'Class := Integer_Ptr'Storage_Pool;

I expect that P will be a reference to the standard pool, not its copy
(it cannot be a copy, because Root_Storage_Pool is limited). Is this
reasoning correct?

Last but not least: does AARM 13.11/20 mean that the above program is
incorrect? How to implement it correctly, then?

--
Maciej Sobczak * www.msobczak.com * www.inspirel.com



^ permalink raw reply	[relevance 4%]

* Re: Does 3.9.3(10) apply to untagged private whose full view is tagged?
  @ 2007-07-26  8:58  4% ` anon
  0 siblings, 0 replies; 96+ results
From: anon @ 2007-07-26  8:58 UTC (permalink / raw)


Compiling: pak1.ads (source file time stamp: 2007-07-25 03:45:40)

     1. package Pak1 is
     2.    type T1 is private ;
     3. 
     4. private
     5.    type T1 is tagged record
     6.       F1 : Integer ;
     7.   end record ;
     8.   function Func ( X : Integer ) return T2 ;
                                               |
        >>> "T2" is undefined

     9. end Pak1;
    10. 

T2 must be defined.  So, assume T2 is a typo for T1

Compiling: pak1.ads (source file time stamp: 2007-07-25 03:27:16)

     1. package Pak1 is
     2.    type T1 is private;
     3. 
     4. private
     5.    type T1 is tagged record
     6.       F1 : Integer;
     7.   end record;
     8.   function Func (X : Integer) return T1 ;
                   |
        >>> private function with tagged result must override visible-part function
        >>> move subprogram to the visible part (RM 3.9.3(10))

     9. end Pak1;
    10. 

GNAT is correct!  A better example of how to write is type 
of code is System.Storage_Pools package (RM 13.11) which 
uses the System.Storage_Elements package (RM 13.7.1).


Ada 95: RM 3.9.3 (10) says 
10   For an abstract type declared in a visible part, an abstract primitive
subprogram shall not be declared in the private part, unless it is overriding
an abstract subprogram implicitly declared in the visible part.  For a tagged
type declared in a visible part, a primitive function with a controlling
result shall not be declared in the private part, unless it is overriding a
function implicitly declared in the visible part.

In your code there is no function or abstract subprogram that is 
implicitly declared in the visible part! So the code result is a 
compiler error.


Note: AARM is for compiler developers, so it has changes which may 
or may not be valid in the L(RM). Also, since there are 3 current 
83/95/2005 specifications use should denote which version you are 
talking about. Because some things are valid in 83 that are not in 
95/2005, while others are only valid in 2005. And with GNAT 
inter-mixing specifications it can be confusing without using the 
GNAT language specifiction pragma.



In <1185401098.912519.245650@z28g2000prd.googlegroups.com>,  Adam Beneschan <adam@irvine.com> writes:
>I think the following is legal, but the version of GNAT I'm using
>rejects it, citing 3.9.3(10):
>
>package Pak1 is
>   type T1 is private;
>private
>   type T1 is tagged record
>      F1 : Integer;
>  end record;
>  function Func (X : Integer) return T2;
>end Pak1;
>
>3.9.3(10) says, in part, "For a tagged type declared in a visible
>part, a primitive function with a controlling result shall not be
>declared in the private part, unless it is overriding a function
>implicitly declared in the visible part."  My interpretation, though,
>is that it doesn't apply here, and that it only applies to types that
>are *visibly* tagged in the visible part---not to untagged private
>types whose full view is tagged.  The AARM reasoning for the rule has
>to do with other packages that declare type extensions of the type
>that wouldn't know that there's a private function that needs to be
>overridden---but in this case, other packages (except for private
>children, which have access to the entire private part of Pak1) can't
>declare a type extension of T1; so it would make sense that the rule
>wouldn't apply to this code.  Anyway, that's my interpretation, but it
>seems within the realm of possibility to interpret it the other way.
>
>So who's right?  Me or GNAT?
>
>                           -- Adam
>




^ permalink raw reply	[relevance 4%]

* Re: Finding out minimal allocation unit
  @ 2007-04-06 17:17  7%                 ` Simon Wright
  0 siblings, 0 replies; 96+ results
From: Simon Wright @ 2007-04-06 17:17 UTC (permalink / raw)


Stefan Bellon <sbellon@sbellon.de> writes:

> Well, our idea was to build a generic storage pool which can handle
> only memory chunks of one size. And the generic storage pool is
> instantiated with that size as generic parameter. So that each data
> structure instance (be it a list, a tree, hash table, ...) has its
> own storage pool with the exact Item_Type'Size instantiated.

I have a feeling that generics were problematic when I tried something
like this -- but you can always use a constraint:

   with System.Storage_Pools;
   with System.Storage_Elements;

   package BC.Support.Managed_Storage is

      pragma Elaborate_Body;

      package SSE renames System.Storage_Elements;
      package SSP renames System.Storage_Pools;

      type Pool (Chunk_Size : SSE.Storage_Count) is
        new SSP.Root_Storage_Pool with private;

from the Booch Components (this particular pool has a bug filed
against it at the moment, caused by a perceived need to allocate
variously-sized items from within large chunks and the resulting need
to chain the free list through chunks ...)



^ permalink raw reply	[relevance 7%]

* Re: Finding out minimal allocation unit
    @ 2007-04-06 12:38  5%         ` Stephen Leake
  1 sibling, 0 replies; 96+ results
From: Stephen Leake @ 2007-04-06 12:38 UTC (permalink / raw)


Stefan Bellon <sbellon@sbellon.de> writes:

> Are there examples of such a storage pool implementation around?

Here's the debug storage pool from SAL
(http://stephe-leake.org/ada/sal.html)

I wrote it to check for memory leaks in the SAL containers. It doesn't
resize the pool when it gets full, but you can add that using other
SAL containers :).

-- 
-- Stephe

--  Abstract:
--
--  A storage pool that keeps track of allocation and deallocation,
--  and allows queries. Used to verify storage management in container
--  tests. NOT task safe!
--
--  Copyright (C) 1997 - 1999, 2002 Stephen Leake.  All Rights Reserved.
--
--  This program is free software; you can redistribute it and/or
--  modify it under terms of the GNU General Public License as
--  published by the Free Software Foundation; either version 2, or
--  (at your option) any later version. This program is distributed in
--  the hope that it will be useful, but WITHOUT ANY WARRANTY; without
--  even the implied warranty of MERCHANTABILITY or FITNESS FOR A
--  PARTICULAR PURPOSE. See the GNU General Public License for more
--  details. You should have received a copy of the GNU General Public
--  License distributed with this program; see file COPYING. If not,
--  write to the Free Software Foundation, 59 Temple Place - Suite
--  330, Boston, MA 02111-1307, USA.

with System.Storage_Pools;
with System.Storage_Elements;
package Test_Storage_Pools is
   pragma Elaborate_Body; -- body depends on Ada.Text_IO;

   type String_Access_Constant_Type is access constant String;

   type Storage_Pool_Type
      (Pool_Size : System.Storage_Elements.Storage_Count;
       Name      : String_Access_Constant_Type) -- for debug messages
   is new System.Storage_Pools.Root_Storage_Pool with private;

   -----------
   --  Override Root_Storage_Pool operations

   procedure Allocate
      (Pool                     : in out Storage_Pool_Type;
       Storage_Address          :    out System.Address;
       Size_In_Storage_Elements : in     System.Storage_Elements.Storage_Count;
       Alignment                : in     System.Storage_Elements.Storage_Count);

   procedure Deallocate
      (Pool                     : in out Storage_Pool_Type;
       Storage_Address          : in     System.Address;
       Size_In_Storage_Elements : in     System.Storage_Elements.Storage_Count;
       Alignment                : in     System.Storage_Elements.Storage_Count);

   function Storage_Size (Pool : in Storage_Pool_Type) return System.Storage_Elements.Storage_Count;

   -----------
   --  New operations (alphabetical)

   function Allocate_Count (Pool : in Storage_Pool_Type) return Natural;
   --  Number of times Allocate has been called successfully.

   function Allocated_Elements (Pool : in Storage_Pool_Type) return Natural;
   --  Net allocated storage.

   procedure Check_Deallocated (Pool : in Storage_Pool_Type);
   --  If Allocated_Elements is not zero, print an error message and
   --  call Show_Storage.

   function Deallocate_Count (Pool : in Storage_Pool_Type) return Natural;
   --  Number of times Deallocate has been called.

   function Max_Allocated_Elements (Pool : in Storage_Pool_Type) return Natural;
   --  Max allocated storage, over lifetime of Pool.

   procedure Reset_Counts (Pool : in out Storage_Pool_Type);
   --  Reset Allocated and Deallocated counts to zero.

   procedure Set_Debug (Pool : in out Storage_Pool_Type; Debug : in Boolean);
   --  If Debug is True, Allocate, Deallocate, and Show_Storage print
   --  helpful messages to Standard_Output.

   procedure Show_Storage (Pool : in Storage_Pool_Type; Force_Debug : in Boolean := False);
   --  Print storage stats to Ada.Text_IO.Standard_Output, if
   --  Pool.Debug or Force_Debug is True.

private

   procedure Initialize (Pool : in out Storage_Pool_Type);

   type Block_Header_Type;
   type Block_Access_Type is access all Block_Header_Type;
   type Block_Header_Type is record
      Size : System.Storage_Elements.Storage_Count;
      Next : Block_Access_Type;
   end record;

   type Storage_Pool_Type
      (Pool_Size : System.Storage_Elements.Storage_Count;
       Name      : String_Access_Constant_Type)
   is new System.Storage_Pools.Root_Storage_Pool with
   record
      Debug                  : Boolean;
      Allocate_Count         : Natural;
      Deallocate_Count       : Natural;
      Allocated_Elements     : Natural;
      Max_Allocated_Elements : Natural;
      First_Free             : Block_Access_Type;
      Storage                : System.Storage_Elements.Storage_Array (1 .. Pool_Size);
      --  The first few elements of each free block contain the block
      --  header. Small requested blocks are padded up to at least the
      --  block header size. All blocks have alignment 8, to keep
      --  things simple.
   end record;

end Test_Storage_Pools;
--  Abstract:
--
--  see spec
--
--  Copyright (C) 1997 - 1999, 2002, 2003 Stephen Leake.  All Rights Reserved.
--
--  This program is free software; you can redistribute it and/or
--  modify it under terms of the GNU General Public License as
--  published by the Free Software Foundation; either version 2, or (at
--  your option) any later version. This program is distributed in the
--  hope that it will be useful, but WITHOUT ANY WARRANTY; without even
--  the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR
--  PURPOSE. See the GNU General Public License for more details. You
--  should have received a copy of the GNU General Public License
--  distributed with this program; see file COPYING. If not, write to
--  the Free Software Foundation, 59 Temple Place - Suite 330, Boston,
--  MA 02111-1307, USA.

pragma License (GPL);

with Ada.Text_IO;
with System.Address_To_Access_Conversions;
with Ada.Exceptions;
package body Test_Storage_Pools is

   Block_Header_Size : constant System.Storage_Elements.Storage_Count :=
      System.Storage_Elements.Storage_Count (Block_Header_Type'Size /
                                             System.Storage_Elements.Storage_Element'Size);

   --  This would be cleaner if Address_To_Access_Conversions took the
   --  pointer type as parameter, instead of declaring it!
   package Address_To_Block_Access is new System.Address_To_Access_Conversions (Block_Header_Type);

   function To_Block_Access
      (Pool    : in Storage_Pool_Type;
       Address : in System.Address)
       return Block_Access_Type
   is
      use type System.Address;
   begin
      if Address < Pool.Storage (1)'Address or
         Address > Pool.Storage (Pool.Pool_Size)'Address
      then
         raise Storage_Error;
      end if;
      return Block_Access_Type (Address_To_Block_Access.To_Pointer (Address));
   end To_Block_Access;

   function To_Address (Value : in Block_Access_Type) return System.Address
   is begin
      return Address_To_Block_Access.To_Address (Address_To_Block_Access.Object_Pointer (Value));
   end To_Address;

   function Aligned_Address
      (Address     : in System.Storage_Elements.Integer_Address;
       Alignment   : in System.Storage_Elements.Storage_Count)
      return System.Storage_Elements.Integer_Address
      --  Adjust Address upwards to next Alignment.
   is
      use System.Storage_Elements;
      Aligned : constant Integer_Address := Address + Address rem Integer_Address (Alignment);
   begin
      return Aligned;
   end Aligned_Address;

   -----------
   --  Override Root_Storage_Pool operations

   procedure Allocate
      (Pool                     : in out Storage_Pool_Type;
       Storage_Address          :    out System.Address;
       Size_In_Storage_Elements : in     System.Storage_Elements.Storage_Count;
       Alignment                : in     System.Storage_Elements.Storage_Count)
   is
      pragma Unreferenced (Alignment);

      use System.Storage_Elements;
      use Ada.Exceptions;
      Block                : Block_Access_Type := Pool.First_Free;
      Block_Start          : Integer_Address;
      Remaining_Block      : Block_Access_Type;
      Aligned              : Integer_Address;
      Prev                 : Block_Access_Type := null;

      --  We store a block header in free'd blocks, to maintain the
      --  free block list. So each allocated block has to be at least
      --  that big.
      Padded_Size    : constant Storage_Count := Storage_Count'Max (Size_In_Storage_Elements, Block_Header_Size);
      Allocated_Size : Storage_Count;
   begin
      if Pool.Debug then
         Ada.Text_IO.Put_Line ("allocating " &
                               Storage_Count'Image (Size_In_Storage_Elements) &
                               " from " &
                               Pool.Name.all);
      end if;

      Find_Free_Fit :
      loop
         if Block = null then
            Raise_Exception (Storage_Error'Identity, "Allocate: pool full (or fragmented)");
         end if;
         exit Find_Free_Fit when Block.Size >= Padded_Size;
         Prev := Block;
         Block := Block.Next;
      end loop Find_Free_Fit;

      --  Aligned points past the end of the just-allocated block; it
      --  is the base of the block of remaining space.
      Block_Start := To_Integer (To_Address (Block));
      Aligned     := Aligned_Address
          (Address   => Block_Start + Integer_Address (Padded_Size),
           Alignment => 8);

      Allocated_Size  := Storage_Count (Aligned - Block_Start);

      --  Allocated_Size might be > Block.Size because of alignment.
      --  In that case, their is no remaining space, so it can't be a
      --  block.
      if Block.Size > Allocated_Size and then Block.Size - Allocated_Size >= Block_Header_Size then
         --  Ok, remaining space can be a real block. But check to see
         --  if it is outside the pool!
         begin
            Remaining_Block := To_Block_Access (Pool, To_Address (Aligned));
         exception
         when Storage_Error =>
            Raise_Exception (Storage_Error'Identity, "Allocate: pool full (or fragmented)");
         end;

         if Prev = null then
            --  Allocated from first free block.
            Pool.First_Free := Remaining_Block;
         else
            Prev.Next := Remaining_Block;
         end if;

         Remaining_Block.all :=
            (Size => Block.Size - Allocated_Size,
             Next => Block.Next);
      else
         --  Remaining space too small for a block. Just link to next
         --  free block.
         if Prev = null then
            --  Allocated from first free block.
            Pool.First_Free := Pool.First_Free.Next;
         else
            Prev.Next := Block.Next;
         end if;

      end if;

      Pool.Allocate_Count         := Pool.Allocate_Count + 1;
      --  Only track actual request in Allocated_Elements, since
      --  that's what will be deallocated.
      Pool.Allocated_Elements     := Pool.Allocated_Elements + Natural (Size_In_Storage_Elements);
      Pool.Max_Allocated_Elements := Natural'Max (Pool.Allocated_Elements, Pool.Max_Allocated_Elements);
      Storage_Address             := To_Address (Block);
   end Allocate;

   procedure Deallocate
      (Pool                     : in out Storage_Pool_Type;
       Storage_Address          : in     System.Address;
       Size_In_Storage_Elements : in     System.Storage_Elements.Storage_Count;
       Alignment                : in     System.Storage_Elements.Storage_Count)
   is
      pragma Unreferenced (Alignment);

      use System.Storage_Elements;
      Block : Block_Access_Type;
   begin
      if Pool.Debug then
         Ada.Text_IO.Put_Line ("deallocating " &
                               Storage_Count'Image (Size_In_Storage_Elements) &
                               " from " &
                               Pool.Name.all);
      end if;

      --  Store a free-list block header in the free'd block, add
      --  block to head of free list.

      Block := To_Block_Access (Pool, Storage_Address);

      Block.all :=
         (Size => Size_In_Storage_Elements,
          Next => Pool.First_Free);

      Pool.First_Free := Block;

      Pool.Deallocate_Count := Pool.Deallocate_Count + 1;
      Pool.Allocated_Elements := Pool.Allocated_Elements - Natural (Size_In_Storage_Elements);
   exception
   when Storage_Error =>
      Ada.Exceptions.Raise_Exception
         (Program_Error'Identity,
          "Address not from storage pool " & Pool.Name.all);
   end Deallocate;

   function Storage_Size (Pool : Storage_Pool_Type) return System.Storage_Elements.Storage_Count
   is begin
      return Pool.Pool_Size;
   end Storage_Size;

   -----------
   --  New operations

   function Allocate_Count (Pool : Storage_Pool_Type) return Natural
   is begin
      return Pool.Allocate_Count;
   end Allocate_Count;

   function Allocated_Elements (Pool : Storage_Pool_Type) return Natural
   is begin
      return Pool.Allocated_Elements;
   end Allocated_Elements;

   procedure Check_Deallocated (Pool : in Storage_Pool_Type)
   is begin
      if Pool.Allocated_Elements /= 0 then
         Ada.Text_IO.Put_Line ("Error : " & Pool.Name.all & " not deallocated");
         Show_Storage (Pool, Force_Debug => True);
      end if;
   end Check_Deallocated;

   function Deallocate_Count (Pool : Storage_Pool_Type) return Natural
   is begin
      return Pool.Deallocate_Count;
   end Deallocate_Count;

   function Max_Allocated_Elements (Pool : Storage_Pool_Type) return Natural
   is begin
      return Pool.Max_Allocated_Elements;
   end Max_Allocated_Elements;

   procedure Reset_Counts (Pool : in out Storage_Pool_Type)
   is begin
      Pool.Deallocate_Count := 0;
      Pool.Allocate_Count := 0;
      Pool.Max_Allocated_Elements := Pool.Allocated_Elements;
   end Reset_Counts;

   procedure Set_Debug (Pool : in out Storage_Pool_Type; Debug : in Boolean)
   is begin
      Pool.Debug := Debug;
   end Set_Debug;

   procedure Show_Storage (Pool : in Storage_Pool_Type; Force_Debug : in Boolean := False)
   is
      use Ada.Text_IO;
   begin
      if Pool.Debug or Force_Debug then
         Put_Line (Pool.Name.all & " : ");
         Put_Line ("Allocate_Count         => " & Natural'Image (Pool.Allocate_Count));
         Put_Line ("Deallocate_Count       => " & Natural'Image (Pool.Deallocate_Count));
         Put_Line ("Allocated_Elements     => " & Natural'Image (Pool.Allocated_Elements));
         Put_Line ("Max_Allocated_Elements => " & Natural'Image (Pool.Max_Allocated_Elements));
      end if;
   end Show_Storage;

   -----------
   --  Private operations

   procedure Initialize (Pool : in out Storage_Pool_Type)
   is
      use System.Storage_Elements;
      use Ada.Exceptions;
   begin
      if Pool.Pool_Size < Block_Header_Size then
         Raise_Exception (Storage_Error'Identity, "Initialize: pool_size < header_size");
      end if;

      Pool.Debug                  := False;
      Pool.Allocate_Count         := 0;
      Pool.Deallocate_Count       := 0;
      Pool.Allocated_Elements     := 0;
      Pool.Max_Allocated_Elements := 0;
      Pool.First_Free             := To_Block_Access
         (Pool,
          To_Address
            (Aligned_Address
               (Address   => To_Integer (Pool.Storage'Address),
                Alignment => 8)));
      Pool.First_Free.all         := (Pool.Pool_Size, null);
   end Initialize;

end Test_Storage_Pools;



^ permalink raw reply	[relevance 5%]

* A novel design of linked lists (was: Address of an object)
@ 2006-09-19 13:30  4% Dmitry A. Kazakov
  0 siblings, 0 replies; 96+ results
From: Dmitry A. Kazakov @ 2006-09-19 13:30 UTC (permalink / raw)


[ It seems to me that some people have an impression that I am looking for
something extraordinary when asking for the object address, so I feel
necessary to provide an elaborated example where it were needed. ]

Let's consider referential double-linked lists as an example. The drawbacks
of the Ada.Containers design are obvious. A typical design of such lists in
other languages would be adding Prev, Next pointers to the elements. Note
also, that we wished to have linked lists of elements which might
participate in many lists simultaneously. We also liked to statically check
the types of such lists, so that paths in different lists could never
converge.

There are two ways to do add links Prevs and Nexts. One of them is to do it
upon inheritance. Another is by using new elements containing pointers to
the "true" elements.

1. The variant with inheritance is not an option in current Ada, because of
lack of MI. Even with MI it faces the problem that links has to be added to
the base type. That would require downcasting later, all over the program.
Adding links in the leaves of the type hierarchy would break it apart and
also freeze the types for future derivation. Ad-hoc supertypes could help,
but, firstly, they are not supported and, secondly, they barely could have
referential semantics. So the elements will require copying.

2. The variant with pointers is not a solution at all, because, honestly,
it would be a list of pointers rather than of the elements.

An alternative to these two variants would be to add links transparently
without intervening with *what* is the element. Ada's pools provide this
functionality. The package could go as follows:

with System;                   use System;
with System.Storage_Elements;  use System.Storage_Elements;
with System.Storage_Pools;     use System.Storage_Pools;

generic
   type List_Identification_Type is (<>);
   type List_Item_Type (<>) is limited private;
   Pool : in out Root_Storage_Pool'Class;
package Generic_Linked_Lists is

Here:

- List_Identification_Type is an enumeration type to name the lists. An
element may participate in exactly one list corresponding to the given
value of List_Identification_Type.
- List_Item_Type is the type of elements.
- Pool is the pool where elements will be eventually allocated

The package defines its own pool type, which takes memory from another pool
and the object Items_Pool of this type bound to the actual pool passed as
the generic formal parameter Pool. [ It would be nice to default it to the
standard pool, but, I don't know any good way to do it. ]

   type Items_Storage_Pool (Host : access Root_Storage_Pool'Class) is
      new Root_Storage_Pool with null record;
   ...
   Items_Pool : Items_Storage_Pool (Pool'Access);

Then it defines a pointer type to refer the list items:

   type Item_Ptr is access List_Item_Type;
   for Item_Ptr'Storage_Pool use Items_Pool;

Then it defines the list operations in the terms of this pointer type. Note
that unlikely to Ada.Containers the semantics is referential. Nothing is
copied. So Insert looks like:

   procedure Insert
             (  List  : List_Identification_Type;
                Head  : in out Item_Ptr;
                Item  : Item_Ptr;
                Order : Item_Disposition := After
             );

- List identifies the list type we are dealing with. The same item can be
situated in as many lists as the range of List_Identification_Type.

- Head is the pointer to the list. In can be null. when the first item is
inserted.

- Item is the pointer to the item to insert.

- Order is an enumeration After or Before. When Item is placed before Head,
Head is set to Item.

The use of Insert is trivial and need not to be illustrated. A new Item is
created using plain "new." Other operations could be:

   procedure Move
             (  List   : List_Identification_Type;
                Target : in out Item_Ptr;
                Item   : Item_Ptr;
                Source : in out Item_Ptr;
                Order  : Item_Disposition := After
             );

Moves Item form one list to another. Both lists are of the same type.

   function Next
            (  List : List_Identification_Type;
               Item : Item_Ptr
            )  return Item_Ptr;

Returns the next item in the list

   function Previous
            (  List : List_Identification_Type;
               Item : Item_Ptr
            )  return Item_Ptr;

   procedure Remove
             (  List : List_Identification_Type;
                Head  : in out Item_Ptr; 
                Item  : Item_Ptr;
                Order : Item_Disposition := After
             );

Removes Item from the list.

For dealing with the elements of one list type without specifying the type,
a small wrapper package could be provided:

generic
   List : List_Identification_Type;
package Generic_Linked_Lists.Generic_List is
   type List_Ptr is new Item_Ptr;
   procedure Insert
             (  Head  : in out List_Ptr;
                Item  : Item_Ptr;
                Order : Item_Disposition := After
             );
   procedure Move
             (  Target : in out List_Ptr;
                Item   : Item_Ptr;
                Source : in out List_Ptr;
                Order  : Item_Disposition := After
             );
   function Next (Item : Item_Ptr)  return List_Ptr;
   function Previous (Item : Item_Ptr) return List_Ptr;
   procedure Remove
             (  Head  : in out List_Ptr; 
                Item  : Item_Ptr;
                Order : Item_Disposition := After
             );
end Generic_Linked_Lists.Generic_List;

Note that locally defined List_Ptr is a "list specific" pointer, while Item
is a sort of "class-wide" pointer, valid across all list types. So Item in
all calls is just a pointer to an item, while Head controls "dispatch" to
the proper list. [ Of course no dynamic dispatch happens. It is a static
polymorphism. ]

Now how this works. When an element is allocated, Allocate of
Items_Storage_Pool places the array of links

   type List_Header is record
      Next : Address;
      Prev : Address;
   end record;
   type Item_Header is array (List_Identification_Type) of List_Header;

in front of it. Allocate looks like this:

   procedure Allocate
             (  Pool            : in out Items_Storage_Pool;
                Storage_Address : out Address; 
                Size            : Storage_Count;
                Alignment       : Storage_Count
             )  is
      Header_Alignment : constant Storage_Count :=
         Storage_Count'Max (Item_Header'Alignment, Alignment);
      Header_Offset    : constant Storage_Offset :=
         Header_Size + (-Header_Size) mod Header_Alignment;
   begin
      Allocate -- Grab memory in the host pool
      (  Pool.Host.all,
         Storage_Address,
         Size + Header_Offset,
         Header_Alignment
      );
      Storage_Address := Storage_Address + Header_Offset;
      declare
         Header : Item_Header renames To_Header (Storage_Address).all;
      begin
         for List in Header'Range loop
            Header (List).Next := Null_Address; -- Links initialization
         end loop;
      end;
   end Allocate;

When Next, Insert etc are called Item_Header is obtained from the pointer
and, the rest is obvious. For example Next:

   function Next
            (  List : List_Identification_Type;
               Item : Item_Ptr
            )  return Item_Ptr is
   begin
      return To_Item_Ptr (To_Header (From_Item_Ptr (Item)) (List).Next);
   end Next;

It works perfectly well for all types except ones for which the compiler
mangles pointers, as I have explained in other thread.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 4%]

* Re: Memory Mapped Storage Pools.
       [not found]     <pan.2005.10.26.22.16.09.200167@nowhere.net>
@ 2005-10-26  1:41  6% ` Dan Baysinger
  0 siblings, 0 replies; 96+ results
From: Dan Baysinger @ 2005-10-26  1:41 UTC (permalink / raw)


I use mmap'ed storage for essentially the same reasons that you gave. 
However, I just derived from System.Storage_Pools.Root_Storage_Pool and 
  overrode all of the subprograms to allocate the requested objects 
using mmap and deallocate with unmap.

The Root_Storage _Pool type was extended with a private pointer to a 
linked list of allocations made for the client's storage pool.  I used 
an opaque type (incomplete declaration in the spec's private area and 
completion in the body) for the elements of the allocation linked list 
to discourage (not actually prevent) users from trying to manipulate the 
allocations directly.

You need to override finalization so that it walks the allocation list 
and unmaps all allocations for the user's storage pool.

Also, I mmapped to /dev/zero so that an actual file was not created.

This has worked quite well for my purposes, and its usage is completely 
compatible with the storage_pool specification for access types, the 
'new' allocator, and Ada.Unchecked_Deallocation.  From the user's 
perspective the behavior is identical to that of a storage pool created 
System.Storage_Pools.Root_Storage_Pool.

Dan Baysinger




Freejack wrote:

> Ada Storage Pools, in Unix/Posix type environments, are typically
> handled via the omnipresent C malloc() routine. While this undoubtedly
> simplifies compiler/runtime development, it has left me desiring a
> mechanism with a bit more control.
> 
> So I've begun working on a library that allocates storage pools through
> the lower level mmap() suite of system utilities. I'm tentatively calling
> it Custom_Storage.Mapped_Pools
> 
> It's intended use is for very large allocations that are intended to be
> returned to the system upon finalization, rather than having the extra
> memory linger in the program's process "space".
> 
> Such a package's interfaces need to be carefully designed so as to prevent
> it's client developers from going ape shit every time  they need a clear
> definition of exactly what the routine is going to do to the rest of their
> process space. Hence I would like some advice. How would you like to see
> such a package laid out? Should I make a set of thick or thin bindings to
> the mmap() facilities to go along with the Mapped_Pools package? What
> things should I keep in mind as to making the package portable to other
> environments with an mmap() facility?
> 
> Any tips would be appreciated.
> 
> Freejack




^ permalink raw reply	[relevance 6%]

* Re: Teaching new tricks to an old dog (C++ -->Ada)
  @ 2005-03-08 20:59  4%                       ` Dmitry A. Kazakov
  0 siblings, 0 replies; 96+ results
From: Dmitry A. Kazakov @ 2005-03-08 20:59 UTC (permalink / raw)


On Tue, 08 Mar 2005 15:13:20 -0500, CTips wrote:

> Dmitry A. Kazakov wrote:
> 
>> On Tue, 08 Mar 2005 13:33:33 -0500, CTips wrote:
>> 
>>>How easy is it to build an arena allocator in Ada?
>> 
>> It is trivial:
>> 
>> type Object is ...;
>> type Object_Ptr is access Object;
>> for Object_Ptr'Storage_Pool use My_Arena;
>> 
>> Here you are:
>> 
>> Ptr : Object_Ptr := new Object; -- This allocates it in My_Arena
> 
> And how is My_Arena defined? Is it just a blob of memory? Or is it a 
> "class" that can invoke sbrk (or whatever) when it needs to?

It is completely up to you. My_Arena has to be derived from
System.Storage_Pools.Root_Storage_Pool. Which is the abstract base of all
storage pools. The implementation of Allocate and Deallocate is at your
discretion. For an arena the pool may contain a statically allocated array
organized as a stack. Deallocate could be then void, or it can pop
everything above it as in mark'n'release. A more advanced application could
allocate memory in segments at request etc. For a sample implementation of
a segmented stack pool see:

http://www.dmitry-kazakov.de/ada/components.htm#Pools_etc 

>>>Given a processor with load-word-locked and store-word-conditional, how 
>>>would I build an atomic increment function?
>> 
>> Why should I have atomic increment function? Ada has native concurrency
>> support. But if somebody would need that extremely low level thing as
>> atomic integers, then:
>> 
>> protected type Atomic_Integer is
>>    procedure Increment;
>> private
>>    Value : Integer;
>> end Atomic_Integer;
>> 
>> -- Implementation
>> protected body Atomic_Integer is
>>    procedure Increment is
>>    begin
>>       Value := Value + 1;
>>    end Increment;
>> end Atomic_Integer;
>> 
> Will that generate:
>    L0:
>        lwlock temp,&Value
>        add    temp,temp,1
>        stwcond temp,&Value
>        if( failed ) goto L0;
> or will it generate something much more heavy-weight.

Ask your compiler vendor. Though it wouldn't be necessarily polling. Also
usually protected objects are not used for so utterly fine-grained mutual
exclusion/locking. Atomic integer increment is normally just a small part
of some larger (but not lengthy) operation. For example, placing something
in a queue. Therefore spinning for a lock (which probably would be the
implementation) will likely be less expensive than some tricky guards
attached to each and every instruction. Note also that at such a low level
it would be very difficult if possible to maintain data consistency.
Compiler simply does not know what is related to what and will try to cope
with the worst case scenario. Protected types in Ada are to describe this
sort of semantics. So in the end atomic integers are pretty useless, no
matter how efficient they could be implemented.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 4%]

* Re: No call for Ada (was Re: Announcing new scripting/prototyping language)
  @ 2004-04-03 15:09  4%                 ` Robert I. Eachus
  0 siblings, 0 replies; 96+ results
From: Robert I. Eachus @ 2004-04-03 15:09 UTC (permalink / raw)


Martin Krischik wrote:

> Wich reminds me. Does anybody know what - should - happen when:
> 
> Access_X is access X;
> All_X is access all X;
> 
> for Access_X'Pool use Access_Pool;
> for All_X'Pool use All_Pool;
> 
> Some_X : Access_X := new X;
> Another_X : All_X := Some_X;
> 
> function Deallocate is new Unchecked_Deallocation (X, All_X);
> 
> begin
>     Deallocate (Another_X);
> end;

No.  The execution of the call to Deallocate is erroneous.  That means 
that anything can happen: RM 13.11.2(16) "The execution of a call to an 
instance of Unchecked_Deallocation is erroneous if the object was 
created other than by an allocator for an access type whose pool is 
Name'Storage_Pool."

The proper thing to do is to do the necessary check inside your 
Deallocate.  Unfortunately, there is no language defined attribute that 
can be used to determine the storage pool associated with an access 
object.  Of course, if you define a storage pool, you can also provide 
such an operation:

function Storage_Pool_Of(X: Address) return Root_Storage_Pool'Class;

But it would be nice to have 'Storage_Pool defined for both subtypes (as 
at present) and for all access objects.  That way you could do the 
necessary check to see whether access values denote an object in the 
default storage pool.  In fact, it might be better to have both 
'Storage_Pool, and 'Allocated, where Object'Allocated returns a boolean. 
  ('Storage_Pool should raise an exception if called with a parameter 
that does not belong to any storage pool.)  Or perhaps we could add a value:

No_Storage_Pool: constant Root_Storage_Pool;

to System.Storage_Pools.

However, in the meantime, the best policy is probably to only 
instantiate Unchecked_Deallocation for types which are not declared 
access all.

-- 

                                           Robert I. Eachus

"The terrorist enemy holds no territory, defends no population, is 
unconstrained by rules of warfare, and respects no law of morality. Such 
an enemy cannot be deterred, contained, appeased or negotiated with. It 
can only be destroyed--and that, ladies and gentlemen, is the business 
at hand."  -- Dick Cheney




^ permalink raw reply	[relevance 4%]

* Re: Question about OO programming in Ada
  2003-12-03 14:11  0%                         ` Ludovic Brenta
@ 2003-12-03 14:45  0%                           ` Dmitry A. Kazakov
  0 siblings, 0 replies; 96+ results
From: Dmitry A. Kazakov @ 2003-12-03 14:45 UTC (permalink / raw)


On 03 Dec 2003 15:11:51 +0100, Ludovic Brenta
<ludovic.brenta@insalien.org> wrote:

>Dmitry A. Kazakov <mailbox@dmitry-kazakov.de> writes:
>
>But the GNAT doc says that deallocation occurs when the storage pool
>is finalized.  Your example does not demonstrate this since your
>storage pool does not override Finalize.

Of course, when storage pool object gets destroyed the memory of the
objects allocated there will be reclaimed (though without calling
Unchecked_Deallocate on them, in a hope that it was already made
before)

>> with Ada.Finalization;
>> with System;  use System;
>> with System.Storage_Elements;  use System.Storage_Elements;
>> with System.Storage_Pools;  use System.Storage_Pools;
>> package A is
>>    type Misty is
>>       new Ada.Finalization.Limited_Controlled with null record;
>>    procedure Finalize (X : in out Misty);
>>    type Pool is new Root_Storage_Pool with record
>>       Free   : Storage_Offset := 1;
>>       Memory : aliased Storage_Array (1..1024);
>>    end record;
>>    procedure Allocate
>>              (  Stack     : in out Pool;
>>                 Place     : out Address;
>>                 Size      : Storage_Count;
>>                 Alignment : Storage_Count
>>              );
>>    procedure Deallocate
>>              (  Stack     : in out Pool;
>>                 Place     : Address;
>>                 Size      : Storage_Count;
>>                 Alignment : Storage_Count
>>              );
>>    function Storage_Size (Stack : Pool) return Storage_Count; 
>
>     procedure Finalize (Stack : in out Pool);
>
>> end A;
>> 
>> with Text_IO; use Text_IO;
>> package body A is
>>    procedure Finalize (X : in out Misty) is
>>    begin
>>       Put_Line ("finalized!");
>>    end Finalize;
>>    procedure Allocate
>>              (  Stack     : in out Pool;
>>                 Place     : out Address;
>>                 Size      : Storage_Count;
>>                 Alignment : Storage_Count
>>              )  is
>>    begin -- Alignment is ignored for simplicity sake
>>       Put_Line ("Allocated");
>>       Place := Stack.Memory (Stack.Free)'Address;
>>       Stack.Free := Stack.Free + Size;
>>    end Allocate;
>>    procedure Deallocate
>>              (  Stack     : in out Pool;
>>                 Place     : Address;
>>                 Size      : Storage_Count;
>>                 Alignment : Storage_Count
>>              )  is
>>    begin -- Does nothing
>>       Put_Line ("Deallocated");   
>>    end Deallocate;
>>    function Storage_Size (Stack : Pool) return Storage_Count is
>>    begin
>>       return 0;
>>    end Storage_Size; 
>
>     procedure Finalize (Stack : in out Pool) is
>     begin
>        Put_Line ("Deallocating all objects.");
>        Deallocate (Stack, To_Address (Integer_Address (0)), 0, 0);
>     end Finalize;
>
>> end A;
>> 
>> with A;  use A;
>> with Text_IO;  use Text_IO;
>> procedure Test is
>>    Storage : Pool;
>> begin
>>    Put_Line ("Begin of a scope");
>>    declare
>>       type Pointer is access Misty;
>>       for Pointer'Storage_Pool use Storage;
>>       X : Pointer;
>>    begin
>>       X := new Misty; -- This is not dangled!
>>    end;
>>    Put_Line ("End of the scope");
>> end Test;
>> 
>> With GNAT Test should print:
>> 
>> Begin of a scope
>> Allocated
>> finalized!
>
>  Deallocating all objects.  (yes, I tested it)
>  Deallocated
>
>> End of the scope
>> 
>> So even with a user-defined pool it does not work as "should be".
>> 
>> Of course one could call Unchecked_Deallocation from Finalize as
>> Pascal noted. But it would be awful for an uncounted number of
>> reasons. To start with, you never know, who calls Finalize, then you
>> have no pointer to the object, you can get it, but that will be of a
>> generic access type, so if you have several pools how do you know,
>> where the object was allocated? and so on and so far.
>
>The finalization is not that of the allocated objects, it is that of
>the storage pool itself (storage pools are limited controlled).  So,
>this scheme actually works pretty well and is quite straightforward to
>implement.

Only if the scope of the access type and the scope of the pool object
are same.

>The part that I do not understand is why GNAT's Unbounded_Reclaim_Pool
>doesn't seem to be selected for a local access type.  I think this
>either contradicts the GNAT reference manual, or is an instance of me
>not understanding it.

But to make it working there should be a new object of
Unbounded_Reclaim_Pool per scope:

declare
   type Pointer is access Controlled_Something;

should be translated into:

declare
   Local_Pool : Unbounded_Reclaim_Pool;
   type Pointer is access Controlled_Something;
   for Pointer'Storage_Pool use Local_Pool;

Theoretically it is possible, but practically? Maybe there is only one
object of Unbounded_Reclaim_Pool [per task?]

--
Regards,
Dmitry Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 0%]

* Re: Question about OO programming in Ada
  2003-12-03 13:41  6%                       ` Dmitry A. Kazakov
@ 2003-12-03 14:11  0%                         ` Ludovic Brenta
  2003-12-03 14:45  0%                           ` Dmitry A. Kazakov
  0 siblings, 1 reply; 96+ results
From: Ludovic Brenta @ 2003-12-03 14:11 UTC (permalink / raw)


Dmitry A. Kazakov <mailbox@dmitry-kazakov.de> writes:

But the GNAT doc says that deallocation occurs when the storage pool
is finalized.  Your example does not demonstrate this since your
storage pool does not override Finalize.

> with Ada.Finalization;
> with System;  use System;
> with System.Storage_Elements;  use System.Storage_Elements;
> with System.Storage_Pools;  use System.Storage_Pools;
> package A is
>    type Misty is
>       new Ada.Finalization.Limited_Controlled with null record;
>    procedure Finalize (X : in out Misty);
>    type Pool is new Root_Storage_Pool with record
>       Free   : Storage_Offset := 1;
>       Memory : aliased Storage_Array (1..1024);
>    end record;
>    procedure Allocate
>              (  Stack     : in out Pool;
>                 Place     : out Address;
>                 Size      : Storage_Count;
>                 Alignment : Storage_Count
>              );
>    procedure Deallocate
>              (  Stack     : in out Pool;
>                 Place     : Address;
>                 Size      : Storage_Count;
>                 Alignment : Storage_Count
>              );
>    function Storage_Size (Stack : Pool) return Storage_Count; 

     procedure Finalize (Stack : in out Pool);

> end A;
> 
> with Text_IO; use Text_IO;
> package body A is
>    procedure Finalize (X : in out Misty) is
>    begin
>       Put_Line ("finalized!");
>    end Finalize;
>    procedure Allocate
>              (  Stack     : in out Pool;
>                 Place     : out Address;
>                 Size      : Storage_Count;
>                 Alignment : Storage_Count
>              )  is
>    begin -- Alignment is ignored for simplicity sake
>       Put_Line ("Allocated");
>       Place := Stack.Memory (Stack.Free)'Address;
>       Stack.Free := Stack.Free + Size;
>    end Allocate;
>    procedure Deallocate
>              (  Stack     : in out Pool;
>                 Place     : Address;
>                 Size      : Storage_Count;
>                 Alignment : Storage_Count
>              )  is
>    begin -- Does nothing
>       Put_Line ("Deallocated");   
>    end Deallocate;
>    function Storage_Size (Stack : Pool) return Storage_Count is
>    begin
>       return 0;
>    end Storage_Size; 

     procedure Finalize (Stack : in out Pool) is
     begin
        Put_Line ("Deallocating all objects.");
        Deallocate (Stack, To_Address (Integer_Address (0)), 0, 0);
     end Finalize;

> end A;
> 
> with A;  use A;
> with Text_IO;  use Text_IO;
> procedure Test is
>    Storage : Pool;
> begin
>    Put_Line ("Begin of a scope");
>    declare
>       type Pointer is access Misty;
>       for Pointer'Storage_Pool use Storage;
>       X : Pointer;
>    begin
>       X := new Misty; -- This is not dangled!
>    end;
>    Put_Line ("End of the scope");
> end Test;
> 
> With GNAT Test should print:
> 
> Begin of a scope
> Allocated
> finalized!

  Deallocating all objects.  (yes, I tested it)
  Deallocated

> End of the scope
> 
> So even with a user-defined pool it does not work as "should be".
> 
> Of course one could call Unchecked_Deallocation from Finalize as
> Pascal noted. But it would be awful for an uncounted number of
> reasons. To start with, you never know, who calls Finalize, then you
> have no pointer to the object, you can get it, but that will be of a
> generic access type, so if you have several pools how do you know,
> where the object was allocated? and so on and so far.

The finalization is not that of the allocated objects, it is that of
the storage pool itself (storage pools are limited controlled).  So,
this scheme actually works pretty well and is quite straightforward to
implement.

The part that I do not understand is why GNAT's Unbounded_Reclaim_Pool
doesn't seem to be selected for a local access type.  I think this
either contradicts the GNAT reference manual, or is an instance of me
not understanding it.

-- 
Ludovic Brenta.



^ permalink raw reply	[relevance 0%]

* Re: Question about OO programming in Ada
  @ 2003-12-03 13:41  6%                       ` Dmitry A. Kazakov
  2003-12-03 14:11  0%                         ` Ludovic Brenta
  0 siblings, 1 reply; 96+ results
From: Dmitry A. Kazakov @ 2003-12-03 13:41 UTC (permalink / raw)


On 03 Dec 2003 13:49:20 +0100, Ludovic Brenta
<ludovic.brenta@insalien.org> wrote:

>Dmitry A. Kazakov <mailbox@dmitry-kazakov.de> writes:
>
>> On 03 Dec 2003 10:29:17 +0100, Pascal Obry <p.obry@wanadoo.fr> wrote:
>> 
>> >
>> >Dmitry A. Kazakov <mailbox@dmitry-kazakov.de> writes:
>> >
>> >> All controlled objects allocated by the allocator new, being not
>> >> explicity destroyed using Unchecked_Deallocation, will be destroyed
>> >> upon finalization of the access type.
>> >
>> >There is no magic done by Finalize here! Finalize gives a chance to the
>> >component implementer to do the memory deallocation for the end user. That's
>> >all.
>> 
>> Yes, you are right. Controlled objects will be finalized, but the
>> memory might be not reclaimed. At least, it seems that ARM does not
>> require that.
>
>I am confused.  I thought that the storage would be reclaimed when the
>access type went out of scope, but I tested it with GNAT 3.15p and it
>isn't.  Granted, the ARM doesn't seem to require it, but GNAT has the
>following in its reference manual:
>
>    *53*.  The manner of choosing a storage pool for an access type
>    when `Storage_Pool' is not specified for the type.  See 13.11(17).
>
>    There are 3 different standard pools used by the compiler when
>    `Storage_Pool' is not specified depending whether the type is
>    local to a subprogram or defined at the library level and whether
>    `Storage_Size'is specified or not.  See documentation in the
>    runtime library units `System.Pool_Global', `System.Pool_Size' and
>    `System.Pool_Local' in files `s-poosiz.ads', `s-pooglo.ads' and
>    `s-pooloc.ads' for full details on the default pools used.
>
>And in s-pooloc.ads it says:
>
>   ----------------------------
>   -- Unbounded_Reclaim_Pool --
>   ----------------------------
>
>   --  Allocation strategy:
>
>   --    Call to malloc/free for each Allocate/Deallocate
>   --    no user specifiable size
>   --    Space of allocated objects is reclaimed at pool finalization
>   --    Manages a list of allocated objects
>
>   --  Default pool in the compiler for access types locally declared
>
>   type Unbounded_Reclaim_Pool is new [...]
>
>I tried to run a test program in gnatgdb but couldn't check what the
>storage pool actually was.  Would anyone care to shed some light on
>this?  Now I'm really curious.

No storage pool can help, if deallocator is not called. If we continue
the example:

with Ada.Finalization;
with System;  use System;
with System.Storage_Elements;  use System.Storage_Elements;
with System.Storage_Pools;  use System.Storage_Pools;
package A is
   type Misty is
      new Ada.Finalization.Limited_Controlled with null record;
   procedure Finalize (X : in out Misty);
   type Pool is new Root_Storage_Pool with record
      Free   : Storage_Offset := 1;
      Memory : aliased Storage_Array (1..1024);
   end record;
   procedure Allocate
             (  Stack     : in out Pool;
                Place     : out Address;
                Size      : Storage_Count;
                Alignment : Storage_Count
             );
   procedure Deallocate
             (  Stack     : in out Pool;
                Place     : Address;
                Size      : Storage_Count;
                Alignment : Storage_Count
             );
   function Storage_Size (Stack : Pool) return Storage_Count; 
end A;

with Text_IO; use Text_IO;
package body A is
   procedure Finalize (X : in out Misty) is
   begin
      Put_Line ("finalized!");
   end Finalize;
   procedure Allocate
             (  Stack     : in out Pool;
                Place     : out Address;
                Size      : Storage_Count;
                Alignment : Storage_Count
             )  is
   begin -- Alignment is ignored for simplicity sake
      Put_Line ("Allocated");
      Place := Stack.Memory (Stack.Free)'Address;
      Stack.Free := Stack.Free + Size;
   end Allocate;
   procedure Deallocate
             (  Stack     : in out Pool;
                Place     : Address;
                Size      : Storage_Count;
                Alignment : Storage_Count
             )  is
   begin -- Does nothing
      Put_Line ("Deallocated");   
   end Deallocate;
   function Storage_Size (Stack : Pool) return Storage_Count is
   begin
      return 0;
   end Storage_Size; 
end A;

with A;  use A;
with Text_IO;  use Text_IO;
procedure Test is
   Storage : Pool;
begin
   Put_Line ("Begin of a scope");
   declare
      type Pointer is access Misty;
      for Pointer'Storage_Pool use Storage;
      X : Pointer;
   begin
      X := new Misty; -- This is not dangled!
   end;
   Put_Line ("End of the scope");
end Test;

With GNAT Test should print:

Begin of a scope
Allocated
finalized!
End of the scope

So even with a user-defined pool it does not work as "should be".

Of course one could call Unchecked_Deallocation from Finalize as
Pascal noted. But it would be awful for an uncounted number of
reasons. To start with, you never know, who calls Finalize, then you
have no pointer to the object, you can get it, but that will be of a
generic access type, so if you have several pools how do you know,
where the object was allocated? and so on and so far.

--
Regards,
Dmitry Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 6%]

* Re: Q:Usage of storage Pools
  2003-06-01  8:05  5%         ` Simon Wright
@ 2003-06-02 19:28  0%           ` Michael Erdmann
  0 siblings, 0 replies; 96+ results
From: Michael Erdmann @ 2003-06-02 19:28 UTC (permalink / raw)


Simon Wright wrote:
> Michael Erdmann <michael.erdmann@snafu.de> writes:
> 
> 
>>Since the pool knows the sturcture of the objects to be stored there
>>he is able to derefernce the pointers like Next when wiriting it
>>into a file.
> 
> 
> This is a very clever pool!

I will publish the software after it has been tested.

> 
> The BCs do this by passing the pool as a generic parameter:
> 
> generic
>    Storage : in out System.Storage_Pools.Root_Storage_Pool'Class;
> package BC.Containers.Collections.Unbounded is





^ permalink raw reply	[relevance 0%]

* Re: Q:Usage of storage Pools
  @ 2003-06-01  8:05  5%         ` Simon Wright
  2003-06-02 19:28  0%           ` Michael Erdmann
  0 siblings, 1 reply; 96+ results
From: Simon Wright @ 2003-06-01  8:05 UTC (permalink / raw)


Michael Erdmann <michael.erdmann@snafu.de> writes:

> Since the pool knows the sturcture of the objects to be stored there
> he is able to derefernce the pointers like Next when wiriting it
> into a file.

This is a very clever pool!

The BCs do this by passing the pool as a generic parameter:

generic
   Storage : in out System.Storage_Pools.Root_Storage_Pool'Class;
package BC.Containers.Collections.Unbounded is



^ permalink raw reply	[relevance 5%]

* Re: Generic and Access problem
@ 2003-01-09 11:03  5% Grein, Christoph
  0 siblings, 0 replies; 96+ results
From: Grein, Christoph @ 2003-01-09 11:03 UTC (permalink / raw)


generic

   type Item_Type is private;
   type Index_Type is (<>);

package Generic_Pool is

   type Id_Type is private;
   type Reference_Type is access all Item_Type;

   -- There is no operation by which an object of type Id_Type
   -- can get a value.
   -- So how is an object of Item_Type supposed to be stored in Buf?
   -- If you've solved this problem, perhaps your problem with pointer
   -- lifetime is also solved.

   function Item (P: Id_Type; Ix: Index_Type) return Reference_Type;

private

   type Buffer_Type is array (Index_Type) of aliased Item_Type;

   type Id_Type is
   record
      Buf               : Buffer_Type;
      None_Allocated_Yet: Boolean    := True;
      Last_Used         : Index_Type := Index_Type'First;
   end record;
   
end Generic_Pool;

Why don't you you use System.Storage_Pools RM 13.11?



^ permalink raw reply	[relevance 5%]

* Re: Storage Pools and alloca
  2002-10-15 15:42  5% Storage Pools and alloca Frank J. Lhota
@ 2002-10-15 19:14  0% ` Robert A Duff
  0 siblings, 0 replies; 96+ results
From: Robert A Duff @ 2002-10-15 19:14 UTC (permalink / raw)


"Frank J. Lhota" <NOSPAM.lhota.adarose@verizon.net> writes:

> C / C++ sometimes cut down on the hassles of memory management by using the
> "alloca" function. The "alloca" function, which is frequently implicit,
> allocates storage from the stack.

What do you mean by "frequently implicit"?

>... Since memory allocated by "alloca" is on
> the stack, it is reclaimed automatically as soon as the function that
> allocated this memory returns.
> 
> AFAIK, the "alloca" functionality could be added to Ada using the storage
> pool facility. One could derive a type from
> System.Storage_Pools.Root_Storage_Pool and write the required subprograms
> for this type as follows:
> 
>     - The Allocate procedure would allocate memory from the stack, sort of
> like the C "alloca" function;
>     - The Deallocate procedure should do nothing; and
>     - The Storage_Size should return the amount of space left on the stack.

Storage_Size is supposed to return the amount of "reserved" space,
which in virtual memory systems might be zero.  ('Storage_Size is kind of
useless, actually.  I've never written a program that queried
'Storage_Size.  Has anybody?)

> Of course, this is highly platform dependant, and would often require
> machine code insertions.
> 
> Questions:
> 
>     1) Does any Ada compiler provide this type of storage pool?

I believe the GNAT compiler uses a storage pool to implement
dynamically-sized stack objects.  I think most other compilers
don't use a storage pool per se, but use essentially the same
run-time mechanisms as alloca.  (I know of one Ada 83 compiler
that used heap allocation to implement the Ada features -- but I
think an alloca-like mechanism is better.)

I don't see any reason to use such a storage pool directly.
Ada's dynamically-sized stack objects seem to do everything
alloca can do, but more safely.  In fact, the Ada mechanism is
more powerful, since you can return unknown-sized objects from
functions.  (I mean, unknown size at the call site -- the size is
fixed at the point of "return" in the called function.  Like when
the spec of the function says "return String".)

>     2) If this type of storage pool was available, would you find it useful?

No.

>     3) Would an "alloca" storage pool be a worthwhile addition to Ada 0x?

No, I don't think so.  There's alloca-like stuff going on behind the
scenes in Ada, but I don't see why a programmer would want direct access
to that mechanism.

Can you think of any case (in C or C++) that uses alloca, but can't be
easily translated into the existing Ada mechanisms?  I can't.

- Bob



^ permalink raw reply	[relevance 0%]

* Storage Pools and alloca
@ 2002-10-15 15:42  5% Frank J. Lhota
  2002-10-15 19:14  0% ` Robert A Duff
  0 siblings, 1 reply; 96+ results
From: Frank J. Lhota @ 2002-10-15 15:42 UTC (permalink / raw)


C / C++ sometimes cut down on the hassles of memory management by using the
"alloca" function. The "alloca" function, which is frequently implicit,
allocates storage from the stack. Since memory allocated by "alloca" is on
the stack, it is reclaimed automatically as soon as the function that
allocated this memory returns.

AFAIK, the "alloca" functionality could be added to Ada using the storage
pool facility. One could derive a type from
System.Storage_Pools.Root_Storage_Pool and write the required subprograms
for this type as follows:

    - The Allocate procedure would allocate memory from the stack, sort of
like the C "alloca" function;
    - The Deallocate procedure should do nothing; and
    - The Storage_Size should return the amount of space left on the stack.

Of course, this is highly platform dependant, and would often require
machine code insertions.

Questions:

    1) Does any Ada compiler provide this type of storage pool?
    2) If this type of storage pool was available, would you find it useful?
    3) Would an "alloca" storage pool be a worthwhile addition to Ada 0x?





^ permalink raw reply	[relevance 5%]

* Re: Specialization
  @ 2002-05-31 19:44  5%   ` Simon Wright
  0 siblings, 0 replies; 96+ results
From: Simon Wright @ 2002-05-31 19:44 UTC (permalink / raw)


dennison@telepath.com (Ted Dennison) writes:

> Why wouldn't that happen automaticly? If you want to *manually*
> control finalization, you probably shouldn't be using controlled
> types.

I _knew_ there was a problem in the Booch Containers around here
... if you use a bounded container it places the elements in an array,
so if they need finalization it may well happen long after you were
expecting it to. I guess I'd need to add something to the generic ..

   generic
      type Item is private;
      with function "=" (L, R : Item) return Boolean is <>;
      Null_Value : Item;                                    --  new
   package BC.Containers is

which means yet another non-defaultable generic parameter, people are
fed up enough with instantiating all these nested generics as it is. I
suppose this could be deferred to the forms that need it, clearly
Unbounded doesn't:

   generic
      type Item is private;
      with function "=" (L, R : Item) return Boolean is <>;
   package BC.Containers is

   generic
      Maximum_Size : Positive;
      Null_Value : Item;                                     -- new
   package BC.Containers.Collections.Bounded is

   generic
      Storage : in out System.Storage_Pools.Root_Storage_Pool'Class;
   package BC.Containers.Collections.Unbounded is




^ permalink raw reply	[relevance 5%]

* Re: Generic default parameters
  2002-05-10 22:14  7% ` Stephen Leake
@ 2002-05-13  7:49  5%   ` Thomas Wolf
  0 siblings, 0 replies; 96+ results
From: Thomas Wolf @ 2002-05-13  7:49 UTC (permalink / raw)


stephen.a.leake.1@gsfc.nasa.gov wrote:
> Thomas Wolf <t_wolf@angelfire.com> writes:
> 
> > 5. Linked to (3) above: some way to specify a storage pool that
> >    is equal to whatever pool the compiler would use if no
> >    "for Some_Access'Storage_Pool use ..." clause was present, i.e.
> >    a generic way to refer to the standard storage pool of a type
> >    without referring to the type.

[...]

> I think a cleaner solution to 5 is a standard name for the standard
> storage pool, combined with 3 (default object for "in out"). So we'd
> have:
> 
>   generic
>      type Something is private;
>      Pool : in out System.Storage_Pools.Root_Storage_Pool'Class := 
>          System.Storage_Pools.Default_Storage_Pool;
>   package X is
>      type Some_Access is access all Something;
>      for Some_Access'Storage_Pool use Pool;
> 
> There may have to be more than one default storage pool; that may be
> why there is no standard name now.

Exactly. Every access type may have its own "standard" pool as far as I
can tell from the RM. Hence maybe something like your
System.Storage_Pools.Default_Storage_Pool, but it would need to be
treated specially: it'd have to denote not *one* particular pool,
but would have to denote depending on context *the* pool from the
set of all possible standard pools that would apply to a given access
type. Hmm... what about other uses of storage pools? It appears that
besides passing it around to finally assign it to some access type
with a representation clause one cannot do very much with a storage
pool, see RM 13.11(20).

While I still think something like that would be useful, I'm not sure
I like such a context dependent semantics...

-- 
-----------------------------------------------------------------
Thomas Wolf                          e-mail: t_wolf@angelfire.com




^ permalink raw reply	[relevance 5%]

* Re: Generic default parameters
  2002-05-10 14:22  6% Generic default parameters Thomas Wolf
@ 2002-05-10 22:14  7% ` Stephen Leake
  2002-05-13  7:49  5%   ` Thomas Wolf
  0 siblings, 1 reply; 96+ results
From: Stephen Leake @ 2002-05-10 22:14 UTC (permalink / raw)


Thomas Wolf <t_wolf@angelfire.com> writes:

> 5. Linked to (3) above: some way to specify a storage pool that
>    is equal to whatever pool the compiler would use if no
>    "for Some_Access'Storage_Pool use ..." clause was present, i.e.
>    a generic way to refer to the standard storage pool of a type
>    without referring to the type. Something like
> 
>    generic
>       type Something is private;
>       Pool : in out System.Storage_Pools.Root_Storage_Pool'Class := <>;
>    package X is
>       type Some_Access is access all Something;
>       for Some_Access'Storage_Pool use Pool;
>       ...
> 
>    and if an instantiation provides an actual for 'Pool', that will
>    be taken as the storage pool of type 'Some_Access', but if an
>    instantiation doesn't provide an actual, 'Some_Access' will use
>    a standard storage pool.
> 
>    Not sure if point (5) makes sense, especially since it would be
>    useful only for storage pools, but make no sense at all for other
>    types...

I think a cleaner solution to 5 is a standard name for the standard
storage pool, combined with 3 (default object for "in out"). So we'd
have:

  generic
     type Something is private;
     Pool : in out System.Storage_Pools.Root_Storage_Pool'Class := 
         System.Storage_Pools.Default_Storage_Pool;
  package X is
     type Some_Access is access all Something;
     for Some_Access'Storage_Pool use Pool;

There may have to be more than one default storage pool; that may be
why there is no standard name now.
  
> Comments, anyone? Would these things be worth to consider for inclusion
> in the next Ada revision? 

I agree they would all be useful, but I have personally only seen the
need for 5 and 3.

-- 
-- Stephe



^ permalink raw reply	[relevance 7%]

* Generic default parameters
@ 2002-05-10 14:22  6% Thomas Wolf
  2002-05-10 22:14  7% ` Stephen Leake
  0 siblings, 1 reply; 96+ results
From: Thomas Wolf @ 2002-05-10 14:22 UTC (permalink / raw)



It seems I'm not alone with these ideas... so let's summarize
and see if we can get a halfway decent proposal for the ARG
out of the discussions:

Ada 95 lacks features for:

1. specifying a default type for generic formal type parameters

   The idea would be to allow something like

   generic
      type Something is range <> := Natural;

   and if an instantiation does *not* supply an actual for
   'Something', 'Natural' will be taken.

2. specifying a default for generic formal package parameters:

   generic
      with package X is new Y (<>) := Z;

   where Z of course would have to be an instantiation of Y.

   Or maybe even

   generic
      with package X is new Y (<>) := Y (Param1 => Default1,
                                         Param2 => Default2,
                                         ...);

   i.e., allow the default to be an anonymous instance?
   (I guess, the first variant is sufficient, and the second
   would only unnecessarily complicate matters.)

3. specify a default for a generic formal "in out" object:

   with System.Storage_Pools;
   generic
      type Something is private;
      Pool : in out System.Storage_Pools.Root_Storage_Pool'Class :=
         Some_Default_Pool_Instance;
   package X is
      type Some_Access is access all Something;
      for Some_Access'Storage_Pool use Pool;
      ...

4. providing defaults in a generic renaming:

   generic
     type Something is private;
   package A is ...

   generic package B renames A (Something => Integer);

   or even

   generic
     type Something is range <> := Natural;
   package C is ...

   generic package D renames C (Something => Integer);

5. Linked to (3) above: some way to specify a storage pool that
   is equal to whatever pool the compiler would use if no
   "for Some_Access'Storage_Pool use ..." clause was present, i.e.
   a generic way to refer to the standard storage pool of a type
   without referring to the type. Something like

   generic
      type Something is private;
      Pool : in out System.Storage_Pools.Root_Storage_Pool'Class := <>;
   package X is
      type Some_Access is access all Something;
      for Some_Access'Storage_Pool use Pool;
      ...

   and if an instantiation provides an actual for 'Pool', that will
   be taken as the storage pool of type 'Some_Access', but if an
   instantiation doesn't provide an actual, 'Some_Access' will use
   a standard storage pool.

   Not sure if point (5) makes sense, especially since it would be
   useful only for storage pools, but make no sense at all for other
   types...

Personally, I have encountered several occasions where I would have
liked to have some (or all) of these features. They'd help a lot in
writing general generics (:-) that still are simple to instantiate.
 
Comments, anyone? Would these things be worth to consider for inclusion
in the next Ada revision? 

-- 
-----------------------------------------------------------------
Thomas Wolf                          e-mail: t_wolf@angelfire.com




^ permalink raw reply	[relevance 6%]

* Re: Booch Components 20020117
  2002-02-07 15:12  5%   ` Stephen Leake
@ 2002-02-10 12:32  7%     ` Simon Wright
  0 siblings, 0 replies; 96+ results
From: Simon Wright @ 2002-02-10 12:32 UTC (permalink / raw)


Stephen Leake <stephen.a.leake.1@gsfc.nasa.gov> writes:

> "Matthew Heaney" <mheaney@on2.com> writes:
> 
> > "Simon Wright" <simon@pushface.org> wrote in message
> > news:x7vlmeuddd6.fsf@smaug.pushface.org...
> > >     The way Storage Management is specified has changed significantly:
> > >     you now supply a single generic parameter of type
> > >     System.Storage_Pools.Root_Storage_Pool'Class. This will be painful
> > >     to start with, but should simplify matters in the long run.
> > 
> > I had trouble doing this:
> > 
> > package Pools is
> >    type Pool_Type is new Root_Storage_Pool with record ...;
> >    Pool : Pool_Type;
> > end;
> > 
> > generic
> >    Pool : in out Root_Storage_Pool'Class;
> > package GP is
> > 
> > 
> > with Pools;
> > package P is new GP (Pools.Pool);
> > 
> > The compiler complained that my Pool object wasn't the correct type.  How
> > are you instantiating your generics which accept a generic formal pool
> > object?
> 
> This got me too. You have to do:
> 
> Pool => System.Storage_Pools.Root_Storage_Pool'Class (Pools.Pool)
> 
> I thought it was a compiler bug, but both ObjectAda and GNAT agree on
> it. I never submitted a report. I didn't chase it down in the LRM,
> since it works :).

I'm afraid I agree with the smiley :-(

At one point I see i've used

   Pool : BC.Support.Managed_Storage.Pool (10_000);
   Pool_View : System.Storage_Pools.Root_Storage_Pool'Class
     renames System.Storage_Pools.Root_Storage_Pool'Class (Pool);

which is a tad longwinded, I agree.



^ permalink raw reply	[relevance 7%]

* Re: Booch Components 20020117
  2002-02-06 23:35  0% ` Matthew Heaney
@ 2002-02-07 15:12  5%   ` Stephen Leake
  2002-02-10 12:32  7%     ` Simon Wright
  0 siblings, 1 reply; 96+ results
From: Stephen Leake @ 2002-02-07 15:12 UTC (permalink / raw)


"Matthew Heaney" <mheaney@on2.com> writes:

> "Simon Wright" <simon@pushface.org> wrote in message
> news:x7vlmeuddd6.fsf@smaug.pushface.org...
> >     The way Storage Management is specified has changed significantly:
> >     you now supply a single generic parameter of type
> >     System.Storage_Pools.Root_Storage_Pool'Class. This will be painful
> >     to start with, but should simplify matters in the long run.
> 
> I had trouble doing this:
> 
> package Pools is
>    type Pool_Type is new Root_Storage_Pool with record ...;
>    Pool : Pool_Type;
> end;
> 
> generic
>    Pool : in out Root_Storage_Pool'Class;
> package GP is
> 
> 
> with Pools;
> package P is new GP (Pools.Pool);
> 
> The compiler complained that my Pool object wasn't the correct type.  How
> are you instantiating your generics which accept a generic formal pool
> object?

This got me too. You have to do:

Pool => System.Storage_Pools.Root_Storage_Pool'Class (Pools.Pool)

I thought it was a compiler bug, but both ObjectAda and GNAT agree on
it. I never submitted a report. I didn't chase it down in the LRM,
since it works :).


-- 
-- Stephe



^ permalink raw reply	[relevance 5%]

* Re: Booch Components 20020117
  2002-01-19  7:11  5% Booch Components 20020117 Simon Wright
@ 2002-02-06 23:35  0% ` Matthew Heaney
  2002-02-07 15:12  5%   ` Stephen Leake
  0 siblings, 1 reply; 96+ results
From: Matthew Heaney @ 2002-02-06 23:35 UTC (permalink / raw)



"Simon Wright" <simon@pushface.org> wrote in message
news:x7vlmeuddd6.fsf@smaug.pushface.org...
>     The way Storage Management is specified has changed significantly:
>     you now supply a single generic parameter of type
>     System.Storage_Pools.Root_Storage_Pool'Class. This will be painful
>     to start with, but should simplify matters in the long run.

I had trouble doing this:

package Pools is
   type Pool_Type is new Root_Storage_Pool with record ...;
   Pool : Pool_Type;
end;

generic
   Pool : in out Root_Storage_Pool'Class;
package GP is


with Pools;
package P is new GP (Pools.Pool);

The compiler complained that my Pool object wasn't the correct type.  How
are you instantiating your generics which accept a generic formal pool
object?







^ permalink raw reply	[relevance 0%]

* Booch Components 20020117
@ 2002-01-19  7:11  5% Simon Wright
  2002-02-06 23:35  0% ` Matthew Heaney
  0 siblings, 1 reply; 96+ results
From: Simon Wright @ 2002-01-19  7:11 UTC (permalink / raw)


This release has been uploaded to

  http://www.pushface.org/components/bc/

(still an alias for the old http://www.pogner.demon.co.uk/components/bc/)
and is mirrored at http://www.adapower.net/booch/ .

There was an unannounced release 20011011.

Significant features since 20010819:

  Interface:

    The Containers that don't provide structural sharing (Bags,
    Collections, Dequeues, Maps, Queues, Rings, Sets and Stacks) now
    support Streams ('Input, 'Output).
     Unfortunately, GNAT 3.13p doesn't support this for dynamic or
    unbounded forms (runtime errors), while ObjectAda fails at runtime
    when the Item type is a discriminated record (OK for tagged types,
    though). Walking on broken glass here.

    The way Storage Management is specified has changed significantly:
    you now supply a single generic parameter of type
    System.Storage_Pools.Root_Storage_Pool'Class. This will be painful
    to start with, but should simplify matters in the long run.

    You couldn't override equality for a Map's Key.

  Contributions:

    Pat Rogers has added a storage manager for real-time applications.




^ permalink raw reply	[relevance 5%]

* Re: List container strawman
  2001-11-03  8:09  8%   ` Simon Wright
@ 2001-11-03 12:46  0%     ` Simon Wright
  0 siblings, 0 replies; 96+ results
From: Simon Wright @ 2001-11-03 12:46 UTC (permalink / raw)


Simon Wright <simon@pushface.org> writes:

> Aha! this compiles (GNAT 3.14a1), whether it is legal and works on
> other compilers is a different matter of course ..
> 
>   with System.Storage_Pools;
>   package Default_Pool is
> 
>      type Pool_Access
>      is access all System.Storage_Pools.Root_Storage_Pool'Class;
> 
>      type T is access Integer;
>      Pool : System.Storage_Pools.Root_Storage_Pool'Class
>        renames T'Storage_Pool;
> 
>      generic
> 	Storage : Pool_Access := Pool'Access;
>      package G is
>      end G;
> 
>   end Default_Pool;

Drat, I fear it's not legal; well, ObjectAda thinks not. Pool needs to
be aliased so that Pool'Access at line 12 is permitted. Bug report
sent to ACT ..



^ permalink raw reply	[relevance 0%]

* Re: List container strawman
  @ 2001-11-03  8:09  8%   ` Simon Wright
  2001-11-03 12:46  0%     ` Simon Wright
  0 siblings, 1 reply; 96+ results
From: Simon Wright @ 2001-11-03  8:09 UTC (permalink / raw)


Ted Dennison<dennison@telepath.com> writes:

> In article <mailman.1004730907.14961.comp.lang.ada@ada.eu.org>, Mike Brenner
> says...
> >
> >Comment 3. There is no method of putting in a garbage collector.
> 
> *That's* the other thing I forgot! I was thinking of having a
> storage pool be an optional parameter (the default being the default
> storage pool). Any problems with that?

I couldn't find a way of giving the parameter a default; the problem
being that there's no standard way of getting at the standard storage
pool. GNAT makes it visible, but warns you about using features that
aren't "officially" supported.

I guess one could go in for indirections using accesses or functions
.. I have

  generic
     Storage : in out System.Storage_Pools.Root_Storage_Pool'Class;
  package BC.Containers.Collections.Unbounded is

and you can get at the default pool using

  with System.Storage_Pools;

  package BC.Support.Standard_Storage is

     type T is access Integer; -- arbitrary subtype

     Pool : System.Storage_Pools.Root_Storage_Pool'Class
       renames T'Storage_Pool;

  end BC.Support.Standard_Storage;


Aha! this compiles (GNAT 3.14a1), whether it is legal and works on
other compilers is a different matter of course ..

  with System.Storage_Pools;
  package Default_Pool is

     type Pool_Access
     is access all System.Storage_Pools.Root_Storage_Pool'Class;

     type T is access Integer;
     Pool : System.Storage_Pools.Root_Storage_Pool'Class
       renames T'Storage_Pool;

     generic
	Storage : Pool_Access := Pool'Access;
     package G is
     end G;

  end Default_Pool;



^ permalink raw reply	[relevance 8%]

* Re: Container reqs
  @ 2001-10-23  1:13  4%               ` Stephen Leake
  0 siblings, 0 replies; 96+ results
From: Stephen Leake @ 2001-10-23  1:13 UTC (permalink / raw)


Jeffrey Carter <jrcarter@acm.org> writes:

> Stephen Leake wrote:
> > 
> > Jeffrey Carter <jeffrey.carter@boeing.com> writes:
> > 
> > > Ehud Lamm wrote:
> > > > <snip>
> > > > What I dodn't like is the need for several, possibly nested, instantiations
> > > > simply to get a simple queue or hash table.
> > >
> > > I wholeheartedly agree. Wright's posting here a few days ago of the
> > > sequence of instantiations needed to obtain a simple structure with the
> > > Booch components clearly indicates that they fail this requirement.
> > 
> > This is easy to say. But can you provide an alternative, that still
> > allows the container to handle all reasonable Ada types?
> 
> I refer you to the PragmAda Reusable Components as an example of a
> component library that provides single instantiations for simple
> structures that handle all reasonable Ada types.
> 
> http://home.earthlink.net/~jrcarter010/pragmarc.htm

Well, I've looked at it (briefly). Here's the relevant part of the
unbounded list package:

generic -- PragmARC.List_Unbounded
   type Element is limited private; -- Do not instantiate with a scalar

   with procedure Assign (To : in out Element; From : in Element) is <>;
package PragmARC.List_Unbounded is

And the equivalent from my library:
generic
   type Item_Type (<>) is limited private;
   type Item_Node_Type is private;
   with function To_Item_Node (Item : in Item_Type) return Item_Node_Type;
   with procedure Free_Item (Item : in out Item_Node_Type);
   -- If Item_Type is definite non-limited, Item_Node_Type should just be
   -- Item_Type. Then To_Item_Node should just return Item, and Free_Item
   -- should be null (and both should be inlined). See
   -- SAL.Aux.Definite_Private_Items.
   --
   -- If Item_Type is indefinite, Item_Node_Type should be 'access
   -- Item_Type'. Then To_Item_Node should allocate Item and return a
   -- pointer to it, and Free_Item should be Unchecked_Deallocation. See
   -- SAL.Aux.Indefinite_Private_Items.
   --
   -- To create a list of limited objects (say of type Limited_Type),
   -- Item_Type can be a non-limited type holding the parameters needed to
   -- create an object (non-limited to allow the user to create aggregates
   -- of creation parameters), and Item_Node_Type can be 'access
   -- Limited_Type'. Then To_Item_Node must allocate an object of type
   -- Limited_Type and initialize it using the parameters in Item_Type. See
   -- SAL.Aux.Indefinite_Limited_Items.
   --
   -- Other usages may be possible.
   --

   with function Copy (Source : in Item_Node_Type) return Item_Node_Type is <>;
   -- Deep copy of Source, for use in allocators in Copy (List).

   Node_Storage_Pool : in out System.Storage_Pools.Root_Storage_Pool'Class;
   -- Root_Storage_Pool is limited, which does not allow defaults. Default
   -- for a global list type should be <some_global_access_type>'Storage_Pool.
   -- Default for a local list type, which should be reclaimed when the
   -- list type goes out of scope, is implementation defined (sigh).
package SAL.Gen.Lists.Double is

PragmARC does _not_ support indefinite types, which are a large part
of Ada (strings, unconstrained variant records, tagged types with
unconstrained discriminants). In addition, the comment says "no
scalars"; I'm not clear why.

So I don't think PragmARC meets the criteria of "simple instantiation
for all reasonable Ada types".

Perhaps we disagree on the meaning of "reasonable" here.

-- 
-- Stephe



^ permalink raw reply	[relevance 4%]

* Re: Container reqs
  @ 2001-10-17  5:55  8%     ` Simon Wright
  0 siblings, 0 replies; 96+ results
From: Simon Wright @ 2001-10-17  5:55 UTC (permalink / raw)


"Ehud Lamm" <mslamm@mscc.huji.ac.il> writes:

> James Rogers <jimmaureenrogers@worldnet.att.net> wrote in message
> news:3BCA173D.FA305845@worldnet.att.net...
> >
> >
> > For the unbounded containers we may want versions allowing one to
> > designate the storage pool used.
> 
> What's the best way to do this?

The BCs now say eg

  with System.Storage_Pools;

  generic
     Storage : in out System.Storage_Pools.Root_Storage_Pool'Class;
  package BC.Containers.Collections.Unbounded is

> Does this mean that we would have to implement useful storage pools as part
> of the effort, and if so - which?

and it seems you can get away with

  with System.Storage_Pools;

  package BC.Support.Standard_Storage is

     type T is access Integer; -- arbitrary subtype

     Pool : System.Storage_Pools.Root_Storage_Pool'Class renames T'Storage_Pool;

  end BC.Support.Standard_Storage;

(ObjectAda & GNAT)


It would be Quite Nice if there were standardised access to the
system's default Storage_Pool, though I can see that if different
types had to be allocated from different pools this might be hard.



^ permalink raw reply	[relevance 8%]

* Re: why not "standardize" the Booch Components?  (was Re: is Ada dying?)
  @ 2001-10-11 20:52  5%             ` Simon Wright
  0 siblings, 0 replies; 96+ results
From: Simon Wright @ 2001-10-11 20:52 UTC (permalink / raw)


"Pat Rogers" <progers@classwide.com> writes:

> "Marin David Condic" <dont.bother.mcondic.auntie.spam@[acm.org> wrote in
> message news:9q49fc$nh3$1@nh.pace.co.uk...

> > It ought to be noted that something like the Booch components are not going
> > to be suitable for all applications. If they rely on dynamic memory, they
> > may be unsuitable for any sort of realtime work. If they rely on fixed
> > memory, they may not be suitable for very dynamic workstation apps. If they
> > provide both implementations, they may be "too big" and/or offer too many
> > choices to the user. IOW, they cannot be all things to all users and hence
> > it should be clear as to what the intended usage is.
> 
> Yes, that's true, but at least the storage management is an explicit
> part of the abstraction when allocations are involved -- one has to
> specify the pool to instantiate those components.  For predictable
> storage allocation one would use, for example, a fixed-block pool.
> Barnes' book has one, and I show one in my Real-Time Ada course, so
> they aren't hard to get.  Better yet would be to add it to the
> existing BC pool managers already available.  I'll see if Simon is
> open to that.

Absolutely.

I managed to find some pathological allocation patterns with the Pool
that Pat contrbuted to the BCs recently, things like removing every
other element, so as ever one would have to look at the actual
requirement.

The BCs have a middle form (Dynamic) between the two extrmenes
mentioned so far (Bounded & Unbounded), as ever performance varies
with usage (and I think I've not actually implemented the C++
faithfully here; but since this form looks like a poor person's
Storage Pool, perhaps I won't worry too much).

The next release of the BCs will use Storage Pools like

   generic
      Storage : in out System.Storage_Pools.Root_Storage_Pool'Class;
   package BC.Containers.Collections.Unbounded is

so really you can use any storage pool you like.



^ permalink raw reply	[relevance 5%]

* User-defined access dereference
@ 2001-08-17 23:54  3% Stanley R. Allen
  0 siblings, 0 replies; 96+ results
From: Stanley R. Allen @ 2001-08-17 23:54 UTC (permalink / raw)



Language design.

In the last couple of years I've had a number of situations arise in
which it would be very convenient to be able to replace the dereferencing
of a pointer object with a function of my own.  In at least one case, I
was in enough need of doing this and knew that the dereferences were limited
to a single (but very large) package, that I felt it was worthwhile to create
a special 'dereference' function and systematically replace all implicit and
explicit uses of ".all" with a call to my function.  There were about 350
dereferences which had to be changed.  It would have been very nice and less
error-prone if it had been possible to redefine the dereference. (The error-
proneness of this change was due to the fact that, if some derefs were missed
then the code would still compile and execute since the original implicit and
explicit ".all"s were valid Ada text -- you just would not know that it failed
until it was 'too late'.)

This kind of thing has cropped up a number of times in our large, long-lived
project, because we are making heavy use of shared memory.  The package
described above was modified as stated because of the need to define pointer
values which were not really addresses, but offsets within shared memory
segments.  The dereference operation had to do more that retrieve the value;
it was necessary first to compute the actual address using the base virtual
address and the offset.  

Now we are faced with another situation in which it would be nice to replace
".all".  This time, there are over 10,000 dereferences in over a million lines
of code, so it's out of the question to do to this code what was done to the
other code before.  (The latest issue is the need to error-check each reference
because it's possible for 'remote' references to have recoverable point failures
in a what is essentially 'reflected memory' for a Linux cluster.)

I haven't been able to track down the reasons why user-defined dereferencing
was not permitted for Ada 95 (I'm guessing it was considered).  Package
System.Storage_Pools already provides the capability to define your own
storage allocation and deallocation for a particular access type, so it seems
reasonable that a user-defined dereference would also be associated with a
storage pool.

I've been trying to play with this idea for an hour or so, and came up
with this:

    Pool : A_Storage_Pool_Type;

    type Accessor is access Object;
    for Accessor'Storage_Pool use Pool;
    function De_Ref (P : in out A_Storage_Pool_Type; A : Accessor) return Object;
    for Accessor'Dereference use De_Ref;     -- not Ada 95

The compiler would recognize that all dereference operations on this type
would translate into a call to this function.

Any thoughts?

--
Stanley Allen
mailto:Stanley_R_Allen-NR@Raytheon.com



^ permalink raw reply	[relevance 3%]

* Storage Pool
@ 2001-06-13 19:25  6% ANH_VO
  0 siblings, 0 replies; 96+ results
From: ANH_VO @ 2001-06-13 19:25 UTC (permalink / raw)
  To: comp.lang.ada

Is it correct to assume that Size_In_Storage_Element mod Alignment = 0 for both
subprograms Allocate and Deallocate for any type derived from Root_Storage_Pool
as shown below

   procedure Allocate (
      Pool            : in out General_Pool;
      Storage_Address :    out System.Address;
      Size_In_Storage_Elements : in System.Storage_Elements.Storage_Count;
      Alignment       : in System.Storage_Elements.Storage_Count);

   procedure Deallocate (
      Pool            : in out General_Pool;
      Storage_Address : in     System.Address;
      Size_In_Storage_Elements : in System.Storage_Elements.Storage_Count;
      Alignment       : in System.Storage_Elements.Storage_Count);

   where type General_Pool (Size : System.Storage_Elements.Storage_Count;
                            User : access String ) is new
                       System.Storage_Pools.Root_Storage_Pool with private;
   ...

   or is it compiler dependent?
   
   Thanks.

   Anh Vo



^ permalink raw reply	[relevance 6%]

* Better support for garbage collection
@ 2001-03-13 18:37  3% Nick Roberts
  0 siblings, 0 replies; 96+ results
From: Nick Roberts @ 2001-03-13 18:37 UTC (permalink / raw)


There follows a proposal that I intend to make to the ARG in the next few
days. I would appreciate comments and criticisms before doing so.

This is the first of many proposals that I shall be likely to make. The fact
that this one comes first is of no significance.

----------

I would like to make a proposal for the next revision of the language which
would provide standardised support for partially user-defined garbage
collection, and a standard mechanism for disposability.

I think these facilities should be defined in an optional annex.

RM95-13.11 defines a mechanism permitting a degree of user control over the
dynamic allocation and deallocation of storage for objects. This mechanism
is based on the abstract type Root_Storage_Pool, and defines the interface
for this type. However this interface is not sufficient for the provision
of a user-defined storage pool which supports garbage collection.

The following proposal defines a new abstract type, derived from
Root_Storage_Pool, which adds sufficient extra functionality to this
interface to facilitate user-defined garbage-collecting storage pools
(UDGCSPs). The new type is called Repositioning_Storage_Pool, from the
assumption that garbage collection will (generally) require the
repositioning of objects in memory.

The language should define the following package:

   package System.Storage_Pools.Repositioning is

      pragma Preelaborate(System.Storage_Pools.Repositioning);

      type Repositioning_Storage_Pool is
         abstract new Root_Storage_Pool with private;

      type Object_Token is new Address;

      procedure Allocate(
         Pool : in out Repositioning_Storage_Pool;
         Token : out Object_Token) is abstract;

      procedure Deallocate(
         Pool : in out Repositioning_Storage_Pool;
         Token : in Object_Token) is abstract;

      procedure Lock(
         Pool : in out Repositioning_Storage_Pool;
         Token : in Object_Token;
         Storage_Address : out Address) is abstract;

      procedure Unlock(
         Pool : in out Repositioning_Storage_Pool;
         Token : in Object_Token) is abstract;

      procedure Tidy(
         Pool : in out Repositioning_Storage_Pool) is abstract;

      function Max_Lock_Count(Pool : Repositioning_Storage_Pool)
         return Natural is abstract;

      Locking_Error: exception;

   private
      ... -- not specified by the language
   end System.Storage_Pools.Repositioning;

A type derived from Repositioning_Storage_Pool is a 'repositioning pool' (a
UDGCSP), whose operations are defined below.

These operations all work in a way which is 100% upwards-compatible with
Root_Storage_Pool, so that a compiler which does not support the extra
functionality implied by a repositioning pool will nevertheless work
correctly with the pool (although no garbage collection will be performed).

Each pool element is identified by a unique (within the pool) value of the
type Object_Token, called the element's 'token'. This value will never
change throughout the life (from its allocation to its deallocation) of the
element. The type Object_Token is the same size as System.Address (and will
typically actually be an address, hence the declaration which makes this
conversion convenient).

Each pool element has a 'lock count', of an unspecified integer (or
modular) subtype, whose range does not exceed that of Standard.Natural. The
element is said to be 'locked' if its lock count is a value other than 0.

The overloading of the Allocate procedure with a Storage_Address parameter
sets the lock count of the pool element it allocates to 1, reserves a token
for the element, and reserves a block of memory, whose address is passed
out to the Storage_Address parameter.

The overloading of the Allocate procedure with a Token parameter sets the
lock count of the pool element it allocates to 0, reserves a block of
memory, and reserves a token for the element, whose value is passed out to
the Token parameter.

Either Allocate procedure may raise Storage_Error as a result of having
insufficient memory for a block or for a token.

The Lock procedure increments (by 1) the lock count of a pool element. The
current address of the block of memory reserved for the element is passed
out in Storage_Address.

For any repositioning pool, there is a maximum value the lock count of any
of its elements can reach. The Max_Lock_Count function returns this
maximum. If a call is made to Lock for an element whose lock count equals
this value, the Locking_Error exception is raised (and the lock count is
not changed).

I suggest a recommendation (or perhaps a stipulation) that the maximum lock
count is never less than 15. (Although this recommendation will apply to
the user rather than the implementation, except for implementation-supplied
repositioning pools.)

The Unlock procedure decrements (by 1) the lock count of a pool element,
unless the element's lock count is already 0, in which case it raises the
Locking_Error exception instead.

The overloading of the Deallocate procedure which takes a Storage_Address
parameter raises the Locking_Error exception if the pool element's lock
count is not 1 (and does not deallocate the element).

The overloading of the Deallocate procedure which takes a Token parameter
raises the Locking_Error exception if the pool element's locking count is
not 0 (and does not deallocate the element).

The Tidy procedure carries out what is called 'compaction' or
'defragmentation' (the second stage of the garbage collection process) on a
pool. Blocks of memory reserved for objects are moved (their contents
copied to other locations in memory) so as to reduce (to a minimum) the
amount of memory which is effectively unusable (typically because many of
the gaps between the blocks have become too small). The block of memory
reserved for a pool element must not be moved if the element is locked (its
lock count is not 0).

The first stage of the garbage collection process is 'scavenging', the
recognition and deallocation of allocated objects which have become
'unreachable' (inaccessible by any degree of indirection). This stage needs
to be carried out by code specially generated by the compiler.

A 'disposable object' is a dynamically allocated object which an
implementation (of Ada) is permitted to deallocate at any time, if it needs
to do so in order to successfully complete the allocation of another
object.

The language should define a subtype in the package System:

   subtype Disposability_Level is
      Integer range 0..implementation_defined;

and an attribute Disposability, which applies to any pool-specific access
type, and has a static value of subtype Disposability_Level. A value other
than 0 indicates that objects referenced by access values of this access
type are disposable. The disposability level of the objects is the same as
the disposability level of the access type. The default value is 0, but may
be set by a representation clause. An implementation must never attempt to
dispose of an object with a certain disposability level if there exists
another object with a higher disposability level.

Disposal of a controlled object will cause finalization of the object as
normal.

The principles behind the above interface are explained briefly below.

Whenever an implementation makes an attempt to allocate an object in a
repositioning pool, and that attempt fails (Storage_Error being raised), it
can intervene by carrying out garbage collection (both stages) and then
attempting the allocation again. If the second attempt fails, the
implementation may attempt to deallocate a disposable object, and then try
once more. Eventually, on repeated failures, defeat must be conceded (and
the Storage_Error exception propagated as normal).

Additional calls to Tidy may be made, by the implementation or the user,
e.g. as part of an ongoing garbage collection strategy.

The imlementation must always lock a pool element before reading from it or
writing into it, in order to prevent it being moved at an inopportune
moment. On the other hand, the implementation should unlock elements as
frequently as possible (without overly reducing execution speed), so that
the Tidy procedure is not stymied by locked elements to the point of being
made ineffective.

I would suggest that an implementation should employ a strategy where it
unlocks any elements of a particular pool it has locked at every 'control
point', where a control point with respect to a pool is defined as being:

(1) just before any call to an allocator for an access value associated
with that pool;

(2) just before any call to a subprogram which may (or does) contain a
control point for that pool;

(3) any instance of pragma Inspection_Point (see RM95-H.3.2).

The same comments made in RM95-13.11(27-30), regarding tasking, would apply
to UDGCSPs. Locking, unlocking, and moving operations would need to be
atomic, for a task-safe pool.

The use of access values associated with UDGCSPs will, in general, be
inefficient compared to non-repositioning pools; this is a compromise
inherent in (full) garbage collection. It may be possible for compilers to
remove a great deal of locking and unlocking in the absence of (potential)
parallel task usage of a UDGCSP. Only calls to Tidy should ever move pool
elements; elements should remain statically positioned in memory otherwise
(regardless of their lock counts).

Garbage collection facilities for Ada tend to be rare at the moment. I
believe there are many situations where the availability of garbage
collection would be of genuine value to Ada programmers.

For example: students beginning to learn Ada, and wanting to be relieved of
the burden of storage management until later in their studies; anyone
writing a program which is likely to have a very short useful life, or who
for any reason requires speed of development more than speed of execution;
whenever an 'engine' of something else that requires garbage collection
(e.g. a Java Virtual Machine) is being implemented in Ada.

I think that a language definition of user-defined garbage-collecting
storage pools (UDGCSPs) would help in two ways towards making garbage
collection facilities more available to Ada programmers: first, it would
lessen the burden on the compiler writer, who would need only to be
concerned with the first stage of garbage collection (the second stage
being the province of UDGCSPs); second, it would open up a 'market' in
UDGCSPs, offering hopefully many variations with regard to price,
functionality, reliability, and efficiency.

Disposability is a facility provided by a variety of other languages, and
its use is an important technique for certain kinds of software (e.g. many
'artifical intelligence' applications). In addition, it is a facility that
can be very helpful for some kinds of commercial software, especially
programs which need to be able to cope gracefully with environments that
provide widely differing amounts of memory.

Even if an implementation supports repositioning pools, it should not be
required for any of its standard storage pools to be repositioning pools.
Every implementation must continue to support non-repositioning pools.

Finally, I believe the design I propose above would have the benefit that
UDGCSPs could still be used with implementations that did not specifically
support them (albeit without the garbage collection functionality), and
that it does not impose any difficulty on the programmer requiring -- e.g.
for speed reasons -- a non-repositioning pool.

----------

One question in my mind is whether the second parameter of the Unlock
procedure should be a token or an address. Might the latter enable compilers
to generate slightly better code?

Apologies for the length of the post!

--
Nick Roberts
http://www.AdaOS.org






^ permalink raw reply	[relevance 3%]

* Re: Constructors/Destructors in Ada95
  @ 2000-10-26 11:44  6%                 ` dmitry6243
  0 siblings, 0 replies; 96+ results
From: dmitry6243 @ 2000-10-26 11:44 UTC (permalink / raw)


In article <8t6vhc$fmb$1@nnrp1.deja.com>,
  mark.biggar@trustedsyslabs.com wrote:
> In article <8t6pi9$9s8$1@nnrp1.deja.com>,
>   dmitry6243@my-deja.com wrote:
> > In article <39F6D201.73C006FA@acm.org>,
> >   Marin David Condic <mcondic.nospam@acm.org> wrote:
> > > Ray Blaak wrote:
> > >
> > > > I really would like to be able to do:
> > > >
> > > >   procedure ":="(target : in out T; source : in T);
> > > >
> > > > so as to have complete control over what is happening. I vaguely
> recall some
> > > > rationale from the Ada 9X discussions for why user-defined
> assignment per se
> > > > was not incorporated. Does anyone remember?
> > >
> > > Does a
> > > statement like: "X < Y ;" make sense in Ada?) As a procedure,
you'd
> have to allow
> > > procedures to have symbol names - which opens up a whole can of
> worms. Further, it
> > > would mean allowing "infix procedures" which is hard to make sense
> of - or at least
> > > could make programs look really strange.
> >
> > It would be nice (it is in my private Ada to-do list for a long
time):
> >
> > function "*" (Left, Right : Matrix) return Matrix;  -- Produces a
new
> object
> > procedure "*" (Left : in out Matrix; Right : Matrix);  -- Multiplies
> Left to
> > Right "in-place"
> >
> > So I would count it as an advantage. There is another. If you have
> >
> > procedure ":="(target : in out T; source : in T);
> >
> > then your assignment may take a look on the left-side object before
> its
> > destruction. Ada's Adjust is much more (IMO too much) specialized.
> >
> > > I'm sure there are dozens of other reasons why it was decided not
to
> provide a
> > > means of letting the user define assignment. I'd think it would
> require perverting,
> > > warping and twisting language concepts too much.
> >
> > I think that the major reason was the decision to limit user defined
> > assigments by Controlled types. Doing so you must drop ":=" form,
> which
> > ontherwise would permanently remind you that actually all types
might
> be
> > assigned (:-))
>
> One of the problems with this proposal (redefineing ":=") is that
> you would have to define Initialize, Adjust and Finialize anyway
> as you need them to implement value parameter passing, temporary
> creation and function return values correctly.  Each of those is
> like assingment, but not exactly the same being, built out of the
> three primitives in different ways.

Yes. However, actually it is 5 primitives:

Allocator (System.Storage_Pools),
Default constructor (Initialize),
Copy constructor ("memmove" + Adjust),
Destructor (Finalize),
Deallocator (System.Storage_Pools)

> So it makes more sense to just
> define the three primitives and have the compiler generate
> standard usage sequences then to redefine ":=" and have strange
> and hard to understand things happen.

Most of programs are making strange and and hard to understand things
(:-)).

Yes. The compiler would generate the default assigment out of the
primitives and the programmer would override it if he were not satisfied
with the result.

There are lot of pitfalls here, but Initialize-Adjust-Finalize is
neither free of them. I had got a very nasty bug when a controlled type
was passed by copy instead of by reference as I thought (or better to
say, didn't care).

> There's a reason that C++ has several types of constructors and in
> many ways the Ada mechanism is simpler.

One needs at least two constructors, one for initialization, another for
creating temporal values (for instance, when an object is passed by
copy). We have this in Ada, we have this in C++.

I see nothing wrong if Ada would offer an ability to have initializing
constructors with parameters too. When

X : String (80);

is legal, why:

X : MyType (Y, Z, 3.1415);

cannot be allowed in addition to famous:

X : MyType := +(Y, Z, 3.1415); -- (:-))

User defined aggregates could also be a nice feature.

--
Regards,
Dmitry Kazakov


Sent via Deja.com http://www.deja.com/
Before you buy.



^ permalink raw reply	[relevance 6%]

* Re: Access to classwide type
  @ 2000-07-25  0:00  5%       ` Laurent Guerby
  0 siblings, 0 replies; 96+ results
From: Laurent Guerby @ 2000-07-25  0:00 UTC (permalink / raw)


dvdeug@x8b4e53cd.dhcp.okstate.edu (David Starner) writes:
> [...] I believe GNAT just implements it as a small wrapper around 
> C's free function.

For the default allocation pool in GNAT yes (gnat_free). 

In general at the language level, if you write your own pools, the
deallocation function (see System.Storage_Pools) has size and
alignment parameters, and the compiler has always a way to fill them
with the corresponding allocated parameters as required by 13.11.2
(9). So you know a bit more than C free.

I believe that for all tagged types, GNAT generates a few hidden
primitive subprograms to handle this in the class-wide case (see -gnatdg
expansion of 'size attributes on such beasts to make your mind ;-). I
don't know for other compiler technology.

For arrays and discriminated types, the compiler can obviously
generate small pieces of code to compute the size of things, since the
information must be around in some ways to do all the Ada required
checking.

-- 
Laurent Guerby <guerby@acm.org>




^ permalink raw reply	[relevance 5%]

* Re: Access to classwide type
  @ 2000-07-24  0:00  5%     ` Pat Rogers
      2 siblings, 0 replies; 96+ results
From: Pat Rogers @ 2000-07-24  0:00 UTC (permalink / raw)


<reason67@my-deja.com> wrote in message
news:8li0m5$1i4$1@nnrp1.deja.com...
> How in the heck does it do that? Does Ada.Unchecked_Deallocation
read
> the tag and do a `size on the data structure to determine the size
of
> the memory in heap to release? I am suprised by this. It is more
> implicit than I am used to in Ada.
> ---
> Jeffrey
>
> In article <xtPe5.19463$T5.28006@east2.usenetserver.com>,
>   "David Botton" <David@Botton.com> wrote:
>
> >    procedure Free_Object is
> >       new Ada.Unchecked_Deallocation (T'Class, T_Ptr);

Have a look at package System.Storage_Pools.  You'll note that the
primitives are abstract -- i.e., dispatching.


--
Pat Rogers                            Consulting and Training in:
http://www.classwide.com      Deadline Schedulability Analysis
progers@classwide.com        Software Fault Tolerance
(281)648-3165                       Real-Time/OO Languages






^ permalink raw reply	[relevance 5%]

* Re: Access to classwide type
  @ 2000-07-24  0:00  0%         ` David Botton
  0 siblings, 0 replies; 96+ results
From: David Botton @ 2000-07-24  0:00 UTC (permalink / raw)


You may have missed Pat Rogers answer:

>Have a look at package System.Storage_Pools.  You'll note that the
>primitives are abstract -- i.e., dispatching.

Perhaps this will help: Similar to C++ the memory allocation of an object is
a "method" of the object. So just like any "virtual" member of an object
that dispatches, so too the "delete" method.

It is as if you had:

type X is abstract tagged null record;

function Delete (O : X) is abstract;


Then a dispatching function like this is possible:

function Dispatch_Delete (O : X'Class) is
begin
    Delete (O);
end Dispatch_Delete;

delete in C++ and Ada.Unchecked_Deallocation are not like free in C

David Botton


<reason67@my-deja.com> wrote
>Like I said, I am betting it reads the 'size inside the
> unchecked deallocation at run-time and deleting the size it determines.









^ permalink raw reply	[relevance 0%]

* Re: garbage collection
  1999-08-20  0:00  4%   ` Keith Thompson
  1999-08-20  0:00  0%     ` Matthew Heaney
@ 1999-08-21  0:00  0%     ` Brian Rogoff
  1 sibling, 0 replies; 96+ results
From: Brian Rogoff @ 1999-08-21  0:00 UTC (permalink / raw)


On 20 Aug 1999, Keith Thompson wrote:
> Specifying the 'Storage_Pool attribute is a very powerful and
> under-used feature, IMHO.  The biggest obstacle to its use, I suspect,
> is the need to implement the Storage_Pool operations.
> 
> If System.Storage_Pools also provided routines for dereferencing
> access values (perhaps one each for reading and writing), and perhaps
> also for initialization and finalization of access objects, it would
> be even more powerful.  I haven't entirely thought this through, so it
> may be a bad idea for some reason.

See a discussion of this in comp.lang.ada, Nov '96, in a thread named 
"Garbage Collection in Ada". 

-- Brian






^ permalink raw reply	[relevance 0%]

* Re: garbage collection
  @ 1999-08-20  0:00  4%   ` Keith Thompson
  1999-08-20  0:00  0%     ` Matthew Heaney
  1999-08-21  0:00  0%     ` Brian Rogoff
  0 siblings, 2 replies; 96+ results
From: Keith Thompson @ 1999-08-20  0:00 UTC (permalink / raw)


tmoran@bix.com writes:
> > > No.  When the access type goes out of scope there is clearly no way
> > > the storage can be on the target end of a pointer, so the
> > > implementation should free that storage.
> >
> > Just to clarify, most implementations don't actually do this.
>   Why?  Is an implementation not easy, efficient, and predictable?
> And of course overidable by the user simply by raising the
> level where the access type is declared.
>   It seems undesirable to have to specify a number, big enough, but
> not too big, for the amount of storage needed when you merely want
> to get automatic deallocation.

I just realized that I had mis-read the article to which I was
responding.  What "most implementations don't actually do" is general
garbage collection, i.e., freeing allocated memory after it becomes
inaccessible.  Freeing allocated memory when leaving the scope of an
access type is much easier.

I *think* that most implementations don't even do this, but I'm not as
sure on this point.  It does impose a little extra overhead, in both
time and space.

Specifying the 'Storage_Pool attribute is a very powerful and
under-used feature, IMHO.  The biggest obstacle to its use, I suspect,
is the need to implement the Storage_Pool operations.

If System.Storage_Pools also provided routines for dereferencing
access values (perhaps one each for reading and writing), and perhaps
also for initialization and finalization of access objects, it would
be even more powerful.  I haven't entirely thought this through, so it
may be a bad idea for some reason.

-- 
Keith Thompson (The_Other_Keith) kst@cts.com  <http://www.ghoti.net/~kst>
San Diego Supercomputer Center           <*>  <http://www.sdsc.edu/~kst>
One of the great tragedies of ancient history is that Helen of Troy
lived before the invention of the champagne bottle.




^ permalink raw reply	[relevance 4%]

* Re: garbage collection
  1999-08-20  0:00  4%   ` Keith Thompson
@ 1999-08-20  0:00  0%     ` Matthew Heaney
  1999-08-21  0:00  0%     ` Brian Rogoff
  1 sibling, 0 replies; 96+ results
From: Matthew Heaney @ 1999-08-20  0:00 UTC (permalink / raw)


In article <yecwvuqhrkx.fsf@king.cts.com> , Keith Thompson <kst@cts.com>  
wrote:

> Specifying the 'Storage_Pool attribute is a very powerful and
> under-used feature, IMHO.  The biggest obstacle to its use, I suspect,
> is the need to implement the Storage_Pool operations.

One thing I miss is not having a set of nameable, pre-defined storage pools.
You have that in GNAT, but it's not really portable because of certain
low-level calls (to a C routine called "_gnat__allocate", or something like
that).


> If System.Storage_Pools also provided routines for dereferencing
> access values (perhaps one each for reading and writing), and perhaps
> also for initialization and finalization of access objects, it would
> be even more powerful.  I haven't entirely thought this through, so it
> may be a bad idea for some reason.

That's one nice thing about C++.  You can implement a pointer abstraction
that has a syntax identical to a built-in pointer.  In Ada95, you have to
implement a "handle" type that provides a dereference operator:

  type T (<>) is limited private;

  type T_Access is access all T;

  type T_Handle is private;

  function "+" (Handle : T_Handle) return T_Access;

All the primitive operations of T take access parameters, since we're always
dealing with pointers to T:

  procedure Op (O : access T);

  function Get_Attribute (O : access T) return Attr_T;

You also have constructor(s) that return a handle object:

  function New_T return T_Handle;  -- not T_Access


All the actual garbage collection is associated with T_Handle, since there's
no way to do that with the access type T_Access directly.  (Which is how
Ada95 differs from C++.)

I use this technique to implement reference-counting for on-the-heap
abstractions, so that when the count drops to zero the memory is
automatically reclaimed.  See the patterns archives for lots of examples.

<http://www.acm.org/archives/patterns.html>

The only trap door in this scheme is that there's no way to prevent the
client from manipulating the access object directly, say, by making a copy.
It has to be understood by users that that is something you never do with a
handle-based abstraction.

It would be swell if the language were amended to make access types limited;
this would prevent any problems engendered by accidental copying of access
objects.

--
Matt

It is impossible to feel great confidence in a negative theory which has
always rested its main support on the weak points of its opponent.

Joseph Needham, "A Mechanistic Criticism of Vitalism"




^ permalink raw reply	[relevance 0%]

* Re: Allocation from storage pools
  1999-06-28  0:00  6% Allocation from " Andy Askey
  1999-06-29  0:00  0% ` JClezy
@ 1999-07-01  0:00  0% ` Andy Askey
  1 sibling, 0 replies; 96+ results
From: Andy Askey @ 1999-07-01  0:00 UTC (permalink / raw)


Thanx for the info.  The Booch URL and the Barnes references were
exactly what I was looking for.

Andy

Andy Askey wrote:
> 
> I am trying to figure out the best method (most efficient-least runtime
> hit) to allocate/deallocate memory to dynamic objects.  Here is what I
> want to do, in general:
> 
> 1) Grab a chunk of memory during program initialization to serve as a
> dynamic allocation pool for subsequent object memory allocation.
> 
> 2) Allocate new objects (various types) from the previous allocated
> chunk of memory.  I'd like to do something like this:
> 
>   newobj := new newobj_type; (or some form like that, not necessarily
> overloading new, that grabs memory from the chunk)
> 
> 3) Deallocate the objects when I am done with in (freeing up the memory
> from the big chunk).
> 
> I am developing in Apex Ada95 on a Solaris OS.  I found some
> documentation about this in
> System.Storage_Pools.Rational.Storage_Pools.  I do not really want to
> use something that is Apex specific.
> 
> My questions:
> 
> Does Ada95 give me anything I can use to implement 1,2,&3 above?  I can
> write my own code fairly easily to do this, but I want to take advantage
> of anything already provided by Ada95.
> 
> Any help on this topic will be greatly appreciated.

---------------------------------------------------
|                 Andy Askey                      |
|              Software Engineer                  |
|           Raytheon Systems Company              |
|   670 Discovery Drive, Huntsville, AL  35806    |
|   Phone: (256) 971-2367  Fax: (256) 971-2306    |
|        andrew_j_askey@res.raytheon.com          |
---------------------------------------------------




^ permalink raw reply	[relevance 0%]

* Re: Allocation from storage pools
  1999-06-28  0:00  6% Allocation from " Andy Askey
@ 1999-06-29  0:00  0% ` JClezy
  1999-07-01  0:00  0% ` Andy Askey
  1 sibling, 0 replies; 96+ results
From: JClezy @ 1999-06-29  0:00 UTC (permalink / raw)


>I am trying to figure out the best method (most efficient-least runtime
>hit) to allocate/deallocate memory to dynamic objects.  Here is what I
>want to do, in general:
>
>1) Grab a chunk of memory during program initialization to serve as a
>dynamic allocation pool for subsequent object memory allocation.
>
>2) Allocate new objects (various types) from the previous allocated
>chunk of memory.  I'd like to do something like this:
>
>  newobj := new newobj_type; (or some form like that, not necessarily
>overloading new, that grabs memory from the chunk)
>
>3) Deallocate the objects when I am done with in (freeing up the memory
>from the big chunk).
>
>I am developing in Apex Ada95 on a Solaris OS.  I found some
>documentation about this in
>System.Storage_Pools.Rational.Storage_Pools.  I do not really want to
>use something that is Apex specific.
>
>My questions:
>
>Does Ada95 give me anything I can use to implement 1,2,&3 above?  I can
>write my own code fairly easily to do this, but I want to take advantage
>of anything already provided by Ada95.
>

I dont know if this will help but Ada 83 & 95 provided private memory pools. I
cant remember the exact syntax however in essence you specify the amount of
storage to be used for a private pool for a particular access type. When an
object is created via new the memory is taken from the private pool not the
heap. This would require you to create a private pool for each access type.
This is briefly covered in Barnes somewhere.




^ permalink raw reply	[relevance 0%]

* Allocation from storage pools
@ 1999-06-28  0:00  6% Andy Askey
  1999-06-29  0:00  0% ` JClezy
  1999-07-01  0:00  0% ` Andy Askey
  0 siblings, 2 replies; 96+ results
From: Andy Askey @ 1999-06-28  0:00 UTC (permalink / raw)


I am trying to figure out the best method (most efficient-least runtime
hit) to allocate/deallocate memory to dynamic objects.  Here is what I
want to do, in general:

1) Grab a chunk of memory during program initialization to serve as a
dynamic allocation pool for subsequent object memory allocation.

2) Allocate new objects (various types) from the previous allocated
chunk of memory.  I'd like to do something like this:

  newobj := new newobj_type; (or some form like that, not necessarily
overloading new, that grabs memory from the chunk)

3) Deallocate the objects when I am done with in (freeing up the memory
from the big chunk).

I am developing in Apex Ada95 on a Solaris OS.  I found some
documentation about this in
System.Storage_Pools.Rational.Storage_Pools.  I do not really want to
use something that is Apex specific.

My questions:

Does Ada95 give me anything I can use to implement 1,2,&3 above?  I can
write my own code fairly easily to do this, but I want to take advantage
of anything already provided by Ada95.

Any help on this topic will be greatly appreciated.

Thanx.
Andy

-- 
---------------------------------------------------
|                 Andy Askey                      |
|              Software Engineer                  |
|           Raytheon Systems Company              |
|   670 Discovery Drive, Huntsville, AL  35806    |
|   Phone: (256) 971-2367  Fax: (256) 971-2306    |
|        andrew_j_askey@res.raytheon.com          |
---------------------------------------------------




^ permalink raw reply	[relevance 6%]

* Creation of storage pools
@ 1999-05-26  0:00  4% Graeme Perkes
  0 siblings, 0 replies; 96+ results
From: Graeme Perkes @ 1999-05-26  0:00 UTC (permalink / raw)


There is a snippet on Ada95 storage management at the Ada
source code treasury:

http://www.adapower.com/lang/mempool.html

I've found this example to be particularly useful for explaining
how to create pre-sized storage pools.

I'm trying to extend this concept by creating a package that allows
a set of named storage pools to be created. Applications will then
identify desired storage pools by name (i.e. a string).

This is my user-defined pool type: 

   type USER_POOL( SIZE : SYSTEM.STORAGE_ELEMENTS.STORAGE_COUNT;
                   NAME : POOL_NAME_PTR) is
      new SYSTEM.STORAGE_POOLS.ROOT_STORAGE_POOL with private;

   procedure ALLOCATE
      (
      POOL                     : in out USER_POOL;
      STORAGE_ADDRESS          :    out SYSTEM.ADDRESS;
      SIZE_IN_STORAGE_ELEMENTS : in
SYSTEM.STORAGE_ELEMENTS.STORAGE_COUNT;
      ALIGNMENT                : in
SYSTEM.STORAGE_ELEMENTS.STORAGE_COUNT
      );
     
   procedure DEALLOCATE
      (
      POOL                     : in out USER_POOL;
      STORAGE_ADDRESS          : in     SYSTEM.ADDRESS;
      SIZE_IN_STORAGE_ELEMENTS : in
SYSTEM.STORAGE_ELEMENTS.STORAGE_COUNT;
      ALIGNMENT                : in
SYSTEM.STORAGE_ELEMENTS.STORAGE_COUNT
      );      
     
   function STORAGE_SIZE
      (
      POOL : in USER_POOL
      )
      return SYSTEM.STORAGE_ELEMENTS.STORAGE_COUNT;
      
   function GET_POOL_NAME
      (
      POOL : in USER_POOL
      )
      return POOL_NAME;

I defined an access type for this type:

   type POOL_PTR is access all USER_POOL;

I defined an unconstrained array of POOL_PTRs:

   type POOL_LIST is array ( INTEGER range <> ) of POOL_PTR;

I defined a pointer to this type to allow it to be easily
passed to subprograms:

   type POOL_CFG_PTR is access all POOL_LIST;

Another package is initialised with a pools list:

   -- STORAGE_POOLS_LIST is populated by an initialisation procedure:

   MY_POOL : POOL_LIST.POOL_PTR := STORAGE_POOLS_LIST(I);

   type INT_ACC is access INTEGER;
   for INT_ACC'storage_pool use MY_POOL.all;

My test program is able to create a number of storage pools
and call operations such as GET_POOL_NAME, STORAGE_SIZE against
dereferenced elements of STORAGE_POOLS_LIST. These tests
have the desired affect.

The problem is how to use the storage pools I've created.
I'm having trouble with  "for XYZ'storage_pool use ..." syntax
when used with a USER_POOL access variable:

   STORAGE_POOLS_LIST : POOL_CFG_PTR := null;

   -- STORAGE_POOLS_LIST is populated by an initialisation procedure

   MY_POOL : POOL_LIST.POOL_PTR := STORAGE_POOLS_LIST(I);

   type INT_ACC is access INTEGER;
   for INT_ACC'storage_pool use MY_POOL.all;

GNAT 3.11b2 responds with the following error for the use clause:

	"incorrect reference to a Storage Pool"

What am I doing wrong?
What obscure syntax do I need?
Am I trying to violate basic principles of storage pools?

Cheers,
-- 
Graeme Perkes                        GEC Marconi Systems Pty Limited
mailto:graeme.perkes@gecms.com.au    40-52 Talavera Road, North Ryde
Tel: +61 2 9855 8961                 NSW 2113 Australia
Fax: +61 2 9855 8884




^ permalink raw reply	[relevance 4%]

* Garbage Collection for Ada
@ 1999-02-19  0:00  3% Nick Roberts
  0 siblings, 0 replies; 96+ results
From: Nick Roberts @ 1999-02-19  0:00 UTC (permalink / raw)


In another thread, Robert Dewar (dewar@gnat.com) wrote...
|It is of course trivial to implement conservative garbage
|collection, and any number of the commercial tools in this
|area work fine with GNAT. That is of course a given, but
|that is not what I was talking about, I was talking about
|implementing full, accurate, compacting garbage collection
|of the type expected in an Algol-68 compiler. That's a big
|project, probably several person months from someone who
|knows what they are doing, longer for someone who has to
|learn.

I am serious about doing half of this myself, and making it freely available
(under an 'open source' licence - see http://www.opensource.com).

Which half? The half which can be compiler-independent, and implemented
entirely in terms of user-defined pool types.

And the other half? I believe compiler makers would have to provide certain
extra facilities (to those specified by the RM95) in order to enable
comprehensive strategies to work (reliably). I would expect other people to
provide these facilities; it would not be appropriate for me (and I am not
willing) to do this half myself.

These facilities might constitute: (a) a new abstract type (or maybe
several), derived from System.Storage_Pools.Root_Storage_Pool, which defines
certain extra operations; (b) a new pragma; (c) crib generation and a
package to access the crib.

The new type might be called Root_Managed_Pool, and provide the extra
subprograms:

   function Flag (Pool: in Root_Storage_Pool; Object: in Storage_Address)
return Boolean is abstract;

   procedure Set_Flag (Pool: in out Root_Storage_Pool; Object: in
Storage_Address; Value: Boolean := True) is abstract;

   procedure Flagged_Access (Pool: in out Root_Storage_Pool; Object: out
Storage_Address) is abstract;

The idea is that each possible access object within the pool has a Boolean
flag associated with it, and that, under Trap_Flagged_Read_Access and
Trap_Flagged_Write_Access (see below), whenever the compiler attempts to
dereference an access object (for reading or writing respectively) whose
flag is set (True), it calls Flagged_Access first. Upon return from
Flagged_Access, the dereference continues as normal.

The pragma might be:

   pragma Access_Object_Semantics ([Pool_Type =>] type_name,
ao_semantics_item {,ao_semantics_item});

where ao_semantics_item might be one of: Block_Local_Temporaries;
Double_Indirection; Trap_Flagged_Read_Access; Trap_Flagged_Write_Access;
Protected_Access.

Block_Local_Temporaries is intended to prevent the storage of access object
values in temporary places other than where the temporary is loaded and
spilled back entirely within one block (in the source text).
Double_Indirection causes each dereference to be in terms of a
pointer-to-a-pointer (i.e. a double dereference). Protected_Access causes
each dereference to be pool-atomic (thus, almost certainly, having to be
surrounded by a semaphore lock/unlock or similar).

To create a managed pool type, the programmer would derive a type from
Root_Managed_Pool, apply the pragma Access_Object_Semantics to it (with the
appropriate semantics), and then override the various subprograms as
necessary.

My initial idea for a package specification for crib access is enclosed
(below). It
has deficiencies at present, but it gives the general 'flavour'.

Of course, these are all merely preliminary ideas at this stage. They will
have to be discussed, amended, and 'firmed up'.

However, what I need now is some sort of assurance that at least some
compiler makers (including ACT or someone else suitable for modifying GNAT)
would be willing to implement these facilities (or at least would seriously
entertain the idea of doing so).

If the general attitude is going to be "sorry, not interested", then,
naturally, I shall consider it a waste of my time developing the garbage
collectors. Otherwise, all compiler makers who implement the above
facilities will then stand to be able to instantly add my wonderful set of
garbage collectors (which will, genuinely, boast state-of-the-art
technology) to their own compilers. (True, it may take me several 'person
months', but I do know what I'm doing!)

-------------------------------------
Nick Roberts
-------------------------------------



----------------------------------------------------------------------------
--
-- Garbage Collection for Ada Project
----------------------------------------------------------------------------
--

with System.Storage_Elements;

package System.Crib_Access is

   subtype Access_Component_Count is Integer range 0..???;

   type Access_Component_List (NAC: Access_Component_Count) is
      record
         Offsets: array (1..NAC) of System.Storage_Elements.Storage_Offset;
      end record;

   type Access_Component_List_Lookup is
                                     access constant Access_Component_List;

   type Access_Object_Kind is (Single_Object, Array_Object, Record_Object);

   subtype Array_Length is Integer range 0..Integer'Last; -- correct?

   type Access_Object_Descriptor (Kind: Access_Object_Kind) is
      record
         Location: System.Address;
         case Kind is
            when Single_Object => null;
            when Array_Object  => Count: Array_Length;
            when Record_Object => Cmpts: Access_Component_List_Lookup;
         end case;
      end record;

   type Access_Object_Descriptor_Lookup is
                                  access constant Access_Object_Descriptor;

   subtype Access_Object_Count is Integer range 0..???;

   type Activation_Record_Crib (NAO: Access_Object_Count) is
      record
         AOD: array (1..NAO) of Access_Object_Descriptor_Lookup;
      end record;

   subtype Dynamic_Structure_Crib is Access_Object_Crib;

   type Activation_Record_Crib_Lookup is
                                    access constant Activation_Record_Crib;
   type Dynamic_Structure_Crib_Lookup is
                                    access constant Dynamic_Structure_Crib;

   subtype Activation_Record_Count is Integer range 0..???;
   subtype Dynamic_Structure_Count is Integer range 0..???;

   type Program_Crib (NAR: Activation_Record_Count;
                      NDS: Dynamic_Structure_Count) is
      record
         ARC: array (1..NAR) of Activation_Record_Crib_Lookup;
         DSC: array (1..NDS) of Dynamic_Structure_Crib_Lookup;
      end record;

   type Program_Crib_Lookup is access constant Program_Crib;

   function Current_Crib return Program_Crib_Lookup;

end System.Crib_Access;







^ permalink raw reply	[relevance 3%]

* Re: Classwide-type assignments [longish]
  @ 1998-10-15  0:00  4%   ` Niklas Holsti
  0 siblings, 0 replies; 96+ results
From: Niklas Holsti @ 1998-10-15  0:00 UTC (permalink / raw)


This continues my earlier posting, where I wrote:
> 
> jsanchor@cs5.dasd.honeywell.com wrote:
>   [ snip ]
> > I have been trying to assign classwide types with no luck.
    [ snip ]
> I don't think that you can use ":=" to move class-wide
> data to an uninitialized memory area. Perhaps you could
> make a custom Storage Pool that allocates target objects
> from the NV RAM? Then you could clone the RAM object into
> the NV RAM using "new" for the NV RAM Storage Pool.
    [ snip ]

Just for fun, I wrote a custom Storage_Pool sketch to handle
allocations in a special RAM area. Source code included below.
The allocator is trivial (sequential allocation, no deallocation)
but may give you a starting point if you decide to use this
approach.

I tested the program on an i486 with Linux 2.0.0 and GNAT 3.05.
The program consists of
    nv_main.adb      Main procedure
    nv_pool.ad[sb]   Custom storage pool
    nv_user.ad[sb]   Example client with descendant type.

The expected output is:

My_Int.Value =  12345
Allocating 8 elements, alignment = 4
New NV_Off = 8
NV.Value =  12345


Good luck,
Niklas Holsti


-------------- nv_main.adb
with NV_User;

procedure NV_Main is
begin
   NV_User.Use_It;
end NV_Main;


-------------- nv_user.ads
-- This package makes a descendant type of NV_Pool.NV_Object
-- and tries it out.

package NV_User is

   procedure Use_It;

end NV_User;


-------------- nv_user.adb
with NV_Pool;
with Text_IO;
use  Text_IO;

package body NV_User is

   -- The descendant type:
   type NV_Int is new NV_Pool.NV_Object with record
      Value : integer;
   end record;

   type Int_Pointer is access all NV_Int'Class;
   -- This access type can access either RAM or NV RAM objects,
   -- but will create new objects in NV RAM only.

   for Int_Pointer'Storage_Pool use NV_Pool.NV_Pointer'Storage_Pool;
   -- It's a nuisance to have to define the Storage_Pool for
   -- all descendant pointers. Perhaps a generic package could
   -- be made to sort of "mix in" the NV'ness facet.


   My_Int : aliased NV_Int;
   -- The RAM object to be copied to NV RAM.


   procedure Use_It
   is

      RAM_Ptr : Int_Pointer := My_Int'Access;
      -- Pointer to the RAM object (specific type).

      RAM_Class_Ptr : NV_Pool.Pointer := NV_Pool.Pointer (RAM_Ptr);
      -- Pointer to the RAM object (class-wide).

      NV_Ptr : Int_Pointer;
      -- Pointer to the NV RAM copy (specific type).

      NV_Class_Ptr : NV_Pool.Pointer;
      -- Pointer to the NV RAM copy (class-wide).

   begin

      My_Int.Value := 12345;
      -- Define the RAM data.

      Put_Line ("My_Int.Value = " & integer'image(My_Int.Value));

      NV_Ptr := new NV_Int;
      -- Create a place in the NV RAM of this type.
      -- This uses the custom NV storage pool.

      -- Note that the copy in NV RAM could be created simply
      -- by  "NV_Ptr := new NV_Int'(My_Int);".
      -- The following stuff with class-wide accesses is only
      -- to answer the original question on comp.lang.ada.

      NV_Class_Ptr := NV_Pool.Pointer (NV_Ptr);
      -- Make a class-wide pointer to the NV RAM place.

      NV_Class_Ptr.all := RAM_Class_Ptr.all;
      -- Copy the data, class-wide to class-wide.
      -- This includes a tag check. Note that the "new"
      -- for NV_Ptr sets the tag of the NV RAM cell, although
      -- the other components are undefined.

      Put_Line ("NV.Value = " & integer'image(NV_Ptr.Value));

   end Use_It;

end NV_User;


-------------- nv_pool.ads
with System.Storage_Pools;
with System.Storage_Elements;
use  System.Storage_Elements;

package NV_Pool is

   type NV_Object is abstract tagged null record;
   -- The root type for objects that can be copied to
   -- Non-Volatile memory.

   type NV_Pointer is access NV_Object'Class;
   -- Pointer to an object in the Non-Volatile memory.
   -- This access type has a custom storage pool that
   -- allocates areas from the Non-Volatile memory.
   -- Note that access types for descendants of NV_Object
   -- will NOT inherit the custom storage pool, but must
   -- specify it, for example:
   --    for My_NV_Pointer'Storage_Pool use
   --       NV_Pool.NV_Pointer'Storage_Pool;

   type Pointer is access all NV_Object'Class;
   -- Pointer to an object in the volatile memory or in
   -- the non-volatile memory.
   -- This access type uses the default storage pool.


private

   -- Custom Storage Pool for Non-Volatile objects.

   type NV_Storage_Pool is
      new System.Storage_Pools.Root_Storage_Pool
      with null record;

   procedure Allocate (
      Pool            : in out NV_Storage_Pool;
      Storage_Address : out System.Address;
      Size_In_Storage_Elements : in Storage_Count;
      Alignment       : in Storage_Count);

   procedure Deallocate (
      Pool            : in out NV_Storage_Pool;
      Storage_Address : in System.Address;
      Size_In_Storage_Elements : in Storage_Count;
      Alignment       : in Storage_Count);

   function Storage_Size (Pool : NV_Storage_Pool) return Storage_Count;

   NV_Storage : NV_Storage_Pool;

   -- Use the custom allocator for NV objects.

   for NV_Pointer'Storage_Pool use NV_Storage;

end NV_Pool;


-------------- nv_pool.adb
with Text_IO;

package body NV_Pool is
   
   -- Storage to simulate the Non-Volatile area.
   -- The important parts are NV_Size and NV_Address which are
   -- used in the storage pool operations.
   -- For a real NV RAM, modify the value of NV_Size, delete
   -- NV_Simu, and set NV_Address to the literal starting
   -- address.

   NV_Size    : constant Storage_Count  := 1000;

   subtype NV_Count is Storage_Count range 0 .. NV_Size;
   subtype NV_Index is NV_Count range 0 .. NV_Count'last - 1;

   NV_Simu    : array (NV_Index) of Storage_Element;
   NV_Address : constant System.Address :=
NV_Simu(NV_Simu'first)'address;


   -- Custom pool defined as NV_Size storage-elements starting
   -- at address NV_Address.

   NV_Off  : Storage_Offset := 0;
   --  Offset from NV_Address to the next free location.


   procedure Allocate (
      Pool            : in out NV_Storage_Pool;
      Storage_Address : out System.Address;
      Size_In_Storage_Elements : in Storage_Count;
      Alignment       : in Storage_Count)
   --
   -- Allocates NV memory sequentially from NV_Off.
   -- Updates NV_Off.
   --
   is

      Misalign : constant Integer_Address :=
         To_Integer (NV_Address + NV_Off) mod Integer_Address
(Alignment);
      -- The amount of misalignment in NV_Off.

      Next_Off : Storage_Offset;
      -- The aligned value of NV_Off.

   begin
      Text_IO.Put_Line (
         "Allocating"
         & Storage_Count'image(Size_In_Storage_Elements)
         & " elements, alignment ="
         & Storage_Count'image(Alignment));

      -- Check for alignment.
      if Misalign > 0 then
         -- Advance offset to next aligned location.
         Next_Off := NV_Off + (Alignment - Storage_Count(Misalign));
      else
         -- Already aligned.
         Next_Off := NV_Off;
      end if;

      -- Check if storage left.
      if NV_Size - Next_Off < Size_In_Storage_Elements then
         raise Storage_Error;
      end if;

      -- Return address and reserve space.
      Storage_Address := NV_Address + Next_Off;
      NV_Off          := Next_Off + Size_In_Storage_Elements;

      Text_IO.Put_Line (
         "New NV_Off =" & Storage_Offset'image(NV_Off));

   end Allocate;


  procedure Deallocate (
      Pool            : in out NV_Storage_Pool;
      Storage_Address : in System.Address;
      Size_In_Storage_Elements : in Storage_Count;
      Alignment       : in Storage_Count)
   --
   -- Deallocation is not implemented.
   --
   is
   begin
      Text_IO.Put_Line (
         "Deallocating"
         & Storage_Count'image (Size_In_Storage_Elements)
         & " elements, alignment ="
         & Storage_Count'image (Alignment)
         & ", address ="
         & Integer_Address'image(To_Integer(Storage_Address)));

      null;

   end Deallocate;


   function Storage_Size (Pool : NV_Storage_Pool) return Storage_Count
   is
   begin
      return NV_Size;
   end Storage_Size;


end NV_Pool;




^ permalink raw reply	[relevance 4%]

* Re: Freeing Pointers to classwide types
  @ 1998-09-28  0:00  8%                     ` Richard D Riehle
  1998-09-28  0:00  5%                       ` Pat Rogers
  0 siblings, 1 reply; 96+ results
From: Richard D Riehle @ 1998-09-28  0:00 UTC (permalink / raw)


In article <6uo83j$dv2$1@nnrp1.dejanews.com>,
	dewarr@my-dejanews.com wrote:

In reply to a question from Tom Moran about System.Storage_Pools (ALRM
13.11),

>You really should look at the Storage_Pools facility. You seem to be
declaring
>that you are sure it is not a modest change, but then ask questions that
>suggest you are not quite sure what such a change would involve. In the
case
>of GNAT, it is just a matter of adding a single representation clause for
the
>type, not a big burden.

I checked the GNAT documentation. Am I missing something, I wonder?  Does
GNAT already include an overloading of the subprograms in
System.Storage_Pool.  If so, Robert's assertion that "it is just a matter of
adding a single representation clause" might be sufficient.  Otherwise, it
is a bit misleading in its suggestion of simplicity.

The representation clause is only a small part of the requirement for
using the abstract class package System.Storage_Pools.  One must also
overload the Allocate and Deallocate procedures.  In fact, to make this
package really useful, one must also overload the initialize and finalize
procedures from Ada.Finalization.  

There are very few examples in the literature for using 
System.Storage_Pools.  At several Ada conferences I asked prominent
technical experts if they could point me to some references where someone
had actually implemented an overloading  of System.Storage_Pools.  None of
those I asked were forthcoming.  The example in the Rationale falls into the
category of "seduced and abandoned."

More recently, John Barnes, dependable Ada stalwart, included an excellent
example in the Second Edition of his book, Programming in Ada 95.  It is
fully coded, readable, and enlightening.  However, it is clear from studying
the Barnes example that System.Storage_Pools is, in practice, a non-trivial
issue.   

Richard Riehle
richard@adaworks.com
http://www.adaworks.com


 




^ permalink raw reply	[relevance 8%]

* Re: Freeing Pointers to classwide types
  1998-09-28  0:00  8%                     ` Richard D Riehle
@ 1998-09-28  0:00  5%                       ` Pat Rogers
  0 siblings, 0 replies; 96+ results
From: Pat Rogers @ 1998-09-28  0:00 UTC (permalink / raw)


Richard D Riehle wrote in message
<6uojcq$bp2@sjx-ixn3.ix.netcom.com>...
>In article <6uo83j$dv2$1@nnrp1.dejanews.com>,
> dewarr@my-dejanews.com wrote:
>
>In reply to a question from Tom Moran about System.Storage_Pools
(ALRM
>13.11),
>
>>You really should look at the Storage_Pools facility. You seem to
be
>declaring
>>that you are sure it is not a modest change, but then ask
questions that
>>suggest you are not quite sure what such a change would involve.
In the
>case
>>of GNAT, it is just a matter of adding a single representation
clause for
>the
>>type, not a big burden.
>
>I checked the GNAT documentation. Am I missing something, I wonder?
Does
>GNAT already include an overloading of the subprograms in
>System.Storage_Pool.  If so, Robert's assertion that "it is just a
matter of
>adding a single representation clause" might be sufficient.
Otherwise, it
>is a bit misleading in its suggestion of simplicity.

Given the declaration of a pool, all that is required is for the
user to do as Robert says.  The hard part is writing the extension
of Ada.System.Storage_Pools for use in declaraing the pool, and I
gather than GNAT has done this.

>There are very few examples in the literature for using
>System.Storage_Pools.  At several Ada conferences I asked prominent
>technical experts if they could point me to some references where
someone
>had actually implemented an overloading  of System.Storage_Pools.
None of
>those I asked were forthcoming.  The example in the Rationale falls
into the
>category of "seduced and abandoned."

One of the things I've been teaching for the last few years in my
Real-Time class is how to do this, and I show in detail how to write
a deterministic fixed-block pool manager since there are so few
examples around.  I have this little saying I give after the
schedulability analysis chapter: "If you don't take responsbility
for storage management, you'll run out of storage right on
schedule."

In an upcomng release of the Booch Components, you will see an
example of a general purpose ("Managed") allocator that I wrote
based directly on Grady's C++ version.








^ permalink raw reply	[relevance 5%]

* deallocating class-wide objects
@ 1998-07-06  0:00  5% Stephen Leake
  0 siblings, 0 replies; 96+ results
From: Stephen Leake @ 1998-07-06  0:00 UTC (permalink / raw)



When I run the code below (compiled with GNAT 3.10p, Windows NT 4.0),
I get the following output (the Test_Storage_Pools package just adds
debug statments to 'new' and 'free') :

./test_allocate.exe 
allocating   12 from Puppet_Storage_Pool
deallocating 4 from Puppet_Storage_Pool

allocating   8 from Puppet_Storage_Pool
deallocating 4 from Puppet_Storage_Pool

allocating   12 from Muppet_Storage_Pool
deallocating 12 from Muppet_Storage_Pool

The first two cases are wrong; it should deallocate the same amount it
allocates. It appears that GNAT is deallocating just enough for the
root type, rather than for the derived type. The third case
deallocates the derived type directly, and works as expected.

I can't bring myself to believe that GNAT has a bug this
basic at this stage in the game. On the other hand, ObjectAda won't
even compile this code (bug report in the works). Can anyone confirm
that GNAT is wrong, or am I doing something erroneous?

-- Stephe.

with Ada.Text_IO; use Ada.Text_IO;
with Ada.Unchecked_Deallocation;
with Test_Storage_Pools;
procedure Test_Allocate is
   type Puppet_Type is abstract tagged null record;
   type Puppet_Access_Type is access Puppet_Type'Class;

   Puppet_Storage_Pool_Name : aliased String := "Puppet_Storage_Pool";
   Puppet_Storage_Pool : Test_Storage_Pools.Storage_Pool_Type
      (1000, Puppet_Storage_Pool_Name'access);
   for Puppet_Access_Type'Storage_Pool use Puppet_Storage_Pool;

   procedure Free_Puppet is new Ada.Unchecked_Deallocation
      (Puppet_Type'Class, Puppet_Access_Type);

   Muppet_Storage_Pool_Name : aliased String := "Muppet_Storage_Pool";
   Muppet_Storage_Pool : Test_Storage_Pools.Storage_Pool_Type
         (1000, Muppet_Storage_Pool_Name'access);

   type Muppet_Type is new Puppet_Type with record
      Arms : Integer;
      Fingers : Integer;
   end record;

   type Muppet_Access_Type is access Muppet_Type'Class;
   for Muppet_Access_Type'Storage_Pool use Muppet_Storage_Pool;

   procedure Free_Muppet is new Ada.Unchecked_Deallocation
       (Muppet_Type'Class, Muppet_Access_Type);

   type Beanie_Type is new Puppet_Type with record
      Legs : Integer;
   end record;

   Puppet_1 : Puppet_Access_Type;
   Puppet_2 : Puppet_Access_Type;

   Muppet_3 : Muppet_Access_Type;
begin
   Test_Storage_Pools.Set_Debug (Puppet_Storage_Pool, True);
   Test_Storage_Pools.Set_Debug (Muppet_Storage_Pool, True);

   Puppet_1 := new Muppet_Type'(2, 5);
   Free_Puppet (Puppet_1);

   New_Line;
   Puppet_2 := new Beanie_Type'(Legs => 4);
   Free_Puppet (Puppet_2);

   New_Line;
   Muppet_3 := new Muppet_Type'(3, 4);
   Free_Muppet (Muppet_3);
end Test_Allocate;

with Ada.Text_IO;
with System.Address_To_Access_Conversions;
with Ada.Exceptions;
package body Test_Storage_Pools is

   Block_Header_Size : constant System.Storage_Elements.Storage_Count :=
      System.Storage_Elements.Storage_Count
        (Block_Header_Type'Size /
         System.Storage_Elements.Storage_Element'Size);

   -- This would be cleaner if Address_To_Access_Conversions took the
   -- pointer type as parameter, instead of declaring it!
   package Address_To_Block_Access is
      new System.Address_To_Access_Conversions (Block_Header_Type);

   function To_Block_Access (Address : in System.Address)
      return Block_Access_Type
   is begin
      return Block_Access_Type (Address_To_Block_Access.To_Pointer (Address));
   end To_Block_Access;

   function To_Address (Value : in Block_Access_Type) return System.Address
   is begin
      return Address_To_Block_Access.To_Address
        (Address_To_Block_Access.Object_Pointer (Value));
   end To_Address;

   function Aligned_Address
      (Address     : in System.Address;
       Alignment   : in System.Storage_Elements.Storage_Count)
      return System.Address
      -- Adjust Address upwards to next Alignment.
   is
      use System.Storage_Elements;
      Aligned : Integer_Address := To_Integer (Address) + To_Integer
         (Address) rem Integer_Address (Alignment);
   begin
      return To_Address (Aligned);
   end Aligned_Address;

   -----------
   -- Override Root_Storage_Pool operations

   procedure Allocate
      (Pool                     : in out Storage_Pool_Type;
       Storage_Address          :    out System.Address;
       Size_In_Storage_Elements : in     System.Storage_Elements.Storage_Count;
       Alignment                : in     System.Storage_Elements.Storage_Count)
   is
      use System.Storage_Elements;
      use Ada.Exceptions;
      Block           : Block_Access_Type := Pool.First_Free;
      Remaining_Block : Block_Access_Type;
      Aligned         : System.Address;
      Prev            : Block_Access_Type := null;
   begin
      if Pool.Debug then
         Ada.Text_Io.Put_Line ("allocating  " &
                               Storage_Count'Image (Size_In_Storage_Elements) &
                               " from " &
                               Pool.Name.all);
      end if;

      if Size_In_Storage_Elements < Block_Header_Size  then
         Raise_Exception (Storage_Error'Identity,
                          "Allocate: block size < header size");
      end if;

      Find_Free_Fit :
      loop
         if Block = null then
            Raise_Exception (Storage_Error'Identity,
                             "Allocate: pool full (or fragmented)");
         end if;
         exit Find_Free_Fit when Block.Size >= Size_In_Storage_Elements;
         Prev := Block;
         Block := Block.Next;
      end loop Find_Free_Fit;

      Aligned := Aligned_Address
          (Address => To_Address (Block) + Size_In_Storage_Elements,
           Alignment => 8);

      if To_Integer (Aligned) + Integer_Address (Block_Header_Size) <
         To_Integer (To_Address (Block)) + Integer_Address (Block.Size)
      then
         Remaining_Block := To_Block_Access (Aligned);
         if Prev = null then
            -- Allocated from first free block.
            Pool.First_Free := Remaining_Block;
         else
            Prev.Next := Remaining_Block;
         end if;

         Remaining_Block.all :=
            (Size => Block.Size - Size_In_Storage_Elements,
             Next => Block.Next);
      else
         -- Remaining space too small for a block.
         -- Just link to next free block.
         if Prev = null then
            -- Allocated from first free block.
            Pool.First_Free := Pool.First_Free.Next;
         else
            Prev.Next := Block.Next;
         end if;

      end if;

      Storage_Address := To_Address (Block);
   end Allocate;

   procedure Deallocate
      (Pool                     : in out Storage_Pool_Type;
       Storage_Address          : in     System.Address;
       Size_In_Storage_Elements : in     System.Storage_Elements.Storage_Count;
       Alignment                : in     System.Storage_Elements.Storage_Count)
   is
      use System.Storage_Elements;
      Block : Block_Access_Type := To_Block_Access (Storage_Address);
   begin
      if Pool.Debug then
         Ada.Text_Io.Put_Line ("deallocating" &
                               Storage_Count'Image (Size_In_Storage_Elements) &
                               " from " &
                               Pool.Name.all);
      end if;
      -- Add block to head of free list

      Block.all :=
         (Size => Size_In_Storage_Elements,
          Next => Pool.First_Free);
      Pool.First_Free := Block;

   end Deallocate;

   function Storage_Size (Pool : Storage_Pool_Type)
    return System.Storage_Elements.Storage_Count
   is begin
      return Pool.Pool_Size;
   end Storage_Size;

   -----------
   -- New operations

   procedure Set_Debug (Pool : in out Storage_Pool_Type; Debug : in Boolean)
   is begin
      Pool.Debug := Debug;
   end Set_Debug;

   procedure Initialize (Pool : in out Storage_Pool_Type)
   is
      use type System.Storage_Elements.Storage_Offset;
      use Ada.Exceptions;
   begin
      if Pool.Pool_Size < Block_Header_Size then
         Raise_Exception (Storage_Error'Identity,
                          "Initialize: pool_size < header_size");
      end if;

      Pool.Debug := False;
      Pool.First_Free := To_Block_Access
         (Aligned_Address
          (Address => Pool.Storage'Address,
           Alignment => 8));
      Pool.First_Free.all := (Pool.Pool_Size, null);
   end Initialize;

end Test_Storage_Pools;

with System.Storage_Pools;
with System.Storage_Elements;
package Test_Storage_Pools is

   type Storage_Pool_Type
      (Pool_Size : System.Storage_Elements.Storage_Count;
       Name      : access String) -- for debug messages
   is new System.Storage_Pools.Root_Storage_Pool with private;

   -----------
   -- Override Root_Storage_Pool operations

   procedure Allocate
      (Pool                     : in out Storage_Pool_Type;
       Storage_Address          :    out System.Address;
       Size_In_Storage_Elements : in     System.Storage_Elements.Storage_Count;
       Alignment                : in     System.Storage_Elements.Storage_Count);

   procedure Deallocate
      (Pool                     : in out Storage_Pool_Type;
       Storage_Address          : in     System.Address;
       Size_In_Storage_Elements : in     System.Storage_Elements.Storage_Count;
       Alignment                : in     System.Storage_Elements.Storage_Count);

   function Storage_Size (Pool : in Storage_Pool_Type)
    return System.Storage_Elements.Storage_Count;

   -----------
   -- New operations

   procedure Set_Debug (Pool : in out Storage_Pool_Type; Debug : in Boolean);
   -- If Debug is True, Allocate and Deallocate print helpful messages to
   -- Standard_Output.

private

   procedure Initialize (Pool : in out Storage_Pool_Type);

   type Block_Header_Type;
   type Block_Access_Type is access all Block_Header_Type;
   type Block_Header_Type is record
      Size : System.Storage_Elements.Storage_Count;
      Next : Block_Access_Type;
   end record;

   type Storage_Pool_Type
      (Pool_Size : System.Storage_Elements.Storage_Count;
       Name      : access String)
   is new System.Storage_Pools.Root_Storage_Pool with record
         Debug                  : Boolean;
         First_Free             : Block_Access_Type;
         Storage                : System.Storage_Elements.Storage_Array
                                    (1 .. Pool_Size);
         -- The first few elements of each free block contain the block header.
         -- Storage_Error is raised if a free block is smaller than the
         -- block header size.
         -- All blocks have alignment 8, to keep things simple.
      end record;

end Test_Storage_Pools;




^ permalink raw reply	[relevance 5%]

* user specified storage pools
@ 1998-07-06  0:00  5% Stephen Leake
  0 siblings, 0 replies; 96+ results
From: Stephen Leake @ 1998-07-06  0:00 UTC (permalink / raw)



I've started playing with user specified storage pools, mainly to
implement a poor man's Purify to help test my list and binary tree
packages. It turned out to be simple to accomplish my main goal
(although I've found several compiler bugs in the process!).

However, I don't see how to cleanly provide users of the list package
the option of providing a user defined storage pool. Consider this
list package:

package Sal is

   -- Global access type, to allow specifying default storage pools for
   -- containers. Don't use for anything else!
   type Global_Access_Type is access all Integer;

end Sal;

with Ada.Finalization;
with System.Storage_Pools;
generic
   type Item_Type (<>) is limited private;
   type Item_Node_Type is private;
   with function To_Item_Node (Item : in Item_Type) return Item_Node_Type;
   with procedure Free_Item (Item : in out Item_Node_Type);
   -- <nice comments on how to instantiate this stuff>

   Node_Storage_Pool : in out System.Storage_Pools.Root_Storage_Pool'Class;
   -- Root_Storage_Pool is limited, which does not allow defaults.
   -- Default for a global list should be Sal.Global_Access_Type'Storage_Pool.
   -- Default for a local list, which should be reclaimed when the list
   -- type goes out of scope, is implementation defined (sigh).

package Sal.Lists_Single is

   ----------
   -- List operations

   < the usual stuff >

private
   type Node_Type;

   type Node_Access_Type is access Node_Type;
   for Node_Access_Type'Storage_Pool use Node_Storage_Pool;

   type Node_Type is record
      Item : Item_Node_Type;
      Next : Node_Access_Type;
   end record;

   type List_Type is new Ada.Finalization.Limited_Controlled with record
      Head : Node_Access_Type;
   end record;

end Sal.Lists_Single;

The question is how to make this easy for novices to instantiate,
while still providing power users the option of user specified storage
pools. Since Root_Storage_Pool is a limited type, we cannot specify a
default. Thus novices are forced to think about storage pools to use
this list package. On top of that, there is no way for the user to say
"just do what the compiler normally does"; that is, pretend the
'Storage_Pool clause for Node_Access_type was not present.

Is telling users to specify Sal.Global_Access_Type'Storage_Pool for
Node_Storage_Pool safe? For GNAT 3.10p it appears to be "what the
compiler normally does" for global types. However, I can envision a
more advanced compiler picking an allocation algorithm based on the
type (fixed size vs variable size, etc).

If Node_Storage_Pool was of type "access Root_Storage_Pool'class", it
could have a default. Then I could use a pre-processor to turn on or
off the 'Storage_Pool clause for Node_Access_Type. But I'd like a
better way!

-- Stephe




^ permalink raw reply	[relevance 5%]

* Re: Allocating memory--Ada95
  @ 1998-05-19  0:00  5% ` Matthew Heaney
  0 siblings, 0 replies; 96+ results
From: Matthew Heaney @ 1998-05-19  0:00 UTC (permalink / raw)



In article <6jsa9j$ous$1@nnrp1.dejanews.com>, jsanchor@my-dejanews.com wrote:

(start of quote)
I am trying to dynamically allocate storage(using 'new' allocator)...but I
need to allocate within certain bounds. Does anybody know how.
Thank you in advance.
(end of quote)

Override Root_Storage_Pool, declare an object of that type, and place
storage in memory where you require, as in 

with System.Storage_Pools; use ...;
package My_Storage_Pools is

   type My_Storage_Pool (Size : Positive) is
      new Root_Storage_Pool with record
         Elements : Storage_Element_Array (1 .. Size);
      end record;

   <primitive ops>

end;

with My_Storage_Pool; use ...;
package Allocation is

   Pool : My_Storage_Pool (<some large size>);
   for Pool'Address use <some address>;

end;

Now when you declare an access type, use your custom pool to as its storage
pool:

with Allocation;
package P is

   type T is ...;
   type T_Access is access T;
   for T_Access'Storage_Pool use Allocation.Pool;

end;

That's the general flavor of solution.




^ permalink raw reply	[relevance 5%]

* Re: Are global or persistent variables in ADA?
  @ 1998-05-01  0:00  7%   ` Matthew Heaney
  0 siblings, 0 replies; 96+ results
From: Matthew Heaney @ 1998-05-01  0:00 UTC (permalink / raw)



In article <35420cc3.0@news.pacifier.com>, "Steve Doiel"
<nospam_steved@pacifier.com> wrote:

(start of quote)
Fully global variables are
declared inside of a package spec (IMHO not a good practice).
(end of quote)

One idiom where "global" variables do make sense is in the construction of
a subsystem, a complex abstraction that comprises several packages, ie

package P is

   <this is the public interface of the abstraction>

end P;

private package P.Q is

   O : T;
   --
   -- O is a "global" variable, shared by children of P.  However, it is only
   -- global with the subsystem rooted at P.

end P.Q;

with P.Q;
package body P.R is

   ... Q.O ...

end P.R;

This is a handy technique to use when you have data shared among many
modules in a subsystem; perhaps a semaphore or something.

Another example of having a global data, not even in a private package,
would be a storage pool object.  You may decide that all access types in an
application will use a non-default storage pool that you've defined, ie

package Storage_Pools is

   type XYZ_Storage_Pool is
      new Root_Storage_Pool with ...;

   Pool : Storage_Pool;

end Storage_Pools;

As a matter a fact, I did something like this in some B-trees I just wrote. 
One technique I like to use is to pass in a storage pool object to a
dynamic memory manager abstraction, ie

with System.Storage_Pools;

generic

   System_Storage_Pool : in out System.Storage_Pools.Root_Storage_Pool'Class;

package ACL.Trees.Storage.BPlus_Tree.Dynamic_G is

   pragma Elaborate_Body;

   type Dynamic_Storage_Pool is
     new Root_Storage_Pool with private;
...


package body ACL.Trees.Storage.BPlus_Tree.Dynamic_G is

   type Dynamic_Page_Access is
      access all Page_Base;

   for Dynamic_Page_Access'Storage_Pool use System_Storage_Pool;


And I instantiate it as follows:

with ACL.Trees.Storage.BPlus_Tree.Dynamic_G;

package BPlus.Storage.Dynamic is
   new BPlus.Storage.Dynamic_G (BPlus.Storage.Page_Access'Storage_Pool);
 
where I simply use the pool associated with another, already-existing
access type.


Actually, I do declare a global storage pool object, that I use to
instantiate the B-tree iteself;


with BPlus.Storage.Dynamic; use BPlus.Storage.Dynamic;

package BPlus.Storage_Pools is

   Pool : Dynamic_Storage_Pool;

end;

with Ada.Finalization;
with ACL.Trees.Storage.BPlus_Tree;

generic

   type B_Tree_Item is private;

   with function "=" (L, R : B_Tree_Item) return Boolean is <>;
...
   with package Storage is
    new ACL.Trees.Storage.BPlus_Tree
     (B_Tree_Item,
      B_Tree_Item_Array,
      B_Tree_Key,
      B_Tree_Key_Array,
      Index_Order,
      Sequence_Order);

   type B_Tree_Storage_Pool is
     new Storage.Root_Storage_Pool with private;

   Storage_Pool : in out B_Tree_Storage_Pool;  -- pass in storage pool object
 ...


with ACL.Trees.BPlus_Trees;
with BPlus.Searches;        use BPlus.Searches;
with BPlus.Storage.Dynamic;
with BPlus.Storage_Pools;

package BPlus.Trees is
  new ACL.Trees.BPlus_Trees
  (B_Tree_Item => Integer,
   B_Tree_Item_Array => Searches.B_Tree_Item_Array,
   B_Tree_Key => Integer,
   B_Tree_Key_Array => Searches.B_Tree_Key_Array,
   Index_Order => Index_Order,
   Sequence_Order => Sequence_Order,
   Storage => BPlus.Storage,
   B_Tree_Storage_Pool => BPlus.Storage.Dynamic.Dynamic_Storage_Pool,
   Storage_Pool => Storage_Pools.Pool,   -- there it is...
   Get_Key => BPlus.Get_Key);


So, from global data isn't necessarily bad, and is often required for
declaring static, system-wide data.




^ permalink raw reply	[relevance 7%]

* Re: type names (was Re: Child package: private type and IO)
  1998-03-01  0:00  2%       ` Matthew Heaney
@ 1998-03-04  0:00  2%         ` Fergus Henderson
  0 siblings, 0 replies; 96+ results
From: Fergus Henderson @ 1998-03-04  0:00 UTC (permalink / raw)



mheaney@ni.net (Matthew Heaney) writes:

 >blaak@infomatch.com (Ray Blaak) wrote:
 >
 >>>Objects are the memory locations that store a value of a type.
 >>
 >>But you are using the word here as a type! (i.e. the set of things that are
 >>memory locations that store values).
 >
 >No.  You are confused about what a type is.

No, Ray Blaak is correct here.

 >Let's begin by defining what we mean by a type.  A type is defined as "A
 >set of values, and a set of operations on those values."  For example,  I
 >can define a type
 >
 >with the name "Integer"
 >
 >and the set of values
 >
 >   ..., -3, -2, -1, 0, 1, 2, 3, ...
 >
 >and the set of operations
 >
 >   +: Integer x Integer -> Integer
 >   -: Integer x Integer -> Integer
 >   *: Integer x Integer -> Integer
 >   /: Integer x Integer -> Integer
 >   =: Integer x Integer -> Boolean
 >
 >etc

Agreed.

Above, you used the word "Object" to refer to a type with the name "Object",
with the set of values being the different possible memory locations,
and with the set of operations being fetch, store, etc.

Below, you assume that "Object" and "Type" are mutually exclusive;
this is true in Ada, but there are other languages for which it is not true.

 >A type refers to the set of values, NOT the objects.  An object is a memory
 >location inside a computer, that stores a value, a value we interpret as
 >having a certain type.  So when we declare an object,
 >
 >O : T;
 >
 >we're allocating a memory cell, and we're interpreting the value of the
 >data in that cell as being of type T.  The means the memory cell designated
 >by object O will only contain certain values, and that only certain
 >operations may be applied to the value in that cell.
 >
 >The memory cell designated by object O isn't really interesting.  It's the
 >data in that cell that's interesting.  And it's the data in the cell that
 >"is of type T," not the object itself.

No, the object itself "is [an lvalue] of type T".

To say otherwise would imply that objects are untyped, that
only values are typed, and that it is therefore possible to
store a value of any type in a given object.  This is true
for some untyped languages, but it is not true in Ada.

 >It is completely wrong to name a type "Object."

Well, I don't particularly like this convention much myself;
but I think "completely wrong" is overstating the case.

 >Yes, it's true we often say "Object O has type T," but we really mean "O is
 >the name of a memory cell containing a value of type T."

No.  What we really mean is "O has type n<T>",
where "n<T>" is a (parametric) type whose operations
include "fetch" (syntactically implicit in Ada) and "store" (`:=').

"n<T>" might be better named "name<T>", "lvalue<T>", or even "object<T>".

 >>>A type should be named using a noun phrase, such as
 >>>type Singly_Linked_List is ...;
 >>
 >>I think that style of type names used really depends on if type names are
 >>qualified with package names or not.
 >
 >Of course, a type name should NOT be qualified by a package name.  A type
 >name is a type name, and a package name is a package name.  A package name
 >is NOT a type name, and in no way participates in naming a type.  

No, a package name surely does participate in naming a type,
for the type's fully-qualified name includes the name of the
package in which it is contained.

 >A package is a namespace, and serves only to prevent clashes among
 >similarly named types in an otherwise global namespace.

No, packages also provide encapsulation, not just namespace control.

 >A package disambiguates type names, but it is itself not a type name.

Agreed.

 >To use a package as part of the type, as in 
 >
 >package P is 
 >
 >   type Object is ...;
 >...
 >end P;
 >
 >The_Object : P.Object;
 >
 >so that the "real" type name is "P.Object" only confuses the difference
 >between a module and a type.

Nonsense!

The package name is P; the type name is P.Object
(though it can be abbreviated as Object, in certain contexts).
What's there to be confused about?

 >>Having:
 >>
 >>  package Linked_List is
 >>    type Linked_List is ...
 >>  end Linked_List;
 >>
 >>results in usage like:
 >>
 >>  Employees : Linked_List.Linked_List;
 >>
 >>which I personally find irritating.
 >
 >The package is misnamed.  A common idiom, and a very OLD idiom in the Ada
 >community, is to use the plural of the type name as the package name,

Well, that doesn't help much -- now the usage is

    Employees : Linked_Lists.Linked_List;

which is still just as ugly.

 >I'm sorry you find this convention irritating.  If so, then you can tell
 >the language designers that they named the packages
 >
 >Ada.Characters
 >Ada.Interrupts
 >Ada.Interrupts.Names
 >Ada.Exceptions
 >Ada.Numerics
 >Ada.Streams
 >Ada.Strings
 >Interfaces
 >Interfaces.C.Pointers
 >Interfaces.C.Strings
 >System.Address_To_Access_Conversions
 >System.Storage_Elements
 >System.Storage_Pools
 >
 >incorrectly, and that the names they chose irritate you.

It's not a question of "correct" or "incorrect", it's a question
of style.  The style chosen for the standard library strongly
encourages the use of `use', to avoid unnecessary redundancy in
names like `Ada.Strings.Unbounded.Unbounded_String'.
This is probably not such a bad thing
for the standard library, since experienced Ada programmers 
will know the standard library well; but for more general settings,
encouraging the use of `use' may not be such a good idea.

Personally, I quite like the style of naming types `T',
e.g. `Ada.Strings.Unbounded.T'.

 >> However a package like:
 >>
 >>  package Linked_List is
 >>    type Object is ...
 >>  end Linked_List;
 >>
 >>results in usage like:
 >>
 >>  Employees : Linked_List.Object;
 >>
 >>which reads better to me.
 >
 >It reads better to you because you are confused.  You don't understand the
 >difference between a module and a type.

Well, it reads better to me too, and I definitely do
understand the difference between a module and a type
(and I think Ray Blaak probably does too).

 >If you don't believe that this is the Ada idiom, [...]

I think Ada is big enough for more than one idiom!

--
Fergus Henderson              | Designing grand concepts is fun;
fjh@cs.mu.oz.au               | finding nitty little bugs is just work.
http://www.cs.mu.oz.au/~fjh   | -- Brooks, in "The Mythical Man-Month".
PGP key fingerprint: 00 D7 A2 27 65 09 B6 AC  8B 3E 0F 01 E7 5D C4 3F




^ permalink raw reply	[relevance 2%]

* Re: type names (was Re: Child package: private type and IO)
  @ 1998-03-01  0:00  2%       ` Matthew Heaney
  1998-03-04  0:00  2%         ` Fergus Henderson
  0 siblings, 1 reply; 96+ results
From: Matthew Heaney @ 1998-03-01  0:00 UTC (permalink / raw)



In article <6dcio1$fvo$1@berlin.infomatch.com>, blaak@infomatch.com (Ray
Blaak) wrote:

>>Objects are the memory locations that store a value of a type.
>
>But you are using the word here as a type! (i.e. the set of things that are
>memory locations that store values).

No.  You are confused about what a type is.

Let's begin by defining what we mean by a type.  A type is defined as "A
set of values, and a set of operations on those values."  For example,  I
can define a type

with the name "Integer"

and the set of values

   ..., -3, -2, -1, 0, 1, 2, 3, ...

and the set of operations

   +: Integer x Integer -> Integer
   -: Integer x Integer -> Integer
   *: Integer x Integer -> Integer
   /: Integer x Integer -> Integer
   =: Integer x Integer -> Boolean

etc

A type refers to the set of values, NOT the objects.  An object is a memory
location inside a computer, that stores a value, a value we interpret as
having a certain type.  So when we declare an object,

O : T;

we're allocating a memory cell, and we're interpreting the value of the
data in that cell as being of type T.  The means the memory cell designated
by object O will only contain certain values, and that only certain
operations may be applied to the value in that cell.

The memory cell designated by object O isn't really interesting.  It's the
data in that cell that's interesting.  And it's the data in the cell that
"is of type T," not the object itself.
   
It is completely wrong to name a type "Object."  There are 2 reasons:

1) It confuses the difference between a memory cell (which merely stores a
value) and the value itself.  "Type" refers to a set of values, and to the
operations you can perform to manipulate those values.

"Type" does NOT refer to the memory cell containing a value.  The term we
use to refer to a memory cell containing a value is "Object."

Yes, it's true we often say "Object O has type T," but we really mean "O is
the name of a memory cell containing a value of type T."

The name "T" is the name we've bound to the TYPE, not to the object.  So
"T" is the name by which we refer to a set of values and a set of
operations.  The name "O" is the name we bind to an OBJECT, not a type;
that is, "O" refers to a memory cell.

So when you name a type "Object," it's confusing because the term "Object"
refers to a memory cell.  But a type is NOT a memory call, it's a set of
values.

2) It confuses the difference between a module and a type.

In Ada, module and type are ORTHOGONAL language features.  This really
confuses a lot of people, and I have no idea why.

The Ada language construct for a module is a package.  A package is NOT a
type.  A package which exports a type declaration merely demarcates the
"primitive" operations of a type among all the operations that have the
type as a parameter or return value.  

The Ada language construct for a type comprises 2 parts:

a) a type declaration, which binds a name to the type, specifies its class,
and specifies the set of values as a range (or implied range).

b) subprogram declarations, which take parameters of the type, or return
values of the type.

Consider this example:

package P is

   type T is range 1 .. 4;

   procedure Op1 (O : T);

   function Op2 (F : Float) return T;

end P;

with P;
package Q is

   procedure Op3 (O : P.T);

end Q;

Let's analyze this piece by piece.

The declaration 

   type T is range 1 .. 4;

a) specifies the type class, here Integer

b) specifies the set of values (having the Integer class) for the type,
here 1, 2, 3, 4

c) binds a name to the type, here "T"

d) specifies primitive operations that are "predefined" for this class of
type, here

   +: T x T -> T
   +: T -> T
   -: T x T -> T
   -: T -> T
   =: T x T -> Boolean

etc

The operations Op1 and Op2 are also "primitive" operations of the type
whose name is T.  We say they are "user-defined," in contrast to the
"predefined" primitive operations as addition, subtraction, etc.

They are primitive because they take a parameter of the type (Op1) and
return a value of the type (Op2), and they are declared in the same package
(P) as the type declaration.

By contrast, the operation Op3 is NOT a "primitive" operation of the type
whose name is T.  Even though Op3 takes a parameter of type P.T, it is not
primitive because it is not declared in the same package as the type
declaration.

We make the distinction between primitive and non-primitive operations
because only the former are "inherited" during a derivation.  For example,

with P;
package R is

   type NT is new P.T;

  procedure Op4 (O : NT);

end R;

The primitive operations of type R.NT are "+", "-", "*", "/", etc, and Op1,
Op2, and Op4.  Op1 and Op2 (and addition, etc) are inherited from T, and a
new primitive operation, Op4, was added too.

Note the Op3 is NOT an operation of type NT, because Op3 is not a primitive
operation of type T.

And by the way, while I'm on the subject, a "class" in other languages as
C++, Eiffel, and Java maps to an Ada tagged type.  It does NOT map to an
Ada package.  To convert the C++ declaration

class Stack ...;

to Ada, you have to do this:

package Stacks is

   type Stack is ...;  -- this is the "class Stack"


>>So when refer to an object's type as "Object," then how do you refer to the
>>object?
>
>Perhaps as An_Object, or The_List, or The_Set, or even Value. An even better
>approach is to use names from the domain, like maybe Employees, or
>Active_Flights, or Current_Account.

An an even better approach is

Account : Bank_Account;

File : Text_File;

Mode : File_Mode;


>>A type should be named using a noun phrase, such as
>>type Singly_Linked_List is ...;
>
>I think that style of type names used really depends on if type names are
>qualified with package names or not.

Of course, a type name should NOT be qualified by a package name.  A type
name is a type name, and a package name is a package name.  A package name
is NOT a type name, and in no way participates in naming a type.  

A package is a namespace, and serves only to prevent clashes among
similarly named types in an otherwise global namespace.  A package
disambiguates type names, but it is itself not a type name.

To use a package as part of the type, as in 

package P is 

   type Object is ...;
...
end P;

The_Object : P.Object;

so that the "real" type name is "P.Object" only confuses the difference
between a module and a type.

>Having:
>
>  package Linked_List is
>    type Linked_List is ...
>  end Linked_List;
>
>results in usage like:
>
>  Employees : Linked_List.Linked_List;
>
>which I personally find irritating.

The package is misnamed.  A common idiom, and a very OLD idiom in the Ada
community, is to use the plural of the type name as the package name, as in


generic
...
package Stacks

   type Stack is ...;
...;
end Stacks;

I'm sorry you find this convention irritating.  If so, then you can tell
the language designers that they named the packages

Ada.Characters
Ada.Interrupts
Ada.Interrupts.Names
Ada.Exceptions
Ada.Numerics
Ada.Streams
Ada.Strings
Interfaces
Interfaces.C.Pointers
Interfaces.C.Strings
System.Address_To_Access_Conversions
System.Storage_Elements
System.Storage_Pools

incorrectly, and that the names they chose irritate you.

> However a package like:
>
>  package Linked_List is
>    type Object is ...
>  end Linked_List;
>
>results in usage like:
>
>  Employees : Linked_List.Object;
>
>which reads better to me.

It reads better to you because you are confused.  You don't understand the
difference between a module and a type.

>Note this does not imply that all types should be
>called "Object" either. With this example in particular, it is natural to work
>with objects and references to objects:
>
>  type Handle;
>  type Object is record
>    ...
>        Next : Handle;
>        Previous : Handle;
>  end record;
>  type Handle is access Object;


This is another horrible naming convention.  The term "handle" loosely
refers to a pointer-to-pointer.  Handles are used in memory allocation
schemes to allow you to relocate chunks of memory to reduce fragmentation
(Mac programmers will know what I'm talking about).

The Ada idiom for a name of an access type is T_Access, for example

type Stack is tagged private;

type Stack_Access is access all Stack;

type Stack_Class_Access is access all Stack'Class;

Do not name an access type Handle, because it is not a handle.

Do not name an access type Pointer, because access objects are not
pointers.  If they were, then Jean Ichbiah would have chosen the keyword
"pointer" instead of "access," right?

If you don't believe that this is the Ada idiom, then make note of the
names of the types

Ada.Text_IO.File_Access

Ada.Strings.Unbounded.String_Access

Ada.Streams.Stream_IO.Stream_Access


>then one can say things like:
>
>  Manager_Subset : Linked_List.Handle;
>
>which is really clear (to me, of course :-).
>
>If one uses use clauses a lot, then of course more descriptive type names are
>better:
>
>  data : Linked_List;

Ahh, that's more like it.

Here's an example from a library I'm writing:

package ACL.Lists is ...;


package ACL.Lists.Single is

   type Single_List is private;
...;
end ACL.Lists.Single;


package ACL.Lists.Double is

   type Double_List is private;
...
end ACL.Lists.Double;


Here's another example you often find in tutorials:

package Bank_Accounts is

   type Bank_Account is abstract tagged limited private;
...;
end Bank_Accounts;


package Bank_Accounts.Checking is

   type Checking_Account is new Bank_Account with private;
...;
end Bank_Accounts.Checking;


package Bank_Accounts.Savings is

   type Savings_Account is new Bank_Account with private;
...
end Bank_Accounts.Savings;


>>A good guideline is, Be consistant with the style in the reference manual. 
>>There are NO types in the RM named "Object," so there should be none in
>>your code either.
>
>One shouldn't be so afraid to do something different, if one thinks it is an
>improvement. How else can standards get better?

A bunch of guys from all over the planet with PhDs in computer science
designed the language, and somehow they didn't come up with your "better
idea."  Telling, isn't it?  If you think it is an improvement, perhaps that
is because there is knowledge that you don't have.




^ permalink raw reply	[relevance 2%]

* Re: READ 1ST: use eiffel for CAM library development?
  @ 1998-01-23  0:00  5%   ` Brian Rogoff
  0 siblings, 0 replies; 96+ results
From: Brian Rogoff @ 1998-01-23  0:00 UTC (permalink / raw)



On 22 Jan 1998, Nick Roberts wrote:
> I gather that garbage collection tends not be implemented by default by
> most Ada compilers.  Fortunately, however, Ada 95 (the current standard)
> provides a way for the programmer to provide garbage collection in a
> relatively convenient way.

If you mean using controlled types to implement reference counting, that
is really not the same as garbage collection because it will not allow 
cyclic structures to be reclaimed, though that may not be important in
some applications. I remember discussing using System.Storage_Pools for
this purpose before, but I don't think that is quite up to the task
either, though it can be used to implement lots of other memory
reclamation policies. If you need GC in Ada, your best best for now is to
use one of the Ada -> Java Virtual Machine compilers. 

It certainly would be much easier to build a GC for Ada than for C++, but 
I don't know if anyone has gotten around to it yet. 

-- Brian






^ permalink raw reply	[relevance 5%]

* System.Storage_Pools
@ 1998-01-14  0:00  8% Gilbert Gosseyn
  1998-01-14  0:00  7% ` Reformat program [was Re: System.Storage_Pools] Martin C. Carlisle
  0 siblings, 1 reply; 96+ results
From: Gilbert Gosseyn @ 1998-01-14  0:00 UTC (permalink / raw)



I am working with CodeBuilder from Tenon on Ada programs on a Mac. Does 
somebody have already some experience with marking and releasing pools ? 
I have tried it and got less heap storage in total than before. Can
somebody show me an example of proper use ?

I am also looking for a program to reformat my Ada programs following
the Ada 95 style guide. Can somebody give me an address for downloading
?

Gilbert Gosseyn




^ permalink raw reply	[relevance 8%]

* Reformat program [was Re: System.Storage_Pools]
  1998-01-14  0:00  8% System.Storage_Pools Gilbert Gosseyn
@ 1998-01-14  0:00  7% ` Martin C. Carlisle
  0 siblings, 0 replies; 96+ results
From: Martin C. Carlisle @ 1998-01-14  0:00 UTC (permalink / raw)



In article <34BCD438.2229@acm.org>,
Gilbert Gosseyn  <Gilbert.Gosseyn@acm.org> wrote:
>I am also looking for a program to reformat my Ada programs following
>the Ada 95 style guide. Can somebody give me an address for downloading

I must confess to never having read the Ada 95 style guide, but I am
a co-author of a reformatting program.  It does auto indentation and
capitalization according to command-line options, and also can generate
colorized or bolded RTF.

For more info, see ftp://ftp.usafa.af.mil/pub/dfcs/carlisle/reformat/readme.txt
and to download:
ftp://ftp.usafa.af.mil/pub/dfcs/carlisle/reformat/format.zip

This is also mirrored into the PAL, but I wasn't able to find the
exact location right now.

--Martin

-- 
Martin C. Carlisle, Computer Science, US Air Force Academy
mcc@cs.usafa.af.mil, http://www.usafa.af.mil/dfcs/bios/carlisle.html
DISCLAIMER:  This content in no way reflects the opinions, standard or 
policy of the US Air Force Academy or the United States Government.




^ permalink raw reply	[relevance 7%]

* Re: newbie Q: storage management
  @ 1997-05-08  0:00  6%           ` John G. Volan
  0 siblings, 0 replies; 96+ results
From: John G. Volan @ 1997-05-08  0:00 UTC (permalink / raw)



Jon S Anthony wrote:
> 
> One obvious way out of this for Ada is the generalized
> version of what Robert called out as a "compromise": a subsystem of
> generics which offered several variants.  A single global GC handling
> all dynamic memory issues isn't really needed.  In fact, this is an
> area where Ada could do something a little different by offering the
> ability to have multiple collectors per application targetting the
> specific needs of specific types (or classes of types).  This is the
> sort of thing that I've been working on.

I'm very keen to see how true GC (not conservative GC) could be
shoehorned into Ada95 (other than by compiling to the Java virtual
machine).  One difficulty I'm having is seeing how Storage_Pools would
actually help.  It seems to me that, before you can collect the dead
objects in a given pool, you have to be able to locate and identify
every access value that currently points into that pool.  This might be
feasible, for instance, if access types behaved as if they were derived
from Controlled. But all that System.Storage_Pools seems to provide is a
way to define _how_ the designated objects are allocated and deallocated
-- but not _when_.

Looking forward to being edified... :-)

------------------------------------------------------------------------
Internet.Usenet.Put_Signature 
  (Name => "John G. Volan",  Home_Email => "johnvolan@sprintmail.com",
   Slogan => "Ada95: The World's *FIRST* International-Standard OOPL",
   Disclaimer => "These opinions were never defined, so using them " & 
     "would be erroneous...or is that just nondeterministic now? :-) ");
------------------------------------------------------------------------




^ permalink raw reply	[relevance 6%]

* Re: Garbage Collection in Ada
  1996-11-06  0:00  6% ` Brian Rogoff
@ 1996-11-07  0:00  5%   ` Tucker Taft
  0 siblings, 0 replies; 96+ results
From: Tucker Taft @ 1996-11-07  0:00 UTC (permalink / raw)



Brian Rogoff (rogoff@sccm.Stanford.EDU) wrote:

: "Norman H. Cohen" <ncohen@watson.ibm.com> writes:
:    Robert A Duff wrote:

:    > In article <mheaney-ya023280000311962335300001@news.ni.net>,
:    > Matthew Heaney <mheaney@ni.net> wrote:
:    > >Language designers: any reason why overloading "all" would be too hard?
:    > 
:    > Well, functions return values (or constant objects, if you want to be
:    > precise in Ada 95 terms), whereas "P.all" returns a variable (if P is an
:    > access-to-variable type).  So it wouldn't work.  

:    The same scheme that Ada 95 uses to allow programmers to redefine the
:    behavior of "new" could have been used to allow redefinition of the
:    behavior of ".all".  The type System.Storage_Pools.Root_Storage_Pool
:    could have been given another primitive operation to be overridden by
:    those defining their own storage-pool types:

:       procedure Dereference
: 	 (Pool                     : in out Root_Storage_Pool;
: 	  Storage_Address          : in out Address;
: 	  Storage_Size_In_Elements : in Storage_Elements.Storage_Count;
: 	  Alignment                : in Storage_Elements.Storage_Count);

: This looks almost exactly like a proposal I read (a long time ago, on a web 
: page long since forgotten) for adding persistence to Ada 95. The main 
: difference is that Storage_Address was of type "Access_Type", which was a 
: generic formal parameter to the Storage_Pools package, and another parameter 
: to Dereference was a System.Address type. There was also a Rereference 
: procedure for converting System.Address types back to Access_Types.

:    <... snipping description of some the things this might allow ...>

: This seems, at first naive glance, to provide all of the hooks to do GC and 
: more, in a very Ada-like way. The idea seems to have been around for a 
: while too, perhaps hundreds of web-years (at least 10 months). So what are 
: the drawbacks? 

The problem has to do with knowing when the user is "done" with
the result of Dereference, and whether it is a read or a write
reference.  Remember that it is permissible to pass the result of
X.all to a very long subprogram, or to rename it.
In general an operation like this would work for a transaction-oriented
persistence mechanism, where you "commit" changes as a separate
operation, and pages stay in virtual memory indefinitely once referenced
(or until explicitly committed).

: -- Brian

-Tucker Taft   stt@inmet.com   http://www.inmet.com/~stt/
Intermetrics, Inc.  Cambridge, MA  USA




^ permalink raw reply	[relevance 5%]

* Re: Garbage Collection in Ada
       [not found]     <01bbc6a3$4cf03480$829d6482@joy.ericsson.se>
  @ 1996-11-06  0:00  6% ` Brian Rogoff
  1996-11-07  0:00  5%   ` Tucker Taft
  1 sibling, 1 reply; 96+ results
From: Brian Rogoff @ 1996-11-06  0:00 UTC (permalink / raw)



"Norman H. Cohen" <ncohen@watson.ibm.com> writes:
   Robert A Duff wrote:

   > In article <mheaney-ya023280000311962335300001@news.ni.net>,
   > Matthew Heaney <mheaney@ni.net> wrote:
   > >Language designers: any reason why overloading "all" would be too hard?
   > 
   > Well, functions return values (or constant objects, if you want to be
   > precise in Ada 95 terms), whereas "P.all" returns a variable (if P is an
   > access-to-variable type).  So it wouldn't work.  

   The same scheme that Ada 95 uses to allow programmers to redefine the
   behavior of "new" could have been used to allow redefinition of the
   behavior of ".all".  The type System.Storage_Pools.Root_Storage_Pool
   could have been given another primitive operation to be overridden by
   those defining their own storage-pool types:

      procedure Dereference
	 (Pool                     : in out Root_Storage_Pool;
	  Storage_Address          : in out Address;
	  Storage_Size_In_Elements : in Storage_Elements.Storage_Count;
	  Alignment                : in Storage_Elements.Storage_Count);

This looks almost exactly like a proposal I read (a long time ago, on a web 
page long since forgotten) for adding persistence to Ada 95. The main 
difference is that Storage_Address was of type "Access_Type", which was a 
generic formal parameter to the Storage_Pools package, and another parameter 
to Dereference was a System.Address type. There was also a Rereference 
procedure for converting System.Address types back to Access_Types.

   <... snipping description of some the things this might allow ...>

This seems, at first naive glance, to provide all of the hooks to do GC and 
more, in a very Ada-like way. The idea seems to have been around for a 
while too, perhaps hundreds of web-years (at least 10 months). So what are 
the drawbacks? 

-- Brian




^ permalink raw reply	[relevance 6%]

* Re: Garbage Collection in Ada
  @ 1996-11-06  0:00  3%       ` Norman H. Cohen
  0 siblings, 0 replies; 96+ results
From: Norman H. Cohen @ 1996-11-06  0:00 UTC (permalink / raw)



Robert A Duff wrote:
 
> In article <mheaney-ya023280000311962335300001@news.ni.net>,
> Matthew Heaney <mheaney@ni.net> wrote:
> >Language designers: any reason why overloading "all" would be too hard?
> 
> Well, functions return values (or constant objects, if you want to be
> precise in Ada 95 terms), whereas "P.all" returns a variable (if P is an
> access-to-variable type).  So it wouldn't work.  

The same scheme that Ada 95 uses to allow programmers to redefine the
behavior of "new" could have been used to allow redefinition of the
behavior of ".all".  The type System.Storage_Pools.Root_Storage_Pool
could have been given another primitive operation to be overridden by
those defining their own storage-pool types:

   procedure Dereference
      (Pool                     : in out Root_Storage_Pool;
       Storage_Address          : in out Address;
       Storage_Size_In_Elements : in Storage_Elements.Storage_Count;
       Alignment                : in Storage_Elements.Storage_Count);

The compiler would generate code for .all that would compute the nominal
address of the designated object and invoke Dereference, passing that
address to Storage_Address.  Dereference would, in some cases, replace
that address with a different one.  (Unlike Allocate, Deallocate, and
Storage_Size, Dereference would not be abstract; it would have a default
implementation that does nothing.  People not interested in redefining
the behavior of ".all" could ignore it.  I'm not sure why the last two
parameters are really needed; I'm just being "foolishly consistent" with
Allocate and Deallocate.)

One potential use of Dereference would be to recognize "forwarding
pointers" in a storage pool with background compactifying garbage
collection.  As objects are copied from the current area into the new,
compacted area, the old copy of an object is replaced by a special value
indicating that the object has been moved, followed by the new address
of the object.  Dereference would return without doing anything for
objects that had not been moved, and would return the address indicated
by the forwarding pointer for objects that had been moved.

Another potential use of Dereference would be swizzling:  A data
structure consisting of many nodes pointing at each other would be
represented partly in a persistent store (e.g. on a disk) with some sort
of persistent pointers (e.g. disk addresses or indices) and partly in
memory.  Nodes would be lazily brought into memory as needed.  One
possible implementation is to use values of type Address to encode
persistent pointers.  There would be a hash table mapping persistent
pointers to in-memory objects.  Dereference would be passed an encoded
persistent pointer through its Storage_Address parameter and would look
up that perisistent pointer in the hash table.  If there was not already
an entry for that persistent pointer in the hash table, Dereference
would read the node from the persistent store into memory and create a
hash-table entry mapping the persistent pointer to the new in-memory
address.  Then, in any event, Dereference would replace its
Storage_Address parameter with the in-memory address of the object
(either the one that was found already in the hash table or the one that
it just inserted there because it had not been in the hash table).

As a final example, Dereference could be used to implement a storage
pool with *checked* deallocation.  The storage pool would implement a
pointer to X as a pointer to a pointer to X.  Access-value assignment
would have the effect of creating multiple copies to the
pointer-to-pointer-to X.  Deallocation would consist of freeing the
storage for X itself and setting the direct pointer to X to null. 
Dereference would implement the extra level of indirection and also
check that the address it is passed is not the address of a null pointer
(indicating an attempt to dereference a pointer to a deallocated
object).

--
Norman H. Cohen
mailto:ncohen@watson.ibm.com
http://www.research.ibm.com/people/n/ncohen




^ permalink raw reply	[relevance 3%]

* Re: Garbage Collection in Ada
    @ 1996-10-29  0:00  0% ` Jon S Anthony
  1 sibling, 0 replies; 96+ results
From: Jon S Anthony @ 1996-10-29  0:00 UTC (permalink / raw)



In article <Pine.GSO.3.95.961027083501.11380C-100000@nunic.nu.edu> Richard Riehle <rriehle@nunic.nu.edu> writes:

> I find it odd that, in all this discussion of Garbage Collection,
> we have not had any mention of System.Storage_Pools (ALRM 13.11).

Actually, they have been mentioned several times - by me and a couple
others.


> Although I realize this is not the panacea for all garbage collection
> problems, those who have suggested that the run-time executive would
> have to wander blindly through all of a program's memory to determine
> if some wayward pointer is lurking in some hidden corner, might consider,
> when such issues are critical, setting up a storage pool controlled
> via Ada.Finalization.

Or (as has been mentioned) tying (sp?) instances of GC (possibly
different flavors, where each could be more appropriate to the target
type) to specific pools.  Either implementation defined or possibly
even user defined pools.


> I, for one, am quite pleased that the designers of Ada 95 included this
> capability, and sometimes wonder how many of my colleagues in the Ada
> community have examined this feature closely enough to realize that it
> is does have some virtue.

It is a "god send" for those of us trying to put some GC like storage
management into specific applications.  This is the route that I ended
up going down - finalization stuff is largely _irrelevant_.


> While it is true that Root_Storage_Pool is derived
> from Ada.Finalization.Limited_Controlled, this should not be
> a particular hardship when control over the storage pool,
> and automatic garbage collection are essential to a given design.

The keys are being able to

a) tie an access type to a pool
b) define a type which cannot be allocated except by user defined constructor
   (limited type with unknown discriminants).  This gurantees that a) is the
   only access type a client can use for the type.
c) ability to redefine _new_ for the pool

to a much lesser extent: d) ability to redefine manual deallocation for pool.

Finalization for the pool could also be useful (though only in special
cases)

/Jon
-- 
Jon Anthony
Organon Motives, Inc.
Belmont, MA 02178
617.484.3383
jsa@organon.com





^ permalink raw reply	[relevance 0%]

* Re: Garbage Collection in Ada
  @ 1996-10-27  0:00  5%     ` Richard Riehle
  0 siblings, 0 replies; 96+ results
From: Richard Riehle @ 1996-10-27  0:00 UTC (permalink / raw)





I find it odd that, in all this discussion of Garbage Collection,
we have not had any mention of System.Storage_Pools (ALRM 13.11).

Although I realize this is not the panacea for all garbage collection
problems, those who have suggested that the run-time executive would
have to wander blindly through all of a program's memory to determine
if some wayward pointer is lurking in some hidden corner, might consider,
when such issues are critical, setting up a storage pool controlled
via Ada.Finalization. 

I, for one, am quite pleased that the designers of Ada 95 included this
capability, and sometimes wonder how many of my colleagues in the Ada
community have examined this feature closely enough to realize that it
is does have some virtue.

While it is true that Root_Storage_Pool is derived
from Ada.Finalization.Limited_Controlled, this should not be
a particular hardship when control over the storage pool,
and automatic garbage collection are essential to a given design.

Richard Riehle
richard@adaworks.com





^ permalink raw reply	[relevance 5%]

* Re: Why couldn't an operating system be written in ada
  @ 1996-07-16  0:00  4%   ` Jon S Anthony
  0 siblings, 0 replies; 96+ results
From: Jon S Anthony @ 1996-07-16  0:00 UTC (permalink / raw)



In article <xe1687p1cha.fsf@maneki-neko.cygnus.com> Mark Eichin <eichin@cygnus.com> writes:

> > A neat idea whose time is long since gone.  The OS "wars" have
> > been fought and largely lost.... :-(
> 
> Well, the users lost anyway :-}  However, research certainly

Yeah, that's what I meant...


> MK, VSTA, and other operating systems exist to serve as research
> platforms (and sometimes as operational platforms when "modern" 70's
> and 80's systems just can't cut it.)  Surely there is justification
> for using Ada in this context, at least?

I'm sure there is all sorts of good reasons to use Ada in these
contexts.  But, the results will probably never see the light of day -
maybe a peek or two...


> I brought up this point with a well known linux kernel developer, and
> between the two of us we came up with several things that I didn't
> know Ada95 well enough to answer:
> 	1) Can you do efficient raw memory operations (ie. raw byte
> arrays, explicit control of when an access can be eliminated, and no
> overhead [or at least, not stored in-place, for an object like a page
> or a video card?]

Yes, this should not be any sort of a problem.  With
System.Storage_Elements and address clauses and such you should be
well covered.


> 	2) Can you interface efficiently to machine code
> (ie. equivalent of inline asm, where you *mostly* can code a high
> level algorithm but the core needs to be a particular hardware level
> instruction. A GNAT-specific answer is ok, in this case...)

Sure.  Actually this sort of thing is defined in the language with
convention intrinsic (6.3.1) and System.Machine_Code (13.8).


> 	3) Can you work without tasking (since you're implementing the
> scheduler!) [I'll take arguments that you should in fact use Ada
> tasking within the kernel, if they're detailed...]

Sure you can.  But to my mind, it would make as much (or more) sense
to first create the tasking kernel and then build the OS scheduler on
top of this.  This seems like the most straightforward way to proceed
and it has the added benefit that you can use "regular tasking" in
other parts of the OS design and know that you will not be interfering
in some nefarious way with the OS scheduler.  I'm sure there is
probably a reason why you might not want to do this, but it isn't
obvious to me.


> 	4) Can you do complete memory management (without garbage
> collection.) 

Sure.  You can define your own storage pools (System.Storage_Pools)
and write specific MM operations for them.  This way you can have
different styles of AMM for different sorts of "objects" - thereby
allowing the most "appropriate" technique for the resource type.  See
13.11


> As you can see, I *don't* know much Ada, though I've gotten a start on
> Barnes' excellent "Ada95" text.

Yes, for knowledgeable types, outside the RM and Rationale, I would
say Barnes is the best thing going.

>  My guesses are that (1) is possible,
> but you must go out of your way to do it; (2) might be possible in
> GNAT; (3) is probably obvious and (4) is true but the reasoning is
> subtle.

(1): Really rather straight forward and not that big of a deal
(2): Easily done.
(3): Yes, obvious
(4): Really pretty obvious also.  The subtlty comes in how clever the
     AMMs you write are.


> I haven't thought of any other potential obstacles to OS work in Ada;
> it would seem a good choice, based on the *intent* of the design, but
> I can't yet judge the results.

Well, one way to look at it is that since (one of) the primary areas
of intended use for Ada was and is "real-time"/embedded systems, OS
sort of work should "just fall right out".  Access to HW, interrupts,
and that sort of bare machine stuff is defined in the language (well,
the annexes anyway...)

/Jon

-- 
Jon Anthony
Organon Motives, Inc.
1 Williston Road, Suite 4
Belmont, MA 02178

617.484.3383
jsa@organon.com





^ permalink raw reply	[relevance 4%]

Results 1-96 of 96 | reverse | options above
-- pct% links below jump to the message on this page, permalinks otherwise --
1996-07-13  0:00     Why couldn't an operating system be written in ada Mark McKinney
1996-07-15  0:00     ` Jon S Anthony
1996-07-16  0:00  4%   ` Jon S Anthony
1996-10-18  0:00     Garbage Collection in Ada Lars Farm
1996-10-22  0:00     ` Mitch Gart
1996-10-23  0:00       ` Hans-Juergen Boehm
1996-10-27  0:00  5%     ` Richard Riehle
1996-10-29  0:00  0% ` Jon S Anthony
     [not found]     <01bbc6a3$4cf03480$829d6482@joy.ericsson.se>
1996-10-31  0:00     ` Mitch Gart
1996-11-03  0:00       ` Matthew Heaney
1996-11-06  0:00         ` Robert A Duff
1996-11-06  0:00  3%       ` Norman H. Cohen
1996-11-06  0:00  6% ` Brian Rogoff
1996-11-07  0:00  5%   ` Tucker Taft
1997-04-29  0:00     newbie Q: storage management Kaz Kylheku
1997-05-03  0:00     ` Robert Dewar
1997-05-05  0:00       ` Samuel A. Mize
1997-05-06  0:00         ` Robert Dewar
1997-05-06  0:00           ` Robert A Duff
1997-05-08  0:00             ` Jon S Anthony
1997-05-08  0:00  6%           ` John G. Volan
1998-01-14  0:00  8% System.Storage_Pools Gilbert Gosseyn
1998-01-14  0:00  7% ` Reformat program [was Re: System.Storage_Pools] Martin C. Carlisle
1998-01-21  0:00     READ 1ST: use eiffel for CAM library development? Shane Miller
1998-01-22  0:00     ` Nick Roberts
1998-01-23  0:00  5%   ` Brian Rogoff
1998-02-14  0:00     Child package: private type and IO johnjohn
1998-02-17  0:00     ` sparre
1998-02-27  0:00       ` Matthew Heaney
1998-03-01  0:00         ` type names (was Re: Child package: private type and IO) Ray Blaak
1998-03-01  0:00  2%       ` Matthew Heaney
1998-03-04  0:00  2%         ` Fergus Henderson
1998-04-25  0:00     Are global or persistent variables in ADA? Brian Franklin
1998-04-25  0:00     ` Steve Doiel
1998-05-01  0:00  7%   ` Matthew Heaney
1998-05-19  0:00     Allocating memory--Ada95 jsanchor
1998-05-19  0:00  5% ` Matthew Heaney
1998-07-06  0:00  5% deallocating class-wide objects Stephen Leake
1998-07-06  0:00  5% user specified storage pools Stephen Leake
1998-09-24  0:00     Freeing Pointers to classwide types joecool
1998-09-25  0:00     ` Tom Moran
1998-09-25  0:00       ` dewarr
1998-09-26  0:00         ` Tom Moran
1998-09-26  0:00           ` dewarr
1998-09-26  0:00             ` Tom Moran
1998-09-27  0:00               ` dewarr
1998-09-27  0:00                 ` Tom Moran
1998-09-28  0:00                   ` dewarr
1998-09-28  0:00                     ` Tom Moran
1998-09-28  0:00                       ` dewarr
1998-09-28  0:00  8%                     ` Richard D Riehle
1998-09-28  0:00  5%                       ` Pat Rogers
1998-10-12  0:00     Classwide-type assignments jsanchor
1998-10-13  0:00     ` Niklas Holsti
1998-10-15  0:00  4%   ` Classwide-type assignments [longish] Niklas Holsti
1999-02-19  0:00  3% Garbage Collection for Ada Nick Roberts
1999-05-26  0:00  4% Creation of storage pools Graeme Perkes
1999-06-28  0:00  6% Allocation from " Andy Askey
1999-06-29  0:00  0% ` JClezy
1999-07-01  0:00  0% ` Andy Askey
1999-08-18  0:00     garbage collection Keith Thompson
1999-08-20  0:00     ` tmoran
1999-08-20  0:00  4%   ` Keith Thompson
1999-08-20  0:00  0%     ` Matthew Heaney
1999-08-21  0:00  0%     ` Brian Rogoff
2000-07-23  0:00     Access to classwide type reason67
2000-07-24  0:00     ` David Botton
2000-07-24  0:00       ` reason67
2000-07-24  0:00  5%     ` Pat Rogers
2000-07-24  0:00         ` David Starner
2000-07-25  0:00  5%       ` Laurent Guerby
2000-07-24  0:00         ` Larry Kilgallen
2000-07-24  0:00           ` reason67
2000-07-24  0:00  0%         ` David Botton
2000-10-18  0:00     Constructors/Destructors in Ada95 Francois Godme
2000-10-19  0:00     ` tmoran
2000-10-19  0:00       ` Francois Godme
2000-10-20  0:00         ` Tucker Taft
2000-10-23  0:00           ` Francois Godme
2000-10-24  0:00             ` Ray Blaak
2000-10-25  0:00               ` Marin David Condic
2000-10-25  0:00                 ` dmitry6243
2000-10-25  0:00                   ` mark.biggar
2000-10-26 11:44  6%                 ` dmitry6243
2001-03-13 18:37  3% Better support for garbage collection Nick Roberts
2001-06-13 19:25  6% Storage Pool ANH_VO
2001-08-17 23:54  3% User-defined access dereference Stanley R. Allen
2001-10-07 19:31     is Ada dying? Ralph M�ritz
2001-10-08 17:25     ` chris.danx
2001-10-09 14:15       ` John English
2001-10-09 22:49         ` Ehud Lamm
2001-10-11 12:29           ` why not "standardize" the Booch Components? (was Re: is Ada dying?) Pat Rogers
2001-10-11 14:14             ` Marin David Condic
2001-10-11 14:46               ` Pat Rogers
2001-10-11 20:52  5%             ` Simon Wright
2001-10-14 20:46     Container reqs Ehud Lamm
2001-10-14 22:52     ` James Rogers
2001-10-15 20:06       ` Ehud Lamm
2001-10-17  5:55  8%     ` Simon Wright
2001-10-15 14:27     ` Ted Dennison
2001-10-15 20:08       ` Ehud Lamm
2001-10-17  6:08         ` Simon Wright
2001-10-18 20:52           ` Ehud Lamm
2001-10-18 22:29             ` Jeffrey Carter
2001-10-19 15:36               ` Stephen Leake
2001-10-20  2:44                 ` Jeffrey Carter
2001-10-23  1:13  4%               ` Stephen Leake
2001-11-02 19:54     List container strawman Mike Brenner
2001-11-02 21:04     ` Ted Dennison
2001-11-03  8:09  8%   ` Simon Wright
2001-11-03 12:46  0%     ` Simon Wright
2002-01-19  7:11  5% Booch Components 20020117 Simon Wright
2002-02-06 23:35  0% ` Matthew Heaney
2002-02-07 15:12  5%   ` Stephen Leake
2002-02-10 12:32  7%     ` Simon Wright
2002-05-10 14:22  6% Generic default parameters Thomas Wolf
2002-05-10 22:14  7% ` Stephen Leake
2002-05-13  7:49  5%   ` Thomas Wolf
2002-05-30 12:39     Specialization Baugereau
2002-05-30 17:09     ` Specialization Ted Dennison
2002-05-31 19:44  5%   ` Specialization Simon Wright
2002-10-15 15:42  5% Storage Pools and alloca Frank J. Lhota
2002-10-15 19:14  0% ` Robert A Duff
2003-01-09 11:03  5% Generic and Access problem Grein, Christoph
     [not found]     <jcamq-v1p.ln1@boavista.snafu.de>
2003-05-31 20:23     ` Q:Usage of storage Pools Robert A Duff
2003-05-31 20:50       ` Michael Erdmann
2003-05-31 23:55         ` Robert A Duff
2003-06-01  6:55           ` Michael Erdmann
2003-06-01  8:05  5%         ` Simon Wright
2003-06-02 19:28  0%           ` Michael Erdmann
2003-11-25 19:04     Question about OO programming in Ada Ekkehard Morgenstern
2003-11-25 21:48     ` Stephen Leake
2003-11-26  0:01       ` Ekkehard Morgenstern
2003-11-26 17:58         ` Robert I. Eachus
2003-11-27  2:10           ` Ekkehard Morgenstern
2003-11-27 18:35             ` Jeffrey Carter
2003-11-28  4:35               ` Hyman Rosen
2003-12-01 15:57                 ` Martin Krischik
2003-12-02  8:47                   ` Dmitry A. Kazakov
2003-12-03  9:29                     ` Pascal Obry
2003-12-03 11:26                       ` Dmitry A. Kazakov
2003-12-03 12:49                         ` Ludovic Brenta
2003-12-03 13:41  6%                       ` Dmitry A. Kazakov
2003-12-03 14:11  0%                         ` Ludovic Brenta
2003-12-03 14:45  0%                           ` Dmitry A. Kazakov
     [not found]     <20040206174017.7E84F4C4114@lovelace.ada-france.org>
2004-02-07  8:50     ` No call for it Carroll-Tech
2004-02-07 13:00       ` No call for Ada (was Re: Announcing new scripting/prototyping language) Ludovic Brenta
2004-02-07 19:24         ` MSG
2004-02-08  3:15           ` Ludovic Brenta
2004-04-02 23:18             ` Beth Bruzan
2004-04-03  0:08               ` David Starner
2004-04-03  9:13                 ` Ludovic Brenta
2004-04-03 11:51                   ` Martin Krischik
2004-04-03 15:09  4%                 ` Robert I. Eachus
2005-03-05 13:42     Teaching new tricks to an old dog (C++ -->Ada) Turamnvia Suouriviaskimatta
2005-03-05 14:17     ` EventHelix.com
2005-03-05 14:25       ` Ludovic Brenta
2005-03-05 15:02         ` [OT] " Peter Koch Larsen
2005-03-05 15:39           ` Ludovic Brenta
2005-03-05 19:48             ` Ioannis Vranos
2005-03-06  1:01               ` Martin Dowie
2005-03-08 12:14                 ` Hans Malherbe
2005-03-08 15:31                   ` Peter Amey
2005-03-08 18:33                     ` CTips
2005-03-08 19:31                       ` Dmitry A. Kazakov
2005-03-08 20:13                         ` CTips
2005-03-08 20:59  4%                       ` Dmitry A. Kazakov
     [not found]     <pan.2005.10.26.22.16.09.200167@nowhere.net>
2005-10-26  1:41  6% ` Memory Mapped Storage Pools Dan Baysinger
2006-09-19 13:30  4% A novel design of linked lists (was: Address of an object) Dmitry A. Kazakov
2007-04-03 12:43     Finding out minimal allocation unit Stefan Bellon
2007-04-03 13:22     ` Georg Bauhaus
2007-04-03 13:34       ` Martin Krischik
2007-04-03 23:53         ` Randy Brukardt
2007-04-05  6:12           ` Stefan Bellon
2007-04-05 13:07             ` Robert A Duff
2007-04-05 18:02               ` Stefan Bellon
2007-04-06  1:31                 ` Randy Brukardt
2007-04-06  8:10                   ` Stefan Bellon
2007-04-06 17:17  7%                 ` Simon Wright
2007-04-06 12:38  5%         ` Stephen Leake
2007-07-25 22:04     Does 3.9.3(10) apply to untagged private whose full view is tagged? Adam Beneschan
2007-07-26  8:58  4% ` anon
2008-01-28 13:49     Allocators and memory reclamation Maciej Sobczak
2008-01-28 15:15     ` Dmitry A. Kazakov
2008-01-28 22:27  4%   ` Maciej Sobczak
2008-01-28 23:54  0%     ` Adam Beneschan
2009-05-01 21:39     GNAT on WinXP: System.OS_Lib.Spawn raises Program_Error daniel.wengelin
2009-05-02 15:59     ` Martin
2009-05-02 20:39  5%   ` anon
2009-05-03  9:42  0%     ` Martin
2009-08-18 22:26     put of access type Rob Solomon
2009-08-19  7:21     ` Dmitry A. Kazakov
2009-08-19 19:00       ` Rob Solomon
2009-08-19 21:01         ` Adam Beneschan
2009-08-19 22:45           ` Randy Brukardt
2009-08-20  6:18             ` Martin Krischik
2009-08-21  0:18               ` Randy Brukardt
2009-08-21  1:20  4%             ` Adam Beneschan
2011-01-22  0:04     User Defined Storage Pool : did you ever experiment with it ? Yannick Duchêne (Hibou57)
2011-01-22  9:47  4% ` User Defined Storage Pool : Example anon
2012-04-25 21:18  5% Is Storage Subpool Example tested? ytomino
2012-07-04 15:04  4% ANN: Deepend 3.0 Available for Ada 2012 and Ada 2005 Brad Moore
2014-08-12  6:54     A simple question about the "new" allocator NiGHTS
2014-08-12  7:35     ` Dmitry A. Kazakov
2014-08-12 13:38  7%   ` G.B.
2014-09-08  1:27  4% ANN: Deepend 3.4 Storage Pools Brad Moore
2017-04-18  6:31 14% Is there a reason System.Storage_Pools isn't Pure? Shark8
2017-04-18 18:32  6% ` Randy Brukardt
2017-04-18 23:42  6%   ` Shark8
2017-04-19  7:37  7%     ` Dmitry A. Kazakov
2017-04-19 18:50  6%       ` Shark8
2017-04-19 19:48  6%         ` Dmitry A. Kazakov
2017-04-19 20:42  7%       ` Randy Brukardt
2017-04-19 20:36  8%     ` Randy Brukardt
2017-04-20  0:12 12%       ` Shark8
2017-04-22  5:02  8%         ` Randy Brukardt
2017-04-22 17:18  8%           ` Shark8
2017-08-02 13:43     T'Interface attribute Dmitry A. Kazakov
2017-08-03  4:46     ` Randy Brukardt
2017-08-03  7:26  5%   ` Dmitry A. Kazakov
2017-08-04 23:51  0%     ` Randy Brukardt
2017-08-31 12:12     Interest in standard smart pointers for Ada 2020 Alejandro R. Mosteo
2017-08-31 15:17     ` Lucretia
2017-09-01  9:05  5%   ` AdaMagica
2017-10-14  2:53     Allocators design flaw Victor Porton
2017-10-14  7:27     ` Dmitry A. Kazakov
2017-10-14 14:12       ` Victor Porton
2017-10-14 14:28         ` Dmitry A. Kazakov
2017-10-14 15:14           ` Victor Porton
2017-10-14 15:42  4%         ` Simon Wright
2017-10-14 16:29  0%           ` Victor Porton
2018-02-23 20:42     two questions on allocators Mehdi Saada
2018-02-23 22:30  5% ` Shark8
2018-02-23 23:30  0%   ` Mehdi Saada
2018-02-24 10:20  0%   ` AdaMagica
2018-05-29 19:41     Memory pools John Perry
2018-05-31 19:28  5% ` gorgelo
2018-05-31 19:33  4% ` gorgelo
2019-02-16 19:40  5% Alignment issue Simon Wright
2021-09-13  0:53     Custom Storage Pool questions Jere
2021-09-13  5:29     ` Randy Brukardt
2021-09-20  0:31       ` Jere
2021-09-20  6:34         ` Niklas Holsti
2021-09-20  6:48           ` Emmanuel Briot
2021-09-20 16:59  5%         ` Shark8
2021-09-21  0:50             ` Randy Brukardt
2021-09-21 23:08               ` Jere
2021-09-28  4:42                 ` Randy Brukardt
2021-10-02 23:19  4%               ` Jere

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox