diff options
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r-- | lib/stdlib/src/dets.erl | 23 | ||||
-rw-r--r-- | lib/stdlib/src/erl_internal.erl | 2 | ||||
-rw-r--r-- | lib/stdlib/src/filename.erl | 31 | ||||
-rw-r--r-- | lib/stdlib/src/io_lib.erl | 49 | ||||
-rw-r--r-- | lib/stdlib/src/io_lib_format.erl | 8 | ||||
-rw-r--r-- | lib/stdlib/src/io_lib_pretty.erl | 12 | ||||
-rw-r--r-- | lib/stdlib/src/ms_transform.erl | 6 | ||||
-rw-r--r-- | lib/stdlib/src/proc_lib.erl | 175 |
8 files changed, 195 insertions, 111 deletions
diff --git a/lib/stdlib/src/dets.erl b/lib/stdlib/src/dets.erl index e016d5a80e..0488c2bef2 100644 --- a/lib/stdlib/src/dets.erl +++ b/lib/stdlib/src/dets.erl @@ -616,12 +616,18 @@ next(Tab, Key) -> %% Assuming that a file already exists, open it with the %% parameters as already specified in the file itself. %% Return a ref leading to the file. -open_file(File) -> - case dets_server:open_file(to_list(File)) of - badarg -> % Should not happen. - erlang:error(dets_process_died, [File]); - Reply -> - einval(Reply, [File]) +open_file(File0) -> + File = to_list(File0), + case is_list(File) of + true -> + case dets_server:open_file(File) of + badarg -> % Should not happen. + erlang:error(dets_process_died, [File]); + Reply -> + einval(Reply, [File]) + end; + false -> + erlang:error(badarg, [File0]) end. -spec open_file(Name, Args) -> {'ok', Name} | {'error', Reason} when @@ -1088,6 +1094,7 @@ defaults(Tab, Args) -> debug = false}, Fun = fun repl/2, Defaults = lists:foldl(Fun, Defaults0, Args), + true = is_list(Defaults#open_args.file), is_comp_min_max(Defaults). to_list(T) when is_atom(T) -> atom_to_list(T); @@ -1112,9 +1119,7 @@ repl({delayed_write, {Delay,Size} = C}, Defs) Defs#open_args{delayed_write = C}; repl({estimated_no_objects, I}, Defs) -> repl({min_no_slots, I}, Defs); -repl({file, File}, Defs) when is_list(File) -> - Defs#open_args{file = File}; -repl({file, File}, Defs) when is_atom(File) -> +repl({file, File}, Defs) -> Defs#open_args{file = to_list(File)}; repl({keypos, P}, Defs) when is_integer(P), P > 0 -> Defs#open_args{keypos =P}; diff --git a/lib/stdlib/src/erl_internal.erl b/lib/stdlib/src/erl_internal.erl index b311a843c2..939abaff00 100644 --- a/lib/stdlib/src/erl_internal.erl +++ b/lib/stdlib/src/erl_internal.erl @@ -74,6 +74,7 @@ guard_bif(element, 2) -> true; guard_bif(float, 1) -> true; guard_bif(floor, 1) -> true; guard_bif(hd, 1) -> true; +guard_bif(is_map_key, 2) -> true; guard_bif(length, 1) -> true; guard_bif(map_size, 1) -> true; guard_bif(map_get, 2) -> true; @@ -109,7 +110,6 @@ new_type_test(is_function, 2) -> true; new_type_test(is_integer, 1) -> true; new_type_test(is_list, 1) -> true; new_type_test(is_map, 1) -> true; -new_type_test(is_map_key, 2) -> true; new_type_test(is_number, 1) -> true; new_type_test(is_pid, 1) -> true; new_type_test(is_port, 1) -> true; diff --git a/lib/stdlib/src/filename.erl b/lib/stdlib/src/filename.erl index a322bd002d..b7b7b562ab 100644 --- a/lib/stdlib/src/filename.erl +++ b/lib/stdlib/src/filename.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1997-2017. All Rights Reserved. +%% Copyright Ericsson AB 1997-2018. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -1012,24 +1012,33 @@ filename_string_to_binary(List) -> %% basedir %% http://standards.freedesktop.org/basedir-spec/basedir-spec-latest.html --type basedir_type() :: 'user_cache' | 'user_config' | 'user_data' - | 'user_log' - | 'site_config' | 'site_data'. +-type basedir_path_type() :: 'user_cache' | 'user_config' | 'user_data' + | 'user_log'. +-type basedir_paths_type() :: 'site_config' | 'site_data'. --spec basedir(Type,Application) -> file:filename_all() when - Type :: basedir_type(), +-type basedir_opts() :: #{author => string() | binary(), + os => 'windows' | 'darwin' | 'linux', + version => string() | binary()}. + +-spec basedir(PathType,Application) -> file:filename_all() when + PathType :: basedir_path_type(), + Application :: string() | binary(); + (PathsType,Application) -> [file:filename_all()] when + PathsType :: basedir_paths_type(), Application :: string() | binary(). basedir(Type,Application) when is_atom(Type), is_list(Application) orelse is_binary(Application) -> basedir(Type, Application, #{}). --spec basedir(Type,Application,Opts) -> file:filename_all() when - Type :: basedir_type(), +-spec basedir(PathType,Application,Opts) -> file:filename_all() when + PathType :: basedir_path_type(), + Application :: string() | binary(), + Opts :: basedir_opts(); + (PathsType,Application,Opts) -> [file:filename_all()] when + PathsType :: basedir_paths_type(), Application :: string() | binary(), - Opts :: #{author => string() | binary(), - os => 'windows' | 'darwin' | 'linux', - version => string() | binary()}. + Opts :: basedir_opts(). basedir(Type,Application,Opts) when is_atom(Type), is_map(Opts), is_list(Application) orelse diff --git a/lib/stdlib/src/io_lib.erl b/lib/stdlib/src/io_lib.erl index 3a5aba60b4..8223a52873 100644 --- a/lib/stdlib/src/io_lib.erl +++ b/lib/stdlib/src/io_lib.erl @@ -178,11 +178,11 @@ fread(Cont, Chars, Format) -> Data :: [term()]. format(Format, Args) -> - case catch io_lib_format:fwrite(Format, Args) of - {'EXIT',_} -> - erlang:error(badarg, [Format, Args]); - Other -> - Other + try io_lib_format:fwrite(Format, Args) + catch + C:R:S -> + test_modules_loaded(C, R, S), + erlang:error(badarg, [Format, Args]) end. -spec format(Format, Data, Options) -> chars() when @@ -193,11 +193,11 @@ format(Format, Args) -> CharsLimit :: chars_limit(). format(Format, Args, Options) -> - case catch io_lib_format:fwrite(Format, Args, Options) of - {'EXIT',_} -> - erlang:error(badarg, [Format, Args, Options]); - Other -> - Other + try io_lib_format:fwrite(Format, Args, Options) + catch + C:R:S -> + test_modules_loaded(C, R, S), + erlang:error(badarg, [Format, Args]) end. -spec scan_format(Format, Data) -> FormatList when @@ -208,7 +208,9 @@ format(Format, Args, Options) -> scan_format(Format, Args) -> try io_lib_format:scan(Format, Args) catch - _:_ -> erlang:error(badarg, [Format, Args]) + C:R:S -> + test_modules_loaded(C, R, S), + erlang:error(badarg, [Format, Args]) end. -spec unscan_format(FormatList) -> {Format, Data} when @@ -223,7 +225,12 @@ unscan_format(FormatList) -> FormatList :: [char() | format_spec()]. build_text(FormatList) -> - io_lib_format:build(FormatList). + try io_lib_format:build(FormatList) + catch + C:R:S -> + test_modules_loaded(C, R, S), + erlang:error(badarg, [FormatList]) + end. -spec build_text(FormatList, Options) -> chars() when FormatList :: [char() | format_spec()], @@ -232,7 +239,23 @@ build_text(FormatList) -> CharsLimit :: chars_limit(). build_text(FormatList, Options) -> - io_lib_format:build(FormatList, Options). + try io_lib_format:build(FormatList, Options) + catch + C:R:S -> + test_modules_loaded(C, R, S), + erlang:error(badarg, [FormatList, Options]) + end. + +%% Failure to load a module must not be labeled as badarg. +%% C, R, and S are included so that the original error, which could be +%% a bug in io_lib_format, can be found by tracing on +%% test_modules_loaded/3. +test_modules_loaded(_C, _R, _S) -> + Modules = [io_lib_format, io_lib_pretty, string, unicode], + case code:ensure_modules_loaded(Modules) of + ok -> ok; + Error -> erlang:error(Error) + end. -spec print(Term) -> chars() when Term :: term(). diff --git a/lib/stdlib/src/io_lib_format.erl b/lib/stdlib/src/io_lib_format.erl index c814ab50d4..e247b00a04 100644 --- a/lib/stdlib/src/io_lib_format.erl +++ b/lib/stdlib/src/io_lib_format.erl @@ -38,18 +38,16 @@ %% and it also splits the handling of the control characters into two %% parts. --spec fwrite(Format, Data) -> FormatList when +-spec fwrite(Format, Data) -> io_lib:chars() when Format :: io:format(), - Data :: [term()], - FormatList :: [char() | io_lib:format_spec()]. + Data :: [term()]. fwrite(Format, Args) -> build(scan(Format, Args)). --spec fwrite(Format, Data, Options) -> FormatList when +-spec fwrite(Format, Data, Options) -> io_lib:chars() when Format :: io:format(), Data :: [term()], - FormatList :: [char() | io_lib:format_spec()], Options :: [Option], Option :: {'chars_limit', CharsLimit}, CharsLimit :: io_lib:chars_limit(). diff --git a/lib/stdlib/src/io_lib_pretty.erl b/lib/stdlib/src/io_lib_pretty.erl index dca1b37ef3..ba9d9e8434 100644 --- a/lib/stdlib/src/io_lib_pretty.erl +++ b/lib/stdlib/src/io_lib_pretty.erl @@ -722,7 +722,7 @@ printable_list(L, _D, T, latin1) when T < 0 -> io_lib:printable_latin1_list(L); printable_list(L, _D, T, Enc) when T >= 0 -> case slice(L, tsub(T, 2)) of - {prefix, ""} -> + false -> false; {prefix, Prefix} when Enc =:= latin1 -> io_lib:printable_latin1_list(Prefix) andalso {true, Prefix}; @@ -738,11 +738,17 @@ printable_list(L, _D, T, _Uni) when T < 0-> io_lib:printable_list(L). slice(L, N) -> - case string:length(L) =< N of + try string:length(L) =< N of true -> all; false -> - {prefix, string:slice(L, 0, N)} + case string:slice(L, 0, N) of + "" -> + false; + Prefix -> + {prefix, Prefix} + end + catch _:_ -> false end. printable_bin0(Bin, D, T, Enc) -> diff --git a/lib/stdlib/src/ms_transform.erl b/lib/stdlib/src/ms_transform.erl index d117481d2e..3845e35e9b 100644 --- a/lib/stdlib/src/ms_transform.erl +++ b/lib/stdlib/src/ms_transform.erl @@ -224,10 +224,12 @@ transform_from_shell(Dialect, Clauses, BoundEnvironment) -> %% Called when translating during compiling %% --spec parse_transform(Forms, Options) -> Forms2 when +-spec parse_transform(Forms, Options) -> Forms2 | Errors | Warnings when Forms :: [erl_parse:abstract_form() | erl_parse:form_info()], Forms2 :: [erl_parse:abstract_form() | erl_parse:form_info()], - Options :: term(). + Options :: term(), + Errors :: {error, ErrInfo :: [tuple()], WarnInfo :: []}, + Warnings :: {warning, Forms2, WarnInfo :: [tuple()]}. parse_transform(Forms, _Options) -> SaveFilename = setup_filename(), diff --git a/lib/stdlib/src/proc_lib.erl b/lib/stdlib/src/proc_lib.erl index 89a840be2d..cfbaf8b242 100644 --- a/lib/stdlib/src/proc_lib.erl +++ b/lib/stdlib/src/proc_lib.erl @@ -30,7 +30,7 @@ start/3, start/4, start/5, start_link/3, start_link/4, start_link/5, hibernate/3, init_ack/1, init_ack/2, - init_p/3,init_p/5,format/1,format/2,format/3,report_cb/1, + init_p/3,init_p/5,format/1,format/2,format/3,report_cb/2, initial_call/1, translate_initial_call/1, stop/1, stop/3]). @@ -509,7 +509,7 @@ crash_report(Class, Reason, StartF, Stacktrace) -> report=>[my_info(Class, Reason, StartF, Stacktrace), linked_info(self())]}, #{domain=>[otp,sasl], - report_cb=>fun proc_lib:report_cb/1, + report_cb=>fun proc_lib:report_cb/2, logger_formatter=>#{title=>"CRASH REPORT"}, error_logger=>#{tag=>error_report,type=>crash_report}}). @@ -750,14 +750,16 @@ check(Res) -> Res. %%% Format a generated crash info structure. %%% ----------------------------------------------------------- --spec report_cb(CrashReport) -> {Format,Args} when - CrashReport :: #{label=>{proc_lib,crash},report=>[term()]}, - Format :: io:format(), - Args :: [term()]. -report_cb(#{label:={proc_lib,crash}, - report:=CrashReport}) -> - Depth = error_logger:get_format_depth(), - get_format_and_args(CrashReport, utf8, Depth). +-spec report_cb(CrashReport,FormatOpts) -> unicode:chardata() when + CrashReport :: #{label => {proc_lib,crash}, + report => [term()]}, + FormatOpts :: logger:report_cb_config(). +report_cb(#{label:={proc_lib,crash}, report:=CrashReport}, Extra) -> + Default = #{chars_limit => unlimited, + depth => unlimited, + single_line => false, + encoding => utf8}, + do_format(CrashReport, maps:merge(Default,Extra)). -spec format(CrashReport) -> string() when CrashReport :: [term()]. @@ -777,84 +779,121 @@ format(CrashReport, Encoding) -> Depth :: unlimited | pos_integer(). format(CrashReport, Encoding, Depth) -> - {F,A} = get_format_and_args(CrashReport, Encoding, Depth), - lists:flatten(io_lib:format(F,A)). - -get_format_and_args([OwnReport,LinkReport], Encoding, Depth) -> - Extra = {Encoding,Depth}, - MyIndent = " ", - {OwnFormat,OwnArgs} = format_report(OwnReport, MyIndent, Extra, [], []), - {LinkFormat,LinkArgs} = format_link_report(LinkReport, MyIndent, Extra, [], []), - {" crasher:~n"++OwnFormat++" neighbours:~n"++LinkFormat,OwnArgs++LinkArgs}. - -format_link_report([], _Indent, _Extra, Format, Args) -> - {lists:flatten(lists:reverse(Format)),lists:append(lists:reverse(Args))}; -format_link_report([Link|Reps], Indent, Extra, Format, Args) -> + do_format(CrashReport, #{chars_limit => unlimited, + depth => Depth, + encoding => Encoding, + single_line => false}). + +do_format([OwnReport,LinkReport], #{single_line:=Single}=Extra) -> + Indent = if Single -> ""; + true -> " " + end, + MyIndent = Indent ++ Indent, + Sep = nl(Single,"; "), + OwnFormat = format_report(OwnReport, MyIndent, Extra), + LinkFormat = lists:join(Sep,format_link_report(LinkReport, MyIndent, Extra)), + Nl = nl(Single," "), + Str = io_lib:format("~scrasher:"++Nl++"~ts"++Sep++"~sneighbours:"++Nl++"~ts", + [Indent,OwnFormat,Indent,LinkFormat]), + lists:flatten(Str). + +format_link_report([Link|Reps], Indent0, #{single_line:=Single}=Extra) -> Rep = case Link of {neighbour,Rep0} -> Rep0; _ -> Link end, + Indent = if Single -> ""; + true -> Indent0 + end, LinkIndent = [" ",Indent], - {LinkFormat,LinkArgs} = format_report(Rep, LinkIndent, Extra, [], []), - F = "~sneighbour:\n"++LinkFormat, - A = [Indent|LinkArgs], - format_link_report(Reps, Indent, Extra, [F|Format], [A|Args]); -format_link_report(Rep, Indent, Extra, Format, Args) -> - {F,A} = format_report(Rep, Indent, Extra, [], []), - format_link_report([], Indent, Extra, [F|Format],[A|Args]). - -format_report([], _Indent, _Extra, Format, Args) -> - {lists:flatten(lists:reverse(Format)),lists:append(lists:reverse(Args))}; -format_report([Rep|Reps], Indent, Extra, Format, Args) -> - {F,A} = format_rep(Rep, Indent, Extra), - format_report(Reps, Indent, Extra, [F|Format], [A|Args]); -format_report(Rep, Indent, {Enc,unlimited}=Extra, Format, Args) -> - {F,A} = {"~s~"++modifier(Enc)++"p~n", [Indent, Rep]}, - format_report([], Indent, Extra, [F|Format], [A|Args]); -format_report(Rep, Indent, {Enc,Depth}=Extra, Format, Args) -> - {F,A} = {"~s~"++modifier(Enc)++"P~n", [Indent, Rep, Depth]}, - format_report([], Indent, Extra, [F|Format], [A|Args]). - -format_rep({initial_call,InitialCall}, Indent, Extra) -> - format_mfa(Indent, InitialCall, Extra); -format_rep({error_info,{Class,Reason,StackTrace}}, _Indent, Extra) -> - {lists:flatten(format_exception(Class, Reason, StackTrace, Extra)),[]}; -format_rep({Tag,Data}, Indent, Extra) -> - format_tag(Indent, Tag, Data, Extra). - -format_mfa(Indent, {M,F,Args}=StartF, {Enc,_}=Extra) -> + [[Indent,"neighbour:",nl(Single," "),format_report(Rep, LinkIndent, Extra)]| + format_link_report(Reps, Indent, Extra)]; +format_link_report(Rep, Indent, Extra) -> + format_report(Rep, Indent, Extra). + +format_report(Rep, Indent, #{single_line:=Single}=Extra) when is_list(Rep) -> + lists:join(nl(Single,", "),format_rep(Rep, Indent, Extra)); +format_report(Rep, Indent0, #{encoding:=Enc,depth:=Depth, + chars_limit:=Limit,single_line:=Single}) -> + {P,Tl} = p(Enc,Depth), + {Indent,Width} = if Single -> {"","0"}; + true -> {Indent0,""} + end, + Opts = if is_integer(Limit) -> [{chars_limit,Limit}]; + true -> [] + end, + io_lib:format("~s~"++Width++P, [Indent, Rep | Tl], Opts). + +format_rep([{initial_call,InitialCall}|Rep], Indent, Extra) -> + [format_mfa(Indent, InitialCall, Extra)|format_rep(Rep, Indent, Extra)]; +format_rep([{error_info,{Class,Reason,StackTrace}}|Rep], Indent, Extra) -> + [format_exception(Class, Reason, StackTrace, Extra)| + format_rep(Rep, Indent, Extra)]; +format_rep([{Tag,Data}|Rep], Indent, Extra) -> + [format_tag(Indent, Tag, Data, Extra)|format_rep(Rep, Indent, Extra)]; +format_rep(_, _, _Extra) -> + []. + +format_exception(Class, Reason, StackTrace, + #{encoding:=Enc,depth:=Depth,chars_limit:=Limit, + single_line:=Single}=Extra) -> + PF = pp_fun(Extra), + StackFun = fun(M, _F, _A) -> (M =:= erl_eval) or (M =:= ?MODULE) end, + if Single -> + {P,Tl} = p(Enc,Depth), + Opts = if is_integer(Limit) -> [{chars_limit,Limit}]; + true -> [] + end, + [atom_to_list(Class), ": ", + io_lib:format("~0"++P,[{Reason,StackTrace}|Tl],Opts)]; + true -> + EI = " ", + [EI, erl_error:format_exception(1+length(EI), Class, Reason, + StackTrace, StackFun, PF, Enc)] + end. + +format_mfa(Indent0, {M,F,Args}=StartF, #{encoding:=Enc,single_line:=Single}=Extra) -> + Indent = if Single -> ""; + true -> Indent0 + end, try A = length(Args), - {lists:flatten([Indent,"initial call: ",atom_to_list(M), - $:,to_string(F, Enc),$/,integer_to_list(A),"\n"]),[]} + [Indent,"initial call: ",atom_to_list(M),$:,to_string(F, Enc),$/, + integer_to_list(A)] catch error:_ -> format_tag(Indent, initial_call, StartF, Extra) end. -format_tag(Indent, Tag, Data, {Enc,Depth}) -> - {P,Tl} = p(Enc, Depth), - {"~s~p: ~80.18" ++ P ++ "\n", [Indent, Tag, Data|Tl]}. - -format_exception(Class, Reason, StackTrace, {Enc,_}=Extra) -> - PF = pp_fun(Extra), - StackFun = fun(M, _F, _A) -> (M =:= erl_eval) or (M =:= ?MODULE) end, - %% EI = " exception: ", - EI = " ", - [EI, erl_error:format_exception(1+length(EI), Class, Reason, - StackTrace, StackFun, PF, Enc), "\n"]. - to_string(A, latin1) -> io_lib:write_atom_as_latin1(A); to_string(A, _) -> io_lib:write_atom(A). -pp_fun({Enc,Depth}) -> +pp_fun(#{encoding:=Enc,depth:=Depth,chars_limit:=Limit,single_line:=Single}) -> {P,Tl} = p(Enc, Depth), + Width = if Single -> "0"; + true -> "" + end, + Opts = if is_integer(Limit) -> [{chars_limit,Limit}]; + true -> [] + end, fun(Term, I) -> - io_lib:format("~." ++ integer_to_list(I) ++ P, [Term|Tl]) + io_lib:format("~" ++ Width ++ "." ++ integer_to_list(I) ++ P, + [Term|Tl], Opts) end. +format_tag(Indent0, Tag, Data, #{encoding:=Enc,depth:=Depth,chars_limit:=Limit,single_line:=Single}) -> + {P,Tl} = p(Enc, Depth), + {Indent,Width} = if Single -> {"","0"}; + true -> {Indent0,""} + end, + Opts = if is_integer(Limit) -> [{chars_limit,Limit}]; + true -> [] + end, + io_lib:format("~s~" ++ Width ++ "p: ~" ++ Width ++ ".18" ++ P, + [Indent, Tag, Data|Tl], Opts). + p(Encoding, Depth) -> {Letter, Tl} = case Depth of unlimited -> {"p", []}; @@ -866,6 +905,8 @@ p(Encoding, Depth) -> modifier(latin1) -> ""; modifier(_) -> "t". +nl(true,Else) -> Else; +nl(false,_) -> "\n". %%% ----------------------------------------------------------- %%% Stop a process and wait for it to terminate |