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

« back to all changes in this revision

Viewing changes to lib/appmon/src/appmon_txt.erl

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
20
20
%% Simple text viewer
21
21
%%
22
22
%%------------------------------------------------------------
23
 
%%
24
 
%%
25
 
%%              INTRODUCTION
26
 
%%              ------------
27
 
%%
28
 
%%------------------------------------------------------------
29
 
 
30
 
 
31
23
 
32
24
-module(appmon_txt).
33
 
 
34
 
 
35
25
-export([start/0, start/1, print/1, fprint/1]).
36
26
 
37
27
%% gen_server stuff
38
 
-export([init/1, handle_call/3, handle_cast/2, handle_info/2, terminate/2]).
39
 
 
 
28
-export([init/1, handle_call/3, handle_cast/2, handle_info/2,
 
29
         terminate/2]).
40
30
 
41
31
-define(LOADTXT, "Load file").
42
32
-define(SAVETXT, "Save file").
50
40
%% whatever.
51
41
%%
52
42
%%------------------------------------------------------------
53
 
 
54
 
 
 
43
start() ->
 
44
    start([]).
55
45
 
56
46
%%------------------------------------------------------------
57
47
%%
63
53
%% {text, Text}         - insert text at startup
64
54
%%
65
55
%%------------------------------------------------------------
66
 
 
67
 
 
68
 
start() ->
69
 
    start([]).
70
 
 
71
56
start(Opts) ->
72
57
    gen_server:start_link({local, ?MODULE}, ?MODULE, Opts, []).
73
58
 
74
59
%% Start a text viewer if necessary
75
60
print(Txt) ->
76
 
%    case whereis(?MODULE) of
77
 
%       Pid when pid(Pid) ->
78
 
%           ok;
79
 
%       Other ->
80
 
%           start()
81
 
%    end,
82
61
    catch start(),
83
62
    gen_server:call(?MODULE, {add_txt, Txt}),
84
63
    ok.
94
73
 
95
74
init(Opts) ->
96
75
    process_flag(trap_exit, true),
97
 
    %%io:format("Starting editor w args: ~p~n", [Opts]),
98
76
    setup_base_win(),
99
77
    default_status(),
100
78
    setup_opts(Opts),
101
 
%%    receive
102
 
%%    after 6000 -> ok end,
103
79
    {ok, []}.
104
80
 
105
 
terminate(Reason, State) ->
106
 
    %%io:format("Terminating editor:~n", []),
 
81
terminate(_Reason, _State) ->
107
82
    ok.
108
83
 
109
84
%%------------------------------------------------------------
110
85
%% gen server stuff
111
 
handle_call({add_txt, Txt}, From, State) ->
112
 
    %%io:format("~p got call: ~p~n", [self(), Request]),
 
86
handle_call({add_txt, Txt}, _From, State) ->
113
87
    do_insert_text(Txt),
114
88
    scroll_to_last_line(),
115
89
    {reply, ok, State};
116
 
handle_call({add_file, FileName}, From, State) ->
117
 
    %%io:format("~p got call: ~p~n", [self(), Request]),
 
90
handle_call({add_file, FileName}, _From, State) ->
118
91
    do_load_file(FileName),
119
92
    {reply, ok, State};
120
 
handle_call(Request, From, State) ->
121
 
    %%io:format("~p got call: ~p~n", [self(), Request]),
 
93
handle_call(_Request, _From, State) ->
122
94
    {reply, ok, State}.
123
 
handle_cast(Request, State) ->
124
 
    %%io:format("~p got cast: ~p~n", [self(), Request]),
 
95
handle_cast(_Request, State) ->
125
96
    {noreply, State}.
126
97
handle_info({gs, _, click, _, [?CLOSETXT|_]}, State) ->
127
 
    %%d:d("handle_info: exit: Close button pressed~n", []),
128
98
    {stop, normal, State};
129
99
handle_info({gs, _, click, _, [?LOADTXT|_]}, State) ->
130
100
    ui_load(),
134
104
    {noreply, State};
135
105
 
136
106
handle_info({gs, _, destroy, _, _}, State) ->
137
 
%%    ?D("handle_info: exit: window killed~n", []),
138
107
    {stop, normal, State};
