~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/stdlib/src/zip.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 2006-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2006-2010. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
-module(zip).
20
20
 
21
21
%% Basic api
22
22
-export([unzip/1, unzip/2, extract/1, extract/2,
23
 
         zip/2, zip/3, create/2, create/3,
 
23
         zip/2, zip/3, create/2, create/3, foldl/3,
24
24
         list_dir/1, list_dir/2, table/1, table/2,
25
25
         t/1, tt/1]).
26
26
 
38
38
         zip_t/1, zip_tt/1,
39
39
         zip_list_dir/1, zip_list_dir/2,
40
40
         zip_close/1]).
41
 
         
 
41
 
42
42
%% just for debugging zip server, not documented, not tested, not to be used
43
43
-export([zip_get_state/1]).
44
44
 
82
82
-record(openzip_opts, {
83
83
          output,      % output object (fun)
84
84
          open_opts,   % file:open options
85
 
          cwd          % directory to relate paths to     
 
85
          cwd          % directory to relate paths to
86
86
         }).
87
87
 
88
88
% openzip record, state for an open zip-file
93
93
          input,       % archive io object (fun)
94
94
          output,      % output io object (fun)
95
95
          zlib,        % handle to open zlib
96
 
          cwd          % directory to relate paths to     
 
96
          cwd          % directory to relate paths to
97
97
         }).
98
98
 
99
 
% Things that I would like to add to the public record #zip_file, 
 
