~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

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

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
3
%%
4
 
%% Copyright Ericsson AB 1996-2010. All Rights Reserved.
 
4
%% Copyright Ericsson AB 1996-2011. All Rights Reserved.
5
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
42
42
-spec help() -> 'ok'.
43
43
 
44
44
help() ->
45
 
    format("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").
 
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">>).
70
70
 
71
71
%% c(FileName)
72
72
%%  Compile a file/module.
73
73
 
74
 
-spec c(file:name()) -> {'ok', module()} | 'error'.
 
74
-spec c(File) -> {'ok', Module} | 'error' when
 
75
      File :: file:name(),
 
76
      Module :: module().
75
77
 
76
78
c(File) -> c(File, []).
77
79
 
78
 
-spec c(file:name(), [compile:option()]) -> {'ok', module()} | 'error'.
 
80
-spec c(File, Options) -> {'ok', Module} | 'error' when
 
81
      File :: file:name(),
 
82
      Options :: [compile:option()],
 
83
      Module :: module().
79
84
 
80
85
c(File, Opts0) when is_list(Opts0) ->
81
86
    Opts = [report_errors,report_warnings|Opts0],
140
145
%% with constant c2 defined, c1=v1 (v1 must be a term!), include dir
141
146
%% IDir, outdir ODir.
142
147
 
143
 
-spec lc([erl_compile:cmd_line_arg()]) -> 'ok' | 'error'.
 
148
-spec lc(Files) -> 'ok' | 'error' when
 
149
      Files :: [File :: erl_compile:cmd_line_arg()].
144
150
 
145
151
lc(Args) ->
146
152
    case catch split(Args, [], []) of
205
211
            throw(error)
206
212
    end.
207
213
 
208
 
-spec nc(file:name()) -> {'ok', module()} | 'error'.
 
214
-spec nc(File) -> {'ok', Module} | 'error' when
 
215
      File :: file:name(),
 
216
      Module :: module().
209
217
 
210
218
nc(File) -> nc(File, []).
211
219
 
212
 
-spec nc(file:name(), [compile:option()] | compile:option()) ->
213
 
        {'ok', module} | 'error'.
 
220
-spec nc(File, Options) -> {'ok', Module} | 'error' when
 
221
      File :: file:name(),
 
222
      Options :: [Option] | Option,
 
223
      Option:: compile:option(),
 
224
      Module :: module().
214
225
 
215
226
nc(File, Opts0) when is_list(Opts0) ->
216
227
    Opts = Opts0 ++ [report_errors, report_warnings],
234
245
 
235
246
%% l(Mod)
236
247
%%  Reload module Mod from file of same name
237
 
-spec l(module()) -> code:load_ret().
 
248
-spec l(Module) -> code:load_ret() when
 
249
      Module :: module().
238
250
 
239
251
l(Mod) ->
240
252
    code:purge(Mod),
241
253
    code:load_file(Mod).
242
254
 
243
255
%% Network version of l/1
244
 
%%-spec nl(module()) ->
 
256
-spec nl(Module) -> abcast | error when
 
257
      Module :: module().
 
258
 
245
259
nl(Mod) ->
246
260
    case code:get_object_code(Mod) of
247
261
        {_Module, Bin, Fname} ->
396
410
        false -> 0
397
411
    end.
398
412
 
399
 
-spec pid(non_neg_integer(), non_neg_integer(), non_neg_integer()) -> pid().
 
413
-spec pid(X, Y, Z) -> pid() when
 
414
      X :: non_neg_integer(),
 
415
      Y :: non_neg_integer(),
 
416
      Z :: non_neg_integer().
400
417
 
401
418
pid(X, Y, Z) ->
402
419
    list_to_pid("<" ++ integer_to_list(X) ++ "." ++
403
420
                integer_to_list(Y) ++ "." ++
404
421
                integer_to_list(Z) ++ ">").
405
422
 
406
 
-spec i(non_neg_integer(), non_neg_integer(), non_neg_integer()) ->
407
 
        [{atom(), term()}].
 
423
-spec i(X, Y, Z) -> [{atom(), term()}] when
 
424
      X :: non_neg_integer(),
 
425
      Y :: non_neg_integer(),
 
426
      Z :: non_neg_integer().
408
427
 
409
428
i(X, Y, Z) -> pinfo(pid(X, Y, Z)).
410
429
 
413
432
q() ->
414
433
    init:stop().
415
434
 
416
 
-spec bt(pid()) -> 'ok' | 'undefined'.
 
435
-spec bt(Pid) -> 'ok' | 'undefined' when
 
436
      Pid :: pid().
417
437
 
418
438
bt(Pid) ->
419
439
    case catch erlang:process_display(Pid, backtrace) of
476
496
%%
477
497
%% Short and nice form of module info
478
498
%%
479
 
-spec m(module()) -> 'ok'.
 
499
-spec m(Module) -> 'ok' when
 
500
      Module :: module().
480
501
 
481
502
m(M) ->
482
503
    L = M:module_info(),
664
685
            ok = io:format("Cannot determine current directory\n")
665
686
    end.
666
687
 
667
 
-spec cd(file:name()) -> 'ok'.
 
688
-spec cd(Dir) -> 'ok' when
 
689
      Dir :: file:name().
668
690
 
669
691
cd(Dir) ->
670
692
    file:set_cwd(Dir),
679
701
ls() ->
680
702
    ls(".").
681
703
 
682
 
-spec ls(file:name()) -> 'ok'.
 
704
-spec ls(Dir) -> 'ok' when
 
705
      Dir :: file:name().
683
706
 
684
707
ls(Dir) ->
685
708
    case file:list_dir(Dir) of
729
752
%% memory/[0,1]
730
753
%%
731
754
 
732
 
-spec memory() -> [{atom(), non_neg_integer()}].
 
755
-spec memory() -> [{Type, Size}] when
 
756
      Type :: atom(),
 
757
      Size :: non_neg_integer().
733
758
 
734
759
memory() -> erlang:memory().
735
760
 
736
 
-spec memory(atom()) -> non_neg_integer()
737
 
          ; ([atom()]) -> [{atom(), non_neg_integer()}].
 
761
-spec memory(Type) -> Size when
 
762
               Type :: atom(),
 
763
               Size :: non_neg_integer()
 
764
          ; (Types) -> [{Type, Size}] when
 
765
               Types :: [Type],
 
766
               Type :: atom(),
 
767
               Size :: non_neg_integer().
738
768
 
739
769
memory(TypeSpec) -> erlang:memory(TypeSpec).
740
770
 
767
797
    catch
768
798
        error:undef ->
769
799
            case erlang:get_stacktrace() of
770
 
                [{M,F,Args}|_] ->
 
800
                [{M,F,Args,_}|_] ->
771
801
                    Arity = length(Args),
772
802
                    io:format("Call to ~w:~w/~w in application ~w failed.\n",
773
803
                              [M,F,Arity,App]);