From db770869af66309b9505d051770d8dc4d00354bf Mon Sep 17 00:00:00 2001 From: Hans Bolinder Date: Fri, 18 Jan 2013 09:31:40 +0100 Subject: Make adjustments for Unicode --- lib/stdlib/src/base64.erl | 31 ++++++++++++++++--------------- lib/stdlib/src/beam_lib.erl | 28 ++++++++++++++-------------- lib/stdlib/src/c.erl | 17 +++++++++++------ lib/stdlib/src/dets.erl | 8 ++++---- lib/stdlib/src/dets_utils.erl | 2 +- lib/stdlib/src/dets_v8.erl | 2 +- lib/stdlib/src/dets_v9.erl | 2 +- lib/stdlib/src/erl_compile.erl | 10 +++++----- lib/stdlib/src/erl_lint.erl | 2 +- lib/stdlib/src/erl_tar.erl | 18 +++++++++--------- lib/stdlib/src/escript.erl | 14 +++++++------- lib/stdlib/src/ets.erl | 4 ++-- lib/stdlib/src/file_sorter.erl | 6 +++--- lib/stdlib/src/io.erl | 2 -- lib/stdlib/src/lib.erl | 12 ++++++++---- lib/stdlib/src/ms_transform.erl | 4 ++-- lib/stdlib/src/qlc.erl | 10 +++++----- lib/stdlib/src/qlc_pt.erl | 6 +++--- lib/stdlib/src/shell.erl | 2 +- lib/stdlib/src/slave.erl | 2 +- lib/stdlib/src/string.erl | 8 ++++---- lib/stdlib/src/unicode.erl | 2 +- lib/stdlib/src/zip.erl | 10 +++++----- 23 files changed, 105 insertions(+), 97 deletions(-) (limited to 'lib/stdlib/src') 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, <>, 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, <>} = 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/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_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 79cb988c5d..3dddb0d6e7 100644 --- a/lib/stdlib/src/io.erl +++ b/lib/stdlib/src/io.erl @@ -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). diff --git a/lib/stdlib/src/lib.erl b/lib/stdlib/src/lib.erl index b778f3bf64..8351376691 100644 --- a/lib/stdlib/src/lib.erl +++ b/lib/stdlib/src/lib.erl @@ -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) -> 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/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 6b13ddb92d..49529cffd4 100644 --- a/lib/stdlib/src/unicode.erl +++ b/lib/stdlib/src/unicode.erl @@ -25,7 +25,7 @@ -export_type([chardata/0, charlist/0, encoding/0, external_chardata/0, external_charlist/0, latin1_char/0, latin1_chardata/0, - latin1_charlist/0, unicode_binary/0]). + latin1_charlist/0, latin1_binary/0, unicode_binary/0]). -type encoding() :: 'latin1' | 'unicode' | 'utf8' | 'utf16' | {'utf16', endian()} 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). -- cgit v1.2.3