DataMuseum.dk

Presents historical artifacts from the history of:

Rational R1000/400

This is an automatic "excavation" of a thematic subset of
artifacts from Datamuseum.dk's BitArchive.

See our Wiki for more about Rational R1000/400

Excavated with: AutoArchaeologist - Free & Open Source Software.


top - download

⟦4db668ac9⟧ TextFile

    Length: 101481 (0x18c69)
    Types: TextFile
    Notes: R1k Text-file segment

Derivation

└─⟦8527c1e9b⟧ Bits:30000544 8mm tape, Rational 1000, Arrival backup of disks in PAM's R1000
    └─ ⟦5a81ac88f⟧ »Space Info Vol 1« 
        └─⟦799511cda⟧ 
            └─⟦this⟧ 

TextFile


  @node !Tools.Allows_Deallocation

  The Allows_Deallocation generic function determines whether
  unchecked storage deallocation can be performed on a designated
  object using the Unchecked_Deallocation generic procedure.
  Deallocation is allowed only for types that are not tasks or do
  not contain tasks or pointers to tasks as any of their components.

  The formal parameter list of this procedure is:
  generic
      type Object is limited private;
      type Name is access Object;
  function Allows_Deallocation return Boolean;

  The Object type is the type of the object for which storage is
  to be reclaimed.  The Name type is an access type that points to
  objects of the Object type.
  @node !Tools.Allows_Deallocation.Allows_Deallocation

  function Allows_Deallocation return Boolean;

  Determines whether unchecked storage deallocation can be performed
  on objects of Object type using the Unchecked_Deallocation generic
  procedure.

  Deallocation is allowed only for types that are not tasks or do not
  contain tasks or pointers to tasks as any of their components.
  @node !Tools.Allows_Deallocation.Name

  type Name is access Object;

  Defines the pointer to the object on which deallocation will be
  performed.

  Deallocation is allowed only for types that are not tasks or do not
  contain tasks or pointers to tasks as any of their components.
  @node !Tools.Allows_Deallocation.Object

  type Object is limited private;

  Defines the type of object on which deallocation will be performed.

  Deallocation is allowed only for types that are not tasks or do not
  contain tasks or pointers to tasks as any of their components.
  @node !Lrm.Calendar
  package Calendar is
   type Time is private;
   subtype Year_Number  is Integer  range 1901 .. 2099;
   subtype Month_Number is Integer  range 1    .. 12;
   subtype Day_Number   is Integer  range 1    .. 31;
   subtype Day_Duration is Duration range 0.0  .. 86_400.0;
   function Clock return Time;
   function Year    (Date : Time) return Year_Number;
   function Month   (Date : Time) return Month_Number;
   function Day     (Date : Time) return Day_Number;
   function Seconds (Date : Time) return Day_Duration;
   procedure Split (Date    :     Time;
                   Year    : out Year_Number;
                   Month   : out Month_Number;
                   Day     : out Day_Number;
                   Seconds : out Day_Duration);
   function Time_Of (Year    : Year_Number;
                    Month   : Month_Number;
                    Day     : Day_Number;
                    Seconds : Day_Duration := 0.0) return Time;
   function "+" (Left : Time; Right : Duration) return Time;
   function "+" (Left : Duration; Right : Time) return Time;
   function "-" (Left : Time; Right : Duration) return Time;
   function "-" (Left : Time; Right : Time)     return Duration;
   function "<"  (Left, Right : Time) return Boolean;
   function "<=" (Left, Right : Time) return Boolean;
   function ">"  (Left, Right : Time) return Boolean;
   function ">=" (Left, Right : Time) return Boolean;
   Time_Error : Exception;
  end Calendar;

  Ada requires a predefined library package called Calendar.  The
  Ada Language Reference Manual contains the general specification
  in Section 9.6, "Delay Statements, Duration, and Time."  The
  Rational implementation specification of package Calendar is given
  in this section.

  @node !Lrm.Calendar.Clock

  function Clock return Time;

  Returns the current clock time.
  @node !Lrm.Calendar.Day

  function Day (Date : Time) return Day_Number;

  Returns the current day of the month from the specified time.
  @node !Lrm.Calendar.Day_Duration

  subtype Day_Duration is Duration range 0.0 .. 86_400.0;

  Defines the range of seconds in a day.
  @node !Lrm.Calendar.Day_Number

  subtype Day_Number is Integer range 1 .. 31;

  Defines the range of days in a month.
  @node !Lrm.Calendar.Month

  function Month (Date : Time) return Month_Number;

  Returns the current month from the specified time.
  @node !Lrm.Calendar.Month_Number

  subtype Month_Number is Integer range 1 .. 12;

  Defines the range of months in a year.
  @node !Lrm.Calendar.Seconds

  function Seconds (Date : Time) return Day_Duration;

  Returns the current second of the day from the specified time.
  @node !Lrm.Calendar.Split

  procedure Split (Date    :     Time;
                  Year    : out Year_Number;
                  Month   : out Month_Number;
                  Day     : out Day_Number;
                  Seconds : out Day_Duration);

  Splits the specified time into year, month, day, and seconds.
  @node !Lrm.Calendar.Time

  type Time is private;

  Defines the basic type for handling time.
  @node !Lrm.Calendar.Time_Error

  Time_Error : exception;

  Defines an exception that can be raised by several functions in
  this package.

  This exception is raised by the Time_Of function if the actual
  parameters do not form a proper date.  This exception is also
  raised by the operators "+" and "-" if, for the given operands,
  these operators cannot return a date whose year number is in the
  range of the corresponding subtype, or if the operator "-" cannot
  return a result that is in the range of the Duration type.
  @node !Lrm.Calendar.Time_Of

  function Time_Of (Year    : Year_Number;
                   Month   : Month_Number;
                   Day     : Day_Number;
                   Seconds : Day_Duration := 0.0) return Time;

  Converts a year, month, day, and seconds into a time.
  @node !Lrm.Calendar.Year

  function Year (Date : Time) return Year_Number;

  Returns the current year from the specified time.
  @node !Lrm.Calendar.Year_Number

  subtype Year_Number is Integer range 1901 .. 2099;

  Defines the range of allowable years.
  @node !Lrm.Calendar."+"

  function "+" (Left : Time; Right : Duration) return Time;
  function "+" (Left : Duration; Right : Time) return Time;

  Returns the sum of the specified time and duration.
  @node !Lrm.Calendar."-"

  function "-" (Left : Time; Right : Duration) return Time;
  function "-" (Left : Time; Right : Time) return Duration;

  Returns the difference of the specified time and duration or
  specified times.
  @node !Lrm.Calendar."<"

  function "<" (Left, Right : Time) return Boolean;

  Determines whether one specified time is less than another
  specified time.
  @node !Lrm.Calendar."<="

  function "<=" (Left, Right : Time) return Boolean;

  Determines whether one specified time is less than or equal to
  another specified time.
  @node !Lrm.Calendar.">"

  function ">" (Left, Right : Time) return Boolean;

  Determines whether one specified time is greater than another
  specified time.
  @node !Lrm.Calendar.">="

  function ">=" (Left, Right : Time) return Boolean;

  Determines whether one specified time is greater than or equal to
  another specified time.
  @node !Tools.Concurrent_Map_Generic

  Generic package Concurrent_Map_Generic provides a means of mapping
  values of one type into values of another type in multitasking
  programs.  This translation from one type (called the domain type)
  to another type (called the range type) is a one-to-one mapping.

  The package supports any number of concurrent read operations,
  but it serializes all update operations.  Specifically, any
  number of Find/Eval/Is_Empty/Copy operations be done safely in
  parallel with a Define/Undefine/Make_Empty operation.  Multiple
  Define/Undefine/Make_Empty operations are serialized.  Iterators
  over the elements in a map can be used asynchronously; however,
  the sequence of values yielded may reflect the changes that have
  occurred in the map while the values are being accessed.

  Several operations can perform checks for changing domain values
  that are already defined.  A parameter selects whether this check
  allows the redefinition to occur or raises the Multiply_Defined
  exception (in this package).  If any operation is passed an illegal
  input, the Constraint_Error exception is raised.

  The implementation of this generic package uses a hash table.  The
  size of the hash table (the number of buckets) is one of the formal
  parameters of the generic.  The hash function, which spreads the
  values of the domain over the integer range, is also a parameter to
  the generic.

  The formal parameters to the generic are:
  generic
      Size : Integer;
      type Domain_Type is private;
      type Range_Type  is private;
      with function Hash (Key : Domain_Type) return Integer is <>;
  package Concurrent_Map_Generic is
      ...
  end Concurrent_Map_Generic;

  These parameters define the number of buckets in the hash table,
  the type of the domain, the type of the range, and the hash
  function.
  @node !Tools.Concurrent_Map_Generic.Cardinality

  function Cardinality (The_Map : Map) return Natural;

  Returns the number of mappings defined in the specified map.
  @node !Tools.Concurrent_Map_Generic.Copy

  procedure Copy (Target : in out Map;
                 Source :        Map);

  Copies the contents of the source map into the target map.

  This procedure first deletes all entries from the target and then
  adds an entry in the target for each entry in the source.
  @node !Tools.Concurrent_Map_Generic.Define

  procedure Define (The_Map        : in out Map;
                   D             :        Domain_Type;
                   R             :        Range_Type;
                   Trap_Multiples :        Boolean      := False);

  Defines a correspondence between a domain value and a range value.

  This procedure creates entries in the map.  The procedure traps
  multiple definitions of domain values when the Trap_Multiples
  parameter is true.  When the parameter is false, the domain value
  is redefined to the new range value.
  @node !Tools.Concurrent_Map_Generic.Domain_Type

  type Domain_Type is private;

  Defines the type for the domain of the map.

  The type must be a pure value type, and it must be constrained.
  The implicit operations of assignment and equality must work with
  values of this type.
  @node !Tools.Concurrent_Map_Generic.Done

  function Done (Iter : Iterator) return Boolean;

  Determines whether the iteration over the map is complete.
  @node !Tools.Concurrent_Map_Generic.Eval

  function Eval (The_Map : Map;
                D       : Domain_Type) return Range_Type;

  Returns a range value that corresponds to the specified domain
  value in the specified map.

  When the given value of the domain does not exist, the Undefined
  exception is raised.
  @node !Tools.Concurrent_Map_Generic.Find

  procedure Find (The_Map :        Map;
                 D       :        Domain_Type;
                 R       : in out Range_Type;
                 Success :    out Boolean);
  procedure Find (The_Map :        Map;
                 D       :        Domain_Type;
                 P       : in out Pair;
                 Success :    out Boolean);

  Finds the range value corresponding to the specified domain value
  (D) in the specified map.

  This procedure finds the value of the range that corresponds to
  the domain value in the map.  When the given value of the domain
  exists in the map, the R (range), or P (pair), parameter is updated
  with the domain/range values, and the Success parameter is returned
  true.  When the given value of the domain does not exist, the R, or
  P, parameter is not changed, and the Success parameter is returned
  false.
  @node !Tools.Concurrent_Map_Generic.Hash

  with function Hash (Key : Domain_Type) return Integer is <>;

  Defines the hash function used in the map.

  This function takes a value of the domain type and creates an
  integer that is used to select a bucket in the hash table.  That
  bucket will contain a corresponding value of the range type, if
  it exists.  The integer returned by this function is normalized
  internally by the map operations to select a bucket.

  In general, the map will perform better when the range of the
  integer returned by this function is much larger than the size of
  the hash table.
  @node !Tools.Concurrent_Map_Generic.Init

  procedure Init (Iter    : out Iterator;
                 The_Map :     Map);

  Initializes the iterator to iterate through all the entries in the
  specified map.

  When one or more entries exist in the map, the Value function
  returns the first entry in the map using this value of the
  iterator.  When no entries exist in the map, the Done function
  returns the value true using this value of the iterator.
  @node !Tools.Concurrent_Map_Generic.Initialize

  procedure Initialize (The_Map : out Map);

  Creates an initialized and empty map.

  This procedure creates a map; the map does not have to be created
  by the Nil function.  The map contains no entries.
  @node !Tools.Concurrent_Map_Generic.Is_Empty

  function Is_Empty (The_Map : Map) return Boolean;

  Determines whether the specified map is empty.

  This function checks whether the map contains no entries.  When a
  map is initialized or after the Make_Empty procedure is executed on
  the map, this condition is true.
  @node !Tools.Concurrent_Map_Generic.Is_Nil

  function Is_Nil (The_Map : Map) return Boolean;

  Returns true if the indicated map is null---that is, one that has
  not been initialized.
  @node !Tools.Concurrent_Map_Generic.Iterator

  type Iterator is private;

  Defines a type that allows iterating over all entries in a map.

  Objects of the Iterator type contain all of the information
  necessary to step over all of the entries in a map.  The type is
  used with the Init and Next procedures and the Value and Done
  functions.
  @node !Tools.Concurrent_Map_Generic.Make_Empty

  procedure Make_Empty (The_Map : in out Map);

  Clears the map of all entries.
  @node !Tools.Concurrent_Map_Generic.Map

  type Map is private;

  Defines the representation of the map.

  Several important properties of the map type are visible through
  the implicit operations of assignment and equality.  Assignment
  for this type has the property that the contents of the map are
  not copied but a new alias (a new name) for the map is created.
  Equality for this type has the property that the values of the
  maps are not compared but the names are compared.  In other words,
  the operation of equality checks to determine whether any two map
  values designate the same map.
  @node !Tools.Concurrent_Map_Generic.Multiply_Defined

  Multiply_Defined : exception;

  Defines the exception raised by the Define procedure when the
  Domain parameter is already defined in the specified map and the
  value of the Trap_Multiples parameter is true.
  @node !Tools.Concurrent_Map_Generic.Next

  procedure Next (Iter : in out Iterator);

  Steps the iterator to point to the next entry in the map.

  This procedure changes the iterator to point to the next entry in
  the map.  When the iterator steps past the last entry, the Done
  function returns the value true.
  @node !Tools.Concurrent_Map_Generic.Nil

  function Nil return Map;

  Returns a null map---that is, a map that is not initialized.

  This function creates an uninitialized map.  The map must be
  initialized before it can be used.
  @node !Tools.Concurrent_Map_Generic.Pair

  type Pair is
      record
          D : Domain_Type;
          R : Range_Type;
      end record;

  Defines a record that contains a value of both the domain and the
  range.
  @node !Tools.Concurrent_Map_Generic.Range_Type

  type Range_Type is private;

  Defines the type for the range of the map.

  The type must be a pure value type, and it must be constrained.
  The implicit operations of assignment and equality must work with
  values of this type.
  @node !Tools.Concurrent_Map_Generic.Size

  Size : Integer;

  Defines the size of the hash table in the map.

  The value provided for this generic parameter depends on the hash
  function used and the number of expected or allowed values of the
  domain type.  Preferred values are prime numbers.
  @node !Tools.Concurrent_Map_Generic.Undefine

  procedure Undefine (The_Map : in out Map;
                     D       :        Domain_Type);

  Removes a map entry or entries for the domain value.

  This procedure removes all entries for the specified domain value
  from the map.  When the domain value does not exist in the map, the
  procedure raises the Undefined exception.
  @node !Tools.Concurrent_Map_Generic.Undefined

  Undefined : exception;

  Defines the exception raised by the Eval function or the Undefine
  procedure when the Domain parameter does not exist in the specified
  map.
  @node !Tools.Concurrent_Map_Generic.Value

  function Value (Iter : Iterator) return Domain_Type;

  Returns the domain value of the current entry pointed to by the
  iterator.
  @node !Tools.Hash

  This package defines simple hash functions returning Integer and
  Long_Integer values for Long_Integer and Ptr (pointer) types.
  These functions provide a many-to-one mapping between the input
  values and the output values.  All functions are guaranteed not to
  raise any exceptions.
  @node !Tools.Hash.Long_Integer_To_Integer

  function Long_Integer_To_Integer (Value : Long_Integer) return Integer;

  Returns a hash value of the Integer type based on the value of the
  Value parameter.

  This function provides a many-to-one mapping between long integers
  and integers.
      generic
          type T   is limited private;
          type Ptr is access T;
      function Pointer_To_Integer (P : Ptr) return Integer;
  @node !Tools.Hash.Pointer_To_Integer

  function Pointer_To_Integer (P : Ptr) return Integer;

  Provides a many-to-one mapping between pointers and integers.
  @node !Tools.Hash.Ptr

  type Ptr is access T;

  Defines the access type to be hashed.
  @node !Tools.Hash.T

  type T is limited private;

  Defines the type of object designated by the pointer to be hashed.
      generic
          type T   is limited private;
          type Ptr is access T;
      function Pointer_To_Long_Integer (P : Ptr) return Long_Integer;
  @node !Tools.Hash.Pointer_To_Long_Integer

  function Pointer_To_Long_Integer (P : Ptr) return Long_Integer;

  Provides a many-to-one mapping between pointers and long integers.
  @node !Tools.Hash.Ptr

  type Ptr is access T;

  Defines the access type to be hashed.
  @node !Tools.Hash.T

  type T is limited private;

  Defines the type of object designated by the pointer to be hashed.
  @node !Tools.List_Generic

  Generic package List_Generic provides a means of creating and
  manipulating abstract lists of elements.  This generic allows lists
  of arbitrary size.  There are operations for creating and adding
  items to lists, traversing and manipulating lists, and iterating
  over the items in lists.

  If illegal values are provided to any of the operations in this
  package, the Constraint_Error exception is raised.

  The formal parameter to the generic is:
  generic
      type Element is private;
  package List_Generic is
      ...
  end List_Generic;
          This parameter defines the kinds of elements that will make
  up lists.
  @node !Tools.List_Generic.Done

  function Done (Iter : Iterator) return Boolean;

  Determines whether the iterator has cycled through all of the
  elements in a list.
  @node !Tools.List_Generic.Element

  type Element is private;

  Defines the type of elements in lists.

  The actual supplied for this type cannot be unconstrained.
  @node !Tools.List_Generic.First

  function First (L : List) return Element;

  Returns the first element in the list.
  @node !Tools.List_Generic.Free

  procedure Free (L : in out List);

  Reclaims the storage associated with the list and sets it to the
  empty list.
  @node !Tools.List_Generic.Init

  procedure Init (Iter : out Iterator;
                 L    : List);

  Initializes the iterator to iterate over the elements in the
  specified list.

  When one or more elements exist in the list, the Value function
  returns the first element in the list using this value of the
  iterator.  Successive values can be accessed by advancing the
  iterator to the next value using the Next procedure.  When no
  elements exist in the list, the Done function returns the value
  true using this value of the iterator.
  @node !Tools.List_Generic.Is_Empty

  function Is_Empty (L : List) return Boolean;

  Determines whether the list is empty.

  A list is empty if it contains no elements.  This condition is true
  when a list is declared, when a list is set to the value returned
  by the Nil function, or after the Free procedure has been called
  with it.
  @node !Tools.List_Generic.Iterator

  type Iterator is private;

  Defines a type that allows iterating over all elements in a list.

  Objects of this type can contain all of the information necessary
  to step over all of the elements in a list.  The type is used with
  the Init and Next procedures and the Value and Done functions.
  @node !Tools.List_Generic.Length

  function Length (L : List) return Natural;

  Computes the number of elements in a list.

  The length of an empty list is 0.
  @node !Tools.List_Generic.List

  type List is private;

  Defines the representation of a list.

  Several important properties of the List type are visible through
  the implicit operations of assignment and equality.  Assignment
  for this type has the property that the contents of the list are
  not copied but a new alias (a new name) for the list is created.
  Equality for this type has the property that the values of the
  lists are not compared but the names are compared.  In other words,
  the operation of equality checks to determine whether two list
  values designate the same list.
  @node !Tools.List_Generic.Make

  function Make (X : Element;
                L : List) return List;

  Adds the specified element to the front of the specified list and
  returns the new list.
  @node !Tools.List_Generic.Next

  procedure Next (Iter : in out Iterator);

  Advances the iterator to point to the next element in the list.

  When the iterator steps past the last element, the Done function
  returns the value true.
  @node !Tools.List_Generic.Nil

  function Nil return List;

  Returns the empty list containing no elements.
  @node !Tools.List_Generic.Rest

  function Rest (L : List) return List;

  Returns the list of elements that remain after removing the first
  element from the list.
  @node !Tools.List_Generic.Set_First

  procedure Set_First (L     : List;
                      To_Be : Element);

  Replaces the first element in the list with the new element.
  @node !Tools.List_Generic.Set_Rest

  procedure Set_Rest  (L     : List;
                      To_Be : List);

  Replaces all of the elements of the L parameter, other than its
  first element, with the elements in the list specified by the To_Be
  parameter.

  This operation structurally modifies the list L by replacing the
  list of elements after its first element with the list To_Be.  It
  does not create a copy of To_Be.
  @node !Tools.List_Generic.Value

  function Value (Iter : Iterator) return Element;

  Returns the element pointed to by the iterator.
  @node !Tools.Map_Generic

  Generic package Map_Generic provides a means of mapping values of
  one type into values of another type.  This translation from one
  type (called the domain type) to another type (called the range
  type) is a one-to-one mapping.

  Several operations can perform checks for changing domain values
  that are already defined.  A parameter selects whether this check
  allows the redefinition to occur or raises the Multiply_Defined
  exception (in this package).  If any operation is passed an illegal
  input, the Constraint_Error exception is raised.

  The implementation of this generic package uses a hash table.  The
  size of the hash table (the number of buckets) is one of the formal
  parameters of the generic.  The hash function, which spreads the
  values of the domain over the integer range, is also a parameter to
  the generic.

  The formal parameters to the generic are:
  generic
      Size : Integer;
      type Domain_Type is private;
      type Range_Type is private;
      with function Hash (Key : Domain_Type) return Integer is <>;
  package Map_Generic is
      ...
  end Map_Generic;

  These parameters define the number of buckets in the hash table,
  the type of the domain, the type of the range, and the hash
  function.
  @node !Tools.Map_Generic.Cardinality

  function Cardinality (The_Map : Map) return Natural;

  Returns the number of mappings defined in the specified map.
  @node !Tools.Map_Generic.Copy

  procedure Copy (Target : in out Map;
                 Source :        Map);

  Copies the contents of the source map into the target map.

  This procedure first deletes all entries from the target and then
  adds an entry in the target for each entry in the source.
  @node !Tools.Map_Generic.Define

  procedure Define (The_Map        : in out Map;
                   D             :        Domain_Type;
                   R             :        Range_Type;
                   Trap_Multiples :        Boolean      := False);

  Defines a correspondence between a domain value and a range value.

  This procedure creates entries in the map.  The procedure traps
  multiple definitions of domain values when the Trap_Multiples
  parameter is true.  When the parameter is false, the domain value
  is redefined to the new range value.
  @node !Tools.Map_Generic.Domain_Type

  type Domain_Type is private;

  Defines the type for the domain of the map.

  The type must be a pure value type, and it must be constrained.
  The implicit operations of assignment and equality must work with
  values of this type.
  @node !Tools.Map_Generic.Done

  function Done (Iter : Iterator) return Boolean;

  Determines whether the iteration over the map is complete.
  @node !Tools.Map_Generic.Eval

  function Eval (The_Map : Map;
                D       : Domain_Type) return Range_Type;

  Returns a range value that corresponds to the specified domain
  value in the specified map.

  When the given value of the domain does not exist, the Undefined
  exception is raised.
  @node !Tools.Map_Generic.Find

  procedure Find (The_Map :        Map;
                 D       :        Domain_Type;
                 R       : in out Range_Type;
                 Success :    out Boolean);
  procedure Find (The_Map :        Map;
                 D       :        Domain_Type;
                 P       : in out Pair;
                 Success :    out Boolean);

  Finds the range value that corresponds to the specified domain
  value in the specified map.

  When the given value of the domain exists in the map, the R
  (range), or P (pair), parameter is updated with the domain/range
  values, and the Success parameter is returned true.  When the given
  value of the domain does not exist, the R, or P, parameter is not
  changed, and the Success parameter is returned false.
  @node !Tools.Map_Generic.Hash

  with function Hash (Key : Domain_Type) return Integer is <>;

  Defines the hash function used in the map.

  This function takes a value of the domain type and creates an
  integer that is used to select a bucket in the hash table.  That
  bucket will contain a corresponding value of the range type, if
  it exists.  The integer returned by this function is normalized
  internally by the map operations to select a bucket.

  In general, the map will perform better when the range of the
  integer returned by this function is much larger than the size of
  the hash table.
  @node !Tools.Map_Generic.Init

  procedure Init (Iter    : out Iterator;
                 The_Map :     Map);

  Initializes the iterator for the specified map.

  This procedure initializes the iterator for the specified map.
  When one or more entries exist in the map, the Value function
  returns the first entry in the map using this value of the
  iterator.  When no entries exist in the map, the Done function
  returns the value true using this value of the iterator.
  @node !Tools.Map_Generic.Initialize

  procedure Initialize (The_Map : out Map);

  Creates an initialized and empty map.

  This procedure creates a map that contains no entries.
  @node !Tools.Map_Generic.Is_Empty

  function Is_Empty (The_Map : Map) return Boolean;

  Determines whether the specified map is empty.

  This function checks whether the map contains no entries.  When a
  map is initialized or after the Make_Empty procedure is executed on
  the map, this condition is true.
  @node !Tools.Map_Generic.Is_Nil

  function Is_Nil (The_Map : Map) return Boolean;

  Returns true if the indicated map is null---that is, one that has
  not been initialized.
  @node !Tools.Map_Generic.Iterator

  type Iterator is private;

  Defines a type that allows iterating over all entries in a map.

  Objects of the Iterator type contain all of the information
  necessary to step over all of the entries in a map.  The Iterator
  type is used with the Init and Next procedures and the Value and
  Done functions.
  @node !Tools.Map_Generic.Make_Empty

  procedure Make_Empty (The_Map : in out Map);

  Clears the map of all entries.
  @node !Tools.Map_Generic.Map

  type Map is private;

  Defines the representation of the map.

  Several important properties of the Map type are visible through
  the implicit operations of assignment and equality.  Assignment
  for this type has the property that the contents of the map are
  not copied but a new alias (a new name) for the map is created.
  Equality for this type has the property that the values of the
  maps are not compared but the names are compared.  In other words,
  the operation of equality checks to determine whether any two map
  values designate the same map.
  @node !Tools.Map_Generic.Multiply_Defined

  Multiply_Defined : exception;

  Defines the exception raised by the Define procedure when the
  Domain parameter is already defined in the specified map and the
  value of the Trap_Multiples parameter is true.
  @node !Tools.Map_Generic.Next

  procedure Next (Iter : in out Iterator);

  Steps the iterator to point to the next entry in the map.

  This procedure changes the iterator to point to the next entry in
  the map.  When the iterator steps past the last entry, the Done
  function returns the value true.
  @node !Tools.Map_Generic.Nil

  function Nil return Map;

  Returns a null map---that is, a map that is not initialized.

  This function creates an uninitialized map.  The map must be
  initialized before it can be used.
  @node !Tools.Map_Generic.Pair

  type Pair is
      record
          D : Domain_Type;
          R : Range_Type;
      end record;

  Defines a record that contains a value of both the domain and the
  range.
  @node !Tools.Map_Generic.Range_Type

  type Range_Type is private;

  Defines the type for the range of the map.

  The type must be a pure value type, and it must be constrained.
  The implicit operations of assignment and equality must work with
  values of this type.
  @node !Tools.Map_Generic.Size

  Size : Integer;

  Defines the size of the hash table in the map.

  The value provided for this generic parameter depends on the hash
  function used and the number of expected or allowed values of the
  domain type.  Preferred values are prime numbers.
  @node !Tools.Map_Generic.Undefine

  procedure Undefine (The_Map : in out Map;
                     D       :        Domain_Type);

  Removes a map entry or entries for the domain value.

  This procedure removes all entries for the specified domain value
  from the map.  When the domain value does not exist in the map, the
  procedure raises the Undefined exception.
  @node !Tools.Map_Generic.Undefined

  Undefined : exception;

  Defines the exception raised by the Eval function or the Undefine
  procedure when the Domain parameter does not exist in the specified
  map.
  @node !Tools.Map_Generic.Value

  function Value (Iter : Iterator) return Domain_Type;

  Returns the domain value of the current entry pointed to by the
  iterator.
  @node !Tools.Queue_Generic

  Generic package Queue_Generic provides a means of creating and
  manipulating abstract queues of elements.  This generic allows
  queues of arbitrary size.  There are operations for creating
  queues, adding and removing elements from them, and iterating
  over the items in them.

  If illegal values are provided to any of the operations in this
  package, the Constraint_Error exception is raised.

  The formal parameter to the generic is:
  generic
      type Element is private;
  package Queue_Generic is
      ...
  end Queue_Generic;
          This parameter defines the kinds of elements that will be
  queued.
  @node !Tools.Queue_Generic.Add

  procedure Add (Q : in out Queue;
                X :        Element);

  Adds an element to the end of the queue.
  @node !Tools.Queue_Generic.Copy

  procedure Copy (Target : in out Queue;
                 Source :        Queue);

  Deletes any elements in the target, initializes the target if
  necessary, and copies all of the elements in the source into the
  target.
  @node !Tools.Queue_Generic.Delete

  procedure Delete (Q : in out Queue);

  Removes the item at the beginning of the queue from the queue.

  The item at the beginning of the queue is the same as the item
  returned by the First function.
  @node !Tools.Queue_Generic.Done

  function Done (Iter : Iterator) return Boolean;

  Determines whether the iterator has cycled through all of the
  elements in a queue.
  @node !Tools.Queue_Generic.Element

  type Element is private;

  Defines the type of elements in queues.

  The actual supplied for this type cannot be unconstrained.
  @node !Tools.Queue_Generic.First

  function First (Q : Queue) return Element;

  Returns the item at the beginning of the queue.
  @node !Tools.Queue_Generic.Init

  procedure Init (Iter : out Iterator;
                 Q    :     Queue);

  Initializes the iterator to iterate over the elements in the
  specified queue.

  When one or more elements exist in the queue, the Value function
  returns the first element in the queue using this value of the
  iterator.  Successive values can be accessed by advancing the
  iterator to the next value using the Next procedure.  When no
  elements exist in the queue, the Done function returns the value
  true using this value of the iterator.
  @node !Tools.Queue_Generic.Initialize

  procedure Initialize (Q : out Queue);

  Creates an empty queue.

  Note that this procedure is provided for consistency between this
  package and other similar packages.  However, it has no effect
  and need not be called because all the objects of the Queue
  type that are declared are implicitly initialized.Queue type;
  Queue_Generic.Queue; Initialize procedure
  @node !Tools.Queue_Generic.Is_Empty

  function Is_Empty (Q : Queue) return Boolean;

  Determines whether the queue is empty.
  @node !Tools.Queue_Generic.Iterator

  type Iterator is private;

  Defines a type that allows iterating over all elements in a queue.

  Objects of this type can contain all of the information necessary
  to step over all of the elements in a queue.  The type is used with
  the Init and Next procedures and the Value and Done functions.
  @node !Tools.Queue_Generic.Make_Empty

  procedure Make_Empty (Q : in out Queue);

  Removes all of the elements from the queue, making it empty.
  @node !Tools.Queue_Generic.Next

  procedure Next (Iter : in out Iterator);

  Advances the iterator to point to the next element in the queue.

  When the iterator steps past the last element, the Done function
  returns the value true.
  @node !Tools.Queue_Generic.Queue

  type Queue is private;

  Defines the representation of a queue.

  Several important properties of the Queue type are visible through
  the implicit operations of assignment and equality.  Assignment
  for this type has the property that the contents of the queue are
  not copied but a new alias (a new name) for the queue is created.
  Equality for this type has the property that the values of the
  queues are not compared but the names are compared.  In other
  words, the operation of equality checks to determine whether two
  queue values designate the same list.
  @node !Tools.Queue_Generic.Value

  function Value (Iter : Iterator) return Element;

  Returns the element pointed to by the iterator.
  @node !Tools.Set_Generic

  Generic package Set_Generic provides a means of creating and
  manipulating abstract sets of objects.  This generic allows sets
  of arbitrary size.  There are operations for adding members of the
  set, deleting members of the set, checking for membership in the
  set, and iterating over all members of the set.

  If illegal values are passed to any of the operations in this
  package, the Constraint_Error exception is raised.

  The formal parameter to the generic is:
  generic
      type Element is private;
  package Set_Generic is
      ...
  end Set_Generic;

  This parameter can be of any pure value type.
  @node !Tools.Set_Generic.Add

  procedure Add (S : in out Set;
                X :        Element);

  Adds the specified element to the specified set.

  When the element is already in the set, the procedure does not
  alter the set.
  @node !Tools.Set_Generic.Copy

  procedure Copy (Target : in out Set;
                 Source :        Set);

  Copies the contents of the source set into the target set.

  This procedure first removes all elements from the target and then
  adds all elements in the source to the target.
  @node !Tools.Set_Generic.Delete

  procedure Delete (S : in out Set;
                   X :        Element);

  Deletes the specified element from the specified set.

  When the element is not already in the set, the procedure does not
  alter the set.
  @node !Tools.Set_Generic.Done

  function Done (Iter : Iterator) return Boolean;

  Determines whether the iteration over the set is complete.

  This function checks whether the iterator has cycled through all of
  the elements in the set.

  @node !Tools.Set_Generic.Element

  type Element is private;

  Defines the type of elements in the set.

  The type must be a pure value type.  The implicit operations of
  assignment and equality must work with values of this type.
  @node !Tools.Set_Generic.Init

  procedure Init (Iter : out Iterator;
                 S    :     Set);

  Initializes the iterator for the specified set.

  When one or more elements exist in the set, the Value function
  returns the first element in the set using this value of the
  iterator.  When no elements exist in the set, the Done function
  returns the value true using this value of the iterator.
  @node !Tools.Set_Generic.Initialize

  procedure Initialize (S : out Set);

  Creates an initialized and empty set.

  This procedure creates a set that contains no elements.  Objects of
  Set type are initially empty, so the use of this procedure is not
  required.
  @node !Tools.Set_Generic.Is_Empty

  function Is_Empty (S : Set) return Boolean;

  Determines whether the specified set is empty.

  This function checks whether the set contains no elements.  When a
  set is declared or initialized, or after the Make_Empty procedure
  is executed on the set, this condition is true.
  @node !Tools.Set_Generic.Is_Member

  function Is_Member (S : Set;
                     X : Element) return Boolean;

  Determines whether the specified element is a member of the
  specified set.
  @node !Tools.Set_Generic.Iterator

  type Iterator is private;

  Defines a type that allows iterating over all elements in a set.

  Objects of this type contain all of the information necessary to
  step over all of the elements in a set.  The type is used with the
  Init and Next procedures and the Value and Done functions.
  @node !Tools.Set_Generic.Make_Empty

  procedure Make_Empty (S : in out Set);

  Clears the set of all elements.
  @node !Tools.Set_Generic.Next

  procedure Next (Iter : in out Iterator);

  Steps the iterator to point to the next element in the set.

  This procedure changes the iterator to point to the next element in
  the set.  Although the set is unordered, the iterator steps through
  all elements one by one.  When the iterator steps past the last
  element, the Done function returns the value true.
  @node !Tools.Set_Generic.Set

  type Set is private;

  Defines the representation of the set.

  Several important properties of the Set type are visible through
  the implicit operations of assignment and equality.  Assignment
  for this type has the property that the contents of the set are
  not copied but a new alias (a new name) for the set is created.
  Equality for this type has the property that the values of the sets
  are not compared but the names are compared.  In other words, the
  operation of equality checks to determine whether two set values
  designate the same set.
  @node !Tools.Set_Generic.Value

  function Value (Iter : Iterator) return Element;

  Returns the element pointed to by the iterator.
  @node !Tools.Simple_Status

  This package provides an abstraction for simple error status
  reporting.  It defines a type, the Condition type, that can be
  used to return error information from subprogram calls.  The
  status returned from some Environment interfaces is of the
  Condition type and can be interrogated/manipulated with operations
  provided in this package.  Users can also use this abstraction when
  implementing error reporting in their own applications.

  A condition consists of a condition name and a message.  The
  condition name indicates the type of error (if any), the severity
  of the error, and whether the operation completed successfully.
  The message provides additional information about the error.

  By convention, condition names in an application should
  be standardized so that error conditions can be tested
  programmatically.  In simple applications, a condition name alone
  can be used to indicate status.

  Objects of the condition type are relatively large; where space and
  time considerations are important, they should be passed with in
  out mode so that copies are not made when subprograms are called.
  @node !Tools.Simple_Status.Condition

  type Condition is private;

  Defines a status condition that can be used to return error
  information from subprogram calls.

  A condition consists of a condition name and a message.  The
  condition name indicates the type of error (if any), the severity
  of the error, and whether the operation completed successfully.
  The message provides additional information about the error.

  Conditions are self-initializing---objects of the Condition type
  will have null strings for the error type and message components,
  and they will have normal severity.  They can also be initialized
  by calling the Initialize procedure.  The condition that results
  from calling Initialize represents successful completion.

  Objects of the Condition type are relatively large; where space and
  time considerations are important, they should be passed with in
  out mode so that copies are not made when subprograms are called.
  @node !Tools.Simple_Status.Condition_Class

  type Condition_Class is (Normal, Warning, Problem, Fatal);

  Defines the class of error condition (if any) that resulted from an
  operation.

  The class of an error condition is part of its condition name.

  Fatal

  Indicates that the operation did not complete and proceeding is
  dangerous.

  Normal

  Indicates that the operation completed normally.

  Problem

  Indicates that the operation did not complete and it is safe to
  proceed.

  Warning

  Indicates that the operation completed and it is safe to proceed,
  but something unexpected happened.
  @node !Tools.Simple_Status.Condition_Name

  type Condition_Name is private;

  Defines the name of an error condition.

  The name of a condition consists of its type (a string limited to
  63 characters) and its severity level (of Condition_Class type).
  @node !Tools.Simple_Status.Create_Condition

  procedure Create_Condition (Status     : in out Condition;
                             Error_Type :        String;
                             Message    :        String          := "";
                             Severity   :        Condition_Class := Problem);
  procedure Create_Condition (Status     : in out Condition;
                             Error_Type :        Condition_Name;
                             Message    :        String          := "");

  Creates a condition of the indicated type and severity, with the
  message supplied, and returns it in the Status parameter.
  @node !Tools.Simple_Status.Create_Condition_Name

  function Create_Condition_Name (Error_Type : String;
                                 Severity   : Condition_Class := Problem)
                                                    return Condition_Name;

  Creates a condition name of the indicated type and severity.
  @node !Tools.Simple_Status.Display_Message

  function Display_Message (Status : Condition) return String;

  Returns the condition name and message of the indicated condition.

  Typically, this function is used when composing error messages for
  presentation to users.  The string that is returned is text that
  describes the result of an operation and the causes of errors.

  Note that the Log.Put_Condition procedure (SJM) can be used
  to display the same information in logging format to the
  Current_Output window or file.
  @node !Tools.Simple_Status.Equal

  function Equal (Status     : Condition;
                 Error_Type : String) return Boolean;
  function Equal (Status     : Condition;
                 Error_Type : Condition_Name) return Boolean;
  function Equal (Status     : Condition_Name;
                 Error_Type : String) return Boolean;
  function Equal (Status     : Condition_Name;
                 Error_Type : Condition_Name) return Boolean;

  Determines whether the type of error of the condition supplied by
  the Status parameter is the same as the error type supplied by the
  Error_Type parameter.

  The comparison is based on a case-sensitive character string
  comparison.  The severity level does not participate in the
  comparison.
  @node !Tools.Simple_Status.Error

  function Error (Error_Type : Condition_Name;
                 Level      : Condition_Class := Warning) return Boolean;
  function Error (Status : Condition;
                 Level  : Condition_Class := Warning) return Boolean;

  Determines whether the severity level of the indicated condition is
  worse than the indicated level.

  Typically, the Error function is used to determine whether an
  operation that returns a condition completed successfully.  If the
  operation failed, a call to the Error function with the condition
  resulting from the failed operation will return the value true.  If
  the operation did not complete successfully, the Display_Message
  function or the Log.Put_Condition procedure (SJM) can be used to
  determine the cause of the error.

  The levels of severity are normal (lowest), warning, problem, and
  fatal (highest).
  @node !Tools.Simple_Status.Error_Type

  function Error_Type (Status : Condition) return Condition_Name;

  Returns the name of the indicated condition.

  @node !Tools.Simple_Status.Initialize

  procedure Initialize (Status : in out Condition);

  Sets the severity level of the indicated condition to normal.

  The normal value represents a successful completion.  The condition
  name and message fields will be set to the null string.
  @node !Tools.Simple_Status.Message

  function Message (Status : Condition) return String;

  Returns the message of the indicated condition.
  @node !Tools.Simple_Status.Name

  function Name (Error_Type : Condition_Name) return String;
  function Name (Status : Condition) return String;

  Returns the type of error condition for the indicated condition.
  @node !Tools.Simple_Status.Severity

  function Severity (Error_Type : Condition_Name) return Condition_Class;
  function Severity (Status : Condition) return Condition_Class;

  Returns the severity of the indicated condition.
  @node !Tools.Stack_Generic

  Generic package Stack_Generic provides a means of creating and
  manipulating abstract stacks of elements.  This generic allows
  stacks of arbitrary size.  There are operations for creating
  stacks, pushing and popping elements on and off stacks, and
  iterating over the elements in stacks.

  If an attempt is made to pop or read an element off an empty stack,
  the Underflow exception (in this package) is raised.

  The formal parameter to the generic is:
  generic
      type Element is private;
  package Stack_Generic is
      ...
  end Stack_Generic;
          This parameter defines the kinds of elements that are kept
  in stacks.
  @node !Tools.Stack_Generic.Copy

  procedure Copy (Target : in out Stack;
                 Source :        Stack);

  Removes any elements in the target, initializing it if necessary,
  and then copies the elements in the source into it.
  @node !Tools.Stack_Generic.Done

  function Done  (Iter : Iterator) return Boolean;

  Determines whether the iterator has cycled through all of the
  elements in a stack.
  @node !Tools.Stack_Generic.Element

  type Element is private;

  Defines the type of elements in stacks.

  The actual supplied for this type cannot be unconstrained.
  @node !Tools.Stack_Generic.Empty

  function Empty (S : Stack) return Boolean;

  Determines whether there are any elements in the stack.
  @node !Tools.Stack_Generic.Empty_Stack

  Empty_Stack : constant Stack;

  Defines an empty stack containing no elements.
  @node !Tools.Stack_Generic.Init

  procedure Init (Iter : out Iterator;
                 S    :     Stack);

  Initializes the iterator to iterate over the elements in the
  specified stack.

  When one or more elements exist in the stack, the Value function
  returns the first element in the list using this value of the
  iterator.  Successive values can be accessed by advancing the
  iterator to the next value using the Next procedure.  When no
  elements exist in the stack, the Done function returns the value
  true using this value of the iterator.
  @node !Tools.Stack_Generic.Iterator

  type Iterator is private;

  Defines a type that allows iterating over all elements in a list.

  Objects of this type can contain all of the information necessary
  to step over all of the elements in a list.  The type is used with
  the Init and Next procedures and the Value and Done functions.
  @node !Tools.Stack_Generic.Make_Empty

  procedure Make_Empty (S : in out Stack);

  Removes all of the elements in the stack and sets it to the value
  of the Empty_Stack constant.
  @node !Tools.Stack_Generic.Next

  procedure Next (Iter : in out Iterator);

  Advances the iterator to point to the next element in the stack.

  When the iterator steps past the last element, the Done function
  returns the value true.
  @node !Tools.Stack_Generic.Pop

  procedure Pop (S : in out Stack);

  Removes the last item pushed onto the specified stack.
  @node !Tools.Stack_Generic.Push

  procedure Push (X :        Element;
                 S : in out Stack);

  Pushes the specified element onto the top of the specified stack.
  @node !Tools.Stack_Generic.Stack

  type Stack is private;

  Defines the representation of a stack.

  Several important properties of the Stack type are visible through
  the implicit operations of assignment and equality.  Assignment
  for this type has the property that the contents of the stack are
  not copied but a new alias (a new name) for the stack is created.
  Equality for this type has the property that the values of the
  stacks are not compared but the names are compared.  In other
  words, the operation of equality checks to determine whether two
  stack values designate the same stack.
  @node !Tools.Stack_Generic.Top

  function Top (S : Stack) return Element;

  Returns the last element pushed onto the specified stack.
  @node !Tools.Stack_Generic.Underflow

  Underflow : exception;

  Defines an exception raised when an attempt is made to pop or read
  elements from empty stacks.
  @node !Tools.Stack_Generic.Value

  function Value (Iter : Iterator) return Element;

  Returns the element pointed to by the iterator.
  @node !Lrm.Standard
  package Standard is
      type Boolean is (False, True);
      for Boolean'Size use 1;
      type Integer       is range -2**31-1 .. 2**31-1;
      type Long_Integer  is range (-2**62 - 2**62) .. (2**62 - 1 + 2**62);
                              --       -2**63 .. 2**63-1
      type Float is digits 15 range (2.0**1023) - (2.0**97) + (2.0**1023)..
                                - ((2.0**1023) - (2.0**97) + (2.0**1023));
                                 --  -1.7977E308 .. 1.7977E308;
      type Character is (Nul, ..., Del);
      for Character use (0, ..., 127);
      for Character'Size use 8;
      package Ascii is ... end Ascii;
      subtype Natural  is Integer range 0 .. Integer'Last;
      subtype Positive is Integer range 1 .. Integer'Last;
      type String is array (Positive range <>) of Character;
      type Duration is delta 2.0**(-15)
                        -- -3.051757812500E-05
                      range -(2.0**32) .. (2.0**32) - (2.0**(-15));
                        -- -4.294967296000E+09 .. 4.294967296000E+09
      Constraint_Error : exception;
      Numeric_Error    : exception;
      Program_Error    : exception;
      Storage_Error    : exception;
      Tasking_Error    : exception;
  end Standard;

  Ada requires a package called Standard that defines all predefined
  identifiers in the language.  The Ada Language Reference Manual
  contains its general description in Section 8.6, "The Package
  Standard."  The specification for package Standard for the
  Rational architecture is given in this section.
  @node !Lrm.System

  package System is
      type Address is private;
      Null_Address : constant Address;
      type Name    is (R1000);
      System_Name  : constant Name := R1000;
      Bit          : constant :=    1;
      Storage_Unit : constant :=    1 * Bit;
      Word_Size    : constant :=  128 * Bit;
      Byte_Size    : constant :=    8 * Bit;
      Megabyte     : constant := (2 ** 20) * Byte_Size;
      Memory_Size  : constant := 32 * Megabyte;
      -- System-Dependent Named Numbers
      Min_Int      : constant := Long_Integer'Pos (Long_Integer'First);
      Max_Int      : constant := Long_Integer'Pos (Long_Integer'Last);
      Max_Digits   : constant := 15;
      Max_Mantissa : constant := 63;
      Fine_Delta   : constant := 1.0 / (2.0 ** 63);
      Tick         : constant := 200.0E-9;
      subtype Priority is Integer range 0 .. 5;
      type Byte is new Natural range 0 .. 255;
      type Byte_String is array (Natural range <>) of Byte;
      -- Basic units of transmission/reception to/from IO devices.
      -- The following exceptions are raised by Unchecked_Conversion or
         Unchecked_Conversions
      Type_Error       : exception;
      Capability_Error : exception;
      Assertion_Error  : exception;
  end System;

  Ada requires a predefined library package called System that
  includes the definitions of certain configuration-dependent
  characteristics.  The Ada Language Reference Manual contains the
  general specification in Section 13.7, "The Package System."
  The Rational Environment implementation specification of package
  System is given in this section.

  Other declarations defined in package System are reserved for
  internal use and are not documented.  These declarations should not
  be required for users of the Rational Environment.

  This package System is for the R1000.  Other targets have their own
  package System documented with their target-specific information.

  @node !Lrm.System.Address

  type Address is private;

  Defines the type returned by the predefined attribute 'Address.
  @node !Lrm.System.Assertion_Error

  Assertion_Error : exception;

  Defines the exception raised by the Unchecked_Conversion function
  when the object resulting from the conversion has bounds bigger
  than the Target type allows.
  @node !Lrm.System.Bit

  Bit : constant := 1;

  Defines a constant that represents the size of a single bit.
  @node !Lrm.System.Byte

  type Byte is new Natural range 0 .. 255;

  Defines the representation for a byte of data.
  @node !Lrm.System.Byte_Size

  Byte_Size : constant := 8 * Bit;

  Defines the size of a byte.
  @node !Lrm.System.Byte_String

  type Byte_String is array (Natural range <>) of Byte;

  Defines a type that represents a string of bytes.  This type is
  used in some I/O packages to represent the data going to or from
  terminals or tapes.
  @node !Lrm.System.Capability_Error

  Capability_Error : exception;

  Defines the exception raised by the Unchecked_Conversion function
  when the conversion fails.
  @node !Lrm.System.Fine_Delta

  Fine_Delta : constant := 1.0 / (2.0 ** 63);

  Defines the smallest delta allowed in a fixed-point constraint that
  has the range constraint -1.0 ..  1.0.

  This constant is of Universal_Real type.
  @node !Lrm.System.Max_Digits

  Max_Digits : constant := 15;

  Defines the largest value allowed for the number of significant
  decimal digits in a floating-point constraint.

  This constant is of Universal_Integer type.
  @node !Lrm.System.Max_Int

  Max_Int : constant := Long_Integer'Pos (Long_Integer'Last);

  Defines the largest (most positive) value of all predefined integer
  types.

  This constant is of Universal_Integer type.
  @node !Lrm.System.Max_Mantissa

  Max_Mantissa : constant := 63;

  Defines the largest possible number of binary digits in the
  mantissa of model numbers of a fixed-point subtype.

  This constant is of Universal_Integer type.
  @node !Lrm.System.Megabyte

  Megabyte : constant := (2 ** 20) * Byte_Size;

  Defines a constant for the number 1,048,576.

  This constant is of Universal_Integer type.
  @node !Lrm.System.Memory_Size

  Memory_Size : constant := 32 * Megabyte;

  Defines the number of available storage units in the configuration.

  This constant is of Universal_Integer type.
  @node !Lrm.System.Min_Int

  Min_Int : constant := Long_Integer'Pos (Long_Integer'First);

  Defines the smallest (most negative) value of all predefined
  integer types.

  This constant is of Universal_Integer type.
  @node !Lrm.System.Name

  type Name is (R1000);

  Defines values of alternative machine configurations handled by
  the Environment.
  @node !Lrm.System.Null_Address

  Null_Address : constant Address;

  Defines a null value of type Address.
  @node !Lrm.System.Priority

  subtype Priority is Integer range 0 .. 5;

  Defines the range of task priorities available for a task within a
  job.

  Task priorities are assigned according to the rules of the Ada
  Language Reference Manual.  These priorities differ from job
  priorities, which are managed by procedures in SJM, package Job.
  @node !Lrm.System.Storage_Unit

  Storage_Unit : constant := 1 * Bit;

  Defines the number of bits per storage unit.

  This constant is of Universal_Integer type.
  @node !Lrm.System.System_Name

  System_Name  : constant Name := R1000;

  Defines the value of the default system name.
  @node !Lrm.System.Tick

  Tick : constant := 200.0E-9;

  Defines the basic clock period, in seconds (that is, 200
  nanoseconds).

  This constant is of Universal_Real type.
  @node !Lrm.System.Type_Error

  Type_Error : exception;

  Defines the exception raised by the Unchecked_Conversion function
  when the underlying architectural types used to represent the
  Source and Target types are not the same, even though the types are
  compatible in an Ada sense.
  @node !Lrm.System.Word_Size

  Word_Size : constant := 128 * Bit;

  Defines the size of addressed words in the system.
  @node !Tools.Table_Sort_Generic

  The Table_Sort_Generic generic procedure provides a table sorting
  capability.  The formal parameters to the generic include the table
  of elements to be sorted, the element type, the size of the table,
  and a comparison function that defines the ordering of the elements
  in the table.  The generic procedure takes an unsorted table of the
  size and type defined by those parameters and returns the sorted
  table.

  The formal parameters to the generic are:
  generic
    type Element is private;
    type Index is (<>);
    type Element_Array is array (Index range <>) of Element;
    with function "<" (Left  : Element;
                      Right : Element) return Boolean is <>;
  procedure Table_Sort_Generic (Table : in out Element_Array);

  @node !Tools.Table_Sort_Generic."<"

  with function "<" (Left  : Element;
                    Right : Element) return Boolean is <>;

  Defines the function that is to be used to order the elements in
  the table.

  The comparison must meet the following condition:  if A is less
  than B, then B is not less than A. This ensures that if A and B
  are transposed during a pass of the sort, they won't be transposed
  again in a subsequent pass.
  @node !Tools.Table_Sort_Generic.Element

  type Element is private;

  Defines the types of elements in the table.
  @node !Tools.Table_Sort_Generic.Element_Array

  type Element_Array is array (Index range <>) of Element;

  Defines the type of table to be sorted.
  @node !Tools.Table_Sort_Generic.Index

  type Index is (<>);

  Defines the index of the table.
  @node !Tools.Table_Sort_Generic.Table_Sort_Generic

  procedure Table_Sort_Generic (Table : in out Element_Array);

  Sorts the specified table according to the actual parameters of the
  generic.

  This generic procedure sorts the table.  The sorting algorithm
  is defined by the generic actual parameters to the generic.  The
  internal method for sorting is a Shell sort.
  @node !Tools.Time_Utilities

  Package Time_Utilities contains a number of utilities for
  manipulating times and dates.  Package Calendar contains one
  representation for time and subprograms for manipulating time.
  Package Time_Utilities contains two important type definitions
  for alternative representations for time and subprograms for
  manipulating these alternatives.  These are Time type and Interval
  type.

  The package contains:

  o Operations to convert from one representation to another.

  o Image and value operations to convert time to strings and back.

  o Operations to find the current time in these alternate
    representations.

  o Constants and types that represent units of time such as minutes,
    hours, seconds, months, and years.

  Unless otherwise specified, the Constraint_Error exception is
  raised if illegal values are passed to any of the operations in
  this package.
  @node !Tools.Time_Utilities."+"

  function "+" (D : Weekday;
               I : Integer) return Weekday;

  Computes the weekday that it will be after the specified number of
  days have elapsed from the specified weekday.
  @node !Tools.Time_Utilities."--"

  function "-" (D : Weekday;
               I : Integer) return Weekday;

  Computes the weekday that it will be after the specified number of
  days are subtracted from the specified weekday.
  @node !Tools.Time_Utilities.Convert

  function Convert (I : Interval) return Duration;
  function Convert (D : Duration) return Interval;

  Converts the duration to an interval or back.
  @node !Tools.Time_Utilities.Convert_Time

  function Convert_Time (Date : Calendar.Time) return Time;
  function Convert_Time (Date : Time) return Calendar.Time;

  Converts the time format.

  This function converts the time format to or from the time format
  used in package Calendar.
  @node !Tools.Time_Utilities.Date_Format

  type Date_Format is (Expanded, Month_Day_Year, Day_Month_Year,
                                                      Year_Month_Day, Ada);

  Defines the set of styles the image of the date can have.

  The Image function returns a string that can contain the image of
  a specified date.  A parameter of this type is used to specify the
  style in which the image of the date is created.

  Ada

  Creates an image of the following style:  83_09_29

  Day_Month_Year

  Creates an image of the following style:  29-SEP-83

  Expanded

  Creates an image of the following style:  September 29, 1983

  Month_Day_Year

  Creates an image of the following style:  09/29/83

  Year_Month_Day

  Creates an image of the following style:  83/09/29
  @node !Tools.Time_Utilities.Day

  Day : constant Duration := 86_400.0;

  Defines a constant duration that represents the number of seconds
  in a day.
  @node !Tools.Time_Utilities.Day_Count

  type Day_Count is new Integer range 0 .. Integer'Last;

  Defines a type that represents the number of days.
  @node !Tools.Time_Utilities.Day_Of_Week

  function Day_Of_Week (T : Calendar.Time) return Weekday;
  function Day_Of_Week (T : Time := Time_Utilities.Get_Time) return Weekday;

  Returns the day of the week corresponding to the indicated time.
  @node !Tools.Time_Utilities.Days

  type Days is new Calendar.Day_Number;

  Defines a type that represents the set of days in a month.
  @node !Tools.Time_Utilities.Duration_Until

  function Duration_Until (T : Time) return Duration;
  function Duration_Until (T : Calendar.Time) return Duration;

  Returns the duration from the current time to the indicated time.
  @node !Tools.Time_Utilities.Duration_Until_Next

  function Duration_Until_Next (H : Military_Hours;
                               M : Minutes         := 0;
                               S : Seconds         := 0) return Duration;

  Returns the duration from the current time to the next time with
  the indicated hour, minute, and second values.
  @node !Tools.Time_Utilities.Get_Time

  function Get_Time return Time;

  Returns the current time.

  This function is similar to the Calendar.Clock function, but this
  function returns the time in a different format.
  @node !Tools.Time_Utilities.Hour

  Hour : constant Duration := 3600.0;

  Defines a constant duration that represents the number of seconds
  in an hour.
  @node !Tools.Time_Utilities.Hours

  type Hours is new Integer range 1 .. 12;

  Defines a type that represents the number of hours in the A.M. or
  the P.M.
  @node !Tools.Time_Utilities.Image

  function Image (Date       : Time;
                 Date_Style : Date_Format    := Time_Utilities.Expanded;
                 Time_Style : Time_Format    := Time_Utilities.Expanded;
                 Contents   : Image_Contents := Time_Utilities.Both
                                                           return String;
  function Image (I : Interval) return String;
  function Image (D : Duration) return String;
  function Image (D : Weekday) return String;

  Returns the image of the specified time, interval, duration, or
  weekday.

  This function creates a string that represents the specified time.
  This time can be specified as a value of Time type, Duration type,
  Interval type, or Weekday type.  The first version of the function
  allows specifying style and content of the string.
  @node !Tools.Time_Utilities.Image_Contents

  type Image_Contents is (Both, Time_Only, Date_Only);

  Defines the set of combinations of time and date that can be
  produced by the Image function.

  The Image function returns a string that can contain the image of
  a date, the image of a time, or both.  A parameter of this type
  specifies which combination is created.

  Both

  Creates an image that combines both time and date.  When the time
  and date format is expanded, the combination looks like this:
  11:44:55 PM September 29, 1983.  When the time and date format is
  Ada, the combination looks like this:  83_09_29_23_44_55.  All
  combinations of time and date formats are allowed.
  Date_Only

  Creates an image that contains only the date and whose format is
  governed only by the date format.

  Time_Only

  Creates an image that contains only the time and whose format is
  governed only by the time format.
  @node !Tools.Time_Utilities.Interval

  type Interval is
      record
          Elapsed_Days         : Day_Count;
          Elapsed_Hours        : Military_Hours;
          Elapsed_Minutes      : Minutes;
          Elapsed_Seconds      : Seconds;
          Elapsed_Milliseconds : Milliseconds;
      end record;

  Defines a segmented version of the Duration type.
  @node !Tools.Time_Utilities.Is_Nil

  function Is_Nil (Date : Time) return Boolean;
  function Is_Nil (Date : Calendar.Time) return Boolean;

  Checks whether the specified time is nil.
  @node !Tools.Time_Utilities.Military_Hours

  type Military_Hours is new Integer range 0 .. 23;

  Defines a type that represents the number of hours in a day.
  @node !Tools.Time_Utilities.Milliseconds

  type Milliseconds is new Integer range 0 .. 999;

  Defines a type that represents the number of milliseconds in a
  second.
  @node !Tools.Time_Utilities.Minute

  Minute : constant Duration := 60.0;

  Defines a constant duration that represents the number of seconds
  in a minute.
  @node !Tools.Time_Utilities.Minutes

  type Minutes is new Integer range 0 .. 59;

  Defines a type that represents the number of minutes in an hour.
  @node !Tools.Time_Utilities.Months

  type Months is (January, February, March, April, May, June, July, August,
                                   September, October, November, December);

  Defines an enumeration that represents the twelve months of the
  year.
  @node !Tools.Time_Utilities.Nil

  function Nil return Time;
  function Nil return Calendar.Time;

  Returns a nil time.
  @node !Tools.Time_Utilities.Seconds

  type Seconds is new Integer range 0 .. 59;

  Defines a type that represents the number of seconds in a minute.
  @node !Tools.Time_Utilities.Sun_Positions

  type Sun_Positions is (Am, Pm);

  Defines an enumeration that represents the two halves of a day.
  @node !Tools.Time_Utilities.Time

  type Time is
      record
          Year         : Years;
          Month        : Months;
          Day          : Days;
          Hour         : Hours;
          Minute       : Minutes;
          Second       : Seconds;
          Sun_Position : Sun_Positions;
      end record;

  Defines a representation for the time.

  This representation differs from the one used to represent time in
  package Calendar.  Package Calendar represents time as the year,
  month, day, and seconds in the day.  It represents time in subtypes
  of integers and duration.

  This subtype represents time as the year, month, day, hour, minute,
  second, and sun position.  It uses enumerations for months and sun
  positions.
  @node !Tools.Time_Utilities.Time_Format

  type Time_Format is (Expanded, Military, Short, Ada);

  Defines the set of styles the image of the time can have.

  The Image function returns a string that can contain the image of
  a specified time.  A parameter of this type is used to specify the
  style in which the image of the time is created.

  Ada

  Creates an image of the following style:  23_44_55

  Expanded

  Creates an image of the following style:  11:44:55 PM

  Military

  Creates an image of the following style:  23:44:55

  Short

  Creates an image of the following style:  23:44
  @node !Tools.Time_Utilities.Value

  function Value (S : String) return Time;
  function Value (S : String) return Interval;

  Converts the string representation of the time into either a time
  or an interval.

  This function takes a string and converts its contents into either
  a time or an interval.  The string has the same allowed formats
  as the resulting string of the Image function.  Input that does
  not include all fields is assumed to be the current time; that is,
  10:30 is assumed to be 10:30:00 A.M. today.
  @node !Tools.Time_Utilities.Weekday

  type Weekday is new Positive range 1 .. 7;

  Defines a representation for weekdays (Monday is 1).
  @node !Tools.Time_Utilities.Years

  type Years is new Calendar.Year_Number;

  Defines a type that represents the set of years.
  @node !Lrm.Unchecked_Conversion

  The Unchecked_Conversion generic function converts objects of one
  type to objects of another type.

  Its formal parameter list is:
  generic
    type Source is limited private;
    type Target is limited private;
  function Unchecked_Conversion (S : Source) return Target;

  The Source type is the type of the source object bit pattern to be
  converted to the Target type.

  The Target type cannot be an access or task type or contain access
  or task types as any of its components.  If these conditions are
  not met, the System.Capability_Er-ror exception is raised when the
  conversion procedure is called.

  A faster, package version of the Unchecked_Conversion function can
  be found in package Unchecked_Conversions.  Note that, although
  the package version is faster, it will consume more space in the
  executing program.
  @node !Lrm.Unchecked_Conversion.Source

  type Source is limited private;

  Defines the type of object whose bits are to be converted to the
  Target type.

  When the Unchecked_Conversion function is instantiated and then
  used, the actual types of the source values passed to it and the
  actual types of the target value returned typically should be
  the same as those used in the instantiation.  Specifically, there
  should be no differences because of subtypes, derived types, type
  conversions, constants, aggregates, and so on.  These guidelines
  can be relaxed if the Source and Target types are scalars, but they
  must be followed if the Source or Target types have discriminants
  or components that have discriminants.

  If there are type mismatch problems, the System.Type_Error
  exception will be raised when the Unchecked_Conversion function
  is called because the underlying architectural types used to
  represent the Source and the Target types are not the same, even
  though the types are compatible in an Ada sense.  Typically this
  error can be avoided by changing the instantiation to use the
  actual types required when the conversion is performed.
  @node !Lrm.Unchecked_Conversion.Target

  type Target is limited private;

  Defines the type of object to which the bits of the Source type are
  to be converted.

  The Target type cannot be an access or task type or contain access
  or task types as any of its components.  If these conditions are
  not met, the System.Capability_Error exception is raised when the
  instantiation is elaborated---specifically, when the conversion
  procedure is called.

  When the Unchecked_Conversion function is instantiated and then
  used, the actual types of the source values passed to it and the
  actual types of the target value returned typically should be
  the same as those used in the instantiation.  Specifically, there
  should be no differences because of subtypes, derived types, type
  conversions, constants, aggregates, and so on.  These guidelines
  can be relaxed if the Source and Target types are scalars, but they
  must be followed if the Source or Target types have discriminants
  or components that have discriminants.

  If there are type mismatch problems, the System.Type_Error
  exception will be raised when the Unchecked_Conversion function
  is called because the underlying architectural types used to
  represent the Source and the Target types are not the same, even
  though the types are compatible in an Ada sense.  Typically this
  error can be avoided by changing the instantiation to use the
  actual types required when the conversion is performed.
  @node !Lrm.Unchecked_Conversion.Unchecked_Conversion

  function Unchecked_Conversion (S : Source) return Target;

  Returns the bit pattern for the source as an object of the Target
  type.

  The type of the target cannot be an access or task type or contain
  access or task types as any of its components.  If these conditions
  are not met, the System.Capability_Error exception is raised
  when the instantiation is elaborated---specifically, when the
  conversion procedure is called.

  The binary representations of the source and target are left-
  justified.  Thus, the leftmost bit of the source object becomes
  the leftmost bit of the target object.  If Target'Size is greater
  than Source'Size, the target object contains undefined bits in
  the locations not filled by the source.  In most cases, this is
  undesirable.

  If Target'Size is less than Source'Size, the rightmost bits of the
  source are ignored.

  The bits of the source are used from left to right.  In some
  cases, some of the bits will be information on array bounds,
  discriminants, or the like.  For example, if a structured constant
  is passed as a target to the Unchecked_Conversion function, the
  constant may contain such information, whereas a variable of the
  Source type may not.  These extra bits thus would give an undesired
  result or might raise exceptions.

  When the Unchecked_Conversion function is instantiated and then
  used, the actual types of the values passed to it and the actual
  types of the target value returned typically should be the same as
  those used in the instantiation.  Specifically, there should be no
  differences because of subtypes, derived types, type conversions,
  constants, aggregates, and so on.  These guidelines can be relaxed
  if the Source and Target types are scalars, but they must be
  followed if the Source or Target types have discriminants or
  components that have discriminants.

  If there are type mismatch problems, the System.Type_Error
  exception will be raised when the Unchecked_Conversion function
  is called because the underlying architectural types used to
  represent the Source and the Target types are not the same, even
  though the types are compatible in an Ada sense.  Typically this
  error can be avoided by changing the instantiation to use the
  actual types required when the conversion is performed.

  The following are examples of simple conversions in which the
  number of bits in the Source and Target types is the same:

  o Long_Integer to a record with two Integer fields

  o Float to a Long_Integer

  o Integer to an array of 32 Booleans

  o Record to another record of equal size
  @node !Tools.Unchecked_Conversions

  Package Unchecked_Conversions provides functions for converting
  objects of one type to objects of another type.  It includes
  generic package Unchecked_Conversion_Package, which is
  functionally equivalent to the Unchecked_Conversion function, but
  it is faster and it provides functions for converting to and from
  byte strings.  Note that, although this package provides faster
  conversion operations, it will consume more space in the executing
  program.

  The following examples illustrate uses of the operations in this
  package and highlight some of the common errors that can occur.

  The following example illustrates some of the common errors that
  can occur when performing unchecked conversions.
  with Io;
  with System;
  with Unchecked_Conversions;
  procedure Conversions_Errors is
      type S1_Type is range 1 .. 10;  -- 4-bit container
      type T1_Type is range 1 .. 9;   -- 4-bit container
      S1 : S1_Type := 10;
      T1 : T1_Type;
      package Convert1 is new Unchecked_Conversions.Unchecked_Conversion_Package
                                (S1_Type, T1_Type);
      type S2_Type is array (1 .. 64) of Boolean;  -- 64-bit container
      type T2_Type is array (Integer range <>) of  -- 128-bit container
                        Long_Integer;            -- because of additional
                                                 -- bounds information
      S2 : S2_Type := (others => True);
      T2 : T2_Type (1 .. 1);
      package Convert2 is new Unchecked_Conversions.Unchecked_Conversion_Package
                                (S2_Type, T2_Type);
      type Vstring (Max_Length : Positive) is
          record
             Length : Positive;
             Contents : String (1 .. Max_Length);
          end record;
      subtype V20 is Vstring (20);  -- a constrained subtype
      S3 : V20;
      function Convert_To_Bytes is
         new Unchecked_Conversions.Convert_To_Byte_String (V20);
      function Convert_From_Bytes is
         new Unchecked_Conversions.Convert_From_Byte_String (Vstring);
      -- note that different actual types were used in the instantiations

  begin
      begin
          T1 := Convert1.Convert (S1);
      exception
          when Constraint_Error =>
             Io.Put_Line ("First conversion raised Contraint_Error");
      end;
      -- this conversion will raise Constraint_Error because the result
      -- of the conversion does not meet the constraints of the Target type
      begin
          T2 := Convert2.Convert (S2);
      exception
          when System.Assertion_Error =>
             Io.Put_Line ("Second conversion raised Assertion_Error");
      end;
      -- this conversion will raise Assertion_Error because the object
      -- resulting from the conversion has bounds bigger than the Target
      -- type allows; in this example, it results from putting all 1's
      -- into the bounds information field of an object of an unconstrained
      -- type
      S3.Length := 15;
      S3.Contents (1 .. 15) := (others => ' ');
      declare
          T3 : constant System.Byte_String := Convert_To_Bytes (S3);
      begin
          S3 := Convert_From_Bytes (T3);
      exception
          when System.Type_Error =>
             Io.Put_Line ("Third conversion raised Type_Error");
      end;
      -- this conversion will raise the Type_Error exception because the
      -- underlying architectural types used to represent the object S3 and
      -- the Vstring type are not the same
  end Conversions_Errors;
  @node !Tools.Unchecked_Conversions.Unchecked_Conversion_Package

  Generic package Unchecked_Conversion_Package provides a
  function for converting objects of one type to objects of
  another type.  This function is functionally equivalent to the
  Unchecked_Conversion function, but it is faster.

  Its formal parameter list is:
  generic
      type Source is limited private;
      type Target is limited private;
  package Unchecked_Conversion_Package is
      function Convert (S : Source) return Target;
  end Unchecked_Conversion_Package;

  The Source type is the type of the source object bit pattern to be
  converted to the Target type.

  The Target type cannot be an access or task type or contain access
  or task types as any of its components.  If these conditions are
  not met, the System.Capability_Error exception is raised when the
  instantiation is elaborated.
  @node !Tools.Unchecked_Conversions.Unchecked_Conversion_Package.Convert

  function Convert (S : Source) return Target;

  Returns the bit pattern for the source as an object of the Target
  type.

  The type of the target cannot be an access or task type or contain
  access or task types as any of its components.  If these conditions
  are not met, the System.Capability_Error exception is raised when
  the instantiation of Unchecked_Conversion_Package is elaborated.

  The binary representations of the source and target are left-
  justified.  Thus, the leftmost bit of the source object becomes
  the leftmost bit of the target object.  If Target'Size is greater
  than Source'Size, the target object contains undefined bits in
  the locations not filled by the source.  In most cases, this is
  undesirable.

  If Target'Size is less than Source'Size, the rightmost bits of the
  source are ignored.

  The bits of the source are used from left to right.  In some
  cases, some of the bits will be information on array bounds,
  discriminants, or the like.  For example, if a structured constant
  is passed as a target to the Convert function, the constant may
  contain such information, whereas a variable of the Source type may
  not.  These extra bits thus would give an undesired result or might
  raise exceptions.

  When package Unchecked_Conversion_Package is instantiated and
  then used, the actual types of the values passed to it and the
  actual types of the target value returned typically should be
  the same as those used in the instantiation.  Specifically, there
  should be no differences because of subtypes, derived types, type
  conversions, constants, aggregates, and so on.  These guidelines
  can be relaxed if the Source and Target types are scalars, but they
  must be followed if the Source or Target types have discriminants
  or components that have discriminants.

  If there are type mismatch problems, the System.Type_Error
  exception will be raised when the Convert function is called
  because the underlying architectural types used to represent the
  Source and the Target types are not the same, even though the
  types are compatible in an Ada sense.  Typically this error can
  be avoided by changing the instantiation to use the actual types
  required when the conversion is performed.

  The following are examples of simple conversions in which the
  number of bits in the Source and Target types is the same:

  o Long_Integer to a record with two Integer fields

  o Float to a Long_Integer

  o Integer to an array of 32 Booleans

  o Record to another record of equal size
  @node !Tools.Unchecked_Conversions.Unchecked_Conversion_Package.Source

  type Source is limited private;

  Defines the type of object whose bits are to be converted to the
  Target type.

  When package Unchecked_Conversion_Package is instantiated and
  then used, the actual types of the source values passed to the
  Convert function and the actual types of the target value returned
  typically should be the same as those used in the instantiation.
  Specifically, there should be no differences because of subtypes,
  derived types, type conversions, constants, aggregates, and so on.
  These guidelines can be relaxed if the Source and Target types are
  scalars, but they must be followed if the Source or Target types
  have discriminants or components that have discriminants.

  If there are type mismatch problems, the System.Type_Error
  exception will be raised when the Convert function is called
  because the underlying architectural types used to represent the
  Source and the Target types are not the same, even though the types
  are compatible in an Ada sense.  This error usually can be avoided
  by changing the instantiation to use the actual types required when
  the conversion is performed.
  @node !Tools.Unchecked_Conversions.Unchecked_Conversion_Package.Target

  type Target is limited private;

  Defines the type of object to which the bits of the Source type are
  to be converted.

  The type of the target cannot be an access or task type or contain
  access or task types as any of its components.  If these conditions
  are not met, the System.Capability_Error exception is raised when
  the instantiation of package Unchecked_Conversion_Package is
  elaborated.

  When package Unchecked_Conversion_Package is instantiated and then
  the Convert function is used, the actual types of the source values
  passed to it and the actual types of the target value returned
  typically should be the same as those used in the instantiation.
  Specifically, there should be no differences because of subtypes,
  derived types, type conversions, constants, aggregates, and so on.
  These guidelines can be relaxed if the Source and Target types are
  scalars, but they must be followed if the Source or Target types
  have discriminants or components that have discriminants.

  If there are type mismatch problems, the System.Type_Error
  exception will be raised when the Convert function is called
  because the underlying architectural types used to represent the
  Source and the Target types are not the same, even though the types
  are compatible in an Ada sense.  This error usually can be avoided
  by changing the instantiation to use the actual types required when
  the conversion is performed.

  The Convert_From_Byte_String generic function converts byte
  strings to objects of a given type.

  Its formal parameter list is:
  generic
      type Target is limited private;
  function Convert_From_Byte_String (S : System.Byte_String) return Target;

  The Target type is the type to which the target object bit pattern
  is to be converted.
  @node !Tools.Unchecked_Conversions.Convert_From_Byte_String

  function Convert_From_Byte_String (S : System.Byte_String) return Target;

  Returns the bit pattern for the byte string as an object of the
  Target type.

  The byte string should have been produced by a call to an
  instantiation of the Convert_To_Byte_String generic function.

  The type of the target cannot be an access or task type or contain
  access or task types as any of its components.  If these conditions
  are not met, the System.Capability_Error exception is raised
  when the instantiation is elaborated---specifically, when the
  conversion function is called.

  The binary representations of the byte string and the target are
  left-justified.  Thus, the leftmost bit of the byte string becomes
  the leftmost bit of the target object.  If Target'Size is greater
  than the length of the byte string, the target object contains
  undefined bits in the locations not filled by the byte string.  In
  most cases, this is undesirable.

  If Target'Size is less than the length of the byte string, the
  rightmost bits of the byte string are ignored.

  The bits of the byte string are used from left to right.  In some
  cases, some of the bits will be information on array bounds,
  discriminants, or the like.  These extra bits must be preserved
  to avoid undesired results or exceptions.

  When the Convert_From_Byte_String function is instantiated and
  then used, the actual types of the values that are first converted
  to byte strings using the Convert_To_Byte_String generic function
  and the actual types of the target value returned typically
  should be the same as those used in the target instantiation.
  Specifically, there should be no differences because of subtypes,
  derived types, type conversions, constants, aggregates, and so
  on.  These guidelines can be relaxed if the original Source and
  Target types are scalars, but they must be followed if the original
  Source or Target types have discriminants or components that have
  discriminants.

  If there are type mismatch problems, the System.Type_Error
  exception will be raised when the Convert_From_Byte_String
  function is called because the underlying architectural types
  used to represent the original source and the Target types are not
  the same, even though the types are compatible in an Ada sense.
  This error usually can be avoided by changing the instantiation to
  use the actual types required when the conversion is performed.
  @node !Tools.Unchecked_Conversions.Target

  type Target is limited private;

  Defines the type of object to which the bits of the byte string are
  to be converted.

  The type of the target cannot be an access or task type or contain
  access or task types as any of its components.  If these conditions
  are not met, the System.Capability_Error exception is raised
  when the instantiation is elaborated---specifically, when the
  conversion function is called.

  When the Convert_To_Byte_String and Convert_From_Byte_String
  functions are instantiated and then used, the actual types of the
  source values passed to Convert_To_Byte_String and the actual
  types of the target value returned from Convert_From_Byte_String
  typically should be the same as those used in the instantiation.
  Specifically, there should be no differences because of subtypes,
  derived types, type conversions, constants, aggregates, and so on.
  These guidelines can be relaxed if the Source and Target types are
  scalars, but they must be followed if the Source or Target types
  have discriminants or components that have discriminants.

  If there are type mismatch problems, the System.Type_Error
  exception will be raised when the Convert_From_Byte_String
  function is called because the underlying architectural types
  used to represent the Source and the Target types are not the same,
  even though the types are compatible in an Ada sense.  This error
  usually can be avoided by changing the instantiation to use the
  actual types required when the conversion is performed.

  The Convert_To_Byte_String generic function converts objects of
  one type to byte strings.

  Its formal parameter list is:
  generic
      type Source is limited private;
  function Convert_To_Byte_String (S : Source) return System.Byte_String;

  The Source type is the type of the source object bit pattern to be
  converted to a byte string.
  @node !Tools.Unchecked_Conversions.Convert_To_Byte_String

  function Convert_To_Byte_String (S : Source) return System.Byte_String;

  Returns the bit pattern for the source as a byte string.

  The byte string can then be converted back using the
  Convert_From_Byte_String function.

  The binary representations of the source and the byte string are
  left-justified.  Thus, the leftmost bit of the source object
  becomes the leftmost bit of the byte string.  The byte string
  length may include additional undefined bits to pad the source
  object bits to a byte boundary.

  The bits of the source are used from left to right.  In some
  cases, some of the bits will be information on array bounds,
  discriminants, or the like.  These extra bits must be preserved
  to avoid undesired results or exceptions.

  When the Convert_To_Byte_String function is instantiated and
  then used, the actual types of the values passed to it and the
  actual types of the target value returned from instantiations
  of Convert_From_Byte_String typically should be the same as
  those used in the source instantiation.  Specifically, there
  should be no differences because of subtypes, derived types, type
  conversions, constants, aggregates, and so on.  These guidelines
  can be relaxed if the Source and Target types are scalars, but they
  must be followed if the Source or Target types have discriminants
  or components that have discriminants.

  If there are type mismatch problems, the System.Type_Error
  exception will be raised when the Convert_From_Byte_String
  function is called because the underlying architectural types
  used to represent the Source and the Target types are not the same,
  even though the types are compatible in an Ada sense.  This error
  usually can be avoided by changing the instantiation to use the
  actual types required when the conversion is performed.
  @node !Tools.Unchecked_Conversions.Source

  type Source is limited private;

  Defines the type of object whose bits are to be converted to a byte
  string.

  When the Convert_To_Byte_String function is instantiated and then
  used, the actual types of the source values passed to it and the
  actual types of the target value returned from instantiations
  of Convert_From_Byte_String typically should be the same as
  those used in the source instantiation.  Specifically, there
  should be no differences because of subtypes, derived types, type
  conversions, constants, aggregates, and so on.  These guidelines
  can be relaxed if the Source and Target types are scalars, but they
  must be followed if the Source or Target types have discriminants
  or components that have discriminants.

  If there are type mismatch problems, the System.Type_Error
  exception will be raised when the Convert_From_Byte_String
  function is called because the underlying architectural types
  used to represent the Source and the Target types are not the same,
  even though the types are compatible in an Ada sense.  This error
  usually can be avoided by changing the instantiation to use the
  actual types required when the conversion is performed.
  @node !Lrm.Unchecked_Deallocation

  The Unchecked_Deallocation generic procedure is used to perform
  unchecked storage deallocation for the designated objects of
  access types.  Unchecked deallocation is allowed only for types
  that are not tasks or do not contain tasks or pointers to tasks as
  any of their components.  The Allows_Deallocation generic function
  can be used to determine whether deallocation can be performed on a
  particular type.

  The formal parameters to the generic procedure are:
  generic
    type Object is limited private;
    type Name   is access Object;
  procedure Unchecked_Deallocation (X : in out Name);

  The Object type is the type of the object for which storage is
  to be reclaimed.  The Name type is an access type that points to
  objects of the Object type.

  For space to be reclaimed, deallocation must be enabled, which
  can be done by using the Enable_Deallocation library switch
  or the Enable_Deallocation (X) pragma, where X is the name of
  the access type for which you want to reclaim storage.  Using
  the library switch enables deallocation for all access types
  (except those for which deallocation is not supported).  Since
  deallocation adds to the space required for each allocated object,
  the switch or the pragma should not be used unless you intend
  to use deallocation.  This switch is provided for users who
  have uploaded code from another type of system and do not want
  to go back and explicitly add the pragma to each of the access
  types in the uploaded code.  If the library switch is enabled,
  and you do not want to use deallocation for an access type, you
  can use the Disable_Deallocation (X) pragma, where X is the
  type for which deallocation should be disabled.  A call to an
  instantiation of Unchecked_Deallocation will have no effect if the
  designated type is or contains a task.  A call to an instantiation
  of Unchecked_Deallocation will perform deallocation only on a type
  that has had deallocation enabled with the pragma or the switch.
  The pragma will enable deallocation only if it is applied to an
  access type (not subtype or derived types).

  Unchecked Deallocation:  R1000

  An access base type can be identified as allowing deallocation
  (with certain restrictions enumerated later).  Each element in a
  collection for such a type contains some overhead to maintain a
  free list of deallocated elements, currently twice the size of a
  pointer (usually 24 bits).  When allocating in such a collection,
  the microcode scans the free list for the first deallocated element
  that is at least as large as the new element (first fit).  If no
  such deallocated element is found, allocation is performed by
  extending the top of the collection as usual.  No coalescing of
  adjacent deallocated elements occurs; however, any space remaining
  after the allocation of a new element that exceeds the space
  required for overhead will be added to the free list.

  At the source level, the Enable_Deallocation pragma is used to
  indicate that a collection will allow deallocation.  As described
  above, the pragma takes the name of an access type as an argument;
  if the type name is that of a derived type, then the effect of the
  pragma is the same as that of the pragma with the argument being
  the parent type.  The designated type of the access type cannot
  contain tasks or segmented heap pointers (or pointers to such
  types).  Any use of unchecked deallocation on an access type to
  which the pragma has not been applied will have no effect on the
  corresponding collection.
  @node !Lrm.Unchecked_Deallocation.Name

  type Name is access Object;

  Defines the pointer to the object on which deallocation will be
  performed.

  Deallocation is allowed only for types that are not tasks or do not
  contain tasks or pointers to tasks as any of their components.
  @node !Lrm.Unchecked_Deallocation.Object

  type Object is limited private;

  Defines the type of object on which deallocation will performed.

  Deallocation is allowed only for types that are not tasks or do not
  contain tasks or pointers to tasks as any of their components.
  @node !Lrm.Unchecked_Deallocation.Unchecked_Deallocation

  procedure Unchecked_Deallocation (X : in out Name);

  Reclaims the storage associated with the object designated by the
  access value X, if possible.

  Deallocation is allowed only for types that are not tasks or do
  not contain tasks or pointers to tasks as any of their components.
  The Allows_Deallocation generic function can be used to determine
  whether deallocation can be performed on a particular type.

  After the storage for X is reclaimed, X is set to null.  If X is
  null before the call to the Unchecked_Deallocation procedure, the
  call has no effect.  If the Name type did not have deallocation
  enabled, this call has no effect other than setting X to null