diff options
Diffstat (limited to 'lib/stdlib/src')
| -rw-r--r-- | lib/stdlib/src/epp.erl | 5 | ||||
| -rw-r--r-- | lib/stdlib/src/erl_lint.erl | 7 | ||||
| -rw-r--r-- | lib/stdlib/src/erl_pp.erl | 38 | ||||
| -rw-r--r-- | lib/stdlib/src/erl_scan.erl | 6 | ||||
| -rw-r--r-- | lib/stdlib/src/escript.erl | 12 | ||||
| -rw-r--r-- | lib/stdlib/src/ets.erl | 4 | ||||
| -rw-r--r-- | lib/stdlib/src/filename.erl | 4 | ||||
| -rw-r--r-- | lib/stdlib/src/io_lib_format.erl | 10 | ||||
| -rw-r--r-- | lib/stdlib/src/lib.erl | 2 | ||||
| -rw-r--r-- | lib/stdlib/src/otp_internal.erl | 48 | ||||
| -rw-r--r-- | lib/stdlib/src/pool.erl | 6 | ||||
| -rw-r--r-- | lib/stdlib/src/slave.erl | 2 | ||||
| -rw-r--r-- | lib/stdlib/src/string.erl | 10 | 
13 files changed, 104 insertions, 50 deletions
| diff --git a/lib/stdlib/src/epp.erl b/lib/stdlib/src/epp.erl index 31d0d499e3..00e6a10d8a 100644 --- a/lib/stdlib/src/epp.erl +++ b/lib/stdlib/src/epp.erl @@ -479,7 +479,7 @@ com_enc(_B, _Fun, _N, L, Ps) ->      com_enc_end([L | Ps]).  com_enc_end(Ps0) -> -    Ps = lists:reverse([lists:reverse(string:to_lower(P)) || P <- Ps0]), +    Ps = lists:reverse([lists:reverse(lowercase(P)) || P <- Ps0]),      com_encoding(Ps).  com_encoding(["latin","1"|_]) -> @@ -489,6 +489,9 @@ com_encoding(["utf","8"|_]) ->  com_encoding(_) ->      throw(no). % Don't try any further +lowercase(S) -> +    unicode:characters_to_list(string:lowercase(S)). +  normalize_typed_record_fields([]) ->      {typed, []};  normalize_typed_record_fields(Fields) -> diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index 9cd4727dc3..f58cb35cea 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -3910,10 +3910,9 @@ check_format_string(Fmt) ->      extract_sequences(Fmt, []).  extract_sequences(Fmt, Need0) -> -    case string:chr(Fmt, $~) of -        0 -> {ok,lists:reverse(Need0)};         %That's it -        Pos -> -            Fmt1 = string:substr(Fmt, Pos+1),   %Skip ~ +    case string:find(Fmt, [$~]) of +        nomatch -> {ok,lists:reverse(Need0)};         %That's it +        [$~|Fmt1] ->              case extract_sequence(1, Fmt1, Need0) of                  {ok,Need1,Rest} -> extract_sequences(Rest, Need1);                  Error -> Error diff --git a/lib/stdlib/src/erl_pp.erl b/lib/stdlib/src/erl_pp.erl index b0064aadb8..367dbefb82 100644 --- a/lib/stdlib/src/erl_pp.erl +++ b/lib/stdlib/src/erl_pp.erl @@ -237,13 +237,20 @@ lform({attribute,Line,Name,Arg}, Opts) ->  lform({function,Line,Name,Arity,Clauses}, Opts) ->      lfunction({function,Line,Name,Arity,Clauses}, Opts);  %% These are specials to make it easier for the compiler. -lform({error,E}, _Opts) -> -    leaf(format("~p\n", [{error,E}])); -lform({warning,W}, _Opts) -> -    leaf(format("~p\n", [{warning,W}])); +lform({error,_}=E, Opts) -> +    message(E, Opts); +lform({warning,_}=W, Opts) -> +    message(W, Opts);  lform({eof,_Line}, _Opts) ->      $\n. +message(M, #options{encoding = Encoding}) -> +    F = case Encoding of +            latin1 -> "~p\n"; +            unicode -> "~tp\n" +        end, +    leaf(format(F, [M])). +  lattribute({attribute,_Line,type,Type}, Opts) ->      [typeattr(type, Type, Opts),leaf(".\n")];  lattribute({attribute,_Line,opaque,Type}, Opts) -> @@ -902,7 +909,7 @@ maybe_paren(_P, _Prec, Expr) ->      Expr.  leaf(S) -> -    {leaf,chars_size(S),S}. +    {leaf,string:length(S),S}.  %%% Do the formatting. Currently nothing fancy. Could probably have  %%% done it in one single pass. @@ -962,7 +969,7 @@ f({seq,Before,After,Sep,LItems}, I0, ST, WT, PP) ->      Sizes = BSizeL ++ SizeL,      NSepChars = if                      is_list(Sep), Sep =/= [] -> -                        erlang:max(0, length(CharsL)-1); +                        erlang:max(0, length(CharsL)-1); % not string:length                      true ->                          0                  end, @@ -1118,7 +1125,7 @@ incr(I, Incr) ->      I+Incr.  indentation(E, I) when I < 0 -> -    chars_size(E); +    string:length(E);  indentation(E, I0) ->      I = io_lib_format:indentation(E, I0),      case has_nl(E) of @@ -1155,19 +1162,19 @@ write_a_string(S, I, PP) ->  write_a_string([], _N, _Len, _PP) ->      [];  write_a_string(S, N, Len, PP) -> -    SS = string:sub_string(S, 1, N), +    SS = string:slice(S, 0, N),      Sl = write_string(SS, PP), -    case (chars_size(Sl) > Len) and (N > ?MIN_SUBSTRING) of +    case (string:length(Sl) > Len) and (N > ?MIN_SUBSTRING) of          true ->              write_a_string(S, N-1, Len, PP);          false ->              [flat_leaf(Sl) | -             write_a_string(lists:nthtail(length(SS), S), Len, Len, PP)] +             write_a_string(string:slice(S, string:length(SS)), Len, Len, PP)]      end.  flat_leaf(S) ->      L = lists:flatten(S), -    {leaf,length(L),L}. +    {leaf,string:length(L),L}.  write_value(V, PP) ->      (PP#pp.value_fun)(V). @@ -1188,15 +1195,6 @@ write_char(C, PP) ->  a0() ->      erl_anno:new(0). -chars_size([C | Es]) when is_integer(C) -> -    1 + chars_size(Es); -chars_size([E | Es]) -> -    chars_size(E) + chars_size(Es); -chars_size([]) -> -    0; -chars_size(B) when is_binary(B) -> -    byte_size(B). -  -define(N_SPACES, 30).  spacetab() -> diff --git a/lib/stdlib/src/erl_scan.erl b/lib/stdlib/src/erl_scan.erl index 47223b129c..4774c4bf19 100644 --- a/lib/stdlib/src/erl_scan.erl +++ b/lib/stdlib/src/erl_scan.erl @@ -1,7 +1,7 @@  %%  %% %CopyrightBegin%  %% -%% Copyright Ericsson AB 1996-2015. 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. @@ -752,7 +752,7 @@ scan_string(Cs, St, Line, Col, Toks, {Wcs,Str,Line0,Col0}) ->          {char_error,Ncs,Error,Nline,Ncol,EndCol} ->              scan_error(Error, Nline, Ncol, Nline, EndCol, Ncs);          {error,Nline,Ncol,Nwcs,Ncs} -> -            Estr = string:substr(Nwcs, 1, 16), % Expanded escape chars. +            Estr = string:slice(Nwcs, 0, 16), % Expanded escape chars.              scan_error({string,$\",Estr}, Line0, Col0, Nline, Ncol, Ncs); %"          {Ncs,Nline,Ncol,Nstr,Nwcs} ->              Anno = anno(Line0, Col0, St, Nstr), @@ -767,7 +767,7 @@ scan_qatom(Cs, St, Line, Col, Toks, {Wcs,Str,Line0,Col0}) ->          {char_error,Ncs,Error,Nline,Ncol,EndCol} ->              scan_error(Error, Nline, Ncol, Nline, EndCol, Ncs);          {error,Nline,Ncol,Nwcs,Ncs} -> -            Estr = string:substr(Nwcs, 1, 16), % Expanded escape chars. +            Estr = string:slice(Nwcs, 0, 16), % Expanded escape chars.              scan_error({string,$\',Estr}, Line0, Col0, Nline, Ncol, Ncs); %'          {Ncs,Nline,Ncol,Nstr,Nwcs} ->              case catch list_to_atom(Nwcs) of diff --git a/lib/stdlib/src/escript.erl b/lib/stdlib/src/escript.erl index 2b9d8ff65b..132f8efbbe 100644 --- a/lib/stdlib/src/escript.erl +++ b/lib/stdlib/src/escript.erl @@ -224,8 +224,8 @@ return_sections(S, Bin) ->  normalize_section(Name, undefined) ->      {Name, undefined};  normalize_section(shebang, "#!" ++ Chars) -> -    Chopped = string:strip(Chars, right, $\n), -    Stripped = string:strip(Chopped, both), +    Chopped = string:trim(Chars, trailing, "$\n"), +    Stripped = string:trim(Chopped, both),      if  	Stripped =:= ?SHEBANG ->  	    {shebang, default}; @@ -233,8 +233,8 @@ normalize_section(shebang, "#!" ++ Chars) ->  	    {shebang, Stripped}      end;  normalize_section(comment, Chars) -> -    Chopped = string:strip(Chars, right, $\n), -    Stripped = string:strip(string:strip(Chopped, left, $%), both), +    Chopped = string:trim(Chars, trailing, "$\n"), +    Stripped = string:trim(string:trim(Chopped, leading, "$%"), both),      if  	Stripped =:= ?COMMENT ->  	    {comment, default}; @@ -242,8 +242,8 @@ normalize_section(comment, Chars) ->  	    {comment, Stripped}      end;  normalize_section(emu_args, "%%!" ++ Chars) -> -    Chopped = string:strip(Chars, right, $\n), -    Stripped = string:strip(Chopped, both), +    Chopped = string:trim(Chars, trailing, "$\n"), +    Stripped = string:trim(Chopped, both),      {emu_args, Stripped};  normalize_section(Name, Chars) ->      {Name, Chars}. diff --git a/lib/stdlib/src/ets.erl b/lib/stdlib/src/ets.erl index b5d3cd3c8d..4858c8d13c 100644 --- a/lib/stdlib/src/ets.erl +++ b/lib/stdlib/src/ets.erl @@ -1717,7 +1717,7 @@ get_line(P, Default) ->  line_string(Binary) when is_binary(Binary) -> unicode:characters_to_list(Binary);  line_string(Other) -> Other. -nonl(S) -> string:strip(S, right, $\n). +nonl(S) -> string:trim(S, trailing, "$\n").  print_number(Tab, Key, Num) ->      Os = ets:lookup(Tab, Key), @@ -1746,7 +1746,7 @@ do_display_item(_Height, Width, I, Opos)  ->      L = to_string(I),      L2 = if  	     length(L) > Width - 8 -> -                 string:substr(L, 1, Width-13) ++ "  ..."; +                 string:slice(L, 0, Width-13) ++ "  ...";  	     true ->  		 L  	 end, diff --git a/lib/stdlib/src/filename.erl b/lib/stdlib/src/filename.erl index 9bf4290916..63cfeae57b 100644 --- a/lib/stdlib/src/filename.erl +++ b/lib/stdlib/src/filename.erl @@ -1036,10 +1036,10 @@ basedir_linux(Type) ->          user_log    -> getenv("XDG_CACHE_HOME", ?basedir_linux_user_log,   true);          site_data   ->              Base = getenv("XDG_DATA_DIRS",?basedir_linux_site_data,false), -            string:tokens(Base,":"); +            string:lexemes(Base, ":");          site_config ->              Base = getenv("XDG_CONFIG_DIRS",?basedir_linux_site_config,false), -            string:tokens(Base,":") +            string:lexemes(Base, ":")      end.  -define(basedir_darwin_user_data,   "Library/Application Support"). diff --git a/lib/stdlib/src/io_lib_format.erl b/lib/stdlib/src/io_lib_format.erl index 4b2d15c8b3..e345810ca0 100644 --- a/lib/stdlib/src/io_lib_format.erl +++ b/lib/stdlib/src/io_lib_format.erl @@ -380,7 +380,7 @@ float_e(_Fl, {Ds,E}, P) ->  	{Fs,false} -> [Fs|float_exp(E-1)]      end. -%% float_man([Digit], Icount, Dcount) -> {[Chars],CarryFlag}. +%% float_man([Digit], Icount, Dcount) -> {[Char],CarryFlag}.  %%  Generate the characters in the mantissa from the digits with Icount  %%  characters before the '.' and Dcount decimals. Handle carry and let  %%  caller decide what to do at top. @@ -395,7 +395,7 @@ float_man([D|Ds], I, Dc) ->  	{Cs,false} -> {[D|Cs],false}      end;  float_man([], I, Dc) ->				%Pad with 0's -    {string:chars($0, I, [$.|string:chars($0, Dc)]),false}. +    {lists:duplicate(I, $0) ++ [$.|lists:duplicate(Dc, $0)],false}.  float_man([D|_], 0) when D >= $5 -> {[],true};  float_man([_|_], 0) -> {[],false}; @@ -405,7 +405,7 @@ float_man([D|Ds], Dc) ->  	{Cs,true} -> {[D+1|Cs],false};   	{Cs,false} -> {[D|Cs],false}      end; -float_man([], Dc) -> {string:chars($0, Dc),false}.	%Pad with 0's +float_man([], Dc) -> {lists:duplicate(Dc, $0),false}.	%Pad with 0's  %% float_exp(Exponent) -> [Char].  %%  Generate the exponent of a floating point number. Always include sign. @@ -429,7 +429,7 @@ fwrite_f(Fl, F, Adj, P, Pad) when P >= 1 ->  float_f(Fl, Fd, P) when Fl < 0.0 ->      [$-|float_f(-Fl, Fd, P)];  float_f(Fl, {Ds,E}, P) when E =< 0 -> -    float_f(Fl, {string:chars($0, -E+1, Ds),1}, P);	%Prepend enough 0's +    float_f(Fl, {lists:duplicate(-E+1, $0)++Ds,1}, P);	%Prepend enough 0's  float_f(_Fl, {Ds,E}, P) ->      case float_man(Ds, E, P) of  	{Fs,true} -> "1" ++ Fs;			%Handle carry @@ -751,7 +751,7 @@ adjust(Data, Pad, right) -> [Pad|Data].  flat_trunc(List, N) when is_integer(N), N >= 0 ->      string:slice(List, 0, N). -%% A deep version of string:chars/2,3 +%% A deep version of lists:duplicate/2  chars(_C, 0) ->      []; diff --git a/lib/stdlib/src/lib.erl b/lib/stdlib/src/lib.erl index c6eb0d7915..a7980cc294 100644 --- a/lib/stdlib/src/lib.erl +++ b/lib/stdlib/src/lib.erl @@ -646,7 +646,7 @@ pp_arguments(PF, As, I, Enc) ->              Ll = length(L),              A = list_to_atom(lists:duplicate(Ll, $a)),              S0 = unicode:characters_to_list(PF([A | T], I+1), Enc), -            brackets_to_parens([$[,L,string:sub_string(S0, 2+Ll)], Enc); +            brackets_to_parens([$[,L,string:slice(S0, 1+Ll)], Enc);          _ ->               brackets_to_parens(PF(As, I+1), Enc)      end. diff --git a/lib/stdlib/src/otp_internal.erl b/lib/stdlib/src/otp_internal.erl index c59db903dc..122b476ddb 100644 --- a/lib/stdlib/src/otp_internal.erl +++ b/lib/stdlib/src/otp_internal.erl @@ -466,8 +466,6 @@ obsolete_1(inviso, _, _) ->      {removed,"the inviso application was removed in R16"};  %% Added in R15B01. -obsolete_1(gs, _, _) -> -    {removed,"the gs application has been removed; use the wx application instead"};  obsolete_1(ssh, sign_data, 2) ->      {removed,"removed in R16A; use public_key:pem_decode/1, public_key:pem_entry_decode/1 "       "and public_key:sign/3 instead"}; @@ -611,6 +609,52 @@ obsolete_1(filename, find_src, 2) ->  obsolete_1(erlang, hash, 2) ->      {removed, {erlang, phash2, 2}, "20.0"}; +%% Added in OTP-21 +obsolete_1(string, len, 1) -> +    {deprecated, "deprecated; use string:length/3 instead"}; +obsolete_1(string, concat, 2) -> +    {deprecated, "deprecated; use [Str1,Str2] instead"}; +obsolete_1(string, str, 2) -> +    {deprecated, "deprecated; use string:find/2 instead"}; +obsolete_1(string, rstr, 2) -> +    {deprecated, "deprecated; use string:find/3 instead"}; +obsolete_1(string, chr, 2) -> +    {deprecated, "deprecated; use string:find/2 instead"}; +obsolete_1(string, rchr, 2) -> +    {deprecated, "deprecated; use string:find/3 instead"}; +obsolete_1(string, span, 2) -> +    {deprecated, "deprecated; use string:take/2 instead"}; +obsolete_1(string, cspan, 2) -> +    {deprecated, "deprecated; use string:take/3 instead"}; +obsolete_1(string, substr, _) -> +    {deprecated, "deprecated; use string:slice/3 instead"}; +obsolete_1(string, tokens, 2) -> +    {deprecated, "deprecated; use string:lexemes/2 instead"}; +obsolete_1(string, chars, _) -> +    {deprecated, "deprecated; use lists:duplicate/2 instead"}; +obsolete_1(string, copies, _) -> +    {deprecated, "deprecated; use lists:duplicate/2 instead"}; +obsolete_1(string, words, _) -> +    {deprecated, "deprecated; use string:lexemes/2 instead"}; +obsolete_1(string, strip, _) -> +    {deprecated, "deprecated; use string:trim/3 instead"}; +obsolete_1(string, sub_word, _) -> +    {deprecated, "deprecated; use string:nth_lexeme/3 instead"}; +obsolete_1(string, sub_string, _) -> +    {deprecated, "deprecated; use string:slice/3 instead"}; +obsolete_1(string, left, _) -> +    {deprecated, "deprecated; use string:pad/3 instead"}; +obsolete_1(string, right, _) -> +    {deprecated, "deprecated; use string:pad/3 instead"}; +obsolete_1(string, centre, _) -> +    {deprecated, "deprecated; use string:pad/3 instead"}; +obsolete_1(string, join, _) -> +    {deprecated, "deprecated; use lists:join/2 instead"}; +obsolete_1(string, to_upper, _) -> +    {deprecated, "deprecated; use string:uppercase/1 or string:titlecase/1 instead"}; +obsolete_1(string, to_lower, _) -> +    {deprecated, "deprecated; use string:lowercase/1 or string:casefold/1 instead"}; +  %% not obsolete  obsolete_1(_, _, _) -> diff --git a/lib/stdlib/src/pool.erl b/lib/stdlib/src/pool.erl index 05950a1d7c..b12ff205b1 100644 --- a/lib/stdlib/src/pool.erl +++ b/lib/stdlib/src/pool.erl @@ -25,7 +25,7 @@  %% with the least load !!!!  %% This function is callable from any node including the master  %% That is part of the pool -%% nodes are scheduled on a per usgae basis and per load basis, +%% nodes are scheduled on a per usage basis and per load basis,  %% Whenever we use a node, we put at the end of the queue, and whenever  %% a node report a change in load, we insert it accordingly @@ -197,7 +197,7 @@ pure_insert({Load,Node},[{L,N}|Tail]) when Load < L ->  pure_insert(L,[H|T]) -> [H|pure_insert(L,T)].  %% Really should not measure the contributions from -%% the back ground processes here .... which we do :-( +%% the background processes here .... which we do :-(  %% We don't have to monitor the master, since we're slaves anyway  statistic_collector() -> @@ -213,7 +213,7 @@ statistic_collector(I) ->  	    stat_loop(M, 999999)      end. -%% Do not tell the master about our load if it has not  changed +%% Do not tell the master about our load if it has not changed  stat_loop(M, Old) ->      sleep(2000), diff --git a/lib/stdlib/src/slave.erl b/lib/stdlib/src/slave.erl index d7cf6386f5..b3f3206d67 100644 --- a/lib/stdlib/src/slave.erl +++ b/lib/stdlib/src/slave.erl @@ -320,7 +320,7 @@ mk_cmd(Host, Name, Args, Waiter, Prog0) ->  %% emulator and flags as the test node. The return from lib:progname()  %% could then typically be '/<full_path_to>/cerl -gcov').  quote_progname(Progname) -> -    do_quote_progname(string:tokens(to_list(Progname)," ")). +    do_quote_progname(string:lexemes(to_list(Progname)," ")).  do_quote_progname([Prog]) ->      "\""++Prog++"\""; diff --git a/lib/stdlib/src/string.erl b/lib/stdlib/src/string.erl index 4972da297d..5a4d2df2a6 100644 --- a/lib/stdlib/src/string.erl +++ b/lib/stdlib/src/string.erl @@ -87,6 +87,16 @@  %%% May be removed  -export([list_to_float/1, list_to_integer/1]). +-deprecated([{len,1},{concat,2}, +             {str,2},{chr,2},{rchr,2},{rstr,2}, +             {span,2},{cspan,2},{substr,'_'},{tokens,2}, +             {chars,'_'}, +             {copies,2},{words,'_'},{strip,'_'}, +             {sub_word,'_'},{left,'_'},{right,'_'}, +             {sub_string,'_'},{centre,'_'},{join,2}, +             {to_upper,1}, {to_lower,1} +            ]). +  %% Uses bifs: string:list_to_float/1 and string:list_to_integer/1  -spec list_to_float(String) -> {Float, Rest} | {'error', Reason} when        String :: string(), | 
