diff options
author | Hans Bolinder <[email protected]> | 2013-01-25 13:04:01 +0100 |
---|---|---|
committer | Hans Bolinder <[email protected]> | 2013-01-25 13:04:10 +0100 |
commit | 4adc1523254d5e326e2d5cf942b5eeee84fdb8ea (patch) | |
tree | 527d936f6295f3d8f86ceecf44ff2310ab5508b2 /lib/stdlib/src | |
parent | 9afbb879f0397a650a7c403911a8cc30daa6dbbe (diff) | |
parent | 5b68f914f08479759d36557282aee29f44683d97 (diff) | |
download | otp-4adc1523254d5e326e2d5cf942b5eeee84fdb8ea.tar.gz otp-4adc1523254d5e326e2d5cf942b5eeee84fdb8ea.tar.bz2 otp-4adc1523254d5e326e2d5cf942b5eeee84fdb8ea.zip |
Merge branch 'hb/unicode/OTP-10302'
OTP-10742
OTP-10745
OTP-10749
* hb/unicode/OTP-10302:
[stdlib] Remove documentation of ~tp
Remove one use of iolist_size/1 in io_lib_pretty.erl
Add a new function proc_lib:format/2 which takes encoding
Export the type erl_scan:token()
Make adjustments for Unicode
[stdlib] Change default of erl_scan's unicode option
Update preloaded
Correct recently introduced Unicode related type errors
[stdlib] Introduce new functions epp:read_encoding_from_binary/1,2
Extend char() to Unicode characters
[kernel] Correct bugs in the old shell (user.erl)
[parsetools] Change the encoding of test suites to UTF-8
[stdlib] Fix a contract bug
[stdlib] Update the Unicode examples in STDLIB User's Guide
[stdlib] Remove documentation of Unicode functions in io_lib
Diffstat (limited to 'lib/stdlib/src')
32 files changed, 365 insertions, 298 deletions
diff --git a/lib/stdlib/src/base64.erl b/lib/stdlib/src/base64.erl index 0068d82d43..7bf281bd8a 100644 --- a/lib/stdlib/src/base64.erl +++ b/lib/stdlib/src/base64.erl @@ -28,7 +28,8 @@ %% of (some) functions of this module. %%------------------------------------------------------------------------- --type ascii_string() :: [1..127]. +-type ascii_string() :: [1..255]. +-type ascii_binary() :: binary(). %%------------------------------------------------------------------------- %% encode_to_string(ASCII) -> Base64String @@ -39,7 +40,7 @@ %%------------------------------------------------------------------------- -spec encode_to_string(Data) -> Base64String when - Data :: string() | binary(), + Data :: ascii_string() | ascii_binary(), Base64String :: ascii_string(). encode_to_string(Bin) when is_binary(Bin) -> @@ -56,15 +57,15 @@ encode_to_string(List) when is_list(List) -> %%------------------------------------------------------------------------- -spec encode(Data) -> Base64 when - Data :: string() | binary(), - Base64 :: binary(). + Data :: ascii_string() | ascii_binary(), + Base64 :: ascii_binary(). encode(Bin) when is_binary(Bin) -> encode_binary(Bin); encode(List) when is_list(List) -> list_to_binary(encode_l(List)). --spec encode_l(string()) -> ascii_string(). +-spec encode_l(ascii_string()) -> ascii_string(). encode_l([]) -> []; @@ -107,8 +108,8 @@ encode_binary(Bin) -> %%------------------------------------------------------------------------- -spec decode(Base64) -> Data when - Base64 :: string() | binary(), - Data :: binary(). + Base64 :: ascii_string() | ascii_binary(), + Data :: ascii_binary(). decode(Bin) when is_binary(Bin) -> decode_binary(<<>>, Bin); @@ -116,21 +117,21 @@ decode(List) when is_list(List) -> list_to_binary(decode_l(List)). -spec mime_decode(Base64) -> Data when - Base64 :: string() | binary(), - Data :: binary(). + Base64 :: ascii_string() | ascii_binary(), + Data :: ascii_binary(). mime_decode(Bin) when is_binary(Bin) -> mime_decode_binary(<<>>, Bin); mime_decode(List) when is_list(List) -> mime_decode(list_to_binary(List)). --spec decode_l(string()) -> string(). +-spec decode_l(ascii_string()) -> ascii_string(). decode_l(List) -> L = strip_spaces(List, []), decode(L, []). --spec mime_decode_l(string()) -> string(). +-spec mime_decode_l(ascii_string()) -> ascii_string(). mime_decode_l(List) -> L = strip_illegal(List, [], 0), @@ -148,8 +149,8 @@ mime_decode_l(List) -> %%------------------------------------------------------------------------- -spec decode_to_string(Base64) -> DataString when - Base64 :: string() | binary(), - DataString :: string(). + Base64 :: ascii_string() | ascii_binary(), + DataString :: ascii_string(). decode_to_string(Bin) when is_binary(Bin) -> decode_to_string(binary_to_list(Bin)); @@ -157,8 +158,8 @@ decode_to_string(List) when is_list(List) -> decode_l(List). -spec mime_decode_to_string(Base64) -> DataString when - Base64 :: string() | binary(), - DataString :: string(). + Base64 :: ascii_string() | ascii_binary(), + DataString :: ascii_string(). mime_decode_to_string(Bin) when is_binary(Bin) -> mime_decode_to_string(binary_to_list(Bin)); diff --git a/lib/stdlib/src/beam_lib.erl b/lib/stdlib/src/beam_lib.erl index e9a5e6831e..742fda0815 100644 --- a/lib/stdlib/src/beam_lib.erl +++ b/lib/stdlib/src/beam_lib.erl @@ -240,21 +240,21 @@ format_error({error, Error}) -> format_error({error, Module, Error}) -> Module:format_error(Error); format_error({unknown_chunk, File, ChunkName}) -> - io_lib:format("~p: Cannot find chunk ~p~n", [File, ChunkName]); + io_lib:format("~tp: Cannot find chunk ~p~n", [File, ChunkName]); format_error({invalid_chunk, File, ChunkId}) -> - io_lib:format("~p: Invalid contents of chunk ~p~n", [File, ChunkId]); + io_lib:format("~tp: Invalid contents of chunk ~p~n", [File, ChunkId]); format_error({not_a_beam_file, File}) -> - io_lib:format("~p: Not a BEAM file~n", [File]); + io_lib:format("~tp: Not a BEAM file~n", [File]); format_error({file_error, File, Reason}) -> - io_lib:format("~p: ~p~n", [File, file:format_error(Reason)]); + io_lib:format("~tp: ~tp~n", [File, file:format_error(Reason)]); format_error({missing_chunk, File, ChunkId}) -> - io_lib:format("~p: Not a BEAM file: no IFF \"~s\" chunk~n", + io_lib:format("~tp: Not a BEAM file: no IFF \"~s\" chunk~n", [File, ChunkId]); format_error({invalid_beam_file, File, Pos}) -> - io_lib:format("~p: Invalid format of BEAM file near byte number ~p~n", + io_lib:format("~tp: Invalid format of BEAM file near byte number ~p~n", [File, Pos]); format_error({chunk_too_big, File, ChunkId, Size, Len}) -> - io_lib:format("~p: Size of chunk \"~s\" is ~p bytes, " + io_lib:format("~tp: Size of chunk \"~s\" is ~p bytes, " "but only ~p bytes could be read~n", [File, ChunkId, Size, Len]); format_error({chunks_different, Id}) -> @@ -265,16 +265,16 @@ format_error({modules_different, Module1, Module2}) -> io_lib:format("Module names ~p and ~p differ in the two files~n", [Module1, Module2]); format_error({not_a_directory, Name}) -> - io_lib:format("~p: Not a directory~n", [Name]); + io_lib:format("~tp: Not a directory~n", [Name]); format_error({key_missing_or_invalid, File, abstract_code}) -> - io_lib:format("~p: Cannot decrypt abstract code because key is missing or invalid", + io_lib:format("~tp: Cannot decrypt abstract code because key is missing or invalid", [File]); format_error(badfun) -> "not a fun or the fun has the wrong arity"; format_error(exists) -> "a fun has already been installed"; format_error(E) -> - io_lib:format("~p~n", [E]). + io_lib:format("~tp~n", [E]). %% %% Exported functions for encrypted debug info. @@ -324,13 +324,13 @@ diff_directories(Dir1, Dir2) -> {OnlyDir1, OnlyDir2, Diff} = compare_dirs(Dir1, Dir2), diff_only(Dir1, OnlyDir1), diff_only(Dir2, OnlyDir2), - foreach(fun(D) -> io:format("** different: ~p~n", [D]) end, Diff), + foreach(fun(D) -> io:format("** different: ~tp~n", [D]) end, Diff), ok. diff_only(_Dir, []) -> ok; diff_only(Dir, Only) -> - io:format("Only in ~p: ~p~n", [Dir, Only]). + io:format("Only in ~tp: ~tp~n", [Dir, Only]). %% -> {OnlyInDir1, OnlyInDir2, Different} | throw(Error) compare_dirs(Dir1, Dir2) -> @@ -1030,11 +1030,11 @@ f_p_s(P, F) -> {error, enoent} -> {error, enoent}; {error, {Line, _Mod, _Term}=E} -> - error("file:path_script(~p,~p): error on line ~p: ~s~n", + error("file:path_script(~tp,~tp): error on line ~p: ~ts~n", [P, F, Line, file:format_error(E)]), ok; {error, E} when is_atom(E) -> - error("file:path_script(~p,~p): ~s~n", + error("file:path_script(~tp,~tp): ~ts~n", [P, F, file:format_error(E)]), ok; Other -> diff --git a/lib/stdlib/src/c.erl b/lib/stdlib/src/c.erl index 4c1c0f904b..7ef2334106 100644 --- a/lib/stdlib/src/c.erl +++ b/lib/stdlib/src/c.erl @@ -122,7 +122,7 @@ machine_load(Mod, File, Opts) -> code:purge(Mod), check_load(code:load_abs(File2,Mod), Mod); _OtherMod -> - format("** Module name '~p' does not match file name '~p' **~n", + format("** Module name '~p' does not match file name '~tp' **~n", [Mod,File]), {error, badfile} end; @@ -203,11 +203,11 @@ make_term(Str) -> case erl_parse:parse_term(Tokens ++ [{dot, 1}]) of {ok, Term} -> Term; {error, {_,_,Reason}} -> - io:format("~s: ~s~n", [Reason, Str]), + io:format("~ts: ~ts~n", [Reason, Str]), throw(error) end; {error, {_,_,Reason}, _} -> - io:format("~s: ~s~n", [Reason, Str]), + io:format("~ts: ~ts~n", [Reason, Str]), throw(error) end. @@ -475,11 +475,11 @@ f_p_e(P, F) -> {error, enoent} = Enoent -> Enoent; {error, E={Line, _Mod, _Term}} -> - error("file:path_eval(~p,~p): error on line ~p: ~s~n", + error("file:path_eval(~tp,~tp): error on line ~p: ~ts~n", [P, F, Line, file:format_error(E)]), ok; {error, E} -> - error("file:path_eval(~p,~p): ~s~n", + error("file:path_eval(~tp,~tp): ~ts~n", [P, F, file:format_error(E)]), ok; Other -> @@ -588,7 +588,12 @@ month(12) -> "December". flush() -> receive X -> - format("Shell got ~p~n",[X]), + case lists:keyfind(encoding, 1, io:getopts()) of + {encoding,unicode} -> + format("Shell got ~tp~n",[X]); + _ -> + format("Shell got ~p~n",[X]) + end, flush() after 0 -> ok diff --git a/lib/stdlib/src/dets.erl b/lib/stdlib/src/dets.erl index 845fae4bf4..285a7bf587 100644 --- a/lib/stdlib/src/dets.erl +++ b/lib/stdlib/src/dets.erl @@ -2504,7 +2504,7 @@ fopen2(Fname, Tab) -> end, case Do of {repair, Mess} -> - io:format(user, "dets: file ~p~s~n", [Fname, Mess]), + io:format(user, "dets: file ~tp~s~n", [Fname, Mess]), Version = default, case fsck(Fd, Tab, Fname, FH, default, default, Version) of ok -> @@ -2599,7 +2599,7 @@ fopen_existing_file(Tab, OpenArgs) -> _ when FH#fileheader.keypos =/= Kp -> throw({error, {keypos_mismatch, Fname}}); {compact, SourceHead} -> - io:format(user, "dets: file ~p is now compacted ...~n", [Fname]), + io:format(user, "dets: file ~tp is now compacted ...~n", [Fname]), {ok, NewSourceHead} = open_final(SourceHead, Fname, read, false, ?DEFAULT_CACHE, Tab, Debug), case catch compact(NewSourceHead) of @@ -2609,14 +2609,14 @@ fopen_existing_file(Tab, OpenArgs) -> _Err -> _ = file:close(Fd), dets_utils:stop_disk_map(), - io:format(user, "dets: compaction of file ~p failed, " + io:format(user, "dets: compaction of file ~tp failed, " "now repairing ...~n", [Fname]), {ok, Fd2, _FH} = read_file_header(Fname, Acc, Ram), do_repair(Fd2, Tab, Fname, FH, MinSlots, MaxSlots, Version, OpenArgs) end; {repair, Mess} -> - io:format(user, "dets: file ~p~s~n", [Fname, Mess]), + io:format(user, "dets: file ~tp~s~n", [Fname, Mess]), do_repair(Fd, Tab, Fname, FH, MinSlots, MaxSlots, Version, OpenArgs); _ when FH#fileheader.version =/= Version, Version =/= default -> diff --git a/lib/stdlib/src/dets_utils.erl b/lib/stdlib/src/dets_utils.erl index 5db2ad3049..aab7f934c3 100644 --- a/lib/stdlib/src/dets_utils.erl +++ b/lib/stdlib/src/dets_utils.erl @@ -395,7 +395,7 @@ corrupt_reason(Head, Reason0) -> corrupt(Head, Error) -> case get(verbose) of yes -> - error_logger:format("** dets: Corrupt table ~p: ~p\n", + error_logger:format("** dets: Corrupt table ~p: ~tp\n", [Head#head.name, Error]); _ -> ok end, diff --git a/lib/stdlib/src/dets_v8.erl b/lib/stdlib/src/dets_v8.erl index 3e962a1c8b..44829211f7 100644 --- a/lib/stdlib/src/dets_v8.erl +++ b/lib/stdlib/src/dets_v8.erl @@ -1492,7 +1492,7 @@ scan_next_allocated(Bin, From0, _To, <<From:32, To:32, L/binary>>, Ts, R) -> %% Read term from file at position Pos prterm(Head, Pos, ReadAhead) -> Res = dets_utils:pread(Head, Pos, ?OHDSZ, ReadAhead), - ?DEBUGF("file:pread(~p, ~p, ?) -> ~p~n", [Head#head.filename, Pos, Res]), + ?DEBUGF("file:pread(~tp, ~p, ?) -> ~p~n", [Head#head.filename, Pos, Res]), {ok, <<Next:32, Sz:32, _Status:32, Bin0/binary>>} = Res, ?DEBUGF("{Next, Sz} = ~p~n", [{Next, Sz}]), Bin = case byte_size(Bin0) of diff --git a/lib/stdlib/src/dets_v9.erl b/lib/stdlib/src/dets_v9.erl index f577b4410f..6d44c3924e 100644 --- a/lib/stdlib/src/dets_v9.erl +++ b/lib/stdlib/src/dets_v9.erl @@ -2662,7 +2662,7 @@ v_segment(H, SegNo, SegPos, SegSlot) -> {'EXIT', Reason} -> dets_utils:vformat("** dets: Corrupt or truncated dets file~n", []), - io:format("~nERROR ~p~n", [Reason]); + io:format("~nERROR ~tp~n", [Reason]); [] -> %% don't print empty buckets true; {Size, CollP, Objects} -> diff --git a/lib/stdlib/src/epp.erl b/lib/stdlib/src/epp.erl index ebabf8d700..afa39c3fb9 100644 --- a/lib/stdlib/src/epp.erl +++ b/lib/stdlib/src/epp.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2012. All Rights Reserved. +%% Copyright Ericsson AB 1996-2013. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -24,7 +24,8 @@ -export([scan_erl_form/1,parse_erl_form/1,macro_defs/1]). -export([parse_file/1, parse_file/3]). -export([default_encoding/0, encoding_to_string/1, - read_encoding/1, read_encoding/2, set_encoding/1]). + read_encoding_from_binary/1, read_encoding_from_binary/2, + set_encoding/1, read_encoding/1, read_encoding/2]). -export([interpret_file_attribute/1]). -export([normalize_typed_record_fields/1,restore_typed_record_fields/1]). @@ -265,13 +266,41 @@ set_encoding(File) -> ok = io:setopts(File, [{encoding, Enc}]), Encoding. --spec read_encoding_from_file(File, InComment) -> source_encoding() | none when - File :: io:device(), - InComment :: boolean(). +-spec read_encoding_from_binary(Binary) -> source_encoding() | none when + Binary :: binary(). -define(ENC_CHUNK, 32). -define(N_ENC_CHUNK, 16). % a total of 512 bytes +read_encoding_from_binary(Binary) -> + read_encoding_from_binary(Binary, []). + +-spec read_encoding_from_binary(Binary, Options) -> + source_encoding() | none when + Binary :: binary(), + Options :: [Option], + Option :: {in_comment_only, boolean()}. + +read_encoding_from_binary(Binary, Options) -> + InComment = proplists:get_value(in_comment_only, Options, true), + try + com_nl(Binary, fake_reader(0), 0, InComment) + catch + throw:no -> + none + end. + +fake_reader(N) -> + fun() when N =:= ?N_ENC_CHUNK -> + throw(no); + () -> + {<<>>, fake_reader(N+1)} + end. + +-spec read_encoding_from_file(File, InComment) -> source_encoding() | none when + File :: io:device(), + InComment :: boolean(). + read_encoding_from_file(File, InComment) -> {ok, Pos0} = file:position(File, cur), Opts = io:getopts(File), @@ -1276,9 +1305,9 @@ token_src({X, _}) when is_atom(X) -> token_src({var, _, X}) -> atom_to_list(X); token_src({char,_,C}) -> - io_lib:write_unicode_char(C); + io_lib:write_char(C); token_src({string, _, X}) -> - io_lib:write_unicode_string(X); + io_lib:write_string(X); token_src({_, _, X}) -> io_lib:format("~w", [X]). diff --git a/lib/stdlib/src/erl_compile.erl b/lib/stdlib/src/erl_compile.erl index 81bec21a3f..ec106ecc9d 100644 --- a/lib/stdlib/src/erl_compile.erl +++ b/lib/stdlib/src/erl_compile.erl @@ -68,7 +68,7 @@ compile(List) -> {'EXIT', Pid, {compiler_result, Result}} -> Result; {'EXIT', Pid, Reason} -> - io:format("Runtime error: ~p~n", [Reason]), + io:format("Runtime error: ~tp~n", [Reason]), error end. @@ -170,12 +170,12 @@ compile3([], _Cwd, _Options) -> ok. %% Invokes the appropriate compiler, depending on the file extension. compile_file("", Input, _Output, _Options) -> - io:format("File has no extension: ~s~n", [Input]), + io:format("File has no extension: ~ts~n", [Input]), error; compile_file(Ext, Input, Output, Options) -> case compiler(Ext) of no -> - io:format("Unknown extension: '~s'\n", [Ext]), + io:format("Unknown extension: '~ts'\n", [Ext]), error; {M, F} -> case catch M:F(Input, Output, Options) of @@ -215,10 +215,10 @@ make_term(Str) -> case erl_parse:parse_term(Tokens ++ [{dot, 1}]) of {ok, Term} -> Term; {error, {_,_,Reason}} -> - io:format("~s: ~s~n", [Reason, Str]), + io:format("~ts: ~ts~n", [Reason, Str]), throw(error) end; {error, {_,_,Reason}, _} -> - io:format("~s: ~s~n", [Reason, Str]), + io:format("~ts: ~ts~n", [Reason, Str]), throw(error) end. diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index 642d972582..dd5480838f 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -3436,7 +3436,7 @@ check_format_3(Fmt, As) -> _Len -> {warn,1,"wrong number of arguments in format call",[]} end; {error,S} -> - {warn,1,"format string invalid (~s)",[S]} + {warn,1,"format string invalid (~ts)",[S]} end. args_list({cons,_L,_H,T}) -> args_list(T); diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl index 8316462989..9ff25fcbc5 100644 --- a/lib/stdlib/src/erl_parse.yrl +++ b/lib/stdlib/src/erl_parse.yrl @@ -2,7 +2,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2012. All Rights Reserved. +%% Copyright Ericsson AB 1996-2013. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -516,7 +516,7 @@ Erlang code. -type abstract_form() :: term(). -type error_description() :: term(). -type error_info() :: {erl_scan:line(), module(), error_description()}. --type token() :: {Tag :: atom(), Line :: erl_scan:line()}. +-type token() :: erl_scan:token(). %% mkop(Op, Arg) -> {op,Line,Op,Arg}. %% mkop(Left, Op, Right) -> {op,Line,Op,Left,Right}. diff --git a/lib/stdlib/src/erl_pp.erl b/lib/stdlib/src/erl_pp.erl index 0e1156075a..a868867a81 100644 --- a/lib/stdlib/src/erl_pp.erl +++ b/lib/stdlib/src/erl_pp.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2012. All Rights Reserved. +%% Copyright Ericsson AB 1996-2013. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -179,12 +179,12 @@ state(_Hook) -> state(). state() -> - #pp{string_fun = fun io_lib:write_unicode_string_as_latin1/1, - char_fun = fun io_lib:write_unicode_char_as_latin1/1}. + #pp{string_fun = fun io_lib:write_string_as_latin1/1, + char_fun = fun io_lib:write_char_as_latin1/1}. unicode_state() -> - #pp{string_fun = fun io_lib:write_unicode_string/1, - char_fun = fun io_lib:write_unicode_char/1}. + #pp{string_fun = fun io_lib:write_string/1, + char_fun = fun io_lib:write_char/1}. encoding(Options) -> case proplists:get_value(encoding, Options, epp:default_encoding()) of diff --git a/lib/stdlib/src/erl_scan.erl b/lib/stdlib/src/erl_scan.erl index bc0eaf015d..26d5747ee7 100644 --- a/lib/stdlib/src/erl_scan.erl +++ b/lib/stdlib/src/erl_scan.erl @@ -2,7 +2,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2012. All Rights Reserved. +%% Copyright Ericsson AB 1996-2013. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -64,6 +64,7 @@ location/0, options/0, return_cont/0, + token/0, tokens_result/0]). %%% @@ -106,7 +107,7 @@ ws = false :: boolean(), comment = false :: boolean(), text = false :: boolean(), - unicode = false :: boolean()}). + unicode = true :: boolean()}). %%---------------------------------------------------------------------------- @@ -115,7 +116,7 @@ format_error({string,Quote,Head}) -> lists:flatten(["unterminated " ++ string_thing(Quote) ++ " starting with " ++ - io_lib:write_unicode_string(Head, Quote)]); + io_lib:write_string(Head, Quote)]); format_error({illegal,Type}) -> lists:flatten(io_lib:fwrite("illegal ~w", [Type])); format_error(char) -> "unterminated character"; @@ -349,14 +350,14 @@ string_thing(_) -> "string". %% erl_scan:string("[98,2730,99]."). This is to protect the caller %% from character codes greater than 255. Search for UNI to find code %% implementing this "feature". The 'unicode' option is undocumented -%% and will probably be removed later. +%% and will be removed later. -define(NO_UNICODE, 0). -define(UNI255(C), (C =< 16#ff)). options(Opts0) when is_list(Opts0) -> Opts = lists:foldr(fun expand_opt/2, [], Opts0), - [RW_fun] = - case opts(Opts, [reserved_word_fun], []) of + [RW_fun, Unicode] = + case opts(Opts, [reserved_word_fun, unicode], []) of badarg -> erlang:error(badarg, [Opts0]); R -> @@ -365,7 +366,6 @@ options(Opts0) when is_list(Opts0) -> Comment = proplists:get_bool(return_comments, Opts), WS = proplists:get_bool(return_white_spaces, Opts), Txt = proplists:get_bool(text, Opts), - Unicode = proplists:get_bool(unicode, Opts), #erl_scan{resword_fun = RW_fun, comment = Comment, ws = WS, @@ -378,6 +378,8 @@ opts(Options, [Key|Keys], L) -> V = case lists:keyfind(Key, 1, Options) of {reserved_word_fun,F} when ?RESWORDFUN(F) -> {ok,F}; + {unicode, Bool} when is_boolean(Bool) -> + {ok,Bool}; {Key,_} -> badarg; false -> @@ -393,7 +395,9 @@ opts(_Options, [], L) -> lists:reverse(L). default_option(reserved_word_fun) -> - fun reserved_word/1. + fun reserved_word/1; +default_option(unicode) -> + true. expand_opt(return, Os) -> [return_comments,return_white_spaces|Os]; diff --git a/lib/stdlib/src/erl_tar.erl b/lib/stdlib/src/erl_tar.erl index 306834e845..9d32e0ad8b 100644 --- a/lib/stdlib/src/erl_tar.erl +++ b/lib/stdlib/src/erl_tar.erl @@ -154,7 +154,7 @@ table(Name, Opts) -> t(Name) -> case table(Name) of {ok, List} -> - lists:foreach(fun(N) -> ok = io:format("~s\n", [N]) end, List); + lists:foreach(fun(N) -> ok = io:format("~ts\n", [N]) end, List); Error -> Error end. @@ -216,11 +216,11 @@ format_error(bad_header) -> "Bad directory header"; format_error(eof) -> "Unexpected end of file"; format_error(symbolic_link_too_long) -> "Symbolic link too long"; format_error({Name,Reason}) -> - lists:flatten(io_lib:format("~s: ~s", [Name,format_error(Reason)])); + lists:flatten(io_lib:format("~ts: ~ts", [Name,format_error(Reason)])); format_error(Atom) when is_atom(Atom) -> file:format_error(Atom); format_error(Term) -> - lists:flatten(io_lib:format("~p", [Term])). + lists:flatten(io_lib:format("~tp", [Term])). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% @@ -325,13 +325,13 @@ add1(TarFile, Name, NameInArchive, Opts) -> end. add1(Tar, Name, Header, Bin, Options) -> - add_verbose(Options, "a ~s~n", [Name]), + add_verbose(Options, "a ~ts~n", [Name]), file:write(Tar, [Header, Bin, padding(byte_size(Bin), ?record_size)]). add_directory(TarFile, DirName, NameInArchive, Info, Options) -> case file:list_dir(DirName) of {ok, []} -> - add_verbose(Options, "a ~s~n", [DirName]), + add_verbose(Options, "a ~ts~n", [DirName]), Header = create_header(NameInArchive, Info), file:write(TarFile, Header); {ok, Files} -> @@ -731,7 +731,7 @@ write_extracted_element(Header, Bin, Opts) -> symlink -> create_symlink(Name, Header, Opts); Other -> % Ignore. - read_verbose(Opts, "x ~s - unsupported type ~p~n", + read_verbose(Opts, "x ~ts - unsupported type ~p~n", [Name, Other]), not_written end, @@ -757,7 +757,7 @@ create_symlink(Name, #tar_header{linkname=Linkname}=Header, Opts) -> create_symlink(Name, Header, Opts); {error,eexist} -> not_written; {error,enotsup} -> - read_verbose(Opts, "x ~s - symbolic links not supported~n", [Name]), + read_verbose(Opts, "x ~ts - symbolic links not supported~n", [Name]), not_written; {error,Reason} -> throw({error, Reason}) end. @@ -774,10 +774,10 @@ write_extracted_file(Name, Bin, Opts) -> end, case Write of true -> - read_verbose(Opts, "x ~s~n", [Name]), + read_verbose(Opts, "x ~ts~n", [Name]), write_file(Name, Bin); false -> - read_verbose(Opts, "x ~s - exists, not created~n", [Name]), + read_verbose(Opts, "x ~ts - exists, not created~n", [Name]), not_written end. diff --git a/lib/stdlib/src/escript.erl b/lib/stdlib/src/escript.erl index 99a9d138ac..cab5973d0c 100644 --- a/lib/stdlib/src/escript.erl +++ b/lib/stdlib/src/escript.erl @@ -624,7 +624,7 @@ parse_source(S, File, Fd, StartLine, HeaderSz, CheckOnly) -> ok = file:close(Fd), check_source(S3, CheckOnly); {error, Reason} -> - io:format("escript: ~p\n", [Reason]), + io:format("escript: ~tp\n", [Reason]), fatal("Preprocessor error") end. @@ -694,7 +694,7 @@ epp_parse_file2(Epp, S, Forms, Parsed) -> epp_parse_file(Epp, S2, [Form | Forms]); true -> Args = lists:flatten(io_lib:format("illegal mode attribute: ~p", [NewMode])), - io:format("~s:~w ~s\n", [S#state.file,Ln,Args]), + io:format("~ts:~w ~s\n", [S#state.file,Ln,Args]), Error = {error,{Ln,erl_parse,Args}}, Nerrs= S#state.n_errors + 1, epp_parse_file(Epp, S2#state{n_errors = Nerrs}, [Error | Forms]) @@ -710,7 +710,7 @@ epp_parse_file2(Epp, S, Forms, Parsed) -> epp_parse_file(Epp, S, [Form | Forms]) end; {error,{Ln,Mod,Args}} = Form -> - io:format("~s:~w: ~ts\n", + io:format("~ts:~w: ~ts\n", [S#state.file,Ln,Mod:format_error(Args)]), epp_parse_file(Epp, S#state{n_errors = S#state.n_errors + 1}, [Form | Forms]); {eof, _LastLine} = Eof -> @@ -780,10 +780,10 @@ report_errors(Errors) -> Errors). list_errors(F, [{Line,Mod,E}|Es]) -> - io:fwrite("~s:~w: ~ts\n", [F,Line,Mod:format_error(E)]), + io:fwrite("~ts:~w: ~ts\n", [F,Line,Mod:format_error(E)]), list_errors(F, Es); list_errors(F, [{Mod,E}|Es]) -> - io:fwrite("~s: ~ts\n", [F,Mod:format_error(E)]), + io:fwrite("~ts: ~ts\n", [F,Mod:format_error(E)]), list_errors(F, Es); list_errors(_F, []) -> ok. @@ -795,10 +795,10 @@ report_warnings(Ws0) -> lists:foreach(fun({_,Str}) -> io:put_chars(Str) end, Ws). format_message(F, [{Line,Mod,E}|Es]) -> - M = {{F,Line},io_lib:format("~s:~w: Warning: ~ts\n", [F,Line,Mod:format_error(E)])}, + M = {{F,Line},io_lib:format("~ts:~w: Warning: ~ts\n", [F,Line,Mod:format_error(E)])}, [M|format_message(F, Es)]; format_message(F, [{Mod,E}|Es]) -> - M = {none,io_lib:format("~s: Warning: ~ts\n", [F,Mod:format_error(E)])}, + M = {none,io_lib:format("~ts: Warning: ~ts\n", [F,Mod:format_error(E)])}, [M|format_message(F, Es)]; format_message(_, []) -> []. diff --git a/lib/stdlib/src/ets.erl b/lib/stdlib/src/ets.erl index 61bb038737..06f21c1d2c 100644 --- a/lib/stdlib/src/ets.erl +++ b/lib/stdlib/src/ets.erl @@ -501,7 +501,7 @@ fun2ms(ShellFun) when is_function(ShellFun) -> case ms_transform:transform_from_shell( ?MODULE,Clauses,ImportList) of {error,[{_,[{_,_,Code}|_]}|_],_} -> - io:format("Error: ~s~n", + io:format("Error: ~ts~n", [ms_transform:format_error(Code)]), {error,transform_error}; Else -> @@ -1586,7 +1586,7 @@ choice(Height, Width, P, Mode, Tab, Key, Turn, Opos) -> {ok,Re} -> re_search(Height, Width, Tab, ets:first(Tab), Re, 1, 1); {error,{ErrorString,_Pos}} -> - io:format("~s\n", [ErrorString]), + io:format("~ts\n", [ErrorString]), choice(Height, Width, P, Mode, Tab, Key, Turn, Opos) end; _ -> diff --git a/lib/stdlib/src/file_sorter.erl b/lib/stdlib/src/file_sorter.erl index 3f31852afc..83782834cc 100644 --- a/lib/stdlib/src/file_sorter.erl +++ b/lib/stdlib/src/file_sorter.erl @@ -633,7 +633,7 @@ last_merge(R, W) when length(R) =< W#w.no_files -> case W#w.out of Fun when is_function(Fun) -> {Fs, W1} = init_merge(lists:reverse(R), 1, [], W), - ?DEBUG("merging ~p~n", [lists:reverse(R)]), + ?DEBUG("merging ~tp~n", [lists:reverse(R)]), W2 = merge_files(Fs, [], 0, nolast, W1), NW = close_input(W2), outfun(close, NW); @@ -659,7 +659,7 @@ merge_runs([R, R1 | Rs], NRs0, W) -> merge_files(R, W) -> {W1, Temp} = next_temp(W), - ?DEBUG("merging ~p~nto ~p~n", [lists:reverse(R), Temp]), + ?DEBUG("merging ~tp~nto ~tp~n", [lists:reverse(R), Temp]), {Temp, merge_files(R, W1, Temp)}. merge_files(R, W, FileName) -> @@ -1501,7 +1501,7 @@ close_out(_) -> close_file(Fd, W) -> {Fd, FileName} = lists:keyfind(Fd, 1, W#w.temp), - ?DEBUG("closing ~p~n", [FileName]), + ?DEBUG("closing ~tp~n", [FileName]), file:close(Fd), W#w{temp = [FileName | lists:keydelete(Fd, 1, W#w.temp)]}. diff --git a/lib/stdlib/src/io.erl b/lib/stdlib/src/io.erl index ecf2aeb375..3dddb0d6e7 100644 --- a/lib/stdlib/src/io.erl +++ b/lib/stdlib/src/io.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2012. All Rights Reserved. +%% Copyright Ericsson AB 1996-2013. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -127,7 +127,7 @@ rows(Io) -> -spec get_chars(Prompt, Count) -> Data | server_no_data() when Prompt :: prompt(), Count :: non_neg_integer(), - Data :: [unicode:unicode_char()] | unicode:unicode_binary(). + Data :: string() | unicode:unicode_binary(). get_chars(Prompt, N) -> get_chars(default_input(), Prompt, N). @@ -136,14 +136,14 @@ get_chars(Prompt, N) -> IoDevice :: device(), Prompt :: prompt(), Count :: non_neg_integer(), - Data :: [unicode:unicode_char()] | unicode:unicode_binary(). + Data :: string() | unicode:unicode_binary(). get_chars(Io, Prompt, N) when is_integer(N), N >= 0 -> request(Io, {get_chars,unicode,Prompt,N}). -spec get_line(Prompt) -> Data | server_no_data() when Prompt :: prompt(), - Data :: [unicode:unicode_char()] | unicode:unicode_binary(). + Data :: string() | unicode:unicode_binary(). get_line(Prompt) -> get_line(default_input(), Prompt). @@ -151,7 +151,7 @@ get_line(Prompt) -> -spec get_line(IoDevice, Prompt) -> Data | server_no_data() when IoDevice :: device(), Prompt :: prompt(), - Data :: [unicode:unicode_char()] | unicode:unicode_binary(). + Data :: string() | unicode:unicode_binary(). get_line(Io, Prompt) -> request(Io, {get_line,unicode,Prompt}). @@ -221,8 +221,6 @@ write(Io, Term) -> | {'error', ErrorInfo}, ErrorInfo :: erl_scan:error_info() | erl_parse:error_info(). -% Read does not use get_until as erl_scan does not work with unicode -% XXX:PaN fixme? read(Prompt) -> read(default_input(), Prompt). @@ -331,7 +329,7 @@ fread(Prompt, Format) -> Prompt :: prompt(), Format :: format(), Result :: {'ok', Terms :: [term()]} - | {'error', FreadError :: io_lib:fread_error()} + | {'error', {'fread', FreadError :: io_lib:fread_error()}} | server_no_data(). fread(Io, Prompt, Format) -> diff --git a/lib/stdlib/src/io_lib.erl b/lib/stdlib/src/io_lib.erl index 5ad505f683..b7ec848e1e 100644 --- a/lib/stdlib/src/io_lib.erl +++ b/lib/stdlib/src/io_lib.erl @@ -2,7 +2,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2012. All Rights Reserved. +%% Copyright Ericsson AB 1996-2013. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -64,29 +64,31 @@ -export([print/1,print/4,indentation/2]). -export([write/1,write/2,write/3,nl/0,format_prompt/1,format_prompt/2]). --export([write_atom/1,write_string/1,write_string/2,write_unicode_string/1, - write_unicode_string/2, write_char/1, write_unicode_char/1]). +-export([write_atom/1,write_string/1,write_string/2,write_latin1_string/1, + write_latin1_string/2, write_char/1, write_latin1_char/1]). --export([write_unicode_string_as_latin1/1, write_unicode_string_as_latin1/2, - write_unicode_char_as_latin1/1]). +-export([write_string_as_latin1/1, write_string_as_latin1/2, + write_char_as_latin1/1]). --export([quote_atom/2, char_list/1, unicode_char_list/1, - deep_char_list/1, deep_unicode_char_list/1, - printable_list/1, printable_unicode_list/1]). +-export([quote_atom/2, char_list/1, latin1_char_list/1, + deep_char_list/1, deep_latin1_char_list/1, + printable_list/1, printable_latin1_list/1]). %% Utilities for collecting characters. -export([collect_chars/3, collect_chars/4, collect_line/2, collect_line/3, collect_line/4, get_until/3, get_until/4]). --export_type([chars/0, unicode_chars/0, unicode_string/0, continuation/0, - fread_error/0]). +%% The following functions were used by Yecc's include-file. +-export([write_unicode_string/1, write_unicode_char/1, + deep_unicode_char_list/1]). + +-export_type([chars/0, latin1_string/0, continuation/0, fread_error/0]). %%---------------------------------------------------------------------- -type chars() :: [char() | chars()]. --type unicode_chars() :: [unicode:unicode_char() | unicode_chars()]. --type unicode_string() :: [unicode:unicode_char()]. +-type latin1_string() :: [unicode:latin1_char()]. -type depth() :: -1 | non_neg_integer(). -opaque continuation() :: {Format :: string(), @@ -108,10 +110,8 @@ %% Interface calls to sub-modules. --spec fwrite(Format, Data) -> chars() | UnicodeList when +-spec fwrite(Format, Data) -> chars() when Format :: io:format(), - Data :: [term()], - UnicodeList :: [unicode:unicode_char()], Data :: [term()]. fwrite(Format, Args) -> @@ -124,7 +124,7 @@ fwrite(Format, Args) -> | {'more', RestFormat :: string(), Nchars :: non_neg_integer(), InputStack :: chars()} - | {'error', What :: fread_error()}. + | {'error', {'fread', What :: fread_error()}}. fread(Chars, Format) -> io_lib_fread:fread(Chars, Format). @@ -137,15 +137,14 @@ fread(Chars, Format) -> | {'done', Result, LeftOverChars :: string()}, Result :: {'ok', InputList :: [term()]} | 'eof' - | {'error', What :: fread_error()}. + | {'error', {'fread', What :: fread_error()}}. fread(Cont, Chars, Format) -> io_lib_fread:fread(Cont, Chars, Format). --spec format(Format, Data) -> chars() | UnicodeList when +-spec format(Format, Data) -> chars() when Format :: io:format(), - Data :: [term()], - UnicodeList :: [unicode:unicode_char()]. + Data :: [term()]. format(Format, Args) -> case catch io_lib_format:fwrite(Format, Args) of @@ -340,6 +339,11 @@ name_char($_) -> true; name_char($@) -> true; name_char(_) -> false. +%%% There are two functions to write Unicode strings: +%%% - they both escape control characters < 160; +%%% - write_string() never escapes characters >= 160; +%%% - write_string_as_latin1() also escapes characters >= 255. + %% write_string([Char]) -> [Char] %% Generate the list of characters needed to print a string. @@ -352,33 +356,32 @@ write_string(S) -> -spec write_string(string(), char()) -> chars(). write_string(S, Q) -> - [Q|write_string1(latin1, S, Q)]. + [Q|write_string1(unicode_as_unicode, S, Q)]. -%%% There are two functions to write Unicode strings: -%%% - they both escape control characters < 160; -%%% - write_unicode_string() never escapes characters >= 160; -%%% - write_unicode_string_as_latin1() also escapes characters >= 255. +%% Backwards compatibility. +write_unicode_string(S) -> + write_string(S). --spec write_unicode_string(UnicodeString) -> unicode_string() when - UnicodeString :: unicode_string(). +-spec write_latin1_string(Latin1String) -> latin1_string() when + Latin1String :: latin1_string(). -write_unicode_string(S) -> - write_unicode_string(S, $"). %" +write_latin1_string(S) -> + write_latin1_string(S, $"). %" --spec write_unicode_string(unicode_string(), char()) -> unicode_string(). +-spec write_latin1_string(latin1_string(), char()) -> latin1_string(). -write_unicode_string(S, Q) -> - [Q|write_string1(unicode_as_unicode, S, Q)]. +write_latin1_string(S, Q) -> + [Q|write_string1(latin1, S, Q)]. --spec write_unicode_string_as_latin1(UnicodeString) -> string() when - UnicodeString :: unicode_string(). +-spec write_string_as_latin1(String) -> latin1_string() when + String :: string(). -write_unicode_string_as_latin1(S) -> - write_unicode_string_as_latin1(S, $"). %" +write_string_as_latin1(S) -> + write_string_as_latin1(S, $"). %" --spec write_unicode_string_as_latin1(unicode_string(), char()) -> string(). +-spec write_string_as_latin1(string(), char()) -> latin1_string(). -write_unicode_string_as_latin1(S, Q) -> +write_string_as_latin1(S, Q) -> [Q|write_string1(unicode_as_latin1, S, Q)]. write_string1(_,[], Q) -> @@ -412,6 +415,11 @@ string_char(_,C, _, Tail) when C < $\240-> %Other control characters. C3 = (C band 7) + $0, [$\\,C1,C2,C3|Tail]. +%%% There are two functions to write a Unicode character: +%%% - they both escape control characters < 160; +%%% - write_char() never escapes characters >= 160; +%%% - write_char_as_latin1() also escapes characters >= 255. + %% write_char(Char) -> [char()]. %% Generate the list of characters needed to print a character constant. %% Must special case SPACE, $\s, here. @@ -420,48 +428,63 @@ string_char(_,C, _, Tail) when C < $\240-> %Other control characters. Char :: char(). write_char($\s) -> "$\\s"; %Must special case this. -write_char(C) when is_integer(C), C >= $\000, C =< $\377 -> - [$$|string_char(latin1,C, -1, [])]. +write_char(C) when is_integer(C), C >= $\000 -> + [$$|string_char(unicode_as_unicode, C, -1, [])]. -%%% There are two functions to write a Unicode character: -%%% - they both escape control characters < 160; -%%% - write_unicode_char() never escapes characters >= 160; -%%% - write_unicode_char_as_latin1() also escapes characters >= 255. +%% Backwards compatibility. +write_unicode_char(C) -> + write_char(C). --spec write_unicode_char(UnicodeChar) -> unicode_string() when - UnicodeChar :: unicode:unicode_char(). +-spec write_latin1_char(Latin1Char) -> latin1_string() when + Latin1Char :: unicode:latin1_char(). -write_unicode_char(Uni) when is_integer(Uni), Uni >= $\000 -> - [$$|string_char(unicode_as_unicode,Uni, -1, [])]. +write_latin1_char(Lat1) when is_integer(Lat1), Lat1 >= $\000, Lat1 =< $\377 -> + [$$|string_char(latin1, Lat1, -1, [])]. --spec write_unicode_char_as_latin1(UnicodeChar) -> string() when - UnicodeChar :: unicode:unicode_char(). +-spec write_char_as_latin1(Char) -> latin1_string() when + Char :: char(). -write_unicode_char_as_latin1(Uni) when is_integer(Uni), Uni >= $\000 -> +write_char_as_latin1(Uni) when is_integer(Uni), Uni >= $\000 -> [$$|string_char(unicode_as_latin1,Uni, -1, [])]. -%% char_list(CharList) -%% deep_char_list(CharList) -%% Return true if CharList is a (possibly deep) list of characters, else -%% false. +%% latin1_char_list(CharList) +%% deep_latin1_char_list(CharList) +%% Return true if CharList is a (possibly deep) list of Latin-1 +%% characters, else false. + +-spec latin1_char_list(Term) -> boolean() when + Term :: term(). + +latin1_char_list([C|Cs]) when is_integer(C), C >= $\000, C =< $\377 -> + latin1_char_list(Cs); +latin1_char_list([]) -> true; +latin1_char_list(_) -> false. %Everything else is false -spec char_list(Term) -> boolean() when Term :: term(). -char_list([C|Cs]) when is_integer(C), C >= $\000, C =< $\377 -> +char_list([C|Cs]) when is_integer(C), C >= 0, C < 16#D800; + is_integer(C), C > 16#DFFF, C < 16#FFFE; + is_integer(C), C > 16#FFFF, C =< 16#10FFFF -> char_list(Cs); char_list([]) -> true; char_list(_) -> false. %Everything else is false --spec unicode_char_list(Term) -> boolean() when +-spec deep_latin1_char_list(Term) -> boolean() when Term :: term(). -unicode_char_list([C|Cs]) when is_integer(C), C >= 0, C < 16#D800; - is_integer(C), C > 16#DFFF, C < 16#FFFE; - is_integer(C), C > 16#FFFF, C =< 16#10FFFF -> - unicode_char_list(Cs); -unicode_char_list([]) -> true; -unicode_char_list(_) -> false. %Everything else is false +deep_latin1_char_list(Cs) -> + deep_latin1_char_list(Cs, []). + +deep_latin1_char_list([C|Cs], More) when is_list(C) -> + deep_latin1_char_list(C, [Cs|More]); +deep_latin1_char_list([C|Cs], More) when is_integer(C), C >= $\000, C =< $\377 -> + deep_latin1_char_list(Cs, More); +deep_latin1_char_list([], [Cs|More]) -> + deep_latin1_char_list(Cs, More); +deep_latin1_char_list([], []) -> true; +deep_latin1_char_list(_, _More) -> %Everything else is false + false. -spec deep_char_list(Term) -> boolean() when Term :: term(). @@ -471,43 +494,56 @@ deep_char_list(Cs) -> deep_char_list([C|Cs], More) when is_list(C) -> deep_char_list(C, [Cs|More]); -deep_char_list([C|Cs], More) when is_integer(C), C >= $\000, C =< $\377 -> +deep_char_list([C|Cs], More) + when is_integer(C), C >= 0, C < 16#D800; + is_integer(C), C > 16#DFFF, C < 16#FFFE; + is_integer(C), C > 16#FFFF, C =< 16#10FFFF -> deep_char_list(Cs, More); deep_char_list([], [Cs|More]) -> deep_char_list(Cs, More); deep_char_list([], []) -> true; -deep_char_list(_, _More) -> %Everything else is false +deep_char_list(_, _More) -> %Everything else is false false. --spec deep_unicode_char_list(Term) -> boolean() when - Term :: term(). +deep_unicode_char_list(Term) -> + deep_char_list(Term). -deep_unicode_char_list(Cs) -> - deep_unicode_char_list(Cs, []). +%% printable_latin1_list([Char]) -> boolean() +%% Return true if CharList is a list of printable Latin1 characters, else +%% false. -deep_unicode_char_list([C|Cs], More) when is_list(C) -> - deep_unicode_char_list(C, [Cs|More]); -deep_unicode_char_list([C|Cs], More) - when is_integer(C), C >= 0, C < 16#D800; - is_integer(C), C > 16#DFFF, C < 16#FFFE; - is_integer(C), C > 16#FFFF, C =< 16#10FFFF -> - deep_unicode_char_list(Cs, More); -deep_unicode_char_list([], [Cs|More]) -> - deep_unicode_char_list(Cs, More); -deep_unicode_char_list([], []) -> true; -deep_unicode_char_list(_, _More) -> %Everything else is false - false. +-spec printable_latin1_list(Term) -> boolean() when + Term :: term(). + +printable_latin1_list([C|Cs]) when is_integer(C), C >= $\040, C =< $\176 -> + printable_latin1_list(Cs); +printable_latin1_list([C|Cs]) when is_integer(C), C >= $\240, C =< $\377 -> + printable_latin1_list(Cs); +printable_latin1_list([$\n|Cs]) -> printable_latin1_list(Cs); +printable_latin1_list([$\r|Cs]) -> printable_latin1_list(Cs); +printable_latin1_list([$\t|Cs]) -> printable_latin1_list(Cs); +printable_latin1_list([$\v|Cs]) -> printable_latin1_list(Cs); +printable_latin1_list([$\b|Cs]) -> printable_latin1_list(Cs); +printable_latin1_list([$\f|Cs]) -> printable_latin1_list(Cs); +printable_latin1_list([$\e|Cs]) -> printable_latin1_list(Cs); +printable_latin1_list([]) -> true; +printable_latin1_list(_) -> false. %Everything else is false %% printable_list([Char]) -> boolean() %% Return true if CharList is a list of printable characters, else -%% false. +%% false. The notion of printable in Unicode terms is somewhat floating. +%% Everything that is not a control character and not invalid unicode +%% will be considered printable. -spec printable_list(Term) -> boolean() when Term :: term(). printable_list([C|Cs]) when is_integer(C), C >= $\040, C =< $\176 -> printable_list(Cs); -printable_list([C|Cs]) when is_integer(C), C >= $\240, C =< $\377 -> +printable_list([C|Cs]) + when is_integer(C), C >= 16#A0, C < 16#D800; + is_integer(C), C > 16#DFFF, C < 16#FFFE; + is_integer(C), C > 16#FFFF, C =< 16#10FFFF -> printable_list(Cs); printable_list([$\n|Cs]) -> printable_list(Cs); printable_list([$\r|Cs]) -> printable_list(Cs); @@ -517,33 +553,7 @@ printable_list([$\b|Cs]) -> printable_list(Cs); printable_list([$\f|Cs]) -> printable_list(Cs); printable_list([$\e|Cs]) -> printable_list(Cs); printable_list([]) -> true; -printable_list(_) -> false. %Everything else is false - -%% printable_unicode_list([Char]) -> boolean() -%% Return true if CharList is a list of printable characters, else -%% false. The notion of printable in Unicode terms is somewhat floating. -%% Everything that is not a control character and not invalid unicode -%% will be considered printable. - --spec printable_unicode_list(Term) -> boolean() when - Term :: term(). - -printable_unicode_list([C|Cs]) when is_integer(C), C >= $\040, C =< $\176 -> - printable_unicode_list(Cs); -printable_unicode_list([C|Cs]) - when is_integer(C), C >= 16#A0, C < 16#D800; - is_integer(C), C > 16#DFFF, C < 16#FFFE; - is_integer(C), C > 16#FFFF, C =< 16#10FFFF -> - printable_unicode_list(Cs); -printable_unicode_list([$\n|Cs]) -> printable_unicode_list(Cs); -printable_unicode_list([$\r|Cs]) -> printable_unicode_list(Cs); -printable_unicode_list([$\t|Cs]) -> printable_unicode_list(Cs); -printable_unicode_list([$\v|Cs]) -> printable_unicode_list(Cs); -printable_unicode_list([$\b|Cs]) -> printable_unicode_list(Cs); -printable_unicode_list([$\f|Cs]) -> printable_unicode_list(Cs); -printable_unicode_list([$\e|Cs]) -> printable_unicode_list(Cs); -printable_unicode_list([]) -> true; -printable_unicode_list(_) -> false. %Everything else is false +printable_list(_) -> false. %Everything else is false %% List = nl() %% Return a list of characters to generate a newline. diff --git a/lib/stdlib/src/io_lib_format.erl b/lib/stdlib/src/io_lib_format.erl index 5680f83ab6..6a06d9448b 100644 --- a/lib/stdlib/src/io_lib_format.erl +++ b/lib/stdlib/src/io_lib_format.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2012. All Rights Reserved. +%% Copyright Ericsson AB 1996-2013. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -22,7 +22,7 @@ -export([fwrite/2,fwrite_g/1,indentation/2]). -%% fwrite(Format, ArgList) -> [unicode:unicode:char()]. +%% fwrite(Format, ArgList) -> string(). %% Format the arguments in ArgList after string Format. Just generate %% an error if there is an error in the arguments. %% @@ -133,7 +133,7 @@ pcount([{$P,_As,_F,_Ad,_P,_Pad,_Enc}|Cs], Acc) -> pcount(Cs, Acc+1); pcount([_|Cs], Acc) -> pcount(Cs, Acc); pcount([], Acc) -> Acc. -%% build([Control], Pc, Indentation) -> [unicode:unicode_char()]. +%% build([Control], Pc, Indentation) -> string(). %% Interpret the control structures. Count the number of print %% remaining and only calculate indentation when necessary. Must also %% be smart when calculating indentation for characters in format. @@ -154,7 +154,7 @@ decr_pc($p, Pc) -> Pc - 1; decr_pc($P, Pc) -> Pc - 1; decr_pc(_, Pc) -> Pc. -%% indentation([unicode:unicode_char()], Indentation) -> Indentation. +%% indentation(String, Indentation) -> Indentation. %% Calculate the indentation of the end of a string given its start %% indentation. We assume tabs at 8 cols. @@ -167,8 +167,7 @@ indentation([C|Cs], I) -> indentation([], I) -> I. %% control(FormatChar, [Argument], FieldWidth, Adjust, Precision, PadChar, -%% Encoding, Indentation) -> -%% [unicode:unicode_char()] +%% Encoding, Indentation) -> String %% This is the main dispatch function for the various formatting commands. %% Field widths and precisions have already been calculated. @@ -613,7 +612,7 @@ prefixed_integer(Int, F, Adj, Base, Pad, Prefix, Lowercase) term([Prefix|S], F, Adj, none, Pad) end. -%% char(Char, Field, Adjust, Precision, PadChar) -> [unicode:unicode_char()]. +%% char(Char, Field, Adjust, Precision, PadChar) -> string(). char(C, none, _Adj, none, _Pad) -> [C]; char(C, F, _Adj, none, _Pad) -> chars(C, F); diff --git a/lib/stdlib/src/io_lib_fread.erl b/lib/stdlib/src/io_lib_fread.erl index 84d4b8bba0..92a34995b8 100644 --- a/lib/stdlib/src/io_lib_fread.erl +++ b/lib/stdlib/src/io_lib_fread.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2011. All Rights Reserved. +%% Copyright Ericsson AB 1996-2013. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -22,7 +22,7 @@ -export([fread/2,fread/3]). --import(lists, [reverse/1,reverse/2]). +-import(lists, [reverse/1]). -define(is_whitespace(C), ((C) =:= $\s orelse (C) =:= $\t @@ -43,7 +43,7 @@ | {'done', Result, LeftOverChars :: string()}, Result :: {'ok', InputList :: io_lib:chars()} | 'eof' - | {'error', What :: io_lib:fread_error()}. + | {'error', {'read', What :: io_lib:fread_error()}}. fread([], Chars, Format) -> %%io:format("FREAD: ~w `~s'~n", [Format,Chars]), diff --git a/lib/stdlib/src/io_lib_pretty.erl b/lib/stdlib/src/io_lib_pretty.erl index 99ad281a9b..a8f610558a 100644 --- a/lib/stdlib/src/io_lib_pretty.erl +++ b/lib/stdlib/src/io_lib_pretty.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2012. All Rights Reserved. +%% Copyright Ericsson AB 1996-2013. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -51,7 +51,6 @@ print(Term) -> -type max_chars() :: integer(). -type chars() :: io_lib:chars(). --type unicode_chars() :: io_lib:unicode_chars(). -type option() :: {column, column()} | {line_length, line_length()} | {depth, depth()} @@ -60,8 +59,8 @@ print(Term) -> | {encoding, latin1 | utf8 | unicode}. -type options() :: [option()]. --spec print(term(), rec_print_fun()) -> chars() | unicode_chars(); - (term(), options()) -> chars() | unicode_chars(). +-spec print(term(), rec_print_fun()) -> chars(); + (term(), options()) -> chars(). print(Term, Options) when is_list(Options) -> Col = proplists:get_value(column, Options, 1), @@ -74,24 +73,23 @@ print(Term, Options) when is_list(Options) -> print(Term, RecDefFun) -> print(Term, -1, RecDefFun). --spec print(term(), depth(), rec_print_fun()) -> chars() | unicode_chars(). +-spec print(term(), depth(), rec_print_fun()) -> chars(). print(Term, Depth, RecDefFun) -> print(Term, 1, 80, Depth, RecDefFun). --spec print(term(), column(), line_length(), depth()) -> - chars() | unicode_chars(). +-spec print(term(), column(), line_length(), depth()) -> chars(). print(Term, Col, Ll, D) -> print(Term, Col, Ll, D, _M=-1, no_fun, latin1). -spec print(term(), column(), line_length(), depth(), rec_print_fun()) -> - chars() | unicode_chars(). + chars(). print(Term, Col, Ll, D, RecDefFun) -> print(Term, Col, Ll, D, _M=-1, RecDefFun). -spec print(term(), column(), line_length(), depth(), max_chars(), - rec_print_fun()) -> chars() | unicode_chars(). + rec_print_fun()) -> chars(). print(Term, Col, Ll, D, M, RecDefFun) -> print(Term, Col, Ll, D, M, RecDefFun, latin1). @@ -369,13 +367,13 @@ print_length(<<_/bitstring>>=Bin, D, _RF, Enc) -> S = io_lib:write_string(List, $"), %" {[$<,$<,S,$>,$>], 4 + length(S)}; {false, List} when is_list(List) -> - S = io_lib:write_unicode_string(List, $"), %" + S = io_lib:write_string(List, $"), %" {[$<,$<,S,"/utf8>>"], 9 + length(S)}; {true, true, Prefix} -> S = io_lib:write_string(Prefix, $"), %" {[$<,$<, S | "...>>"], 7 + length(S)}; {false, true, Prefix} -> - S = io_lib:write_unicode_string(Prefix, $"), %" + S = io_lib:write_string(Prefix, $"), %" {[$<,$<, S | "/utf8...>>"], 12 + length(S)}; false -> S = io_lib:write(Bin, D), @@ -387,7 +385,7 @@ print_length(<<_/bitstring>>=Bin, D, _RF, Enc) -> end; print_length(Term, _D, _RF, _Enc) -> S = io_lib:write(Term), - {S, iolist_size(S)}. + {S, lists:flatlength(S)}. print_length_tuple(_Tuple, 1, _RF, _Enc) -> {"{...}", 5}; @@ -451,9 +449,9 @@ list_length_tail({_, Len}, Acc) -> printable_list(_L, 1, _Enc) -> false; printable_list(L, _D, latin1) -> - io_lib:printable_list(L); + io_lib:printable_latin1_list(L); printable_list(L, _D, _Uni) -> - io_lib:printable_unicode_list(L). + io_lib:printable_list(L). %% Truncated lists could break some existing code. % printable_list(L, D, Enc) when D >= 0 -> % Len = ?CHARS * (D - 1), @@ -538,9 +536,9 @@ printable_unicode(Bin, I, L) -> {I, Bin, lists:reverse(L)}. write_string(S, latin1) -> - io_lib:write_string(S, $"); %" + io_lib:write_latin1_string(S, $"); %" write_string(S, _Uni) -> - io_lib:write_unicode_string(S, $"). %" + io_lib:write_string(S, $"). %" %% Throw 'no_good' if the indentation exceeds half the line length %% unless there is room for M characters on the line. diff --git a/lib/stdlib/src/lib.erl b/lib/stdlib/src/lib.erl index b2ce2a5a8f..8351376691 100644 --- a/lib/stdlib/src/lib.erl +++ b/lib/stdlib/src/lib.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2012. All Rights Reserved. +%% Copyright Ericsson AB 1996-2013. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -44,7 +44,7 @@ flush_receive() -> Args :: [term()]. error_message(Format, Args) -> - io:format(<<"** ~s **\n">>, [io_lib:format(Format, Args)]). + io:format(<<"** ~ts **\n">>, [io_lib:format(Format, Args)]). %% Return the name of the script that starts (this) erlang %% @@ -84,10 +84,14 @@ sendw(To, Msg) -> %% eval_str(InStr) -> {ok, OutStr} | {error, ErrStr'} %% InStr must represent a body +%% Note: If InStr is a binary it has to be a Latin-1 string. +%% If you have a UTF-8 encoded binary you have to call +%% unicode:characters_to_list/1 before the call to eval_str(). -define(result(F,D), lists:flatten(io_lib:format(F, D))). --spec eval_str(string() | binary()) -> {'ok', string()} | {'error', string()}. +-spec eval_str(string() | unicode:latin1_binary()) -> + {'ok', string()} | {'error', string()}. eval_str(Str) when is_list(Str) -> case erl_scan:tokens([], Str, 0) of @@ -105,12 +109,12 @@ eval_str(Str) when is_list(Str) -> {error, ?result("*** eval: ~p", [Other])} end; {error, {_Line, Mod, Args}} -> - Msg = ?result("*** ~s",[Mod:format_error(Args)]), + Msg = ?result("*** ~ts",[Mod:format_error(Args)]), {error, Msg} end; false -> {error, ?result("Non-white space found after " - "end-of-form :~s", [Rest])} + "end-of-form :~ts", [Rest])} end end; eval_str(Bin) when is_binary(Bin) -> @@ -426,9 +430,9 @@ brackets_to_parens(S, Enc) -> [$(,R,$)]. printable_list(latin1, As) -> - io_lib:printable_list(As); + io_lib:printable_latin1_list(As); printable_list(_, As) -> - io_lib:printable_unicode_list(As). + io_lib:printable_list(As). mfa_to_string(M, F, A) -> io_lib:fwrite(<<"~s/~w">>, [mf_to_string({M, F}, A), A]). diff --git a/lib/stdlib/src/ms_transform.erl b/lib/stdlib/src/ms_transform.erl index 4389fd457c..4868024eed 100644 --- a/lib/stdlib/src/ms_transform.erl +++ b/lib/stdlib/src/ms_transform.erl @@ -100,7 +100,7 @@ format_error({?ERR_GUARDREMOTECALL, Module, Name, Arithy}) -> [Module,Name,Arithy])); format_error({?ERR_GUARDELEMENT, Str}) -> lists:flatten( - io_lib:format("the language element ~s (in guard) cannot be translated " + io_lib:format("the language element ~ts (in guard) cannot be translated " "into match_spec", [Str])); format_error({?ERR_GUARDBINCONSTRUCT, Var}) -> lists:flatten( @@ -126,7 +126,7 @@ format_error({?ERR_BODYREMOTECALL, Module, Name, Arithy}) -> [Module,Name,Arithy])); format_error({?ERR_BODYELEMENT, Str}) -> lists:flatten( - io_lib:format("the language element ~s (in body) cannot be translated " + io_lib:format("the language element ~ts (in body) cannot be translated " "into match_spec", [Str])); format_error({?ERR_BODYBINCONSTRUCT, Var}) -> lists:flatten( diff --git a/lib/stdlib/src/proc_lib.erl b/lib/stdlib/src/proc_lib.erl index 4bca4c1e6d..1eb6fc2e86 100644 --- a/lib/stdlib/src/proc_lib.erl +++ b/lib/stdlib/src/proc_lib.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2012. All Rights Reserved. +%% Copyright Ericsson AB 1996-2013. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -29,7 +29,8 @@ 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,initial_call/1,translate_initial_call/1]). + init_p/3,init_p/5,format/1,format/2,initial_call/1, + translate_initial_call/1]). %% Internal exports. -export([wake_up/3]). @@ -692,34 +693,41 @@ check(Res) -> Res. -spec format(CrashReport) -> string() when CrashReport :: [term()]. - -format([OwnReport,LinkReport]) -> - OwnFormat = format_report(OwnReport), - LinkFormat = format_report(LinkReport), - S = io_lib:format(" crasher:~n~s neighbours:~n~s",[OwnFormat,LinkFormat]), - lists:flatten(S). - -format_report(Rep) when is_list(Rep) -> - format_rep(Rep); -format_report(Rep) -> - io_lib:format("~p~n", [Rep]). - -format_rep([{initial_call,InitialCall}|Rep]) -> - [format_mfa(InitialCall)|format_rep(Rep)]; -format_rep([{error_info,{Class,Reason,StackTrace}}|Rep]) -> - [format_exception(Class, Reason, StackTrace)|format_rep(Rep)]; -format_rep([{Tag,Data}|Rep]) -> - [format_tag(Tag, Data)|format_rep(Rep)]; -format_rep(_) -> +format(CrashReport) -> + format(CrashReport, latin1). + +-spec format(CrashReport, Encoding) -> string() when + CrashReport :: [term()], + Encoding :: latin1 | unicode | utf8. + +format([OwnReport,LinkReport], Encoding) -> + OwnFormat = format_report(OwnReport, Encoding), + LinkFormat = format_report(LinkReport, Encoding), + Str = io_lib:format(" crasher:~n~ts neighbours:~n~ts", + [OwnFormat, LinkFormat]), + lists:flatten(Str). + +format_report(Rep, Enc) when is_list(Rep) -> + format_rep(Rep,Enc); +format_report(Rep, Enc) -> + io_lib:format("~"++modifier(Enc)++"p~n", [Rep]). + +format_rep([{initial_call,InitialCall}|Rep], Enc) -> + [format_mfa(InitialCall)|format_rep(Rep, Enc)]; +format_rep([{error_info,{Class,Reason,StackTrace}}|Rep], Enc) -> + [format_exception(Class, Reason, StackTrace, Enc)|format_rep(Rep, Enc)]; +format_rep([{Tag,Data}|Rep], Enc) -> + [format_tag(Tag, Data)|format_rep(Rep, Enc)]; +format_rep(_, _Enc) -> []. -format_exception(Class, Reason, StackTrace) -> - PF = pp_fun(), +format_exception(Class, Reason, StackTrace, Enc) -> + PF = pp_fun(Enc), StackFun = fun(M, _F, _A) -> (M =:= erl_eval) or (M =:= ?MODULE) end, %% EI = " exception: ", EI = " ", [EI, lib:format_exception(1+length(EI), Class, Reason, - StackTrace, StackFun, PF), "\n"]. + StackTrace, StackFun, PF, Enc), "\n"]. format_mfa({M,F,Args}=StartF) -> try @@ -731,10 +739,14 @@ format_mfa({M,F,Args}=StartF) -> format_tag(initial_call, StartF) end. -pp_fun() -> +pp_fun(Enc) -> + P = modifier(Enc) ++ "p", fun(Term, I) -> - io_lib:format("~." ++ integer_to_list(I) ++ "p", [Term]) + io_lib:format("~." ++ integer_to_list(I) ++ P, [Term]) end. format_tag(Tag, Data) -> io_lib:format(" ~p: ~80.18p~n", [Tag, Data]). + +modifier(latin1) -> ""; +modifier(_) -> "t". diff --git a/lib/stdlib/src/qlc.erl b/lib/stdlib/src/qlc.erl index 9b71d0edb8..9351674e00 100644 --- a/lib/stdlib/src/qlc.erl +++ b/lib/stdlib/src/qlc.erl @@ -386,25 +386,25 @@ format_error(nomatch_pattern) -> format_error(nomatch_filter) -> io_lib:format("filter evaluates to 'false'", []); format_error({Line, Mod, Reason}) when is_integer(Line) -> - io_lib:format("~p: ~s~n", + io_lib:format("~p: ~ts~n", [Line, lists:flatten(Mod:format_error(Reason))]); %% file_sorter errors format_error({bad_object, FileName}) -> - io_lib:format("the temporary file \"~s\" holding answers is corrupt", + io_lib:format("the temporary file \"~ts\" holding answers is corrupt", [FileName]); format_error(bad_object) -> io_lib:format("the keys could not be extracted from some term", []); format_error({file_error, FileName, Reason}) -> - io_lib:format("\"~s\": ~p~n",[FileName, file:format_error(Reason)]); + io_lib:format("\"~ts\": ~tp~n",[FileName, file:format_error(Reason)]); format_error({premature_eof, FileName}) -> - io_lib:format("\"~s\": end-of-file was encountered inside some binary term", + io_lib:format("\"~ts\": end-of-file was encountered inside some binary term", [FileName]); format_error({tmpdir_usage, Why}) -> io_lib:format("temporary file was needed for ~w~n", [Why]); format_error({error, Module, Reason}) -> Module:format_error(Reason); format_error(E) -> - io_lib:format("~p~n", [E]). + io_lib:format("~tp~n", [E]). -spec(info(QH) -> Info when QH :: query_handle_or_list(), diff --git a/lib/stdlib/src/qlc_pt.erl b/lib/stdlib/src/qlc_pt.erl index d441f38e44..0744a5ffb9 100644 --- a/lib/stdlib/src/qlc_pt.erl +++ b/lib/stdlib/src/qlc_pt.erl @@ -214,7 +214,7 @@ compile_messages(Forms, FormsNoShadows, Options, State) -> end, {_,BGens} = qual_fold(BGenF, [], [], FormsNoShadows, State), GenForm = used_genvar_check(FormsNoShadows, State), - ?DEBUG("GenForm = ~s~n", [catch erl_pp:form(GenForm)]), + ?DEBUG("GenForm = ~ts~n", [catch erl_pp:form(GenForm)]), WarnFun = fun(Id, LC, A) -> {tag_lines(LC, get_lcid_no(Id)), A} end, {WForms,ok} = qlc_mapfold(WarnFun, ok, Forms, State), {Es,Ws} = compile_forms(WForms ++ [GenForm], Options), @@ -337,7 +337,7 @@ compile_errors(FormsNoShadows) -> {[], _Warnings} -> []; {Errors, _Warnings} -> - ?DEBUG("got errors ~p~n", [Errors]), + ?DEBUG("got errors ~tp~n", [Errors]), lists:flatmap(fun({_File,Es}) -> Es end, Errors) end. @@ -2742,7 +2742,7 @@ family(L) -> display_forms(Forms) -> io:format("Forms ***~n"), lists:foreach(fun(Form) -> - io:format("~s~n", [catch erl_pp:form(Form)]) + io:format("~ts~n", [catch erl_pp:form(Form)]) end, Forms), io:format("End Forms ***~n"). -else. diff --git a/lib/stdlib/src/shell.erl b/lib/stdlib/src/shell.erl index 5c929d2f51..bb90353e76 100644 --- a/lib/stdlib/src/shell.erl +++ b/lib/stdlib/src/shell.erl @@ -273,7 +273,7 @@ get_command(Prompt, Eval, Bs, RT, Ds) -> fun() -> exit( case - io:scan_erl_exprs(group_leader(), Prompt, 1, [unicode]) + io:scan_erl_exprs(group_leader(), Prompt, 1) of {ok,Toks,_EndPos} -> erl_parse:parse_exprs(Toks); diff --git a/lib/stdlib/src/slave.erl b/lib/stdlib/src/slave.erl index de0179da59..317d06a44b 100644 --- a/lib/stdlib/src/slave.erl +++ b/lib/stdlib/src/slave.erl @@ -229,7 +229,7 @@ wait_for_slave(Parent, Host, Name, Node, Args, LinkTo, Prog) -> Waiter = register_unique_name(0), case mk_cmd(Host, Name, Args, Waiter, Prog) of {ok, Cmd} -> -%% io:format("Command: ~s~n", [Cmd]), +%% io:format("Command: ~ts~n", [Cmd]), open_port({spawn, Cmd}, [stream]), receive {SlavePid, slave_started} -> diff --git a/lib/stdlib/src/string.erl b/lib/stdlib/src/string.erl index 03f0a19f14..aeaf9cb5c1 100644 --- a/lib/stdlib/src/string.erl +++ b/lib/stdlib/src/string.erl @@ -484,8 +484,8 @@ to_upper_char(C) -> C. -spec to_lower(String) -> Result when - String :: string(), - Result :: string() + String :: io_lib:latin1_string(), + Result :: io_lib:latin1_string() ; (Char) -> CharResult when Char :: char(), CharResult :: char(). @@ -496,8 +496,8 @@ to_lower(C) when is_integer(C) -> to_lower_char(C). -spec to_upper(String) -> Result when - String :: string(), - Result :: string() + String :: io_lib:latin1_string(), + Result :: io_lib:latin1_string() ; (Char) -> CharResult when Char :: char(), CharResult :: char(). diff --git a/lib/stdlib/src/unicode.erl b/lib/stdlib/src/unicode.erl index 8b9412fb1b..49529cffd4 100644 --- a/lib/stdlib/src/unicode.erl +++ b/lib/stdlib/src/unicode.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2008-2012. All Rights Reserved. +%% Copyright Ericsson AB 2008-2013. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -24,26 +24,33 @@ bom_to_encoding/1, encoding_to_bom/1]). -export_type([chardata/0, charlist/0, encoding/0, external_chardata/0, - external_charlist/0, latin1_chardata/0, - latin1_charlist/0, unicode_binary/0, unicode_char/0]). + external_charlist/0, latin1_char/0, latin1_chardata/0, + latin1_charlist/0, latin1_binary/0, unicode_binary/0]). -type encoding() :: 'latin1' | 'unicode' | 'utf8' | 'utf16' | {'utf16', endian()} | 'utf32' | {'utf32', endian()}. -type endian() :: 'big' | 'little'. -type unicode_binary() :: binary(). --type unicode_char() :: non_neg_integer(). --type charlist() :: [unicode_char() | unicode_binary() | charlist()]. +-type charlist() :: + maybe_improper_list(char() | unicode_binary() | charlist(), + unicode_binary() | nil()). -type chardata() :: charlist() | unicode_binary(). -type external_unicode_binary() :: binary(). -type external_chardata() :: external_charlist() | external_unicode_binary(). --type external_charlist() :: [unicode_char() | external_unicode_binary() - | external_charlist()]. +-type external_charlist() :: + maybe_improper_list(char() | + external_unicode_binary() | + external_charlist(), + external_unicode_binary() | nil()). -type latin1_binary() :: binary(). -type latin1_char() :: byte(). -type latin1_chardata() :: latin1_charlist() | latin1_binary(). --type latin1_charlist() :: [latin1_char() | latin1_binary() - | latin1_charlist()]. +-type latin1_charlist() :: + maybe_improper_list(latin1_char() | + latin1_binary() | + latin1_charlist(), + latin1_binary() | nil()). %%% BIFs %%% diff --git a/lib/stdlib/src/zip.erl b/lib/stdlib/src/zip.erl index c383540db7..489406c023 100644 --- a/lib/stdlib/src/zip.erl +++ b/lib/stdlib/src/zip.erl @@ -610,9 +610,9 @@ get_zip_opt([Unknown | _Rest], _Opts) -> %% feedback funs silent(_) -> ok. -verbose_unzip(FN) -> io:format("extracting: ~p\n", [FN]). +verbose_unzip(FN) -> io:format("extracting: ~tp\n", [FN]). -verbose_zip(FN) -> io:format("adding: ~p\n", [FN]). +verbose_zip(FN) -> io:format("adding: ~tp\n", [FN]). %% file filter funs all(_) -> true. @@ -943,7 +943,7 @@ raw_short_print_info_etc(EOCD, X, Comment, Y, Acc) when is_record(EOCD, eocd) -> raw_long_print_info_etc(EOCD, X, Comment, Y, Acc). print_file_name(FileName) -> - io:format("~s\n", [FileName]). + io:format("~ts\n", [FileName]). %% for printing directory (tt/1) @@ -960,14 +960,14 @@ raw_long_print_info_etc(EOCD, _, Comment, _, Acc) when is_record(EOCD, eocd) -> Acc. print_header(CompSize, MTime, UncompSize, FileName, FileComment) -> - io:format("~8w ~s ~8w ~2w% ~s ~s\n", + io:format("~8w ~s ~8w ~2w% ~ts ~ts\n", [CompSize, time_to_string(MTime), UncompSize, get_percent(CompSize, UncompSize), FileName, FileComment]). print_comment("") -> ok; print_comment(Comment) -> - io:format("Archive comment: ~s\n", [Comment]). + io:format("Archive comment: ~ts\n", [Comment]). get_percent(_, 0) -> 100; get_percent(CompSize, Size) -> round(CompSize * 100 / Size). |