~rdoering/ubuntu/intrepid/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/kernel/src/zlib.erl

  • Committer: Bazaar Package Importer
  • Author(s): Soren Hansen
  • Date: 2007-05-01 16:57:10 UTC
  • mfrom: (1.1.9 upstream)
  • Revision ID: james.westby@ubuntu.com-20070501165710-2sapk0hp2gf3o0ip
Tags: 1:11.b.4-2ubuntu1
* Merge with Debian Unstable. Remaining changes:
  - Add -fno-stack-protector to fix broken crypto_drv.
* DebianMaintainerField update.

Show diffs side-by-side

added added

removed removed

Lines of Context:
81
81
-define(OS_ACORN,  13).
82
82
-define(OS_UNKNOWN,255).
83
83
 
84
 
-record(gzip, 
85
 
        {
86
 
          method = ?Z_DEFLATED, 
87
 
          flags = 0,         %% :8
88
 
          mtime = 0,         %% :32/little
89
 
          xflags = 0,        %% :8
90
 
          ostype = ?OS_UNIX, %% :8 = unix
91
 
          extra,
92
 
          name,
93
 
          comment,
94
 
          crc
95
 
         }).
96
 
          
97
 
 
98
84
-define(DEFLATE_INIT,    1).
99
85
-define(DEFLATE_INIT2,   2).
100
86
-define(DEFLATE_SETDICT, 3).
266
252
    close(Z),
267
253
    list_to_binary(Bs).
268
254
    
269
 
gzip(Data) ->
270
 
    Bin0 = if list(Data) -> 
271
 
                   list_to_binary(Data);
272
 
              binary(Data) ->
273
 
                   Data;
274
 
              true -> 
275
 
                   erlang:error(badarg)
276
 
           end,
 
255
gzip(Data) when is_binary(Data); is_list(Data) ->
277
256
    Z = open(),
278
 
    deflateInit(Z, default, deflated, -?MAX_WBITS, 8, default),
279
 
    Bs = deflate(Z, Bin0, finish),
 
257
    deflateInit(Z, default, deflated, 16+?MAX_WBITS, 8, default),
 
258
    Bs = deflate(Z, Data, finish),
280
259
    deflateEnd(Z),
281
 
    Crc = crc32(Z, Bin0),
282
260
    close(Z),
283
 
    %% add header and crc
284
 
    Head = write_gzip_header(#gzip {}),
285
 
    Tail = <<Crc:32/little, (size(Bin0)):32/little>>,
286
 
    list_to_binary([Head,Bs,Tail]).
 
261
    iolist_to_binary(Bs);
 
262
gzip(_) -> erlang:error(badarg).
287
263
 
288
 
gunzip(Bin0 = <<?ID1, ?ID2, Method, Flags, MTime:32, 
289
 
               XFlags, OsType, _/binary>>) ->
290
 
    Gz0 = #gzip { method = Method,
291
 
                  flags = Flags, 
292
 
                  mtime = MTime, 
293
 
                  xflags = XFlags, 
294
 
                  ostype = OsType },
295
 
    {_,Bin1} = read_gzip_header(Flags, Bin0, 10, Gz0),
296
 
    %% io:format("gunzip header = ~p\n", [Gz1]),
 
264
gunzip(Data) when is_binary(Data); is_list(Data) ->
297
265
    Z = open(),
298
 
    inflateInit(Z, -?MAX_WBITS),
299
 
    Bs = inflate(Z, Bin1),
300
 
    Crc = crc32(Z),
301
 
    Remain = getQSize(Z),
 
266
    inflateInit(Z, 16+?MAX_WBITS),
 
267
    Bs = inflate(Z, Data),
302
268
    inflateEnd(Z),
303
269
    close(Z),
304
 
    Offset = size(Bin1) - Remain,
305
 
    Bin2 = list_to_binary(Bs),
306
 
    <<_:Offset/binary, Crc32:32/little, Length:32/little, _/binary>> = Bin1,
307
 
    if Crc32 =/= Crc ->
308
 
            erlang:error(bad_crc);
309
 
       Length =/= size(Bin2) ->
310
 
            erlang:error(bad_length);
311
 
       true ->
312
 
            Bin2
313
 
    end;
314
 
gunzip(_) -> 
315
 
    erlang:error(badarg).
316
 
    
317
 
 
318
 
write_gzip_header(Gz) ->
319
 
    {D1,F1} = 
320
 
        if Gz#gzip.extra == undefined ->
321
 
                {<<>>, 0};
322
 
           true ->
