~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/observer/src/observer_lib.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 2011. 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(observer_lib).
 
20
 
 
21
-export([get_wx_parent/1,
 
22
         display_info_dialog/1, user_term/3,
 
23
         interval_dialog/4, start_timer/1, stop_timer/1,
 
24
         display_info/2, fill_info/2, update_info/2, to_str/1,
 
25
         create_menus/3, create_menu_item/3,
 
26
         create_attrs/0,
 
27
         set_listctrl_col_size/2
 
28
        ]).
 
29
 
 
30
-include_lib("wx/include/wx.hrl").
 
31
-include("observer_defs.hrl").
 
32
 
 
33
get_wx_parent(Window) ->
 
34
    Parent = wxWindow:getParent(Window),
 
35
    case wx:is_null(Parent) of
 
36
        true -> Window;
 
37
        false -> get_wx_parent(Parent)
 
38
    end.
 
39
 
 
40
interval_dialog(Parent0, {Timer, Value}, Min, Max) ->
 
41
    Parent = get_wx_parent(Parent0),
 
42
    Dialog = wxDialog:new(Parent, ?wxID_ANY, "Update Interval",
 
43
                          [{style, ?wxDEFAULT_DIALOG_STYLE bor
 
44
                                ?wxRESIZE_BORDER}]),
 
45
    Panel = wxPanel:new(Dialog),
 
46
    Check = wxCheckBox:new(Panel, ?wxID_ANY, "Periodical refresh"),
 
47
    wxCheckBox:setValue(Check, Timer /= false),
 
48
    Style = ?wxSL_HORIZONTAL bor ?wxSL_AUTOTICKS bor ?wxSL_LABELS,
 
49
    Slider = wxSlider:new(Panel, ?wxID_ANY, Value, Min, Max,
 
50
                          [{style, Style}, {size, {200, -1}}]),
 
51
    wxWindow:enable(Slider, [{enable, Timer /= false}]),
 
52
    InnerSizer = wxBoxSizer:new(?wxVERTICAL),
 
53
    Buttons = wxDialog:createButtonSizer(Dialog, ?wxOK bor ?wxCANCEL),
 
54
    Flags = [{flag, ?wxEXPAND bor ?wxALL}, {border, 2}],
 
55
    wxSizer:add(InnerSizer, Check,  Flags),
 
56
    wxSizer:add(InnerSizer, Slider, Flags),
 
57
    wxPanel:setSizer(Panel, InnerSizer),
 
58
    TopSizer = wxBoxSizer:new(?wxVERTICAL),
 
59
    wxSizer:add(TopSizer, Panel, [{flag, ?wxEXPAND bor ?wxALL}, {border, 5}]),
 
60
    wxSizer:add(TopSizer, Buttons, [{flag, ?wxEXPAND}]),
 
61
    wxWindow:setSizerAndFit(Dialog, TopSizer),
 
62
    wxSizer:setSizeHints(TopSizer, Dialog),
 
