Specification of package Corba_Ios







 ========================================================================= --
 ===                                                                   === --
 ===                 Top Graph'X CORBA Implementation                  === --
 ===                                                                   === --
 ===                 Copyright (c) 1996, Top Graph'X.                  === --
 ===                                                                   === --
 ===                     --- Copyright Notice ---                      === --
 ===                                                                   === --
 ===    This software is protected as an unpublished work under the    === --
 ===     Copyright Act of 1976.  All rights reserved.  Top Graph'X.    === --
 ===                                                                   === --
 ========================================================================= --

with System ;
with Ada.Finalization ;

with Tgx.Atomic ;
with Tgx.Ios ;
package Corba_Ios is
   Is_Little_Endian : constant Boolean := System."="
      (System.Default_Bit_Order, System.Low_Order_First) ;
   Is_Big_Endian    : constant Boolean := System."="
      (System.Default_Bit_Order, System.High_Order_First) ;

   Increment : constant := 64 ;

   type Stream_Element is mod 2 ** 8 ;
   type Stream_Element_Offset is mod 2**32 ;
   for Stream_Element_Offset'size use 32 ;
   subtype Stream_Element_Count is Stream_Element_Offset ;
   type Stream_Element_Array is array (Stream_Element_Count range <>) of
      Stream_Element ;

   type Stream_Element_Table is access all Stream_Element_Array ;
   type Stream_Elements is access constant Stream_Element_Array ;

   type Iop_Stream_Type ;
   type Iop_Stream_Access is access all Iop_Stream_Type ;

   procedure Stream_Element_Array_Read
      ( Stream : access Iop_Stream_Type ;
        Item   : out Stream_Element_Array ) ;

   procedure Stream_Element_Array_Write
      ( Stream : access Iop_Stream_Type ;
        Item   : in Stream_Element_Array ) ;

   procedure Swap_2 ( Data   : in out Stream_Element_Array ;
                      Offset : in Stream_Element_Offset ) ;

   procedure Swap_4 ( Data   : in out Stream_Element_Array ;
                      Offset : in Stream_Element_Offset ) ;

   procedure Swap_8 ( Data   : in out Stream_Element_Array ;
                      Offset : in Stream_Element_Offset ) ;

   procedure Swap_16 ( Data   : in out Stream_Element_Array ;
                       Offset : in Stream_Element_Offset ) ;

    pragma Inline (Swap_2, Swap_4, Swap_8, Swap_16) ;

   type Reference_Count is new Tgx.Atomic.Count ;
   type Stream_Data_Record (Length : Stream_Element_Count) is
   record
      Used      : Stream_Element_Count := 0 ;
      Ref_Count : aliased Reference_Count := 1 ;
      Bytes     : aliased Stream_Element_Array (1 .. Length) ;
   end record ;

   type Stream_Data is access all Stream_Data_Record ;

   function Allocate (Length : in Stream_Element_Count) return Stream_Data ;
   procedure Dispose (Data : in out Stream_Data) ;

   type Controlled_Stream is new Ada.Finalization.Controlled with
   record
      Data : Stream_Data ;
   end record ;

      pragma Finalize_Storage_Only (Controlled_Stream) ;

    For CORBA encapsulations (first four bytes should be the byte count)
   procedure Controlled_Stream_Read
      ( Stream : access Iop_Stream_Type ;
        Item   : in out Controlled_Stream ) ;

   procedure Controlled_Stream_Write
      ( Stream : access Iop_Stream_Type ;
        Item   : in Controlled_Stream ) ;

   procedure Adjust (Object : in out Controlled_Stream) ;
   procedure Finalize (Object : in out Controlled_Stream) ;

   Null_Controlled_Stream : constant Controlled_Stream :=
      (Ada.Finalization.Controlled with Data => null) ;

    To store value information for indirect offset purposes
   type Value_Address is
   record
      Ptr : System.Address ;  Value implementation address
      Idx : Stream_Element_Count ;  Offset of marshaled value in the stream 
   end record ;

   type Value_Address_Array is array (Positive range <>) of Value_Address ;
   type Value_Address_Table is access all Value_Address_Array ;

   type Unsigned_32 is mod 2**32 ;
   for Unsigned_32'size use 32 ;

   type Iop_Stream_Type is
   record
      Swap    : Boolean := False ;  Does bytes need swapping
      Local   : Boolean := False ;  Is this stream used for a local call
      Chunked : Boolean := False ;  Is current value chunked
      Version : Natural := 258 ;  GIOP version to be used
      Level   : Natural := 0 ;  Imbrication level of current value
      V_Num   : Natural := 0 ;  Number of stored value addresses
      C_Start : Stream_Element_Count := 0;  Chunk size index
      C_End   : Stream_Element_Count := 0;  Chunk end index
      Values  : Value_Address_Table ;  List of stored value addresses
      Used    : Stream_Element_Count := 0;  Elements written count
      Index   : Stream_Element_Count := 0;  Elements read count
      Req_Id  : Unsigned_32 := 0 ;  Request Id
      Orb     : Unsigned_32 := 0 ;  Orb used
      Service : Integer := 0 ;  Orb service used
      Channel : Tgx.Ios.Io_Connection_Access ;  Connection used by the stream
      Items   : Controlled_Stream ;  Data bytes
   end record ;

   procedure Read_Align ( Stream : access Iop_Stream_Type ;
                          At_Mod : in Stream_Element_Offset ) ;

   procedure Write_Align ( Stream : access Iop_Stream_Type ;
                           At_Mod : in Stream_Element_Offset ) ;

   procedure Extend ( Stream : access Iop_Stream_Type ;
                      Bytes  : in Stream_Element_Count ) ;

   procedure Update_Value_Index ( Stream : access Iop_Stream_Type ;
                                  Value  : in System.Address ;
                                  Index  : in out Stream_Element_Count) ;

   function Get_Value
      ( Stream : access Iop_Stream_Type ;
        Offset : in Stream_Element_Offset) return System.Address ;

   procedure Clean (Stream : access Iop_Stream_Type) ;

   procedure Memcpy ( Target : in System.Address ;
                      Source : in System.Address ;
                      Num    : in Stream_Element_Count) ;
   pragma Import (C, Memcpy, "memcpy") ;

end Corba_Ios ;




List of definition uses










This page was generated by PrismTech's ada2html on Friday Mai 12 2006 16:18