Skip to content

System#

For each implementation there is a library package called System which includes the definitions of certain configuration-dependent characteristics.

package System
   with Pure is

   type Name is <implementation-defined-enumeration-type>;
   System_Name: constant Name := <implementation-defined>;

   -- System-Dependent Named Numbers:
   Min_Int              : constant := root_integer'First;
   Max_Int              : constant := root_integer'Last;
   Max_Binary_Modulus   : constant := <implementation-defined>;
   Max_Nonbinary_Modulus: constant := <implementation-defined>;
   Max_Base_Digits      : constant := root_real'Digits;
   Max_Digits           : constant := <implementation-defined>;
   Max_Mantissa         : constant := <implementation-defined>;
   Fine_Delta           : constant := <implementation-defined>;
   Tick                 : constant := <implementation-defined>;

   -- Storage-related Declarations:
   type Address is <implementation-defined>;
   Null_Address: constant Address;
   Storage_Unit: constant := <implementation-defined>;
   Word_Size   : constant := <implementation-defined> * Storage_Unit;
   Memory_Size : constant := <implementation-defined>;

   -- Address Comparison:
   function "<" (Left, Right: Address) return Boolean with Convention => Intrinsic;
   function "<="(Left, Right: Address) return Boolean with Convention => Intrinsic;
   function ">" (Left, Right: Address) return Boolean with Convention => Intrinsic;
   function ">="(Left, Right: Address) return Boolean with Convention => Intrinsic;
   function "=" (Left, Right: Address) return Boolean with Convention => Intrinsic;
   -- function "/="(Left, Right: Address) return Boolean;
   -- "/=" is implicitly defined

   -- Other System-Dependent Declarations:
   type Bit_Order is (High_Order_First, Low_Order_First);
   Default_Bit_Order: constant Bit_Order := <implementation-defined>;

   -- Priority-related declarations (see D.1):
   subtype Any_Priority       is Integer      range <implementation-defined>;
   subtype Priority           is Any_Priority range Any_Priority'First .. <implementation-defined>;
   subtype Interrupt_Priority is Any_Priority range Priority'Last + 1 .. Any_Priority'Last;

   Default_Priority: constant Priority := (Priority'First + Priority'Last)/2;
end System;
System.Address_To_Access_Conversions
generic
   type Object(<>) is limited private;
package System.Address_To_Access_Conversions is
   with Preelaborate, Nonblocking, Global => in out synchronized is

   type Object_Pointer is access all Object;

   function To_Pointer(Value: Address)        return Object_Pointer with Convention => Intrinsic;
   function To_Address(Value: Object_Pointer) return Address        with Convention => Intrinsic;
end System.Address_To_Access_Conversions;

Storage Elements#

package System.Storage_Elements
   with Pure is

   type Storage_Offset is range <implementation-defined>;
   subtype Storage_Count is Storage_Offset range 0 .. Storage_Offset'Last;

   type Storage_Element is mod <implementation-defined>;
   for Storage_Element'Size use Storage_Unit;

   type Storage_Array is array(Storage_Offset range <>) of aliased Storage_Element;
   for Storage_Array'Component_Size use Storage_Unit;

   function "+"(Left: Address; Right: Storage_Offset) return Address with Convention => Intrinsic;
   function "+"(Left: Storage_Offset; Right: Address) return Address with Convention => Intrinsic;
   function "-"(Left: Address; Right: Storage_Offset) return Address with Convention => Intrinsic;
   function "-"(Left, Right: Address) return Storage_Offset with Convention => Intrinsic;

   function "mod"(Left: Address; Right: Storage_Offset) return Storage_Offset
      with Convention => Intrinsic;

   type Integer_Address is <implementation-defined>;
   function To_Address(Value: Integer_Address) return Address         with Convention => Intrinsic;
   function To_Integer(Value: Address)         return Integer_Address with Convention => Intrinsic;
end System.Storage_Elements;

Storage Pools#

