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

« back to all changes in this revision

Viewing changes to lib/stdlib/src/c.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-2011. 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(c).
20
20
 
21
21
%% Utilities to use from shell.
22
22
 
 
23
%% Avoid warning for local function error/2 clashing with autoimported BIF.
 
24
-compile({no_auto_import,[error/2]}).
23
25
-export([help/0,lc/1,c/1,c/2,nc/1,nc/2, nl/1,l/1,i/0,i/1,ni/0,
24
26
         y/1, y/2,
25
27
         lc_batch/0, lc_batch/1,
31
33
-export([display_info/1]).
32
34
-export([appcall/4]).
33
35
 
34
 
-import(lists, [reverse/1,flatten/1,sublist/3,sort/1,keysearch/3,keysort/2,
 
36
-import(lists, [reverse/1,flatten/1,sublist/3,sort/1,keysort/2,
35
37
                concat/1,max/1,min/1,foreach/2,foldl/3,flatmap/2]).
36
38
-import(io, [format/1, format/2]).
37
39
 
 
40
%%-----------------------------------------------------------------------
 
41
 
 
42
-spec help() -> 'ok'.
 
43
 
38
44
help() ->
39
 
    format("bt(Pid)    -- stack backtrace for a process\n"
40
 
           "c(File)    -- compile and load code in <File>\n"
41
 
           "cd(Dir)    -- change working directory\n"
42
 
           "flush()    -- flush any messages sent to the shell\n"
43
 
           "help()     -- help info\n"
44
 
           "i()        -- information about the system\n"
45
 
           "ni()       -- information about the networked system\n"
46
 
           "i(X,Y,Z)   -- information about pid <X,Y,Z>\n"
47
 
           "l(Module)  -- load or reload module\n"
48
 
           "lc([File]) -- compile a list of Erlang modules\n"
49
 
           "ls()       -- list files in the current directory\n"
50
 
           "ls(Dir)    -- list files in directory <Dir>\n"
51
 
           "m()        -- which modules are loaded\n"
52
 
           "m(Mod)     -- information about module <Mod>\n"
53
 
           "memory()   -- memory allocation information\n"
54
 
           "memory(T)  -- memory allocation information of type <T>\n"
55
 
           "nc(File)   -- compile and load code in <File> on all nodes\n"
56
 
           "nl(Module) -- load module on all nodes\n"
57
 
           "pid(X,Y,Z) -- convert X,Y,Z to a Pid\n"
58
 
           "pwd()      -- print working directory\n"
59
 
           "q()        -- quit - shorthand for init:stop()\n"
60
 
           "regs()     -- information about registered processes\n"
61
 
           "nregs()    -- information about all registered processes\n"
62
 
           "xm(M)      -- cross reference check a module\n"
63
 
           "y(File)    -- generate a Yecc parser\n").
 
45
    io:put_chars(<<"bt(Pid)    -- stack backtrace for a process\n"
 
46
                   "c(File)    -- compile and load code in <File>\n"
 
47
                   "cd(Dir)    -- change working directory\n"
 
48
                   "flush()    -- flush any messages sent to the shell\n"
 
49
                   "help()     -- help info\n"
 
50
                   "i()        -- information about the system\n"
 
51
                   "ni()       -- information about the networked system\n"
 
52
                   "i(X,Y,Z)   -- information about pid <X,Y,Z>\n"
 
53
                   "l(Module)  -- load or reload module\n"
 
54
                   "lc([File]) -- compile a list of Erlang modules\n"
 
55
                   "ls()       -- list files in the current directory\n"
 
56
                   "ls(Dir)    -- list files in directory <Dir>\n"
 
57
                   "m()        -- which modules are loaded\n"
 
58
                   "m(Mod)     -- information about module <Mod>\n"
 
59
                   "memory()   -- memory allocation information\n"
 
60
                   "memory(T)  -- memory allocation information of type <T>\n"
 
61
                   "nc(File)   -- compile and load code in <File> on all nodes\n"
 
62
                   "nl(Module) -- load module on all nodes\n"
 
63
                   "pid(X,Y,Z) -- convert X,Y,Z to a Pid\n"
 
64
                   "pwd()      -- print working directory\n"
 
65
                   "q()        -- quit - shorthand for init:stop()\n"
 
66
                   "regs()     -- information about registered processes\n"
 
67
                   "nregs()    -- information about all registered processes\n"
 
68
                   "xm(M)      -- cross reference check a module\n"
 
69
                   "y(File)    -- generate a Yecc parser\n">>).
64
70
 
65
71
%% c(FileName)
66
72
%%  Compile a file/module.
67
73
 
 
74
-spec c(file:name()) -> {'ok', module()} | 'error'.
 
75
 
68
76
c(File) -> c(File, []).
69
77
 
 
78
-spec c(file:name(), [compile:option()]) -> {'ok', module()} | 'error'.
 
79
 
70
80
c(File, Opts0) when is_list(Opts0) ->
71
81
    Opts = [report_errors,report_warnings|Opts0],
72
82
    case compile:file(File, Opts) of
82
92
 
83
93
%%% Obtain the 'outdir' option from the argument. Return "." if no
84
94
%%% such option was given.
 
95
-spec outdir([compile:option()]) -> file:filename().
 
96
 
85
97
outdir([]) ->
86
98
    ".";
87
99
outdir([Opt|Rest]) ->
118
130
%%% loaded from some other place than current directory.
119
131
%%% Now, loading from other than current directory is supposed to work.
120
132
%%% so this function does nothing special.
121
 
check_load({error, R}, _) -> {error, R};
122
 
check_load(_, X) -> {ok, X}.
 
133
check_load({error, _R} = Error, _) -> Error;
 
134
check_load(_, Mod) -> {ok, Mod}.
123
135
 
124
136
%% Compile a list of modules
125
137
%% enables the nice unix shell cmd
128
140
%% with constant c2 defined, c1=v1 (v1 must be a term!), include dir
129
141
%% IDir, outdir ODir.
130
142
 
 
143
-spec lc([erl_compile:cmd_line_arg()]) -> 'ok' | 'error'.
 
144
 
131
145
lc(Args) ->
132
146
    case catch split(Args, [], []) of
133
147
        error -> error;
145
159
    io:format("Error: no files to compile~n"),
146
160
    halt(1).
147
161
 
148
 
-spec lc_batch([_]) -> no_return().
 
162
-spec lc_batch([erl_compile:cmd_line_arg()]) -> no_return().
149
163
 
150
164
lc_batch(Args) ->
151
165
    try split(Args, [], []) of
191
205
            throw(error)
192
206
    end.
193
207
 
 
208
-spec nc(file:name()) -> {'ok', module()} | 'error'.
 
209
 
194
210
nc(File) -> nc(File, []).
195
211
 
 
212
-spec nc(file:name(), [compile:option()] | compile:option()) ->
 
213
        {'ok', module} | 'error'.
 
214
 
196
215
nc(File, Opts0) when is_list(Opts0) ->
197
216
    Opts = Opts0 ++ [report_errors, report_warnings],
198
217
    case compile:file(File, Opts) of
199
218
        {ok,Mod} ->
200
 
            Fname = concat([File, code:objfile_extension()]),
 
219
            Dir = outdir(Opts),
 
220
            Obj = filename:basename(File, ".erl") ++ code:objfile_extension(),
 
221
            Fname = filename:join(Dir, Obj),
201
222
            case file:read_file(Fname) of
202
223
                {ok,Bin} ->
203
224
                    rpc:eval_everywhere(code,load_binary,[Mod,Fname,Bin]),
213
234
 
214
235
%% l(Mod)
215
236
%%  Reload module Mod from file of same name
 
237
-spec l(module()) -> code:load_ret().
216
238
 
217
239
l(Mod) ->
218
240
    code:purge(Mod),
219
241
    code:load_file(Mod).
220
242
 
221
243
%% Network version of l/1
 
244
%%-spec nl(module()) ->
222
245
nl(Mod) ->
223
246
    case code:get_object_code(Mod) of
224
247
        {_Module, Bin, Fname} ->
225
 
            rpc:eval_everywhere(code,load_binary,[Mod,Fname,Bin]);
 
248
            rpc:eval_everywhere(code, load_binary, [Mod, Fname, Bin]);
226
249
        Other ->
227
250
            Other
228
251
    end.
229
252
 
 
253
-spec i() -> 'ok'.
 
254
 
230
255
i() -> i(processes()).
 
256
 
 
257
-spec ni() -> 'ok'.
 
258
 
231
259
ni() -> i(all_procs()).
232
260
 
 
261
-spec i([pid()]) -> 'ok'.
 
262
 
233
263
i(Ps) ->
234
264
    i(Ps, length(Ps)).
235
265
 
 
266
-spec i([pid()], non_neg_integer()) -> 'ok'.
 
267
 
236
268
i(Ps, N) when N =< 100 ->
237
269
    iformat("Pid", "Initial Call", "Heap", "Reds",
238
270
            "Msgs"),
273
305
            paged_i([], NewAcc, 0, Page)
274
306
    end.
275
307
 
276
 
 
277
308
choice(F) ->
278
309
    case get_line('(c)ontinue (q)uit -->', "c\n") of
279
310
        "c\n" ->
283
314
        _ ->
284
315
            choice(F)
285
316
    end.
286
 
    
287
317
 
288
318
get_line(P, Default) ->
289
319
    case io:get_line(P) of
303
333
mfa_string(X) ->
304
334
    w(X).
305
335
 
306
 
 
307
336
display_info(Pid) ->
308
337
    case pinfo(Pid) of
309
338
        undefined -> {0,0,0,0};
315
344
                       Other ->
316
345
                           Other
317
346
                   end,
318
 
            Reds  = fetch(reductions, Info),
 
347
            Reds = fetch(reductions, Info),
319
348
            LM = length(fetch(messages, Info)),
320
349
            HS = fetch(heap_size, Info),
321
350
            SS = fetch(stack_size, Info),
362
391
    end.
363
392
 
364
393
fetch(Key, Info) ->
365
 
    case keysearch(Key, 1, Info) of
366
 
        {value, {_, Val}} -> Val;
 
394
    case lists:keyfind(Key, 1, Info) of
 
395
        {_, Val} -> Val;
367
396
        false -> 0
368
397
    end.
369
398
 
370
 
pid(X,Y,Z) ->
 
399
-spec pid(non_neg_integer(), non_neg_integer(), non_neg_integer()) -> pid().
 
400
 
 
401
pid(X, Y, Z) ->
371
402
    list_to_pid("<" ++ integer_to_list(X) ++ "." ++
372
403
                integer_to_list(Y) ++ "." ++
373
404
                integer_to_list(Z) ++ ">").
374
405
 
375
 
i(X,Y,Z) -> pinfo(pid(X,Y,Z)).
 
406
-spec i(non_neg_integer(), non_neg_integer(), non_neg_integer()) ->
 
407
        [{atom(), term()}].
 
408
 
 
409
i(X, Y, Z) -> pinfo(pid(X, Y, Z)).
 
410
 
 
411
-spec q() -> no_return().
376
412
 
377
413
q() ->
378
414
    init:stop().
379
415
 
 
416
-spec bt(pid()) -> 'ok' | 'undefined'.
 
417
 
380
418
bt(Pid) ->
381
419
    case catch erlang:process_display(Pid, backtrace) of
382
420
        {'EXIT', _} ->
385
423
            ok
386
424
    end.
387
425
 
 
426
-spec m() -> 'ok'.
 
427
 
388
428
m() ->
389
429
    mformat("Module", "File"),
390
430
    foreach(fun ({Mod,File}) -> mformat(Mod, File) end, sort(code:all_loaded())).
412
452
 
413
453
f_p_e(P, F) ->
414
454
    case file:path_eval(P, F) of
415
 
        {error, enoent} ->
416
 
            {error, enoent};
 
455
        {error, enoent} = Enoent ->
 
456
            Enoent;
417
457
        {error, E={Line, _Mod, _Term}} ->
418
458
            error("file:path_eval(~p,~p): error on line ~p: ~s~n",
419
459
                  [P, F, Line, file:format_error(E)]),
436
476
%%
437
477
%% Short and nice form of module info
438
478
%%
 
479
-spec m(module()) -> 'ok'.
439
480
 
440
481
m(M) ->
441
482
    L = M:module_info(),
442
 
    {value,{exports,E}} = keysearch(exports, 1, L),
 
483
    {exports,E} = lists:keyfind(exports, 1, L),
443
484
    Time = get_compile_time(L),
444
485
    COpts = get_compile_options(L),
445
486
    format("Module ~w compiled: ",[M]), print_time(Time),
468
509
    end.
469
510
 
470
511
get_compile_info(L, Tag) ->
471
 
    case keysearch(compile, 1, L) of
472
 
        {value, {compile, I}} ->
473
 
            case keysearch(Tag, 1, I) of
474
 
                {value, {Tag, Val}} -> {ok,Val};
 
512
    case lists:keyfind(compile, 1, L) of
 
513
        {compile, I} ->
 
514
            case lists:keyfind(Tag, 1, I) of
 
515
                {Tag, Val} -> {ok,Val};
475
516
                false -> error
476
517
            end;
477
518
        false -> error
521
562
month(12) -> "December".
522
563
 
523
564
%% Just because we can't eval receive statements...
 
565
-spec flush() -> 'ok'.
 
566
 
524
567
flush() ->
525
568
    receive
526
569
        X ->
531
574
    end.
532
575
 
533
576
%% Print formatted info about all registered names in the system
 
577
-spec nregs() -> 'ok'.
 
578
 
534
579
nregs() ->
535
580
    foreach(fun (N) -> print_node_regs(N) end, all_regs()).
536
581
 
 
582
-spec regs() -> 'ok'.
 
583
 
537
584
regs() ->
538
585
    print_node_regs({node(),registered()}).
539
586
 
607
654
%% cd(Directory)
608
655
%%  These are just wrappers around the file:get/set_cwd functions.
609
656
 
 
657
-spec pwd() -> 'ok'.
 
658
 
610
659
pwd() ->
611
660
    case file:get_cwd() of
612
661
        {ok, Str} ->
613
 
            ok = io:format("~s\n", [Str]);
 
662
            ok = io:format("~ts\n", [fixup_one_bin(Str)]);
614
663
        {error, _} ->
615
664
            ok = io:format("Cannot determine current directory\n")
616
665
    end.
617
666
 
 
667
-spec cd(file:name()) -> 'ok'.
 
668
 
618
669
cd(Dir) ->
619
670
    file:set_cwd(Dir),
620
671
    pwd().
623
674
%% ls(Directory)
624
675
%%  The strategy is to print in fixed width files.
625
676
 
 
677
-spec ls() -> 'ok'.
 
678
 
626
679
ls() ->
627
680
    ls(".").
628
681
 
 
682
-spec ls(file:name()) -> 'ok'.
 
683
 
629
684
ls(Dir) ->
630
685
    case file:list_dir(Dir) of
631
686
        {ok, Entries} ->
632
 
            ls_print(sort(Entries));
 
687
            ls_print(sort(fixup_bin(Entries)));
633
688
        {error,_E} ->
634
689
            format("Invalid directory\n")
635
690
    end.
636
691
 
 
692
fixup_one_bin(X) when is_binary(X) ->
 
693
    L = binary_to_list(X),
 
694
    [ if 
 
695
          El > 127 ->
 
696
              $?;
 
697
          true ->
 
698
              El
 
699
      end || El <- L];
 
700
fixup_one_bin(X) -> 
 
701
    X.
 
702
fixup_bin([H|T]) ->
 
703
    [fixup_one_bin(H) | fixup_bin(T)];
 
704
fixup_bin([]) ->
 
705
    [].
 
706
              
 
707
 
637
708
ls_print([]) -> ok;
638
709
ls_print(L) ->
639
710
    Width = min([max(lengths(L, [])), 40]) + 5,
643
714
    io:nl(),
644
715
    ls_print(X, Width, 0);
645
716
ls_print([H|T], Width, Len) ->
646
 
    io:format("~-*s",[Width,H]),
 
717
    io:format("~-*ts",[Width,H]),
647
718
    ls_print(T, Width, Len+Width);
648
719
ls_print([], _, _) ->
649
720
    io:nl().
658
729
%% memory/[0,1]
659
730
%%
660
731
 
661
 
memory()         -> erlang:memory().
 
732
-spec memory() -> [{atom(), non_neg_integer()}].
 
733
 
 
734
memory() -> erlang:memory().
 
735
 
 
736
-spec memory(atom()) -> non_neg_integer()
 
737
          ; ([atom()]) -> [{atom(), non_neg_integer()}].
 
738
 
662
739
memory(TypeSpec) -> erlang:memory(TypeSpec).
663
740
 
664
741
%%
665
742
%% Cross Reference Check
666
743
%% 
667
 
 
 
744
%%-spec xm(module() | file:filename()) -> xref:m/1 return
668
745
xm(M) ->
669
746
    appcall(tools, xref, m, [M]).
670
747
 
671
748
%%
672
749
%% Call yecc 
673
750
%% 
674
 
 
 
751
%%-spec y(file:name()) -> yecc:file/2 return
675
752
y(File) -> y(File, []).
676
753
 
 
754
%%-spec y(file:name(), [yecc:option()]) -> yecc:file/2 return
677
755
y(File, Opts) ->
678
 
    appcall(parsetools, yecc, file, [File,Opts]).
 
756
    appcall(parsetools, yecc, file, [File, Opts]).
679
757
 
680
758
 
681
759
%%
697
775
                    erlang:raise(error, undef, Stk)
698
776
            end
699
777
    end.
700