~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/stdlib/src/shell.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1996-2010. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
-module(shell).
22
22
-export([whereis_evaluator/0, whereis_evaluator/1]).
23
23
-export([start_restricted/1, stop_restricted/0]).
24
24
-export([local_allowed/3, non_local_allowed/3]).
 
25
-export([prompt_func/1]).
25
26
 
26
27
-define(LINEMAX, 30).
27
28
-define(CHAR_MAX, 60).
28
29
-define(DEF_HISTORY, 20).
29
30
-define(DEF_RESULTS, 20).
30
31
-define(DEF_CATCH_EXCEPTION, false).
 
32
-define(DEF_PROMPT_FUNC, default).
31
33
 
32
34
-define(RECORDS, shell_records).
33
35
 
235
237
    {History,Results} = check_and_get_history_and_results(),
236
238
    server_loop(0, start_eval(Bs, RT, []), Bs, RT, [], History, Results).
237
239
 
238
 
server_loop(N0, Eval_0, Bs0, RT, Ds0, History0, Results0) ->
 
240
server_loop(N0, Eval_0, Bs00, RT, Ds00, History0, Results0) ->
239
241
    N = N0 + 1,
240
 
    {Res, Eval0} = get_command(prompt(N), Eval_0, Bs0, RT, Ds0),
 
242
    {Eval_1,Bs0,Ds0,Prompt} = prompt(N, Eval_0, Bs00, RT, Ds00),
 
243
    {Res,Eval0} = get_command(Prompt, Eval_1, Bs0, RT, Ds0),
241
244
    case Res of 
242
245
        {ok,Es0,_EndLine} ->
243
246
            case expand_hist(Es0, N) of
244
247
                {ok,Es} ->
245
 
                    {V,Eval,Bs,Ds} = shell_cmd(Es, Eval0, Bs0, RT, Ds0),
 
248
                    {V,Eval,Bs,Ds} = shell_cmd(Es, Eval0, Bs0, RT, Ds0, cmd),
246
249
                    {History,Results} = check_and_get_history_and_results(),
247
250
                    add_cmd(N, Es, V),
248
251
                    HB1 = del_cmd(command, N - History, N - History0, false),
301
304
            get_command1(Pid, start_eval(Bs, RT, Ds), Bs, RT, Ds)
302
305
    end.
303
306
 
304
 
prompt(N) ->
 
307
prompt(N, Eval0, Bs0, RT, Ds0) ->
 
308
    case get_prompt_func() of
 
309
        {M,F} ->
 
310
            L = [{history,N}],
 
311
            C = {call,1,{remote,1,{atom,1,M},{atom,1,F}},[{value,1,L}]},
 
312
            {V,Eval,Bs,Ds} = shell_cmd([C], Eval0, Bs0, RT, Ds0, pmt),
 
313
            {Eval,Bs,Ds,case V of
 
314
                            {pmt,Val} ->
 
315
                                Val;
 
316
                            _ ->
 
317
                                bad_prompt_func({M,F}),
 
318
                                default_prompt(N)
 
319
                        end};
 
320
        default ->
 
321
            {Eval0,Bs0,Ds0,default_prompt(N)}
 
322
    end.
 
323
 
 
324
get_prompt_func() ->
 
325
    case application:get_env(stdlib, shell_prompt_func) of
 
326
        {ok,{M,F}=PromptFunc} when is_atom(M), is_atom(F) ->
 
327
            PromptFunc;
 
328
        {ok,default=Default} ->
 
329
            Default;
 
330
        {ok,Term} ->
 
331
            bad_prompt_func(Term),
 
332
            default;
 
333
        undefined ->
 
334
            default
 
335
    end.
 
336
 
 
337
bad_prompt_func(M) ->
 
338
    fwrite_severity(benign, <<"Bad prompt function: ~p">>, [M]).
 
339
 
 
340
default_prompt(N) ->
 
341
    %% Don't bother flattening the list irrespective of what the
 
342
    %% I/O-protocol states.
305
343
    case is_alive() of
306
344
        true  -> io_lib:format(<<"(~s)~w> ">>, [node(), N]);
307
345
        false -> io_lib:format(<<"~w> ">>, [N])
461
499
    has_bin(element(I, T)),
462
500
    has_bin(T, I - 1).
463
501
 
464
 
%% shell_cmd(Sequence, Evaluator, Bindings, RecordTable, Dictionary)
 
502
%% shell_cmd(Sequence, Evaluator, Bindings, RecordTable, Dictionary, What)
465
503
%% shell_rep(Evaluator, Bindings, RecordTable, Dictionary) ->
466
504
%%      {Value,Evaluator,Bindings,Dictionary}
467
505
%%  Send a command to the evaluator and wait for the reply. Start a new
468
506
%%  evaluator if necessary.
 
507
%%  What = pmt | cmd. When evaluating a prompt ('pmt') the evaluated value
 
508
%%  must not be displayed, and it has to be returned.
469
509
 
470
 
shell_cmd(Es, Eval, Bs, RT, Ds) ->
471
 
    Eval ! {shell_cmd,self(),{eval,Es}},
 
