Home | History | Annotate | Line # | Download | only in ada
zlib-streams.ads revision 1.1.1.1.76.1
      1           1.1  christos ----------------------------------------------------------------
      2           1.1  christos --  ZLib for Ada thick binding.                               --
      3           1.1  christos --                                                            --
      4           1.1  christos --  Copyright (C) 2002-2003 Dmitriy Anisimkov                 --
      5           1.1  christos --                                                            --
      6           1.1  christos --  Open source license information is in the zlib.ads file.  --
      7           1.1  christos ----------------------------------------------------------------
      8           1.1  christos 
      9  1.1.1.1.76.1  pgoyette --  $Id: zlib-streams.ads,v 1.1.1.1.76.1 2017/03/20 06:51:33 pgoyette Exp $
     10           1.1  christos 
     11           1.1  christos package ZLib.Streams is
     12           1.1  christos 
     13           1.1  christos    type Stream_Mode is (In_Stream, Out_Stream, Duplex);
     14           1.1  christos 
     15           1.1  christos    type Stream_Access is access all Ada.Streams.Root_Stream_Type'Class;
     16           1.1  christos 
     17           1.1  christos    type Stream_Type is
     18           1.1  christos       new Ada.Streams.Root_Stream_Type with private;
     19           1.1  christos 
     20           1.1  christos    procedure Read
     21           1.1  christos      (Stream : in out Stream_Type;
     22           1.1  christos       Item   :    out Ada.Streams.Stream_Element_Array;
     23           1.1  christos       Last   :    out Ada.Streams.Stream_Element_Offset);
     24           1.1  christos 
     25           1.1  christos    procedure Write
     26           1.1  christos      (Stream : in out Stream_Type;
     27           1.1  christos       Item   : in     Ada.Streams.Stream_Element_Array);
     28           1.1  christos 
     29           1.1  christos    procedure Flush
     30           1.1  christos      (Stream : in out Stream_Type;
     31           1.1  christos       Mode   : in     Flush_Mode := Sync_Flush);
     32           1.1  christos    --  Flush the written data to the back stream,
     33           1.1  christos    --  all data placed to the compressor is flushing to the Back stream.
     34  1.1.1.1.76.1  pgoyette    --  Should not be used until necessary, because it is decreasing
     35           1.1  christos    --  compression.
     36           1.1  christos 
     37           1.1  christos    function Read_Total_In (Stream : in Stream_Type) return Count;
     38           1.1  christos    pragma Inline (Read_Total_In);
     39           1.1  christos    --  Return total number of bytes read from back stream so far.
     40           1.1  christos 
     41           1.1  christos    function Read_Total_Out (Stream : in Stream_Type) return Count;
     42           1.1  christos    pragma Inline (Read_Total_Out);
     43           1.1  christos    --  Return total number of bytes read so far.
     44           1.1  christos 
     45           1.1  christos    function Write_Total_In (Stream : in Stream_Type) return Count;
     46           1.1  christos    pragma Inline (Write_Total_In);
     47           1.1  christos    --  Return total number of bytes written so far.
     48           1.1  christos 
     49           1.1  christos    function Write_Total_Out (Stream : in Stream_Type) return Count;
     50           1.1  christos    pragma Inline (Write_Total_Out);
     51           1.1  christos    --  Return total number of bytes written to the back stream.
     52           1.1  christos 
     53           1.1  christos    procedure Create
     54           1.1  christos      (Stream            :    out Stream_Type;
     55           1.1  christos       Mode              : in     Stream_Mode;
     56           1.1  christos       Back              : in     Stream_Access;
     57           1.1  christos       Back_Compressed   : in     Boolean;
     58           1.1  christos       Level             : in     Compression_Level := Default_Compression;
     59           1.1  christos       Strategy          : in     Strategy_Type     := Default_Strategy;
     60           1.1  christos       Header            : in     Header_Type       := Default;
     61           1.1  christos       Read_Buffer_Size  : in     Ada.Streams.Stream_Element_Offset
     62           1.1  christos                                     := Default_Buffer_Size;
     63           1.1  christos       Write_Buffer_Size : in     Ada.Streams.Stream_Element_Offset
     64           1.1  christos                                     := Default_Buffer_Size);
     65           1.1  christos    --  Create the Comression/Decompression stream.
     66           1.1  christos    --  If mode is In_Stream then Write operation is disabled.
     67           1.1  christos    --  If mode is Out_Stream then Read operation is disabled.
     68           1.1  christos 
     69           1.1  christos    --  If Back_Compressed is true then
     70           1.1  christos    --  Data written to the Stream is compressing to the Back stream
     71           1.1  christos    --  and data read from the Stream is decompressed data from the Back stream.
     72           1.1  christos 
     73           1.1  christos    --  If Back_Compressed is false then
     74           1.1  christos    --  Data written to the Stream is decompressing to the Back stream
     75           1.1  christos    --  and data read from the Stream is compressed data from the Back stream.
     76           1.1  christos 
     77           1.1  christos    --  !!! When the Need_Header is False ZLib-Ada is using undocumented
     78           1.1  christos    --  ZLib 1.1.4 functionality to do not create/wait for ZLib headers.
     79           1.1  christos 
     80           1.1  christos    function Is_Open (Stream : Stream_Type) return Boolean;
     81           1.1  christos 
     82           1.1  christos    procedure Close (Stream : in out Stream_Type);
     83           1.1  christos 
     84           1.1  christos private
     85           1.1  christos 
     86           1.1  christos    use Ada.Streams;
     87           1.1  christos 
     88           1.1  christos    type Buffer_Access is access all Stream_Element_Array;
     89           1.1  christos 
     90           1.1  christos    type Stream_Type
     91           1.1  christos      is new Root_Stream_Type with
     92           1.1  christos    record
     93           1.1  christos       Mode       : Stream_Mode;
     94           1.1  christos 
     95           1.1  christos       Buffer     : Buffer_Access;
     96           1.1  christos       Rest_First : Stream_Element_Offset;
     97           1.1  christos       Rest_Last  : Stream_Element_Offset;
     98           1.1  christos       --  Buffer for Read operation.
     99           1.1  christos       --  We need to have this buffer in the record
    100  1.1.1.1.76.1  pgoyette       --  because not all read data from back stream
    101           1.1  christos       --  could be processed during the read operation.
    102           1.1  christos 
    103           1.1  christos       Buffer_Size : Stream_Element_Offset;
    104           1.1  christos       --  Buffer size for write operation.
    105           1.1  christos       --  We do not need to have this buffer
    106  1.1.1.1.76.1  pgoyette       --  in the record because all data could be
    107           1.1  christos       --  processed in the write operation.
    108           1.1  christos 
    109           1.1  christos       Back       : Stream_Access;
    110           1.1  christos       Reader     : Filter_Type;
    111           1.1  christos       Writer     : Filter_Type;
    112           1.1  christos    end record;
    113           1.1  christos 
    114           1.1  christos end ZLib.Streams;
    115