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

⟦3d2549eb0⟧ TextFile

    Length: 65038 (0xfe0e)
    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« 
        └─⟦1806bb2cf⟧ 
            └─⟦this⟧ 

TextFile


  @node !Tools.Networking.Interchange

  This package defines a collection of types for data interchange.
  Each type has:

  o A local representation dependent on the characteristics of the
    local architecture and compiler

  o A machine-independent interchange representation (as a byte
    sequence)

  This package provides operations for converting between the local
  and interchange representations.  The types provided are analogous
  to types in the Ada predefined language environment (packages
  Standard and Calendar; see the Rational Environment Reference
  Manual, Programming Tools (PT book).  The conversion operations are
  generic on a procedural byte stream, so that they can be used on a
  variety of interchange media (communication channels, tapes, and
  disks).

  The interchange representation does not carry type information.
  Thus, to convert interchanged data back to their local
  representations, their types must be known beforehand.

  The interchange representation largely follows the rules of
  Courier, the Xerox System Integration Standard for remote
  procedure call protocol.  In particular, all interchange values
  are a multiple of two bytes (16 bits) in length.  Values that
  occupy several bytes are represented with their most significant
  byte first.

  The algorithms for conversion to and from the interchange form can
  be extended to any Ada type except access values and task types.
  The rules for forming new type conversion algorithms are:

  o A discrete (integer subtype or enumeration type) is represented
    by its 'Pos, converted to a Short_Integer type.  This
    representation rule is implemented by the generic package
    Operations.Discrete.

  o A vector (one-dimensional array) is represented by its 'Length,
    followed by its elements in index order.  The 'Length is
    represented as a Natural subtype.  This kind of representation
    loses information about the 'First of the vector (as does Ada
    slice assignment).  This representation rule is implemented by
    the generic package Operations.Vector.

  o A record is represented by the sequence of its fields, in
    the order of their declaration.  Inaccessible fields in
    variant records are omitted.  In other words, the interchange
    representation is ordered in the same way as its value would be
    written as an Ada aggregate.
  @node !Tools.Networking.Interchange.Byte

  subtype Byte is Byte_Defs.Byte;

  Defines an eight-bit byte.

  The interchange representation is like a Short_Integer type.
  @node !Tools.Networking.Interchange.Byte_String

  subtype Byte_String is Byte_Defs.Byte_String;

  Defines a string of bytes indexed by Standard.Integer.

  The interchange representation is a byte count (represented as
  an Integer type) followed by the bytes themselves in index order.
  The bytes are packed so that consecutive bytes in the string are
  represented as consecutive bytes in the interchange form.  An
  extra padding byte is added if the string contains an odd number of
  bytes.  This padding makes the entire value a multiple of two bytes
  in length.
  @node !Tools.Networking.Interchange.Constraint_Error

  Constraint_Error : exception;

  Occurs when an interchange conversion procedure encounters an
  out-of-range value.

  This exception is analogous to the Standard.Constraint_Error
  exception.
  @node !Tools.Networking.Interchange.Convert

  function Convert (X : Calendar.Time) return Interchange.Time;
  function Convert (X : Interchange.Time) return Calendar.Time;
  function Convert (X : Standard.Duration) return Interchange.Duration;
  function Convert (X : Interchange.Duration) return Standard.Duration;

  Converts between time representations.
  @node !Tools.Networking.Interchange.Day_Duration

  subtype Day_Duration is Interchange.Duration;

  Defines the interchange analog of Calendar.Day_Duration.
  @node !Tools.Networking.Interchange.Day_Number

  subtype Day_Number is Interchange.Short_Integer range 1 .. 31;

  Defines the interchange analog of Calendar.Day_Number.
  @node !Tools.Networking.Interchange.Duration

  type Duration is
    record
        Seconds     : Interchange.Integer;
        Nanoseconds : Interchange.Nanosecond_Count;
    end record;

  Defines the interchange analog of Standard.Duration.

  The interchange representation is the sequence of the fields in the
  order of their declaration (seconds, nanoseconds).
  @node !Tools.Networking.Interchange.Float

  type Float is new Interchange_Defs.Float;

  Defines the interchange analog of Standard.Float.

  The interchange representation is IEEE single-precision (32-bit)
  floating point.
  @node !Tools.Networking.Interchange.Integer

  type Integer is new Interchange_Defs.Longest_Integer
              range - (2 ** 30) - (2 ** 30) .. (2 ** 30) + ((2 ** 30) - 1);

  Defines the interchange analog of a Standard.Integer.

  The interchange representation is 32 bits, given in two's-
  complement notation.
  @node !Tools.Networking.Interchange.Long_Float

  type Long_Float is new Interchange_Defs.Long_Float;

  Defines the interchange analog of a Standard.Long_Float.

  The interchange representation is IEEE double-precision (64-bit)
  floating point.
  @node !Tools.Networking.Interchange.Long_Integer

  type Long_Integer is new Interchange_Defs.Longest_Integer;

  Defines the interchange analog of Standard.Long_Integer.

  The range of Long_Integer is machine-dependent and so should be
  chosen to be as large as possible.

  The interchange representation is of arbitrary precision.  Thus,
  as many bytes are used as are required to contain the value,
  represented as a Byte_String subtype (a byte count followed by
  the bytes).  Two's-complement notation is used.
  @node !Tools.Networking.Interchange.Long_Natural

  subtype Long_Natural is Long_Integer range 0 .. Long_Integer'Last;

  Defines the interchange analog of Standard.Long_Natural.
  @node !Tools.Networking.Interchange.Long_Positive

  subtype Long_Positive is Long_Integer range 1 .. Long_Integer'Last;

  Defines the interchange analog of Standard.Long_Positive.
  @node !Tools.Networking.Interchange.Month_Number

  subtype Month_Number is Interchange.Short_Integer range 1 .. 12;

  Defines the interchange analog of Calendar.Month_Number.

  @node !Tools.Networking.Interchange.Nanosecond_Count

  subtype Nanosecond_Count is Interchange.Natural range 0 .. 10 ** 9 - 1;

  Defines the set of digits to the right of the decimal point in a
  Duration type.
  @node !Tools.Networking.Interchange.Natural

  subtype Natural is Integer range 0 .. Integer'Last;

  Defines the interchange analog of Standard.Natural.
  @node !Tools.Networking.Interchange.Positive

  subtype Positive is Integer range 1 .. Integer'Last;

  Defines the interchange analog of Standard.Positive.
  @node !Tools.Networking.Interchange.Short_Integer

  type Short_Integer is range - (2 ** 14) - (2 ** 14) .. (2 ** 14) =
                                                          ((2 ** 14) - 1);

  Defines the interchange analog of Standard.Short_Integer.

  The interchange representation is 16 bits, given in two's-
  complement notation.
  @node !Tools.Networking.Interchange.Short_Natural

  subtype Short_Natural is Short_Integer range 0 .. Short_Integer'Last;

  Defines the interchange analog of Standard.Short_Natural.
  @node !Tools.Networking.Interchange.Short_Positive

  subtype Short_Positive is Short_Integer range 1 .. Short_Integer'Last;

  Defines the interchange analog of Standard.Short_Positive.
  @node !Tools.Networking.Interchange.Time

  type Time is
      record
          Year    : Year_Number;
          Month   : Month_Number;
          Day     : Day_Number;
          Seconds : Day_Duration;
      end record;

  Defines the interchange analog of Calendar.Time.

  The interchange representation is the sequence of the field
  values given in the order of their declaration (year, month, day,
  seconds).
  @node !Tools.Networking.Interchange.Year_Number

  subtype Year_Number is Interchange.Short_Integer;

  Defines the interchange analog of Calendar.Year_Number.
  @node !Tools.Networking.Interchange.Discrete

  Given a discrete type, this package provides operations for
  interchanging values of that type.

  The specification of the package is:
      generic
          type Discrete_Type is (<>);
      package Discrete is
          ...
      end Discrete;

  @node !Tools.Networking.Interchange.Discrete.Discrete_Type

  type Discrete_Type is (<>);

  Defines the type to be interchanged.

  The interchange representation of a value of this type is the 'Pos
  of the value converted to a Short_Integer type.
  @node !Tools.Networking.Interchange.Discrete.Get

  procedure Get (From :     Stream_Id;
                Data : out Discrete_Type);

  Converts a value of the Discrete_Type type from its interchange
  representation to its local representation.
  @node !Tools.Networking.Interchange.Discrete.Put

  procedure Put (Into : Stream_Id;
                Data : Discrete_Type);

  Converts a value of the Discrete_Type type from its local
  representation to its interchange representation.
  @node !Tools.Networking.Interchange.Operations

  Given a facility for interchanging bytes, package Operations
  provides a facility for interchanging values of other types.

  For each type, Put and Get operations are defined.  Put converts
  any value to a sequence of bytes; Get reconstructs the original
  value.

  The specification of the package is:
      generic
          type Stream_Id is limited private;
          with procedure Put (Into : Stream_Id;
                             Data : Byte_String) is <>;
          with procedure Get (From : Stream_Id;
                             Data : out Byte_String) is <>;
      package Operations is
          ...
      end Operations;

  The generic formal parameters define an abstract byte stream and
  operations for interchanging bytes on it.  To function, a stream
  must not lose bytes and must deliver bytes in order.

  A stream must perform fragmentation and reassembly.  That is, the
  sequence of operations:
      Put (Into, Data (1 .. X));
      Put (Into, Data (X + 1 .. N));

  must be equivalent to the single operation:
      Put (Into, Data (1 .. N));

  for any value of X in the range 1 ..  N. Likewise, the sequence of
  operations:
      Get (From, Data (1 .. X));
      Get (From, Data (X + 1 .. N));

  must be equivalent to the single operation:
      Get (From, Data (1 .. N));

  for any value of X in the range 1 ..  N.
  @node !Tools.Networking.Interchange.Operations.Get

  procedure Get (From :     Stream_Id;
                Data : out Byte);
  procedure Get (From :     Stream_Id;
                Data : out Interchange.Duration);
  procedure Get (From :     Stream_Id;
                Data : out Interchange.Float);
  procedure Get (From :     Stream_Id;
                Data : out Interchange.Integer);
  procedure Get (From :     Stream_Id;
                Data : out Interchange.Long_Float);
  procedure Get (From :     Stream_Id;
                Data : out Interchange.Long_Integer);
  procedure Get (From :     Stream_Id;
                Data : out Interchange.Short_Integer);
  procedure Get (From :     Stream_Id;
                Data : out Interchange.Time);
  procedure Get (From :     Stream_Id;
                Data : out Standard.Boolean);
  procedure Get (From :     Stream_Id;
                Data : out Standard.Character);

  Converts a value from its interchange representation to its local
  representation.

  The interchange representation of a Standard.Boolean is given as
  a Short_Integer type, with the value 0 for false and 1 for true.
  The interchange representation of a Standard.Character is its 'Pos
  converted to a Short_Integer type.
  @node !Tools.Networking.Interchange.Operations.Get

  with procedure Get (From :     Stream_Id;
                     Data : out Byte_String) is <>;

  Gets some bytes from a stream.
  @node !Tools.Networking.Interchange.Operations.Get_Byte_String

  function Get_Byte_String (From : Stream_Id) return Byte_String;

  Converts a byte string from its interchange representation to its
  local representation.

  Get_Byte_String is a function because Byte_String is an
  unconstrained subtype.
  @node !Tools.Networking.Interchange.Operations.Get_String

  function Get_String (From : Stream_Id) return Standard.String;

  Converts a string from its interchange representation to its local
  representation.

  Get_String is a function because String is an unconstrained type.

  The interchange representation of a Standard.String is given as a
  Byte_String subtype, with one character per byte.  Each character
  is represented by its 'Pos (its ASCII code).
  @node !Tools.Networking.Interchange.Operations.Put

  procedure Put (Into : Stream_Id;
                Data : Byte);
  procedure Put (Into : Stream_Id;
                Data : Interchange.Duration);
  procedure Put (Into : Stream_Id;
                Data : Interchange.Float);
  procedure Put (Into : Stream_Id;
                Data : Interchange.Integer);
  procedure Put (Into : Stream_Id;
                Data : Interchange.Long_Float);
  procedure Put (Into : Stream_Id;
                Data : Interchange.Long_Integer);
  procedure Put (Into : Stream_Id;
                Data : Interchange.Short_Integer);
  procedure Put (Into : Stream_Id;
                Data : Interchange.Time);
  procedure Put (Into : Stream_Id;
                Data : Standard.Boolean);
  procedure Put (Into : Stream_Id;
                Data : Standard.Character);

  Converts a value from its interchange representation to its local
  representation.

  The interchange representation of a Standard.Boolean is given as
  a Short_Integer type, with the value 0 for false and 1 for true.
  The interchange representation of a Standard.Character is its 'Pos
  converted to a Short_Integer type.
  @node !Tools.Networking.Interchange.Operations.Put

  with procedure Put (Into : Stream_Id;
                     Data : Byte_String) is <>;

  Puts some bytes into a stream.
  @node !Tools.Networking.Interchange.Operations.Put_Byte_String

  procedure Put_Byte_String (Into : Stream_Id;
                            Data : Byte_String);

  Converts a Byte_String from its local representation to its
  interchange representation.
  @node !Tools.Networking.Interchange.Operations.Put_String

  procedure Put_String (Into : Stream_Id;
                       Data : Standard.String);

  Converts a Standard.String from its local representation to its
  interchange representation.

  The interchange representation of a Standard.String is a
  Byte_String subtype, with one character per byte.  Each character
  is represented by its 'Pos (its ASCII code).
  @node !Tools.Networking.Interchange.Operations.Stream_Id

  type Stream_Id is limited private;

  Specifies that data be taken from the selected stream of bytes.

  The interchange representation of values is put into or taken from
  a stream.

  @node !Tools.Networking.Interchange.Vector

  A vector is a one-dimensional array of elements.  Given a vector
  type (an unconstrained array type), this package provides
  interchange operations on that type.

  The specification of the package is:
      generic
          type Element_Type is private;
          with procedure Put (Into : Stream_Id;
                             Data : Element_Type) is <>;
          with procedure Get (From : Stream_Id;
                             Data : out Element_Type) is <>;
          type Index_Type is (<>);
          with procedure Put (Into : Stream_Id;
                             Data : Index_Type) is <>;
          with procedure Get (From : Stream_Id;
                             Data : out Index_Type) is <>;
          type Vector_Type is array (Index_Type range <>) of Element_Type;
      package Vector is
          ...
      end Vector;

  @node !Tools.Networking.Interchange.Vector.Element_Type

  type Element_Type is private;

  Specifies the type of each element of a vector.

  The interchange representation of this type is supplied by the user
  as Put and Get generic formal procedures.
  @node !Tools.Networking.Interchange.Vector.Get

  function Get (From : Stream_Id) return Vector_Type;

  Converts a vector from its interchange representation to its local
  representation.
  @node !Tools.Networking.Interchange.Vector.Get

  with procedure Get (From :     Stream_Id;
                     Data : out Element_Type) is <>;
  with procedure Get (From :     Stream_Id;
                     Data : out Index_Type) is <>;

  Converts a value from its interchange representation to its local
  representation.
  @node !Tools.Networking.Interchange.Vector.Index_Type

  type Index_Type is (<>);

  Specifies the index type of a vector.

  The interchange representation of this type is supplied by the user
  as Put and Get generic formal procedures.
  @node !Tools.Networking.Interchange.Vector.Put

  procedure Put (Into : Stream_Id;
                Data : Vector_Type);

  Converts a vector from its local representation to its interchange
  representation.
  @node !Tools.Networking.Interchange.Vector.Put

  with procedure Put (Into : Stream_Id;
                     Data : Element_Type) is <>;
  with procedure Put (Into : Stream_Id;
                     Data : Index_Type) is <>;

  Converts a value from its local representation to its interchange
  representation.
  @node !Tools.Networking.Interchange.Vector.Vector_Type

  type Vector_Type is array (Index_Type range <>) of Element_Type;

  Represents a one-dimensional array of elements.

  This is the type for which package Vector provides interchange
  operations.

  The interchange representation of a value of this type is the
  number of elements (given as an Integer type) followed by the
  elements in index order.
  @node !Tools.Networking.Interchange_Defs

  Package Interchange_Defs defines numeric types and operators for
  package Interchange.  When porting this package, you should modify
  it to indicate the appropriate types on your system.
  @node !Tools.Networking.Interchange_Defs."="

  function "=" (X, Y : Longest_Integer) return Boolean renames Standard."=";

  Renames the standard operator.
  @node !Tools.Networking.Interchange_Defs.">"

  function ">" (X, Y : Longest_Integer) return Boolean renames Standard.">";

  Renames the standard operator.
  @node !Tools.Networking.Interchange_Defs."<"

  function "<" (X, Y : Longest_Integer) return Boolean renames Standard."<";

  Renames the standard operator.
  @node !Tools.Networking.Interchange_Defs.">="

  function ">=" (X, Y : Longest_Integer) return Boolean
                                                    renames Standard.">=";

  Renames the standard operator.
  @node !Tools.Networking.Interchange_Defs."<="

  function "<=" (X, Y : Longest_Integer) return Boolean
                                                    renames Standard."<=";

  Renames the standard operator.
  @node !Tools.Networking.Interchange_Defs."+"

  function "+" (X, Y : Longest_Integer) return Longest_Integer
                                                     renames Standard."+";

  Renames the standard operator.
  @node !Tools.Networking.Interchange_Defs."--"

  function "-" (X, Y : Longest_Integer) return Longest_Integer
                                                     renames Standard."-";

  Renames the standard operator.
  @node !Tools.Networking.Interchange_Defs."*"

  function "*" (X, Y : Longest_Integer) return Longest_Integer
                                                     renames Standard."*";

  Renames the standard operator.
  @node !Tools.Networking.Interchange_Defs."/"

  function "/" (X, Y : Longest_Integer) return Longest_Integer
                                                     renames Standard."/";

  Renames the standard operator.
  @node !Tools.Networking.Interchange_Defs."mod"

  function "mod" (X, Y : Longest_Integer) return Longest_Integer
                                                   renames Standard."mod";

  Renames the standard operator.
  @node !Tools.Networking.Interchange_Defs."rem"

  function "rem" (X, Y : Longest_Integer) return Longest_Integer
                                                   renames Standard."rem";

  Renames the standard operator.
  @node !Tools.Networking.Interchange_Defs.Duration_Magnitude

  function Duration_Magnitude return Standard.Integer;

  This function returns a constant that is:

  o An integral power of 10 (10, 100, 1,000, and so on)

  o <= 10 ** 9

  o <= Standard.Duration'Last

  o <= Standard.Integer'Last

  This constant is used by the Interchange.Convert procedure.
  @node !Tools.Networking.Interchange_Defs.Float

  type Float is new Standard.Float;

  Represents IEEE floating-point, single-precision format.
  @node !Tools.Networking.Interchange_Defs.Long_Float

  type Long_Float is new Standard.Float;

  Represents IEEE floating-point, double-precision format.
  @node !Tools.Networking.Interchange_Defs.Longest_Integer

  subtype Longest_Integer is Standard.Long_Integer;

  Acts as a signed integer of the highest available precision.

  This type is used for internal arithmetic by the Interchange
  conversion algorithms.

  Package Interchange_Defs must define the following arithmetic and
  comparison operators for type Longest_Integer:

        =, >, <, >=, <=, +, --, *, /, mod, rem

  In the Rational implementation, these are defined by renaming the
  operators from package Standard.
  @node !Tools.Networking.Rpc

  This package defines the data types used to represent programs,
  versions, procedures, and exceptions.
  @node !Tools.Networking.Rpc.Defined_Versions

  Defined_Versions : constant Version_Range := (3, 5);

  Defines RPC protocol versions.
  @node !Tools.Networking.Rpc.Error_Type

  type Error_Type is (Error_Other, Error_Constraint, Error_Numeric,
                     Error_Program, Error_Storage, Error_Tasking,
                     Status_Error, Mode_Error, Name_Error, Use_Error,
                     Device_Error, End_Error, Data_Error, Layout_Error,
                     Error_Server_Defined, Error_Username_Or_Password);

  Represents exceptions in RPC response message headers.

  Each value corresponds to an exception or class of exceptions.
  Refer to the table of "Error Messages" in the reference entry for
  the Get_Message function.

  This type indicates a server-defined error.  These exceptions
  indicate the general cause of an error.  The exact cause depends on
  the particulars of the user's server.

  Error_Other

  Indicates any of a variety of errors, excluding the following
  errors.
  Data_Error

  Indicates data error.
  Device_Error

  Indicates device error.
  End_Error

  Indicates end error.
  Error_Constraint

  Indicates contraint error.
  Error_Numeric

  Indicates numeric error.
  Error_Program

  Indicates program error.

  Error_Server_Defined

  Indicates other server-defined error.
  Error_Storage

  Indicates storage error.

  Error_Tasking

  Indicates tasking error.

  Error_Username_Or_Password

  Indicates username or password error.

  Layout_Error

  Indicates layout error.

  Mode_Error

  Indicates mode error.
  Name_Error

  Indicates name error.
  Status_Error

  Indicates status error.
  Use_Error

  Indicates use error.
  @node !Tools.Networking.Rpc.Exception_Number

  type Exception_Number is new Interchange.Integer;

  Represents server-defined exceptions in RPC response headers.

  Each value corresponds to an exception.  The correspondence is
  determined by the service that raises the exception.
  @node !Tools.Networking.Rpc.Exception_Versions

  Exception_Versions : constant Version_Range := (4, Version_Number'Last);

  Defines RPC protocol versions that support server-defined
  exceptions.
  @node !Tools.Networking.Rpc.Get

  procedure Get (From :     Stream_Id;
                Data : out Version_Range);
  procedure Get (From :     Stream_Id;
                Data : out Exception_Number);

  Gets a value of the Version_Range or Exception_Number types from a
  stream.
  @node !Tools.Networking.Rpc.Get_Message

  function Get_Message (From : Stream_Id) return Message_Header;

  Gets a value of the Message_Header type from a stream.

  Refer to the table of "Error Messages" on the following page.
  @node !Tools.Networking.Rpc.Invalid_Argument

  Invalid_Argument : exception;

  Occurs when the interchange form of an argument is invalid.

  An example would be the encoding of a value outside the legal
  range.
  @node !Tools.Networking.Rpc.Max

  function Max (X, Y : Version_Range) return Version_Number;

  Returns the largest version that is common to both X and Y.

  If the server supports a range of protocol versions and the client
  supports a separate range of protocol versions, this function
  returns the largest version of the protocol that is common to both
  the client and the server.
  @node !Tools.Networking.Rpc.Message_Header

  type Message_Header (Kind : Message_Kind := Return_Message) is
      record
          Id : Transaction_Id :=0;
          case Kind is
             when Call_Message =>
              Program : Program_Number;
              Version : Version_Number;
              Proc    : Procedure_Number;
             when Reject_Message =>
              Details : Reject_Details;
             when Return_Message =>
              null;
             when Abort_Message =>
              Error : Error_Type;
           end case;
       end record;

  Begins each RPC message (request or response) with introductory
  information about the message.
  @node !Tools.Networking.Rpc.Message_Kind

  type Message_Kind is (Call_Message, Reject_Message, Return_Message,
                                                           Abort_Message);

  Acts as the discriminant of the Message_Header type.

  Each RPC message (request or response) must be one of the above
  kinds.
  Abort_Message

  Indicates that an exception was raised by the called subprogram.

  Call_Message

  Indicates the initial request for service sent by client to server.

  Reject_Message

  Indicates some problem with the requested program number, version
  number, or procedure number.

  Return_Message

  Indicates normal completion of the requested operation.
  @node !Tools.Networking.Rpc.No_Such_Procedure

  No_Such_Procedure : exception;

  Occurs when a nonexistent procedure is called.

  This exception is raised when a server receives a request message
  containing a procedure number that does not identify an existing
  procedure.  The exception may indicate a disagreement between
  client and server about procedure numbering.
  @node !Tools.Networking.Rpc.No_Such_Program

  No_Such_Program : exception;

  Occurs when a nonexistent program is called.

  This exception is raised when a server receives a request message
  containing a program number that does not identify an existing
  program.  The exception may indicate a disagreement between client
  and server about program numbering.
  @node !Tools.Networking.Rpc.No_Such_Version

  No_Such_Version : exception;

  Occurs when a nonexistent version is called.

  This exception is raised when a server receives a request message
  containing a version number that does not identify a supported
  version.
  @node !Tools.Networking.Rpc.Other_Error

  Other_Error : exception;

  Occurs under a variety of circumstances.

  This exception is raised by the Get_Message function to indicate
  that an unknown exception has been raised in the server.
  @node !Tools.Networking.Rpc.Overlaps

  function Overlaps (X, Y : Version_Range) return Boolean:

  Checks whether two ranges of version numbers overlap.
  @node !Tools.Networking.Rpc.Procedure_Number

  type Procedure_Number is new Interchange.Short_Integer;

  Identifies a procedure within a program.

  The correspondence between procedure numbers and procedures is
  determined by each service.
  @node !Tools.Networking.Rpc.Program_Number

  type Program_Number is new Interchange.Integer;

  Identifies a program.
  @node !Tools.Networking.Rpc.Protocol_Error

  Protocol_Error : exception;

  Occurs when an event happens that is not legal in the RPC protocol.

  An example event would be a server receiving a response message.
  @node !Tools.Networking.Rpc.Put

  procedure Put (Into : Stream_Id;
                Data : Exception_Number);

  Puts a value of the Exception_Number type into a stream.
  @node !Tools.Networking.Rpc.Put

  procedure Put (Into : Stream_Id;
                Data : Version_Range);

  Puts a value of the Version_Range type into a stream.
  @node !Tools.Networking.Rpc.Put_Message

  procedure Put_Message (Into : Stream_Id;
                        Data : Message_Header);

  Puts a value of the Message_Header type into a stream.
  @node !Tools.Networking.Rpc.Reject_Details

  type Reject_Details (Kind : Reject_Kind := Rej_Invalid_Argument) is
      record
        case Kind is
            when Rej_No_Such_Version =>
               Supported : Version_Range;
            when other =>
               null;
        end case;
      end record;

  Identifies the reason for rejecting an RPC request.
  @node !Tools.Networking.Rpc.Reject_Kind

  type Reject_Kind is (Rej_No_Such_Program, Rej_No_Such_Version,
                      Rej_No_Such_Procedure, Rej_No_Such_Argument);

  Acts as the discriminant of the Reject_Details type.
  @node !Tools.Networking.Rpc.Server_Defined_Error

  Server_Defined_Error : exception;

  Indicates that some server-defined exception has been raised.
  @node !Tools.Networking.Rpc.Stream_Id

  subtype Stream_Id is Transport_Stream.Stream_Id;

  Identifies a bidirectional stream of bytes.
  @node !Tools.Networking.Rpc.Transaction_Id

  type Transaction_Id is new Interchange.Short_Integer;

  Identifies a transaction.

  A transaction is associated with each remote procedure call.  This
  type is not used currently.
  @node !Tools.Networking.Rpc.Username_Or_Password_Error

  Username_Or_Password_Error : exception;

  Occurs when the username and/or password supplied with a remote
  procedure call is rejected by the server machine.

  This exception is raised when either there is no such username or
  the password is incorrect.
  @node !Tools.Networking.Rpc.Username_Versions

  Username_Versions : constant Version_Range := (5, Version_Number'Last);

  Defines RPC protocol versions that support passing username and
  password information with each call.
  @node !Tools.Networking.Rpc.Version_Number

  type Version_Number is new Interchange.Short_Integer;

  Identifies a particular version of a program (service).
  @node !Tools.Networking.Rpc.Version_Range

  type Version_Range is
        record
            First, Last : Version_Number;
        end record;

  Identifies a range of versions.

  By convention, a value X of the Version_Range type represents
  versions in the Ada range:  X.First ..  X.Last.
  @node !Tools.Networking.Rpc_Access_Utilities

  Package Rpc_Access_Utilities is used by RPC client programs to
  obtain usernames and passwords to control the identity of RPC
  servers running on other machines.
  @node !Tools.Networking.Rpc_Access_Utilities.Remote_Password

  function Remote_Password
        (Host_Name : String;
         Response  : Profile.Response_Profile := Profile.Get) return String;

  Returns a password to be used by the machine named by the Host_Name
  parameter.

  This function reads the object named by the Remote_Passwords switch
  in the given response profile, searching for a line that matches
  the given Host_Name.  If a matching line is found, and the password
  field in that line is "<PROMPT>", the calling user is prompted
  to enter a password in an I/O window, and the entered password is
  returned.  If the password field is not "<PROMPT>", the field is
  returned.  If there is no line in the Remote_Passwords file that
  matches the Host_Name, the null string ("") is returned.
  @node !Tools.Networking.Rpc_Access_Utilities.Remote_Session

  function Remote_Session
        (Host_Name : String;
         Response  : Profile.Response_Profile := Profile.Get) return String;

  Returns a session (account) name to be used by the machine named by
  the Host_Name parameter.

  This function reads the object named by the Remote_Sessions switch
  in the given response profile, searching for a line that matches
  the given Host_Name.  If a matching line is found, and the session
  field in that line is "<PROMPT>", the calling user is prompted
  to enter a session in an I/O window, and the entered session is
  returned.  If the session field is not "<PROMPT>", the field is
  returned.  If there is no line in the Remote_Sessions file that
  matches the Host_Name, the null string ("") is returned.
  @node !Tools.Networking.Rpc_Access_Utilities.Remote_Username

  function Remote_Username
        (Host_Name : String;
         Response  : Profile.Response_Profile := Profile.Get) return String;

  Returns a username to be used by the machine named by the Host_Name
  parameter.

  This function reads the object named by the Remote_Passwords switch
  in the given response profile, searching for a line that matches
  the given Host_Name.  If a matching line is found, and the username
  field in that line is "<PROMPT>", the calling user is prompted
  to enter a username in an I/O window, and the entered username is
  returned.  If the username field is not "<PROMPT>", the field is
  returned.  If there is no line in the Remote_Passwords file that
  matches the Host_Name, the null string ("") is returned.
  @node !Tools.Networking.Rpc_Access_Utilities.Start_Request_Generic

  generic
      Default_Host_Name : String;
      Default_Socket    : Transport_Defs.Socket_Id;
      Default_Program   : Rpc.Program_Number;
      Default_Version   : Rpc.Version_Number;
      Default_Username  : String                  := "";
      Default_Password  : String                  := "";
  procedure Start_Request_Generic
           (Stream    : out Transport_Stream.Stream_Id;
            Proc      :     Rpc.Procedure_Number;
            Host_Name :     String                    := Default_Host_Name;
            Socket    :     Transport_Defs.Socket_Id   := Default_Socket;
            Program   :     Rpc.Program_Number         := Default_Program;
            Version   :     Rpc.Version_Number         := Default_Version;
            Username  :     String                    := Default_Username;
            Password  :     String                    := Default_Password;
            Response  :     Profile.Response_Profile   := Profile.Get);

  Allocates a stream and transmits a request header with the
  specified program, version, procedure, username, and password
  values.

  Host_Name is resolved to a Host_Id and a Network_Name by
  package Transport_Name.  If Username = "", it is replaced by
  Remote_Username (Host_Name, Response).  If Password = "", it is
  replaced by Remote_Password (Host_Name, Response).

  This procedure is similar to
  the Rpc_Client.Start_Request_With_Username generic procedure,
  with the addition of Host_Name resolution and Remote_Password file
  processing.
  @node !Tools.Networking.Rpc_Client

  Package Rpc_Client provides operations used by clients to initiate
  remote procedure calls.
  @node !Tools.Networking.Rpc_Client.End_Request

  procedure End_Request (Stream : Transport_Stream.Stream_Id);

  Flushes the transmit buffer and gets a response header.

  Either this procedure or the End_Request_With_Exception procedure
  must be called by each client procedure after transmitting all
  request parameters but before receiving any response parameters.

  Flushes the transmit buffer and gets a response header.

  If the reponse header contains a server-defined exception, it is
  raised by the Raise_Exception procedure.  Either this procedure

  or the End_Request procedure is called by each client procedure
  after transmitting all request parameters but before receiving any
  response parameters.

  The formal parameters to the generic procedure are:
      generic
          with procedure Raise_Exception (Excep : Rpc.Exception_Number);
      procedure End_Request_With_Exception
           (Stream : Transport_Stream.Stream_Id);

  @node !Tools.Networking.Rpc_Client.End_Request_With_Exception

  procedure End_Request_With_Exception
                  (Stream : Transport_Stream.Stream_Id);

  Flushes the transmit buffer and gets a response header.

  If the reponse header contains a server-defined exception, it is
  raised by the Raise_Exception procedure.  Either this procedure
  or the End_Request procedure is called by each client procedure
  after transmitting all request parameters but before receiving any
  response parameters.
  @node !Tools.Networking.Rpc_Client.Raise_Exception

  with procedure Raise_Exception (Excep : Rpc.Exception_Number);

  Raises a server-defined exception.
  @node !Tools.Networking.Rpc_Client.End_Response

  procedure End_Response (Stream : Transport_Stream.Stream_Id);

  Deallocates the stream.

  This procedure is called by each client procedure after getting all
  response parameters.

  Allocates a stream from the pool and transmits a request message
  header with the given program, version, and procedure values.

  The Stream parameter returns the identification number of the
  stream into which to put request parameters and from which to get
  response parameters.

  The Proc parameter specifies the number of the remote procedure
  called.

  The formal parameters to the generic procedure are:
      generic
          Default_Network : Transport_Defs.Network_Name;
          Default_Host : Transport_Defs.Host_Id;
          Default_Socket : Transport_Defs.Socket_Id;
          Default_Program : Rpc.Program_Number;
          Default_Version : Rpc.Version_Number;
      procedure Start_Request_Generic
           (Stream : out Transport_Stream.Stream_Id;
            Proc : Rpc.Procedure_Number;
            Network : Transport_Defs.Network_Name := Default_Network;
            Host : Transport_Defs.Host_Id := Default_Host;
            Socket : Transport_Defs.Socket_Id := Default_Socket;
            Program : Rpc.Program_Number := Default_Number;
            Version : Rpc.Version_Number := Default_Version);

  @node !Tools.Networking.Rpc_Client.Default_Host

  Default_Host : Transport_Defs.Host_Id;

  Defines the host identifier that is to be used as the default host
  by the Start_Request_Generic procedure.
  @node !Tools.Networking.Rpc_Client.Default_Network

  Default_Network : Transport_Defs.Network_Name;

  Defines the network name that is to be used as the default name by
  the Start_Request_Generic procedure.
  @node !Tools.Networking.Rpc_Client.Default_Program

  Default_Program : Rpc.Program_Number;

  Defines the program number that is to be used as the default number
  by the Start_Request_Generic procedure.
  @node !Tools.Networking.Rpc_Client.Default_Socket

  Default_Socket : Transport_Defs.Socket_Id;

  Defines the socket identifier that is to be used as the default
  socket by the Start_Request_Generic procedure.
  @node !Tools.Networking.Rpc_Client.Default_Version

  Default_Version : Rpc.Version_Number;

  Defines the version number that is to be used as the default number
  by the Start_Request_Generic procedure.
  @node !Tools.Networking.Rpc_Client.Start_Request_Generic

  procedure Start_Request_Generic
             (Stream : out Transport_Stream.Stream_Id;
             Proc : Rpc.Procedure_Number;
             Network : Transport_Defs.Network_Name := Default_Network;
             Host : Transport_Defs.Host_Id := Default_Host;
             Socket : Transport_Defs.Socket_Id := Default_Socket;
             Program : Rpc.Program_Number := Default_Number;
             Version : Rpc.Version_Number := Default_Version);

  Allocates a stream from the pool and transmits a request message
  header with the given program, version, and procedure values.

  Allocates a stream from the pool and transmits a request message
  header with the given program, version, and procedure values.

  The Stream parameter returns the identification number of the
  stream into which to put request parameters and from which to get
  response parameters.

  The Proc parameter specifies the number of the remote procedure
  called.

  The Username and Password parameters can be passed to the server
  when the server must assume an identity in the access control
  system of the server machine.

  The formal parameters to the generic procedure are:
      generic
          Default_Network : Transport_Defs.Network_Name;
          Default_Host : Transport_Defs.Host_Id;

          Default_Socket : Transport_Defs.Socket_Id;
          Default_Program : Rpc.Program_Number;
          Default_Version : Rpc.Version_Number;
          Default_Username : String := "";
          Default_Password : String := "";
      procedure Start_Request_With_Username
           (Stream : out Transport_Stream.Stream_Id;
            Proc : Rpc.Procedure_Number;
            Network : Transport_Defs.Network_Name := Default_Network;
            Host : Transport_Defs.Host_Id := Default_Host;
            Socket : Transport_Defs.Socket_Id := Default_Socket;
            Program : Rpc.Program_Number := Default_Program;
            Version : Rpc.Version_Number := Default_Version;
            Username : String := Default_Username;
            Password : String := Default_Password);
  @node !Tools.Networking.Rpc_Client.Default_Host

  Default_Host : Transport_Defs.Host_Id;

  Defines the host identifier that is to be used as the default host
  by the Start_Request_With_Username procedure.
  @node !Tools.Networking.Rpc_Client.Default_Network

  Default_Network : Transport_Defs.Network_Name;

  Defines the network name that is to be used as the default name by
  the Start_Request_With_Username procedure.
  @node !Tools.Networking.Rpc_Client.Default_Password

  Default_Password : String := "";

  Defines the password that is to be used as the default by the
  Start_Request_With_Username procedure.
  @node !Tools.Networking.Rpc_Client.Default_Program

  Default_Program : Rpc.Program_Number;

  Defines the program number that is to be used as the default number
  by the Start_Request_With_Username procedure.
  @node !Tools.Networking.Rpc_Client.Default_Socket

  Default_Socket : Transport_Defs.Socket_Id;

  Defines the socket identifier that is to be used as the default
  socket by the Start_Request_With_Username procedure.
  @node !Tools.Networking.Rpc_Client.Default_Username

  Default_Username : String := "";

  Defines the username that is to be used as the default by the
  Start_Request_With_Username procedure.
  @node !Tools.Networking.Rpc_Client.Default_Version

  Default_Version : Rpc.Version_Number;

  Defines the version number that is to be used as the default number
  by the Start_Request_With_Username procedure.
  @node !Tools.Networking.Rpc_Client.Start_Request_With_Username

  procedure Start_Request_With_Username
             (Stream : out Transport_Stream.Stream_Id;
             Proc : Rpc.Procedure_Number;
             Network : Transport_Defs.Network_Name := Default_Network;
             Host : Transport_Defs.Host_Id := Default_Host;
             Socket : Transport_Defs.Socket_Id := Default_Socket;
             Program : Rpc.Program_Number := Default_Program;
             Version : Rpc.Version_Number := Default_Version;
             Username : String := Default_Username;
             Password : String := Default_Password);

  Allocates a stream from the pool and transmits a request message
  header with the given program, version, and procedure values.

  The Username and Password parameters can be passed to the server
  when the server must assume an identity in the access control
  system of the server machine.
  @node !Tools.Networking.Rpc_Product

  Package Rpc_Product provides a way to check whether the RPC product
  has been installed on your machine.
  @node !Tools.Networking.Rpc_Product.Is_Installed

  function Is_Installed return Boolean;

  Returns true if the RPC product has been installed on your machine.
  @node !Tools.Networking.Rpc_Product.Is_Not_Installed

  Is_Not_Installed : exception;

  Occurs when an RPC subprogram is called, if the RPC product is not
  installed on your machine.
  @node !Tools.Networking.Rpc_Server

  Package Rpc_Server provides operations used
  by servers to handle remote procedure calls.
  @node !Tools.Networking.Rpc_Server.Begin_Response

  procedure Begin_Response (Stream : Transport_Stream.Stream_Id;
                           Id     : Rpc.Transaction_Id);

  Transmits a response header.

  This procedure is called from the body of the Process_Call
  procedure after request parameters are got from the stream but
  before response parameters are put into the stream.
  @node !Tools.Networking.Rpc_Server.Return_Exception

  procedure Return_Exception (Stream : Transport_Stream.Stream_Id;
                             Id     : Rpc.Transaction_Id;
                             Excep  : Rpc.Exception_Number);

  Transmits an exception message in response to an RPC request.

  This procedure is called by the Process_Call procedure.

  Services an incoming RPC connection.

  This procedure:

  o Allocates a transport stream.

  o Checks compatibility of incoming package and version.  An
    exception message is returned if there is a mismatch.

  o Processes calls until the connection is disconnected.

  o Catches, on each call, any propagated exceptions, transmitting
    them and flushing the transmit buffer.

  o Deallocates resources after disconnection.

  The formal parameters to the generic procedure are:
      generic
          Program : Rpc.Program_Number;
          Supported : Rpc.Version_Range := (0, Rpc.Version_Number'Last);
          with procedure Process_Call (Stream : Transport_Stream.Stream_Id;
                                     Id : Rpc.Transaction_Id;
                                     Version : Rpc.Version_Number;
                                     Proc : Rpc.Procedure_Number) is <>;
      procedure Serve (Connection : Transport.Connection_Id);

  @node !Tools.Networking.Rpc_Server.Process_Call

  with procedure Process_Call (Stream  : Transport_Stream.Stream_Id;
                              Id      : Rpc.Transaction_Id;
                              Version : Rpc.Version_Number;
                              Proc    : Rpc.Procedure_Number) is <>;

  Processes one remote procedure call.

  This procedure is supplied by the RPC server user and is called by
  an instantiation of the Serve_With_Username procedure.
  @node !Tools.Networking.Rpc_Server.Program

  Program : Rpc.Program_Number;

  Supplies the number of the program (package) supported by this RPC
  server.
  @node !Tools.Networking.Rpc_Server.Serve

  procedure Serve (Connection : Transport.Connection_Id);

  Serves an incoming RPC connection by allocating a transport
  stream, checking the incoming package and version for a match,
  and processing calls until the connection is disconnected.

  For each RPC call, this procedure catches any propagated
  exceptions, transmits them, and then flushes the transmit buffer.
  When the connection is disconnected or a protocol error occurs, the
  procedure deallocates the transport stream and returns.
  @node !Tools.Networking.Rpc_Server.Supported

  Supported : Rpc.Version_Range := (0, Rpc.Version_Number'Last);

  Indicates the range of versions supported by this RPC server.

  Services an incoming RPC connection.

  This procedure:

  o Allocates a transport stream

  o Checks compatibility of incoming package and version.  An
    exception message is returned if there is a mismatch

  o Processes calls until the connection is disconnected

  o Catches, on each call, any propagated exceptions, transmitting
    them and flushing the transmit buffer

  o Deallocates resources after disconnection

  The formal parameters to the generic procedure are:
      generic
          Program : Rpc.Program_Number;
          Supported : Rpc.Version_Range := (0, Rpc.Version_Number'Last);
          with procedure Process_Call (Stream : Transport_Stream.Stream_Id;
                                     Id : Rpc.Transaction_Id;
                                     Version : Rpc.Version_Number;
                                     Proc : Rpc.Procedure_Number;
                                     Username : String;
                                     Password : String) is <>;
      procedure Serve_With_Username (Connection : Transport.Connection_Id);

  @node !Tools.Networking.Rpc_Server.Process_Call

  with procedure Process_Call (Stream   : Transport_Stream.Stream_Id;
                              Id       : Rpc.Transaction_Id;
                              Version  : Rpc.Version_Number;
                              Proc     : Rpc.Procedure_Number;
                              Username : String;
                              Password : String) is <>;

  Processes one remote procedure call.

  This procedure is supplied by the RPC server user and is called by
  an instantiation of the Serve procedure.
  @node !Tools.Networking.Rpc_Server.Program

  Program : Rpc.Program_Number;

  Supplies the number of the program (package) supported by this RPC
  server.
  @node !Tools.Networking.Rpc_Server.Serve_With_Username

  procedure Serve_With_Username (Connection : Transport.Connection_Id);

  Serves an incoming RPC connection by allocating a transport
  stream, checking the incoming package and version for a match,
  and processing calls until the connection is disconnected.

  For each RPC call, this procedure catches any propagated
  exceptions, transmits them, and then flushes the transmit buffer.
  When the connection is disconnected or a protocol error occurs, the
  procedure deallocates the transport stream and returns.
  @node !Tools.Networking.Rpc_Server.Supported

  Supported : Rpc.Version_Range := (0, Rpc.Version_Number'Last);

  Indicates the range of versions supported by this RPC server.
  @node !Tools.Networking.Transport_Interchange

  Instantiates package Interchange for use on a transport stream.

  Package Transport_Interchange provides procedures for
  interchanging various standard types over transport connections.

  This package is used by RPC programs for interchanging the
  parameters and results of remote procedure calls.

  The specification of the package is:
      with Interchange;

      with Transport_Stream;
      package Transport_Interchange is new Interchange.Operations
           (Stream_Id => Transport_Stream.Stream_Id,
            Put => Transport_Stream.Transmit,
            Get => Transport_Stream.Receive);
  @node !Tools.Networking.Transport_Server

  This package handles the creation of server tasks in response to
  incoming connections.  The algorithm to be used for serving each
  connection is supplied by the user as a generic parameter.

  This package is used by RPC servers to manage the tasks providing
  an RPC service.

  The specification of the package is:
      with Transport;
      with Transport_Defs;
      generic
          with procedure Serve (Connection : Transport.Connection_Id) is <>;
      package Transport_Server is
          type Pool_Id is private;
          function Create (Network : Transport_Defs.Network_Name;
                          Local_Socket : Transport_Defs.Socket_Id;
                          Max_Servers : Natural := Natural'Last)
                                                           return Pool_Id;
          procedure Finalize (Abort_Servers : Boolean := False);
          function Local_Socket (Pool : Pool_Id)
                                          return Transport_Defs.Socket_Id;
          function Max_Servers (Pool : Pool_Id) return Natural;
          function Network (Pool : Pool_Id)
                                       return Transport_Defs.Network_Name;
          procedure Set_Max_Servers (Pool : Pool_Id;
                                    Max_Servers : Natural);
          function Servers (Pool : Pool_Id) return Natural;
          end Transport_Server;
  @node !Tools.Networking.Transport_Server.Create

  function Create
               (Network      : Transport_Defs.Network_Name;
                Local_Socket : Transport_Defs.Socket_Id;
                Max_Servers  : Natural                    := Natural'Last)
                                                           return Pool_Id;

  Creates a pool of server tasks.

  Each pool contains a waiter task that waits for incoming
  connections on the specified network and local socket.  The waiter
  task starts waiting when the pool is created.

  When a connection arrives, a server task is allocated to serve it.
  The server task calls the Serve procedure and passes it the newly
  arrived connection.  When the Serve procedure returns, there is
  nothing more to be done with the connection.  The server task then
  closes the connection and terminates.

  The waiter task continues to wait for more incoming connections.
  In addition, the waiter task keeps track of the number of active
  servers.  If this number reaches the given Max_Servers limit, the
  waiter task stops waiting for incoming connections.
  @node !Tools.Networking.Transport_Server.Finalize

  procedure Finalize (Abort_Servers : Boolean := False);

  Terminates all tasks dependent on this instantiation of package
  Transport_Server and closes all transport connections.

  This procedure permits the caller to exit the scope in which
  package Transport_Server was instantiated.  See the Ada Language
  Reference Manual, Section 9.4.
  @node !Tools.Networking.Transport_Server.Local_Socket

  function Local_Socket (Pool : Pool_Id) return Transport_Defs.Socket_Id;

  Returns the local socket on which the given pool is waiting for
  incoming connections.

  This value is set when the pool is created.
  @node !Tools.Networking.Transport_Server.Max_Servers

  function Max_Servers (Pool : Pool_Id) return Natural;

  Returns the maximum number of server tasks that can be active
  simultaneously in the given pool.

  This value is initialized when the pool is created and subsequently
  can be set by the user.
  @node !Tools.Networking.Transport_Server.Network

  function Network (Pool : Pool_Id) return Transport_Defs.Network_Name;

  Returns the network on which the given pool waits for incoming
  connections.

  This value is set when the pool is created.
  @node !Tools.Networking.Transport_Server.Pool_Id

  type Pool_Id is private;

  Identifies a pool of server tasks.
  @node !Tools.Networking.Transport_Server.Serve

  procedure Serve (Connection : Transport.Connection_Id) is <>;

  Serves a connection.

  This procedure is called once for each incoming connection.  The
  tasks that call the Serve procedure are created and managed by
  manipulating pool objects.
  @node !Tools.Networking.Transport_Server.Servers

  function Servers (Pool : Pool_Id) return Natural;

  Returns the number of server tasks currently active in the given
  pool.

  This number is initially 0.  The value increases each time a
  connection arrives and decreases each time a server terminates.
  @node !Tools.Networking.Transport_Server.Set_Max_Servers

  procedure Set_Max_Servers (Pool        : Pool_Id;
                            Max_Servers : Natural);

  Sets the maximum number of server tasks that can be active in the
  given pool.

  Once the number of active servers reaches this limit, the pool's
  waiter task stops waiting for incoming connections.

  If the Max_Servers parameter is set to a number less than the
  current number of active servers, the existing servers will
  continue to run until they terminate by themselves.
  @node !Tools.Networking.Transport_Server_Job

  This package handles the creation of server jobs in response
  to incoming connections.  The algorithm used for serving each
  connection is supplied by the user as a generic parameter.

  This package is used by RPC servers to manage the jobs providing a
  RPC service.

  The specification of the package is:
      with Transport;
      with Transport_Defs;
      package Transport_Server_Job is
          generic
             Network : Transport_Defs.Network_Name;
             Local_Socket : Transport_Defs.Socket_Id;
             with procedure Server_Start;
             with procedure Serve (Connection : Transport.Connection_Id);
          procedure Server_Generic;
          procedure Change_Identity (Username : String;
                                    Password : String);
      end Transport_Server_Job;
  @node !Tools.Networking.Transport_Server_Job.Change_Identity

  procedure Change_Identity (Username : String;
                            Password : String);

  Sets the calling job's access control identity to the specified
  username and password.

  If Username = Password = "", the calling job's identity is set
  back to its original value---that is, the identity with which the
  job was first run.
  @node !Tools.Networking.Transport_Server_Job.Local_Socket

  Local_Socket : Transport_Defs.Socket_Id;

  Denotes a socket within the context of a machine.

  For TCP/IP, the socket identifier is a TCP port number.
  @node !Tools.Networking.Transport_Server_Job.Network

  Network : Transport_Defs.Network_Name;

  Denotes one of several networks to which this machine can be
  attached.

  Only TCP/IP is currently defined.
  @node !Tools.Networking.Transport_Server_Job.Serve

  procedure Serve (Connection : Transport.Connection_Id);

  Processes incoming requests from the connection.

  This procedure is called once for each incoming connection.
  @node !Tools.Networking.Transport_Server_Job.Server_Generic

  procedure Server_Generic;

  Waits for an incoming request for connection on the specified
  network and local socket.

  When a connection request arrives, this procedure executes
  procedures Server_Start and Serve(Connection).  The procedure
  repeats this process until the local socket is in use, and then it
  returns.
  @node !Tools.Networking.Transport_Server_Job.Server_Start

  procedure Server_Start;

  Starts another server job, using the network specified by the
  Network parameter at the socket specified by the Local_Socket
  parameter.
  @node !Tools.Networking.Transport_Stream

  This package handles the details of allocating and using transport
  connections.

  A transport stream combines a transport connection with some
  buffering and provides a simplified transmit/receive interface.

  This package provides a facility for creating pools of streams.
  Allocating and deallocating streams occurs very quickly and
  introduces little overhead.  If a stream remains deallocated for a
  few minutes, the transport connection associated with it is closed.

  This package is useful for programs needing to communicate with
  another machine, without setting up and disconnecting transport
  connections, or for handling transport status codes.
  @node !Tools.Networking.Transport_Stream.Allocate

  procedure Allocate (Stream     : out Stream_Id;
                     Connection :     Transport.Connection_Id);

  Creates a stream without a pool around the given connection.

  The connection is closed when the stream is deallocated.
  @node !Tools.Networking.Transport_Stream.Allocate

  procedure Allocate (Stream  : out Stream_Id;
                     Is_New  : out Boolean;
                     Network :     Transport_Defs.Network_Name;
                     Host    :     Transport_Defs.Host_Id;
                     Socket  :     Transport_Defs.Socket_Id);

  Locates or sets up a stream to the given network/host/socket
  combination.
  @node !Tools.Networking.Transport_Stream.Allocate

  procedure Allocate (Stream : out Stream_Id;
                     Pool   :     Pool_Id;
                     Is_New : out Boolean);

  Locates an idle stream from the specified pool.

  If no idle stream is available, the procedure sets up an idle
  stream, opens and connects a transport connection, and returns
  Is_New = True.
  @node !Tools.Networking.Transport_Stream.Connection

  function Connection (Stream : Stream_Id) return Transport.Connection_Id;

  Returns the transport connection to which the stream is bound.
  @node !Tools.Networking.Transport_Stream.Create

  function Create (Network       : Transport_Defs.Network_Name;
                  Remote_Host   : Transport_Defs.Host_Id;
                  Remote_Socket : Transport_Defs.Socket_Id;
                  Local_Socket  : Transport_Defs.Socket_Id
                          := Transport_Defs.Null_Socket_Id) return Pool_Id;

  Creates a pool of active streams.
  @node !Tools.Networking.Transport_Stream.Deallocate

  procedure Deallocate (Stream : Stream_Id);

  Returns a stream to its pool.

  Once a stream has been deallocated, it must not be used
  subsequently because it may be reallocated to another program.
  @node !Tools.Networking.Transport_Stream.Destroy

  procedure Destroy (Pool : Pool_Id);

  Disconnects all streams in the pool and terminates all tasks
  associated with the pool.
  @node !Tools.Networking.Transport_Stream.Disconnect

  procedure Disconnect (Stream : Stream_Id);

  Disconnects the transport connection to which the stream is bound.
  @node !Tools.Networking.Transport_Stream.Finalize

  procedure Finalize;

  Destroys all pools and terminates all tasks.

  This procedure is used when exiting a subprogram in which package
  Transport_Stream (and by extension the tasks within it) was
  elaborated.  See the Ada Language Reference Manual, Section 9.4.
  @node !Tools.Networking.Transport_Stream.Flush_Receive_Buffer

  function Flush_Receive_Buffer (Stream : Stream_Id)
                                             return Byte_Defs.Byte_String;

  Empties and gives as the return value the contents of a stream's
  receive buffer.
  @node !Tools.Networking.Transport_Stream.Flush_Transmit_Buffer

  procedure Flush_Transmit_Buffer (Stream : Stream_Id);

  Transmits any data currently in the stream's transmit buffer.

  This procedure does not return until all buffered data have been
  transmitted.
  @node !Tools.Networking.Transport_Stream.Get_User_Id

  function Get_User_Id (Stream : Stream_Id) return Integer;

  Returns the User_Id integer that is associated with the current
  stream.
  @node !Tools.Networking.Transport_Stream.Not_Connected

  Not_Connected : exception;

  Occurs when an attempt is made to operate on a unconnected stream.
  @node !Tools.Networking.Transport_Stream.Pool_Id

  type Pool_Id is private;

  Identifies a pool of streams.
  @node !Tools.Networking.Transport_Stream.Receive

  procedure Receive (From :     Stream_Id;
                    Data : out Byte_Defs.Byte_String);

  Receives data over a transport stream.

  This call does not return until Data'Length bytes are received.
  @node !Tools.Networking.Transport_Stream.Scavenge

  procedure Scavenge (Pool : Pool_Id);

  Disconnects any deallocated streams in the pool.
  @node !Tools.Networking.Transport_Stream.Scavenge

  procedure Scavenge;

  Scavenges all pools for unused streams.

  Periodically, a task within package Transport_Stream automatically
  scavenges all pools.
  @node !Tools.Networking.Transport_Stream.Set_User_Id

  procedure Set_User_Id (Stream  : Stream_Id;
                        User_Id : Integer   := 0);

  Maps the stream identification number to a user identification
  number.

  The user identification number is not used by package
  Transport_Stream but is provided so that you can associate higher-
  level information with each stream.
  @node !Tools.Networking.Transport_Stream.Stream_Id

  type Stream_Id is private;

  Identifies a data pipe, called a stream, consisting of a transport
  connection and some associated buffers.

  @node !Tools.Networking.Transport_Stream.Transmit

  procedure Transmit (Into : Stream_Id;
                     Data : Byte_Defs.Byte_String);

  Transmits data over a transport stream.

  The given data are either transmitted or stored in a buffer
  for later transmission.  The buffer can be cleared using the
  Flush_Transmit_Buffer procedure.
  @node !Tools.Networking.Transport_Stream.Unique

  function Unique (Stream : Stream_Id) return Unique_Id;

  Converts the stream identification number to a unique number.

  Stream_Id is a private type and its image cannot be obtained
  directly.  Converting Stream_Id to Unique_Id provides a handle
  to allow you to use the identification number for printing hash
  tables, for example.
  @node !Tools.Networking.Transport_Stream.Unique_Id

  subtype Unique_Id is Integer;

  Identifies a unique value of the stream identification number.

  The unique identification number can be used as a handle for
  printing hash tables, for example