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

« back to all changes in this revision

Viewing changes to lib/kernel/src/user.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
%% Basic standard i/o server for user interface port.
21
21
 
22
22
-export([start/0, start/1, start_out/0]).
 
23
-export([interfaces/1]).
23
24
 
24
25
-define(NAME, user).
25
26
 
50
51
    register(?NAME,Id),
51
52
    Id.
52
53
 
 
54
%% Return the pid of the shell process.
 
55
%% Note: We can't ask the user process for this info since it
 
56
%% may be busy waiting for data from the port.
 
57
interfaces(User) ->
 
58
    case process_info(User, dictionary) of
 
59
        {dictionary,Dict} ->
 
60
            case lists:keysearch(shell, 1, Dict) of
 
61
                {value,Sh={shell,Shell}} when pid(Shell) ->
 
62
                    [Sh];
 
63
                _ ->
 
64
                    []
 
65
            end;
 
66
        _ ->
 
67
            []
 
68
    end.
 
69
 
 
70
 
53
71
server(Pid) when pid(Pid) ->
54
72
    process_flag(trap_exit, true),
55
73
    link(Pid),
65
83
    case init:get_argument(noshell) of
66
84
        %% non-empty list -> noshell
67
85
        {ok, [_|_]} -> 
68
 
            put(noshell, true),
 
86
            put(shell, noshell),
69
87
            server_loop(P, queue:new());
70
88
        _ ->
71
89
            group_leader(self(), self()),
72
 
            catch_loop(P, start_new_shell())
 
90
            catch_loop(P, start_init_shell())
73
91
    end.
74
92
 
75
93
catch_loop(Port, Shell) ->
95
113
            exit(R)
96
114
    end.
97
115
 
 
116
link_and_save_shell(Shell) ->
 
117
    link(Shell),
 
118
    put(shell, Shell),
 
119
    Shell.        
 
120
 
 
121
start_init_shell() ->
 
122
    link_and_save_shell(shell:start(init)).
 
123
 
98
124
start_new_shell() ->
99
 
    Shell = shell:start(),
100
 
    link(Shell),
101
 
    Shell.
 
125
    link_and_save_shell(shell:start()).
102
126
 
103
127
server_loop(Port, Q) ->
104
128
    receive
105
129
        {Port,{data,Bytes}} ->
106
 
            case get(noshell) of
107
 
                undefined ->
108
 
                    case string_chr(Bytes, 7) of
 
130
            case get(shell) of
 
131
                noshell ->
 
132
                    case string_chr(Bytes, [7,3]) of
109
133
                        0 ->
110
134
                            server_loop(Port, queue:snoc(Q, Bytes));
111
135
                        _ ->
128
152
 
129
153
        %% Check if shell has exited
130
154
        {'EXIT',SomePid,What} ->
131
 
            case get(noshell) of
132
 
                undefined ->
133
 
                    throw({unknown_exit,{SomePid,What},Q});
 
155
            case get(shell) of
 
156
                noshell ->
 
157
                    server_loop(Port, Q);       % Ignore
134
158
                _ ->
135
 
                    server_loop(Port, Q)        % Ignore
 
159
                    throw({unknown_exit,{SomePid,What},Q})
136
160
            end;
137
 
 
 
161
        
138
162
        _Other ->                               % Ignore other messages
139
163
            server_loop(Port, Q)
140
164
    end.
282
306
%% Second loop. Pass data to client as long as it wants more.
283
307
%% A ^G in data interrupts loop if 'noshell' is not undefined.
284
308
get_chars_bytes(State, M, F, Xa, Port, Q, Bytes) ->
285
 
    case get(noshell) of
286
 
        undefined ->
287
 
            case string_chr(Bytes, 7) of
 
309
    case get(shell) of
 
310
        noshell ->
 
311
            get_chars_apply(State, M, F, Xa, Port, queue:snoc(Q, Bytes));
 
312
        _ ->
 
313
            case string_chr(Bytes, [7,3]) of
288
314
                0 ->
289
315
                    get_chars_apply(State, M, F, Xa, Port, 
290
316
                                    queue:snoc(Q, Bytes));
291
317
                _ ->
292
318
                    throw(new_shell)
293
 
            end;
294
 
        _ ->
295
 
            get_chars_apply(State, M, F, Xa, Port, queue:snoc(Q, Bytes))
 
319
            end
296
320
    end.
297
321
 
298
322
get_chars_apply(State0, M, F, Xa, Port, Q) ->
357
381
err_func(_, F, _) ->
358
382
    F.
359
383
 
360
 
%% Search for a character in a list or binary
361
 
string_chr(Bin, Character) when binary(Bin), integer(Character) ->
362
 
    string_chr_bin(0, Bin, Character);
363
 
string_chr(List, Character) when list(List), integer(Character) ->
364
 
    string_chr_list(1, List, Character).
 
384
%% Search for characters in a list or binary
 
385
string_chr(Bin, Characters) when is_binary(Bin), is_list(Characters) ->
 
386
    string_chr_bin(0, Bin, Characters);
 
387
string_chr(List, Characters) when is_list(List), is_list(Characters) ->
 
388
    string_chr_list(1, List, Characters).
365
389
 
366
 
string_chr_bin(I, B, C) when I < size(B) ->
 
390
string_chr_bin(I, B, Cs) when I < size(B) ->
367
391
    J = I+1,
 
392
    case string_chr_bin_check(I, B, Cs) of
 
393
        ok ->
 
394
            J;
 
395
        0 ->
 
396
            string_chr_bin(J, B, Cs)
 
397
    end;
 
398
string_chr_bin(_, _, _) ->
 
399
    0.
 
400
 
 
401
string_chr_bin_check(I, B, [C|Cs]) ->
368
402
    case B of
369
403
        <<_:I/binary,C,_/binary>> ->
370
 
            J;
 
404
            ok;
371
405
        _ ->
372
 
            string_chr_bin(J, B, C)
 
406
            string_chr_bin_check(I, B, Cs)
373
407
    end;
374
 
string_chr_bin(_, _, _) ->
 
408
string_chr_bin_check(_, _, []) ->
375
409
    0.
376
 
 
 
410
    
 
411
string_chr_list(I, [C|T], Cs) ->
 
412
    case lists:member(C, Cs) of
 
413
        true ->
 
414
            I;
 
415
        false ->
 
416
            string_chr_list(I+1, T, Cs)
 
417
    end;
377
418
string_chr_list(_, [], _) ->
378
 
    0;
379
 
string_chr_list(I, [C|_], C) ->
380
 
    I;
381
 
string_chr_list(I, [_|T], C) ->
382
 
    string_chr_list(I+1, T, C).
 
419
    0.
383
420
 
384
421
%% Convert a buffer between list and binary
385
422
cast(Data) ->