99
% Things that I would like to add to the public record #zip_file,
100
100
% but can't as it would make things fail at upgrade.
101
101
% Instead we use {#zip_file,#zip_file_extra} internally.
102
102
-record(zip_file_extra, {
278
278
        [ZFile|_] -> ZFile;
279
279
        [] -> false
280
280
    end.
281
 
             
 
281
 
282
282
%% %% add a file to an open archive
283
283
%% openzip_add(File, OpenZip) ->
284
284
%%     case ?CATCH do_openzip_add(File, OpenZip) of
344
344
    Input(close, In1),
345
345
    {ok, Files}.
346
346
 
 
347
%% Iterate over all files in a zip archive
 
348
foldl(Fun, Acc0, Archive) when is_function(Fun, 4) ->
 
349
    ZipFun =
 
350
        fun({Name, GetInfo, GetBin}, A) ->
 
351
                A2 = Fun(Name, GetInfo, GetBin, A),
 
352
                {true, false, A2}
 
353
        end,
 
354
    case prim_zip:open(ZipFun, Acc0, Archive) of
 
355
        {ok, PrimZip, Acc1} ->
 
356
            ok = prim_zip:close(PrimZip),
 
357
            {ok, Acc1};
 
358
        {error, bad_eocd} ->
 
359
            {error, "Not an archive file"};
 
360
        {error, Reason} ->
 
361
            {error, Reason}
 
362
    end;
 
363
foldl(_,_, _) ->
 
364
    {error, einval}.
 
365
 
347
366
%% Create zip archive name F from Files or binaries
348
367
%%
349
368
%% Accepted options:
383
402
 
384
403
do_list_dir(F, Options) ->
385
404
    Opts = get_list_dir_options(F, Options),
386
 
    #list_dir_opts{input = Input, open_opts = OpO, 
 
405
    #list_dir_opts{input = Input, open_opts = OpO,
387
406
                   raw_iterator = RawIterator} = Opts,
388
407
    In0 = Input({open, F, OpO}, []),
389
408
    {Info, In1} = get_central_dir(In0, RawIterator, Input),
417
436
tt(F) -> t(F, fun raw_long_print_info_etc/5).
418
437
 
419
438
 
420
 
%% option utils 
 
439
%% option utils
421
440
get_unzip_opt([], Opts) ->
422
441
    Opts;
423
442
get_unzip_opt([verbose | Rest], Opts) ->
470
489
get_zip_opt([{comment, C} | Rest], Opts) ->
471
490
    get_zip_opt(Rest, Opts#zip_opts{comment = C});
472
491
get_zip_opt([{compress, Which} = O| Rest], Opts) ->
473
 
    Which2 = 
 
492
    Which2 =
474
493
        case Which of
475
494
            all ->
476
495
                all;
485
504
        end,
486
505
    get_zip_opt(Rest, Opts#zip_opts{compress = Which2});
487
506
get_zip_opt([{uncompress, Which} = O| Rest], Opts) ->
488
 
    Which2 = 
 
507
    Which2 =
489
508
        case Which of
490
509
            all ->
491
510
                all;
560
579
get_input(F) when is_binary(F) ->
561
580
    fun binary_io/2;
562
581
get_input(F) when is_list(F) ->
563
 
    fun file_io/2.
 
582
    fun file_io/2;
 
583
get_input(_) ->
 
584
    throw(einval).
564
585
 
565
586
get_zip_input({F, B}) when is_binary(B), is_list(F) ->
566
587
    fun binary_io/2;
 
588
get_zip_input({F, B, #file_info{}}) when is_binary(B), is_list(F) ->
 
589
    fun binary_io/2;
 
590
get_zip_input({F, #file_info{}, B}) when is_binary(B), is_list(F) ->
 
591
    fun binary_io/2;
567
592
get_zip_input(F) when is_list(F) ->
568
593
    fun file_io/2;
569
594
get_zip_input({files, []}) ->
570
595
    fun binary_io/2;
571
596
get_zip_input({files, [File | _]}) ->
572
 
    get_zip_input(File).
 
597
    get_zip_input(File);
 
598
get_zip_input(_) ->
 
599
    throw(einval).
573
600
 
574
601
get_list_dir_options(F, Options) ->
575
602
    Opts = #list_dir_opts{raw_iterator = fun raw_file_info_public/5,
620
647
 
621
648
get_filename({Name, _}, Type) ->
622
649
    get_filename(Name, Type);
 
650
get_filename({Name, _, _}, Type) ->
 
651
    get_filename(Name, Type);
623
652
get_filename(Name, regular) ->
624
653
    Name;
625
654
get_filename(Name, directory) ->
895
924
     CompSize:32/little,
896
925
     UncompSize:32/little,
897
926
     FileNameLength:16/little,
898
 
     ExtraFieldLength:16/little>>.    
 
927
     ExtraFieldLength:16/little>>.
899
928
 
900
929
eocd_to_bin(#eocd{disk_num = DiskNum,
901
930
           start_disk_num = StartDiskNum,
912
941
     Offset:32/little,
913
942
     ZipCommentLength:16/little>>.
914
943
 
915
 
%% put together a local file header 
 
944
%% put together a local file header
916
945
local_file_header_from_info_method_name(#file_info{mtime = MTime},
917
946
                                        UncompSize,
918
947
                                        CompMethod, Name) ->
939
968
                    server_loop(NewOpenZip);
940
969
                Error ->
941
970
                    From ! {self(), Error}
942
 
            end;                    
 
971
            end;
943
972
        {From, close} ->
944
973
            From ! {self(), openzip_close(OpenZip)};
945
974
        {From, get} ->
1024
1053
    F(Hd),
1025
1054
    lists_foreach(F, Tl).
1026
1055
 
1027
 
%% option utils 
 
1056
%% option utils
1028
1057
get_openzip_opt([], Opts) ->
1029
1058
    Opts;
1030
1059
get_openzip_opt([cooked | Rest], #openzip_opts{open_opts = OO} = Opts) ->
1121
1150
             Other -> Other
1122
1151
         end,
1123
1152
    [H2|T].
1124
 
      
 
1153
 
1125
1154
 
1126
1155
%% make a file_info from a central directory header
1127
1156
cd_file_header_to_file_info(FileName,
1213
1242
                    {dir, In3};
1214
1243
                _ ->
1215
1244
                    %% FileInfo = local_file_header_to_file_info(LH)
1216
 
                    %%{Out, In4, CRC, UncompSize} = 
1217
 
                    {Out, In4, CRC, _UncompSize} = 
 
1245
                    %%{Out, In4, CRC, UncompSize} =
 
1246
                    {Out, In4, CRC, _UncompSize} =
1218
1247
                        get_z_data(CompMethod, In3, FileName1,
1219
1248
                                   CompSize, Input, Output, OpO, Z),
1220
1249
                    In5 = skip_z_data_descriptor(GPFlag, Input, In4),
1280
1309
            Out1 = Output({write, Uncompressed}, Out0),
1281
1310
            get_z_data_loop(CompSize-N, UncompSize + iolist_size(Uncompressed),
1282
1311
                            In1, Out1, Input, Output, Z)
1283
 
    end.    
 
1312
    end.
1284
1313
 
1285
1314
 
1286
1315
%% skip data descriptor if any
1298
1327
    <<Hour:5, Min:6, Sec:5>> = <<DosTime:16>>,
1299
1328
    <<YearFrom1980:7, Month:4, Day:5>> = <<DosDate:16>>,
1300
1329
    {{YearFrom1980+1980, Month, Day},
1301
 
     {Hour, Min, Sec}}. 
 
1330
     {Hour, Min, Sec}}.
1302
1331
 
1303
1332
dos_date_time_from_datetime({{Year, Month, Day}, {Hour, Min, Sec}}) ->
1304
1333
    YearFrom1980 = Year-1980,
1319
1348
     Var};
1320
1349
unix_extra_field_and_var_from_bin(_) ->
1321
1350
    throw(bad_unix_extra_field).
1322
 
                       
1323
1351
 
1324
1352
%% A pwrite-like function for iolists (used by memory-option)
1325
1353
 
1478
1506
%% io functions
1479
1507
binary_io({file_info, {_Filename, _B, #file_info{} = FI}}, _A) ->
1480
1508
    FI;
 
1509
binary_io({file_info, {_Filename, #file_info{} = FI, _B}}, _A) ->
 
1510
    FI;
1481
1511
binary_io({file_info, {_Filename, B}}, A) ->
1482
1512
    binary_io({file_info, B}, A);
1483
1513
binary_io({file_info, B}, _) ->
1493
1523
               links = 1, major_device = 0,
1494
1524
               minor_device = 0, inode = 0,
1495
1525
               uid = 0, gid = 0};
1496
 
binary_io({open, {_Filename, B, _FI}, _Opts}, _) ->
1497
 
    {0, B};
1498
 
binary_io({open, {_Filename, B}, _Opts}, _) ->
 
1526
binary_io({open, {_Filename, B, _FI}, _Opts}, _) when is_binary(B) ->
 
1527
    {0, B};
 
1528
binary_io({open, {_Filename, _FI, B}, _Opts}, _) when is_binary(B) ->
 
1529
    {0, B};
 
1530
binary_io({open, {_Filename, B}, _Opts}, _) when is_binary(B) ->
1499
1531
    {0, B};
1500
1532
binary_io({open, B, _Opts}, _) when is_binary(B) ->
1501
1533
    {0, B};