aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r--lib/stdlib/src/array.erl2
-rw-r--r--lib/stdlib/src/erl_eval.erl46
-rw-r--r--lib/stdlib/src/io.erl11
-rw-r--r--lib/stdlib/src/io_lib_pretty.erl2
-rw-r--r--lib/stdlib/src/maps.erl9
-rw-r--r--lib/stdlib/src/string.erl12
6 files changed, 70 insertions, 12 deletions
diff --git a/lib/stdlib/src/array.erl b/lib/stdlib/src/array.erl
index a237eaa489..939b1fb488 100644
--- a/lib/stdlib/src/array.erl
+++ b/lib/stdlib/src/array.erl
@@ -290,7 +290,7 @@ new(Size, Fixed, Default) ->
end,
#array{size = Size, max = M, default = Default, elements = E}.
--spec find_max(integer(), integer()) -> integer().
+-spec find_max(integer(), non_neg_integer()) -> non_neg_integer().
find_max(I, M) when I >= M ->
find_max(I, ?extend(M));
diff --git a/lib/stdlib/src/erl_eval.erl b/lib/stdlib/src/erl_eval.erl
index 0f6d48b9a3..31c0e60fe1 100644
--- a/lib/stdlib/src/erl_eval.erl
+++ b/lib/stdlib/src/erl_eval.erl
@@ -29,7 +29,7 @@
-export([new_bindings/0,bindings/1,binding/2,add_binding/3,del_binding/2]).
-export([extended_parse_exprs/1, extended_parse_term/1,
subst_values_for_vars/2]).
--export([is_constant_expr/1, partial_eval/1]).
+-export([is_constant_expr/1, partial_eval/1, eval_str/1]).
%% Is used by standalone Erlang (escript).
%% Also used by shell.erl.
@@ -1557,6 +1557,50 @@ ev_expr({cons,_,H,T}) -> [ev_expr(H) | ev_expr(T)].
%% true = erl_internal:guard_bif(F, length(As)),
%% apply(erlang, F, [ev_expr(X) || X <- As]);
+%% 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() | unicode:latin1_binary()) ->
+ {'ok', string()} | {'error', string()}.
+
+eval_str(Str) when is_list(Str) ->
+ case erl_scan:tokens([], Str, 0) of
+ {more, _} ->
+ {error, "Incomplete form (missing .<cr>)??"};
+ {done, {ok, Toks, _}, Rest} ->
+ case all_white(Rest) of
+ true ->
+ case erl_parse:parse_exprs(Toks) of
+ {ok, Exprs} ->
+ case catch erl_eval:exprs(Exprs, erl_eval:new_bindings()) of
+ {value, Val, _} ->
+ {ok, Val};
+ Other ->
+ {error, ?result("*** eval: ~p", [Other])}
+ end;
+ {error, {_Line, Mod, Args}} ->
+ Msg = ?result("*** ~ts",[Mod:format_error(Args)]),
+ {error, Msg}
+ end;
+ false ->
+ {error, ?result("Non-white space found after "
+ "end-of-form :~ts", [Rest])}
+ end
+ end;
+eval_str(Bin) when is_binary(Bin) ->
+ eval_str(binary_to_list(Bin)).
+
+all_white([$\s|T]) -> all_white(T);
+all_white([$\n|T]) -> all_white(T);
+all_white([$\t|T]) -> all_white(T);
+all_white([]) -> true;
+all_white(_) -> false.
+
ret_expr(_Old, New) ->
%% io:format("~w: reduced ~s => ~s~n",
%% [line(Old), erl_pp:expr(Old), erl_pp:expr(New)]),
diff --git a/lib/stdlib/src/io.erl b/lib/stdlib/src/io.erl
index f510f61e9f..5d5773c80c 100644
--- a/lib/stdlib/src/io.erl
+++ b/lib/stdlib/src/io.erl
@@ -86,7 +86,16 @@ put_chars(Chars) ->
CharData :: unicode:chardata().
put_chars(Io, Chars) ->
- o_request(Io, {put_chars,unicode,Chars}, put_chars).
+ put_chars(Io, unicode, Chars).
+
+%% This function is here to make the erlang:raise in o_request actually raise to
+%% a valid function.
+-spec put_chars(IoDevice, Encoding, CharData) -> 'ok' when
+ IoDevice :: device(),
+ Encoding :: unicode,
+ CharData :: unicode:chardata().
+put_chars(Io, Encoding, Chars) ->
+ o_request(Io, {put_chars,Encoding,Chars}, put_chars).
-spec nl() -> 'ok'.
diff --git a/lib/stdlib/src/io_lib_pretty.erl b/lib/stdlib/src/io_lib_pretty.erl
index 3d5a979b3e..dca1b37ef3 100644
--- a/lib/stdlib/src/io_lib_pretty.erl
+++ b/lib/stdlib/src/io_lib_pretty.erl
@@ -131,6 +131,8 @@ print(Term, Col, Ll, D, M0, T, RecDefFun, Enc, Str) when is_tuple(Term);
%% use Len as CHAR_MAX if M0 = -1
M = max_cs(M0, Len),
if
+ Ll =:= 0 ->
+ write(If);
Len < Ll - Col, Len =< M ->
%% write the whole thing on a single line when there is room
write(If);
diff --git a/lib/stdlib/src/maps.erl b/lib/stdlib/src/maps.erl
index a13f340709..a1634547f3 100644
--- a/lib/stdlib/src/maps.erl
+++ b/lib/stdlib/src/maps.erl
@@ -249,7 +249,7 @@ fold(Fun,Init,Map) when is_function(Fun,3), is_map(Map) ->
fold(Fun,Init,Iterator) when is_function(Fun,3), ?IS_ITERATOR(Iterator) ->
fold_1(Fun,Init,Iterator);
fold(Fun,Init,Map) ->
- erlang:error(error_type(Map),[Fun,Init,Map]).
+ erlang:error(error_type_iter(Map),[Fun,Init,Map]).
fold_1(Fun, Acc, Iter) ->
case next(Iter) of
@@ -272,7 +272,7 @@ map(Fun,Map) when is_function(Fun, 2), is_map(Map) ->
map(Fun,Iterator) when is_function(Fun, 2), ?IS_ITERATOR(Iterator) ->
maps:from_list(map_1(Fun, Iterator));
map(Fun,Map) ->
- erlang:error(error_type(Map),[Fun,Map]).
+ erlang:error(error_type_iter(Map),[Fun,Map]).
map_1(Fun, Iter) ->
case next(Iter) of
@@ -342,5 +342,8 @@ with(Ks,M) ->
erlang:error(error_type(M),[Ks,M]).
-error_type(M) when is_map(M); ?IS_ITERATOR(M) -> badarg;
+error_type(M) when is_map(M) -> badarg;
error_type(V) -> {badmap, V}.
+
+error_type_iter(M) when is_map(M); ?IS_ITERATOR(M) -> badarg;
+error_type_iter(V) -> {badmap, V}.
diff --git a/lib/stdlib/src/string.erl b/lib/stdlib/src/string.erl
index f5d271c06d..cf48b882e4 100644
--- a/lib/stdlib/src/string.erl
+++ b/lib/stdlib/src/string.erl
@@ -691,9 +691,9 @@ uppercase_list(CPs0, Changed) ->
uppercase_bin(CP1, <<CP2/utf8, Bin/binary>>, _Changed)
when $a =< CP1, CP1 =< $z, CP2 < 256 ->
[CP1-32|uppercase_bin(CP2, Bin, true)];
-uppercase_bin(CP1, <<CP2/utf8, Bin/binary>>, _Changed)
+uppercase_bin(CP1, <<CP2/utf8, Bin/binary>>, Changed)
when CP1 < 128, CP2 < 256 ->
- [CP1|uppercase_bin(CP2, Bin, false)];
+ [CP1|uppercase_bin(CP2, Bin, Changed)];
uppercase_bin(CP1, Bin, Changed) ->
case unicode_util:uppercase([CP1|Bin]) of
[CP1|CPs] ->
@@ -732,9 +732,9 @@ lowercase_list(CPs0, Changed) ->
lowercase_bin(CP1, <<CP2/utf8, Bin/binary>>, _Changed)
when $A =< CP1, CP1 =< $Z, CP2 < 256 ->
[CP1+32|lowercase_bin(CP2, Bin, true)];
-lowercase_bin(CP1, <<CP2/utf8, Bin/binary>>, _Changed)
+lowercase_bin(CP1, <<CP2/utf8, Bin/binary>>, Changed)
when CP1 < 128, CP2 < 256 ->
- [CP1|lowercase_bin(CP2, Bin, false)];
+ [CP1|lowercase_bin(CP2, Bin, Changed)];
lowercase_bin(CP1, Bin, Changed) ->
case unicode_util:lowercase([CP1|Bin]) of
[CP1|CPs] ->
@@ -773,9 +773,9 @@ casefold_list(CPs0, Changed) ->
casefold_bin(CP1, <<CP2/utf8, Bin/binary>>, _Changed)
when $A =< CP1, CP1 =< $Z, CP2 < 256 ->
[CP1+32|casefold_bin(CP2, Bin, true)];
-casefold_bin(CP1, <<CP2/utf8, Bin/binary>>, _Changed)
+casefold_bin(CP1, <<CP2/utf8, Bin/binary>>, Changed)
when CP1 < 128, CP2 < 256 ->
- [CP1|casefold_bin(CP2, Bin, false)];
+ [CP1|casefold_bin(CP2, Bin, Changed)];
casefold_bin(CP1, Bin, Changed) ->
case unicode_util:casefold([CP1|Bin]) of
[CP1|CPs] ->