~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): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (1.1.13 upstream)
  • Revision ID: james.westby@ubuntu.com-20090215164252-dxpjjuq108nz4noa
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
132
132
        {Port,{data,Bytes}} ->
133
133
            case get(shell) of
134
134
                noshell ->
135
 
                    case string_chr(Bytes, [7,3]) of
136
 
                        0 ->
 
135
                    server_loop(Port, queue:snoc(Q, Bytes));
 
136
                _ ->
 
137
                    case contains_ctrl_g_or_ctrl_c(Bytes) of
 
138
                        false ->
137
139
                            server_loop(Port, queue:snoc(Q, Bytes));
138
140
                        _ ->
139
141
                            throw(new_shell)
140
 
                    end;
141
 
                _ ->
142
 
                    server_loop(Port, queue:snoc(Q, Bytes))
 
142
                    end
143
143
            end;
144
144
        {io_request,From,ReplyAs,Request} when is_pid(From) ->
145
145
            server_loop(Port, do_io_request(Request, From, ReplyAs, Port, Q));
341
341
        noshell ->
342
342
            get_chars_apply(State, M, F, Xa, Port, queue:snoc(Q, Bytes));
343
343
        _ ->
344
 
            case string_chr(Bytes, [7,3]) of
345
 
                0 ->
 
344
            case contains_ctrl_g_or_ctrl_c(Bytes) of
 
345
                false ->
346
346
                    get_chars_apply(State, M, F, Xa, Port, 
347
347
                                    queue:snoc(Q, Bytes));
348
348
                _ ->
391
391
 
392
392
%% prompt(Port, Prompt)
393
393
%%  Print Prompt onto Port
 
394
 
 
395
%% common case, reduces execution time by 20%
 
396
prompt(_Port, '') -> ok;
 
397
 
394
398
prompt(Port, Prompt) ->
395
399
    put_port(io_lib:format_prompt(Prompt), Port).
396
400
 
400
404
err_func(_, F, _) ->
401
405
    F.
402
406
 
403
 
%% Search for characters in a list or binary
404
 
string_chr(Bin, Characters) when is_binary(Bin), is_list(Characters) ->
405
 
    string_chr_bin(0, Bin, Characters);
406
 
string_chr(List, Characters) when is_list(List), is_list(Characters) ->
407
 
    string_chr_list(1, List, Characters).
408
 
 
409
 
string_chr_bin(I, B, Cs) when I < byte_size(B) ->
410
 
    J = I+1,
411
 
    case string_chr_bin_check(I, B, Cs) of
412
 
        ok ->
413
 
            J;
414
 
        0 ->
415
 
            string_chr_bin(J, B, Cs)
416
 
    end;
417
 
string_chr_bin(_, _, _) ->
418
 
    0.
419
 
 
420
 
string_chr_bin_check(I, B, [C|Cs]) ->
421
 
    case B of
422
 
        <<_:I/binary,C,_/binary>> ->
423
 
            ok;
424
 
        _ ->
425
 
            string_chr_bin_check(I, B, Cs)
426
 
    end;
427
 
string_chr_bin_check(_, _, []) ->
428
 
    0.
429
 
    
430
 
string_chr_list(I, [C|T], Cs) ->
431
 
    case lists:member(C, Cs) of
432
 
        true ->
433
 
            I;
434
 
        false ->
435
 
            string_chr_list(I+1, T, Cs)
436
 
    end;
437
 
string_chr_list(_, [], _) ->
438
 
    0.
 
407
%% using regexp reduces execution time by >50% compared to old code
 
408
%% running two regexps in sequence is much faster than \\x03|\\x07
 
409
contains_ctrl_g_or_ctrl_c(BinOrList)->
 
410
    case {re:run(BinOrList, <<3>>),re:run(BinOrList, <<7>>)} of
 
411
        {nomatch, nomatch} -> false;
 
412
        _ -> true
 
413
    end.
439
414
 
440
415
%% Convert a buffer between list and binary
441
416
cast(Data) ->