1275793eaSopenharmony_ci----------------------------------------------------------------
2275793eaSopenharmony_ci--  ZLib for Ada thick binding.                               --
3275793eaSopenharmony_ci--                                                            --
4275793eaSopenharmony_ci--  Copyright (C) 2002-2004 Dmitriy Anisimkov                 --
5275793eaSopenharmony_ci--                                                            --
6275793eaSopenharmony_ci--  Open source license information is in the zlib.ads file.  --
7275793eaSopenharmony_ci----------------------------------------------------------------
8275793eaSopenharmony_ci
9275793eaSopenharmony_ci--  $Id: zlib.adb,v 1.31 2004/09/06 06:53:19 vagul Exp $
10275793eaSopenharmony_ci
11275793eaSopenharmony_ciwith Ada.Exceptions;
12275793eaSopenharmony_ciwith Ada.Unchecked_Conversion;
13275793eaSopenharmony_ciwith Ada.Unchecked_Deallocation;
14275793eaSopenharmony_ci
15275793eaSopenharmony_ciwith Interfaces.C.Strings;
16275793eaSopenharmony_ci
17275793eaSopenharmony_ciwith ZLib.Thin;
18275793eaSopenharmony_ci
19275793eaSopenharmony_cipackage body ZLib is
20275793eaSopenharmony_ci
21275793eaSopenharmony_ci   use type Thin.Int;
22275793eaSopenharmony_ci
23275793eaSopenharmony_ci   type Z_Stream is new Thin.Z_Stream;
24275793eaSopenharmony_ci
25275793eaSopenharmony_ci   type Return_Code_Enum is
26275793eaSopenharmony_ci      (OK,
27275793eaSopenharmony_ci       STREAM_END,
28275793eaSopenharmony_ci       NEED_DICT,
29275793eaSopenharmony_ci       ERRNO,
30275793eaSopenharmony_ci       STREAM_ERROR,
31275793eaSopenharmony_ci       DATA_ERROR,
32275793eaSopenharmony_ci       MEM_ERROR,
33275793eaSopenharmony_ci       BUF_ERROR,
34275793eaSopenharmony_ci       VERSION_ERROR);
35275793eaSopenharmony_ci
36275793eaSopenharmony_ci   type Flate_Step_Function is access
37275793eaSopenharmony_ci     function (Strm : in Thin.Z_Streamp; Flush : in Thin.Int) return Thin.Int;
38275793eaSopenharmony_ci   pragma Convention (C, Flate_Step_Function);
39275793eaSopenharmony_ci
40275793eaSopenharmony_ci   type Flate_End_Function is access
41275793eaSopenharmony_ci      function (Ctrm : in Thin.Z_Streamp) return Thin.Int;
42275793eaSopenharmony_ci   pragma Convention (C, Flate_End_Function);
43275793eaSopenharmony_ci
44275793eaSopenharmony_ci   type Flate_Type is record
45275793eaSopenharmony_ci      Step : Flate_Step_Function;
46275793eaSopenharmony_ci      Done : Flate_End_Function;
47275793eaSopenharmony_ci   end record;
48275793eaSopenharmony_ci
49275793eaSopenharmony_ci   subtype Footer_Array is Stream_Element_Array (1 .. 8);
50275793eaSopenharmony_ci
51275793eaSopenharmony_ci   Simple_GZip_Header : constant Stream_Element_Array (1 .. 10)
52275793eaSopenharmony_ci     := (16#1f#, 16#8b#,                 --  Magic header
53275793eaSopenharmony_ci         16#08#,                         --  Z_DEFLATED
54275793eaSopenharmony_ci         16#00#,                         --  Flags
55275793eaSopenharmony_ci         16#00#, 16#00#, 16#00#, 16#00#, --  Time
56275793eaSopenharmony_ci         16#00#,                         --  XFlags
57275793eaSopenharmony_ci         16#03#                          --  OS code
58275793eaSopenharmony_ci        );
59275793eaSopenharmony_ci   --  The simplest gzip header is not for informational, but just for
60275793eaSopenharmony_ci   --  gzip format compatibility.
61275793eaSopenharmony_ci   --  Note that some code below is using assumption
62275793eaSopenharmony_ci   --  Simple_GZip_Header'Last > Footer_Array'Last, so do not make
63275793eaSopenharmony_ci   --  Simple_GZip_Header'Last <= Footer_Array'Last.
64275793eaSopenharmony_ci
65275793eaSopenharmony_ci   Return_Code : constant array (Thin.Int range <>) of Return_Code_Enum
66275793eaSopenharmony_ci     := (0 => OK,
67275793eaSopenharmony_ci         1 => STREAM_END,
68275793eaSopenharmony_ci         2 => NEED_DICT,
69275793eaSopenharmony_ci        -1 => ERRNO,
70275793eaSopenharmony_ci        -2 => STREAM_ERROR,
71275793eaSopenharmony_ci        -3 => DATA_ERROR,
72275793eaSopenharmony_ci        -4 => MEM_ERROR,
73275793eaSopenharmony_ci        -5 => BUF_ERROR,
74275793eaSopenharmony_ci        -6 => VERSION_ERROR);
75275793eaSopenharmony_ci
76275793eaSopenharmony_ci   Flate : constant array (Boolean) of Flate_Type
77275793eaSopenharmony_ci     := (True  => (Step => Thin.Deflate'Access,
78275793eaSopenharmony_ci                   Done => Thin.DeflateEnd'Access),
79275793eaSopenharmony_ci         False => (Step => Thin.Inflate'Access,
80275793eaSopenharmony_ci                   Done => Thin.InflateEnd'Access));
81275793eaSopenharmony_ci
82275793eaSopenharmony_ci   Flush_Finish : constant array (Boolean) of Flush_Mode
83275793eaSopenharmony_ci     := (True => Finish, False => No_Flush);
84275793eaSopenharmony_ci
85275793eaSopenharmony_ci   procedure Raise_Error (Stream : in Z_Stream);
86275793eaSopenharmony_ci   pragma Inline (Raise_Error);
87275793eaSopenharmony_ci
88275793eaSopenharmony_ci   procedure Raise_Error (Message : in String);
89275793eaSopenharmony_ci   pragma Inline (Raise_Error);
90275793eaSopenharmony_ci
91275793eaSopenharmony_ci   procedure Check_Error (Stream : in Z_Stream; Code : in Thin.Int);
92275793eaSopenharmony_ci
93275793eaSopenharmony_ci   procedure Free is new Ada.Unchecked_Deallocation
94275793eaSopenharmony_ci      (Z_Stream, Z_Stream_Access);
95275793eaSopenharmony_ci
96275793eaSopenharmony_ci   function To_Thin_Access is new Ada.Unchecked_Conversion
97275793eaSopenharmony_ci     (Z_Stream_Access, Thin.Z_Streamp);
98275793eaSopenharmony_ci
99275793eaSopenharmony_ci   procedure Translate_GZip
100275793eaSopenharmony_ci     (Filter    : in out Filter_Type;
101275793eaSopenharmony_ci      In_Data   : in     Ada.Streams.Stream_Element_Array;
102275793eaSopenharmony_ci      In_Last   :    out Ada.Streams.Stream_Element_Offset;
103275793eaSopenharmony_ci      Out_Data  :    out Ada.Streams.Stream_Element_Array;
104275793eaSopenharmony_ci      Out_Last  :    out Ada.Streams.Stream_Element_Offset;
105275793eaSopenharmony_ci      Flush     : in     Flush_Mode);
106275793eaSopenharmony_ci   --  Separate translate routine for make gzip header.
107275793eaSopenharmony_ci
108275793eaSopenharmony_ci   procedure Translate_Auto
109275793eaSopenharmony_ci     (Filter    : in out Filter_Type;
110275793eaSopenharmony_ci      In_Data   : in     Ada.Streams.Stream_Element_Array;
111275793eaSopenharmony_ci      In_Last   :    out Ada.Streams.Stream_Element_Offset;
112275793eaSopenharmony_ci      Out_Data  :    out Ada.Streams.Stream_Element_Array;
113275793eaSopenharmony_ci      Out_Last  :    out Ada.Streams.Stream_Element_Offset;
114275793eaSopenharmony_ci      Flush     : in     Flush_Mode);
115275793eaSopenharmony_ci   --  translate routine without additional headers.
116275793eaSopenharmony_ci
117275793eaSopenharmony_ci   -----------------
118275793eaSopenharmony_ci   -- Check_Error --
119275793eaSopenharmony_ci   -----------------
120275793eaSopenharmony_ci
121275793eaSopenharmony_ci   procedure Check_Error (Stream : in Z_Stream; Code : in Thin.Int) is
122275793eaSopenharmony_ci      use type Thin.Int;
123275793eaSopenharmony_ci   begin
124275793eaSopenharmony_ci      if Code /= Thin.Z_OK then
125275793eaSopenharmony_ci         Raise_Error
126275793eaSopenharmony_ci            (Return_Code_Enum'Image (Return_Code (Code))
127275793eaSopenharmony_ci              & ": " & Last_Error_Message (Stream));
128275793eaSopenharmony_ci      end if;
129275793eaSopenharmony_ci   end Check_Error;
130275793eaSopenharmony_ci
131275793eaSopenharmony_ci   -----------
132275793eaSopenharmony_ci   -- Close --
133275793eaSopenharmony_ci   -----------
134275793eaSopenharmony_ci
135275793eaSopenharmony_ci   procedure Close
136275793eaSopenharmony_ci     (Filter       : in out Filter_Type;
137275793eaSopenharmony_ci      Ignore_Error : in     Boolean := False)
138275793eaSopenharmony_ci   is
139275793eaSopenharmony_ci      Code : Thin.Int;
140275793eaSopenharmony_ci   begin
141275793eaSopenharmony_ci      if not Ignore_Error and then not Is_Open (Filter) then
142275793eaSopenharmony_ci         raise Status_Error;
143275793eaSopenharmony_ci      end if;
144275793eaSopenharmony_ci
145275793eaSopenharmony_ci      Code := Flate (Filter.Compression).Done (To_Thin_Access (Filter.Strm));
146275793eaSopenharmony_ci
147275793eaSopenharmony_ci      if Ignore_Error or else Code = Thin.Z_OK then
148275793eaSopenharmony_ci         Free (Filter.Strm);
149275793eaSopenharmony_ci      else
150275793eaSopenharmony_ci         declare
151275793eaSopenharmony_ci            Error_Message : constant String
152275793eaSopenharmony_ci              := Last_Error_Message (Filter.Strm.all);
153275793eaSopenharmony_ci         begin
154275793eaSopenharmony_ci            Free (Filter.Strm);
155275793eaSopenharmony_ci            Ada.Exceptions.Raise_Exception
156275793eaSopenharmony_ci               (ZLib_Error'Identity,
157275793eaSopenharmony_ci                Return_Code_Enum'Image (Return_Code (Code))
158275793eaSopenharmony_ci                  & ": " & Error_Message);
159275793eaSopenharmony_ci         end;
160275793eaSopenharmony_ci      end if;
161275793eaSopenharmony_ci   end Close;
162275793eaSopenharmony_ci
163275793eaSopenharmony_ci   -----------
164275793eaSopenharmony_ci   -- CRC32 --
165275793eaSopenharmony_ci   -----------
166275793eaSopenharmony_ci
167275793eaSopenharmony_ci   function CRC32
168275793eaSopenharmony_ci     (CRC  : in Unsigned_32;
169275793eaSopenharmony_ci      Data : in Ada.Streams.Stream_Element_Array)
170275793eaSopenharmony_ci      return Unsigned_32
171275793eaSopenharmony_ci   is
172275793eaSopenharmony_ci      use Thin;
173275793eaSopenharmony_ci   begin
174275793eaSopenharmony_ci      return Unsigned_32 (crc32 (ULong (CRC),
175275793eaSopenharmony_ci                                 Data'Address,
176275793eaSopenharmony_ci                                 Data'Length));
177275793eaSopenharmony_ci   end CRC32;
178275793eaSopenharmony_ci
179275793eaSopenharmony_ci   procedure CRC32
180275793eaSopenharmony_ci     (CRC  : in out Unsigned_32;
181275793eaSopenharmony_ci      Data : in     Ada.Streams.Stream_Element_Array) is
182275793eaSopenharmony_ci   begin
183275793eaSopenharmony_ci      CRC := CRC32 (CRC, Data);
184275793eaSopenharmony_ci   end CRC32;
185275793eaSopenharmony_ci
186275793eaSopenharmony_ci   ------------------
187275793eaSopenharmony_ci   -- Deflate_Init --
188275793eaSopenharmony_ci   ------------------
189275793eaSopenharmony_ci
190275793eaSopenharmony_ci   procedure Deflate_Init
191275793eaSopenharmony_ci     (Filter       : in out Filter_Type;
192275793eaSopenharmony_ci      Level        : in     Compression_Level  := Default_Compression;
193275793eaSopenharmony_ci      Strategy     : in     Strategy_Type      := Default_Strategy;
194275793eaSopenharmony_ci      Method       : in     Compression_Method := Deflated;
195275793eaSopenharmony_ci      Window_Bits  : in     Window_Bits_Type   := Default_Window_Bits;
196275793eaSopenharmony_ci      Memory_Level : in     Memory_Level_Type  := Default_Memory_Level;
197275793eaSopenharmony_ci      Header       : in     Header_Type        := Default)
198275793eaSopenharmony_ci   is
199275793eaSopenharmony_ci      use type Thin.Int;
200275793eaSopenharmony_ci      Win_Bits : Thin.Int := Thin.Int (Window_Bits);
201275793eaSopenharmony_ci   begin
202275793eaSopenharmony_ci      if Is_Open (Filter) then
203275793eaSopenharmony_ci         raise Status_Error;
204275793eaSopenharmony_ci      end if;
205275793eaSopenharmony_ci
206275793eaSopenharmony_ci      --  We allow ZLib to make header only in case of default header type.
207275793eaSopenharmony_ci      --  Otherwise we would either do header by ourselves, or do not do
208275793eaSopenharmony_ci      --  header at all.
209275793eaSopenharmony_ci
210275793eaSopenharmony_ci      if Header = None or else Header = GZip then
211275793eaSopenharmony_ci         Win_Bits := -Win_Bits;
212275793eaSopenharmony_ci      end if;
213275793eaSopenharmony_ci
214275793eaSopenharmony_ci      --  For the GZip CRC calculation and make headers.
215275793eaSopenharmony_ci
216275793eaSopenharmony_ci      if Header = GZip then
217275793eaSopenharmony_ci         Filter.CRC    := 0;
218275793eaSopenharmony_ci         Filter.Offset := Simple_GZip_Header'First;
219275793eaSopenharmony_ci      else
220275793eaSopenharmony_ci         Filter.Offset := Simple_GZip_Header'Last + 1;
221275793eaSopenharmony_ci      end if;
222275793eaSopenharmony_ci
223275793eaSopenharmony_ci      Filter.Strm        := new Z_Stream;
224275793eaSopenharmony_ci      Filter.Compression := True;
225275793eaSopenharmony_ci      Filter.Stream_End  := False;
226275793eaSopenharmony_ci      Filter.Header      := Header;
227275793eaSopenharmony_ci
228275793eaSopenharmony_ci      if Thin.Deflate_Init
229275793eaSopenharmony_ci           (To_Thin_Access (Filter.Strm),
230275793eaSopenharmony_ci            Level      => Thin.Int (Level),
231275793eaSopenharmony_ci            method     => Thin.Int (Method),
232275793eaSopenharmony_ci            windowBits => Win_Bits,
233275793eaSopenharmony_ci            memLevel   => Thin.Int (Memory_Level),
234275793eaSopenharmony_ci            strategy   => Thin.Int (Strategy)) /= Thin.Z_OK
235275793eaSopenharmony_ci      then
236275793eaSopenharmony_ci         Raise_Error (Filter.Strm.all);
237275793eaSopenharmony_ci      end if;
238275793eaSopenharmony_ci   end Deflate_Init;
239275793eaSopenharmony_ci
240275793eaSopenharmony_ci   -----------
241275793eaSopenharmony_ci   -- Flush --
242275793eaSopenharmony_ci   -----------
243275793eaSopenharmony_ci
244275793eaSopenharmony_ci   procedure Flush
245275793eaSopenharmony_ci     (Filter    : in out Filter_Type;
246275793eaSopenharmony_ci      Out_Data  :    out Ada.Streams.Stream_Element_Array;
247275793eaSopenharmony_ci      Out_Last  :    out Ada.Streams.Stream_Element_Offset;
248275793eaSopenharmony_ci      Flush     : in     Flush_Mode)
249275793eaSopenharmony_ci   is
250275793eaSopenharmony_ci      No_Data : Stream_Element_Array := (1 .. 0 => 0);
251275793eaSopenharmony_ci      Last    : Stream_Element_Offset;
252275793eaSopenharmony_ci   begin
253275793eaSopenharmony_ci      Translate (Filter, No_Data, Last, Out_Data, Out_Last, Flush);
254275793eaSopenharmony_ci   end Flush;
255275793eaSopenharmony_ci
256275793eaSopenharmony_ci   -----------------------
257275793eaSopenharmony_ci   -- Generic_Translate --
258275793eaSopenharmony_ci   -----------------------
259275793eaSopenharmony_ci
260275793eaSopenharmony_ci   procedure Generic_Translate
261275793eaSopenharmony_ci     (Filter          : in out ZLib.Filter_Type;
262275793eaSopenharmony_ci      In_Buffer_Size  : in     Integer := Default_Buffer_Size;
263275793eaSopenharmony_ci      Out_Buffer_Size : in     Integer := Default_Buffer_Size)
264275793eaSopenharmony_ci   is
265275793eaSopenharmony_ci      In_Buffer  : Stream_Element_Array
266275793eaSopenharmony_ci                     (1 .. Stream_Element_Offset (In_Buffer_Size));
267275793eaSopenharmony_ci      Out_Buffer : Stream_Element_Array
268275793eaSopenharmony_ci                     (1 .. Stream_Element_Offset (Out_Buffer_Size));
269275793eaSopenharmony_ci      Last       : Stream_Element_Offset;
270275793eaSopenharmony_ci      In_Last    : Stream_Element_Offset;
271275793eaSopenharmony_ci      In_First   : Stream_Element_Offset;
272275793eaSopenharmony_ci      Out_Last   : Stream_Element_Offset;
273275793eaSopenharmony_ci   begin
274275793eaSopenharmony_ci      Main : loop
275275793eaSopenharmony_ci         Data_In (In_Buffer, Last);
276275793eaSopenharmony_ci
277275793eaSopenharmony_ci         In_First := In_Buffer'First;
278275793eaSopenharmony_ci
279275793eaSopenharmony_ci         loop
280275793eaSopenharmony_ci            Translate
281275793eaSopenharmony_ci              (Filter   => Filter,
282275793eaSopenharmony_ci               In_Data  => In_Buffer (In_First .. Last),
283275793eaSopenharmony_ci               In_Last  => In_Last,
284275793eaSopenharmony_ci               Out_Data => Out_Buffer,
285275793eaSopenharmony_ci               Out_Last => Out_Last,
286275793eaSopenharmony_ci               Flush    => Flush_Finish (Last < In_Buffer'First));
287275793eaSopenharmony_ci
288275793eaSopenharmony_ci            if Out_Buffer'First <= Out_Last then
289275793eaSopenharmony_ci               Data_Out (Out_Buffer (Out_Buffer'First .. Out_Last));
290275793eaSopenharmony_ci            end if;
291275793eaSopenharmony_ci
292275793eaSopenharmony_ci            exit Main when Stream_End (Filter);
293275793eaSopenharmony_ci
294275793eaSopenharmony_ci            --  The end of in buffer.
295275793eaSopenharmony_ci
296275793eaSopenharmony_ci            exit when In_Last = Last;
297275793eaSopenharmony_ci
298275793eaSopenharmony_ci            In_First := In_Last + 1;
299275793eaSopenharmony_ci         end loop;
300275793eaSopenharmony_ci      end loop Main;
301275793eaSopenharmony_ci
302275793eaSopenharmony_ci   end Generic_Translate;
303275793eaSopenharmony_ci
304275793eaSopenharmony_ci   ------------------
305275793eaSopenharmony_ci   -- Inflate_Init --
306275793eaSopenharmony_ci   ------------------
307275793eaSopenharmony_ci
308275793eaSopenharmony_ci   procedure Inflate_Init
309275793eaSopenharmony_ci     (Filter      : in out Filter_Type;
310275793eaSopenharmony_ci      Window_Bits : in     Window_Bits_Type := Default_Window_Bits;
311275793eaSopenharmony_ci      Header      : in     Header_Type      := Default)
312275793eaSopenharmony_ci   is
313275793eaSopenharmony_ci      use type Thin.Int;
314275793eaSopenharmony_ci      Win_Bits : Thin.Int := Thin.Int (Window_Bits);
315275793eaSopenharmony_ci
316275793eaSopenharmony_ci      procedure Check_Version;
317275793eaSopenharmony_ci      --  Check the latest header types compatibility.
318275793eaSopenharmony_ci
319275793eaSopenharmony_ci      procedure Check_Version is
320275793eaSopenharmony_ci      begin
321275793eaSopenharmony_ci         if Version <= "1.1.4" then
322275793eaSopenharmony_ci            Raise_Error
323275793eaSopenharmony_ci              ("Inflate header type " & Header_Type'Image (Header)
324275793eaSopenharmony_ci               & " incompatible with ZLib version " & Version);
325275793eaSopenharmony_ci         end if;
326275793eaSopenharmony_ci      end Check_Version;
327275793eaSopenharmony_ci
328275793eaSopenharmony_ci   begin
329275793eaSopenharmony_ci      if Is_Open (Filter) then
330275793eaSopenharmony_ci         raise Status_Error;
331275793eaSopenharmony_ci      end if;
332275793eaSopenharmony_ci
333275793eaSopenharmony_ci      case Header is
334275793eaSopenharmony_ci         when None =>
335275793eaSopenharmony_ci            Check_Version;
336275793eaSopenharmony_ci
337275793eaSopenharmony_ci            --  Inflate data without headers determined
338275793eaSopenharmony_ci            --  by negative Win_Bits.
339275793eaSopenharmony_ci
340275793eaSopenharmony_ci            Win_Bits := -Win_Bits;
341275793eaSopenharmony_ci         when GZip =>
342275793eaSopenharmony_ci            Check_Version;
343275793eaSopenharmony_ci
344275793eaSopenharmony_ci            --  Inflate gzip data defined by flag 16.
345275793eaSopenharmony_ci
346275793eaSopenharmony_ci            Win_Bits := Win_Bits + 16;
347275793eaSopenharmony_ci         when Auto =>
348275793eaSopenharmony_ci            Check_Version;
349275793eaSopenharmony_ci
350275793eaSopenharmony_ci            --  Inflate with automatic detection
351275793eaSopenharmony_ci            --  of gzip or native header defined by flag 32.
352275793eaSopenharmony_ci
353275793eaSopenharmony_ci            Win_Bits := Win_Bits + 32;
354275793eaSopenharmony_ci         when Default => null;
355275793eaSopenharmony_ci      end case;
356275793eaSopenharmony_ci
357275793eaSopenharmony_ci      Filter.Strm        := new Z_Stream;
358275793eaSopenharmony_ci      Filter.Compression := False;
359275793eaSopenharmony_ci      Filter.Stream_End  := False;
360275793eaSopenharmony_ci      Filter.Header      := Header;
361275793eaSopenharmony_ci
362275793eaSopenharmony_ci      if Thin.Inflate_Init
363275793eaSopenharmony_ci         (To_Thin_Access (Filter.Strm), Win_Bits) /= Thin.Z_OK
364275793eaSopenharmony_ci      then
365275793eaSopenharmony_ci         Raise_Error (Filter.Strm.all);
366275793eaSopenharmony_ci      end if;
367275793eaSopenharmony_ci   end Inflate_Init;
368275793eaSopenharmony_ci
369275793eaSopenharmony_ci   -------------
370275793eaSopenharmony_ci   -- Is_Open --
371275793eaSopenharmony_ci   -------------
372275793eaSopenharmony_ci
373275793eaSopenharmony_ci   function Is_Open (Filter : in Filter_Type) return Boolean is
374275793eaSopenharmony_ci   begin
375275793eaSopenharmony_ci      return Filter.Strm /= null;
376275793eaSopenharmony_ci   end Is_Open;
377275793eaSopenharmony_ci
378275793eaSopenharmony_ci   -----------------
379275793eaSopenharmony_ci   -- Raise_Error --
380275793eaSopenharmony_ci   -----------------
381275793eaSopenharmony_ci
382275793eaSopenharmony_ci   procedure Raise_Error (Message : in String) is
383275793eaSopenharmony_ci   begin
384275793eaSopenharmony_ci      Ada.Exceptions.Raise_Exception (ZLib_Error'Identity, Message);
385275793eaSopenharmony_ci   end Raise_Error;
386275793eaSopenharmony_ci
387275793eaSopenharmony_ci   procedure Raise_Error (Stream : in Z_Stream) is
388275793eaSopenharmony_ci   begin
389275793eaSopenharmony_ci      Raise_Error (Last_Error_Message (Stream));
390275793eaSopenharmony_ci   end Raise_Error;
391275793eaSopenharmony_ci
392275793eaSopenharmony_ci   ----------
393275793eaSopenharmony_ci   -- Read --
394275793eaSopenharmony_ci   ----------
395275793eaSopenharmony_ci
396275793eaSopenharmony_ci   procedure Read
397275793eaSopenharmony_ci     (Filter : in out Filter_Type;
398275793eaSopenharmony_ci      Item   :    out Ada.Streams.Stream_Element_Array;
399275793eaSopenharmony_ci      Last   :    out Ada.Streams.Stream_Element_Offset;
400275793eaSopenharmony_ci      Flush  : in     Flush_Mode := No_Flush)
401275793eaSopenharmony_ci   is
402275793eaSopenharmony_ci      In_Last    : Stream_Element_Offset;
403275793eaSopenharmony_ci      Item_First : Ada.Streams.Stream_Element_Offset := Item'First;
404275793eaSopenharmony_ci      V_Flush    : Flush_Mode := Flush;
405275793eaSopenharmony_ci
406275793eaSopenharmony_ci   begin
407275793eaSopenharmony_ci      pragma Assert (Rest_First in Buffer'First .. Buffer'Last + 1);
408275793eaSopenharmony_ci      pragma Assert (Rest_Last in Buffer'First - 1 .. Buffer'Last);
409275793eaSopenharmony_ci
410275793eaSopenharmony_ci      loop
411275793eaSopenharmony_ci         if Rest_Last = Buffer'First - 1 then
412275793eaSopenharmony_ci            V_Flush := Finish;
413275793eaSopenharmony_ci
414275793eaSopenharmony_ci         elsif Rest_First > Rest_Last then
415275793eaSopenharmony_ci            Read (Buffer, Rest_Last);
416275793eaSopenharmony_ci            Rest_First := Buffer'First;
417275793eaSopenharmony_ci
418275793eaSopenharmony_ci            if Rest_Last < Buffer'First then
419275793eaSopenharmony_ci               V_Flush := Finish;
420275793eaSopenharmony_ci            end if;
421275793eaSopenharmony_ci         end if;
422275793eaSopenharmony_ci
423275793eaSopenharmony_ci         Translate
424275793eaSopenharmony_ci           (Filter   => Filter,
425275793eaSopenharmony_ci            In_Data  => Buffer (Rest_First .. Rest_Last),
426275793eaSopenharmony_ci            In_Last  => In_Last,
427275793eaSopenharmony_ci            Out_Data => Item (Item_First .. Item'Last),
428275793eaSopenharmony_ci            Out_Last => Last,
429275793eaSopenharmony_ci            Flush    => V_Flush);
430275793eaSopenharmony_ci
431275793eaSopenharmony_ci         Rest_First := In_Last + 1;
432275793eaSopenharmony_ci
433275793eaSopenharmony_ci         exit when Stream_End (Filter)
434275793eaSopenharmony_ci           or else Last = Item'Last
435275793eaSopenharmony_ci           or else (Last >= Item'First and then Allow_Read_Some);
436275793eaSopenharmony_ci
437275793eaSopenharmony_ci         Item_First := Last + 1;
438275793eaSopenharmony_ci      end loop;
439275793eaSopenharmony_ci   end Read;
440275793eaSopenharmony_ci
441275793eaSopenharmony_ci   ----------------
442275793eaSopenharmony_ci   -- Stream_End --
443275793eaSopenharmony_ci   ----------------
444275793eaSopenharmony_ci
445275793eaSopenharmony_ci   function Stream_End (Filter : in Filter_Type) return Boolean is
446275793eaSopenharmony_ci   begin
447275793eaSopenharmony_ci      if Filter.Header = GZip and Filter.Compression then
448275793eaSopenharmony_ci         return Filter.Stream_End
449275793eaSopenharmony_ci            and then Filter.Offset = Footer_Array'Last + 1;
450275793eaSopenharmony_ci      else
451275793eaSopenharmony_ci         return Filter.Stream_End;
452275793eaSopenharmony_ci      end if;
453275793eaSopenharmony_ci   end Stream_End;
454275793eaSopenharmony_ci
455275793eaSopenharmony_ci   --------------
456275793eaSopenharmony_ci   -- Total_In --
457275793eaSopenharmony_ci   --------------
458275793eaSopenharmony_ci
459275793eaSopenharmony_ci   function Total_In (Filter : in Filter_Type) return Count is
460275793eaSopenharmony_ci   begin
461275793eaSopenharmony_ci      return Count (Thin.Total_In (To_Thin_Access (Filter.Strm).all));
462275793eaSopenharmony_ci   end Total_In;
463275793eaSopenharmony_ci
464275793eaSopenharmony_ci   ---------------
465275793eaSopenharmony_ci   -- Total_Out --
466275793eaSopenharmony_ci   ---------------
467275793eaSopenharmony_ci
468275793eaSopenharmony_ci   function Total_Out (Filter : in Filter_Type) return Count is
469275793eaSopenharmony_ci   begin
470275793eaSopenharmony_ci      return Count (Thin.Total_Out (To_Thin_Access (Filter.Strm).all));
471275793eaSopenharmony_ci   end Total_Out;
472275793eaSopenharmony_ci
473275793eaSopenharmony_ci   ---------------
474275793eaSopenharmony_ci   -- Translate --
475275793eaSopenharmony_ci   ---------------
476275793eaSopenharmony_ci
477275793eaSopenharmony_ci   procedure Translate
478275793eaSopenharmony_ci     (Filter    : in out Filter_Type;
479275793eaSopenharmony_ci      In_Data   : in     Ada.Streams.Stream_Element_Array;
480275793eaSopenharmony_ci      In_Last   :    out Ada.Streams.Stream_Element_Offset;
481275793eaSopenharmony_ci      Out_Data  :    out Ada.Streams.Stream_Element_Array;
482275793eaSopenharmony_ci      Out_Last  :    out Ada.Streams.Stream_Element_Offset;
483275793eaSopenharmony_ci      Flush     : in     Flush_Mode) is
484275793eaSopenharmony_ci   begin
485275793eaSopenharmony_ci      if Filter.Header = GZip and then Filter.Compression then
486275793eaSopenharmony_ci         Translate_GZip
487275793eaSopenharmony_ci           (Filter   => Filter,
488275793eaSopenharmony_ci            In_Data  => In_Data,
489275793eaSopenharmony_ci            In_Last  => In_Last,
490275793eaSopenharmony_ci            Out_Data => Out_Data,
491275793eaSopenharmony_ci            Out_Last => Out_Last,
492275793eaSopenharmony_ci            Flush    => Flush);
493275793eaSopenharmony_ci      else
494275793eaSopenharmony_ci         Translate_Auto
495275793eaSopenharmony_ci           (Filter   => Filter,
496275793eaSopenharmony_ci            In_Data  => In_Data,
497275793eaSopenharmony_ci            In_Last  => In_Last,
498275793eaSopenharmony_ci            Out_Data => Out_Data,
499275793eaSopenharmony_ci            Out_Last => Out_Last,
500275793eaSopenharmony_ci            Flush    => Flush);
501275793eaSopenharmony_ci      end if;
502275793eaSopenharmony_ci   end Translate;
503275793eaSopenharmony_ci
504275793eaSopenharmony_ci   --------------------
505275793eaSopenharmony_ci   -- Translate_Auto --
506275793eaSopenharmony_ci   --------------------
507275793eaSopenharmony_ci
508275793eaSopenharmony_ci   procedure Translate_Auto
509275793eaSopenharmony_ci     (Filter    : in out Filter_Type;
510275793eaSopenharmony_ci      In_Data   : in     Ada.Streams.Stream_Element_Array;
511275793eaSopenharmony_ci      In_Last   :    out Ada.Streams.Stream_Element_Offset;
512275793eaSopenharmony_ci      Out_Data  :    out Ada.Streams.Stream_Element_Array;
513275793eaSopenharmony_ci      Out_Last  :    out Ada.Streams.Stream_Element_Offset;
514275793eaSopenharmony_ci      Flush     : in     Flush_Mode)
515275793eaSopenharmony_ci   is
516275793eaSopenharmony_ci      use type Thin.Int;
517275793eaSopenharmony_ci      Code : Thin.Int;
518275793eaSopenharmony_ci
519275793eaSopenharmony_ci   begin
520275793eaSopenharmony_ci      if not Is_Open (Filter) then
521275793eaSopenharmony_ci         raise Status_Error;
522275793eaSopenharmony_ci      end if;
523275793eaSopenharmony_ci
524275793eaSopenharmony_ci      if Out_Data'Length = 0 and then In_Data'Length = 0 then
525275793eaSopenharmony_ci         raise Constraint_Error;
526275793eaSopenharmony_ci      end if;
527275793eaSopenharmony_ci
528275793eaSopenharmony_ci      Set_Out (Filter.Strm.all, Out_Data'Address, Out_Data'Length);
529275793eaSopenharmony_ci      Set_In  (Filter.Strm.all, In_Data'Address, In_Data'Length);
530275793eaSopenharmony_ci
531275793eaSopenharmony_ci      Code := Flate (Filter.Compression).Step
532275793eaSopenharmony_ci        (To_Thin_Access (Filter.Strm),
533275793eaSopenharmony_ci         Thin.Int (Flush));
534275793eaSopenharmony_ci
535275793eaSopenharmony_ci      if Code = Thin.Z_STREAM_END then
536275793eaSopenharmony_ci         Filter.Stream_End := True;
537275793eaSopenharmony_ci      else
538275793eaSopenharmony_ci         Check_Error (Filter.Strm.all, Code);
539275793eaSopenharmony_ci      end if;
540275793eaSopenharmony_ci
541275793eaSopenharmony_ci      In_Last  := In_Data'Last
542275793eaSopenharmony_ci         - Stream_Element_Offset (Avail_In (Filter.Strm.all));
543275793eaSopenharmony_ci      Out_Last := Out_Data'Last
544275793eaSopenharmony_ci         - Stream_Element_Offset (Avail_Out (Filter.Strm.all));
545275793eaSopenharmony_ci   end Translate_Auto;
546275793eaSopenharmony_ci
547275793eaSopenharmony_ci   --------------------
548275793eaSopenharmony_ci   -- Translate_GZip --
549275793eaSopenharmony_ci   --------------------
550275793eaSopenharmony_ci
551275793eaSopenharmony_ci   procedure Translate_GZip
552275793eaSopenharmony_ci     (Filter    : in out Filter_Type;
553275793eaSopenharmony_ci      In_Data   : in     Ada.Streams.Stream_Element_Array;
554275793eaSopenharmony_ci      In_Last   :    out Ada.Streams.Stream_Element_Offset;
555275793eaSopenharmony_ci      Out_Data  :    out Ada.Streams.Stream_Element_Array;
556275793eaSopenharmony_ci      Out_Last  :    out Ada.Streams.Stream_Element_Offset;
557275793eaSopenharmony_ci      Flush     : in     Flush_Mode)
558275793eaSopenharmony_ci   is
559275793eaSopenharmony_ci      Out_First : Stream_Element_Offset;
560275793eaSopenharmony_ci
561275793eaSopenharmony_ci      procedure Add_Data (Data : in Stream_Element_Array);
562275793eaSopenharmony_ci      --  Add data to stream from the Filter.Offset till necessary,
563275793eaSopenharmony_ci      --  used for add gzip headr/footer.
564275793eaSopenharmony_ci
565275793eaSopenharmony_ci      procedure Put_32
566275793eaSopenharmony_ci        (Item : in out Stream_Element_Array;
567275793eaSopenharmony_ci         Data : in     Unsigned_32);
568275793eaSopenharmony_ci      pragma Inline (Put_32);
569275793eaSopenharmony_ci
570275793eaSopenharmony_ci      --------------
571275793eaSopenharmony_ci      -- Add_Data --
572275793eaSopenharmony_ci      --------------
573275793eaSopenharmony_ci
574275793eaSopenharmony_ci      procedure Add_Data (Data : in Stream_Element_Array) is
575275793eaSopenharmony_ci         Data_First : Stream_Element_Offset renames Filter.Offset;
576275793eaSopenharmony_ci         Data_Last  : Stream_Element_Offset;
577275793eaSopenharmony_ci         Data_Len   : Stream_Element_Offset; --  -1
578275793eaSopenharmony_ci         Out_Len    : Stream_Element_Offset; --  -1
579275793eaSopenharmony_ci      begin
580275793eaSopenharmony_ci         Out_First := Out_Last + 1;
581275793eaSopenharmony_ci
582275793eaSopenharmony_ci         if Data_First > Data'Last then
583275793eaSopenharmony_ci            return;
584275793eaSopenharmony_ci         end if;
585275793eaSopenharmony_ci
586275793eaSopenharmony_ci         Data_Len  := Data'Last     - Data_First;
587275793eaSopenharmony_ci         Out_Len   := Out_Data'Last - Out_First;
588275793eaSopenharmony_ci
589275793eaSopenharmony_ci         if Data_Len <= Out_Len then
590275793eaSopenharmony_ci            Out_Last  := Out_First  + Data_Len;
591275793eaSopenharmony_ci            Data_Last := Data'Last;
592275793eaSopenharmony_ci         else
593275793eaSopenharmony_ci            Out_Last  := Out_Data'Last;
594275793eaSopenharmony_ci            Data_Last := Data_First + Out_Len;
595275793eaSopenharmony_ci         end if;
596275793eaSopenharmony_ci
597275793eaSopenharmony_ci         Out_Data (Out_First .. Out_Last) := Data (Data_First .. Data_Last);
598275793eaSopenharmony_ci
599275793eaSopenharmony_ci         Data_First := Data_Last + 1;
600275793eaSopenharmony_ci         Out_First  := Out_Last + 1;
601275793eaSopenharmony_ci      end Add_Data;
602275793eaSopenharmony_ci
603275793eaSopenharmony_ci      ------------
604275793eaSopenharmony_ci      -- Put_32 --
605275793eaSopenharmony_ci      ------------
606275793eaSopenharmony_ci
607275793eaSopenharmony_ci      procedure Put_32
608275793eaSopenharmony_ci        (Item : in out Stream_Element_Array;
609275793eaSopenharmony_ci         Data : in     Unsigned_32)
610275793eaSopenharmony_ci      is
611275793eaSopenharmony_ci         D : Unsigned_32 := Data;
612275793eaSopenharmony_ci      begin
613275793eaSopenharmony_ci         for J in Item'First .. Item'First + 3 loop
614275793eaSopenharmony_ci            Item (J) := Stream_Element (D and 16#FF#);
615275793eaSopenharmony_ci            D := Shift_Right (D, 8);
616275793eaSopenharmony_ci         end loop;
617275793eaSopenharmony_ci      end Put_32;
618275793eaSopenharmony_ci
619275793eaSopenharmony_ci   begin
620275793eaSopenharmony_ci      Out_Last := Out_Data'First - 1;
621275793eaSopenharmony_ci
622275793eaSopenharmony_ci      if not Filter.Stream_End then
623275793eaSopenharmony_ci         Add_Data (Simple_GZip_Header);
624275793eaSopenharmony_ci
625275793eaSopenharmony_ci         Translate_Auto
626275793eaSopenharmony_ci           (Filter   => Filter,
627275793eaSopenharmony_ci            In_Data  => In_Data,
628275793eaSopenharmony_ci            In_Last  => In_Last,
629275793eaSopenharmony_ci            Out_Data => Out_Data (Out_First .. Out_Data'Last),
630275793eaSopenharmony_ci            Out_Last => Out_Last,
631275793eaSopenharmony_ci            Flush    => Flush);
632275793eaSopenharmony_ci
633275793eaSopenharmony_ci         CRC32 (Filter.CRC, In_Data (In_Data'First .. In_Last));
634275793eaSopenharmony_ci      end if;
635275793eaSopenharmony_ci
636275793eaSopenharmony_ci      if Filter.Stream_End and then Out_Last <= Out_Data'Last then
637275793eaSopenharmony_ci         --  This detection method would work only when
638275793eaSopenharmony_ci         --  Simple_GZip_Header'Last > Footer_Array'Last
639275793eaSopenharmony_ci
640275793eaSopenharmony_ci         if Filter.Offset = Simple_GZip_Header'Last + 1 then
641275793eaSopenharmony_ci            Filter.Offset := Footer_Array'First;
642275793eaSopenharmony_ci         end if;
643275793eaSopenharmony_ci
644275793eaSopenharmony_ci         declare
645275793eaSopenharmony_ci            Footer : Footer_Array;
646275793eaSopenharmony_ci         begin
647275793eaSopenharmony_ci            Put_32 (Footer, Filter.CRC);
648275793eaSopenharmony_ci            Put_32 (Footer (Footer'First + 4 .. Footer'Last),
649275793eaSopenharmony_ci                    Unsigned_32 (Total_In (Filter)));
650275793eaSopenharmony_ci            Add_Data (Footer);
651275793eaSopenharmony_ci         end;
652275793eaSopenharmony_ci      end if;
653275793eaSopenharmony_ci   end Translate_GZip;
654275793eaSopenharmony_ci
655275793eaSopenharmony_ci   -------------
656275793eaSopenharmony_ci   -- Version --
657275793eaSopenharmony_ci   -------------
658275793eaSopenharmony_ci
659275793eaSopenharmony_ci   function Version return String is
660275793eaSopenharmony_ci   begin
661275793eaSopenharmony_ci      return Interfaces.C.Strings.Value (Thin.zlibVersion);
662275793eaSopenharmony_ci   end Version;
663275793eaSopenharmony_ci
664275793eaSopenharmony_ci   -----------
665275793eaSopenharmony_ci   -- Write --
666275793eaSopenharmony_ci   -----------
667275793eaSopenharmony_ci
668275793eaSopenharmony_ci   procedure Write
669275793eaSopenharmony_ci     (Filter : in out Filter_Type;
670275793eaSopenharmony_ci      Item   : in     Ada.Streams.Stream_Element_Array;
671275793eaSopenharmony_ci      Flush  : in     Flush_Mode := No_Flush)
672275793eaSopenharmony_ci   is
673275793eaSopenharmony_ci      Buffer   : Stream_Element_Array (1 .. Buffer_Size);
674275793eaSopenharmony_ci      In_Last  : Stream_Element_Offset;
675275793eaSopenharmony_ci      Out_Last : Stream_Element_Offset;
676275793eaSopenharmony_ci      In_First : Stream_Element_Offset := Item'First;
677275793eaSopenharmony_ci   begin
678275793eaSopenharmony_ci      if Item'Length = 0 and Flush = No_Flush then
679275793eaSopenharmony_ci         return;
680275793eaSopenharmony_ci      end if;
681275793eaSopenharmony_ci
682275793eaSopenharmony_ci      loop
683275793eaSopenharmony_ci         Translate
684275793eaSopenharmony_ci           (Filter   => Filter,
685275793eaSopenharmony_ci            In_Data  => Item (In_First .. Item'Last),
686275793eaSopenharmony_ci            In_Last  => In_Last,
687275793eaSopenharmony_ci            Out_Data => Buffer,
688275793eaSopenharmony_ci            Out_Last => Out_Last,
689275793eaSopenharmony_ci            Flush    => Flush);
690275793eaSopenharmony_ci
691275793eaSopenharmony_ci         if Out_Last >= Buffer'First then
692275793eaSopenharmony_ci            Write (Buffer (1 .. Out_Last));
693275793eaSopenharmony_ci         end if;
694275793eaSopenharmony_ci
695275793eaSopenharmony_ci         exit when In_Last = Item'Last or Stream_End (Filter);
696275793eaSopenharmony_ci
697275793eaSopenharmony_ci         In_First := In_Last + 1;
698275793eaSopenharmony_ci      end loop;
699275793eaSopenharmony_ci   end Write;
700275793eaSopenharmony_ci
701275793eaSopenharmony_ciend ZLib;
702