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

« back to all changes in this revision

Viewing changes to lib/reltool/src/reltool_utils.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 2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2009-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(reltool_utils).
20
20
 
21
21
%% Public
22
 
-compile([export_all]).
 
22
-export([root_dir/0, erl_libs/0, lib_dirs/1,
 
23
         split_app_name/1, prim_consult/1,
 
24
         default_rels/0, choose_default/3,
 
25
 
 
26
         assign_image_list/1, get_latest_resize/1,
 
27
         mod_conds/0, list_to_mod_cond/1, mod_cond_to_index/1,
 
28
         incl_conds/0, list_to_incl_cond/1, incl_cond_to_index/1, elem_to_index/2,
 
29
         app_dir_test/2, split_app_dir/1,
 
30
         get_item/1, get_items/1, get_selected_items/3,
 
31
         select_items/3, select_item/2,
 
32
 
 
33
         safe_keysearch/5, print/4, return_first_error/2, add_warning/2,
 
34
 
 
35
         create_dir/1, list_dir/1, read_file_info/1,
 
36
         write_file_info/2, read_file/1, write_file/2,
 
37
         recursive_delete/1, delete/2, recursive_copy_file/2, copy_file/2,
 
38
 
 
39
         throw_error/2,
 
40
 
 
41
         decode_regexps/3,
 
42
         default_val/2,
 
43
         escript_foldl/3,
 
44
 
 
45
         call/2, cast/2, reply/3]).
23
46
 
24
47
-include_lib("kernel/include/file.hrl").
25
48
-include_lib("wx/include/wx.hrl").
30
53
 
31
54
erl_libs() ->
32
55
    case os:getenv("ERL_LIBS") of
33
 
        false -> 
 
56
        false ->
34
57
            [];
35
58
        LibStr ->
36
59
            string:tokens(LibStr, ":;")
37
 
    end.    
 
60
    end.
38
61
 
39
62
lib_dirs(Dir) ->
40
63
    case erl_prim_loader:list_dir(Dir) of
42
65
            [F || F <- Files,
43
66
                  filelib:is_dir(filename:join([Dir, F]),
44
67
                                 erl_prim_loader)];
45
 
        error -> 
 
68
        error ->
46
69
            []
47
70
    end.
48
71
 
55
78
                    Elem >= $0, Elem =< $9 -> true;
56
79
                    true -> false
57
80
                end
58
 
        end, 
 
81
        end,
59
82
    case lists:splitwith(Pred, lists:reverse(Name)) of
60
83
        {Vsn, [$- | App]} ->
61
84
            {list_to_atom(lists:reverse(App)), lists:reverse(Vsn)};
103
126
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
104
127
 
105
128
default_rels() ->
106
 
    Kernel = #rel_app{name = kernel, incl_apps = []},
107
 
    Stdlib = #rel_app{name = stdlib, incl_apps = []},
108
 
    Sasl   = #rel_app{name = sasl,   incl_apps = []},
 
129
    %%Kernel = #rel_app{name = kernel, incl_apps = []},
 
130
    %%Stdlib = #rel_app{name = stdlib, incl_apps = []},
 
131
    Sasl = #rel_app{name = sasl,   incl_apps = []},
109
132
    [
110
133
     #rel{name = ?DEFAULT_REL_NAME,
111
134
          vsn = "1.0",
112
 
          rel_apps = [Kernel, Stdlib]},
 
135
          rel_apps = []},
 
136
          %%rel_apps = [Kernel, Stdlib]},
113
137
     #rel{name = "start_sasl",
114
138
          vsn = "1.0",
115
 
          rel_apps = [Kernel, Sasl, Stdlib]}
 
139
          rel_apps = [Sasl]}
 
140
          %%rel_apps = [Kernel, Sasl, Stdlib]}
116
141
    ].
117
142
 
 
143
choose_default(Tag, Profile, InclDefs)
 
144
  when Profile =:= ?DEFAULT_PROFILE; InclDefs ->
 
145
    case Tag of
 
146
        incl_sys_filters  -> ?DEFAULT_INCL_SYS_FILTERS;
 
147
        excl_sys_filters  -> ?DEFAULT_EXCL_SYS_FILTERS;
 
148
        incl_app_filters  -> ?DEFAULT_INCL_APP_FILTERS;
 
