aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r--lib/stdlib/src/io_lib.erl24
-rw-r--r--lib/stdlib/src/io_lib_pretty.erl14
2 files changed, 31 insertions, 7 deletions
diff --git a/lib/stdlib/src/io_lib.erl b/lib/stdlib/src/io_lib.erl
index a91143a764..28e5007e5a 100644
--- a/lib/stdlib/src/io_lib.erl
+++ b/lib/stdlib/src/io_lib.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2016. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2017. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -68,8 +68,8 @@
-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_string_as_latin1/1, write_string_as_latin1/2,
- write_char_as_latin1/1]).
+-export([write_atom_as_latin1/1, write_string_as_latin1/1,
+ write_string_as_latin1/2, write_char_as_latin1/1]).
-export([quote_atom/2, char_list/1, latin1_char_list/1,
deep_char_list/1, deep_latin1_char_list/1,
@@ -344,6 +344,11 @@ write_binary_body(B, _D) ->
<<X:L>> = B,
[integer_to_list(X),$:,integer_to_list(L)].
+%%% There are two functions to write Unicode atoms:
+%%% - they both escape control characters < 160;
+%%% - write_atom() never escapes characters >= 160;
+%%% - write_atom_as_latin1() also escapes characters >= 255.
+
%% write_atom(Atom) -> [Char]
%% Generate the list of characters needed to print an atom.
@@ -351,17 +356,26 @@ write_binary_body(B, _D) ->
Atom :: atom().
write_atom(Atom) ->
+ write_possibly_quoted_atom(Atom, fun write_string/2).
+
+-spec write_atom_as_latin1(Atom) -> latin1_string() when
+ Atom :: atom().
+
+write_atom_as_latin1(Atom) ->
+ write_possibly_quoted_atom(Atom, fun write_string_as_latin1/2).
+
+write_possibly_quoted_atom(Atom, PFun) ->
Chars = atom_to_list(Atom),
case quote_atom(Atom, Chars) of
true ->
- write_string(Chars, $'); %'
+ PFun(Chars, $'); %'
false ->
Chars
end.
%% quote_atom(Atom, CharList)
%% Return 'true' if atom with chars in CharList needs to be quoted, else
-%% return 'false'.
+%% return 'false'. Notice that characters >= 160 are always quoted.
-spec quote_atom(atom(), chars()) -> boolean().
diff --git a/lib/stdlib/src/io_lib_pretty.erl b/lib/stdlib/src/io_lib_pretty.erl
index aabccfc5d9..ff368d02da 100644
--- a/lib/stdlib/src/io_lib_pretty.erl
+++ b/lib/stdlib/src/io_lib_pretty.erl
@@ -105,6 +105,8 @@ print(_, _, _, 0, _M, _RF, _Enc, _Str) -> "...";
print(Term, Col, Ll, D, M, RecDefFun, Enc, Str) when Col =< 0 ->
%% ensure Col is at least 1
print(Term, 1, Ll, D, M, RecDefFun, Enc, Str);
+print(Atom, _Col, _Ll, _D, _M, _RF, Enc, _Str) when is_atom(Atom) ->
+ write_atom(Atom, Enc);
print(Term, Col, Ll, D, M0, RecDefFun, Enc, Str) when is_tuple(Term);
is_list(Term);
is_map(Term);
@@ -407,6 +409,9 @@ print_length({}, _D, _RF, _Enc, _Str) ->
{"{}", 2};
print_length(#{}=M, _D, _RF, _Enc, _Str) when map_size(M) =:= 0 ->
{"#{}", 3};
+print_length(Atom, _D, _RF, Enc, _Str) when is_atom(Atom) ->
+ S = write_atom(Atom, Enc),
+ {S, lists:flatlength(S)};
print_length(List, D, RF, Enc, Str) when is_list(List) ->
%% only flat lists are "printable"
case Str andalso printable_list(List, D, Enc) of
@@ -500,7 +505,7 @@ print_length_tuple(Tuple, D, RF, Enc, Str) ->
print_length_record(_Tuple, 1, _RF, _RDefs, _Enc, _Str) ->
{"{...}", 5};
print_length_record(Tuple, D, RF, RDefs, Enc, Str) ->
- Name = [$# | io_lib:write_atom(element(1, Tuple))],
+ Name = [$# | write_atom(element(1, Tuple), Enc)],
NameL = length(Name),
Elements = tl(tuple_to_list(Tuple)),
L = print_length_fields(RDefs, D - 1, Elements, RF, Enc, Str),
@@ -515,7 +520,7 @@ print_length_fields([Def | Defs], D, [E | Es], RF, Enc, Str) ->
print_length_fields(Defs, D - 1, Es, RF, Enc, Str)].
print_length_field(Def, D, E, RF, Enc, Str) ->
- Name = io_lib:write_atom(Def),
+ Name = write_atom(Def, Enc),
{S, L} = print_length(E, D, RF, Enc, Str),
NameL = length(Name) + 3,
{{field, Name, NameL, {S, L}}, NameL + L}.
@@ -664,6 +669,11 @@ printable_char(C,unicode) ->
C > 16#DFFF andalso C < 16#FFFE orelse
C > 16#FFFF andalso C =< 16#10FFFF.
+write_atom(A, latin1) ->
+ io_lib:write_atom_as_latin1(A);
+write_atom(A, _Uni) ->
+ io_lib:write_atom(A).
+
write_string(S, latin1) ->
io_lib:write_latin1_string(S, $"); %"
write_string(S, _Uni) ->