diff options
Diffstat (limited to 'lib/stdlib/src')
| -rw-r--r-- | lib/stdlib/src/beam_lib.erl | 3 | ||||
| -rw-r--r-- | lib/stdlib/src/binary.erl | 28 | ||||
| -rw-r--r-- | lib/stdlib/src/epp.erl | 18 | ||||
| -rw-r--r-- | lib/stdlib/src/ets.erl | 11 | ||||
| -rw-r--r-- | lib/stdlib/src/string.erl | 8 | ||||
| -rw-r--r-- | lib/stdlib/src/uri_string.erl | 65 | 
6 files changed, 93 insertions, 40 deletions
| diff --git a/lib/stdlib/src/beam_lib.erl b/lib/stdlib/src/beam_lib.erl index 06c15fceda..24349c74e8 100644 --- a/lib/stdlib/src/beam_lib.erl +++ b/lib/stdlib/src/beam_lib.erl @@ -148,7 +148,8 @@ chunks(File, Chunks, Options) ->      try read_chunk_data(File, Chunks, Options)      catch Error -> Error end. --spec all_chunks(beam()) -> {'ok', 'beam_lib', [{chunkid(), dataB()}]}. +-spec all_chunks(beam()) -> +           {'ok', 'beam_lib', [{chunkid(), dataB()}]} | {'error', 'beam_lib', info_rsn()}.  all_chunks(File) ->      read_all_chunks(File). diff --git a/lib/stdlib/src/binary.erl b/lib/stdlib/src/binary.erl index 6a64133b45..7d0e42489e 100644 --- a/lib/stdlib/src/binary.erl +++ b/lib/stdlib/src/binary.erl @@ -47,23 +47,39 @@ at(_, _) ->  -spec bin_to_list(Subject) -> [byte()] when        Subject :: binary(). -bin_to_list(_) -> -    erlang:nif_error(undef). +bin_to_list(Subject) -> +    binary_to_list(Subject).  -spec bin_to_list(Subject, PosLen) -> [byte()] when        Subject :: binary(),        PosLen :: part(). -bin_to_list(_, _) -> -    erlang:nif_error(undef). +bin_to_list(Subject, {Pos, Len}) -> +    bin_to_list(Subject, Pos, Len); +bin_to_list(_Subject, _BadArg) -> +    erlang:error(badarg).  -spec bin_to_list(Subject, Pos, Len) -> [byte()] when        Subject :: binary(),        Pos :: non_neg_integer(),        Len :: integer(). -bin_to_list(_, _, _) -> -    erlang:nif_error(undef). +bin_to_list(Subject, Pos, Len) when not is_binary(Subject); +                                    not is_integer(Pos); +                                    not is_integer(Len) -> +    %% binary_to_list/3 allows bitstrings as long as the slice fits, and we +    %% want to badarg when Pos/Len aren't integers instead of raising badarith +    %% when adjusting args for binary_to_list/3. +    erlang:error(badarg); +bin_to_list(Subject, Pos, 0) when Pos >= 0, Pos =< byte_size(Subject) -> +    %% binary_to_list/3 doesn't handle this case. +    []; +bin_to_list(_Subject, _Pos, 0) -> +    erlang:error(badarg); +bin_to_list(Subject, Pos, Len) when Len < 0 -> +    bin_to_list(Subject, Pos + Len, -Len); +bin_to_list(Subject, Pos, Len) when Len > 0 -> +    binary_to_list(Subject, Pos + 1, Pos + Len).  -spec compile_pattern(Pattern) -> cp() when        Pattern :: binary() | [binary()]. diff --git a/lib/stdlib/src/epp.erl b/lib/stdlib/src/epp.erl index 00e6a10d8a..77cc88eb08 100644 --- a/lib/stdlib/src/epp.erl +++ b/lib/stdlib/src/epp.erl @@ -1,7 +1,7 @@  %%  %% %CopyrightBegin%  %% -%% Copyright Ericsson AB 1996-2017. All Rights Reserved. +%% Copyright Ericsson AB 1996-2018. 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. @@ -1197,21 +1197,21 @@ skip_else(_Else, From, St, Sis) ->  %% macro_expansion(Tokens, Anno)  %%  Extract the macro parameters and the expansion from a macro definition. -macro_pars([{')',_Lp}, {',',Ld}|Ex], Args) -> -    {ok, {lists:reverse(Args), macro_expansion(Ex, Ld)}}; -macro_pars([{var,_,Name}, {')',_Lp}, {',',Ld}|Ex], Args) -> +macro_pars([{')',_Lp}, {',',_Ld}=Comma|Ex], Args) -> +    {ok, {lists:reverse(Args), macro_expansion(Ex, Comma)}}; +macro_pars([{var,_,Name}, {')',_Lp}, {',',_Ld}=Comma|Ex], Args) ->      false = lists:member(Name, Args),		%Prolog is nice -    {ok, {lists:reverse([Name|Args]), macro_expansion(Ex, Ld)}}; +    {ok, {lists:reverse([Name|Args]), macro_expansion(Ex, Comma)}};  macro_pars([{var,_L,Name}, {',',_}|Ts], Args) ->      false = lists:member(Name, Args),      macro_pars(Ts, [Name|Args]). -macro_expansion([{')',_Lp},{dot,_Ld}], _Anno0) -> []; -macro_expansion([{dot,_}=Dot], _Anno0) -> +macro_expansion([{')',_Lp},{dot,_Ld}], _T0) -> []; +macro_expansion([{dot,_}=Dot], _T0) ->      throw({error,loc(Dot),missing_parenthesis}); -macro_expansion([T|Ts], _Anno0) -> +macro_expansion([T|Ts], _T0) ->      [T|macro_expansion(Ts, T)]; -macro_expansion([], Anno0) -> throw({error,loc(Anno0),premature_end}). +macro_expansion([], T0) -> throw({error,loc(T0),premature_end}).  %% expand_macros(Tokens, St)  %% expand_macro(Tokens, MacroToken, RestTokens) diff --git a/lib/stdlib/src/ets.erl b/lib/stdlib/src/ets.erl index 039ab45868..6a559f0be5 100644 --- a/lib/stdlib/src/ets.erl +++ b/lib/stdlib/src/ets.erl @@ -73,7 +73,8 @@           select_count/2, select_delete/2, select_replace/2, select_reverse/1,           select_reverse/2, select_reverse/3, setopts/2, slot/2,           take/2, -         update_counter/3, update_counter/4, update_element/3]). +         update_counter/3, update_counter/4, update_element/3, +         whereis/1]).  %% internal exports  -export([internal_request_all/0]). @@ -145,6 +146,7 @@ give_away(_, _, _) ->        InfoList :: [InfoTuple],        InfoTuple :: {compressed, boolean()}                   | {heir, pid() | none} +                 | {id, tid()}                   | {keypos, pos_integer()}                   | {memory, non_neg_integer()}                   | {name, atom()} @@ -162,7 +164,7 @@ info(_) ->  -spec info(Tab, Item) -> Value | undefined when        Tab :: tab(), -      Item :: compressed | fixed | heir | keypos | memory +      Item :: compressed | fixed | heir | id | keypos | memory              | name | named_table | node | owner | protection              | safe_fixed | safe_fixed_monotonic_time | size | stats | type  	    | write_concurrency | read_concurrency, @@ -512,6 +514,11 @@ update_counter(_, _, _, _) ->  update_element(_, _, _) ->      erlang:nif_error(undef). +-spec whereis(TableName) -> tid() | undefined when +    TableName :: atom(). +whereis(_) -> +    erlang:nif_error(undef). +  %%% End of BIFs  -opaque comp_match_spec() :: reference(). diff --git a/lib/stdlib/src/string.erl b/lib/stdlib/src/string.erl index e01bb7d85e..4e89819e41 100644 --- a/lib/stdlib/src/string.erl +++ b/lib/stdlib/src/string.erl @@ -420,10 +420,12 @@ to_number(_, Number, Rest, _, Tail) ->  %% Return the remaining string with prefix removed or else nomatch  -spec prefix(String::unicode:chardata(), Prefix::unicode:chardata()) ->                      'nomatch' | unicode:chardata(). -prefix(Str, []) -> Str;  prefix(Str, Prefix0) -> -    Prefix = unicode:characters_to_list(Prefix0), -    case prefix_1(Str, Prefix) of +    Result = case unicode:characters_to_list(Prefix0) of +                 [] -> Str; +                 Prefix -> prefix_1(Str, Prefix) +             end, +    case Result of          [] when is_binary(Str) -> <<>>;          Res -> Res      end. diff --git a/lib/stdlib/src/uri_string.erl b/lib/stdlib/src/uri_string.erl index a84679c595..28d36ea229 100644 --- a/lib/stdlib/src/uri_string.erl +++ b/lib/stdlib/src/uri_string.erl @@ -227,7 +227,7 @@  %% External API  %%-------------------------------------------------------------------------  -export([compose_query/1, compose_query/2, -         dissect_query/1, normalize/1, parse/1, +         dissect_query/1, normalize/1, normalize/2, parse/1,           recompose/1, transcode/2]).  -export_type([error/0, uri_map/0, uri_string/0]). @@ -292,18 +292,36 @@  %%-------------------------------------------------------------------------  %% Normalize URIs  %%------------------------------------------------------------------------- --spec normalize(URIString) -> NormalizedURI when -      URIString :: uri_string(), -      NormalizedURI :: uri_string(). -normalize(URIString) -> -    %% Percent-encoding normalization and case normalization for -    %% percent-encoded triplets are achieved by running parse and -    %% recompose on the input URI string. -    recompose( -      normalize_path_segment( -        normalize_scheme_based( -          normalize_case( -            parse(URIString))))). +-spec normalize(URI) -> NormalizedURI when +      URI :: uri_string() | uri_map(), +      NormalizedURI :: uri_string() +                     | error(). +normalize(URIMap) -> +    normalize(URIMap, []). + + +-spec normalize(URI, Options) -> NormalizedURI when +      URI :: uri_string() | uri_map(), +      Options :: [return_map], +      NormalizedURI :: uri_string() | uri_map(). +normalize(URIMap, []) when is_map(URIMap) -> +    recompose(normalize_map(URIMap)); +normalize(URIMap, [return_map]) when is_map(URIMap) -> +    normalize_map(URIMap); +normalize(URIString, []) -> +    case parse(URIString) of +        Value when is_map(Value) -> +            recompose(normalize_map(Value)); +        Error -> +            Error +    end; +normalize(URIString, [return_map]) -> +    case parse(URIString) of +        Value when is_map(Value) -> +            normalize_map(Value); +        Error -> +            Error +    end.  %%------------------------------------------------------------------------- @@ -385,7 +403,8 @@ transcode(URIString, Options) when is_list(URIString) ->  %%-------------------------------------------------------------------------  %% Functions for working with the query part of a URI as a list  %% of key/value pairs. -%% HTML5 - 4.10.22.6 URL-encoded form data +%% HTML 5.2 - 4.10.21.6 URL-encoded form data - WHATWG URL (10 Jan 2018) - UTF-8 +%% HTML 5.0 - 4.10.22.6 URL-encoded form data - non UTF-8  %%-------------------------------------------------------------------------  %%------------------------------------------------------------------------- @@ -393,7 +412,7 @@ transcode(URIString, Options) when is_list(URIString) ->  %% (application/x-www-form-urlencoded encoding algorithm)  %%-------------------------------------------------------------------------  -spec compose_query(QueryList) -> QueryString when -      QueryList :: [{uri_string(), uri_string()}], +      QueryList :: [{unicode:chardata(), unicode:chardata()}],        QueryString :: uri_string()                     | error().  compose_query(List) -> @@ -401,7 +420,7 @@ compose_query(List) ->  -spec compose_query(QueryList, Options) -> QueryString when -      QueryList :: [{uri_string(), uri_string()}], +      QueryList :: [{unicode:chardata(), unicode:chardata()}],        Options :: [{encoding, atom()}],        QueryString :: uri_string()                     | error(). @@ -432,7 +451,7 @@ compose_query([], _Options, IsList, Acc) ->  %%-------------------------------------------------------------------------  -spec dissect_query(QueryString) -> QueryList when        QueryString :: uri_string(), -      QueryList :: [{uri_string(), uri_string()}] +      QueryList :: [{unicode:chardata(), unicode:chardata()}]                   | error().  dissect_query(<<>>) ->      []; @@ -1755,7 +1774,8 @@ get_separator(_L) ->      <<"&">>. -%% HTML5 - 4.10.22.6 URL-encoded form data - encoding +%% HTML 5.2 - 4.10.21.6 URL-encoded form data - WHATWG URL (10 Jan 2018) - UTF-8 +%% HTML 5.0 - 4.10.22.6 URL-encoded form data - encoding (non UTF-8)  form_urlencode(Cs, [{encoding, latin1}]) when is_list(Cs) ->      B = convert_to_binary(Cs, utf8, utf8),      html5_byte_encode(base10_encode(B)); @@ -1850,7 +1870,8 @@ dissect_query_value(<<>>, IsList, Acc, Key, Value) ->      lists:reverse([{K,V}|Acc]). -%% Form-urldecode input based on RFC 1866 [8.2.1] +%% HTML 5.2 - 4.10.21.6 URL-encoded form data - WHATWG URL (10 Jan 2018) - UTF-8 +%% HTML 5.0 - 4.10.22.6 URL-encoded form data - decoding (non UTF-8)  form_urldecode(true, B) ->      Result = base10_decode(form_urldecode(B, <<>>)),      convert_to_list(Result, utf8); @@ -1903,6 +1924,12 @@ base10_decode_unicode(<<H,_/binary>>, _, _) ->  %% Helper functions for normalize  %%------------------------------------------------------------------------- +normalize_map(URIMap) -> +      normalize_path_segment( +        normalize_scheme_based( +          normalize_case(URIMap))). + +  %% 6.2.2.1.  Case Normalization  normalize_case(#{scheme := Scheme, host := Host} = Map) ->      Map#{scheme => to_lower(Scheme), | 
