diff options
Diffstat (limited to 'lib/stdlib/src')
37 files changed, 369 insertions, 310 deletions
diff --git a/lib/stdlib/src/Makefile b/lib/stdlib/src/Makefile index dfe6bf3e68..c95f7637f7 100644 --- a/lib/stdlib/src/Makefile +++ b/lib/stdlib/src/Makefile @@ -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. diff --git a/lib/stdlib/src/beam_lib.erl b/lib/stdlib/src/beam_lib.erl index 24349c74e8..01181b1097 100644 --- a/lib/stdlib/src/beam_lib.erl +++ b/lib/stdlib/src/beam_lib.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2000-2017. All Rights Reserved. +%% Copyright Ericsson AB 2000-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. @@ -690,30 +690,31 @@ chunk_to_data(debug_info=Id, Chunk, File, _Cs, AtomTable, Mod) -> <<0:8,N:8,Mode0:N/binary,Rest/binary>> -> Mode = binary_to_atom(Mode0, utf8), Term = decrypt_chunk(Mode, Mod, File, Id, Rest), - {AtomTable, {Id, Term}}; + {AtomTable, {Id, anno_from_term(Term)}}; _ -> case catch binary_to_term(Chunk) of {'EXIT', _} -> error({invalid_chunk, File, chunk_name_to_id(Id, File)}); Term -> - {AtomTable, {Id, Term}} + {AtomTable, {Id, anno_from_term(Term)}} end end; chunk_to_data(abstract_code=Id, Chunk, File, _Cs, AtomTable, Mod) -> + %% Before Erlang/OTP 20.0. case Chunk of <<>> -> {AtomTable, {Id, no_abstract_code}}; <<0:8,N:8,Mode0:N/binary,Rest/binary>> -> Mode = binary_to_atom(Mode0, utf8), Term = decrypt_chunk(Mode, Mod, File, Id, Rest), - {AtomTable, {Id, anno_from_term(Term)}}; + {AtomTable, {Id, old_anno_from_term(Term)}}; _ -> case catch binary_to_term(Chunk) of {'EXIT', _} -> error({invalid_chunk, File, chunk_name_to_id(Id, File)}); Term -> try - {AtomTable, {Id, anno_from_term(Term)}} + {AtomTable, {Id, old_anno_from_term(Term)}} catch _:_ -> error({invalid_chunk, File, @@ -947,14 +948,24 @@ decrypt_chunk(Type, Module, File, Id, Bin) -> error({key_missing_or_invalid, File, Id}) end. -anno_from_term({raw_abstract_v1, Forms}) -> +old_anno_from_term({raw_abstract_v1, Forms}) -> {raw_abstract_v1, anno_from_forms(Forms)}; -anno_from_term({Tag, Forms}) when Tag =:= abstract_v1; Tag =:= abstract_v2 -> +old_anno_from_term({Tag, Forms}) when Tag =:= abstract_v1; + Tag =:= abstract_v2 -> try {Tag, anno_from_forms(Forms)} catch _:_ -> {Tag, Forms} end; +old_anno_from_term(T) -> + T. + +anno_from_term({debug_info_v1=Tag1, erl_abstract_code=Tag2, {Forms, Opts}}) -> + try {Tag1, Tag2, {anno_from_forms(Forms), Opts}} + catch + _:_ -> + {Tag1, Tag2, {Forms, Opts}} + end; anno_from_term(T) -> T. diff --git a/lib/stdlib/src/binary.erl b/lib/stdlib/src/binary.erl index 7d0e42489e..52b9fedc9c 100644 --- a/lib/stdlib/src/binary.erl +++ b/lib/stdlib/src/binary.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2010-2017. All Rights Reserved. +%% Copyright Ericsson AB 2010-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. diff --git a/lib/stdlib/src/c.erl b/lib/stdlib/src/c.erl index 13f78841aa..0362b72536 100644 --- a/lib/stdlib/src/c.erl +++ b/lib/stdlib/src/c.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. diff --git a/lib/stdlib/src/dets.erl b/lib/stdlib/src/dets.erl index e1a36abc70..e016d5a80e 100644 --- a/lib/stdlib/src/dets.erl +++ b/lib/stdlib/src/dets.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. diff --git a/lib/stdlib/src/dets_utils.erl b/lib/stdlib/src/dets_utils.erl index 4c8ea9e82b..12394bd1ad 100644 --- a/lib/stdlib/src/dets_utils.erl +++ b/lib/stdlib/src/dets_utils.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2001-2017. All Rights Reserved. +%% Copyright Ericsson AB 2001-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. diff --git a/lib/stdlib/src/edlin.erl b/lib/stdlib/src/edlin.erl index 5df9c504f9..f027d05f55 100644 --- a/lib/stdlib/src/edlin.erl +++ b/lib/stdlib/src/edlin.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2016. 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. diff --git a/lib/stdlib/src/erl_eval.erl b/lib/stdlib/src/erl_eval.erl index 31c0e60fe1..2066b2f60f 100644 --- a/lib/stdlib/src/erl_eval.erl +++ b/lib/stdlib/src/erl_eval.erl @@ -329,7 +329,8 @@ expr({'fun',Line,{clauses,Cs}} = Ex, Bs, Lf, Ef, RBs) -> 20 -> fun (A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S,T) -> eval_fun([A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S,T], Info) end; _Other -> - erlang:raise(error, {'argument_limit',{'fun',Line,Cs}}, + L = erl_anno:location(Line), + erlang:raise(error, {'argument_limit',{'fun',L,to_terms(Cs)}}, ?STACKTRACE) end, ret_expr(F, Bs, RBs); @@ -381,7 +382,9 @@ expr({named_fun,Line,Name,Cs} = Ex, Bs, Lf, Ef, RBs) -> eval_named_fun([A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S,T], RF, Info) end; _Other -> - erlang:raise(error, {'argument_limit',{named_fun,Line,Name,Cs}}, + L = erl_anno:location(Line), + erlang:raise(error, {'argument_limit', + {named_fun,L,Name,to_terms(Cs)}}, ?STACKTRACE) end, ret_expr(F, Bs, RBs); @@ -1092,7 +1095,7 @@ match(Pat, Term, Bs) -> match(Pat, Term, Bs, BBs) -> case catch match1(Pat, Term, Bs, BBs) of invalid -> - erlang:raise(error, {illegal_pattern,Pat}, ?STACKTRACE); + erlang:raise(error, {illegal_pattern,to_term(Pat)}, ?STACKTRACE); Other -> Other end. @@ -1288,6 +1291,12 @@ merge_bindings(Bs1, Bs2) -> %% end %% end, Bs2, Bs1). +to_terms(Abstrs) -> + [to_term(Abstr) || Abstr <- Abstrs]. + +to_term(Abstr) -> + erl_parse:anno_to_term(Abstr). + %% Substitute {value, A, Item} for {var, A, Var}, preserving A. %% {value, A, Item} is a shell/erl_eval convention, and for example %% the linter cannot handle it. diff --git a/lib/stdlib/src/erl_internal.erl b/lib/stdlib/src/erl_internal.erl index dd509191ef..939abaff00 100644 --- a/lib/stdlib/src/erl_internal.erl +++ b/lib/stdlib/src/erl_internal.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1998-2017. All Rights Reserved. +%% Copyright Ericsson AB 1998-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. @@ -74,6 +74,7 @@ guard_bif(element, 2) -> true; guard_bif(float, 1) -> true; guard_bif(floor, 1) -> true; guard_bif(hd, 1) -> true; +guard_bif(is_map_key, 2) -> true; guard_bif(length, 1) -> true; guard_bif(map_size, 1) -> true; guard_bif(map_get, 2) -> true; @@ -109,7 +110,6 @@ new_type_test(is_function, 2) -> true; new_type_test(is_integer, 1) -> true; new_type_test(is_list, 1) -> true; new_type_test(is_map, 1) -> true; -new_type_test(is_map_key, 2) -> true; new_type_test(is_number, 1) -> true; new_type_test(is_pid, 1) -> true; new_type_test(is_port, 1) -> true; diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl index 0c338b5952..9602f0bcd9 100644 --- a/lib/stdlib/src/erl_parse.yrl +++ b/lib/stdlib/src/erl_parse.yrl @@ -2,7 +2,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. @@ -980,7 +980,7 @@ Erlang code. -type af_unary_op(T) :: {'op', anno(), unary_op(), T}. --type unary_op() :: '+' | '*' | 'bnot' | 'not'. +-type unary_op() :: '+' | '-' | 'bnot' | 'not'. %% See also lib/stdlib/{src/erl_bits.erl,include/erl_bits.hrl}. -type type_specifier_list() :: 'default' | [type_specifier(), ...]. diff --git a/lib/stdlib/src/erl_posix_msg.erl b/lib/stdlib/src/erl_posix_msg.erl index 8959fea498..b9ed4a3a9d 100644 --- a/lib/stdlib/src/erl_posix_msg.erl +++ b/lib/stdlib/src/erl_posix_msg.erl @@ -81,9 +81,9 @@ message_1(el2hlt) -> <<"level 2 halted">>; message_1(el2nsync) -> <<"level 2 not synchronized">>; message_1(el3hlt) -> <<"level 3 halted">>; message_1(el3rst) -> <<"level 3 reset">>; -message_1(elibacc) -> <<"can not access a needed shared library">>; +message_1(elibacc) -> <<"cannot access a needed shared library">>; message_1(elibbad) -> <<"accessing a corrupted shared library">>; -message_1(elibexec) -> <<"can not exec a shared library directly">>; +message_1(elibexec) -> <<"cannot exec a shared library directly">>; message_1(elibmax) -> <<"attempting to link in more shared libraries than system limit">>; message_1(elibscn) -> <<".lib section in a.out corrupted">>; diff --git a/lib/stdlib/src/erl_pp.erl b/lib/stdlib/src/erl_pp.erl index 367dbefb82..dd302a2880 100644 --- a/lib/stdlib/src/erl_pp.erl +++ b/lib/stdlib/src/erl_pp.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. @@ -59,7 +59,7 @@ _ -> ?TEST(T) end). -define(EXPRS_TEST(L), - [?TEST(E) || E <- L]). + _ = [?TEST(E) || E <- L]). -define(TEST(T), %% Assumes that erl_anno has been compiled with DEBUG=true. %% erl_pp does not use the annoations, but test it anyway. diff --git a/lib/stdlib/src/escript.erl b/lib/stdlib/src/escript.erl index 89a81684f5..3f14894b55 100644 --- a/lib/stdlib/src/escript.erl +++ b/lib/stdlib/src/escript.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2007-2017. All Rights Reserved. +%% Copyright Ericsson AB 2007-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. diff --git a/lib/stdlib/src/ets.erl b/lib/stdlib/src/ets.erl index a35f79c0d9..29f907ad73 100644 --- a/lib/stdlib/src/ets.erl +++ b/lib/stdlib/src/ets.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. diff --git a/lib/stdlib/src/file_sorter.erl b/lib/stdlib/src/file_sorter.erl index 7f74e71136..191e050538 100644 --- a/lib/stdlib/src/file_sorter.erl +++ b/lib/stdlib/src/file_sorter.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2001-2016. All Rights Reserved. +%% Copyright Ericsson AB 2001-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. diff --git a/lib/stdlib/src/gen.erl b/lib/stdlib/src/gen.erl index 2e6223d2bb..a7f743bd4c 100644 --- a/lib/stdlib/src/gen.erl +++ b/lib/stdlib/src/gen.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. diff --git a/lib/stdlib/src/gen_event.erl b/lib/stdlib/src/gen_event.erl index 3ee2031d02..8213282867 100644 --- a/lib/stdlib/src/gen_event.erl +++ b/lib/stdlib/src/gen_event.erl @@ -589,7 +589,7 @@ server_update(Handler1, Func, Event, SName) -> ?LOG_WARNING(#{label=>{gen_event,no_handle_info}, module=>Mod1, message=>Event}, - #{domain=>[beam,erlang,otp], + #{domain=>[otp], report_cb=>fun gen_event:format_log/1, error_logger=>#{tag=>warning_msg}}), % warningmap?? {ok, Handler1}; @@ -751,7 +751,7 @@ report_error(Handler, Reason, State, LastIn, SName) -> state=>format_status(terminate,Handler#handler.module, get(),State), reason=>Reason}, - #{domain=>[beam,erlang,otp], + #{domain=>[otp], report_cb=>fun gen_event:format_log/1, error_logger=>#{tag=>error}}). diff --git a/lib/stdlib/src/gen_fsm.erl b/lib/stdlib/src/gen_fsm.erl index 1646186761..caaaf8fa2e 100644 --- a/lib/stdlib/src/gen_fsm.erl +++ b/lib/stdlib/src/gen_fsm.erl @@ -505,7 +505,7 @@ handle_msg(Msg, Parent, Name, StateName, StateData, Mod, _Time, HibernateAfterTi ?LOG_WARNING(#{label=>{gen_fsm,no_handle_info}, module=>Mod, message=>Msg}, - #{domain=>[beam,erlang,otp], + #{domain=>[otp], report_cb=>fun gen_fsm:format_log/1, error_logger=>#{tag=>warning_msg}}), loop(Parent, Name, StateName, StateData, Mod, infinity, HibernateAfterTimeout, []); @@ -616,7 +616,7 @@ error_info(Reason, Name, Msg, StateName, StateData, Debug) -> state_name=>StateName, state_data=>StateData, reason=>Reason}, - #{domain=>[beam,erlang,otp], + #{domain=>[otp], report_cb=>fun gen_fsm:format_log/1, error_logger=>#{tag=>error}}), sys:print_log(Debug), diff --git a/lib/stdlib/src/gen_server.erl b/lib/stdlib/src/gen_server.erl index 09f77c0810..44e9231ebe 100644 --- a/lib/stdlib/src/gen_server.erl +++ b/lib/stdlib/src/gen_server.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. @@ -645,7 +645,7 @@ try_dispatch(Mod, Func, Msg, State) -> #{label=>{gen_server,no_handle_info}, module=>Mod, message=>Msg}, - #{domain=>[beam,erlang,otp], + #{domain=>[otp], report_cb=>fun gen_server:format_log/1, error_logger=>#{tag=>warning_msg}}), {ok, {noreply, State}}; @@ -891,7 +891,7 @@ error_info(Reason, Name, From, Msg, Mod, State, Debug) -> state=>format_status(terminate, Mod, get(), State), reason=>Reason, client_info=>client_stacktrace(From)}, - #{domain=>[beam,erlang,otp], + #{domain=>[otp], report_cb=>fun gen_server:format_log/1, error_logger=>#{tag=>error}}), sys:print_log(Debug), diff --git a/lib/stdlib/src/gen_statem.erl b/lib/stdlib/src/gen_statem.erl index b36b8cd5a5..faa43fbc1e 100644 --- a/lib/stdlib/src/gen_statem.erl +++ b/lib/stdlib/src/gen_statem.erl @@ -1448,13 +1448,13 @@ loop_event_done( [?sys_debug( Debug_0, {S#state.name,State}, - {postpone,Event_0,State}), + {postpone,Event_0,NextState}), Event_0|P_0]; false -> [?sys_debug( Debug_0, {S#state.name,State}, - {consume,Event_0,State})|P_0] + {consume,Event_0,NextState})|P_0] end, {Events_2,P_2,Timers_2} = %% Move all postponed events to queue, @@ -1900,7 +1900,7 @@ error_info( state_enter=>StateEnter, state=>format_status(terminate, get(), S), reason=>{Class,Reason,Stacktrace}}, - #{domain=>[beam,erlang,otp], + #{domain=>[otp], report_cb=>fun gen_statem:format_log/1, error_logger=>#{tag=>error}}). diff --git a/lib/stdlib/src/io.erl b/lib/stdlib/src/io.erl index 5d5773c80c..63c9a6bddf 100644 --- a/lib/stdlib/src/io.erl +++ b/lib/stdlib/src/io.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2015. 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. diff --git a/lib/stdlib/src/io_lib_pretty.erl b/lib/stdlib/src/io_lib_pretty.erl index 3d5a979b3e..ba9d9e8434 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); @@ -720,7 +722,7 @@ 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)) of - {prefix, ""} -> + false -> false; {prefix, Prefix} when Enc =:= latin1 -> io_lib:printable_latin1_list(Prefix) andalso {true, Prefix}; @@ -736,11 +738,17 @@ printable_list(L, _D, T, _Uni) when T < 0-> io_lib:printable_list(L). slice(L, N) -> - case string:length(L) =< N of + try string:length(L) =< N of true -> all; false -> - {prefix, string:slice(L, 0, N)} + case string:slice(L, 0, N) of + "" -> + false; + Prefix -> + {prefix, Prefix} + end + catch _:_ -> false end. printable_bin0(Bin, D, T, Enc) -> diff --git a/lib/stdlib/src/maps.erl b/lib/stdlib/src/maps.erl index a13f340709..51965ddb57 100644 --- a/lib/stdlib/src/maps.erl +++ b/lib/stdlib/src/maps.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2013-2016. All Rights Reserved. +%% Copyright Ericsson AB 2013-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. @@ -21,7 +21,7 @@ -module(maps). -export([get/3, filter/2,fold/3, - map/2, size/1, + map/2, size/1, new/0, update_with/3, update_with/4, without/2, with/2, iterator/1, next/1]). @@ -29,13 +29,15 @@ %% BIFs -export([get/2, find/2, from_list/1, is_key/2, keys/1, merge/2, - new/0, put/3, remove/2, take/2, + put/3, remove/2, take/2, to_list/1, update/3, values/1]). --opaque iterator() :: {term(), term(), iterator()} - | none | nonempty_improper_list(integer(),map()). +-opaque iterator(Key, Value) :: {Key, Value, iterator(Key, Value)} | none + | nonempty_improper_list(integer(), #{Key => Value}). --export_type([iterator/0]). +-type iterator() :: iterator(term(), term()). + +-export_type([iterator/2, iterator/0]). -dialyzer({no_improper_lists, iterator/1}). @@ -50,9 +52,7 @@ get(_,_) -> erlang:nif_error(undef). -spec find(Key,Map) -> {ok, Value} | error when - Key :: term(), - Map :: map(), - Value :: term(). + Map :: #{Key => Value, _ => _}. find(_,_) -> erlang:nif_error(undef). @@ -75,9 +75,8 @@ is_key(_,_) -> erlang:nif_error(undef). -spec keys(Map) -> Keys when - Map :: map(), - Keys :: [Key], - Key :: term(). + Map :: #{Key => _}, + Keys :: [Key]. keys(_) -> erlang:nif_error(undef). @@ -91,13 +90,6 @@ keys(_) -> erlang:nif_error(undef). merge(_,_) -> erlang:nif_error(undef). - --spec new() -> Map when - Map :: map(). - -new() -> erlang:nif_error(undef). - - %% Shadowed by erl_bif_types: maps:put/3 -spec put(Key,Value,Map1) -> Map2 when Key :: term(), @@ -116,17 +108,13 @@ put(_,_,_) -> erlang:nif_error(undef). remove(_,_) -> erlang:nif_error(undef). -spec take(Key,Map1) -> {Value,Map2} | error when - Key :: term(), - Map1 :: map(), - Value :: term(), - Map2 :: map(). + Map1 :: #{Key => Value, _ => _}, + Map2 :: #{_ => _}. take(_,_) -> erlang:nif_error(undef). -spec to_list(Map) -> [{Key,Value}] when - Map :: map(), - Key :: term(), - Value :: term(). + Map :: #{Key => Value}. to_list(Map) when is_map(Map) -> to_list_internal(erts_internal:map_next(0, Map, [])); @@ -140,79 +128,69 @@ to_list_internal(Acc) -> %% Shadowed by erl_bif_types: maps:update/3 -spec update(Key,Value,Map1) -> Map2 when - Key :: term(), - Value :: term(), - Map1 :: map(), - Map2 :: map(). + Map1 :: #{Key := _, _ => _}, + Map2 :: #{Key := Value, _ => _}. update(_,_,_) -> erlang:nif_error(undef). -spec values(Map) -> Values when - Map :: map(), - Values :: [Value], - Value :: term(). + Map :: #{_ => Value}, + Values :: [Value]. values(_) -> erlang:nif_error(undef). %% End of BIFs +-spec new() -> Map when + Map :: #{}. + +new() -> #{}. + -spec update_with(Key,Fun,Map1) -> Map2 when - Key :: term(), - Map1 :: map(), - Map2 :: map(), - Fun :: fun((Value1 :: term()) -> Value2 :: term()). + Map1 :: #{Key := Value1, _ => _}, + Map2 :: #{Key := Value2, _ => _}, + Fun :: fun((Value1) -> Value2). update_with(Key,Fun,Map) when is_function(Fun,1), is_map(Map) -> - try maps:get(Key,Map) of - Val -> maps:update(Key,Fun(Val),Map) - catch - error:{badkey,_} -> - erlang:error({badkey,Key},[Key,Fun,Map]) + case Map of + #{Key := Value} -> Map#{Key := Fun(Value)}; + #{} -> erlang:error({badkey,Key},[Key,Fun,Map]) end; update_with(Key,Fun,Map) -> erlang:error(error_type(Map),[Key,Fun,Map]). -spec update_with(Key,Fun,Init,Map1) -> Map2 when - Key :: term(), - Map1 :: Map1, - Map2 :: Map2, - Fun :: fun((Value1 :: term()) -> Value2 :: term()), - Init :: term(). + Map1 :: #{Key => Value1, _ => _}, + Map2 :: #{Key := Value2 | Init, _ => _}, + Fun :: fun((Value1) -> Value2). update_with(Key,Fun,Init,Map) when is_function(Fun,1), is_map(Map) -> - case maps:find(Key,Map) of - {ok,Val} -> maps:update(Key,Fun(Val),Map); - error -> maps:put(Key,Init,Map) + case Map of + #{Key := Value} -> Map#{Key := Fun(Value)}; + #{} -> Map#{Key => Init} end; update_with(Key,Fun,Init,Map) -> erlang:error(error_type(Map),[Key,Fun,Init,Map]). -spec get(Key, Map, Default) -> Value | Default when - Key :: term(), - Map :: map(), - Value :: term(), - Default :: term(). + Map :: #{Key => Value, _ => _}. get(Key,Map,Default) when is_map(Map) -> - case maps:find(Key, Map) of - {ok, Value} -> - Value; - error -> - Default + case Map of + #{Key := Value} -> Value; + #{} -> Default end; get(Key,Map,Default) -> erlang:error({badmap,Map},[Key,Map,Default]). --spec filter(Pred,MapOrIter) -> Map when +-spec filter(Pred, MapOrIter) -> Map when Pred :: fun((Key, Value) -> boolean()), - Key :: term(), - Value :: term(), - MapOrIter :: map() | iterator(), - Map :: map(). + MapOrIter :: #{Key => Value} | iterator(Key, Value), + Map :: #{Key => Value}. filter(Pred,Map) when is_function(Pred,2), is_map(Map) -> maps:from_list(filter_1(Pred, iterator(Map))); @@ -235,21 +213,18 @@ filter_1(Pred, Iter) -> end. -spec fold(Fun,Init,MapOrIter) -> Acc when - Fun :: fun((K, V, AccIn) -> AccOut), + Fun :: fun((Key, Value, AccIn) -> AccOut), Init :: term(), - Acc :: term(), - AccIn :: term(), - AccOut :: term(), - MapOrIter :: map() | iterator(), - K :: term(), - V :: term(). + Acc :: AccOut, + AccIn :: Init | AccOut, + MapOrIter :: #{Key => Value} | iterator(Key, Value). fold(Fun,Init,Map) when is_function(Fun,3), is_map(Map) -> fold_1(Fun,Init,iterator(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 @@ -260,19 +235,16 @@ fold_1(Fun, Acc, Iter) -> end. -spec map(Fun,MapOrIter) -> Map when - Fun :: fun((K, V1) -> V2), - MapOrIter :: map() | iterator(), - Map :: map(), - K :: term(), - V1 :: term(), - V2 :: term(). + Fun :: fun((Key, Value1) -> Value2), + MapOrIter :: #{Key => Value1} | iterator(Key, Value1), + Map :: #{Key => Value2}. map(Fun,Map) when is_function(Fun, 2), is_map(Map) -> maps:from_list(map_1(Fun, iterator(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 @@ -291,17 +263,15 @@ size(Val) -> erlang:error({badmap,Val},[Val]). -spec iterator(Map) -> Iterator when - Map :: map(), - Iterator :: iterator(). + Map :: #{Key => Value}, + Iterator :: iterator(Key, Value). iterator(M) when is_map(M) -> [0 | M]; iterator(M) -> erlang:error({badmap, M}, [M]). -spec next(Iterator) -> {Key, Value, NextIterator} | 'none' when - Iterator :: iterator(), - Key :: term(), - Value :: term(), - NextIterator :: iterator(). + Iterator :: iterator(Key, Value), + NextIterator :: iterator(Key, Value). next({K, V, I}) -> {K, V, I}; next([Path | Map]) when is_integer(Path), is_map(Map) -> @@ -318,29 +288,29 @@ next(Iter) -> K :: term(). without(Ks,M) when is_list(Ks), is_map(M) -> - lists:foldl(fun(K, M1) -> maps:remove(K, M1) end, M, Ks); + lists:foldl(fun maps:remove/2, M, Ks); without(Ks,M) -> erlang:error(error_type(M),[Ks,M]). -spec with(Ks, Map1) -> Map2 when Ks :: [K], - Map1 :: map(), - Map2 :: map(), - K :: term(). + Map1 :: #{K => V, _ => _}, + Map2 :: #{K => V}. with(Ks,Map1) when is_list(Ks), is_map(Map1) -> - Fun = fun(K, List) -> - case maps:find(K, Map1) of - {ok, V} -> - [{K, V} | List]; - error -> - List - end - end, - maps:from_list(lists:foldl(Fun, [], Ks)); + maps:from_list(with_1(Ks, Map1)); with(Ks,M) -> erlang:error(error_type(M),[Ks,M]). +with_1([K|Ks], Map) -> + case Map of + #{K := V} -> [{K,V}|with_1(Ks, Map)]; + #{} -> with_1(Ks, Map) + end; +with_1([], _Map) -> []. -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/ms_transform.erl b/lib/stdlib/src/ms_transform.erl index 428c23524b..d117481d2e 100644 --- a/lib/stdlib/src/ms_transform.erl +++ b/lib/stdlib/src/ms_transform.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2002-2017. All Rights Reserved. +%% Copyright Ericsson AB 2002-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. diff --git a/lib/stdlib/src/ordsets.erl b/lib/stdlib/src/ordsets.erl index 939e147ad8..176047079b 100644 --- a/lib/stdlib/src/ordsets.erl +++ b/lib/stdlib/src/ordsets.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2016. 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. diff --git a/lib/stdlib/src/otp_internal.erl b/lib/stdlib/src/otp_internal.erl index ceec3079a1..aaed13ba3a 100644 --- a/lib/stdlib/src/otp_internal.erl +++ b/lib/stdlib/src/otp_internal.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1999-2017. All Rights Reserved. +%% Copyright Ericsson AB 1999-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. @@ -620,6 +620,8 @@ obsolete_1(ssl, ssl_accept, 2) -> {deprecated, "deprecated; use ssl:handshake/2 instead"}; obsolete_1(ssl, ssl_accept, 3) -> {deprecated, "deprecated; use ssl:handshake/3 instead"}; +obsolete_1(otp_mib, F, _) when F =:= load; F =:= unload -> + {deprecated, "deprecated; functionality will be removed in a future release"}; %% not obsolete diff --git a/lib/stdlib/src/pool.erl b/lib/stdlib/src/pool.erl index b12ff205b1..599be55607 100644 --- a/lib/stdlib/src/pool.erl +++ b/lib/stdlib/src/pool.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2016. 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. diff --git a/lib/stdlib/src/proc_lib.erl b/lib/stdlib/src/proc_lib.erl index 5f14e78f91..d07c62500b 100644 --- a/lib/stdlib/src/proc_lib.erl +++ b/lib/stdlib/src/proc_lib.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. @@ -30,7 +30,7 @@ start/3, start/4, start/5, start_link/3, start_link/4, start_link/5, hibernate/3, init_ack/1, init_ack/2, - init_p/3,init_p/5,format/1,format/2,format/3,report_cb/1, + init_p/3,init_p/5,format/1,format/2,format/3,report_cb/2, initial_call/1, translate_initial_call/1, stop/1, stop/3]). @@ -508,8 +508,8 @@ crash_report(Class, Reason, StartF, Stacktrace) -> ?LOG_ERROR(#{label=>{proc_lib,crash}, report=>[my_info(Class, Reason, StartF, Stacktrace), linked_info(self())]}, - #{domain=>[beam,erlang,otp,sasl], - report_cb=>fun proc_lib:report_cb/1, + #{domain=>[otp,sasl], + report_cb=>fun proc_lib:report_cb/2, logger_formatter=>#{title=>"CRASH REPORT"}, error_logger=>#{tag=>error_report,type=>crash_report}}). @@ -750,14 +750,15 @@ check(Res) -> Res. %%% Format a generated crash info structure. %%% ----------------------------------------------------------- --spec report_cb(CrashReport) -> {Format,Args} when - CrashReport :: #{label=>{proc_lib,crash},report=>[term()]}, - Format :: io:format(), - Args :: [term()]. -report_cb(#{label:={proc_lib,crash}, - report:=CrashReport}) -> - Depth = error_logger:get_format_depth(), - get_format_and_args(CrashReport, utf8, Depth). +-spec report_cb(CrashReport,FormatOpts) -> unicode:chardata() when + CrashReport :: #{label => {proc_lib,crash}, + report => [term()]}, + FormatOpts :: logger:report_cb_config(). +report_cb(#{label:={proc_lib,crash}, report:=CrashReport}, Extra) -> + Default = #{chars_limit => unlimited, + depth => unlimited, + encoding => latin1}, + do_format(CrashReport, maps:merge(Default,Extra)). -spec format(CrashReport) -> string() when CrashReport :: [term()]. @@ -777,66 +778,47 @@ format(CrashReport, Encoding) -> Depth :: unlimited | pos_integer(). format(CrashReport, Encoding, Depth) -> - {F,A} = get_format_and_args(CrashReport, Encoding, Depth), - lists:flatten(io_lib:format(F,A)). + do_format(CrashReport, #{chars_limit => unlimited, + depth => Depth, + encoding => Encoding}). -get_format_and_args([OwnReport,LinkReport], Encoding, Depth) -> - Extra = {Encoding,Depth}, +do_format([OwnReport,LinkReport], Extra) -> MyIndent = " ", - {OwnFormat,OwnArgs} = format_report(OwnReport, MyIndent, Extra, [], []), - {LinkFormat,LinkArgs} = format_link_report(LinkReport, MyIndent, Extra, [], []), - {" crasher:~n"++OwnFormat++" neighbours:~n"++LinkFormat,OwnArgs++LinkArgs}. + OwnFormat = format_report(OwnReport, MyIndent, Extra), + LinkFormat = format_link_report(LinkReport, MyIndent, Extra), + Str = io_lib:format(" crasher:~n~ts neighbours:~n~ts", + [OwnFormat, LinkFormat]), + lists:flatten(Str). -format_link_report([], _Indent, _Extra, Format, Args) -> - {lists:flatten(lists:reverse(Format)),lists:append(lists:reverse(Args))}; -format_link_report([Link|Reps], Indent, Extra, Format, Args) -> +format_link_report([Link|Reps], Indent, Extra) -> Rep = case Link of {neighbour,Rep0} -> Rep0; _ -> Link end, LinkIndent = [" ",Indent], - {LinkFormat,LinkArgs} = format_report(Rep, LinkIndent, Extra, [], []), - F = "~sneighbour:\n"++LinkFormat, - A = [Indent|LinkArgs], - format_link_report(Reps, Indent, Extra, [F|Format], [A|Args]); -format_link_report(Rep, Indent, Extra, Format, Args) -> - {F,A} = format_report(Rep, Indent, Extra, [], []), - format_link_report([], Indent, Extra, [F|Format],[A|Args]). - -format_report([], _Indent, _Extra, Format, Args) -> - {lists:flatten(lists:reverse(Format)),lists:append(lists:reverse(Args))}; -format_report([Rep|Reps], Indent, Extra, Format, Args) -> - {F,A} = format_rep(Rep, Indent, Extra), - format_report(Reps, Indent, Extra, [F|Format], [A|Args]); -format_report(Rep, Indent, {Enc,unlimited}=Extra, Format, Args) -> - {F,A} = {"~s~"++modifier(Enc)++"p~n", [Indent, Rep]}, - format_report([], Indent, Extra, [F|Format], [A|Args]); -format_report(Rep, Indent, {Enc,Depth}=Extra, Format, Args) -> - {F,A} = {"~s~"++modifier(Enc)++"P~n", [Indent, Rep, Depth]}, - format_report([], Indent, Extra, [F|Format], [A|Args]). - -format_rep({initial_call,InitialCall}, Indent, Extra) -> - format_mfa(Indent, InitialCall, Extra); -format_rep({error_info,{Class,Reason,StackTrace}}, _Indent, Extra) -> - {lists:flatten(format_exception(Class, Reason, StackTrace, Extra)),[]}; -format_rep({Tag,Data}, Indent, Extra) -> - format_tag(Indent, Tag, Data, Extra). - -format_mfa(Indent, {M,F,Args}=StartF, {Enc,_}=Extra) -> - try - A = length(Args), - {lists:flatten([Indent,"initial call: ",atom_to_list(M), - $:,to_string(F, Enc),$/,integer_to_list(A),"\n"]),[]} - catch - error:_ -> - format_tag(Indent, initial_call, StartF, Extra) - end. - -format_tag(Indent, Tag, Data, {Enc,Depth}) -> - {P,Tl} = p(Enc, Depth), - {"~s~p: ~80.18" ++ P ++ "\n", [Indent, Tag, Data|Tl]}. + [Indent,"neighbour:\n",format_report(Rep, LinkIndent, Extra)| + format_link_report(Reps, Indent, Extra)]; +format_link_report(Rep, Indent, Extra) -> + format_report(Rep, Indent, Extra). + +format_report(Rep, Indent, Extra) when is_list(Rep) -> + format_rep(Rep, Indent, Extra); +format_report(Rep, Indent, #{encoding:=Enc,depth:=unlimited}) -> + io_lib:format("~s~"++modifier(Enc)++"p~n", [Indent, Rep]); +format_report(Rep, Indent, #{encoding:=Enc,depth:=Depth}) -> + io_lib:format("~s~"++modifier(Enc)++"P~n", [Indent, Rep, Depth]). + +format_rep([{initial_call,InitialCall}|Rep], Indent, Extra) -> + [format_mfa(Indent, InitialCall, Extra)|format_rep(Rep, Indent, Extra)]; +format_rep([{error_info,{Class,Reason,StackTrace}}|Rep], Indent, Extra) -> + [format_exception(Class, Reason, StackTrace, Extra)| + format_rep(Rep, Indent, Extra)]; +format_rep([{Tag,Data}|Rep], Indent, Extra) -> + [format_tag(Indent, Tag, Data, Extra)|format_rep(Rep, Indent, Extra)]; +format_rep(_, _, _Extra) -> + []. -format_exception(Class, Reason, StackTrace, {Enc,_}=Extra) -> +format_exception(Class, Reason, StackTrace, #{encoding:=Enc}=Extra) -> PF = pp_fun(Extra), StackFun = fun(M, _F, _A) -> (M =:= erl_eval) or (M =:= ?MODULE) end, %% EI = " exception: ", @@ -844,17 +826,37 @@ format_exception(Class, Reason, StackTrace, {Enc,_}=Extra) -> [EI, erl_error:format_exception(1+length(EI), Class, Reason, StackTrace, StackFun, PF, Enc), "\n"]. +format_mfa(Indent, {M,F,Args}=StartF, #{encoding:=Enc}=Extra) -> + try + A = length(Args), + [Indent,"initial call: ",atom_to_list(M),$:,to_string(F, Enc),$/, + integer_to_list(A),"\n"] + catch + error:_ -> + format_tag(Indent, initial_call, StartF, Extra) + end. + to_string(A, latin1) -> io_lib:write_atom_as_latin1(A); to_string(A, _) -> io_lib:write_atom(A). -pp_fun({Enc,Depth}) -> +pp_fun(#{encoding:=Enc,depth:=Depth,chars_limit:=Limit}) -> {P,Tl} = p(Enc, Depth), + Opts = if is_integer(Limit) -> [{chars_limit,Limit}]; + true -> [] + end, fun(Term, I) -> - io_lib:format("~." ++ integer_to_list(I) ++ P, [Term|Tl]) + io_lib:format("~." ++ integer_to_list(I) ++ P, [Term|Tl], Opts) end. +format_tag(Indent, Tag, Data, #{encoding:=Enc,depth:=Depth,chars_limit:=Limit}) -> + {P,Tl} = p(Enc, Depth), + Opts = if is_integer(Limit) -> [{chars_limit,Limit}]; + true -> [] + end, + io_lib:format("~s~p: ~80.18" ++ P ++ "\n", [Indent, Tag, Data|Tl], Opts). + p(Encoding, Depth) -> {Letter, Tl} = case Depth of unlimited -> {"p", []}; diff --git a/lib/stdlib/src/qlc.erl b/lib/stdlib/src/qlc.erl index 4a0e976ba4..a1c1117e31 100644 --- a/lib/stdlib/src/qlc.erl +++ b/lib/stdlib/src/qlc.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2004-2017. All Rights Reserved. +%% Copyright Ericsson AB 2004-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. diff --git a/lib/stdlib/src/rand.erl b/lib/stdlib/src/rand.erl index 362e98006e..4951dc727b 100644 --- a/lib/stdlib/src/rand.erl +++ b/lib/stdlib/src/rand.erl @@ -486,7 +486,7 @@ uniform_real_s(Alg, Next, M0, BitNo, R1, V1, Bits) -> {M1 * math:pow(2.0, BitNo - 56), {Alg, R1}}; BitNo =:= -1008 -> %% Endgame - %% For the last round we can not have 14 zeros or more + %% For the last round we cannot have 14 zeros or more %% at the top of M1 because then we will underflow, %% so we need at least 43 bits if diff --git a/lib/stdlib/src/sets.erl b/lib/stdlib/src/sets.erl index ac0fc80526..8adb9016e2 100644 --- a/lib/stdlib/src/sets.erl +++ b/lib/stdlib/src/sets.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2000-2016. All Rights Reserved. +%% Copyright Ericsson AB 2000-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. diff --git a/lib/stdlib/src/slave.erl b/lib/stdlib/src/slave.erl index 37c1f6bfd9..5e8c1a43ea 100644 --- a/lib/stdlib/src/slave.erl +++ b/lib/stdlib/src/slave.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. diff --git a/lib/stdlib/src/string.erl b/lib/stdlib/src/string.erl index cf48b882e4..2939e78d9d 100644 --- a/lib/stdlib/src/string.erl +++ b/lib/stdlib/src/string.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. diff --git a/lib/stdlib/src/supervisor.erl b/lib/stdlib/src/supervisor.erl index eb46ac611a..1ac7334830 100644 --- a/lib/stdlib/src/supervisor.erl +++ b/lib/stdlib/src/supervisor.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. @@ -43,7 +43,7 @@ {errorContext,Error}, {reason,Reason}, {offender,extract_child(Child)}]}, - #{domain=>[beam,erlang,otp,sasl], + #{domain=>[otp,sasl], report_cb=>fun logger:format_otp_report/1, logger_formatter=>#{title=>"SUPERVISOR REPORT"}, error_logger=>#{tag=>error_report, @@ -580,7 +580,7 @@ handle_info({'EXIT', Pid, Reason}, State) -> handle_info(Msg, State) -> ?LOG_ERROR("Supervisor received unexpected message: ~tp~n",[Msg], - #{domain=>[beam,erlang,otp], + #{domain=>[otp], error_logger=>#{tag=>error}}), {noreply, State}. @@ -1419,7 +1419,7 @@ report_progress(Child, SupName) -> ?LOG_INFO(#{label=>{supervisor,progress}, report=>[{supervisor,SupName}, {started,extract_child(Child)}]}, - #{domain=>[beam,erlang,otp,sasl], + #{domain=>[otp,sasl], report_cb=>fun logger:format_otp_report/1, logger_formatter=>#{title=>"PROGRESS REPORT"}, error_logger=>#{tag=>info_report,type=>progress}}). diff --git a/lib/stdlib/src/supervisor_bridge.erl b/lib/stdlib/src/supervisor_bridge.erl index 39372935fa..21ba6f53af 100644 --- a/lib/stdlib/src/supervisor_bridge.erl +++ b/lib/stdlib/src/supervisor_bridge.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2016. 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. @@ -135,7 +135,7 @@ report_progress(Pid, Mod, StartArgs, SupName) -> report=>[{supervisor, SupName}, {started, [{pid, Pid}, {mfa, {Mod, init, [StartArgs]}}]}]}, - #{domain=>[beam,erlang,otp,sasl], + #{domain=>[otp,sasl], report_cb=>fun logger:format_otp_report/1, logger_formatter=>#{title=>"PROGRESS REPORT"}, error_logger=>#{tag=>info_report,type=>progress}}). @@ -146,7 +146,7 @@ report_error(Error, Reason, #state{name = Name, pid = Pid, mod = Mod}) -> {errorContext, Error}, {reason, Reason}, {offender, [{pid, Pid}, {mod, Mod}]}]}, - #{domain=>[beam,erlang,otp,sasl], + #{domain=>[otp,sasl], report_cb=>fun logger:format_otp_report/1, logger_formatter=>#{title=>"SUPERVISOR REPORT"}, error_logger=>#{tag=>error_report,type=>supervisor_report}}). diff --git a/lib/stdlib/src/uri_string.erl b/lib/stdlib/src/uri_string.erl index 28d36ea229..d33dc89af8 100644 --- a/lib/stdlib/src/uri_string.erl +++ b/lib/stdlib/src/uri_string.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2017. All Rights Reserved. +%% Copyright Ericsson AB 2017-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. @@ -297,7 +297,10 @@ NormalizedURI :: uri_string() | error(). normalize(URIMap) -> - normalize(URIMap, []). + try normalize(URIMap, []) + catch + throw:{error, Atom, RestData} -> {error, Atom, RestData} + end. -spec normalize(URI, Options) -> NormalizedURI when @@ -412,7 +415,7 @@ transcode(URIString, Options) when is_list(URIString) -> %% (application/x-www-form-urlencoded encoding algorithm) %%------------------------------------------------------------------------- -spec compose_query(QueryList) -> QueryString when - QueryList :: [{unicode:chardata(), unicode:chardata()}], + QueryList :: [{unicode:chardata(), unicode:chardata() | true}], QueryString :: uri_string() | error(). compose_query(List) -> @@ -420,7 +423,7 @@ compose_query(List) -> -spec compose_query(QueryList, Options) -> QueryString when - QueryList :: [{unicode:chardata(), unicode:chardata()}], + QueryList :: [{unicode:chardata(), unicode:chardata() | true}], Options :: [{encoding, atom()}], QueryString :: uri_string() | error(). @@ -432,6 +435,11 @@ compose_query(List, Options) -> throw:{error, Atom, RestData} -> {error, Atom, RestData} end. %% +compose_query([{Key,true}|Rest], Options, IsList, Acc) -> + Separator = get_separator(Rest), + K = form_urlencode(Key, Options), + IsListNew = IsList orelse is_list(Key), + compose_query(Rest, Options, IsListNew, <<Acc/binary,K/binary,Separator/binary>>); compose_query([{Key,Value}|Rest], Options, IsList, Acc) -> Separator = get_separator(Rest), K = form_urlencode(Key, Options), @@ -451,7 +459,7 @@ compose_query([], _Options, IsList, Acc) -> %%------------------------------------------------------------------------- -spec dissect_query(QueryString) -> QueryList when QueryString :: uri_string(), - QueryList :: [{unicode:chardata(), unicode:chardata()}] + QueryList :: [{unicode:chardata(), unicode:chardata() | true}] | error(). dissect_query(<<>>) -> []; @@ -523,34 +531,34 @@ parse_relative_part(?STRING_REST("//", Rest), URI) -> {T, URI1} -> Userinfo = calculate_parsed_userinfo(Rest, T), URI2 = maybe_add_path(URI1), - URI2#{userinfo => decode_userinfo(Userinfo)} + URI2#{userinfo => Userinfo} catch throw:{_,_,_} -> {T, URI1} = parse_host(Rest, URI), Host = calculate_parsed_host_port(Rest, T), URI2 = maybe_add_path(URI1), - URI2#{host => decode_host(remove_brackets(Host))} + URI2#{host => remove_brackets(Host)} end; parse_relative_part(?STRING_REST($/, Rest), URI) -> {T, URI1} = parse_segment(Rest, URI), % path-absolute Path = calculate_parsed_part(Rest, T), - URI1#{path => decode_path(?STRING_REST($/, Path))}; + URI1#{path => ?STRING_REST($/, Path)}; parse_relative_part(?STRING_REST($?, Rest), URI) -> {T, URI1} = parse_query(Rest, URI), % path-empty ?query Query = calculate_parsed_query_fragment(Rest, T), URI2 = maybe_add_path(URI1), - URI2#{query => decode_query(Query)}; + URI2#{query => Query}; parse_relative_part(?STRING_REST($#, Rest), URI) -> {T, URI1} = parse_fragment(Rest, URI), % path-empty Fragment = calculate_parsed_query_fragment(Rest, T), URI2 = maybe_add_path(URI1), - URI2#{fragment => decode_fragment(Fragment)}; + URI2#{fragment => Fragment}; parse_relative_part(?STRING_REST(Char, Rest), URI) -> case is_segment_nz_nc(Char) of true -> {T, URI1} = parse_segment_nz_nc(Rest, URI), % path-noscheme Path = calculate_parsed_part(Rest, T), - URI1#{path => decode_path(?STRING_REST(Char, Path))}; + URI1#{path => ?STRING_REST(Char, Path)}; false -> throw({error,invalid_uri,[Char]}) end. @@ -593,11 +601,11 @@ parse_segment(?STRING_REST($/, Rest), URI) -> parse_segment(?STRING_REST($?, Rest), URI) -> {T, URI1} = parse_query(Rest, URI), % ?query Query = calculate_parsed_query_fragment(Rest, T), - {Rest, URI1#{query => decode_query(Query)}}; + {Rest, URI1#{query => Query}}; parse_segment(?STRING_REST($#, Rest), URI) -> {T, URI1} = parse_fragment(Rest, URI), Fragment = calculate_parsed_query_fragment(Rest, T), - {Rest, URI1#{fragment => decode_fragment(Fragment)}}; + {Rest, URI1#{fragment => Fragment}}; parse_segment(?STRING_REST(Char, Rest), URI) -> case is_pchar(Char) of true -> parse_segment(Rest, URI); @@ -616,11 +624,11 @@ parse_segment_nz_nc(?STRING_REST($/, Rest), URI) -> parse_segment_nz_nc(?STRING_REST($?, Rest), URI) -> {T, URI1} = parse_query(Rest, URI), % ?query Query = calculate_parsed_query_fragment(Rest, T), - {Rest, URI1#{query => decode_query(Query)}}; + {Rest, URI1#{query => Query}}; parse_segment_nz_nc(?STRING_REST($#, Rest), URI) -> {T, URI1} = parse_fragment(Rest, URI), Fragment = calculate_parsed_query_fragment(Rest, T), - {Rest, URI1#{fragment => decode_fragment(Fragment)}}; + {Rest, URI1#{fragment => Fragment}}; parse_segment_nz_nc(?STRING_REST(Char, Rest), URI) -> case is_segment_nz_nc(Char) of true -> parse_segment_nz_nc(Rest, URI); @@ -709,31 +717,31 @@ parse_hier(?STRING_REST("//", Rest), URI) -> try parse_userinfo(Rest, URI) of {T, URI1} -> Userinfo = calculate_parsed_userinfo(Rest, T), - {Rest, URI1#{userinfo => decode_userinfo(Userinfo)}} + {Rest, URI1#{userinfo => Userinfo}} catch throw:{_,_,_} -> {T, URI1} = parse_host(Rest, URI), Host = calculate_parsed_host_port(Rest, T), - {Rest, URI1#{host => decode_host(remove_brackets(Host))}} + {Rest, URI1#{host => remove_brackets(Host)}} end; parse_hier(?STRING_REST($/, Rest), URI) -> {T, URI1} = parse_segment(Rest, URI), % path-absolute Path = calculate_parsed_part(Rest, T), - {Rest, URI1#{path => decode_path(?STRING_REST($/, Path))}}; + {Rest, URI1#{path => ?STRING_REST($/, Path)}}; parse_hier(?STRING_REST($?, Rest), URI) -> {T, URI1} = parse_query(Rest, URI), % path-empty ?query Query = calculate_parsed_query_fragment(Rest, T), - {Rest, URI1#{query => decode_query(Query)}}; + {Rest, URI1#{query => Query}}; parse_hier(?STRING_REST($#, Rest), URI) -> {T, URI1} = parse_fragment(Rest, URI), % path-empty Fragment = calculate_parsed_query_fragment(Rest, T), - {Rest, URI1#{fragment => decode_fragment(Fragment)}}; + {Rest, URI1#{fragment => Fragment}}; parse_hier(?STRING_REST(Char, Rest), URI) -> % path-rootless case is_pchar(Char) of true -> % segment_nz {T, URI1} = parse_segment(Rest, URI), Path = calculate_parsed_part(Rest, T), - {Rest, URI1#{path => decode_path(?STRING_REST(Char, Path))}}; + {Rest, URI1#{path => ?STRING_REST(Char, Path)}}; false -> throw({error,invalid_uri,[Char]}) end; parse_hier(?STRING_EMPTY, URI) -> @@ -770,7 +778,7 @@ parse_userinfo(?CHAR($@), URI) -> parse_userinfo(?STRING_REST($@, Rest), URI) -> {T, URI1} = parse_host(Rest, URI), Host = calculate_parsed_host_port(Rest, T), - {Rest, URI1#{host => decode_host(remove_brackets(Host))}}; + {Rest, URI1#{host => remove_brackets(Host)}}; parse_userinfo(?STRING_REST(Char, Rest), URI) -> case is_userinfo(Char) of true -> parse_userinfo(Rest, URI); @@ -836,20 +844,25 @@ parse_host(?STRING_REST($:, Rest), URI) -> parse_host(?STRING_REST($/, Rest), URI) -> {T, URI1} = parse_segment(Rest, URI), % path-abempty Path = calculate_parsed_part(Rest, T), - {Rest, URI1#{path => decode_path(?STRING_REST($/, Path))}}; + {Rest, URI1#{path => ?STRING_REST($/, Path)}}; parse_host(?STRING_REST($?, Rest), URI) -> {T, URI1} = parse_query(Rest, URI), % path-empty ?query Query = calculate_parsed_query_fragment(Rest, T), - {Rest, URI1#{query => decode_query(Query)}}; + {Rest, URI1#{query => Query}}; parse_host(?STRING_REST($[, Rest), URI) -> parse_ipv6_bin(Rest, [], URI); parse_host(?STRING_REST($#, Rest), URI) -> {T, URI1} = parse_fragment(Rest, URI), % path-empty Fragment = calculate_parsed_query_fragment(Rest, T), - {Rest, URI1#{fragment => decode_fragment(Fragment)}}; + {Rest, URI1#{fragment => Fragment}}; parse_host(?STRING_REST(Char, Rest), URI) -> case is_digit(Char) of - true -> parse_ipv4_bin(Rest, [Char], URI); + true -> + try parse_ipv4_bin(Rest, [Char], URI) + catch + throw:{_,_,_} -> + parse_reg_name(?STRING_REST(Char, Rest), URI) + end; false -> parse_reg_name(?STRING_REST(Char, Rest), URI) end; parse_host(?STRING_EMPTY, URI) -> @@ -865,15 +878,15 @@ parse_reg_name(?STRING_REST($:, Rest), URI) -> parse_reg_name(?STRING_REST($/, Rest), URI) -> {T, URI1} = parse_segment(Rest, URI), % path-abempty Path = calculate_parsed_part(Rest, T), - {Rest, URI1#{path => decode_path(?STRING_REST($/, Path))}}; + {Rest, URI1#{path => ?STRING_REST($/, Path)}}; parse_reg_name(?STRING_REST($?, Rest), URI) -> {T, URI1} = parse_query(Rest, URI), % path-empty ?query Query = calculate_parsed_query_fragment(Rest, T), - {Rest, URI1#{query => decode_query(Query)}}; + {Rest, URI1#{query => Query}}; parse_reg_name(?STRING_REST($#, Rest), URI) -> {T, URI1} = parse_fragment(Rest, URI), % path-empty Fragment = calculate_parsed_query_fragment(Rest, T), - {Rest, URI1#{fragment => decode_fragment(Fragment)}}; + {Rest, URI1#{fragment => Fragment}}; parse_reg_name(?STRING_REST(Char, Rest), URI) -> case is_reg_name(Char) of true -> parse_reg_name(Rest, URI); @@ -899,17 +912,17 @@ parse_ipv4_bin(?STRING_REST($/, Rest), Acc, URI) -> _ = validate_ipv4_address(lists:reverse(Acc)), {T, URI1} = parse_segment(Rest, URI), % path-abempty Path = calculate_parsed_part(Rest, T), - {Rest, URI1#{path => decode_path(?STRING_REST($/, Path))}}; + {Rest, URI1#{path => ?STRING_REST($/, Path)}}; parse_ipv4_bin(?STRING_REST($?, Rest), Acc, URI) -> _ = validate_ipv4_address(lists:reverse(Acc)), {T, URI1} = parse_query(Rest, URI), % path-empty ?query Query = calculate_parsed_query_fragment(Rest, T), - {Rest, URI1#{query => decode_query(Query)}}; + {Rest, URI1#{query => Query}}; parse_ipv4_bin(?STRING_REST($#, Rest), Acc, URI) -> _ = validate_ipv4_address(lists:reverse(Acc)), {T, URI1} = parse_fragment(Rest, URI), % path-empty Fragment = calculate_parsed_query_fragment(Rest, T), - {Rest, URI1#{fragment => decode_fragment(Fragment)}}; + {Rest, URI1#{fragment => Fragment}}; parse_ipv4_bin(?STRING_REST(Char, Rest), Acc, URI) -> case is_ipv4(Char) of true -> parse_ipv4_bin(Rest, [Char|Acc], URI); @@ -961,15 +974,15 @@ parse_ipv6_bin_end(?STRING_REST($:, Rest), URI) -> parse_ipv6_bin_end(?STRING_REST($/, Rest), URI) -> {T, URI1} = parse_segment(Rest, URI), % path-abempty Path = calculate_parsed_part(Rest, T), - {Rest, URI1#{path => decode_path(?STRING_REST($/, Path))}}; + {Rest, URI1#{path => ?STRING_REST($/, Path)}}; parse_ipv6_bin_end(?STRING_REST($?, Rest), URI) -> {T, URI1} = parse_query(Rest, URI), % path-empty ?query Query = calculate_parsed_query_fragment(Rest, T), - {Rest, URI1#{query => decode_query(Query)}}; + {Rest, URI1#{query => Query}}; parse_ipv6_bin_end(?STRING_REST($#, Rest), URI) -> {T, URI1} = parse_fragment(Rest, URI), % path-empty Fragment = calculate_parsed_query_fragment(Rest, T), - {Rest, URI1#{fragment => decode_fragment(Fragment)}}; + {Rest, URI1#{fragment => Fragment}}; parse_ipv6_bin_end(?STRING_REST(Char, Rest), URI) -> case is_ipv6(Char) of true -> parse_ipv6_bin_end(Rest, URI); @@ -999,15 +1012,15 @@ validate_ipv6_address(Addr) -> parse_port(?STRING_REST($/, Rest), URI) -> {T, URI1} = parse_segment(Rest, URI), % path-abempty Path = calculate_parsed_part(Rest, T), - {Rest, URI1#{path => decode_path(?STRING_REST($/, Path))}}; + {Rest, URI1#{path => ?STRING_REST($/, Path)}}; parse_port(?STRING_REST($?, Rest), URI) -> {T, URI1} = parse_query(Rest, URI), % path-empty ?query Query = calculate_parsed_query_fragment(Rest, T), - {Rest, URI1#{query => decode_query(Query)}}; + {Rest, URI1#{query => Query}}; parse_port(?STRING_REST($#, Rest), URI) -> {T, URI1} = parse_fragment(Rest, URI), % path-empty Fragment = calculate_parsed_query_fragment(Rest, T), - {Rest, URI1#{fragment => decode_fragment(Fragment)}}; + {Rest, URI1#{fragment => Fragment}}; parse_port(?STRING_REST(Char, Rest), URI) -> case is_digit(Char) of true -> parse_port(Rest, URI); @@ -1033,7 +1046,7 @@ parse_port(?STRING_EMPTY, URI) -> parse_query(?STRING_REST($#, Rest), URI) -> {T, URI1} = parse_fragment(Rest, URI), Fragment = calculate_parsed_query_fragment(Rest, T), - {Rest, URI1#{fragment => decode_fragment(Fragment)}}; + {Rest, URI1#{fragment => Fragment}}; parse_query(?STRING_REST(Char, Rest), URI) -> case is_query(Char) of true -> parse_query(Rest, URI); @@ -1088,6 +1101,31 @@ is_fragment(Char) -> is_pchar(Char). %% %%------------------------------------------------------------------------- +%% Return true if input char is reserved. +-spec is_reserved(char()) -> boolean(). +is_reserved($:) -> true; +is_reserved($/) -> true; +is_reserved($?) -> true; +is_reserved($#) -> true; +is_reserved($[) -> true; +is_reserved($]) -> true; +is_reserved($@) -> true; + +is_reserved($!) -> true; +is_reserved($$) -> true; +is_reserved($&) -> true; +is_reserved($') -> true; +is_reserved($() -> true; +is_reserved($)) -> true; + +is_reserved($*) -> true; +is_reserved($+) -> true; +is_reserved($,) -> true; +is_reserved($;) -> true; +is_reserved($=) -> true; +is_reserved(_) -> false. + + %% Check if char is sub-delim. -spec is_sub_delim(char()) -> boolean(). is_sub_delim($!) -> true; @@ -1276,36 +1314,6 @@ byte_size_exl_head(Binary) -> byte_size(Binary) + 1. %% %% pct-encoded = "%" HEXDIG HEXDIG %%------------------------------------------------------------------------- --spec decode_userinfo(binary()) -> binary(). -decode_userinfo(Cs) -> - check_utf8(decode(Cs, fun is_userinfo/1, <<>>)). - --spec decode_host(binary()) -> binary(). -decode_host(Cs) -> - check_utf8(decode(Cs, fun is_host/1, <<>>)). - --spec decode_path(binary()) -> binary(). -decode_path(Cs) -> - check_utf8(decode(Cs, fun is_path/1, <<>>)). - --spec decode_query(binary()) -> binary(). -decode_query(Cs) -> - check_utf8(decode(Cs, fun is_query/1, <<>>)). - --spec decode_fragment(binary()) -> binary(). -decode_fragment(Cs) -> - check_utf8(decode(Cs, fun is_fragment/1, <<>>)). - - -%% Returns Cs if it is utf8 encoded. -check_utf8(Cs) -> - case unicode:characters_to_list(Cs) of - {incomplete,_,_} -> - throw({error,invalid_utf8,Cs}); - {error,_,_} -> - throw({error,invalid_utf8,Cs}); - _ -> Cs - end. %%------------------------------------------------------------------------- %% Percent-encode @@ -1351,20 +1359,56 @@ encode_fragment(Cs) -> %%------------------------------------------------------------------------- %% Helper funtions for percent-decode %%------------------------------------------------------------------------- -decode(<<$%,C0,C1,Cs/binary>>, Fun, Acc) -> + +-spec decode(list()|binary()) -> list() | binary(). +decode(Cs) -> + decode(Cs, <<>>). +%% +decode(L, Acc) when is_list(L) -> + B0 = unicode:characters_to_binary(L), + B1 = decode(B0, Acc), + unicode:characters_to_list(B1); +decode(<<$%,C0,C1,Cs/binary>>, Acc) -> case is_hex_digit(C0) andalso is_hex_digit(C1) of true -> B = ?HEX2DEC(C0)*16+?HEX2DEC(C1), - decode(Cs, Fun, <<Acc/binary, B>>); + case is_reserved(B) of + true -> + %% [2.2] Characters in the reserved set are protected from + %% normalization. + %% [2.1] For consistency, URI producers and normalizers should + %% use uppercase hexadecimal digits for all percent- + %% encodings. + H0 = hex_to_upper(C0), + H1 = hex_to_upper(C1), + decode(Cs, <<Acc/binary,$%,H0,H1>>); + false -> + decode(Cs, <<Acc/binary, B>>) + end; false -> throw({error,invalid_percent_encoding,<<$%,C0,C1>>}) end; -decode(<<C,Cs/binary>>, Fun, Acc) -> - case Fun(C) of - true -> decode(Cs, Fun, <<Acc/binary, C>>); - false -> throw({error,invalid_percent_encoding,<<C,Cs/binary>>}) - end; -decode(<<>>, _Fun, Acc) -> - Acc. +decode(<<C,Cs/binary>>, Acc) -> + decode(Cs, <<Acc/binary, C>>); +decode(<<>>, Acc) -> + check_utf8(Acc). + +%% Returns Cs if it is utf8 encoded. +check_utf8(Cs) -> + case unicode:characters_to_list(Cs) of + {incomplete,_,_} -> + throw({error,invalid_utf8,Cs}); + {error,_,_} -> + throw({error,invalid_utf8,Cs}); + _ -> Cs + end. + +%% Convert hex digit to uppercase form +hex_to_upper(H) when $a =< H, H =< $f -> + H - 32; +hex_to_upper(H) when $0 =< H, H =< $9;$A =< H, H =< $F-> + H; +hex_to_upper(H) -> + throw({error,invalid_input, H}). %% Check if char is allowed in host -spec is_host(char()) -> boolean(). @@ -1850,13 +1894,12 @@ dissect_query_key(<<$=,T/binary>>, IsList, Acc, Key, Value) -> dissect_query_value(T, IsList, Acc, Key, Value); dissect_query_key(<<"&#",T/binary>>, IsList, Acc, Key, Value) -> dissect_query_key(T, IsList, Acc, <<Key/binary,"&#">>, Value); -dissect_query_key(<<$&,_T/binary>>, _IsList, _Acc, _Key, _Value) -> - throw({error, missing_value, "&"}); +dissect_query_key(T = <<$&,_/binary>>, IsList, Acc, Key, <<>>) -> + dissect_query_value(T, IsList, Acc, Key, true); dissect_query_key(<<H,T/binary>>, IsList, Acc, Key, Value) -> dissect_query_key(T, IsList, Acc, <<Key/binary,H>>, Value); -dissect_query_key(B, _, _, _, _) -> - throw({error, missing_value, B}). - +dissect_query_key(T = <<>>, IsList, Acc, Key, <<>>) -> + dissect_query_value(T, IsList, Acc, Key, true). dissect_query_value(<<$&,T/binary>>, IsList, Acc, Key, Value) -> K = form_urldecode(IsList, Key), @@ -1869,9 +1912,10 @@ dissect_query_value(<<>>, IsList, Acc, Key, Value) -> V = form_urldecode(IsList, Value), lists:reverse([{K,V}|Acc]). - %% 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) -> + true; form_urldecode(true, B) -> Result = base10_decode(form_urldecode(B, <<>>)), convert_to_list(Result, utf8); @@ -1925,9 +1969,10 @@ base10_decode_unicode(<<H,_/binary>>, _, _) -> %%------------------------------------------------------------------------- normalize_map(URIMap) -> - normalize_path_segment( - normalize_scheme_based( - normalize_case(URIMap))). + normalize_path_segment( + normalize_scheme_based( + normalize_percent_encoding( + normalize_case(URIMap)))). %% 6.2.2.1. Case Normalization @@ -1942,6 +1987,18 @@ normalize_case(#{} = Map) -> Map. +%% 6.2.2.2. Percent-Encoding Normalization +normalize_percent_encoding(Map) -> + Fun = fun (K,V) when K =:= userinfo; K =:= host; K =:= path; + K =:= query; K =:= fragment -> + decode(V); + %% Handle port and scheme + (_,V) -> + V + end, + maps:map(Fun, Map). + + to_lower(Cs) when is_list(Cs) -> B = convert_to_binary(Cs, utf8, utf8), convert_to_list(to_lower(B), utf8); diff --git a/lib/stdlib/src/zip.erl b/lib/stdlib/src/zip.erl index 39be2abff6..a922bf3fbe 100644 --- a/lib/stdlib/src/zip.erl +++ b/lib/stdlib/src/zip.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2006-2017. All Rights Reserved. +%% Copyright Ericsson AB 2006-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. |