diff options
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r-- | lib/stdlib/src/erl_lint.erl | 12 | ||||
-rw-r--r-- | lib/stdlib/src/io_lib.erl | 23 | ||||
-rw-r--r-- | lib/stdlib/src/io_lib_format.erl | 110 | ||||
-rw-r--r-- | lib/stdlib/src/io_lib_pretty.erl | 57 | ||||
-rw-r--r-- | lib/stdlib/src/stdlib.app.src | 2 | ||||
-rw-r--r-- | lib/stdlib/src/stdlib.appup.src | 34 | ||||
-rw-r--r-- | lib/stdlib/src/string.erl | 78 |
7 files changed, 199 insertions, 117 deletions
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index e0c37ca030..0cd0aef124 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -2,7 +2,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2018. All Rights Reserved. +%% Copyright Ericsson AB 1996-2019. 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. @@ -386,6 +386,8 @@ format_error({redefine_callback, {F, A}}) -> format_error({bad_callback, {M, F, A}}) -> io_lib:format("explicit module not allowed for callback ~tw:~tw/~w", [M, F, A]); +format_error({bad_module, {M, F, A}}) -> + io_lib:format("spec for function ~w:~tw/~w from other module", [M, F, A]); format_error({spec_fun_undefined, {F, A}}) -> io_lib:format("spec for undefined function ~tw/~w", [F, A]); format_error({missing_spec, {F,A}}) -> @@ -3010,7 +3012,13 @@ spec_decl(Line, MFA0, TypeSpecs, St00 = #lint{specs = Specs, module = Mod}) -> St1 = St0#lint{specs = dict:store(MFA, Line, Specs)}, case dict:is_key(MFA, Specs) of true -> add_error(Line, {redefine_spec, MFA0}, St1); - false -> check_specs(TypeSpecs, spec_wrong_arity, Arity, St1) + false -> + case MFA of + {Mod, _, _} -> + check_specs(TypeSpecs, spec_wrong_arity, Arity, St1); + _ -> + add_error(Line, {bad_module, MFA}, St1) + end end. %% callback_decl(Line, Fun, Types, State) -> State. diff --git a/lib/stdlib/src/io_lib.erl b/lib/stdlib/src/io_lib.erl index 2b5a374cf2..21d66c5529 100644 --- a/lib/stdlib/src/io_lib.erl +++ b/lib/stdlib/src/io_lib.erl @@ -412,14 +412,25 @@ write_port(Port) -> write_ref(Ref) -> erlang:ref_to_list(Ref). +write_map(_, 1, _E) -> "#{}"; write_map(Map, D, E) when is_integer(D) -> - [$#,${,write_map_body(maps:to_list(Map), D, D - 1, E),$}]. + I = maps:iterator(Map), + case maps:next(I) of + {K, V, NextI} -> + D0 = D - 1, + W = write_map_assoc(K, V, D0, E), + [$#,${,[W | write_map_body(NextI, D0, D0, E)],$}]; + none -> "#{}" + end. -write_map_body(_, 1, _D0, _E) -> "..."; -write_map_body([], _, _D0, _E) -> []; -write_map_body([{K,V}], _D, D0, E) -> write_map_assoc(K, V, D0, E); -write_map_body([{K,V}|KVs], D, D0, E) -> - [write_map_assoc(K, V, D0, E),$, | write_map_body(KVs, D - 1, D0, E)]. +write_map_body(_, 1, _D0, _E) -> ",..."; +write_map_body(I, D, D0, E) -> + case maps:next(I) of + {K, V, NextI} -> + W = write_map_assoc(K, V, D0, E), + [$,,W|write_map_body(NextI, D - 1, D0, E)]; + none -> "" + end. write_map_assoc(K, V, D, E) -> [write1(K, D, E)," => ",write1(V, D, E)]. diff --git a/lib/stdlib/src/io_lib_format.erl b/lib/stdlib/src/io_lib_format.erl index d1aa4cd157..157cc07e19 100644 --- a/lib/stdlib/src/io_lib_format.erl +++ b/lib/stdlib/src/io_lib_format.erl @@ -327,11 +327,11 @@ indentation([], I) -> I. %% PadChar, Encoding, StringP, ChrsLim, Indentation) -> String %% These are the dispatch functions for the various formatting controls. -control_small($s, [A], F, Adj, P, Pad, latin1) when is_atom(A) -> +control_small($s, [A], F, Adj, P, Pad, latin1=Enc) when is_atom(A) -> L = iolist_to_chars(atom_to_list(A)), - string(L, F, Adj, P, Pad); -control_small($s, [A], F, Adj, P, Pad, unicode) when is_atom(A) -> - string(atom_to_list(A), F, Adj, P, Pad); + string(L, F, Adj, P, Pad, Enc); +control_small($s, [A], F, Adj, P, Pad, unicode=Enc) when is_atom(A) -> + string(atom_to_list(A), F, Adj, P, Pad, Enc); control_small($e, [A], F, Adj, P, Pad, _Enc) when is_float(A) -> fwrite_e(A, F, Adj, P, Pad); control_small($f, [A], F, Adj, P, Pad, _Enc) when is_float(A) -> @@ -371,12 +371,12 @@ control_small($n, [], F, Adj, P, Pad, _Enc) -> newline(F, Adj, P, Pad); control_small($i, [_A], _F, _Adj, _P, _Pad, _Enc) -> []; control_small(_C, _As, _F, _Adj, _P, _Pad, _Enc) -> not_small. -control_limited($s, [L0], F, Adj, P, Pad, latin1, _Str, CL, _I) -> - L = iolist_to_chars(L0), - string(limit_string(L, F, CL), limit_field(F, CL), Adj, P, Pad); -control_limited($s, [L0], F, Adj, P, Pad, unicode, _Str, CL, _I) -> - L = cdata_to_chars(L0), - uniconv(string(limit_string(L, F, CL), limit_field(F, CL), Adj, P, Pad)); +control_limited($s, [L0], F, Adj, P, Pad, latin1=Enc, _Str, CL, _I) -> + L = iolist_to_chars(L0, F, CL), + string(L, limit_field(F, CL), Adj, P, Pad, Enc); +control_limited($s, [L0], F, Adj, P, Pad, unicode=Enc, _Str, CL, _I) -> + L = cdata_to_chars(L0, F, CL), + uniconv(string(L, limit_field(F, CL), Adj, P, Pad, Enc)); control_limited($w, [A], F, Adj, P, Pad, Enc, _Str, CL, _I) -> Chars = io_lib:write(A, [{depth, -1}, {encoding, Enc}, {chars_limit, CL}]), term(Chars, F, Adj, P, Pad); @@ -718,7 +718,10 @@ fwrite_g(Fl, F, Adj, P, Pad) when P >= 1 -> end. -%% iolist_to_chars(iolist()) -> io_lib:chars() +iolist_to_chars(Cs, F, CharsLimit) when CharsLimit < 0; CharsLimit >= F -> + iolist_to_chars(Cs); +iolist_to_chars(Cs, _, CharsLimit) -> + limit_iolist_to_chars(Cs, sub(CharsLimit, 3), [], normal). % three dots iolist_to_chars([C|Cs]) when is_integer(C), C >= $\000, C =< $\377 -> [C | iolist_to_chars(Cs)]; @@ -729,12 +732,34 @@ iolist_to_chars([]) -> iolist_to_chars(B) when is_binary(B) -> binary_to_list(B). -%% cdata() :: clist() | cbinary() -%% clist() :: maybe_improper_list(char() | cbinary() | clist(), -%% cbinary() | nil()) -%% cbinary() :: unicode:unicode_binary() | unicode:latin1_binary() +limit_iolist_to_chars(Cs, 0, S, normal) -> + L = limit_iolist_to_chars(Cs, 4, S, final), + case iolist_size(L) of + N when N < 4 -> L; + 4 -> "..." + end; +limit_iolist_to_chars(_Cs, 0, _S, final) -> []; +limit_iolist_to_chars([C|Cs], Limit, S, Mode) when C >= $\000, C =< $\377 -> + [C | limit_iolist_to_chars(Cs, Limit - 1, S, Mode)]; +limit_iolist_to_chars([I|Cs], Limit, S, Mode) -> + limit_iolist_to_chars(I, Limit, [Cs|S], Mode); +limit_iolist_to_chars([], _Limit, [], _Mode) -> + []; +limit_iolist_to_chars([], Limit, [Cs|S], Mode) -> + limit_iolist_to_chars(Cs, Limit, S, Mode); +limit_iolist_to_chars(B, Limit, S, Mode) when is_binary(B) -> + case byte_size(B) of + Sz when Sz > Limit -> + {B1, B2} = split_binary(B, Limit), + [binary_to_list(B1) | limit_iolist_to_chars(B2, 0, S, Mode)]; + Sz -> + [binary_to_list(B) | limit_iolist_to_chars([], Limit-Sz, S, Mode)] + end. -%% cdata_to_chars(cdata()) -> io_lib:chars() +cdata_to_chars(Cs, F, CharsLimit) when CharsLimit < 0; CharsLimit >= F -> + cdata_to_chars(Cs); +cdata_to_chars(Cs, _, CharsLimit) -> + limit_cdata_to_chars(Cs, sub(CharsLimit, 3), normal). % three dots cdata_to_chars([C|Cs]) when is_integer(C), C >= $\000 -> [C | cdata_to_chars(Cs)]; @@ -748,11 +773,25 @@ cdata_to_chars(B) when is_binary(B) -> _ -> binary_to_list(B) end. -limit_string(S, F, CharsLimit) when CharsLimit < 0; CharsLimit >= F -> S; -limit_string(S, _F, CharsLimit) -> - case io_lib:chars_length(S) =< CharsLimit of - true -> S; - false -> [string:slice(S, 0, sub(CharsLimit, 3)), "..."] +limit_cdata_to_chars(Cs, 0, normal) -> + L = limit_cdata_to_chars(Cs, 4, final), + case string:length(L) of + N when N < 4 -> L; + 4 -> "..." + end; +limit_cdata_to_chars(_Cs, 0, final) -> []; +limit_cdata_to_chars(Cs, Limit, Mode) -> + case string:next_grapheme(Cs) of + {error, <<C,Cs1/binary>>} -> + %% This is how ~ts handles Latin1 binaries with option + %% chars_limit. + [C | limit_cdata_to_chars(Cs1, Limit - 1, Mode)]; + {error, [C|Cs1]} -> % not all versions of module string return this + [C | limit_cdata_to_chars(Cs1, Limit - 1, Mode)]; + [] -> + []; + [GC|Cs1] -> + [GC | limit_cdata_to_chars(Cs1, Limit - 1, Mode)] end. limit_field(F, CharsLimit) when CharsLimit < 0; F =:= none -> @@ -762,30 +801,30 @@ limit_field(F, CharsLimit) -> %% string(String, Field, Adjust, Precision, PadChar) -string(S, none, _Adj, none, _Pad) -> S; -string(S, F, Adj, none, Pad) -> - string_field(S, F, Adj, io_lib:chars_length(S), Pad); -string(S, none, _Adj, P, Pad) -> - string_field(S, P, left, io_lib:chars_length(S), Pad); -string(S, F, Adj, P, Pad) when F >= P -> +string(S, none, _Adj, none, _Pad, _Enc) -> S; +string(S, F, Adj, none, Pad, Enc) -> + string_field(S, F, Adj, io_lib:chars_length(S), Pad, Enc); +string(S, none, _Adj, P, Pad, Enc) -> + string_field(S, P, left, io_lib:chars_length(S), Pad, Enc); +string(S, F, Adj, P, Pad, Enc) when F >= P -> N = io_lib:chars_length(S), if F > P -> if N > P -> - adjust(flat_trunc(S, P), chars(Pad, F-P), Adj); + adjust(flat_trunc(S, P, Enc), chars(Pad, F-P), Adj); N < P -> adjust([S|chars(Pad, P-N)], chars(Pad, F-P), Adj); true -> % N == P adjust(S, chars(Pad, F-P), Adj) end; true -> % F == P - string_field(S, F, Adj, N, Pad) + string_field(S, F, Adj, N, Pad, Enc) end. -string_field(S, F, _Adj, N, _Pad) when N > F -> - flat_trunc(S, F); -string_field(S, F, Adj, N, Pad) when N < F -> +string_field(S, F, _Adj, N, _Pad, Enc) when N > F -> + flat_trunc(S, F, Enc); +string_field(S, F, Adj, N, Pad, _Enc) when N < F -> adjust(S, chars(Pad, F-N), Adj); -string_field(S, _, _, _, _) -> % N == F +string_field(S, _, _, _, _, _) -> % N == F S. %% unprefixed_integer(Int, Field, Adjust, Base, PadChar, Lowercase) @@ -837,7 +876,10 @@ adjust(Data, Pad, right) -> [Pad|Data]. %% Flatten and truncate a deep list to at most N elements. -flat_trunc(List, N) when is_integer(N), N >= 0 -> +flat_trunc(List, N, latin1) when is_integer(N), N >= 0 -> + {S, _} = lists:split(N, lists:flatten(List)), + S; +flat_trunc(List, N, unicode) when is_integer(N), N >= 0 -> string:slice(List, 0, N). %% A deep version of lists:duplicate/2 diff --git a/lib/stdlib/src/io_lib_pretty.erl b/lib/stdlib/src/io_lib_pretty.erl index 8f2fd7ea8f..77f02eafe0 100644 --- a/lib/stdlib/src/io_lib_pretty.erl +++ b/lib/stdlib/src/io_lib_pretty.erl @@ -462,7 +462,9 @@ find_upper(Lower, Term, T, Dl, Dd, D, RF, Enc, Str) -> case If of {_, _, _Dots=0, _} -> % even if Len > T If; - {_, Len, _, _} when Len =< T, D1 < D orelse D < 0 -> + {_, _Len=T, _, _} -> % increasing the depth is meaningless + If; + {_, Len, _, _} when Len < T, D1 < D orelse D < 0 -> find_upper(If, Term, T, D1, Dd2, D, RF, Enc, Str); _ -> search_depth(Lower, If, Term, T, Dl, D1, RF, Enc, Str) @@ -720,55 +722,40 @@ printable_list(_L, 1, _T, _Enc) -> false; printable_list(L, _D, T, latin1) when T < 0 -> io_lib:printable_latin1_list(L); -printable_list(L, _D, T, Enc) when T >= 0 -> - case slice(L, tsub(T, 2), Enc) of - false -> - false; - {prefix, Prefix} when Enc =:= latin1 -> - io_lib:printable_latin1_list(Prefix) andalso {true, Prefix}; - {prefix, Prefix} -> - %% Probably an overestimation. - io_lib:printable_list(Prefix) andalso {true, Prefix}; - all when Enc =:= latin1 -> - io_lib:printable_latin1_list(L); +printable_list(L, _D, T, latin1) when T >= 0 -> + N = tsub(T, 2), + case printable_latin1_list(L, N) of all -> - io_lib:printable_list(L) - end; -printable_list(L, _D, T, _Uni) when T < 0-> - io_lib:printable_list(L). - -slice(L, N, latin1) -> - try lists:split(N, L) of - {_, []} -> - all; - {[], _} -> - false; - {L1, _} -> - {prefix, L1} - catch - _:_ -> - all + true; + 0 -> + {L1, _} = lists:split(N, L), + {true, L1}; + _NC -> + false end; -slice(L, N, _Uni) -> +printable_list(L, _D, T, _Unicode) when T >= 0 -> + N = tsub(T, 2), %% Be careful not to traverse more of L than necessary. try string:slice(L, 0, N) of "" -> false; Prefix -> - %% Assume no binaries are introduced by string:slice(). case is_flat(L, lists:flatlength(Prefix)) of true -> case string:equal(Prefix, L) of true -> - all; + io_lib:printable_list(L); false -> - {prefix, Prefix} + io_lib:printable_list(Prefix) + andalso {true, Prefix} end; false -> false end catch _:_ -> false - end. + end; +printable_list(L, _D, T, _Uni) when T < 0-> + io_lib:printable_list(L). is_flat(_L, 0) -> true; @@ -795,6 +782,8 @@ printable_bin0(Bin, D, T, Enc) -> end, printable_bin(Bin, Len, D, Enc). +printable_bin(_Bin, 0, _D, _Enc) -> + false; printable_bin(Bin, Len, D, latin1) -> N = erlang:min(20, Len), L = binary_to_list(Bin, 1, N), @@ -845,7 +834,7 @@ printable_bin1(Bin, Start, Len) -> end. %% -> all | integer() >=0. Adopted from io_lib.erl. -% printable_latin1_list([_ | _], 0) -> 0; +printable_latin1_list([_ | _], 0) -> 0; printable_latin1_list([C | Cs], N) when C >= $\s, C =< $~ -> printable_latin1_list(Cs, N - 1); printable_latin1_list([C | Cs], N) when C >= $\240, C =< $\377 -> diff --git a/lib/stdlib/src/stdlib.app.src b/lib/stdlib/src/stdlib.app.src index 9cd425db9a..ecb514e9f3 100644 --- a/lib/stdlib/src/stdlib.app.src +++ b/lib/stdlib/src/stdlib.app.src @@ -108,7 +108,7 @@ dets]}, {applications, [kernel]}, {env, []}, - {runtime_dependencies, ["sasl-3.0","kernel-6.0","erts-@OTP-15128@","crypto-3.3", + {runtime_dependencies, ["sasl-3.0","kernel-6.0","erts-10.4","crypto-3.3", "compiler-5.0"]} ]}. diff --git a/lib/stdlib/src/stdlib.appup.src b/lib/stdlib/src/stdlib.appup.src index 08612ed17f..0c270e9dd5 100644 --- a/lib/stdlib/src/stdlib.appup.src +++ b/lib/stdlib/src/stdlib.appup.src @@ -19,22 +19,15 @@ %% %% We allow upgrade from, and downgrade to all previous %% versions from the following OTP releases: -%% - OTP 20 %% - OTP 21 +%% - OTP 22 %% %% We also allow upgrade from, and downgrade to all %% versions that have branched off from the above %% stated previous versions. %% {"%VSN%", - [{<<"^3\\.4$">>,[restart_new_emulator]}, - {<<"^3\\.4\\.0(?:\\.[0-9]+)+$">>,[restart_new_emulator]}, - {<<"^3\\.4\\.1(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, - {<<"^3\\.4\\.2(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, - {<<"^3\\.4\\.3(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, - {<<"^3\\.4\\.4(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, - {<<"^3\\.4\\.5(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, - {<<"^3\\.5$">>,[restart_new_emulator]}, + [{<<"^3\\.5$">>,[restart_new_emulator]}, {<<"^3\\.5\\.0(?:\\.[0-9]+)+$">>,[restart_new_emulator]}, {<<"^3\\.5\\.1(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, {<<"^3\\.6$">>,[restart_new_emulator]}, @@ -43,15 +36,13 @@ {<<"^3\\.7\\.0(?:\\.[0-9]+)+$">>,[restart_new_emulator]}, {<<"^3\\.7\\.1(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, {<<"^3\\.8$">>,[restart_new_emulator]}, - {<<"^3\\.8\\.0(?:\\.[0-9]+)+$">>,[restart_new_emulator]}], - [{<<"^3\\.4$">>,[restart_new_emulator]}, - {<<"^3\\.4\\.0(?:\\.[0-9]+)+$">>,[restart_new_emulator]}, - {<<"^3\\.4\\.1(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, - {<<"^3\\.4\\.2(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, - {<<"^3\\.4\\.3(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, - {<<"^3\\.4\\.4(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, - {<<"^3\\.4\\.5(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, - {<<"^3\\.5$">>,[restart_new_emulator]}, + {<<"^3\\.8\\.0(?:\\.[0-9]+)+$">>,[restart_new_emulator]}, + {<<"^3\\.8\\.1(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, + {<<"^3\\.8\\.2(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, + {<<"^3\\.9$">>,[restart_new_emulator]}, + {<<"^3\\.9\\.0(?:\\.[0-9]+)+$">>,[restart_new_emulator]}, + {<<"^3\\.9\\.1(?:\\.[0-9]+)*$">>,[restart_new_emulator]}], + [{<<"^3\\.5$">>,[restart_new_emulator]}, {<<"^3\\.5\\.0(?:\\.[0-9]+)+$">>,[restart_new_emulator]}, {<<"^3\\.5\\.1(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, {<<"^3\\.6$">>,[restart_new_emulator]}, @@ -60,4 +51,9 @@ {<<"^3\\.7\\.0(?:\\.[0-9]+)+$">>,[restart_new_emulator]}, {<<"^3\\.7\\.1(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, {<<"^3\\.8$">>,[restart_new_emulator]}, - {<<"^3\\.8\\.0(?:\\.[0-9]+)+$">>,[restart_new_emulator]}]}. + {<<"^3\\.8\\.0(?:\\.[0-9]+)+$">>,[restart_new_emulator]}, + {<<"^3\\.8\\.1(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, + {<<"^3\\.8\\.2(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, + {<<"^3\\.9$">>,[restart_new_emulator]}, + {<<"^3\\.9\\.0(?:\\.[0-9]+)+$">>,[restart_new_emulator]}, + {<<"^3\\.9\\.1(?:\\.[0-9]+)*$">>,[restart_new_emulator]}]}. diff --git a/lib/stdlib/src/string.erl b/lib/stdlib/src/string.erl index 1f8bdc5432..a418754caf 100644 --- a/lib/stdlib/src/string.erl +++ b/lib/stdlib/src/string.erl @@ -128,7 +128,8 @@ length(CD) -> to_graphemes(CD0) -> case unicode_util:gc(CD0) of [GC|CD] -> [GC|to_graphemes(CD)]; - [] -> [] + [] -> []; + {error, Err} -> error({badarg, Err}) end. %% Compare two strings return boolean, assumes that the input are @@ -332,7 +333,10 @@ uppercase(<<CP1/utf8, Rest/binary>>=Orig) -> catch unchanged -> Orig end; uppercase(<<>>) -> - <<>>. + <<>>; +uppercase(Bin) -> + error({badarg, Bin}). + %% Lowercase all chars in Str -spec lowercase(String::unicode:chardata()) -> unicode:chardata(). @@ -346,7 +350,10 @@ lowercase(<<CP1/utf8, Rest/binary>>=Orig) -> catch unchanged -> Orig end; lowercase(<<>>) -> - <<>>. + <<>>; +lowercase(Bin) -> + error({badarg, Bin}). + %% Make a titlecase of the first char in Str -spec titlecase(String::unicode:chardata()) -> unicode:chardata(). @@ -375,7 +382,9 @@ casefold(<<CP1/utf8, Rest/binary>>=Orig) -> catch unchanged -> Orig end; casefold(<<>>) -> - <<>>. + <<>>; +casefold(Bin) -> + error({badarg, Bin}). -spec to_integer(String) -> {Int, Rest} | {'error', Reason} when String :: unicode:chardata(), @@ -544,7 +553,8 @@ length_1([CP1|[CP2|_]=Cont], N) when ?ASCII_LIST(CP1,CP2) -> length_1(Str, N) -> case unicode_util:gc(Str) of [] -> N; - [_|Rest] -> length_1(Rest, N+1) + [_|Rest] -> length_1(Rest, N+1); + {error, Err} -> error({badarg, Err}) end. length_b(<<CP2/utf8, Rest/binary>>, CP1, N) @@ -554,7 +564,8 @@ length_b(Bin0, CP1, N) -> [_|Bin1] = unicode_util:gc([CP1|Bin0]), case unicode_util:cp(Bin1) of [] -> N+1; - [CP3|Bin] -> length_b(Bin, CP3, N+1) + [CP3|Bin] -> length_b(Bin, CP3, N+1); + {error, Err} -> error({badarg, Err}) end. equal_1([A|AR], [B|BR]) when is_integer(A), is_integer(B) -> @@ -599,7 +610,8 @@ reverse_1([CP1|[CP2|_]=Cont], Acc) when ?ASCII_LIST(CP1,CP2) -> reverse_1(CD, Acc) -> case unicode_util:gc(CD) of [GC|Rest] -> reverse_1(Rest, [GC|Acc]); - [] -> Acc + [] -> Acc; + {error, Err} -> error({badarg, Err}) end. reverse_b(<<CP2/utf8, Rest/binary>>, CP1, Acc) @@ -609,7 +621,8 @@ reverse_b(Bin0, CP1, Acc) -> [GC|Bin1] = unicode_util:gc([CP1|Bin0]), case unicode_util:cp(Bin1) of [] -> [GC|Acc]; - [CP3|Bin] -> reverse_b(Bin, CP3, [GC|Acc]) + [CP3|Bin] -> reverse_b(Bin, CP3, [GC|Acc]); + {error, Err} -> error({badarg, Err}) end. slice_l0(<<CP1/utf8, Bin/binary>>, N) when N > 0 -> @@ -622,7 +635,8 @@ slice_l([CP1|[CP2|_]=Cont], N) when ?ASCII_LIST(CP1,CP2),N > 0 -> slice_l(CD, N) when N > 0 -> case unicode_util:gc(CD) of [_|Cont] -> slice_l(Cont, N-1); - [] -> [] + [] -> []; + {error, Err} -> error({badarg, Err}) end; slice_l(Cont, 0) -> Cont. @@ -634,7 +648,8 @@ slice_lb(Bin, CP1, N) -> if N > 1 -> case unicode_util:cp(Rest) of [CP2|Cont] -> slice_lb(Cont, CP2, N-1); - [] -> <<>> + [] -> <<>>; + {error, Err} -> error({badarg, Err}) end; N =:= 1 -> Rest @@ -647,7 +662,10 @@ slice_trail(Orig, N) when is_binary(Orig) -> Sz = byte_size(Orig) - Length, <<Keep:Sz/binary, _/binary>> = Orig, Keep; - _ -> <<>> + <<_, _/binary>> when N > 0 -> + error({badarg, Orig}); + _ -> + <<>> end; slice_trail(CD, N) when is_list(CD) -> slice_list(CD, N). @@ -657,7 +675,8 @@ slice_list([CP1|[CP2|_]=Cont], N) when ?ASCII_LIST(CP1,CP2),N > 0 -> slice_list(CD, N) when N > 0 -> case unicode_util:gc(CD) of [GC|Cont] -> append(GC, slice_list(Cont, N-1)); - [] -> [] + [] -> []; + {error, Err} -> error({badarg, Err}) end; slice_list(_, 0) -> []. @@ -668,7 +687,8 @@ slice_bin(CD, CP1, N) when N > 0 -> [_|Bin] = unicode_util:gc([CP1|CD]), case unicode_util:cp(Bin) of [CP2|Cont] -> slice_bin(Cont, CP2, N-1); - [] -> 0 + [] -> 0; + {error, Err} -> error({badarg, Err}) end; slice_bin(CD, CP1, 0) -> byte_size(CD)+byte_size(<<CP1/utf8>>). @@ -703,14 +723,18 @@ uppercase_bin(CP1, Bin, Changed) -> [] when Changed -> [CP1]; [] -> - throw(unchanged) + throw(unchanged); + {error, Err} -> + error({badarg, Err}) end; [Char|CPs] -> case unicode_util:cp(CPs) of [Next|Rest] -> [Char|uppercase_bin(Next, Rest, true)]; [] -> - [Char] + [Char]; + {error, Err} -> + error({badarg, Err}) end end. @@ -744,14 +768,18 @@ lowercase_bin(CP1, Bin, Changed) -> [] when Changed -> [CP1]; [] -> - throw(unchanged) + throw(unchanged); + {error, Err} -> + error({badarg, Err}) end; [Char|CPs] -> case unicode_util:cp(CPs) of [Next|Rest] -> [Char|lowercase_bin(Next, Rest, true)]; [] -> - [Char] + [Char]; + {error, Err} -> + error({badarg, Err}) end end. @@ -785,14 +813,18 @@ casefold_bin(CP1, Bin, Changed) -> [] when Changed -> [CP1]; [] -> - throw(unchanged) + throw(unchanged); + {error, Err} -> + error({badarg, Err}) end; [Char|CPs] -> case unicode_util:cp(CPs) of [Next|Rest] -> [Char|casefold_bin(Next, Rest, true)]; [] -> - [Char] + [Char]; + {error, Err} -> + error({badarg, Err}) end end. @@ -1634,7 +1666,9 @@ bin_search_inv_1(<<CP1/utf8, BinRest/binary>>=Bin0, Cont, Sep) -> bin_search_inv_1(<<>>, Cont, _Sep) -> {nomatch, Cont}; bin_search_inv_1([], Cont, _Sep) -> - {nomatch, Cont}. + {nomatch, Cont}; +bin_search_inv_1(Bin, _, _) -> + error({badarg, Bin}). bin_search_inv_n(<<CP1/utf8, BinRest/binary>>=Bin0, Cont, Seps) -> @@ -1666,7 +1700,9 @@ bin_search_inv_n(<<CP1/utf8, BinRest/binary>>=Bin0, Cont, Seps) -> bin_search_inv_n(<<>>, Cont, _Sep) -> {nomatch, Cont}; bin_search_inv_n([], Cont, _Sep) -> - {nomatch, Cont}. + {nomatch, Cont}; +bin_search_inv_n(Bin, _, _) -> + error({badarg, Bin}). bin_search_str(Bin0, Start, [], SearchCPs) -> Compiled = binary:compile_pattern(unicode:characters_to_binary(SearchCPs)), |