~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/reltool/src/reltool_utils.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-07 15:07:37 UTC
  • mfrom: (1.2.1 upstream) (5.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090507150737-i4yb5elwinm7r0hc
Tags: 1:13.b-dfsg1-1
* Removed another bunch of non-free RFCs from original tarball
  (closes: #527053).
* Fixed build-dependencies list by adding missing comma. This requires
  libsctp-dev again. Also, added libsctp1 dependency to erlang-base and
  erlang-base-hipe packages because the shared library is loaded via
  dlopen now and cannot be added using dh_slibdeps (closes: #526682).
* Weakened dependency of erlang-webtool on erlang-observer to recommends
  to avoid circular dependencies (closes: #526627).
* Added solaris-i386 to HiPE enabled architectures.
* Made script sources in /usr/lib/erlang/erts-*/bin directory executable,
  which is more convenient if a user wants to create a target Erlang system.
* Shortened extended description line for erlang-dev package to make it
  fit 80x25 terminals.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2009. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%% 
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%% 
 
17
%% %CopyrightEnd%
 
18
 
 
19
-module(reltool_utils).
 
20
 
 
21
%% Public
 
22
-compile([export_all]).
 
23
 
 
24
-include_lib("wx/include/wx.hrl").
 
25
-include("reltool.hrl").
 
26
 
 
27
root_dir() ->
 
28
    code:root_dir().
 
29
 
 
30
erl_libs() ->
 
31
    case os:getenv("ERL_LIBS") of
 
32
        false -> 
 
33
            [];
 
34
        LibStr ->
 
35
            string:tokens(LibStr, ":;")
 
36
    end.    
 
37
 
 
38
lib_dirs(Dir) ->
 
39
    case erl_prim_loader:list_dir(Dir) of
 
40
        {ok, Files} ->
 
41
            [F || F <- Files,
 
42
                  filelib:is_dir(filename:join([Dir, F]),
 
43
                                 erl_prim_loader)];
 
44
        error -> 
 
45
            []
 
46
    end.
 
47
 
 
48
%% "asn1-1.6.2" -> {"asn1", "1.6.2"}; "asn1" -> {"asn1", ""}
 
49
split_app_name(Name) ->
 
50
    Pred =
 
51
        fun(Elem) ->
 
52
                if
 
53
                    Elem =:= $\. -> true;
 
54
                    Elem >= $0, Elem =< $9 -> true;
 
55
                    true -> false
 
56
                end
 
57
        end, 
 
58
    case lists:splitwith(Pred, lists:reverse(Name)) of
 
59
        {Vsn, [$- | App]} ->
 
60
            {list_to_atom(lists:reverse(App)), lists:reverse(Vsn)};
 
61
        _ ->
 
62
            {list_to_atom(Name), ""}
 
63
    end.
 
64
 
 
65
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
66
 
 
67
prim_consult(Bin) when is_binary(Bin) ->
 
68
    case erl_scan:string(binary_to_list(Bin)) of
 
69
        {ok, Tokens, _EndLine} ->
 
70
            prim_parse(Tokens, []);
 
71
        {error, {_ErrorLine, Module, Reason}, _EndLine} ->
 
72
            {error, Module:format_error(Reason)}
 
73
    end;
 
74
prim_consult(FullName) when is_list(FullName) ->
 
75
    case erl_prim_loader:get_file(FullName) of
 
76
        {ok, Bin, _} ->
 
77
            prim_consult(Bin);
 
78
        error ->
 
79
            {error, file:format_error(enoent)}
 
80
    end.
 
81
 
 
82
prim_parse(Tokens, Acc) ->
 
83
    case lists:splitwith(fun(T) -> element(1,T) =/= dot end, Tokens) of
 
84
        {[], []} ->
 
85
            {ok, lists:reverse(Acc)};
 
86
        {Tokens2, [{dot,_} = Dot | Rest]} ->
 
87
            case erl_parse:parse_term(Tokens2 ++ [Dot]) of
 
88
                {ok, Term} ->
 
89
                    prim_parse(Rest, [Term | Acc]);
 
90
                {error, {_ErrorLine, Module, Reason}} ->
 
91
                    {error, Module:format_error(Reason)}
 
92
            end;
 
93
        {Tokens2, []} ->
 
94
            case erl_parse:parse_term(Tokens2) of
 
95
                {ok, Term} ->
 
96
                    {ok, lists:reverse([Term | Acc])};
 
97
                {error, {_ErrorLine, Module, Reason}} ->
 
98
                    {error, Module:format_error(Reason)}
 
99
            end
 
100
    end.
 
101
 
 
102
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
103
 
 
104
default_rels() ->
 
105
    Kernel = #rel_app{name = kernel, incl_apps = []},
 
106
    Stdlib = #rel_app{name = stdlib, incl_apps = []},
 
107
    Sasl   = #rel_app{name = sasl,   incl_apps = []},
 
108
    [
 
109
     #rel{name = ?DEFAULT_REL_NAME,
 
110
          vsn = "1.0",
 
111
          rel_apps = [Kernel, Stdlib]},
 
112
     #rel{name = "start_sasl",
 
113
          vsn = "1.0",
 
114
          rel_apps = [Kernel, Sasl, Stdlib]}
 
115
    ].
 
116
 
 
117
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
118
 
 
119
assign_image_list(ListCtrl) ->
 
120
    Art = wxImageList:new(16,16),
 
121
    [wxImageList:add(Art, wxArtProvider:getBitmap(Image, [{size, {16,16}}])) 
 
122
     || Image <- ["wxART_ERROR",
 
123
                  "wxART_WARNING",
 
124
                  "wxART_QUESTION",
 
125
                  "wxART_TICK_MARK",
 
126
                  "wxART_CROSS_MARK",
 
127
                  "wxART_GO_HOME"]],
 
128
    wxListCtrl:assignImageList(ListCtrl, Art, ?wxIMAGE_LIST_SMALL).
 
129
 
 
130
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
131
 
 
132
get_latest_resize(#wx{obj = ObjRef, event = #wxSize{}} = Wx) ->
 
133
    receive
 
134
        #wx{obj = ObjRef, event = #wxSize{}} = Wx2 ->
 
135
            get_latest_resize(Wx2)
 
136
    after 10 ->
 
137
            Wx
 
138
    end.
 
139
 
 
140
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
141
 
 
142
mod_conds() ->
 
143
    ["all (ebin + app file)", "ebin + derived", "app file + derived", "derived", "none"].
 
144
 
 
145
list_to_mod_cond(List) ->
 
146
    case List of
 
147
        "all" ++ _   -> all;
 
148
        "ebin" ++ _  -> ebin;
 
149
        "app" ++ _   -> app;
 
150
        "derived"    -> derived;
 
151
        "none"       -> none
 
152
    end.
 
153
 
 
154
mod_cond_to_index(ModCond) ->
 
155
    case ModCond of
 
156
        all       -> 0;
 
157
        ebin      -> 1; 
 
158
        app       -> 2;
 
159
        derived   -> 3;
 
160
        undefined -> 3;
 
161
        none      -> 4
 
162
    end.
 
163
 
 
164
incl_conds() ->
 
165
    ["include", "exclude", "derived"].
 
166
 
 
167
list_to_incl_cond(List) ->
 
168
    case List of
 
169
        "include" -> include;
 
170
        "exclude" -> exclude;
 
171
        "derived" -> derived
 
172
    end.
 
173
 
 
174
incl_cond_to_index(ModCond) ->
 
175
    case ModCond of
 
176
        include -> 0;
 
177
        exclude -> 1;   
 
178
        derived -> 2
 
179
    end.
 
180
 
 
181
elem_to_index(Elem, List) ->
 
182
    elem_to_index(Elem, List, 1).
 
183
 
 
184
elem_to_index(Elem, [H | T], Index) ->
 
185
    case Elem =:= H of
 
186
        true -> Index;
 
187
        false -> elem_to_index(Elem, T, Index + 1)
 
188
    end;
 
189
elem_to_index(Elem, [], _) ->
 
190
    erlang:error({not_found, Elem}).
 
191
 
 
192
app_dir_test(Dir1, Dir2) ->
 
193
    {Name1, Vsn1, Parent1} = split_app_dir(Dir1),
 
194
    {Name2, Vsn2, Parent2} = split_app_dir(Dir2),
 
195
    if
 
196
        Name1 < Name2 -> true;
 
197
        Name1 > Name2 -> false;
 
198
        Vsn1 < Vsn2 -> false;
 
199
        Vsn1 > Vsn2 -> true;
 
200
        Parent1 < Parent2 -> true;
 
201
        true -> false
 
202
    end.
 
203
 
 
204
split_app_dir(Dir) ->
 
205
    ParentDir = filename:dirname(Dir),
 
206
    Base = filename:basename(Dir),
 
207
    {Name, Vsn} = split_app_name(Base),
 
208
    Vsn2 = 
 
209
        try
 
210
            [list_to_integer(N) || N <- string:tokens(Vsn, ".")]
 
211
        catch
 
212
            _:_ ->
 
213
                Vsn
 
214
        end,
 
215
    {Name, Vsn2, ParentDir}.
 
216
 
 
217
get_item(ListCtrl) ->
 
218
    case wxListCtrl:getItemCount(ListCtrl) of
 
219
        0 ->
 
220
            undefined;
 
221
        _ ->
 
222
            case wxListCtrl:getNextItem(ListCtrl,
 
223
                                        -1,
 
224
                                        [{geometry, ?wxLIST_NEXT_ALL},
 
225
                                         {state, ?wxLIST_STATE_SELECTED}]) of
 
226
                -1 ->
 
227
                    ItemNo = wxListCtrl:getTopItem(ListCtrl),
 
228
                    case wxListCtrl:getItemText(ListCtrl, ItemNo) of
 
229
                        "" ->
 
230
                            undefined;
 
231
                        Text ->
 
232
                            {ItemNo, Text}
 
233
                    end;
 
234
                ItemNo ->
 
235
                    Text = wxListCtrl:getItemText(ListCtrl, ItemNo),
 
236
                    {ItemNo, Text}
 
237
            end
 
238
    end.
 
239
 
 
240
get_items(ListCtrl) ->
 
241
    case wxListCtrl:getItemCount(ListCtrl) of
 
242
        0 ->
 
243
            [];
 
244
        Count ->
 
245
            case get_selected_items(ListCtrl, -1, []) of
 
246
                [] ->
 
247
                    ItemNo = wxListCtrl:getTopItem(ListCtrl),
 
248
                    case wxListCtrl:getItemText(ListCtrl, ItemNo) of
 
249
                        "" ->
 
250
                            [];
 
251
                        Text when Text =/= ?MISSING_APP_TEXT ->
 
252
                            [{ItemNo, Text}];
 
253
                        _MissingText when Count > 1 ->
 
254
                            case wxListCtrl:getItemText(ListCtrl, ItemNo + 1) of
 
255
                                "" ->
 
256
                                    [];
 
257
                                Text ->
 
258
                                    [{ItemNo, Text}]
 
259
                            end;
 
260
                        _MissingText ->
 
261
                            []
 
262
                    end;
 
263
                Items ->
 
264
                    Items
 
265
            end
 
266
    end.
 
267
 
 
268
get_selected_items(ListCtrl, PrevItem, Acc) ->
 
269
    case wxListCtrl:getNextItem(ListCtrl,
 
270
                                PrevItem,
 
271
                                [{geometry, ?wxLIST_NEXT_ALL},
 
272
                                 {state, ?wxLIST_STATE_SELECTED}]) of
 
273
        -1 ->
 
274
            Acc;
 
275
        ItemNo ->
 
276
            case wxListCtrl:getItemText(ListCtrl, ItemNo) of
 
277
                Text when Text =/= ?MISSING_APP_TEXT ->
 
278
                    get_selected_items(ListCtrl, ItemNo, [{ItemNo, Text} | Acc]);
 
279
                _Text ->
 
280
                    get_selected_items(ListCtrl, ItemNo, Acc)
 
281
            end
 
282
    end.
 
283
 
 
284
select_items(_ListCtrl, _OldItems, []) ->
 
285
    %% No new items. Nothing to select.
 
286
    false;
 
287
select_items(ListCtrl, [], Items) ->
 
288
    %% No old selection. Select first.
 
289
    select_item(ListCtrl, Items);
 
290
select_items(ListCtrl, _OldItems, [Item]) ->
 
291
    %% Only one new item. Select it.
 
292
    select_item(ListCtrl, [Item]);
 
293
select_items(ListCtrl, OldItems, NewItems) ->
 
294
    %% Try to propagate old selection to new items.
 
295
    Filter =
 
296
        fun({_OldItemNo, Text}) ->
 
297
                case lists:keysearch(Text, 2, NewItems) of
 
298
                    {value, Item} -> {true, Item};
 
299
                    false -> false
 
300
                end
 
301
        end,
 
302
    case lists:zf(Filter, OldItems) of
 
303
        [] ->
 
304
            %% None of the old selections are valid. Select the first.
 
305
            select_item(ListCtrl, NewItems);
 
306
        ValidItems ->
 
307
            %% Some old selections are still valid. Select them again.
 
308
            lists:foreach(fun(Item) -> select_item(ListCtrl, [Item]) end, ValidItems)
 
309
    end.
 
310
 
 
311
select_item(ListCtrl, [{ItemNo, Text} | Items]) ->
 
312
    case Text =:= ?MISSING_APP_TEXT of
 
313
        true ->
 
314
            select_item(ListCtrl, Items);
 
315
        false ->
 
316
            StateMask = ?wxLIST_STATE_SELECTED,
 
317
            State = wxListCtrl:getItemState(ListCtrl, ItemNo, StateMask),
 
318
            State2 = State bor ?wxLIST_STATE_SELECTED,
 
319
            wxListCtrl:setItemState(ListCtrl, ItemNo, State2, StateMask),
 
320
            wxListCtrl:refreshItem(ListCtrl, ItemNo)
 
321
    end;
 
322
select_item(_ListCtrl, []) ->
 
323
    ok.
 
324
 
 
325
safe_keysearch(Key, Pos, List, Mod, Line) ->
 
326
    case lists:keysearch(Key, Pos, List) of
 
327
        false ->
 
328
            io:format("~p(~p): lists:keysearch(~p, ~p, ~p) -> false\n",
 
329
                      [Mod, Line, Key, Pos, List]),
 
330
            erlang:error({Mod, Line, lists, keysearch, [Key, Pos, List]});
 
331
        {value, Val} ->
 
332
            Val
 
333
    end.
 
334
 
 
335
print(X, X, Format, Args) ->
 
336
    io:format(Format, Args);
 
337
print(_, _, _, _) ->
 
338
    ok.
 
339
 
 
340
%% -define(SAFE(M,F,A), safe(M, F, A, ?MODULE, ?LINE)).
 
341
%% 
 
342
%% safe(M, F, A, Mod, Line) ->
 
343
%%     case catch apply(M, F, A) of
 
344
%%      {'EXIT', Reason} ->
 
345
%%          io:format("~p(~p): ~p:~p~p -> ~p\n", [Mod, Line, M, F, A, Reason]),
 
346
%%          timer:sleep(infinity);
 
347
%%      Res ->
 
348
%%          Res
 
349
%%     end.
 
350
 
 
351
return_first_error(Status, NewError) when is_list(NewError) ->
 
352
    case Status of
 
353
        {ok, _Warnings} ->
 
354
            {error, NewError};
 
355
        {error, OldError} ->
 
356
            {error, OldError}
 
357
    end.
 
358
    
 
359
add_warning(Status, Warning) ->
 
360
    case Status of
 
361
        {ok, Warnings} ->
 
362
            {ok, [Warning | Warnings]};
 
363
        {error, Error} ->
 
364
            {error, Error}
 
365
    end.