323
 
                Extra = list_to_binary([Gz#gzip.extra]),
324
 
                { <<(size(Extra)):16/little, Extra/binary>>, ?FEXTRA}
325
 
        end,
326
 
    {D2,F2} =
327
 
        if Gz#gzip.name == undefined ->
328
 
                {<<>>, 0};
329
 
           true ->
330
 
                Name = list_to_binary([Gz#gzip.name, 0]),
331
 
                { Name, ?FNAME }
332
 
        end,
333
 
    {D3,F3} =
334
 
        if Gz#gzip.comment == undefined ->
335
 
                {<<>>, 0};
336
 
           true ->
337
 
                Comment = list_to_binary([Gz#gzip.comment, 0]),
338
 
                { Comment, ?FCOMMENT }
339
 
        end,
340
 
    {D4,F4} =
341
 
        if Gz#gzip.crc == undefined ->
342
 
                {<<>>, 0};
343
 
           true ->
344
 
                { <<(Gz#gzip.crc):16/little >>, ?FHCRC }
345
 
        end,
346
 
    << ?ID1, ?ID2, 
347
 
     (Gz#gzip.method):8,
348
 
     (F1 bor F2 bor F3 bor F4):8,
349
 
     (Gz#gzip.mtime):32/little,
350
 
     (Gz#gzip.xflags):8,
351
 
     (Gz#gzip.ostype):8,
352
 
     D1/binary, D2/binary, D3/binary, D4/binary>>.
353
 
 
354
 
 
355
 
%% read the variable part of the gzip header
356
 
read_gzip_header(Flags, Binary, Offs0, Gz0) ->
357
 
    {Gz1,Offs1} =
358
 
        if (Flags band ?FEXTRA) =/= 0 ->
359
 
                <<_:Offs0/binary, Len:16/little, _/binary>> = Binary,
360
 
                Offs00 = Offs0+2,
361
 
                <<_:Offs00/binary, Extra:Len/binary,_/binary>> = Binary,
362
 
                {Gz0#gzip{extra = Extra}, Offs0 + 2 + Len};
363
 
           true -> 
364
 
                {Gz0,Offs0}
365
 
        end,
366
 
     {Gz2,Offs2} = 
367
 
        if (Flags band ?FNAME) =/= 0 ->
368
 
                Name = cname(Binary, Offs1),
369
 
                {Gz1#gzip{name = Name}, Offs1 + length(Name)+1};
370
 
           true ->
371
 
                {Gz1, Offs1}
372
 
        end,
373
 
    {Gz3, Offs3} = 
374
 
        if (Flags band ?FCOMMENT) =/= 0 ->
375
 
                Comment = cname(Binary, Offs2),
376
 
                {Gz2#gzip{comment = Comment}, Offs2 + length(Comment)+1};
377
 
           true ->
378
 
                {Gz2, Offs2}
379
 
        end,
380
 
    {Gz4, Offs4} = 
381
 
        if (Flags band ?FHCRC) =/= 0 ->
382
 
                <<_:Offs3, Crc:16/little, _/binary>> = Binary,
383
 
                {Gz3#gzip{crc = Crc}, Offs3+2};
384
 
           true ->
385
 
                {Gz3, Offs3}
386
 
        end,
387
 
    <<_:Offs4/binary, Body/binary>> = Binary,
388
 
    {Gz4, Body}.
389
 
 
390
 
 
391
 
cname(Binary, Offs) ->
392
 
    case Binary of
393
 
        <<_:Offs/binary, C, _/binary>> ->
394
 
            if C =:= 0 -> [];
395
 
               true -> [C|cname(Binary, Offs+1)]
396
 
            end;
397
 
        <<_:Offs/binary>> ->
398
 
            []
399
 
    end.    
400
 
    
401
 
            
 
270
    iolist_to_binary(Bs);
 
271
gunzip(_) -> erlang:error(badarg).
 
272
 
402
273
collect(Z) -> 
403
274
    collect(Z,[]).
404
275
 
440
311
arg_method(deflated) -> ?Z_DEFLATED;
441
312
arg_method(_) -> erlang:error(badarg).
442
313
 
443
 
arg_bitsz(Bits) when is_integer(Bits), 8 < abs(Bits), abs(Bits) =< 15 -> Bits;
 
314
arg_bitsz(Bits) when is_integer(Bits) andalso
 
315
                     ((8 < Bits andalso Bits < 48) orelse
 
316
                      (-15 =< Bits andalso Bits < -8)) ->
 
317
    Bits;
444
318
arg_bitsz(_) -> erlang:error(badarg).
445
319
 
446
320
arg_mem(Level) when is_integer(Level), 1 =< Level, Level =< 9 -> Level;