Home | History | Annotate | Line # | Download | only in ada
      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 --  Continuous test for ZLib multithreading. If the test would fail
      9      1.1  christos --  we should provide thread safe allocation routines for the Z_Stream.
     10      1.1  christos --
     11  1.1.1.3  christos --  Id: mtest.adb,v 1.4 2004/07/23 07:49:54 vagul Exp 
     12      1.1  christos 
     13      1.1  christos with ZLib;
     14      1.1  christos with Ada.Streams;
     15      1.1  christos with Ada.Numerics.Discrete_Random;
     16      1.1  christos with Ada.Text_IO;
     17      1.1  christos with Ada.Exceptions;
     18      1.1  christos with Ada.Task_Identification;
     19      1.1  christos 
     20      1.1  christos procedure MTest is
     21      1.1  christos    use Ada.Streams;
     22      1.1  christos    use ZLib;
     23      1.1  christos 
     24      1.1  christos    Stop : Boolean := False;
     25      1.1  christos 
     26      1.1  christos    pragma Atomic (Stop);
     27      1.1  christos 
     28      1.1  christos    subtype Visible_Symbols is Stream_Element range 16#20# .. 16#7E#;
     29      1.1  christos 
     30      1.1  christos    package Random_Elements is
     31      1.1  christos       new Ada.Numerics.Discrete_Random (Visible_Symbols);
     32      1.1  christos 
     33      1.1  christos    task type Test_Task;
     34      1.1  christos 
     35      1.1  christos    task body Test_Task is
     36      1.1  christos       Buffer : Stream_Element_Array (1 .. 100_000);
     37      1.1  christos       Gen : Random_Elements.Generator;
     38      1.1  christos 
     39      1.1  christos       Buffer_First  : Stream_Element_Offset;
     40      1.1  christos       Compare_First : Stream_Element_Offset;
     41      1.1  christos 
     42      1.1  christos       Deflate : Filter_Type;
     43      1.1  christos       Inflate : Filter_Type;
     44      1.1  christos 
     45      1.1  christos       procedure Further (Item : in Stream_Element_Array);
     46      1.1  christos 
     47      1.1  christos       procedure Read_Buffer
     48      1.1  christos         (Item : out Ada.Streams.Stream_Element_Array;
     49      1.1  christos          Last : out Ada.Streams.Stream_Element_Offset);
     50      1.1  christos 
     51      1.1  christos       -------------
     52      1.1  christos       -- Further --
     53      1.1  christos       -------------
     54      1.1  christos 
     55      1.1  christos       procedure Further (Item : in Stream_Element_Array) is
     56      1.1  christos 
     57      1.1  christos          procedure Compare (Item : in Stream_Element_Array);
     58      1.1  christos 
     59      1.1  christos          -------------
     60      1.1  christos          -- Compare --
     61      1.1  christos          -------------
     62      1.1  christos 
     63      1.1  christos          procedure Compare (Item : in Stream_Element_Array) is
     64      1.1  christos             Next_First : Stream_Element_Offset := Compare_First + Item'Length;
     65      1.1  christos          begin
     66      1.1  christos             if Buffer (Compare_First .. Next_First - 1) /= Item then
     67      1.1  christos                raise Program_Error;
     68      1.1  christos             end if;
     69      1.1  christos 
     70      1.1  christos             Compare_First := Next_First;
     71      1.1  christos          end Compare;
     72      1.1  christos 
     73      1.1  christos          procedure Compare_Write is new ZLib.Write (Write => Compare);
     74      1.1  christos       begin
     75      1.1  christos          Compare_Write (Inflate, Item, No_Flush);
     76      1.1  christos       end Further;
     77      1.1  christos 
     78      1.1  christos       -----------------
     79      1.1  christos       -- Read_Buffer --
     80      1.1  christos       -----------------
     81      1.1  christos 
     82      1.1  christos       procedure Read_Buffer
     83      1.1  christos         (Item : out Ada.Streams.Stream_Element_Array;
     84      1.1  christos          Last : out Ada.Streams.Stream_Element_Offset)
     85      1.1  christos       is
     86      1.1  christos          Buff_Diff   : Stream_Element_Offset := Buffer'Last - Buffer_First;
     87      1.1  christos          Next_First : Stream_Element_Offset;
     88      1.1  christos       begin
     89      1.1  christos          if Item'Length <= Buff_Diff then
     90      1.1  christos             Last := Item'Last;
     91      1.1  christos 
     92      1.1  christos             Next_First := Buffer_First + Item'Length;
     93      1.1  christos 
     94      1.1  christos             Item := Buffer (Buffer_First .. Next_First - 1);
     95      1.1  christos 
     96      1.1  christos             Buffer_First := Next_First;
     97      1.1  christos          else
     98      1.1  christos             Last := Item'First + Buff_Diff;
     99      1.1  christos             Item (Item'First .. Last) := Buffer (Buffer_First .. Buffer'Last);
    100      1.1  christos             Buffer_First := Buffer'Last + 1;
    101      1.1  christos          end if;
    102      1.1  christos       end Read_Buffer;
    103      1.1  christos 
    104      1.1  christos       procedure Translate is new Generic_Translate
    105      1.1  christos                                    (Data_In  => Read_Buffer,
    106      1.1  christos                                     Data_Out => Further);
    107      1.1  christos 
    108      1.1  christos    begin
    109      1.1  christos       Random_Elements.Reset (Gen);
    110      1.1  christos 
    111      1.1  christos       Buffer := (others => 20);
    112      1.1  christos 
    113      1.1  christos       Main : loop
    114      1.1  christos          for J in Buffer'Range loop
    115      1.1  christos             Buffer (J) := Random_Elements.Random (Gen);
    116      1.1  christos 
    117      1.1  christos             Deflate_Init (Deflate);
    118      1.1  christos             Inflate_Init (Inflate);
    119      1.1  christos 
    120      1.1  christos             Buffer_First  := Buffer'First;
    121      1.1  christos             Compare_First := Buffer'First;
    122      1.1  christos 
    123      1.1  christos             Translate (Deflate);
    124      1.1  christos 
    125      1.1  christos             if Compare_First /= Buffer'Last + 1 then
    126      1.1  christos                raise Program_Error;
    127      1.1  christos             end if;
    128      1.1  christos 
    129      1.1  christos             Ada.Text_IO.Put_Line
    130      1.1  christos               (Ada.Task_Identification.Image
    131      1.1  christos                  (Ada.Task_Identification.Current_Task)
    132      1.1  christos                & Stream_Element_Offset'Image (J)
    133      1.1  christos                & ZLib.Count'Image (Total_Out (Deflate)));
    134      1.1  christos 
    135      1.1  christos             Close (Deflate);
    136      1.1  christos             Close (Inflate);
    137      1.1  christos 
    138      1.1  christos             exit Main when Stop;
    139      1.1  christos          end loop;
    140      1.1  christos       end loop Main;
    141      1.1  christos    exception
    142      1.1  christos       when E : others =>
    143      1.1  christos          Ada.Text_IO.Put_Line (Ada.Exceptions.Exception_Information (E));
    144      1.1  christos          Stop := True;
    145      1.1  christos    end Test_Task;
    146      1.1  christos 
    147      1.1  christos    Test : array (1 .. 4) of Test_Task;
    148      1.1  christos 
    149      1.1  christos    pragma Unreferenced (Test);
    150      1.1  christos 
    151      1.1  christos    Dummy : Character;
    152      1.1  christos 
    153      1.1  christos begin
    154      1.1  christos    Ada.Text_IO.Get_Immediate (Dummy);
    155      1.1  christos    Stop := True;
    156      1.1  christos end MTest;
    157