1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 1996-2018. All Rights Reserved.
5%%
6%% Licensed under the Apache License, Version 2.0 (the "License");
7%% you may not use this file except in compliance with the License.
8%% You may obtain a copy of the License at
9%%
10%%     http://www.apache.org/licenses/LICENSE-2.0
11%%
12%% Unless required by applicable law or agreed to in writing, software
13%% distributed under the License is distributed on an "AS IS" BASIS,
14%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15%% See the License for the specific language governing permissions and
16%% limitations under the License.
17%%
18%% %CopyrightEnd%
19%%
20-module(c).
21
22-include_lib("kernel/include/eep48.hrl").
23
24%% Utilities to use from shell.
25
26%% Avoid warning for local function error/2 clashing with autoimported BIF.
27-compile({no_auto_import,[error/2]}).
28-export([help/0,lc/1,c/1,c/2,c/3,nc/1,nc/2, nl/1,l/1,i/0,i/1,ni/0,
29         y/1, y/2,
30	 lc_batch/0, lc_batch/1,
31	 i/3,pid/3,m/0,m/1,mm/0,lm/0,
32	 bt/1, q/0,
33         h/1,h/2,h/3,ht/1,ht/2,ht/3,hcb/1,hcb/2,hcb/3,
34	 erlangrc/0,erlangrc/1,bi/1, flush/0, regs/0, uptime/0,
35	 nregs/0,pwd/0,ls/0,ls/1,cd/1,memory/1,memory/0, xm/1]).
36
37-export([display_info/1]).
38-export([appcall/4]).
39
40-import(lists, [reverse/1,flatten/1,sublist/3,sort/1,keysort/2,
41		foreach/2,foldl/3,flatmap/2]).
42-import(io, [format/1, format/2]).
43
44%%-----------------------------------------------------------------------
45
46-spec help() -> 'ok'.
47
48help() ->
49    io:put_chars(<<"bt(Pid)    -- stack backtrace for a process\n"
50		   "c(Mod)     -- compile and load module or file <Mod>\n"
51		   "cd(Dir)    -- change working directory\n"
52		   "flush()    -- flush any messages sent to the shell\n"
53		   "help()     -- help info\n"
54                   "h(M)       -- module documentation\n"
55                   "h(M,F)     -- module function documentation\n"
56                   "h(M,F,A)   -- module function arity documentation\n"
57		   "i()        -- information about the system\n"
58		   "ni()       -- information about the networked system\n"
59		   "i(X,Y,Z)   -- information about pid <X,Y,Z>\n"
60		   "l(Module)  -- load or reload module\n"
61		   "lm()       -- load all modified modules\n"
62		   "lc([File]) -- compile a list of Erlang modules\n"
63		   "ls()       -- list files in the current directory\n"
64		   "ls(Dir)    -- list files in directory <Dir>\n"
65		   "m()        -- which modules are loaded\n"
66		   "m(Mod)     -- information about module <Mod>\n"
67		   "mm()       -- list all modified modules\n"
68		   "memory()   -- memory allocation information\n"
69		   "memory(T)  -- memory allocation information of type <T>\n"
70		   "nc(File)   -- compile and load code in <File> on all nodes\n"
71		   "nl(Module) -- load module on all nodes\n"
72		   "pid(X,Y,Z) -- convert X,Y,Z to a Pid\n"
73		   "pwd()      -- print working directory\n"
74		   "q()        -- quit - shorthand for init:stop()\n"
75		   "regs()     -- information about registered processes\n"
76		   "nregs()    -- information about all registered processes\n"
77		   "uptime()   -- print node uptime\n"
78		   "xm(M)      -- cross reference check a module\n"
79		   "y(File)    -- generate a Yecc parser\n">>).
80
81%% c(Module)
82%%  Compile a module/file.
83
84-spec c(Module) -> {'ok', ModuleName} | 'error' when
85      Module :: file:name(),
86      ModuleName :: module().
87
88c(Module) -> c(Module, []).
89
90-spec c(Module, Options) -> {'ok', ModuleName} | 'error' when
91      Module :: file:name(),
92      Options :: [compile:option()] | compile:option(),
93      ModuleName :: module().
94
95c(Module, SingleOption) when not is_list(SingleOption) ->
96    c(Module, [SingleOption]);
97c(Module, Opts) when is_atom(Module) ->
98    %% either a module name or a source file name (possibly without
99    %% suffix); if such a source file exists, it is used to compile from
100    %% scratch with the given options, otherwise look for an object file
101    Suffix = case filename:extension(Module) of
102                 "" -> src_suffix(Opts);
103                 S -> S
104             end,
105    SrcFile = filename:rootname(Module, Suffix) ++ Suffix,
106    case filelib:is_file(SrcFile) of
107        true ->
108            compile_and_load(SrcFile, Opts);
109        false ->
110            c(Module, Opts, fun (_) -> true end)
111    end;
112c(Module, Opts) ->
113    %% we never interpret a string as a module name, only as a file
114    compile_and_load(Module, Opts).
115
116%% This tries to find an existing object file and use its compile_info and
117%% source path to recompile the module, overwriting the old object file.
118%% The Filter parameter is applied to the old compile options
119
120-spec c(Module, Options, Filter) -> {'ok', ModuleName} | 'error' when
121      Module :: atom(),
122      Options :: [compile:option()],
123      Filter :: fun ((compile:option()) -> boolean()),
124      ModuleName :: module().
125
126c(Module, Options, Filter) when is_atom(Module) ->
127    case find_beam(Module) of
128        BeamFile when is_list(BeamFile) ->
129            c(Module, Options, Filter, BeamFile);
130        Error ->
131            {error, Error}
132    end.
133
134c(Module, Options, Filter, BeamFile) ->
135    case compile_info(Module, BeamFile) of
136        Info when is_list(Info) ->
137            case find_source(BeamFile, Info) of
138                SrcFile when is_list(SrcFile) ->
139                    c(SrcFile, Options, Filter, BeamFile, Info);
140                Error ->
141                    Error
142            end;
143        Error ->
144            Error
145    end.
146
147c(SrcFile, NewOpts, Filter, BeamFile, Info) ->
148    %% Filter old options; also remove options that will be replaced.
149    %% Write new beam over old beam unless other outdir is specified.
150    F = fun (Opt) -> not is_outdir_opt(Opt) andalso Filter(Opt) end,
151    Options = (NewOpts ++ [{outdir,filename:dirname(BeamFile)}]
152               ++ lists:filter(F, old_options(Info))),
153    format("Recompiling ~ts\n", [SrcFile]),
154    safe_recompile(SrcFile, Options, BeamFile).
155
156-type h_return() :: ok | {error, missing | {unknown_format, unicode:chardata()}}.
157-type hf_return() :: h_return() | {error, function_missing}.
158-type ht_return() :: h_return() | {error, type_missing}.
159-type hcb_return() :: h_return() | {error, callback_missing}.
160
161-define(RENDERABLE_FORMAT(Format),
162        Format =:= ?NATIVE_FORMAT;
163        binary_part(Format, 0, 5) =:= <<"text/">>).
164
165-spec h(module()) -> h_return().
166h(Module) ->
167    case code:get_doc(Module) of
168        {ok, #docs_v1{ format = Format } = Docs} when ?RENDERABLE_FORMAT(Format) ->
169            format_docs(shell_docs:render(Module, Docs));
170        {ok, #docs_v1{ format = Enc }} ->
171            {error, {unknown_format, Enc}};
172        Error ->
173            Error
174    end.
175
176-spec h(module(),function()) -> hf_return().
177h(Module,Function) ->
178    case code:get_doc(Module) of
179        {ok, #docs_v1{ format = Format } = Docs} when ?RENDERABLE_FORMAT(Format) ->
180            format_docs(shell_docs:render(Module, Function, Docs));
181        {ok, #docs_v1{ format = Enc }} ->
182            {error, {unknown_format, Enc}};
183        Error ->
184            Error
185    end.
186
187-spec h(module(),function(),arity()) -> hf_return().
188h(Module,Function,Arity) ->
189    case code:get_doc(Module) of
190        {ok, #docs_v1{ format = Format } = Docs} when ?RENDERABLE_FORMAT(Format) ->
191            format_docs(shell_docs:render(Module, Function, Arity, Docs));
192        {ok, #docs_v1{ format = Enc }} ->
193            {error, {unknown_format, Enc}};
194        Error ->
195            Error
196    end.
197
198-spec ht(module()) -> h_return().
199ht(Module) ->
200    case code:get_doc(Module) of
201        {ok, #docs_v1{ format = Format } = Docs} when ?RENDERABLE_FORMAT(Format) ->
202            format_docs(shell_docs:render_type(Module, Docs));
203        {ok, #docs_v1{ format = Enc }} ->
204            {error, {unknown_format, Enc}};
205        Error ->
206            Error
207    end.
208
209-spec ht(module(),Type :: atom()) -> ht_return().
210ht(Module,Type) ->
211    case code:get_doc(Module) of
212        {ok, #docs_v1{ format = Format } = Docs} when ?RENDERABLE_FORMAT(Format) ->
213            format_docs(shell_docs:render_type(Module, Type, Docs));
214        {ok, #docs_v1{ format = Enc }} ->
215            {error, {unknown_format, Enc}};
216        Error ->
217            Error
218    end.
219
220-spec ht(module(),Type :: atom(),arity()) ->
221          ht_return().
222ht(Module,Type,Arity) ->
223    case code:get_doc(Module) of
224        {ok, #docs_v1{ format = Format } = Docs} when ?RENDERABLE_FORMAT(Format) ->
225            format_docs(shell_docs:render_type(Module, Type, Arity, Docs));
226        {ok, #docs_v1{ format = Enc }} ->
227            {error, {unknown_format, Enc}};
228        Error ->
229            Error
230    end.
231
232-spec hcb(module()) -> h_return().
233hcb(Module) ->
234    case code:get_doc(Module) of
235        {ok, #docs_v1{ format = Format } = Docs} when ?RENDERABLE_FORMAT(Format) ->
236            format_docs(shell_docs:render_callback(Module, Docs));
237        {ok, #docs_v1{ format = Enc }} ->
238            {error, {unknown_format, Enc}};
239        Error ->
240            Error
241    end.
242
243-spec hcb(module(),Callback :: atom()) -> hcb_return().
244hcb(Module,Callback) ->
245    case code:get_doc(Module) of
246        {ok, #docs_v1{ format = Format } = Docs} when ?RENDERABLE_FORMAT(Format) ->
247            format_docs(shell_docs:render_callback(Module, Callback, Docs));
248        {ok, #docs_v1{ format = Enc }} ->
249            {error, {unknown_format, Enc}};
250        Error ->
251            Error
252    end.
253
254-spec hcb(module(),Callback :: atom(),arity()) ->
255          hcb_return().
256hcb(Module,Callback,Arity) ->
257    case code:get_doc(Module) of
258        {ok, #docs_v1{ format = Format } = Docs} when ?RENDERABLE_FORMAT(Format) ->
259            format_docs(shell_docs:render_callback(Module, Callback, Arity, Docs));
260        {ok, #docs_v1{ format = Enc }} ->
261            {error, {unknown_format, Enc}};
262        Error ->
263            Error
264    end.
265
266format_docs({error,_} = E) ->
267    E;
268format_docs(Docs) ->
269    {match, Lines} = re:run(Docs,"(.+\n|\n)",[unicode,global,{capture,all_but_first,binary}]),
270    _ = paged_output(fun(Line,_) ->
271                             format("~ts",Line),
272                             {1,undefined}
273                     end, undefined, Lines),
274    ok.
275
276old_options(Info) ->
277    case lists:keyfind(options, 1, Info) of
278        {options, Opts} -> Opts;
279        false -> []
280    end.
281
282%% prefer the source path in the compile info if the file exists,
283%% otherwise do a standard source search relative to the beam file
284find_source(BeamFile, Info) ->
285    case lists:keyfind(source, 1, Info) of
286        {source, SrcFile} ->
287            case filelib:is_file(SrcFile) of
288                true -> SrcFile;
289                false -> find_source(BeamFile)
290            end;
291        _ ->
292            find_source(BeamFile)
293    end.
294
295find_source(BeamFile) ->
296    case filelib:find_source(BeamFile) of
297        {ok, SrcFile} -> SrcFile;
298        _ -> {error, no_source}
299    end.
300
301%% find the beam file for a module, preferring the path reported by code:which()
302%% if it still exists, or otherwise by searching the code path
303find_beam(Module) when is_atom(Module) ->
304    case code:which(Module) of
305        Beam when is_list(Beam), Beam =/= "" ->
306            case erlang:module_loaded(Module) of
307                false ->
308                    Beam;  % code:which/1 found this in the path
309                true ->
310                    case filelib:is_file(Beam) of
311                        true -> Beam;
312                        false -> find_beam_1(Module)  % file moved?
313                    end
314            end;
315        Other when Other =:= ""; Other =:= cover_compiled ->
316            %% module is loaded but not compiled directly from source
317            find_beam_1(Module);
318        Error ->
319            Error
320    end.
321
322find_beam_1(Module) ->
323    File = atom_to_list(Module) ++ code:objfile_extension(),
324    case code:where_is_file(File) of
325        Beam when is_list(Beam) ->
326            Beam;
327        Error ->
328            Error
329    end.
330
331%% get the compile_info for a module
332%% -will report the info for the module in memory, if loaded
333%% -will try to find and examine the beam file if not in memory
334%% -will not cause a module to become loaded by accident
335compile_info(Module, Beam) when is_atom(Module) ->
336    case erlang:module_loaded(Module) of
337        true ->
338            %% getting the compile info for a loaded module should normally
339            %% work, but return an empty info list if it fails
340            try erlang:get_module_info(Module, compile)
341            catch _:_ -> []
342            end;
343        false ->
344            case beam_lib:chunks(Beam, [compile_info]) of
345                {ok, {_Module, [{compile_info, Info}]}} ->
346                    Info;
347                Error ->
348                    Error
349            end
350    end.
351
352%% compile module, backing up any existing target file and restoring the
353%% old version if compilation fails (this should only be used when we have
354%% an old beam file that we want to preserve)
355safe_recompile(File, Options, BeamFile) ->
356    %% Note that it's possible that because of options such as 'to_asm',
357    %% the compiler might not actually write a new beam file at all
358    Backup = BeamFile ++ ".bak",
359    case file:rename(BeamFile, Backup) of
360        Status when Status =:= ok; Status =:= {error,enoent} ->
361            case compile_and_load(File, Options) of
362                {ok, _} = Result ->
363                    _ = if Status =:= ok -> file:delete(Backup);
364                           true -> ok
365                        end,
366                    Result;
367                Error ->
368                    _ = if Status =:= ok -> file:rename(Backup, BeamFile);
369                           true -> ok
370                        end,
371                    Error
372            end;
373        Error ->
374            Error
375    end.
376
377%% Compile the file and load the resulting object code (if any).
378%% Automatically ensures that there is an outdir option, by default the
379%% directory of File, and that a 'from' option will be passed to match the
380%% actual source suffix if needed (unless already specified).
381compile_and_load(File, Opts0) when is_list(Opts0) ->
382    Opts = [report_errors, report_warnings
383            | ensure_from(filename:extension(File),
384                          ensure_outdir(".", Opts0))],
385    case compile:file(File, Opts) of
386	{ok,Mod} ->				%Listing file.
387	    purge_and_load(Mod, File, Opts);
388	{ok,Mod,_Ws} ->				%Warnings maybe turned on.
389	    purge_and_load(Mod, File, Opts);
390	Other ->				%Errors go here
391	    Other
392    end;
393compile_and_load(File, Opt) ->
394    compile_and_load(File, [Opt]).
395
396ensure_from(Suffix, Opts0) ->
397    case lists:partition(fun is_from_opt/1, Opts0++from_opt(Suffix)) of
398        {[Opt|_], Opts} -> [Opt | Opts];
399        {[], Opts} -> Opts
400    end.
401
402ensure_outdir(Dir, Opts0) ->
403    {[Opt|_], Opts} = lists:partition(fun is_outdir_opt/1,
404                                      Opts0++[{outdir,Dir}]),
405    [Opt | Opts].
406
407is_outdir_opt({outdir, _}) -> true;
408is_outdir_opt(_) -> false.
409
410is_from_opt(from_core) -> true;
411is_from_opt(from_asm) -> true;
412is_from_opt(_) -> false.
413
414from_opt(".core") -> [from_core];
415from_opt(".S")    -> [from_asm];
416from_opt(_)       -> [].
417
418%%% Obtain the 'outdir' option from the argument. Return "." if no
419%%% such option was given.
420-spec outdir([compile:option()]) -> file:filename().
421
422outdir([]) ->
423    ".";
424outdir([Opt|Rest]) ->
425    case Opt of
426	{outdir, D} ->
427	    D;
428	_ ->
429	    outdir(Rest)
430    end.
431
432%% mimic how suffix is selected in compile:file().
433src_suffix([from_core|_]) -> ".core";
434src_suffix([from_asm|_])  -> ".S";
435src_suffix([_|Opts]) -> src_suffix(Opts);
436src_suffix([]) -> ".erl".
437
438%%% We have compiled File with options Opts. Find out where the
439%%% output file went and load it, purging any old version.
440purge_and_load(Mod, File, Opts) ->
441    Dir = outdir(Opts),
442    Base = filename:basename(File, src_suffix(Opts)),
443    OutFile = filename:join(Dir, Base),
444    case compile:output_generated(Opts) of
445	true ->
446	    case atom_to_list(Mod) of
447		Base ->
448		    code:purge(Mod),
449                    %% Note that load_abs() adds the object file suffix
450		    case code:load_abs(OutFile, Mod) of
451                        {error, _R}=Error -> Error;
452                        _ -> {ok, Mod}
453                    end;
454		_OtherMod ->
455		    format("** Module name '~p' does not match file name '~tp' **~n",
456			   [Mod,File]),
457		    {error, badfile}
458	    end;
459	false ->
460	    format("** Warning: No object file created - nothing loaded **~n", []),
461	    ok
462    end.
463
464%% Compile a list of modules
465%% enables the nice unix shell cmd
466%% erl -s c lc f1 f2 f3 @d c1=v1 @c2 @i IDir @o ODir -s erlang halt
467%% to compile files f1.erl , f2.erl ....... from a unix shell
468%% with constant c2 defined, c1=v1 (v1 must be a term!), include dir
469%% IDir, outdir ODir.
470
471-spec lc(Files) -> 'ok' | 'error' when
472      Files :: [File :: erl_compile:cmd_line_arg()].
473
474lc(Args) ->
475    case catch split(Args, [], []) of
476	error -> error;
477	{Opts, Files} ->
478	    COpts = [report_errors, report_warnings | reverse(Opts)],
479	    foreach(fun(File) -> compile:file(File, COpts) end, reverse(Files))
480    end.
481
482%%% lc_batch/1 works like lc/1, but halts afterwards, with appropriate
483%%% exit code. This is meant to be called by "erl -compile".
484
485-spec lc_batch() -> no_return().
486
487lc_batch() ->
488    io:format("Error: no files to compile~n"),
489    halt(1).
490
491-spec lc_batch([erl_compile:cmd_line_arg()]) -> no_return().
492
493lc_batch(Args) ->
494    try split(Args, [], []) of
495	{Opts, Files} ->
496	    COpts = [report_errors, report_warnings | reverse(Opts)],
497            Res = [compile:file(File, COpts) || File <- reverse(Files)],
498	    case lists:member(error, Res) of
499		true ->
500		    halt(1);
501		false ->
502		    halt(0)
503	    end
504    catch
505	throw:error -> halt(1)
506    end.
507
508split(['@i', Dir | T], Opts, Files) ->
509    split(T, [{i, atom_to_list(Dir)} | Opts], Files);
510split(['@o', Dir | T], Opts, Files) ->
511    split(T, [{outdir, atom_to_list(Dir)} | Opts], Files);
512split(['@d', Def | T], Opts, Files) ->
513    split(T, [split_def(atom_to_list(Def), []) | Opts], Files);
514split([File | T], Opts, Files) ->
515    split(T, Opts, [File | Files]);
516split([], Opts, Files) ->
517    {Opts, Files}.
518
519split_def([$= | T], Res) -> {d, list_to_atom(reverse(Res)),make_term(T)};
520split_def([H | T], Res) -> split_def(T, [H | Res]);
521split_def([], Res) -> {d, list_to_atom(reverse(Res))}.
522
523make_term(Str) ->
524    case erl_scan:string(Str) of
525	{ok, Tokens, _} ->
526	    case erl_parse:parse_term(Tokens ++ [{dot, erl_anno:new(1)}]) of
527		{ok, Term} -> Term;
528		{error, {_,_,Reason}} ->
529		    io:format("~ts: ~ts~n", [Reason, Str]),
530		    throw(error)
531	    end;
532	{error, {_,_,Reason}, _} ->
533	    io:format("~ts: ~ts~n", [Reason, Str]),
534	    throw(error)
535    end.
536
537-spec nc(File) -> {'ok', Module} | 'error' when
538      File :: file:name(),
539      Module :: module().
540
541nc(File) -> nc(File, []).
542
543-spec nc(File, Options) -> {'ok', Module} | 'error' when
544      File :: file:name(),
545      Options :: [Option] | Option,
546      Option:: compile:option(),
547      Module :: module().
548
549nc(File, Opts0) when is_list(Opts0) ->
550    Opts = Opts0 ++ [report_errors, report_warnings],
551    case compile:file(File, Opts) of
552	{ok,Mod} ->
553	    Dir = outdir(Opts),
554	    Obj = filename:basename(File, ".erl") ++ code:objfile_extension(),
555	    Fname = filename:join(Dir, Obj),
556	    case file:read_file(Fname) of
557		{ok,Bin} ->
558		    rpc:eval_everywhere(code,load_binary,[Mod,Fname,Bin]),
559		    {ok,Mod};
560		Other ->
561		    Other
562	    end;
563	Other ->                                %Errors go here
564	    Other
565    end;
566nc(File, Opt) when is_atom(Opt) ->
567    nc(File, [Opt]).
568
569%% l(Mod)
570%%  Reload module Mod from file of same name
571-spec l(Module) -> code:load_ret() when
572      Module :: module().
573
574l(Mod) ->
575    code:purge(Mod),
576    code:load_file(Mod).
577
578%% Network version of l/1
579-spec nl(Module) -> abcast | error when
580      Module :: module().
581
582nl(Mod) ->
583    case code:get_object_code(Mod) of
584	{_Module, Bin, Fname} ->
585            rpc:eval_everywhere(code, load_binary, [Mod, Fname, Bin]);
586	Other ->
587	    Other
588    end.
589
590-spec i() -> 'ok'.
591
592i() -> i(processes()).
593
594-spec ni() -> 'ok'.
595
596ni() -> i(all_procs()).
597
598-spec i([pid()]) -> 'ok'.
599
600i(Ps) ->
601    iformat("Pid", "Initial Call", "Heap", "Reds", "Msgs"),
602    iformat("Registered", "Current Function", "Stack", "", ""),
603    case paged_output(fun(Pid, {R,M,H,S}) ->
604                              {A,B,C,D} = display_info(Pid),
605                              {2,{R+A,M+B,H+C,S+D}}
606                      end, 2, {0,0,0,0}, Ps) of
607        {R,M,H,S} ->
608            iformat("Total", "", w(H), w(R), w(M)),
609            iformat("", "", w(S), "", "");
610        less ->
611            ok
612    end.
613
614paged_output(Fun, Acc, Items) ->
615    paged_output(Fun, 0, Acc, Items).
616paged_output(Fun, CurrLine, Acc, Items) ->
617    Limit =
618        case io:rows() of
619            {ok, Rows} -> Rows-2;
620            _ -> 100
621        end,
622    paged_output(Fun, CurrLine, Limit, Acc, Items).
623
624paged_output(PrintFun, CurrLine, Limit, Acc, Items) when CurrLine >= Limit ->
625    case more() of
626        more ->
627            paged_output(PrintFun, 0, Limit, Acc, Items);
628        less ->
629            less
630    end;
631paged_output(PrintFun, CurrLine, Limit, Acc, [H|T]) ->
632    {Lines, NewAcc} = PrintFun(H, Acc),
633    paged_output(PrintFun, CurrLine+Lines, Limit, NewAcc, T);
634paged_output(_, _, _, Acc, []) ->
635    Acc.
636
637more() ->
638    case get_line('more (y/n)? (y) ', "y\n") of
639	"c\n" ->
640            more;
641	"y\n" ->
642            more;
643	"q\n" ->
644	    less;
645	"n\n" ->
646	    less;
647	_ ->
648	    more()
649    end.
650
651get_line(P, Default) ->
652    case line_string(io:get_line(P)) of
653	"\n" ->
654	    Default;
655	L ->
656	    L
657    end.
658
659%% If the standard input is set to binary mode
660%% convert it to a list so we can properly match.
661line_string(Binary) when is_binary(Binary) -> unicode:characters_to_list(Binary);
662line_string(Other) -> Other.
663
664mfa_string(Fun) when is_function(Fun) ->
665    {module,M} = erlang:fun_info(Fun, module),
666    {name,F} = erlang:fun_info(Fun, name),
667    {arity,A} = erlang:fun_info(Fun, arity),
668    mfa_string({M,F,A});
669mfa_string({M,F,A}) ->
670    io_lib:format("~w:~tw/~w", [M,F,A]);
671mfa_string(X) ->
672    w(X).
673
674display_info(Pid) ->
675    case pinfo(Pid) of
676	undefined -> {0,0,0,0};
677	Info ->
678	    Call = initial_call(Info),
679	    Curr = case fetch(current_function, Info) of
680		       {Mod,F,Args} when is_list(Args) ->
681			   {Mod,F,length(Args)};
682		       Other ->
683			   Other
684		   end,
685	    Reds = fetch(reductions, Info),
686	    LM = fetch(message_queue_len, Info),
687	    HS = fetch(heap_size, Info),
688	    SS = fetch(stack_size, Info),
689	    iformat(w(Pid), mfa_string(Call),
690		    w(HS),
691		    w(Reds), w(LM)),
692	    iformat(case fetch(registered_name, Info) of
693			0 -> "";
694			X -> io_lib:format("~tw", [X])
695		    end,
696		    mfa_string(Curr),
697		    w(SS),
698		    "",
699		    ""),
700	    {Reds, LM, HS, SS}
701    end.
702
703%% We have to do some assumptions about the initial call.
704%% If the initial call is proc_lib:init_p/3,5 we can find more information
705%% calling the function proc_lib:initial_call/1.
706
707initial_call(Info)  ->
708    case fetch(initial_call, Info) of
709	{proc_lib, init_p, _} ->
710	    proc_lib:translate_initial_call(Info);
711	ICall ->
712	    ICall
713    end.
714
715iformat(A1, A2, A3, A4, A5) ->
716    format("~-21ts ~-33ts ~8s ~8s ~4s~n", [A1,A2,A3,A4,A5]).
717
718all_procs() ->
719    case is_alive() of
720	true -> flatmap(fun (N) -> rpc:call(N,erlang,processes,[]) end,
721			[node()|nodes()]);
722	false -> processes()
723    end.
724
725pinfo(Pid) ->
726    case is_alive() of
727	true -> rpc:call(node(Pid), erlang, process_info, [Pid]);
728	false -> process_info(Pid)
729    end.
730
731fetch(Key, Info) ->
732    case lists:keyfind(Key, 1, Info) of
733	{_, Val} -> Val;
734	false -> 0
735    end.
736
737-spec pid(X, Y, Z) -> pid() when
738      X :: non_neg_integer(),
739      Y :: non_neg_integer(),
740      Z :: non_neg_integer().
741
742pid(X, Y, Z) ->
743    list_to_pid("<" ++ integer_to_list(X) ++ "." ++
744		integer_to_list(Y) ++ "." ++
745		integer_to_list(Z) ++ ">").
746
747-spec i(X, Y, Z) -> [{atom(), term()}] when
748      X :: non_neg_integer(),
749      Y :: non_neg_integer(),
750      Z :: non_neg_integer().
751
752i(X, Y, Z) -> pinfo(pid(X, Y, Z)).
753
754-spec q() -> no_return().
755
756q() ->
757    init:stop().
758
759-spec bt(Pid) -> 'ok' | 'undefined' when
760      Pid :: pid().
761
762bt(Pid) ->
763    case catch erlang:process_display(Pid, backtrace) of
764	{'EXIT', _} ->
765	    undefined;
766	_ ->
767	    ok
768    end.
769
770-spec m() -> 'ok'.
771
772m() ->
773    mformat("Module", "File"),
774    foreach(fun ({Mod,File}) -> mformat(Mod, File) end, sort(code:all_loaded())).
775
776mformat(A1, A2) ->
777    format("~-20s  ~ts\n", [A1,A2]).
778
779-spec mm() -> [module()].
780
781mm() ->
782    code:modified_modules().
783
784-spec lm() -> [code:load_ret()].
785
786lm() ->
787    [l(M) || M <- mm()].
788
789%% erlangrc(Home)
790%%  Try to run a ".erlang" file in home directory.
791
792-spec erlangrc() -> {ok, file:filename()} | {error, term()}.
793
794erlangrc() ->
795    case init:get_argument(home) of
796	{ok,[[Home]]} ->
797	    erlangrc([Home]);
798	_ ->
799            {error, enoent}
800    end.
801
802-spec erlangrc(PathList) -> {ok, file:filename()} | {error, term()}
803                                when PathList :: [Dir :: file:name()].
804
805erlangrc([Home|_]=Paths) when is_list(Home) ->
806    f_p_e(Paths, ".erlang").
807
808error(Fmt, Args) ->
809    error_logger:error_msg(Fmt, Args).
810
811f_p_e(P, F) ->
812    case file:path_eval(P, F) of
813	{error, enoent} = Enoent ->
814	    Enoent;
815	{error, E={Line, _Mod, _Term}} ->
816	    error("file:path_eval(~tp,~tp): error on line ~p: ~ts~n",
817		  [P, F, Line, file:format_error(E)]),
818	    {error, E};
819	{error, E} ->
820	    error("file:path_eval(~tp,~tp): ~ts~n",
821		  [P, F, file:format_error(E)]),
822	    {error, E};
823	Other ->
824	    Other
825    end.
826
827bi(I) ->
828    case erlang:system_info(I) of
829	X when is_binary(X) -> io:put_chars(binary_to_list(X));
830	X when is_list(X) -> io:put_chars(X);
831	X -> format("~w", [X])
832    end.
833
834%%
835%% Short and nice form of module info
836%%
837-spec m(Module) -> 'ok' when
838      Module :: module().
839
840m(M) ->
841    L = M:module_info(),
842    {exports,E} = lists:keyfind(exports, 1, L),
843    Time = get_compile_time(L),
844    COpts = get_compile_options(L),
845    format("Module: ~w~n", [M]),
846    print_md5(L),
847    format("Compiled: "),
848    print_time(Time),
849    print_object_file(M),
850    format("Compiler options:  ~p~n", [COpts]),
851    format("Exports: ~n",[]), print_exports(keysort(1, E)).
852
853print_object_file(Mod) ->
854    case code:is_loaded(Mod) of
855	{file,File} ->
856	    format("Object file: ~ts\n", [File]);
857	_ ->
858	    ignore
859    end.
860
861print_md5(L) ->
862    case lists:keyfind(md5, 1, L) of
863        {md5,<<MD5:128>>} -> io:format("MD5: ~.16b~n",[MD5]);
864        _ -> ok
865    end.
866
867get_compile_time(L) ->
868    case get_compile_info(L, time) of
869	{ok,Val} -> Val;
870	error -> notime
871    end.
872
873get_compile_options(L) ->
874    case get_compile_info(L, options) of
875	{ok,Val} -> Val;
876	error -> []
877    end.
878
879get_compile_info(L, Tag) ->
880    case lists:keyfind(compile, 1, L) of
881	{compile, I} ->
882	    case lists:keyfind(Tag, 1, I) of
883		{Tag, Val} -> {ok,Val};
884		false -> error
885	    end;
886	false -> error
887    end.
888
889print_exports(X) when length(X) > 16 ->
890    split_print_exports(X);
891print_exports([]) -> ok;
892print_exports([{F, A} |Tail]) ->
893    format("         ~tw/~w~n",[F, A]),
894    print_exports(Tail).
895
896split_print_exports(L) ->
897    Len = length(L),
898    Mid = Len div 2,
899    L1 = sublist(L, 1, Mid),
900    L2 = sublist(L, Mid +1, Len - Mid + 1),
901    split_print_exports(L1, L2).
902
903split_print_exports([], [{F, A}|T]) ->
904    Str = " ",
905    format("~-30ts~tw/~w~n", [Str, F, A]),
906    split_print_exports([], T);
907split_print_exports([{F1, A1}|T1], [{F2, A2} | T2]) ->
908    Str = flatten(io_lib:format("~tw/~w", [F1, A1])),
909    format("~-30ts~tw/~w~n", [Str, F2, A2]),
910    split_print_exports(T1, T2);
911split_print_exports([], []) -> ok.
912
913print_time({Year,Month,Day,Hour,Min,_Secs}) ->
914    format("~s ~w ~w, ", [month(Month),Day,Year]),
915    format("~.2.0w:~.2.0w~n", [Hour,Min]);
916print_time(notime) ->
917    format("No compile time info available~n",[]).
918
919month(1) -> "January";
920month(2) -> "February";
921month(3) -> "March";
922month(4) -> "April";
923month(5) -> "May";
924month(6) -> "June";
925month(7) -> "July";
926month(8) -> "August";
927month(9) -> "September";
928month(10) -> "October";
929month(11) -> "November";
930month(12) -> "December".
931
932%% Just because we can't eval receive statements...
933-spec flush() -> 'ok'.
934
935flush() ->
936    receive
937	X ->
938            case lists:keyfind(encoding, 1, io:getopts()) of
939                {encoding,unicode} ->
940                    format("Shell got ~tp~n",[X]);
941                _ ->
942                    format("Shell got ~p~n",[X])
943            end,
944	    flush()
945    after 0 ->
946	    ok
947    end.
948
949%% Print formatted info about all registered names in the system
950-spec nregs() -> 'ok'.
951
952nregs() ->
953    foreach(fun (N) -> print_node_regs(N) end, all_regs()).
954
955-spec regs() -> 'ok'.
956
957regs() ->
958    print_node_regs({node(),registered()}).
959
960all_regs() ->
961    case is_alive() of
962        true -> [{N,rpc:call(N, erlang, registered, [])} ||
963                    N <- [node()|nodes()]];
964	false -> [{node(),registered()}]
965    end.
966
967print_node_regs({N, List}) when is_list(List) ->
968    {Pids,Ports,_Dead} = pids_and_ports(N, sort(List), [], [], []),
969    %% print process info
970    format("~n** Registered procs on node ~w **~n",[N]),
971    procformat("Name", "Pid", "Initial Call", "Reds", "Msgs"),
972    foreach(fun({Name,PI,Pid}) -> procline(Name, PI, Pid) end, Pids),
973    %% print port info
974    format("~n** Registered ports on node ~w **~n",[N]),
975    portformat("Name", "Id", "Command"),
976    foreach(fun({Name,PI,Id}) -> portline(Name, PI, Id) end, Ports).
977
978pids_and_ports(_, [], Pids, Ports, Dead) ->
979    {reverse(Pids),reverse(Ports),reverse(Dead)};
980
981pids_and_ports(Node, [Name|Names], Pids, Ports, Dead) ->
982    case pwhereis(Node, Name) of
983	Pid when is_pid(Pid) ->
984	    pids_and_ports(Node, Names, [{Name,pinfo(Pid),Pid}|Pids],
985			   Ports, Dead);
986	Id when is_port(Id) ->
987	    pids_and_ports(Node, Names, Pids,
988			   [{Name,portinfo(Id),Id}|Ports], Dead);
989	undefined ->
990	    pids_and_ports(Node, Names, Pids, Ports, [Name|Dead])
991    end.
992
993pwhereis(Node, Name) ->
994    case is_alive() of
995	true -> rpc:call(Node, erlang, whereis, [Name]);
996	false -> whereis(Name)
997    end.
998
999portinfo(Id) ->
1000    case is_alive() of
1001	true ->  [ rpc:call(node(Id), erlang, port_info, [Id,name]) ];
1002	false -> [ erlang:port_info(Id, name) ]
1003    end.
1004
1005procline(Name, Info, Pid) ->
1006    Call = initial_call(Info),
1007    Reds  = fetch(reductions, Info),
1008    LM = fetch(message_queue_len, Info),
1009    procformat(io_lib:format("~tw",[Name]),
1010	       io_lib:format("~w",[Pid]),
1011	       io_lib:format("~ts",[mfa_string(Call)]),
1012	       integer_to_list(Reds), integer_to_list(LM)).
1013
1014procformat(Name, Pid, Call, Reds, LM) ->
1015    format("~-21ts ~-12s ~-25ts ~12s ~4s~n", [Name,Pid,Call,Reds,LM]).
1016
1017portline(Name, Info, Id) ->
1018    Cmd = fetch(name, Info),
1019    portformat(io_lib:format("~tw",[Name]),
1020	       erlang:port_to_list(Id),
1021	       Cmd).
1022
1023portformat(Name, Id, Cmd) ->
1024    format("~-21ts ~-15s ~-40ts~n", [Name,Id,Cmd]).
1025
1026%% pwd()
1027%% cd(Directory)
1028%%  These are just wrappers around the file:get/set_cwd functions.
1029
1030-spec pwd() -> 'ok'.
1031
1032pwd() ->
1033    case file:get_cwd() of
1034	{ok, Str} ->
1035	    ok = io:format("~ts\n", [Str]);
1036	{error, _} ->
1037	    ok = io:format("Cannot determine current directory\n")
1038    end.
1039
1040-spec cd(Dir) -> 'ok' when
1041      Dir :: file:name().
1042
1043cd(Dir) ->
1044    _ = file:set_cwd(Dir),
1045    pwd().
1046
1047%% ls()
1048%% ls(Directory)
1049%%  The strategy is to print in fixed width files.
1050
1051-spec ls() -> 'ok'.
1052
1053ls() ->
1054    ls(".").
1055
1056-spec ls(Dir) -> 'ok' when
1057      Dir :: file:name().
1058
1059ls(Dir0) ->
1060    case file:list_dir(Dir0) of
1061	{ok, Entries} ->
1062	    ls_print(sort(Entries));
1063	{error, enotdir} ->
1064            Dir = if
1065                      is_list(Dir0) -> lists:flatten(Dir0);
1066                      true -> Dir0
1067                  end,
1068	    ls_print([Dir]);
1069	{error, Error} ->
1070	    format("~ts\n", [file:format_error(Error)])
1071    end.
1072
1073ls_print([]) -> ok;
1074ls_print(L) ->
1075    Width = erlang:min(max_length(L, 0), 40) + 5,
1076    ls_print(L, Width, 0).
1077
1078ls_print(X, Width, Len) when Width + Len >= 80 ->
1079    io:nl(),
1080    ls_print(X, Width, 0);
1081ls_print([H|T], Width, Len) ->
1082    io:format("~-*ts",[Width,H]),
1083    ls_print(T, Width, Len+Width);
1084ls_print([], _, _) ->
1085    io:nl().
1086
1087max_length([H|T], L) when is_atom(H) ->
1088    max_length([atom_to_list(H)|T], L);
1089max_length([H|T], L) ->
1090    max_length(T, erlang:max(length(H), L));
1091max_length([], L) ->
1092    L.
1093
1094w(X) ->
1095    io_lib:write(X).
1096
1097%%
1098%% memory/[0,1]
1099%%
1100
1101-spec memory() -> [{Type, Size}] when
1102      Type :: atom(),
1103      Size :: non_neg_integer().
1104
1105memory() -> erlang:memory().
1106
1107-spec memory(Type) -> Size when
1108               Type :: atom(),
1109               Size :: non_neg_integer()
1110          ; (Types) -> [{Type, Size}] when
1111               Types :: [Type],
1112               Type :: atom(),
1113               Size :: non_neg_integer().
1114
1115memory(TypeSpec) -> erlang:memory(TypeSpec).
1116
1117%%
1118%% uptime/0
1119%%
1120
1121-spec uptime() -> 'ok'.
1122
1123uptime() ->
1124    io:format("~s~n", [uptime(get_uptime())]).
1125
1126uptime({D, {H, M, S}}) ->
1127    lists:flatten(
1128      [[ io_lib:format("~p days, ", [D]) || D > 0 ],
1129       [ io_lib:format("~p hours, ", [H]) || D+H > 0 ],
1130       [ io_lib:format("~p minutes and ", [M]) || D+H+M > 0 ],
1131       io_lib:format("~p seconds", [S])]).
1132
1133get_uptime() ->
1134    {UpTime, _} = erlang:statistics(wall_clock),
1135    calendar:seconds_to_daystime(UpTime div 1000).
1136
1137%%
1138%% Cross Reference Check
1139%%
1140%%-spec xm(module() | file:filename()) -> xref:m/1 return
1141xm(M) ->
1142    appcall(tools, xref, m, [M]).
1143
1144%%
1145%% Call yecc
1146%%
1147%%-spec y(file:name()) -> yecc:file/2 return
1148y(File) -> y(File, []).
1149
1150%%-spec y(file:name(), [yecc:option()]) -> yecc:file/2 return
1151y(File, Opts) ->
1152    appcall(parsetools, yecc, file, [File, Opts]).
1153
1154
1155%%
1156%% Avoid creating strong components in xref and dialyzer by making calls
1157%% from helper functions to other applications indirect.
1158%%
1159
1160appcall(App, M, F, Args) ->
1161    try
1162	apply(M, F, Args)
1163    catch
1164	error:undef:S ->
1165	    case S of
1166		[{M,F,Args,_}|_] ->
1167		    Arity = length(Args),
1168		    io:format("Call to ~w:~w/~w in application ~w failed.\n",
1169			      [M,F,Arity,App]);
1170		Stk ->
1171		    erlang:raise(error, undef, Stk)
1172	    end
1173    end.
1174