149
        excl_app_filters  -> ?DEFAULT_EXCL_APP_FILTERS;
 
150
        embedded_app_type -> ?DEFAULT_EMBEDDED_APP_TYPE
 
151
    end;
 
152
choose_default(Tag, standalone, _InclDefs) ->
 
153
    case Tag of
 
154
        incl_sys_filters  -> ?STANDALONE_INCL_SYS_FILTERS;
 
155
        excl_sys_filters  -> ?STANDALONE_EXCL_SYS_FILTERS;
 
156
        incl_app_filters  -> ?STANDALONE_INCL_APP_FILTERS;
 
157
        excl_app_filters  -> ?STANDALONE_EXCL_APP_FILTERS;
 
158
        embedded_app_type -> ?DEFAULT_EMBEDDED_APP_TYPE
 
159
    end;
 
160
choose_default(Tag, embedded, _InclDefs) ->
 
161
    case Tag of
 
162
        incl_sys_filters  -> ?EMBEDDED_INCL_SYS_FILTERS;
 
163
        excl_sys_filters  -> ?EMBEDDED_EXCL_SYS_FILTERS;
 
164
        incl_app_filters  -> ?EMBEDDED_INCL_APP_FILTERS;
 
165
        excl_app_filters  -> ?EMBEDDED_EXCL_APP_FILTERS;
 
166
        embedded_app_type -> ?EMBEDDED_APP_TYPE
 
167
    end.
 
168
 
118
169
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
119
170
 
120
171
assign_image_list(ListCtrl) ->
121
172
    Art = wxImageList:new(16,16),