139
 
%%%handle_info({gs, _, click, _, [?HELPTXT|_]}, State) ->
140
 
%%%    d:d("~p: help:~n", [node()]),
141
 
%%%    print_help(),
142
 
%%%    {noreply, State};
143
 
%%%handle_info({gs, Id, click, {mode, Mode}, _}, State) ->
144
 
%%%    %%io:format("handle_info: Setting mode: ~p~n", [Mode]),
145
 
%%%    set_mode(Id, Mode),
146
 
%%%    {noreply, State};
147
108
handle_info(Request, State) ->
148
109
    io:format("~p got info: ~p~n", [self(), Request]),
149
110
    print_status("Not implemented"),
166
127
            do_lock();
167
128
        {text, Text} ->
168
129
            do_insert_text(Text);
169
 
        Other ->
 
130
        _Other ->
170
131
            ok
171
132
    end.
172
133
 
173
134
do_load_file(FileName) ->
174
 
    Msg = case catch i_load_file(FileName) of
175
 
              ok ->
176
 
                  default_status();
177
 
              Other -> 
178
 
                  print_status(lists:append(["File not found: ", FileName]))
179
 
          end.
180
 
 
 
135
    case catch i_load_file(FileName) of
 
136
        ok ->
 
137
            default_status();
 
138
        _Other -> 
 
139
            print_status(lists:append(["File not found: ", FileName]))
 
140
    end.
181
141
 
182
142
i_load_file(FileName) ->
183
143
    {ok, Bin} = file:read_file(FileName),
192
152
    case catch ui_list_dialog(Title, "File: ", Files) of
193
153
        {ok, FileName} ->
194
154
            do_load_file(FileName);
195
 
        Other ->
 
155
        _Other ->
196
156
            print_status("Load cancelled")
197
157
    end.
198
158
 
199
159
get_file_list() ->
200
160
    case file:list_dir(".") of
201
161
        {ok, FileList} -> lists:sort(FileList);
202
 
        Other -> []
 
162
        _Other -> []
203
163
    end.
204
164
 
205
 
 
206
 
 
207
165
do_insert_text(Text) ->
208
166
    gs:config(editor(), {insert, {'end', Text}}),
209
167
    ok.
213
171
    H = gs:read(editor(), size),
214
172
    R = gs:read(editor(), height),
215
173
    TopRow = H-R/15,
216
 
%%    io:format("Top: ~p, ~p - ~p~n", [TopRow, H, R]),
217
174
    if  TopRow > 0 -> gs:config(editor(), {vscrollpos, TopRow});
218
175
        true       -> gs:config(editor(), {vscrollpos, 0})
219
176
        end,
220
177
    ok.
221
178
 
222
 
 
223
179
do_lock() ->    
224
180
    gs:config(editor(), {enable, false}).
225
181
 
226
 
 
227
 
 
228
182
i_do_clear() ->
229
183
    gs:config(editor(), clear).
230
184
 
231
 
 
232
185
%%------------------------------------------------------------
233
186
%% Graphical stuff
234
187
 
243
196
    set_winroot(F),
244
197
 
245
198
    Win = gs:create(window, F, [{width, W}, {height, H}, 
246
 
                                {title, "APPMON: Process Information"}]),
 
199
                                {title,"APPMON: Process Information"}]),
247
200
 