63
    wxCheckBox:connect(Check, command_checkbox_clicked,
 
64
                       [{callback, fun(#wx{event=#wxCommand{commandInt=Enable0}},_) ->
 
65
                                           Enable = Enable0 > 0,
 
66
                                           wxWindow:enable(Slider, [{enable, Enable}])
 
67
                                   end}]),
 
68
    Res = case wxDialog:showModal(Dialog) of
 
69
              ?wxID_OK ->
 
70
                  Enabled = wxCheckBox:isChecked(Check),
 
71
                  setup_timer(Enabled, {Timer, wxSlider:getValue(Slider)});
 
72
              ?wxID_CANCEL ->
 
73
                  {Timer, Value}
 
74
          end,
 
75
    wxDialog:destroy(Dialog),
 
76
    Res.
 
77
 
 
78
stop_timer(Timer = {false, _}) -> Timer;
 
79
stop_timer(Timer = {true, _}) -> Timer;
 
80
stop_timer(Timer = {_, Intv}) ->
 
81
    setup_timer(false, Timer),
 
82
    {true, Intv}.
 
83
start_timer(Intv) when is_integer(Intv) ->
 
84
    setup_timer(true, {true, Intv});
 
85
start_timer(Timer) ->
 
86
    setup_timer(true, Timer).
 
87
 
 
88
setup_timer(false, {Timer, Value})
 
89
  when is_boolean(Timer) ->
 
90
    {false, Value};
 
91
setup_timer(true,  {false, Value}) ->
 
92
    {ok, Timer} = timer:send_interval(Value * 1000, refresh_interval),
 
93
    {Timer, Value};
 
94
setup_timer(Bool, {Timer, Old}) ->
 
95
    timer:cancel(Timer),
 
96
    setup_timer(Bool, {false, Old}).
 
97
 
 
98
display_info_dialog(Str) ->
 
99
    Dlg = wxMessageDialog:new(wx:null(), Str),
 
100
    wxMessageDialog:showModal(Dlg),
 
101
    wxMessageDialog:destroy(Dlg),
 
102
    ok.
 
103
 
 
104
%% display_info(Parent, [{Title, [{Label, Info}]}]) -> {Panel, Sizer, InfoFieldsToUpdate}
 
105
display_info(Frame, Info) ->
 
106
    Panel = wxPanel:new(Frame),
 
107
    wxWindow:setBackgroundColour(Panel, {255,255,255}),
 
108
    Sizer = wxBoxSizer:new(?wxVERTICAL),
 
109
    wxSizer:addSpacer(Sizer, 5),
 
110
    Add = fun(BoxInfo) ->
 
111
                  {Box, InfoFs} = create_box(Panel, BoxInfo),
 
112
                  wxSizer:add(Sizer, Box, [{flag, ?wxEXPAND bor ?wxALL},
 
113
                                           {border, 5}]),
 
114
                  wxSizer:addSpacer(Sizer, 5),
 
115
                  InfoFs
 
116
          end,
 
117
    InfoFs = [Add(I) || I <- Info],
 
118
    wxWindow:setSizerAndFit(Panel, Sizer),
 
119
    {Panel, Sizer, InfoFs}.
 
120
 
 
121
fill_info([{Str, Key}|Rest], Data) when is_atom(Key); is_function(Key) ->
 
122
    [{Str, get_value(Key, Data)} | fill_info(Rest, Data)];
 
123
fill_info([{Str, {Format, Key}}|Rest], Data)
 
124
  when is_atom(Key); is_function(Key), is_atom(Format) ->
 
125
    [{Str, {Format, get_value(Key,Data)}} | fill_info(Rest, Data)];
 
126
fill_info([{Str,SubStructure}|Rest], Data) when is_list(SubStructure) ->
 
127
    [{Str, fill_info(SubStructure, Data)}|fill_info(Rest,Data)];
 
128
fill_info([{Str,Attrib,SubStructure}|Rest], Data) ->
 
129
    [{Str, Attrib, fill_info(SubStructure, Data)}|fill_info(Rest,Data)];
 
130
fill_info([], _) -> [].
 
131
 
 
132
get_value(Key, Data) when is_atom(Key) ->
 
133
    proplists:get_value(Key,Data);
 
134
get_value(Fun, Data) when is_function(Fun) ->
 
135
    Fun(Data).
 
136
 
 
137
update_info([Fields|Fs], [{_Header, SubStructure}| Rest]) ->
 
138
    update_info2(Fields, SubStructure),
 
139
    update_info(Fs, Rest);
 
140
update_info([Fields|Fs], [{_Header, _Attrib, SubStructure}| Rest]) ->
 
141
    update_info2(Fields, SubStructure),
 
142
    update_info(Fs, Rest);
 
143
update_info([], []) ->
 
144
    ok.
 
145
 
 
146
update_info2([Field|Fs], [{_Str, Value}|Rest]) ->
 
147
    wxStaticText:setLabel(Field, to_str(Value)),
 
148
    update_info2(Fs, Rest);
 
149
update_info2([], []) -> ok.
 
150
 
 
151
 
 
152
to_str(Value) when is_atom(Value) ->
 
153
    atom_to_list(Value);
 
154
to_str({bytes, B}) ->
 
155
    KB = B div 1024,
 
156
    MB = KB div 1024,
 
157
    if
 
158
        MB > 10 -> integer_to_list(MB) ++ " mB";
 
159
        KB >  0 -> integer_to_list(KB) ++ " kB";
 
160
        true -> integer_to_list(B) ++ " B "
 
161
    end;
 
162
to_str({time_ms, MS}) ->
 
163
    S = MS div 1000,
 
164
    Min = S div 60,
 
165
    Hours = Min div 60,
 
166
    Days = Hours div 24,
 
167
    if
 
168
        Days > 0 -> integer_to_list(Days) ++ " Days";
 
169
        Hours > 0 -> integer_to_list(Hours) ++ " Hours";
 
170
        Min > 0 -> integer_to_list(Min) ++ " Mins";
 
171
        true -> integer_to_list(S) ++ " Secs"
 
172
    end;
 
173
 
 
174
to_str({func, {F,A}}) when is_atom(F), is_integer(A) ->
 
175
    lists:concat([F, "/", A]);
 
176
to_str({func, {F,'_'}}) when is_atom(F) ->
 
177
    atom_to_list(F);
 
178
to_str({A, B}) when is_atom(A), is_atom(B) ->
 
179
    lists:concat([A, ":", B]);
 
180
to_str({M,F,A}) when is_atom(M), is_atom(F), is_integer(A) ->
 
181
    lists:concat([M, ":", F, "/", A]);
 
182
to_str(Value) when is_list(Value) ->
 
183
    case lists:all(fun(X) -> is_integer(X) end, Value) of
 
184
        true -> Value;
 
185
        false ->
 
186
            lists:foldl(fun(X, Acc) ->
 
187
                                to_str(X) ++ " " ++ Acc end,
 
188
                        "", Value)
 
189
    end;
 
190
to_str(Port) when is_port(Port) ->
 
191
    erlang:port_to_list(Port);
 
192
to_str(Pid) when is_pid(Pid) ->
 
193
    pid_to_list(Pid);
 
194
to_str(No) when is_integer(No) ->
 
195
    integer_to_list(No);
 
196
to_str(Term) ->
 
197
    io_lib:format("~w", [Term]).
 
198
 
 
199
create_menus([], _MenuBar, _Type) -> ok;
 
200
create_menus(Menus, MenuBar, Type) ->
 
201
    Add = fun({Tag, Ms}, Index) ->
 
202
                  create_menu(Tag, Ms, Index, MenuBar, Type)
 
203
          end,
 
204
    [{First, _}|_] = Menus,
 
205
    OnMac = os:type() =:= {unix, darwin},
 
206
    Index = if Type =:= default -> 0;
 
207
               First =:= "File" -> 0;
 
208
               OnMac -> 0;
 
209
               true -> 1
 
210
            end,
 
211
    wx:foldl(Add, Index, Menus),
 
212
    ok.
 
213
 
 
214
create_menu("File", MenuItems, Index, MenuBar, Type) ->
 
215
    OnMac = os:type() =:= {unix, darwin},
 
216
    if OnMac, Type =:= default ->
 
217
            Index;
 
218
       not OnMac, Type =:= plugin ->
 
219
            MenuId = wxMenuBar:findMenu(MenuBar, "File"),
 
220
            Menu = wxMenuBar:getMenu(MenuBar, MenuId),
 
221
            lists:foldl(fun(Record, N) ->
 
222
                                create_menu_item(Record, Menu, N)
 
223
                        end, 0, MenuItems),
 
224
            Index + 1;
 
225
       true ->
 
226
            Menu = wxMenu:new(),
 
227
            lists:foldl(fun(Record, N) ->
 
228
                                create_menu_item(Record, Menu, N)
 
229
                        end, 0, MenuItems),
 
230
            wxMenuBar:insert(MenuBar, Index, Menu, "File"),
 
231
            Index+1
 
232
    end;
 
233
create_menu(Name, MenuItems, Index, MenuBar, _Type) ->
 
234
    Menu = wxMenu:new(),
 
235
    lists:foldl(fun(Record, N) ->
 
236
                        create_menu_item(Record, Menu, N)
 
237
                end, 0, MenuItems),
 
238
    wxMenuBar:insert(MenuBar, Index, Menu, Name),
 
239
    Index+1.
 
240
 
 
241
create_menu_item(#create_menu{id = ?wxID_HELP=Id}, Menu, Index) ->
 
242
    wxMenu:insert(Menu, Index, Id),
 
243
    Index+1;
 
244
create_menu_item(#create_menu{id=Id, text=Text, help=Help, type=Type, check=Check},
 
245
                 Menu, Index) ->
 
246
    Opts = case Help of
 
247
               [] -> [];
 
248
               _ -> [{help, Help}]
 
249
           end,
 
250
    case Type of
 
251
        append ->
 
252
            wxMenu:insert(Menu, Index, Id,
 
253
                          [{text, Text}|Opts]);
 
254
        check ->
 
255
            wxMenu:insertCheckItem(Menu, Index, Id, Text, Opts),
 
256
            wxMenu:check(Menu, Id, Check);
 
257
        radio ->
 
258
            wxMenu:insertRadioItem(Menu, Index, Id, Text, Opts),
 
259
            wxMenu:check(Menu, Id, Check);
 
260
        separator ->
 
261
            wxMenu:insertSeparator(Menu, Index)
 
262
    end,
 
263
    Index+1;
 
264
create_menu_item(separator, Menu, Index) ->
 
265
    wxMenu:insertSeparator(Menu, Index),
 
266
    Index+1.
 
267
 
 
268
create_attrs() ->
 
269
    Font = wxSystemSettings:getFont(?wxSYS_DEFAULT_GUI_FONT),
 
270
    Text = case wxSystemSettings:getColour(?wxSYS_COLOUR_LISTBOXTEXT) of
 
271
               {255,255,255,_} -> {10,10,10};  %% Is white on Mac for some reason
 
272
               Color -> Color
 
273
           end,
 
274
    #attrs{even = wxListItemAttr:new(Text, ?BG_EVEN, Font),
 
275
           odd  = wxListItemAttr:new(Text, ?BG_ODD, Font),
 
276
           deleted = wxListItemAttr:new(?FG_DELETED, ?BG_DELETED, Font),
 
277
           changed = wxListItemAttr:new(Text, ?BG_CHANGED, Font),
 
278
           searched = wxListItemAttr:new(Text, ?BG_SEARCHED, Font)
 
279
          }.
 
280
 
 
281
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
282
 
 
283
get_box_info({Title, List}) when is_list(List) -> {Title, ?wxALIGN_LEFT, List};
 
284
get_box_info({Title, left, List}) -> {Title, ?wxALIGN_LEFT, List};
 
285
get_box_info({Title, right, List}) -> {Title, ?wxALIGN_RIGHT, List}.
 
286
 
 
287
create_box(Panel, Data) ->
 
288
    {Title, Align, Info} = get_box_info(Data),
 
289
    Box = wxStaticBoxSizer:new(?wxHORIZONTAL, Panel, [{label, Title}]),
 
290
    Left  = wxBoxSizer:new(?wxVERTICAL),
 
291
    Right = wxBoxSizer:new(?wxVERTICAL),
 
292
    Expand    = [{flag, ?wxEXPAND}],
 
293
    ExpAlign  = [{flag, Align}],
 
294
    AddRow = fun({Desc, Value}) ->
 
295
                     wxSizer:add(Left, wxStaticText:new(Panel, ?wxID_ANY, Desc ++ ":"), Expand),
 
296
                     Field = wxStaticText:new(Panel, ?wxID_ANY, to_str(Value)),
 
297
                     wxSizer:add(Right, Field, ExpAlign),
 
298
                     Field
 
299
             end,
 
300
    InfoFields = [AddRow(Entry) || Entry <- Info],
 
301
    wxSizer:add(Box, Left),
 
302
    wxSizer:addSpacer(Box, 10),
 
303
    wxSizer:add(Box, Right),
 
304
    wxSizer:addSpacer(Box, 30),
 
305
    {Box, InfoFields}.
 
306
 
 
307
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
308
set_listctrl_col_size(LCtrl, Total) ->
 
309
    wx:batch(fun() -> calc_last(LCtrl, Total) end).
 
310
 
 
311
calc_last(LCtrl, _Total) ->
 
312
    Cols = wxListCtrl:getColumnCount(LCtrl),
 
313
    {Total, _} = wxWindow:getClientSize(LCtrl),
 
314
    SBSize = scroll_size(LCtrl),
 
315
    Last = lists:foldl(fun(I, Last) ->
 
316
                               Last - wxListCtrl:getColumnWidth(LCtrl, I)
 
317
                       end, Total-SBSize, lists:seq(0, Cols - 2)),
 
318
    Size = max(150, Last),
 
319
    wxListCtrl:setColumnWidth(LCtrl, Cols-1, Size).
 
320
 
 
321
scroll_size(LCtrl) ->
 
322
    case os:type() of
 
323
        {win32, nt} -> 0;
 
324
        {unix, darwin} ->
 
325
            %% I can't figure out is there is a visible scrollbar
 
326
            %% Always make room for it
 
327
            wxSystemSettings:getMetric(?wxSYS_VSCROLL_X);
 
328
        _ ->
 
329
            case wxWindow:hasScrollbar(LCtrl, ?wxVERTICAL) of
 
330
                true -> wxSystemSettings:getMetric(?wxSYS_VSCROLL_X);
 
331
                false -> 0
 
332
            end
 
333
    end.
 
334
 
 
335
 
 
336
user_term(Parent, Title, Default) ->
 
337
    Dialog = wxTextEntryDialog:new(Parent, Title, [{value, Default}]),
 
338
    case wxTextEntryDialog:showModal(Dialog) of
 
339
        ?wxID_OK ->
 
340
            Str = wxTextEntryDialog:getValue(Dialog),
 
341
            wxTextEntryDialog:destroy(Dialog),
 
342
            parse_string(Str);
 
343
        ?wxID_CANCEL ->
 
344
            wxTextEntryDialog:destroy(Dialog)
 
345
    end.
 
346
 
 
347
parse_string(Str) ->
 
348
    try
 
349
        {ok, Tokens, _} = erl_scan:string(Str),
 
350
        erl_parse:parse_term(Tokens)
 
351
    catch _:{badmatch, {error, {_, _, Err}}} ->
 
352
            {error, ["Parse error: ", Err]};
 
353
          _Err ->
 
354
            {error, ["Syntax error in: ", Str]}
 
355
    end.