122
 
    [wxImageList:add(Art, wxArtProvider:getBitmap(Image, [{size, {16,16}}])) 
 
173
    [wxImageList:add(Art, wxArtProvider:getBitmap(Image, [{size, {16,16}}]))
123
174
     || Image <- ["wxART_ERROR",
124
175
                  "wxART_WARNING",
125
176
                  "wxART_QUESTION",
206
257
    ParentDir = filename:dirname(Dir),
207
258
    Base = filename:basename(Dir),
208
259
    {Name, Vsn} = split_app_name(Base),
209
 
    Vsn2 = 
 
260
    Vsn2 =
210
261
        try
211
262
            [list_to_integer(N) || N <- string:tokens(Vsn, ".")]
212
263
        catch
276
327
        ItemNo ->
277
328
            case wxListCtrl:getItemText(ListCtrl, ItemNo) of
278
329
                Text when Text =/= ?MISSING_APP_TEXT ->
279
 
                    get_selected_items(ListCtrl, ItemNo, [{ItemNo, Text} | Acc]);
 
330
                    get_selected_items(ListCtrl,
 
331
                                       ItemNo,
 
332
                                       [{ItemNo, Text} | Acc]);
280
333
                _Text ->
281
334
                    get_selected_items(ListCtrl, ItemNo, Acc)
282
335
            end
306
359
            select_item(ListCtrl, NewItems);
307
360
        ValidItems ->
308
361
            %% Some old selections are still valid. Select them again.
309
 
            lists:foreach(fun(Item) -> select_item(ListCtrl, [Item]) end, ValidItems)
 
362
            lists:foreach(fun(Item) -> select_item(ListCtrl, [Item]) end,
 
363
                          ValidItems)
310
364
    end.
311
365
 
312
366
select_item(ListCtrl, [{ItemNo, Text} | Items]) ->
339
393
    ok.
340
394
 
341
395
%% -define(SAFE(M,F,A), safe(M, F, A, ?MODULE, ?LINE)).
342
 
%% 
 
396
%%
343
397
%% safe(M, F, A, Mod, Line) ->
344
398
%%     case catch apply(M, F, A) of
345
399
%%      {'EXIT', Reason} ->
356
410
        {error, OldError} ->
357
411
            {error, OldError}
358
412
    end.
359
 
    
 
413
 
360
414
add_warning(Status, Warning) ->
361
415
    case Status of
362
416
        {ok, Warnings} ->
376
430
            ok;
377
431
        {error, Reason} ->
378
432
            Text = file:format_error(Reason),
379
 
            throw_error("create dir ~s: ~s\n", [Dir, Text])
 
433
            throw_error("create dir ~s: ~s", [Dir, Text])
380
434
    end.
381
435
 
382
436
list_dir(Dir) ->
385
439
            Files;
386
440
        error ->
387
441
            Text = file:format_error(enoent),
388
 
            throw_error("list dir ~s: ~s\n", [Dir, Text])
 
442
            throw_error("list dir ~s: ~s", [Dir, Text])
389
443
    end.
390
444
 
391
445
read_file_info(File) ->
394
448
            Info;
395
449
        {error, Reason} ->
396
450
            Text = file:format_error(Reason),
397
 
            throw_error("read file info ~s: ~s\n", [File, Text])
 
451
            throw_error("read file info ~s: ~s", [File, Text])
398
452
    end.
399
453
 
400
454
write_file_info(File, Info) ->
403
457
            ok;
404
458
        {error, Reason} ->
405
459
            Text = file:format_error(Reason),
406
 
            throw_error("write file info ~s: ~s\n", [File, Text])
 
460
            throw_error("write file info ~s: ~s", [File, Text])
407
461
    end.
408
462
 
409
463
read_file(File) ->
412
466
            Bin;
413
467
        {error, Reason} ->
414
468
            Text = file:format_error(Reason),
415
 
            throw_error("read file ~s: ~s\n", [File, Text])
 
469
            throw_error("read file ~s: ~s", [File, Text])
416
470
    end.
417
471
 
418
472
write_file(File, IoList) ->
421
475
            ok;
422
476
        {error, Reason} ->
423
477
            Text = file:format_error(Reason),
424
 
            throw_error("write file ~s: ~s\n", [File, Text])
 
478
            throw_error("write file ~s: ~s", [File, Text])
425
479
    end.
426
480
 
427
481
recursive_delete(Dir) ->
429
483
        true ->
430
484
            case file:list_dir(Dir) of
431
485
                {ok, Files} ->
432
 
                    Fun = fun(F) -> recursive_delete(filename:join([Dir, F])) end,
 
486
                    Fun =
 
487
                        fun(F) -> recursive_delete(filename:join([Dir, F])) end,
433
488
                    lists:foreach(Fun, Files),
434
489
                    delete(Dir, directory);
435
490
                {error, enoent} ->
514
569
do_decode_regexps(Key, [Regexp | Regexps], Acc) ->
515
570
    case catch re:compile(Regexp, []) of
516
571
        {ok, MP} ->
517
 
            do_decode_regexps(Key, Regexps, [#regexp{source = Regexp, compiled = MP} | Acc]);
 
572
            do_decode_regexps(Key,
 
573
                              Regexps,
 
574
                              [#regexp{source = Regexp, compiled = MP} | Acc]);
518
575
        _ ->
519
576
            Text = lists:flatten(io_lib:format("~p", [{Key, Regexp}])),
520
577
            throw({error, "Illegal option: " ++ Text})
532
589
 
533
590
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
534
591
 
 
592
escript_foldl(Fun, Acc, File) ->
 
593
    case escript:extract(File, [compile_source]) of
 
594
        {ok, [_Shebang, _Comment, _EmuArgs, Body]} ->
 
595
            case Body of
 
596
                {source, BeamCode} ->
 
597
                    GetInfo = fun() -> file:read_file_info(File) end,
 
598
                    GetBin = fun() -> BeamCode end,
 
599
                    {ok, Fun(".", GetInfo, GetBin, Acc)};
 
600
                {beam, BeamCode} ->
 
601
                    GetInfo = fun() -> file:read_file_info(File) end,
 
602
                    GetBin = fun() -> BeamCode end,
 
603
                    {ok, Fun(".", GetInfo, GetBin, Acc)};
 
604
                {archive, ArchiveBin} ->
 
605
                    zip:foldl(Fun, Acc, {File, ArchiveBin})
 
606
            end;
 
607
        {error, Reason} ->
 
608
            {error, Reason}
 
609
    end.
 
610
 
 
611
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
612
 
535
613
call(Name, Msg) when is_atom(Name) ->
536
 
    call(whereis(Name), Msg);
 
614
    case whereis(Name) of
 
615
        undefined ->
 
616
            {error, {noproc, Name}};
 
617
        Pid ->
 
618
            call(Pid, Msg)
 
619
    end;
537
620
call(Pid, Msg) when is_pid(Pid) ->
538
621
    Ref = erlang:monitor(process, Pid),
539
622
    Pid ! {call, self(), Ref, Msg},