|  | DataMuseum.dkPresents historical artifacts from the history of: Rational R1000/400 Tapes | 
This is an automatic "excavation" of a thematic subset of
 See our Wiki for more about Rational R1000/400 Tapes Excavated with: AutoArchaeologist - Free & Open Source Software. | 
top - metrics - downloadIndex: T V
    Length: 31792 (0x7c30)
    Types: TextFile
    Names: »V«
└─⟦d10a02448⟧ Bits:30000409 8mm tape, Rational 1000, ENVIRONMENT, D_12_7_3
    └─⟦fc9b38f02⟧ »DATA« 
        └─⟦9b46a407a⟧ 
            └─⟦12c68c704⟧ 
                └─⟦this⟧ 
└─⟦5f3412b64⟧ Bits:30000745 8mm tape, Rational 1000, ENVIRONMENT 12_6_5 TOOLS 
    └─⟦91c658230⟧ »DATA« 
        └─⟦458657fb6⟧ 
            └─⟦220843204⟧ 
                └─⟦this⟧ 
with Action;
with Directory;
with Io_Exceptions;
with System;
package Pipe is
    subtype Action_Id is Action.Id;
    Null_Action_Id : constant Action_Id := Action.Null_Id;
    subtype Byte        is System.Byte;
    subtype Byte_String is System.Byte_String;
    subtype Object_Id   is Directory.Version;
    subtype Operate_Status is Integer;
    Status_Error : exception renames Io_Exceptions.Status_Error;
    Mode_Error   : exception renames Io_Exceptions.Mode_Error;
    Name_Error   : exception renames Io_Exceptions.Name_Error;
    Use_Error    : exception renames Io_Exceptions.Use_Error;
    Device_Error : exception renames Io_Exceptions.Device_Error;
    End_Error    : exception renames Io_Exceptions.End_Error;
    Data_Error   : exception renames Io_Exceptions.Data_Error;
    Layout_Error : exception renames Io_Exceptions.Layout_Error;
    -- Exceptions are raised iff the the comments following the operation
    -- indicate that the exception is possible.  All other exception
    -- propagation is considered a bug in the underlying implementation.
    -- A pipe is an object which contains a queue of messages, possibly empty.
    -- By opening the object for write, one can do "Write" operations which
    -- append messages to the end of the queue.  By opening the object for
    -- read, one can do "Read" operations which consume messages from the
    -- beginning of the queue.  Each message is read by exactly one Read
    -- operation; thus, in the face of concurrent Reads, each client may see
    -- just a subset of the messages that were written to the pipe.
    -- It is ok to make concurrent calls to this package.  BUT, this does NOT
    -- include calls which supply the same Handle; this is considered
    -- erroneous.  The implementation does not prevent such erroneous behavior;
    -- this behavior might cause your Handle to be left inconsistent, but the
    -- internal representation of the pipe itself is protected and will remain
    -- consistent; thus, other Handle's (including those in other jobs) should
    -- still work properly.
    function Pipe_Class return Directory.Class;
    type Handle is private;
    Null_Handle : constant Handle;
    -- Contains control information which is pertinent to a particular "open"
    -- of a particular pipe.  Other control information (about pipes) is kept
    -- internally.  Logically, a Handle is limited private.  Use of multiple
    -- copies is considered erroneous.  The implementation does not prevent
    -- such erroneous behavior.  At worst, an erroneous program will be able
    -- to Read/Write a pipe which is still open elsewhere, even though other
    -- copies of the Handle have been closed; the internal representation of
    -- the pipe itself is protected from such erroneous behavior and will
    -- remain consistent.
    function Max_Buffer_Size return Positive;
    -- Measured in bytes.  Currently about half the maximum size of a heap.
    function Default_Buffer_Size return Positive;
    -- Measured in bytes.  Currently about 20K bytes.
    function Message_Overhead return Natural;
    -- Measured in bytes.  Currently about 8 bytes.  Clients can compute the
    -- value of B = n * (c + M), where "c" is the result of this function, "M"
    -- is the fixed size of messages supplied to the Write operation, "n" is
    -- the desired capacity of the buffer (in messages), and "B" is the
    -- resulting requirement for buffer size, in bytes.  This function may
    -- change between releases of the system.
    type Pipe_Open_Mode is (Exclusive_Read, Shared_Read,
                            Exclusive_Write, Shared_Write, Exclusive);
    -- The read modes allow one to use Read operations to consume messages from
    -- the beginning of the queue.  The write modes allow one to use Write
    -- operations to append messages to the end of the queue.  The same client
    -- can use both Read and Write by opening the pipe multiple times.  The
    -- compatibility matrix is as follows:
    -- Other action compatibility matrix:
    --                   Current Mode
    --                   (other actions)
    --                  ER  SR  EW  SW  E
    --                ---------------------
    --             ER |         X   X
    --                |
    --             SR |     X   X   X
    --                |
    --    Desired  EW | X   X
    --     Mode       |
    --             SW | X   X       X
    --                |
    --             E  |
    --                ---------------------
    -- Absence of an "X" indicates that the desired access will not be granted
    -- if any OTHER action (not including requesting action) has the indicated
    -- current access.  Via Max_Wait, queueing is available when access is
    -- denied for this reason.
    -- Assuming access is not denied by the above rules, the following matrix
    -- indicates the upgrade compatibility rules:
    -- Upgrade matrix:
    --                    Current Access
    --                   (by same action)
    --                  ER  SR  EW  SW  E
    --                ---------------------
    --             ER | ER  ER          E
    --                |
    --             SR | ER  SR          E
    --    Desired     |
    --    Access   EW |         EW  EW  E
    --                |
    --             SW |         EW  SW  E
    --                |
    --             E  |  E   E   E   E  E
    --                ---------------------
    -- Absence of a mode indicates that the desired access will not be granted
    -- if the requesting action already has the indicated current access.
    -- Queueing is not available in this case.  Presence of a mode indicates
    -- that the access will be granted, and indicates the new lock mode in
    -- which the action holds object.
    -- Note that the upgrade rules imply that a single action cannot be used to
    -- both read and write the same pipe.  Of course, a single task can read
    -- and write the same pipe by using 2 actions.
    -- RESTRICTION: In Delta, the Create operation only supports Exclusive,
    -- and the Open operation only supports Shared_Read, Shared_Write, and
    -- Exclusive.
    procedure Create (Pipe               : in out Handle;
                      Mode               : Pipe_Open_Mode;
                      Name               : String;
                      Action             : Action_Id := Null_Action_Id;
                      Max_Wait           : Duration := Directory.Default_Wait;
                      Permanent_Contents : Boolean := False;
                      Buffer_Size        : Positive := Default_Buffer_Size;
                      Reader_Buffer_Size : Natural := 0);
    -- Since it's an object, a pipe lives in the directory system, as specified
    -- by the Name parameter.  Naming of pipes is the same as for vanilla
    -- files.  Multiple versions of a pipe are allowed.
    -- With respect to disk space, the system reserves the right to allocate
    -- disk space for the entire buffer, at any time, including the first
    -- open. Thus, one should not use excessively large buffer sizes. With
    -- respect to working set, under certain circumstances the buffer is used
    -- in a cylic fashion.  Thus, a large buffer size may cause a large
    -- working set.  All in all, its a good idea to use reasonable buffer
    -- sizes.  One rule of thumb is to use a buffer of size 2 * N * E, where
    -- "N" is the number of servers (readers), and "E" is the expected message
    -- size; this tends to leave just enough room for writers to be "double
    -- bufferred".  (Of course, the buffer must be large enough to hold the
    -- biggest message.)
    -- Given variable length messages, it is not possible for clients to
    -- accurately predict the number of messages that can be stored by a buffer
    -- of a particular size.
    -- A pipe is made empty when it is last closed, or first opened if the
    -- system crashes while the pipe is open.  The only difference from the
    -- user's point of view is disk space consumption.
    -- The create operation leaves the pipe "open" in the specified mode.
    -- Rules for Action are the same as for Open.
    -- Abandoning the action may cause the object to dissappear from the
    -- directory system.
    -- Abandoning/Committing the action causes all open handles (using the
    -- action) to become closed.
    -- If Null_Action_Id is supplied, a new action is created.  If the Create
    -- is successful, the new id is stored in the Handle, and committed when
    -- the Handle is closed.  If the Create fails, the new action is
    -- abandoned.
    -- Reader_Buffer_Size controls the operation of the Read function.  If 0,
    -- then it defaults to the result of calling Max_Buffer_Size.
    -- KNOWN BUGS IN DELTA: (1) Abandoning the action which created the pipe
    -- does NOT cause all open handles to become closed immediately.  (2) The
    -- implementation has a window in which concurrent opens may acquire the
    -- object; this will cause the Create to return any of the exceptions that
    -- can be returned by Open.
    -- EXCEPTIONS:
    --     Status_Error:  The given Handle is already open
    --     Mode_Error:    Mode must be Exclusive
    --     Name_Error:    Directory wont create the object
    --     Use_Error:     Illegal buffer size, or lock error, or
    --                      access control violation
    --     Device_Error:  Obj Mgr can't set/get the buffer size;
    --                    and other internal errors
    procedure Open (Pipe               : in out Handle;
                    Mode               : Pipe_Open_Mode;
                    Name               : String;
                    Reader_Buffer_Size : Natural := 0;
                    Action             : Action_Id := Null_Action_Id;
                    Max_Wait           : Duration := Directory.Default_Wait);
    -- Open an already existing pipe.
    -- If the action is abandoned, the Handle may become implicitly closed.
    -- Committing the action has no effect on the state of the pipe buffer.
    -- If Null_Action_Id is supplied, a new action is created, its id stored
    -- in the Handle, and the action is committed when the Handle is closed.
    -- Reader_Buffer_Size controls the operation of the Read function.  If 0,
    -- then it defaults to the result of calling Max_Buffer_Size.
    -- KNOWN BUG IN DELTA: Exclusive access shows up in the action_manager's
    -- lock information as "Update"; all other access modes show up as "Read".
    -- EXCEPTIONS:
    --     Status_error : The given Handle is already open.
    --     Mode_Error:    Mode must be Shared_Read, Shared_Write, or Exclusive
    --     Name_Error:    Directory can't find the object
    --     Use_Error:     Lock error, or access control violation
    --     Device_Error:  Obj mgr can't get the buffer size;
    --                    and other internal errors
    procedure Open (Pipe               : in out Handle;
                    Mode               : Pipe_Open_Mode;
                    Object             : Object_Id;
                    Reader_Buffer_Size : Natural := 0;
                    Action             : Action_Id := Null_Action_Id;
                    Max_Wait           : Duration := Directory.Default_Wait);
    -- Same as above, but assumes that the caller has already resolved the
    -- string name into an object id.
    procedure Close (Pipe     : in out Handle;
                     Max_Wait :        Duration := Directory.Default_Wait);
    -- If the pipe is open for writing, causes an implicit call to
    -- Write_End_Of_File (throwing away a Use_Error caused by Max_Wait
    -- induced timeout);
    -- If the corresponding Create/Open supplied Null_Action_Id, then the
    -- implicit action is either committed (when the Close is successful) or
    -- abandoned (when the Close is unsuccessful).
    -- The handle becomes closed.
    -- EXCEPTIONS:
    --     Status_error:  The given Handle is not open.
    --     Device_Error:  internal errors
    procedure Delete (Pipe     : in out Handle;
                      Max_Wait :        Duration := Directory.Default_Wait);
    -- Like all objects, causes it to be deleted.  Must have the object open
    -- for Exclusive access.  Assuming a reasonable value for retention count,
    -- the object can be "undeleted" using other environment operations.
    -- If the corresponding Create/Open supplied Null_Action_Id, then the
    -- implicit action is either committed (when the Delete is successful) or
    -- abandoned (when the Delete is unsuccessful).
    -- The handle becomes closed.
    -- EXCEPTIONS:
    --     Status_Error:  The given Handle is not open
    --     Name_Error:    Directory returned an error other than Lock_Error or
    --                    access control error
    --     Use_Error:     Directory returned Lock_Error, which probably means
    --                    that Handle was not open for Exclusive access;
    --                    or could be an access control violation
    --     Device_Error:  internal errors
    Dont_Wait : constant Duration := 0.0;
    Forever   : constant Duration := Duration'Last;
    procedure Write (Pipe     : in out Handle;
                     Message  :        Byte_String;
                     Max_Wait :        Duration := Forever);
    procedure Read (Pipe     : in out Handle;
                    Message  : out    Byte_String;
                    Length   : out    Integer;
                    Max_Wait :        Duration := Forever);
    function Read (Pipe : Handle; Max_Wait : Duration := Forever)
                  return Byte_String;
    -- These operations are "record (message) oriented".  That is, the write
    -- operation puts one record into the pipe which remembers the record and
    -- its length.  When successful, the read operation reads exactly one
    -- record (when unsuccessful, it reads 0 records), the Length out parameter
    -- indicates the actual length of the record (as given by the corresponding
    -- Write operation).
    -- This is in contrast with the Device_Independent_Io (Dio) Byte_String
    -- operations which are "stream oriented".  That is, the read operation
    -- returns exactly the number of bytes that are requested, unless
    -- end-of-file is reached, in which case fewer bytes are returned, as
    -- indicated by the Length out parameter.
    -- Given that pipes are record oriented, it is possible to write a program
    -- which reads messages from a pipe, and copies them or sends them
    -- somewhere else, without regard for the actual type of the data, and
    -- preserving message boundaries.
    -- The Read function is the same as the Read procedure except that it
    -- internally allocates a Byte_String (of the length specified by the
    -- Reader_Buffer_Size parameter of Create/Open) in which to read the
    -- message, and then returns the first Length bytes.  For variable length
    -- messages, this frees the client (of this package) from needing to know
    -- the maximum message size.  In the current implementation, this
    -- convenience is not free: the function makes an additional copy of the
    -- message (as compared to the procedure), and it allocates
    -- Reader_Buffer_Size - Length extra bytes in its stack frame. Of course,
    -- if the function call site simply assigns the result into some variable,
    -- there is an additional copy (as compared to the procedure).
    -- Read and Write operations are atomic with respect to each other.  BUT,
    -- This DOES NOT include multiple tasks reading/writing with the same
    -- Handle.
    -- Messages are passed by value.  That is, once Write completes, the entire
    -- message is stored within the pipe.  Termination of the client (which
    -- performed the Write) does not effect the state of the pipe.
    -- Recall that a pipe has finite internal buffer capability.  A Write
    -- operation which would exceed the maximum buffer size (defined at pipe
    -- creation time) always raises Use_Error (and extended status
    -- Item_Too_Big).  A Write operation which would exceed the remaining
    -- buffer capacity is handled as follows: If Max_Wait time expires before
    -- sufficient room becomes available in the buffer (this is immediately
    -- true if Max_Wait = Dont_Wait), then raises Use_Error (and extended
    -- status No_Room_In_Buffer).  When Use_Error is raised, the pipe is left
    -- unmodified (except for overrun notification, as discussed below).  The
    -- client can distinguish between these flavors of Use_Error via the
    -- Get_Extended_Status operation, below.
    -- In the event that there are multiple clients waiting to do Write, they
    -- are typically serviced FIFO in order to avoid starvation.
    -- Similarly, a Read operation specifies the maximum amount of time to
    -- wait for the buffer to become non-empty.  A time of 0 indicates that the
    -- client does not want to wait at all.  If the wait time expires before a
    -- message is received by the client, then the client gets Use_Error, and
    -- the pipe is left unchanged.
    -- The Read operation returns a single message.  The Length parameter
    -- indicates the actual number of bytes written into the Message parameter.
    -- In the event that the actual message (supplied by the corresponding
    -- Write operation) was longer than the Message parameter supplied to Read,
    -- the client will receive Data_Error (and extended status of
    -- Item_Too_Big), and the contents of the pipe are left unchanged.  In
    -- future implementations, negative values of Length may be defined.
    -- Recall that each message is read by exactly one Read operation; thus, in
    -- the face of concurrent Reads, each client may see just a subset of the
    -- messages that were written to the pipe.
    -- In the event that there are multiple clients waiting to do Read, they
    -- are typically serviced LIFO.  We assume that the application considers
    -- all readers to be equivalent.  In this context, LIFO is better than FIFO
    -- because it minimizes the working set of the readers.  (LIFO causes the
    -- reader which most recently finished working to be the next to receive a
    -- message).  This simplifies applications which need to choose the number
    -- of readers; they can simply pick the maximum number of readers which can
    -- operate in parallel.
    -- The implementation of Read and Write waiting can handle aborts of
    -- clients.
    -- Specifying infinite wait times allows one to use the finite buffer
    -- capacity as a flow control mechanism.
    -- "end of file" (eof) messages are written into a pipe via the
    -- Write_End_Of_File operation, and implicitly via Close (which itself may
    -- be implicit via action abandon, which itself may be implicit ...).  When
    -- a Read operation encounters an eof message, it is consumed, and
    -- End_Error is raised.  Unlike other sequential media, one can read an
    -- eof only once.
    -- "Overrun" refers to a situation in which the writer does not wait
    -- forever for buffer space to become available and drops the unsent
    -- messages on the floor.  Pipes include the following mechanism for
    -- detecting overrun:
    -- In addition to messages of type data and eof, there are messages of type
    -- overrun.  A Write operation which raises Use_Error (because there is
    -- insufficient room in the buffer) appends a message of type overrun.
    -- Adjacent overrun messages are coalesced into a single overrun message.
    -- The Read operation consumes the overrun message (when encountered) and
    -- raises Use_Error.  Like eof, an overrun message can only be read once.
    -- Death of a client that has the pipe open for update may sometimes cause
    -- an overrun to be placed in the pipe.
    -- Observations: (1) The writer should probably not "poll" the pipe by
    -- using a short Max_Wait, since each unsuccessful attempt will append an
    -- overrun message, causing the reader to get a Use_Error.  (2) The reader
    -- can distinguish between timeout and overrun (both raise Use_Error) by
    -- using the Extended_Status function, below.
    -- EXCEPTIONS:
    --     Status_Error  : The given Handle is not open
    --     Mode_Error    : Write: Handle was Open'd for Exclusive_Read
    --                       or Shared_Read
    --                     Read: Handle was Open'd for Exclusive_Write
    --                       or Shared_Write
    --     Use_Error     : Write: Max_Wait expired,
    --                       or Message'length is larger than buffer size;
    --                     Read: Max_Wait expired,
    --                       or just consumed an overrun message
    --     Data_Error    : Read: Message'length is shorter than next message
    --                   : Read/Write: touching Message caused
    --                       Nonexistant_Page_Error
    --                   : Read: storing into Message caused
    --                       Write_To_Read_Only_Page
    --     End_Error     : Read: just consumed an end-of-file message
    --     Device_Error  : internal errors
    pragma Consume_Offset (4);
    generic
        type Element_Type is private;
    package Type_Specific_Operations is
        procedure Write (Pipe     : in out Handle;
                         Message  :        Element_Type;
                         Max_Wait :        Duration := Forever);
        procedure Read (Pipe     : in out Handle;
                        Message  : out    Element_Type;
                        Max_Wait :        Duration := Forever);
        function Read (Pipe : Handle; Max_Wait : Duration := Forever)
                      return Element_Type;
        pragma Consume_Offset;
    end Type_Specific_Operations;
    -- The usual "legal type for IO" rules apply to Element_Type. In
    -- particular, Element_Type cannot be (or contain) pointers or tasks.
    -- Both ends of the pipe should instantiate this package with the same
    -- type, else one will get implicit unchecked conversions, and might
    -- get Data_Error.
    -- The generic Write operation first normalizes the Message, converts the
    -- bits (of the Message) into a Byte_String (adding up to 7 bits of
    -- padding, as necessary), and then calls the non-generic Write.
    -- By normalize, we mean the following.  For record types, if the object is
    -- not constrained, allocate a constained instance of the object and copy
    -- the Message into the constrained copy.  Note that this is expensive,
    -- since it involves declaring collections and doing copies.  For array
    -- types, if the "bounds with object"ness of the Message is not the same as
    -- that of the Element_Type (argument to the generic), then a copy is made
    -- to convert the Message to the same boundedness as the Element_Type.
    -- The generic Read procedure calls the non-generic Read procedure to fetch
    -- the padded Byte_String, does an implicit unchecked conversion to
    -- Element_Type, and assigns it to the out parameter.
    -- The conversion may cause Data_Error to be raised when Element_Type is
    -- not "compatable" with the actual bits in the message; this might happen
    -- if the Write generic was instantiated with a different type than the
    -- Read generic, for example.  Some conditions that may cause
    -- incompatibility: The 'size of the result of the unchecked conversion
    -- (rounded to a byte) is not the same as the actual byte length of the
    -- received message. The Element_Type is unconstrained and the message is
    -- garbage (when interpreted according to Element_Type).
    -- The assignment follows Ada semantics, and may therefore fail for a
    -- variety of reasons, causing Data_Error. Some conditions that may cause
    -- the assignment to fail: Element_Type is an unconstrained array type
    -- (such as String), and the 'length of the string value in the buffer is
    -- not the same as the 'length of the Message out parameter.  The
    -- Element_Type is unconstrained and the message is garbage (when
    -- interpreted according to Element_Type).
    -- The generic Read function calls the non-generic Read function, does an
    -- implicit unchecked conversion to Element_Type, and returns the result.
    -- Data_Error may be raised when Element_Type is not "compatible" with the
    -- actual bits in the message, as for the Read procedure.
    -- EXCEPTIONS (in addition to those raised by the non-generic forms):
    --     Data_Error    : Read: bits in the actual message are not
    --                         "compatible" with Element_Type, or := failed.
    --                     Pkg instantiation: raised when Element_Type has
    --                         task or access/heap_access components.
    function End_Of_File (Pipe : Handle) return Boolean;
    -- Returns true iff a read operation would have caused End_Error to be
    -- raised.
    -- EXCEPTIONS:
    --     Status_Error  : The given Handle is not open
    --     Device_Error  : internal errors
    procedure Write_End_Of_File (Pipe     : in out Handle;
                                 Max_Wait :        Duration := Forever);
    -- Puts an end-of-file message into the pipe.  Note that Close (of a pipe
    -- open for writing) may implicitly call this procedure.  Abandoning
    -- an action (of a writer) may implicitly call this procedure.  With
    -- respect to overruns, this call follows rules given for Write.
    -- EXCEPTIONS:
    --     Status_Error  : The given Handle is not open
    --     Use_Error     : Max_Wait expired,
    --                       or Message'length is larger than buffer size;
    --     Device_Error  : internal errors
    function Current_Message_Count (Pipe : Handle) return Natural;
    -- Can be used to "poll" a pipe to see how many messages are queued up,
    -- waiting to be read.
    -- EXCEPTIONS:
    --     Status_Error  : The given Handle is not open
    function Max_Buffer_Size (Pipe : Handle) return Positive;
    -- Return the buffer size of an open pipe.
    -- EXCEPTIONS:
    --     Status_Error  : The given Handle is not open
    function Open_Action (Pipe : Handle) return Action_Id;
    -- Returns the action by which the Handle has the pipe open.
    -- EXCEPTIONS:
    --     Status_Error  : The given Handle is not open
    pragma Consume_Offset (3);
    type Full_Status_Kinds is
       (Pipe_Status, Directory_Error_Status,
        Directory_Name_Status, Manager_Status, U4, U5, U6, U7);
    function Get_Full_Status_Kind (Pipe : Handle) return Full_Status_Kinds;
    -- Defined iff the Handle is currently open and the last PROCEDURE call on
    -- the Handle raised an exception and the following table indicates that
    -- additional status is available.
    --      Status_Error no additional status
    --      Mode_Error no additional status
    --      Name_Error more status available
    --      Use_Error more status available
    --      Device_Error more status available
    --      End_Error more status available
    --      Data_Error more status available
    --      Layout_Error no additional status In this case, indicates which
    -- kind of additional status information is available about the exception.
    type Extended_Status is (Internal_Pipe_Error, Item_Too_Big,
                             No_Room_In_Buffer, Buffer_Is_Empty,
                             Behind_Other_Readers, Read_An_Eof, Read_An_Overrun,
                             Missing_Page, Read_Only_Page, U09,
                             U10, U11, U12, U13, U14, U15, U16);
    function Get_Extended_Status        (Pipe : Handle) return Extended_Status;
    function Get_Directory_Error_Status (Pipe : Handle) return Integer;
    function Get_Directory_Name_Status  (Pipe : Handle) return Integer;
    function Get_Manager_Status         (Pipe : Handle) return Operate_Status;
    -- The above are defined iff Get_Full_Status_Kind is defined and returns
    -- the corresponding value of Full_Status_Kinds. Rational reserves the
    -- right to add additional Extended_Status values. Otherwise, it's ok
    -- to program against Extended_Status values. The integer values returned
    -- by the last 3 functions are for debugging only, and may change between
    -- between releases of this software.
    function Status_Explanation (Pipe : Handle) return String;
    -- Returns, in string form, the best explanation of the status that is
    -- currently available.  This explanation may include additional internal
    -- state information.  The returned string may differ between releases of
    -- this software.
    generic
        with procedure Put_Line (S : String);
    procedure Put_Pipe_Internal_State (Pipe      : Handle;
                                       Depth     : Natural := 25;
                                       Get_Locks : Boolean := False);
    generic
        with procedure Put_Line (S : String);
    procedure Put_Internal_State (Depth     : Natural := 25;
                                  Get_Locks : Boolean := False);
    -- These operations are primarily intended for use as debugging
    -- aids by Rational personnel.  However, it is also possible for customers
    -- to use this information to debug their applications.  The format of the
    -- of the information fed through Put_Line may change in future releases.
    -- The first operation gives you more information if the Handle is for an
    -- open pipe!  Depth is used to keep various algorithms from going into an
    -- infinite loop when the internal data structures for the pipe are
    -- inconsistent.  Get_Locks indicates whether or not the internal data
    -- structures should be viewed from within the appropriate critical
    -- regions; in the current implementation, only the default is supported.
    -- These operations are primarily intended for use as debugging
    -- aids by Rational personnel.  However, it is also possible for customers
    -- to use this information to debug their applications.  The format of the
    -- of the information fed through Put_Line may change in future releases.
    -- The first operation gives you more information if the Handle is for an
    -- open pipe!  Depth is used to keep various algorithms from going into an
    -- infinite loop when the internal data structures for the pipe are
    -- inconsistent.  Get_Locks indicates whether or not the internal data
    -- structures should be viewed from within the appropriate critical
    -- regions; in the current implementation, only the default is supported.
    function Debug_Image (Pipe            : Handle;
                          Level           : Natural;
                          Prefix          : String;
                          Expand_Pointers : Boolean) return String;
    --
    -- Daemon control.  The interval specifies how often the pipe daemon
    -- runs.  It defaults to every 30 seconds at low CPU priority.
    --
    -- Run_Daemon will cause the daemon to run at the priority of the
    -- calling task.  Note that this might actually cause the daemon
    -- to run twice if it is currently scheduled and blocked, since it
    -- has to finish (at the low priority) before this call can run it.
    function Get_Daemon_Interval return Duration;
    procedure Set_Daemon_Interval (Interval : Duration);
    procedure Run_Daemon;
    pragma Subsystem (Input_Output, Private_Part => Closed);
    pragma Module_Name (4, 3223);
end Pipe;