Each access-to-object type has an associated storage pool. The storage allocated by an allocator comes from the pool; instances of Unchecked_Deallocation return storage to the pool. Several access types can share the same pool.

A storage pool is a variable of a type in the class rooted at Root_Storage_Pool, which is an abstract limited controlled type. By default, the implementation chooses a standard storage pool for each access-to-object type. The user may define new pool types, and may override the choice of pool for an access-to-object type by specifying Storage_Pool for the type.

with Ada.Finalization;
with System.Storage_Elements;

package System.Storage_Pools 
   with Pure, Nonblocking => False is

   type Root_Storage_Pool is abstract new Ada.Finalization.Limited_Controlled with private
      with Preelaborable_Initialization;

   procedure Allocate(Pool                    : in out Root_Storage_Pool;
                      Storage_Address         : out Address;
                      Size_In_Storage_Elements: Storage_Elements.Storage_Count;
                      Alignment               : Storage_Elements.Storage_Count)
      is abstract;
   procedure Deallocate(Pool                    : in out Root_Storage_Pool;
                        Storage_Address         : Address;
                        Size_In_Storage_Elements: Storage_Elements.Storage_Count;
                        Alignment               : Storage_Elements.Storage_Count)
      is abstract;
   function Storage_Size(Pool: Root_Storage_Pool) return Storage_Elements.Storage_Count
      is abstract;
end System.Storage_Pools;

Erroneous Execution

If Storage_Pool is specified for an access type, then if Allocate can satisfy the request, it should allocate a contiguous block of memory, and return the address of the first storage element in Storage_Address. The block should contain Size_In_Storage_Elements storage elements, and should be aligned according to Alignment. The allocated storage should not be used for any other purpose while the pool element remains in existence. If the request cannot be satisfied, then Allocate should propagate an exception [(such as Storage_Error)]. If Allocate behaves in any other manner, then the program execution is erroneous.

Examples

To associate an access type with a storage pool object, the user first declares a pool object of some type derived from Root_Storage_Pool. Then, the user defines its Storage_Pool attribute, as follows:

Pool_Object: Some_Storage_Pool_Type;

type T is access Designated;
for T'Storage_Pool use Pool_Object;
Another access type can be added to an existing storage pool, via:
for T2'Storage_Pool use T'Storage_Pool;
The semantics of this is implementation defined for a standard storage pool.

As usual, a derivative of Root_Storage_Pool can may define additional operations. For example, consider the Mark_Release_Pool_Type defined in 13.11.6, that has two additional operations, Mark and Release, the following is a possible use:

-- As defined in package MR_Pool, see 13.11.6
type Mark_Release_Pool_Type(Pool_Size: Storage_Elements.Storage_Count) is
   new Subpools.Root_Storage_Pool_With_Subpools with private;
...
Our_Pool: Mark_Release_Pool_Type(Pool_Size => 2000);
My_Mark : Subpool_Handle; -- As declared in 13.11.6

type Acc is access ...;
for Acc'Storage_Pool use Our_Pool;
...
My_Mark := Mark(Our_Pool);
... -- Allocate objects using “new (My_Mark) Designated(...)”.
Release(My_Mark); -- Finalize objects and reclaim storage.

Storage Subpools#

This subclause defines a package to support the partitioning of a storage pool into subpools. A subpool may be specified as the default to be used for allocation from the associated storage pool, or a particular subpool may be specified as part of an allocator (see 4.8).