248
201
    E = gs:create(editor, Win, [{x, 0}, {y, MenuHeight}, 
249
202
                                {width, W}, 
263
216
 
264
217
    FMB = gs:create(menubutton, MB, [{label, {text, "File"}}]),
265
218
    FM = gs:create(menu, FMB, []),
266
 
    %%gs:create(menuitem, FM, [{label, {text, ?LOADTXT}}]),
267
 
    %%gs:create(menuitem, FM, [{label, {text, ?SAVETXT}}]),
268
 
    %%gs:create(menuitem, FM, [{label, {text, ?SAVEASTXT}}]),
269
 
    %%gs:create(menuitem, FM, [{itemtype, separator}]),
270
219
    gs:create(menuitem, FM, [{label, {text, ?CLOSETXT}}]),
271
220
 
272
 
%%    EMB = gs:create(menubutton, MB, [{label, {text, "Edit"}}]),
273
 
%%    EM = gs:create(menu, EMB, []),
274
 
    
275
 
    
276
 
%    HMB = gs:create(menubutton, MB, [{label, {text, "Help"}}, {side, right}]),
277
 
%    HM = gs:create(menu, HMB, []),
278
 
%    gs:create(menuitem, HM, [{label, {text, ?HELPTXT}}]),
279
 
 
280
221
    gs:config(Win, {configure, true}),
281
222
    ok.
282
223
 
283
224
resize(W, H) ->
284
 
%%    io:format("Resizing to: ~p, ~p~n", [W, H]),
285
 
    %% resize editor
286
225
    gs:config(editor(), [{width, W}, {height, H-label_h()-menu_h()}]),
287
 
    %% resize move label
288
226
    gs:config(status(), [{y, H-label_h()}, {width, W}]),
289
227
    ok.
290
228
 
291
 
 
292
 
 
293
229
%%------------------------------------------------------------
294
230
%% ui_list_dialog(
295
231
%%
309
245
    
310
246
    Win = gs:create(window, winroot(), [{title, Title}, 
311
247
                                        {width, W},{height, H}]),
312
 
    Ok = gs:create(button, Win, [{x, 10}, {y,10}, {width, 50}, {height, 20},
 
248
    Ok = gs:create(button, Win, [{x, 10}, {y,10},
 
249
                                 {width, 50}, {height, 20},
313
250
                                 {label, {text, "Ok"}}]),
314
 
    Cn = gs:create(button, Win, [{x, 70}, {y,10}, {width, 50}, {height, 20},
 
251
    Cn = gs:create(button, Win, [{x, 70}, {y,10},
 
252
                                 {width, 50}, {height, 20},
315
253
                                 {label, {text, "Cancel"}}]),
316
254
 
317
 
    gs:create(label, Win, [{x, 10}, {y, 50}, {width, 60}, {height, 20},
 
255
    gs:create(label, Win, [{x, 10}, {y, 50},
 
256
                           {width, 60}, {height, 20},
318
257
                           {label, {text, LeadText}}]),
319
 
    Box = gs:create(entry, Win, [{x, 10}, {y, 70}, {width, 160}, {height, 20},
 
258
    Box = gs:create(entry, Win, [{x, 10}, {y, 70},
 
259
                                 {width, 160}, {height, 20},
320
260
                                 {keypress, true}]),
321
261
    List = gs:create(listbox, Win, [{x, 10}, {y, 100}, {width, 180}, 
322
262
                                    {height, 190},
323
263
                                    {items, TxtList}, {vscroll, right},
324
264
                                    {hscroll, false}, {click, true},
325
 
                                    {doubleclick, true}, {keypress, true}]),
 
265
                                    {doubleclick, true},
 
266
                                    {keypress, true}]),
326
267
    gs:config(Win, {map, true}),
327
268
 
328
269
    RetVal = ui_load_loop(Box, List, Ok, Cn),
339
280
            ui_load_loop(Box, List, Ok, Cn);
340
281
        {gs, Ok, click, _, _} ->
341
282
            {ok, gs:read(Box, text)};
342
 
        {gs, List, doubleclick, _, [Idx, Txt|_]} ->
 
283
        {gs, List, doubleclick, _, [_Idx, Txt|_]} ->
343
284
            {ok, Txt};
344
 
        {gs, List, click, _, [Idx, Txt|_]} ->
 
285
        {gs, List, click, _, [_Idx, Txt|_]} ->
345
286
            gs:config(Box, {text, Txt}),
346
287
            ui_load_loop(Box, List, Ok, Cn);
347
 
        Other -> 
 
288
        _Other -> 
348
289
            something_else
349
290
    end.
350
291
 
351
 
 
352
 
 
353
 
 
354
292
%% The status row at the bottom of the window
355
293
set_status(Id) -> put(status_row, Id).
356
294
status() -> get(status_row).
362
300
 
363
301
winroot() -> get(winroot).
364
302
set_winroot(X) -> put(winroot, X).
365
 
 
366
 
%%destroy(undefined) -> ok;
367
 
%%destroy(Id) -> gs:destroy(Id).
368
 
 
369
 
 
370
 
 
371