510
shell_cmd(Es, Eval, Bs, RT, Ds, W) ->
 
511
    Eval ! {shell_cmd,self(),{eval,Es}, W},
472
512
    shell_rep(Eval, Bs, RT, Ds).
473
513
 
474
514
shell_rep(Ev, Bs0, RT, Ds0) ->
559
599
 
560
600
eval_loop(Shell, Bs0, RT) ->
561
601
    receive
562
 
        {shell_cmd,Shell,{eval,Es}} ->
 
602
        {shell_cmd,Shell,{eval,Es},W} ->
563
603
            Ef = {value, 
564
604
                  fun(MForFun, As) -> apply_fun(MForFun, As, Shell) end},
565
605
            Lf = local_func_handler(Shell, RT, Ef),
566
 
            Bs = eval_exprs(Es, Shell, Bs0, RT, Lf, Ef),
 
606
            Bs = eval_exprs(Es, Shell, Bs0, RT, Lf, Ef, W),
567
607
            eval_loop(Shell, Bs, RT)
568
608
    end.
569
609
 
570
610
restricted_eval_loop(Shell, Bs0, RT, RShMod) ->
571
611
    receive
572
 
        {shell_cmd,Shell,{eval,Es}} ->
 
612
        {shell_cmd,Shell,{eval,Es}, W} ->
573
613
            {LFH,NLFH} = restrict_handlers(RShMod, Shell, RT),
574
614
            put(restricted_expr_state, []),
575
 
            Bs = eval_exprs(Es, Shell, Bs0, RT, {eval,LFH}, {value,NLFH}),
 
615
            Bs = eval_exprs(Es, Shell, Bs0, RT, {eval,LFH}, {value,NLFH}, W),
576
616
            restricted_eval_loop(Shell, Bs, RT, RShMod)
577
617
    end.
578
618
 
579
 
eval_exprs(Es, Shell, Bs0, RT, Lf, Ef) ->
 
619
eval_exprs(Es, Shell, Bs0, RT, Lf, Ef, W) ->
580
620
    try 
581
 
        {R,Bs2} = exprs(Es, Bs0, RT, Lf, Ef),
 
621
        {R,Bs2} = exprs(Es, Bs0, RT, Lf, Ef, W),
582
622
        Shell ! {shell_rep,self(),R},
583
623
        Bs2
584
624
    catch 
614
654
            false
615
655
    end.
616
656
 
617
 
exprs(Es, Bs0, RT, Lf, Ef) ->
618
 
    exprs(Es, Bs0, RT, Lf, Ef, Bs0).
 
657
exprs(Es, Bs0, RT, Lf, Ef, W) ->
 
658
    exprs(Es, Bs0, RT, Lf, Ef, Bs0, W).
619
659
 
620
 
exprs([E0|Es], Bs1, RT, Lf, Ef, Bs0) ->
 
660
exprs([E0|Es], Bs1, RT, Lf, Ef, Bs0, W) ->
621
661
    UsedRecords = used_record_defs(E0, RT),
622
662
    RBs = record_bindings(UsedRecords, Bs1),
623
663
    case check_command(prep_check([E0]), RBs) of
629
669
            if
630
670
                Es =:= [] ->
631
671
                    VS = pp(V0, 1, RT),
632
 
                    io:requests([{put_chars, VS}, nl]),
 
672
                    [io:requests([{put_chars, VS}, nl]) || W =:= cmd],
633
673
                    %% Don't send the result back if it will be
634
674
                    %% discarded anyway.
635
 
                    V = case result_will_be_saved() of
636
 
                            true -> V0;
637
 
                            false -> ignored
 
675
                    V = if
 
676
                            W =:= pmt ->
 
677
                                {W,V0};
 
678
                            true -> case result_will_be_saved() of
 
679
                                     true -> V0;
 
680
                                     false -> ignored
 
681
                                 end
638
682
                        end,
639
683
                    {{value,V,Bs,get()},Bs};
640
684
                true -> 
641
 
                    exprs(Es, Bs, RT, Lf, Ef, Bs0)
 
685
                    exprs(Es, Bs, RT, Lf, Ef, Bs0, W)
642
686
            end;
643
687
        {error,Error} ->
644
688
            {{command_error,Error},Bs0}
1383
1427
 
1384
1428
columns() ->
1385
1429
    case io:columns() of
1386
 
        {ok,N} ->  N;
 
1430
        {ok,N} -> N;
1387
1431
        _ -> 80
1388
1432
    end.
1389
1433
 
1438
1482
 
1439
1483
catch_exception(Bool) ->
1440
1484
    set_env(stdlib, shell_catch_exception, Bool, ?DEF_CATCH_EXCEPTION).
 
1485
 
 
1486
-type prompt_func() :: 'default' | {module(),atom()}.
 
1487
-spec prompt_func(prompt_func()) -> prompt_func().
 
1488
 
 
1489
prompt_func(String) ->
 
1490
    set_env(stdlib, shell_prompt_func, String, ?DEF_PROMPT_FUNC).