package System.Storage_Pools.Subpools
    with Preelaborate, Global => in out synchronized is

   type Root_Storage_Pool_With_Subpools is abstract new Root_Storage_Pool with private
      with Preelaborable_Initialization;
   type Root_Subpool is abstract tagged limited private
      with Preelaborable_Initialization;

   type Subpool_Handle is access all Root_Subpool'Class;
   for Subpool_Handle'Storage_Size use 0;

   function Create_Subpool(Pool: in out Root_Storage_Pool_With_Subpools)
      return not null Subpool_Handle is abstract;

   -- The following operations are intended for pool implementers:
   function Pool_of_Subpool(Subpool: not null Subpool_Handle)
      return access Root_Storage_Pool_With_Subpools'Class;

   procedure Set_Pool_of_Subpool(Subpool: in not null Subpool_Handle;
                                 To     : in out Root_Storage_Pool_With_Subpools'Class)
      with Global => overriding in out Subpool;
   procedure Allocate_From_Subpool(Pool                    : in out Root_Storage_Pool_With_Subpools;
                                   Storage_Address         : out Address;
                                   Size_In_Storage_Elements: Storage_Elements.Storage_Count;
                                   Alignment               : Storage_Elements.Storage_Count;
                                   Subpool                 : in not null Subpool_Handle)
      is abstract
      with Pre'Class => Pool_of_Subpool(Subpool) = Pool'Access,
           Global    => overriding in out Subpool;
   procedure Deallocate_Subpool(Pool   : in out Root_Storage_Pool_With_Subpools;
                                Subpool: in out Subpool_Handle)
      is abstract
      with Pre'Class => Pool_of_Subpool(Subpool) = Pool'Access;
   function Default_Subpool_for_Pool(Pool: in out Root_Storage_Pool_With_Subpools)
      return not null Subpool_Handle;

   overriding
   procedure Allocate(Pool                    : in out Root_Storage_Pool_With_Subpools;
                      Storage_Address         : out Address;
                      Size_In_Storage_Elements: Storage_Elements.Storage_Count;
                      Alignment               : Storage_Elements.Storage_Count);
   overriding
   procedure Deallocate(Pool                    : in out Root_Storage_Pool_With_Subpools;
                        Storage_Address         : Address;
                        Size_In_Storage_Elements: Storage_Elements.Storage_Count;
                        Alignment               : Storage_Elements.Storage_Count)
      is null;

   overriding function Storage_Size(Pool: Root_Storage_Pool_With_Subpools)
      return Storage_Elements.Storage_Count is
         (Storage_Elements.Storage_Count'Last);
end System.Storage_Pools.Subpools;

Legality Rules

If a storage pool that supports subpools is specified as the Storage_Pool for an access type, the access type is called a subpool access type. A subpool access type shall be a pool-specific access type.

The accessibility level of a subpool access type shall not be statically deeper than that of the storage pool object. If the specified storage pool object is a storage pool that supports subpools, then the name that denotes the object shall not denote part of a formal parameter, nor shall it denote part of a dereference of a value of a non-library-level general access type. In addition to the places where Legality Rules normally apply (see 12.3), these rules also apply in the private part of an instance of a generic unit.

Erroneous Execution

If Allocate_From_Subpool does not meet one or more of the requirements on the Allocate procedure as given in the Erroneous Execution rules of 13.11, then the program execution is erroneous.

Atomic Exchange#

The language-defined generic package System.Atomic_Operations.Exchange provides the following operations:

  • To atomically compare the value of two atomic objects, and update the first atomic object with a desired value if both objects were found to be equal, or otherwise update the second object with the value of the first object.
  • To atomically update the value of an atomic object, and then return the value that the atomic object had just prior to the update.
    generic
       type Atomic_Type is private with Atomic;
    package System.Atomic_Operations.Exchange
       with Pure, Nonblocking is
    
       function Atomic_Exchange(Item: aliased in out Atomic_Type; Value: Atomic_Type) return Atomic_Type
          with Convention => Intrinsic;
       function Atomic_Compare_And_Exchange(Item   : aliased in out Atomic_Type;
                                            Prior  : aliased in out Atomic_Type;
                                            Desired: Atomic_Type) return Boolean
          with Convention => Intrinsic;
       function Is_Lock_Free(Item: aliased Atomic_Type) return Boolean
          with Convention => Intrinsic;
    end System.Atomic_Operations.Exchange;
    
Example of a spin lock using Atomic_Exchange
type Atomic_Boolean is new Boolean with Atomic;
package Exchange is new Atomic_Operations.Exchange(Atomic_Type => Atomic_Boolean);
Lock: aliased Atomic_Boolean := False;
...
begin -- Some critical section, trying to get the lock:
   -- Obtain the lock
   while Exchange.Atomic_Exchange(Item => Lock, Value => True) loop
      null;
   end loop;
   ... -- Do stuff
   Lock := False; -- Release the lock
end;

Atomic Test and Set#

The language-defined package System.Atomic_Operations.Test_And_Set provides an operation to atomically set and clear an atomic flag object.

package System.Atomic_Operations.Test_And_Set
   with Pure, Nonblocking is

   type Test_And_Set_Flag is mod <implementation-defined>
      with Atomic, Default_Value => 0, Size => <implementation-defined>;

   function Atomic_Test_And_Set(Item: aliased in out Test_And_Set_Flag) return Boolean
      with Convention => Intrinsic;
   procedure Atomic_Clear(Item: aliased in out Test_And_Set_Flag)
      with Convention => Intrinsic;
   function Is_Lock_Free(Item: aliased Test_And_Set_Flag) return Boolean
      with Convention => Intrinsic;
end System.Atomic_Operations.Test_And_Set;

Atomic Integer Arithemtic#

The language-defined generic package System.Atomic_Operations.Integer_Arithmetic provides operations to perform arithmetic atomically on objects of integer types.

generic
   type Atomic_Type is range <> with Atomic;
package System.Atomic_Operations.Integer_Arithmetic
   with Pure, Nonblocking is

   procedure Atomic_Add(Item: aliased in out Atomic_Type; Value: Atomic_Type)
      with Convention => Intrinsic;
   procedure Atomic_Subtract(Item: aliased in out Atomic_Type; Value: Atomic_Type)
      with Convention => Intrinsic;

   function Atomic_Fetch_And_Add(Item: aliased in out Atomic_Type; Value: Atomic_Type) return Atomic_Type
      with Convention => Intrinsic;
   function Atomic_Fetch_And_Subtract(Item: aliased in out Atomic_Type; Value: Atomic_Type) return Atomic_Type
      with Convention => Intrinsic;
   function Is_Lock_Free(Item: aliased Atomic_Type) return Boolean
      with Convention => Intrinsic;
end System.Atomic_Operations.Integer_Arithmetic;

Atomic Modular Arithmetic#

The language-defined generic package System.Atomic_Operations.Modular_Arithmetic provides operations to perform arithmetic atomically on objects of modular types.

generic
   type Atomic_Type is mod <> with Atomic;
package System.Atomic_Operations.Modular_Arithmetic
   with Pure, Nonblocking is

   procedure Atomic_Add(Item: aliased in out Atomic_Type; Value: Atomic_Type)
      with Convention => Intrinsic;
   procedure Atomic_Subtract(Item: aliased in out Atomic_Type; Value: Atomic_Type)
      with Convention => Intrinsic;

   function Atomic_Fetch_And_Add(Item: aliased in out Atomic_Type; Value: Atomic_Type) return Atomic_Type
      with Convention => Intrinsic;
   function Atomic_Fetch_And_Subtract(Item: aliased in out Atomic_Type; Value: Atomic_Type) return Atomic_Type
      with Convention => Intrinsic;
   function Is_Lock_Free(Item: aliased Atomic_Type) return Boolean
      with Convention => Intrinsic;
end System.Atomic_Operations.Modular_Arithmetic;

Address-to-Access Conversions#

generic
   type Object(<>) is limited private;
package System.Address_To_Access_Conversions
   with Preelaborate, Nonblocking, Global => in out synchronized is

   type Object_Pointer is access all Object;

   function To_Pointer(Value: Address) return Object_Pointer
      with Convention => Intrinsic;
   function To_Address(Value: Object_Pointer) return Address
      with Convention => Intrinsic;
end System.Address_To_Access_Conversions;

Multiprocessor#

This subclause allows implementations on multiprocessor platforms to be configured.

package System.Multiprocessors
   with Preelaborate, Nonblocking, Global => in out synchronized is

   type CPU_Range is range 0 .. <implementation-defined>;
   subtype CPU is CPU_Range range 1 .. CPU_Range'Last;

   Not_A_Specific_CPU: constant CPU_Range := 0;

   function Number_Of_CPUs return CPU;
end System.Multiprocessors;

Legality Rules

If the CPU aspect is specified for a subprogram, the expression shall be static.

The CPU aspect shall not be specified on a task or protected interface type.

Dispatching Domains#

This subclause allows implementations on multiprocessor platforms to be partitioned into distinct dispatching domains during program startup.

with Ada.Real_Time;
with Ada.Task_Identification;

package System.Multiprocessors.Dispatching_Domains
   with Nonblocking, Global => in out synchronized is

   Dispatching_Domain_Error: exception;

   type Dispatching_Domain(<>) is limited private;

   System_Dispatching_Domain: constant Dispatching_Domain;

   function Create(First, Last: CPU; Last: CPU_Range) return Dispatching_Domain;
   function Get_First_CPU(Domain: Dispatching_Domain) return CPU;
   function Get_Last_CPU (Domain: Dispatching_Domain) return CPU_Range CPU;

   type CPU_Set is array(CPU range <>) of Boolean;

   function Create(Set: CPU_Set) return Dispatching_Domain;
   function Get_CPU_Set(Domain: Dispatching_Domain) return CPU_Set;

   function Get_Dispatching_Domain(T: Ada.Task_Identification.Task_Id :=
                                      Ada.Task_Identification.Current_Task)
      return Dispatching_Domain;
   procedure Assign_Task(Domain: in out Dispatching_Domain;
                         CPU   : CPU_Range                       := Not_A_Specific_CPU;
                         T     : Ada.Task_Identification.Task_Id := Ada.Task_Identification.Current_Task);
   procedure Set_CPU(CPU: CPU_Range;
                     T  : Ada.Task_Identification.Task_Id := Ada.Task_Identification.Current_Task);
   function Get_CPU(T: Ada.Task_Identification.Task_Id :=
                       Ada.Task_Identification.Current_Task)
      return CPU_Range;
   procedure Delay_Until_And_Set_CPU(Delay_Until_Time: Ada.Real_Time.Time; CPU: CPU_Range);
end System.Multiprocessors.Dispatching_Domains;

Partition Communication System#

The Partition Communication Subsystem (PCS) provides facilities for supporting communication between the active partitions of a distributed program. The package System.RPC is a language-defined interface to the PCS.

with Ada.Streams;

package System.RPC
   with Nonblocking => False, Global => in out synchronized is

   type Partition_Id is range 0 .. <implementation-defined>;

   Communication_Error: exception;

   type Params_Stream_Type(Initial_Size: Ada.Streams.Stream_Element_Count) is
      new Ada.Streams.Root_Stream_Type with private;

   procedure Read(Stream: in out Params_Stream_Type;
                  Item  : out Ada.Streams.Stream_Element_Array;
                  Last  : out Ada.Streams.Stream_Element_Offset);
   procedure Write(Stream: in out Params_Stream_Type;
                   Item  : Ada.Streams.Stream_Element_Array);

   -- Synchronous call
   procedure Do_RPC(Partition: Partition_Id;
                    Params   : access Params_Stream_Type;
                    Result   : access Params_Stream_Type);
   -- Asynchronous call
   procedure Do_APC(Partition: Partition_Id;
                    Params   : access Params_Stream_Type);

   -- The handler for incoming RPCs
   type RPC_Receiver is access procedure(Params: access Params_Stream_Type;
                                         Result: access Params_Stream_Type);

   procedure Establish_RPC_Receiver(Partition: Partition_Id;
                                    Receiver : RPC_Receiver);
end System.RPC;