diff options
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r-- | lib/stdlib/src/erl_lint.erl | 78 | ||||
-rw-r--r-- | lib/stdlib/src/erl_pp.erl | 116 | ||||
-rw-r--r-- | lib/stdlib/src/erl_tar.erl | 59 | ||||
-rw-r--r-- | lib/stdlib/src/ets.erl | 28 | ||||
-rw-r--r-- | lib/stdlib/src/io_lib.erl | 24 | ||||
-rw-r--r-- | lib/stdlib/src/io_lib_pretty.erl | 14 | ||||
-rw-r--r-- | lib/stdlib/src/otp_internal.erl | 176 | ||||
-rw-r--r-- | lib/stdlib/src/rand.erl | 521 | ||||
-rw-r--r-- | lib/stdlib/src/re.erl | 7 | ||||
-rw-r--r-- | lib/stdlib/src/shell.erl | 17 |
10 files changed, 765 insertions, 275 deletions
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index 0ffca0886f..78b7a0e751 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -156,6 +156,8 @@ format_error(pmod_unsupported) -> "parameterized modules are no longer supported"; %% format_error({redefine_mod_import, M, P}) -> %% io_lib:format("module '~s' already imported from package '~s'", [M, P]); +format_error(non_latin1_module_unsupported) -> + "module names with non-latin1 characters are not supported"; format_error(invalid_call) -> "invalid function call"; @@ -402,6 +404,10 @@ format_error({not_exported_opaque, {TypeName, Arity}}) -> format_error({underspecified_opaque, {TypeName, Arity}}) -> io_lib:format("opaque type ~w~s is underspecified and therefore meaningless", [TypeName, gen_type_paren(Arity)]); +format_error({bad_dialyzer_attribute,Term}) -> + io_lib:format("badly formed dialyzer attribute: ~w", [Term]); +format_error({bad_dialyzer_option,Term}) -> + io_lib:format("unknown dialyzer warning option: ~w", [Term]); %% --- obsolete? unused? --- format_error({format_error, {Fmt, Args}}) -> io_lib:format(Fmt, Args). @@ -733,9 +739,15 @@ form(Form, #lint{state=State}=St) -> start_state({attribute,Line,module,{_,_}}=Form, St0) -> St1 = add_error(Line, pmod_unsupported, St0), attribute_state(Form, St1#lint{state=attribute}); -start_state({attribute,_,module,M}, St0) -> +start_state({attribute,Line,module,M}, St0) -> St1 = St0#lint{module=M}, - St1#lint{state=attribute}; + St2 = St1#lint{state=attribute}, + case is_non_latin1_name(M) of + true -> + add_error(Line, non_latin1_module_unsupported, St2); + false -> + St2 + end; start_state(Form, St) -> Anno = case Form of {eof, L} -> erl_anno:new(L); @@ -745,6 +757,9 @@ start_state(Form, St) -> St1 = add_error(Anno, undefined_module, St), attribute_state(Form, St1#lint{state=attribute}). +is_non_latin1_name(Name) -> + lists:any(fun(C) -> C > 255 end, atom_to_list(Name)). + %% attribute_state(Form, State) -> %% State' @@ -785,8 +800,7 @@ attribute_state(Form, St) -> %% State' %% Allow for record, type and opaque type definitions and spec %% declarations to be intersperced within function definitions. -%% Dialyzer attributes are also allowed everywhere, but are not -%% checked at all. +%% Dialyzer attributes are also allowed everywhere. function_state({attribute,L,record,{Name,Fields}}, St) -> record_def(L, Name, Fields, St); @@ -872,7 +886,8 @@ post_traversal_check(Forms, St0) -> StD = check_on_load(StC), StE = check_unused_records(Forms, StD), StF = check_local_opaque_types(StE), - check_callback_information(StF). + StG = check_dialyzer_attribute(Forms, StF), + check_callback_information(StG). %% check_behaviour(State0) -> State %% Check that the behaviour attribute is valid. @@ -3105,6 +3120,59 @@ check_local_opaque_types(St) -> end, dict:fold(FoldFun, St, Ts). +check_dialyzer_attribute(Forms, St0) -> + Vals = [{L,V} || + {attribute,L,dialyzer,Val} <- Forms, + V0 <- lists:flatten([Val]), + V <- case V0 of + {O,F} -> + [{A,B} || + A <- lists:flatten([O]), + B <- lists:flatten([F])]; + T -> [T] + end], + {Wellformed, Bad} = + lists:partition(fun ({_,{Option,FA}}) when is_atom(Option) -> + is_fa(FA); + ({_,Option}) when is_atom(Option) -> true; + (_) -> false + end, Vals), + St1 = foldl(fun ({L,Term}, St) -> + add_error(L, {bad_dialyzer_attribute,Term}, St) + end, St0, Bad), + DefFunctions = (gb_sets:to_list(St0#lint.defined) -- pseudolocals()), + Fun = fun ({L,{Option,FA}}, St) -> + case is_function_dialyzer_option(Option) of + true -> + case lists:member(FA, DefFunctions) of + true -> St; + false -> + add_error(L, {undefined_function,FA}, St) + end; + false -> + add_error(L, {bad_dialyzer_option,Option}, St) + end; + ({L,Option}, St) -> + case is_module_dialyzer_option(Option) of + true -> St; + false -> + add_error(L, {bad_dialyzer_option,Option}, St) + end + end, + foldl(Fun, St1, Wellformed). + +is_function_dialyzer_option(nowarn_function) -> true; +is_function_dialyzer_option(Option) -> + is_module_dialyzer_option(Option). + +is_module_dialyzer_option(Option) -> + lists:member(Option, + [no_return,no_unused,no_improper_lists,no_fun_app, + no_match,no_opaque,no_fail_call,no_contracts, + no_behaviours,no_undefined_callbacks,unmatched_returns, + error_handling,race_conditions,no_missing_calls, + specdiffs,overspecs,underspecs,unknown]). + %% icrt_clauses(Clauses, In, ImportVarTable, State) -> %% {UpdVt,State}. diff --git a/lib/stdlib/src/erl_pp.erl b/lib/stdlib/src/erl_pp.erl index 6068afb293..ee5e7a11bf 100644 --- a/lib/stdlib/src/erl_pp.erl +++ b/lib/stdlib/src/erl_pp.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2016. 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. @@ -44,7 +44,7 @@ | {encoding, latin1 | unicode | utf8}). -type(options() :: hook_function() | [option()]). --record(pp, {string_fun, char_fun}). +-record(pp, {value_fun, string_fun, char_fun}). -record(options, {hook, encoding, opts}). @@ -214,11 +214,15 @@ state(_Hook) -> state(). state() -> - #pp{string_fun = fun io_lib:write_string_as_latin1/1, + Options = [{encoding,latin1}], + #pp{value_fun = fun(V) -> io_lib_pretty:print(V, Options) end, + string_fun = fun io_lib:write_string_as_latin1/1, char_fun = fun io_lib:write_char_as_latin1/1}. unicode_state() -> - #pp{string_fun = fun io_lib:write_string/1, + Options = [{encoding,unicode}], + #pp{value_fun = fun(V) -> io_lib_pretty:print(V, Options) end, + string_fun = fun io_lib:write_string/1, char_fun = fun io_lib:write_char/1}. encoding(Options) -> @@ -253,31 +257,30 @@ lattribute({attribute,_Line,Name,Arg}, Opts) -> lattribute(module, {M,Vs}, _Opts) -> A = a0(), - attr("module",[{var,A,pname(M)}, - foldr(fun(V, C) -> {cons,A,{var,A,V},C} - end, {nil,A}, Vs)]); + attr(module,[{var,A,pname(M)}, + foldr(fun(V, C) -> {cons,A,{var,A,V},C} + end, {nil,A}, Vs)]); lattribute(module, M, _Opts) -> - attr("module", [{var,a0(),pname(M)}]); + attr(module, [{var,a0(),pname(M)}]); lattribute(export, Falist, _Opts) -> - call({var,a0(),"-export"}, [falist(Falist)], 0, options(none)); + attrib(export, falist(Falist)); lattribute(import, Name, _Opts) when is_list(Name) -> - attr("import", [{var,a0(),pname(Name)}]); + attr(import, [{var,a0(),pname(Name)}]); lattribute(import, {From,Falist}, _Opts) -> - attr("import",[{var,a0(),pname(From)},falist(Falist)]); + attrib(import, [leaf(pname(From)),falist(Falist)]); lattribute(export_type, Talist, _Opts) -> - call({var,a0(),"-export_type"}, [falist(Talist)], 0, options(none)); + attrib(export_type, falist(Talist)); lattribute(optional_callbacks, Falist, Opts) -> - ArgL = try falist(Falist) - catch _:_ -> abstract(Falist, Opts) - end, - call({var,a0(),"-optional_callbacks"}, [ArgL], 0, options(none)); + try attrib(optional_callbacks, falist(Falist)) + catch _:_ -> attr(optional_callbacks, [abstract(Falist, Opts)]) + end; lattribute(file, {Name,Line}, _Opts) -> - attr("file", [{string,a0(),Name},{integer,a0(),Line}]); + attr(file, [{string,a0(),Name},{integer,a0(),Line}]); lattribute(record, {Name,Is}, Opts) -> - Nl = leaf(format("-record(~w,", [Name])), + Nl = [leaf("-record("),{atom,Name},$,], [{first,Nl,record_fields(Is, Opts)},$)]; lattribute(Name, Arg, Options) -> - attr(write(Name), [abstract(Arg, Options)]). + attr(Name, [abstract(Arg, Options)]). abstract(Arg, #options{encoding = Encoding}) -> erl_parse:abstract(Arg, [{encoding,Encoding}]). @@ -340,7 +343,7 @@ ltype({user_type,Line,T,Ts}, _) -> ltype({remote_type,Line,[M,F,Ts]}, _) -> simple_type({remote,Line,M,F}, Ts); ltype({atom,_,T}, _) -> - leaf(write(T)); + {atom,T}; ltype(E, P) -> lexpr(E, P, options(none)). @@ -382,12 +385,12 @@ tuple_type(Ts, F) -> specattr(SpecKind, {FuncSpec,TypeSpecs}) -> Func = case FuncSpec of {F,_A} -> - format("~w", [F]); + {atom,F}; {M,F,_A} -> - format("~w:~w", [M, F]) + [{atom,M},$:,{atom,F}] end, {first,leaf(lists:concat(["-", SpecKind, " "])), - {list,[{first,leaf(Func),spec_clauses(TypeSpecs)}]}}. + {list,[{first,Func,spec_clauses(TypeSpecs)}]}}. spec_clauses(TypeSpecs) -> {prefer_nl,[$;],[sig_type(T) || T <- TypeSpecs]}. @@ -429,7 +432,10 @@ ltypes(Ts, F, Prec) -> [F(T, Prec) || T <- Ts]. attr(Name, Args) -> - call({var,a0(),format("-~s", [Name])}, Args, 0, options(none)). + {first,[$-,{atom,Name}],args(Args, options(none))}. + +attrib(Name, Args) -> + {first,[$-,{atom,Name}],[{seq,$(,$),[$,],Args}]}. pname(['' | As]) -> [$. | pname(As)]; @@ -441,10 +447,13 @@ pname(A) when is_atom(A) -> write(A). falist([]) -> - {nil,a0()}; -falist([{Name,Arity}|Falist]) -> - A = a0(), - {cons,A,{var,A,format("~w/~w", [Name,Arity])},falist(Falist)}. + [leaf("[]")]; +falist(Falist) -> + L = [begin + {Name,Arity} = Fa, + [{atom,Name},leaf(format("/~w", [Arity]))] + end || Fa <- Falist], + [{seq,$[,$],$,,L}]. lfunction({function,_Line,Name,_Arity,Cs}, Opts) -> Cll = nl_clauses(fun (C, H) -> func_clause(Name, C, H) end, $;, Opts, Cs), @@ -489,7 +498,7 @@ lexpr({var,_,V}, _, _) -> leaf(format("~ts", [V])); lexpr({char,_,C}, _, _) -> {char,C}; lexpr({integer,_,N}, _, _) -> leaf(write(N)); lexpr({float,_,F}, _, _) -> leaf(write(F)); -lexpr({atom,_,A}, _, _) -> leaf(write(A)); +lexpr({atom,_,A}, _, _) -> {atom,A}; lexpr({string,_,S}, _, _) -> {string,S}; lexpr({nil,_}, _, _) -> '[]'; lexpr({cons,_,H,T}, _, Opts) -> @@ -519,7 +528,7 @@ lexpr({record, _, Name, Fs}, Prec, Opts) -> lexpr({record_field, _, Rec, Name, F}, Prec, Opts) -> {L,P,R} = inop_prec('#'), Rl = lexpr(Rec, L, Opts), - Nl = leaf(format("#~w.", [Name])), + Nl = [$#,{atom,Name},$.], El = [Rl,Nl,lexpr(F, R, Opts)], maybe_paren(P, Prec, El); lexpr({record, _, Rec, Name, Fs}, Prec, Opts) -> @@ -538,12 +547,12 @@ lexpr({record_field, _, Rec, F}, Prec, Opts) -> maybe_paren(P, Prec, El); lexpr({map, _, Fs}, Prec, Opts) -> {P,_R} = preop_prec('#'), - El = {first,leaf("#"),map_fields(Fs, Opts)}, + El = {first,$#,map_fields(Fs, Opts)}, maybe_paren(P, Prec, El); lexpr({map, _, Map, Fs}, Prec, Opts) -> {L,P,_R} = inop_prec('#'), Rl = lexpr(Map, L, Opts), - El = {first,[Rl,leaf("#")],map_fields(Fs, Opts)}, + El = {first,[Rl,$#],map_fields(Fs, Opts)}, maybe_paren(P, Prec, El); lexpr({block,_,Es}, _, Opts) -> {list,[{step,'begin',body(Es, Opts)},'end']}; @@ -563,13 +572,16 @@ lexpr({'receive',_,Cs,To,ToOpt}, _, Opts) -> {step,'after',Al}, 'end']}; lexpr({'fun',_,{function,F,A}}, _Prec, _Opts) -> - leaf(format("fun ~w/~w", [F,A])); -lexpr({'fun',_,{function,F,A},Extra}, _Prec, _Opts) -> - {force_nl,fun_info(Extra),leaf(format("fun ~w/~w", [F,A]))}; -lexpr({'fun',_,{function,M,F,A}}, _Prec, _Opts) + [leaf("fun "),{atom,F},leaf(format("/~w", [A]))]; +lexpr({'fun',L,{function,_,_}=Func,Extra}, Prec, Opts) -> + {force_nl,fun_info(Extra),lexpr({'fun',L,Func}, Prec, Opts)}; +lexpr({'fun',L,{function,M,F,A}}, Prec, Opts) when is_atom(M), is_atom(F), is_integer(A) -> %% For backward compatibility with pre-R15 abstract format. - leaf(format("fun ~w:~w/~w", [M,F,A])); + Mod = erl_parse:abstract(M), + Fun = erl_parse:abstract(F), + Arity = erl_parse:abstract(A), + lexpr({'fun',L,{function,Mod,Fun,Arity}}, Prec, Opts); lexpr({'fun',_,{function,M,F,A}}, _Prec, Opts) -> %% New format in R15. NameItem = lexpr(M, Opts), @@ -660,7 +672,7 @@ lexpr({bin,_,Fs}, _, Opts) -> bit_grp(Fs, Opts); %% Special case for straight values. lexpr({value,_,Val}, _,_) -> - leaf(write(Val)); + {value,Val}; %% Now do the hook. lexpr(Other, _Precedence, #options{hook = none}) -> leaf(format("INVALID-FORM:~w:",[Other])); @@ -676,7 +688,7 @@ call(Name, Args, Prec, Opts) -> maybe_paren(P, Prec, Item). fun_info(Extra) -> - leaf(format("% fun-info: ~w", [Extra])). + [leaf("% fun-info: "),{value,Extra}]. %% BITS: @@ -717,7 +729,7 @@ bit_elem_type(T) -> %% end of BITS record_name(Name) -> - leaf(format("#~w", [Name])). + [$#,{atom,Name}]. record_fields(Fs, Opts) -> tuple(Fs, fun record_field/2, Opts). @@ -919,8 +931,10 @@ frmt(Item, I, PP) -> %%% - {force_nl,ExtraInfo,I}: fun-info (a comment) forces linebreak before I. %%% - {prefer_nl,Sep,IPs}: forces linebreak between Is unlesss negative %%% indentation. +%%% - {atom,A}: an atom %%% - {char,C}: a character %%% - {string,S}: a string. +%%% - {value,T}: a term. %%% - {hook,...}, {ehook,...}: hook expressions. %%% %%% list, first, seq, force_nl, and prefer_nl all accept IPs, where each @@ -981,6 +995,10 @@ f({prefer_nl,Sep,LItems}, I0, ST, WT, PP) -> true -> {insert_newlines(CharsSize2L, I0, ST),nsz(lists:last(Sizes), I0)} end; +f({value,V}, I, ST, WT, PP) -> + f(write_a_value(V, PP), I, ST, WT, PP); +f({atom,A}, I, ST, WT, PP) -> + f(write_an_atom(A, PP), I, ST, WT, PP); f({char,C}, I, ST, WT, PP) -> f(write_a_char(C, PP), I, ST, WT, PP); f({string,S}, I, ST, WT, PP) -> @@ -1119,6 +1137,12 @@ has_nl([C|Cs]) -> has_nl([]) -> false. +write_a_value(V, PP) -> + flat_leaf(write_value(V, PP)). + +write_an_atom(A, PP) -> + flat_leaf(write_atom(A, PP)). + write_a_char(C, PP) -> flat_leaf(write_char(C, PP)). @@ -1135,7 +1159,7 @@ write_a_string([], _N, _Len, _PP) -> write_a_string(S, N, Len, PP) -> SS = string:sub_string(S, 1, N), Sl = write_string(SS, PP), - case (length(Sl) > Len) and (N > ?MIN_SUBSTRING) of + case (chars_size(Sl) > Len) and (N > ?MIN_SUBSTRING) of true -> write_a_string(S, N-1, Len, PP); false -> @@ -1147,11 +1171,17 @@ flat_leaf(S) -> L = lists:flatten(S), {leaf,length(L),L}. +write_value(V, PP) -> + (PP#pp.value_fun)(V). + +write_atom(A, PP) -> + (PP#pp.value_fun)(A). + write_string(S, PP) -> - lists:flatten((PP#pp.string_fun)(S)). + (PP#pp.string_fun)(S). write_char(C, PP) -> - lists:flatten((PP#pp.char_fun)(C)). + (PP#pp.char_fun)(C). %% %% Utilities diff --git a/lib/stdlib/src/erl_tar.erl b/lib/stdlib/src/erl_tar.erl index a54df939bf..168ea4002c 100644 --- a/lib/stdlib/src/erl_tar.erl +++ b/lib/stdlib/src/erl_tar.erl @@ -69,6 +69,8 @@ format_error(invalid_gnu_1_0_sparsemap) -> "Invalid GNU sparse map (version 1.0)"; format_error({invalid_gnu_0_1_sparsemap, Format}) -> lists:flatten(io_lib:format("Invalid GNU sparse map (version ~s)", [Format])); +format_error(unsafe_path) -> + "The path points above the current working directory"; format_error({Name,Reason}) -> lists:flatten(io_lib:format("~ts: ~ts", [Name,format_error(Reason)])); format_error(Atom) when is_atom(Atom) -> @@ -120,26 +122,38 @@ do_extract(Handle, Opts) when is_list(Opts) -> extract1(eof, Reader, _, Acc) when is_list(Acc) -> {ok, {ok, lists:reverse(Acc)}, Reader}; +extract1(eof, Reader, _, leading_slash) -> + error_logger:info_msg("erl_tar: removed leading '/' from member names\n"), + {ok, ok, Reader}; extract1(eof, Reader, _, Acc) -> {ok, Acc, Reader}; -extract1(#tar_header{name=Name,size=Size}=Header, Reader, Opts, Acc) -> +extract1(#tar_header{name=Name,size=Size}=Header, Reader0, Opts, Acc0) -> case check_extract(Name, Opts) of true -> - case do_read(Reader, Size) of - {ok, Bin, Reader2} -> - case write_extracted_element(Header, Bin, Opts) of - ok -> - {ok, Acc, Reader2}; - {ok, NameBin} when is_list(Acc) -> - {ok, [NameBin | Acc], Reader2}; - {error, _} = Err -> - throw(Err) - end; + case do_read(Reader0, Size) of + {ok, Bin, Reader1} -> + Acc = extract2(Header, Bin, Opts, Acc0), + {ok, Acc, Reader1}; {error, _} = Err -> throw(Err) end; false -> - {ok, Acc, skip_file(Reader)} + {ok, Acc0, skip_file(Reader0)} + end. + +extract2(Header, Bin, Opts, Acc) -> + case write_extracted_element(Header, Bin, Opts) of + ok -> + case Header of + #tar_header{name="/"++_} -> + leading_slash; + #tar_header{} -> + Acc + end; + {ok, NameBin} when is_list(Acc) -> + [NameBin | Acc]; + {error, _} = Err -> + throw(Err) end. %% Checks if the file Name should be extracted. @@ -1052,14 +1066,11 @@ unpack_modern(Format, #header_v7{}=V7, Bin, #tar_header{}=Header0) safe_join_path([], Name) -> - strip_slashes(Name, both); + filename:join([Name]); safe_join_path(Prefix, []) -> - strip_slashes(Prefix, right); + filename:join([Prefix]); safe_join_path(Prefix, Name) -> - filename:join(strip_slashes(Prefix, right), strip_slashes(Name, both)). - -strip_slashes(Str, Direction) -> - string:strip(Str, Direction, $/). + filename:join(Prefix, Name). new_sparse_file_reader(Reader, Sparsemap, RealSize) -> true = validate_sparse_entries(Sparsemap, RealSize), @@ -1557,7 +1568,7 @@ write_extracted_element(#tar_header{name=Name,typeflag=Type}, ok end; write_extracted_element(#tar_header{name=Name0}=Header, Bin, Opts) -> - Name1 = filename:absname(Name0, Opts#read_opts.cwd), + Name1 = make_safe_path(Name0, Opts), Created = case typeflag(Header#tar_header.typeflag) of regular -> @@ -1585,6 +1596,16 @@ write_extracted_element(#tar_header{name=Name0}=Header, Bin, Opts) -> not_written -> ok end. +make_safe_path([$/|Path], Opts) -> + make_safe_path(Path, Opts); +make_safe_path(Path, #read_opts{cwd=Cwd}) -> + case filename:safe_relative_path(Path) of + unsafe -> + throw({error,{Path,unsafe_path}}); + SafePath -> + filename:absname(SafePath, Cwd) + end. + create_regular(Name, NameInArchive, Bin, Opts) -> case write_extracted_file(Name, Bin, Opts) of not_written -> diff --git a/lib/stdlib/src/ets.erl b/lib/stdlib/src/ets.erl index d6fd1e3ea1..195a407570 100644 --- a/lib/stdlib/src/ets.erl +++ b/lib/stdlib/src/ets.erl @@ -70,15 +70,33 @@ match_object/2, match_object/3, match_spec_compile/1, match_spec_run_r/3, member/2, new/2, next/2, prev/2, rename/2, safe_fixtable/2, select/1, select/2, select/3, - select_count/2, select_delete/2, select_reverse/1, + 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]). +%% internal exports +-export([internal_request_all/0]). + -spec all() -> [Tab] when Tab :: tab(). all() -> + receive_all(ets:internal_request_all(), + erlang:system_info(schedulers), + []). + +receive_all(_Ref, 0, All) -> + All; +receive_all(Ref, N, All) -> + receive + {Ref, SchedAll} -> + receive_all(Ref, N-1, SchedAll ++ All) + end. + +-spec internal_request_all() -> reference(). + +internal_request_all() -> erlang:nif_error(undef). -spec delete(Tab) -> true when @@ -361,6 +379,14 @@ select_count(_, _) -> select_delete(_, _) -> erlang:nif_error(undef). +-spec select_replace(Tab, MatchSpec) -> NumReplaced when + Tab :: tab(), + MatchSpec :: match_spec(), + NumReplaced :: non_neg_integer(). + +select_replace(_, _) -> + erlang:nif_error(undef). + -spec select_reverse(Tab, MatchSpec) -> [Match] when Tab :: tab(), MatchSpec :: match_spec(), diff --git a/lib/stdlib/src/io_lib.erl b/lib/stdlib/src/io_lib.erl index a91143a764..28e5007e5a 100644 --- a/lib/stdlib/src/io_lib.erl +++ b/lib/stdlib/src/io_lib.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2016. 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. @@ -68,8 +68,8 @@ -export([write_atom/1,write_string/1,write_string/2,write_latin1_string/1, write_latin1_string/2, write_char/1, write_latin1_char/1]). --export([write_string_as_latin1/1, write_string_as_latin1/2, - write_char_as_latin1/1]). +-export([write_atom_as_latin1/1, write_string_as_latin1/1, + write_string_as_latin1/2, write_char_as_latin1/1]). -export([quote_atom/2, char_list/1, latin1_char_list/1, deep_char_list/1, deep_latin1_char_list/1, @@ -344,6 +344,11 @@ write_binary_body(B, _D) -> <<X:L>> = B, [integer_to_list(X),$:,integer_to_list(L)]. +%%% There are two functions to write Unicode atoms: +%%% - they both escape control characters < 160; +%%% - write_atom() never escapes characters >= 160; +%%% - write_atom_as_latin1() also escapes characters >= 255. + %% write_atom(Atom) -> [Char] %% Generate the list of characters needed to print an atom. @@ -351,17 +356,26 @@ write_binary_body(B, _D) -> Atom :: atom(). write_atom(Atom) -> + write_possibly_quoted_atom(Atom, fun write_string/2). + +-spec write_atom_as_latin1(Atom) -> latin1_string() when + Atom :: atom(). + +write_atom_as_latin1(Atom) -> + write_possibly_quoted_atom(Atom, fun write_string_as_latin1/2). + +write_possibly_quoted_atom(Atom, PFun) -> Chars = atom_to_list(Atom), case quote_atom(Atom, Chars) of true -> - write_string(Chars, $'); %' + PFun(Chars, $'); %' false -> Chars end. %% quote_atom(Atom, CharList) %% Return 'true' if atom with chars in CharList needs to be quoted, else -%% return 'false'. +%% return 'false'. Notice that characters >= 160 are always quoted. -spec quote_atom(atom(), chars()) -> boolean(). diff --git a/lib/stdlib/src/io_lib_pretty.erl b/lib/stdlib/src/io_lib_pretty.erl index aabccfc5d9..ff368d02da 100644 --- a/lib/stdlib/src/io_lib_pretty.erl +++ b/lib/stdlib/src/io_lib_pretty.erl @@ -105,6 +105,8 @@ print(_, _, _, 0, _M, _RF, _Enc, _Str) -> "..."; print(Term, Col, Ll, D, M, RecDefFun, Enc, Str) when Col =< 0 -> %% ensure Col is at least 1 print(Term, 1, Ll, D, M, RecDefFun, Enc, Str); +print(Atom, _Col, _Ll, _D, _M, _RF, Enc, _Str) when is_atom(Atom) -> + write_atom(Atom, Enc); print(Term, Col, Ll, D, M0, RecDefFun, Enc, Str) when is_tuple(Term); is_list(Term); is_map(Term); @@ -407,6 +409,9 @@ print_length({}, _D, _RF, _Enc, _Str) -> {"{}", 2}; print_length(#{}=M, _D, _RF, _Enc, _Str) when map_size(M) =:= 0 -> {"#{}", 3}; +print_length(Atom, _D, _RF, Enc, _Str) when is_atom(Atom) -> + S = write_atom(Atom, Enc), + {S, lists:flatlength(S)}; print_length(List, D, RF, Enc, Str) when is_list(List) -> %% only flat lists are "printable" case Str andalso printable_list(List, D, Enc) of @@ -500,7 +505,7 @@ print_length_tuple(Tuple, D, RF, Enc, Str) -> print_length_record(_Tuple, 1, _RF, _RDefs, _Enc, _Str) -> {"{...}", 5}; print_length_record(Tuple, D, RF, RDefs, Enc, Str) -> - Name = [$# | io_lib:write_atom(element(1, Tuple))], + Name = [$# | write_atom(element(1, Tuple), Enc)], NameL = length(Name), Elements = tl(tuple_to_list(Tuple)), L = print_length_fields(RDefs, D - 1, Elements, RF, Enc, Str), @@ -515,7 +520,7 @@ print_length_fields([Def | Defs], D, [E | Es], RF, Enc, Str) -> print_length_fields(Defs, D - 1, Es, RF, Enc, Str)]. print_length_field(Def, D, E, RF, Enc, Str) -> - Name = io_lib:write_atom(Def), + Name = write_atom(Def, Enc), {S, L} = print_length(E, D, RF, Enc, Str), NameL = length(Name) + 3, {{field, Name, NameL, {S, L}}, NameL + L}. @@ -664,6 +669,11 @@ printable_char(C,unicode) -> C > 16#DFFF andalso C < 16#FFFE orelse C > 16#FFFF andalso C =< 16#10FFFF. +write_atom(A, latin1) -> + io_lib:write_atom_as_latin1(A); +write_atom(A, _Uni) -> + io_lib:write_atom(A). + write_string(S, latin1) -> io_lib:write_latin1_string(S, $"); %" write_string(S, _Uni) -> diff --git a/lib/stdlib/src/otp_internal.erl b/lib/stdlib/src/otp_internal.erl index fda7a2cd8a..d89ff4a624 100644 --- a/lib/stdlib/src/otp_internal.erl +++ b/lib/stdlib/src/otp_internal.erl @@ -55,6 +55,11 @@ obsolete_1(erlang, now, 0) -> obsolete_1(calendar, local_time_to_universal_time, 1) -> {deprecated, {calendar, local_time_to_universal_time_dst, 1}}; +%% *** CRYPTO added in OTP 20 *** + +obsolete_1(crypto, rand_uniform, 2) -> + {deprecated, {rand, uniform, 1}}; + %% *** CRYPTO added in OTP 19 *** obsolete_1(crypto, rand_bytes, 1) -> @@ -63,178 +68,178 @@ obsolete_1(crypto, rand_bytes, 1) -> %% *** CRYPTO added in R16B01 *** obsolete_1(crypto, md4, 1) -> - {deprecated, {crypto, hash, 2}}; + {removed, {crypto, hash, 2}, "20.0"}; obsolete_1(crypto, md5, 1) -> - {deprecated, {crypto, hash, 2}}; + {removed, {crypto, hash, 2}, "20.0"}; obsolete_1(crypto, sha, 1) -> - {deprecated, {crypto, hash, 2}}; + {removed, {crypto, hash, 2}, "20.0"}; obsolete_1(crypto, md4_init, 0) -> - {deprecated, {crypto, hash_init, 1}}; + {removed, {crypto, hash_init, 1}, "20.0"}; obsolete_1(crypto, md5_init, 0) -> - {deprecated, {crypto, hash_init, 1}}; + {removed, {crypto, hash_init, 1}, "20.0"}; obsolete_1(crypto, sha_init, 0) -> - {deprecated, {crypto, hash_init, 1}}; + {removed, {crypto, hash_init, 1}, "20.0"}; obsolete_1(crypto, md4_update, 2) -> - {deprecated, {crypto, hash_update, 2}}; + {removed, {crypto, hash_update, 2}, "20.0"}; obsolete_1(crypto, md5_update, 2) -> - {deprecated, {crypto, hash_update, 2}}; + {removed, {crypto, hash_update, 2}, "20.0"}; obsolete_1(crypto, sha_update, 2) -> - {deprecated, {crypto, hash_update, 2}}; + {removed, {crypto, hash_update, 2}, "20.0"}; obsolete_1(crypto, md4_final, 1) -> - {deprecated, {crypto, hash_final, 1}}; + {removed, {crypto, hash_final, 1}, "20.0"}; obsolete_1(crypto, md5_final, 1) -> - {deprecated, {crypto, hash_final, 1}}; + {removed, {crypto, hash_final, 1}, "20.0"}; obsolete_1(crypto, sha_final, 1) -> - {deprecated, {crypto, hash_final, 1}}; + {removed, {crypto, hash_final, 1}, "20.0"}; obsolete_1(crypto, md5_mac, 2) -> - {deprecated, {crypto, hmac, 3}}; + {removed, {crypto, hmac, 3}, "20.0"}; obsolete_1(crypto, sha_mac, 2) -> - {deprecated, {crypto, hmac, 3}}; + {removed, {crypto, hmac, 3}, "20.0"}; obsolete_1(crypto, sha_mac, 3) -> - {deprecated, {crypto, hmac, 4}}; + {removed, {crypto, hmac, 4}, "20.0"}; obsolete_1(crypto, sha_mac_96, 2) -> - {deprecated, {crypto, hmac, 4}}; + {removed, {crypto, hmac, 4}, "20.0"}; obsolete_1(crypto, md5_mac_96, 2) -> - {deprecated, {crypto, hmac, 4}}; + {removed, {crypto, hmac, 4}, "20.0"}; obsolete_1(crypto, rsa_sign, 2) -> - {deprecated, {crypto, sign, 4}}; + {removed, {crypto, sign, 4}, "20.0"}; obsolete_1(crypto, rsa_sign, 3) -> - {deprecated, {crypto, sign, 4}}; + {removed, {crypto, sign, 4}, "20.0"}; obsolete_1(crypto, rsa_verify, 3) -> - {deprecated, {crypto, verify, 5}}; + {removed, {crypto, verify, 5}, "20.0"}; obsolete_1(crypto, rsa_verify, 4) -> - {deprecated, {crypto, verify, 5}}; + {removed, {crypto, verify, 5}, "20.0"}; obsolete_1(crypto, dss_sign, 2) -> - {deprecated, {crypto, sign, 4}}; + {removed, {crypto, sign, 4}, "20.0"}; obsolete_1(crypto, dss_sign, 3) -> - {deprecated, {crypto, sign, 4}}; + {removed, {crypto, sign, 4}, "20.0"}; obsolete_1(crypto, dss_verify, 3) -> - {deprecated, {crypto, verify, 5}}; + {removed, {crypto, verify, 5}, "20.0"}; obsolete_1(crypto, dss_verify, 4) -> - {deprecated, {crypto, verify, 5}}; + {removed, {crypto, verify, 5}, "20.0"}; obsolete_1(crypto, mod_exp, 3) -> - {deprecated, {crypto, mod_pow, 3}}; + {removed, {crypto, mod_pow, 3}, "20.0"}; obsolete_1(crypto, dh_compute_key, 3) -> - {deprecated, {crypto, compute_key, 4}}; + {removed, {crypto, compute_key, 4}, "20.0"}; obsolete_1(crypto, dh_generate_key, 1) -> - {deprecated, {crypto, generate_key, 2}}; + {removed, {crypto, generate_key, 2}, "20.0"}; obsolete_1(crypto, dh_generate_key, 2) -> - {deprecated, {crypto, generate_key, 3}}; + {removed, {crypto, generate_key, 3}, "20.0"}; obsolete_1(crypto, des_cbc_encrypt, 3) -> - {deprecated, {crypto, block_encrypt, 4}}; + {removed, {crypto, block_encrypt, 4}, "20.0"}; obsolete_1(crypto, des3_cbc_encrypt, 5) -> - {deprecated, {crypto, block_encrypt, 4}}; + {removed, {crypto, block_encrypt, 4}, "20.0"}; obsolete_1(crypto, des_ecb_encrypt, 2) -> - {deprecated, {crypto, block_encrypt, 3}}; + {removed, {crypto, block_encrypt, 3}, "20.0"}; obsolete_1(crypto, des_ede3_cbc_encrypt, 5) -> - {deprecated, {crypto, block_encrypt, 4}}; + {removed, {crypto, block_encrypt, 4}, "20.0"}; obsolete_1(crypto, des_cfb_encrypt, 3) -> - {deprecated, {crypto, block_encrypt, 4}}; + {removed, {crypto, block_encrypt, 4}, "20.0"}; obsolete_1(crypto, des3_cfb_encrypt, 5) -> - {deprecated, {crypto, block_encrypt, 4}}; + {removed, {crypto, block_encrypt, 4}, "20.0"}; obsolete_1(crypto, blowfish_ecb_encrypt, 2) -> - {deprecated, {crypto, block_encrypt, 3}}; + {removed, {crypto, block_encrypt, 3}, "20.0"}; obsolete_1(crypto, blowfish_cbc_encrypt, 3) -> - {deprecated, {crypto, block_encrypt, 4}}; + {removed, {crypto, block_encrypt, 4}, "20.0"}; obsolete_1(crypto, blowfish_cfb64_encrypt, 3) -> - {deprecated, {crypto, block_encrypt, 4}}; + {removed, {crypto, block_encrypt, 4}, "20.0"}; obsolete_1(crypto, blowfish_ofb64_encrypt, 3) -> - {deprecated, {crypto, block_encrypt, 4}}; + {removed, {crypto, block_encrypt, 4}, "20.0"}; obsolete_1(crypto, aes_cfb_128_encrypt, 3) -> - {deprecated, {crypto, block_encrypt, 4}}; + {removed, {crypto, block_encrypt, 4}, "20.0"}; obsolete_1(crypto, aes_cbc_128_encrypt, 3) -> - {deprecated, {crypto, block_encrypt, 4}}; + {removed, {crypto, block_encrypt, 4}, "20.0"}; obsolete_1(crypto, aes_cbc_256_encrypt, 3) -> - {deprecated, {crypto, block_encrypt, 4}}; + {removed, {crypto, block_encrypt, 4}, "20.0"}; obsolete_1(crypto,rc2_cbc_encrypt, 3) -> - {deprecated, {crypto, block_encrypt, 4}}; + {removed, {crypto, block_encrypt, 4}, "20.0"}; obsolete_1(crypto,rc2_40_cbc_encrypt, 3) -> - {deprecated, {crypto, block_encrypt, 4}}; + {removed, {crypto, block_encrypt, 4}, "20.0"}; obsolete_1(crypto, des_cbc_decrypt, 3) -> - {deprecated, {crypto, block_decrypt, 4}}; + {removed, {crypto, block_decrypt, 4}, "20.0"}; obsolete_1(crypto, des3_cbc_decrypt, 5) -> - {deprecated, {crypto, block_decrypt, 4}}; + {removed, {crypto, block_decrypt, 4}, "20.0"}; obsolete_1(crypto, des_ecb_decrypt, 2) -> - {deprecated, {crypto, block_decrypt, 3}}; + {removed, {crypto, block_decrypt, 3}, "20.0"}; obsolete_1(crypto, des_ede3_cbc_decrypt, 5) -> - {deprecated, {crypto, block_decrypt, 4}}; + {removed, {crypto, block_decrypt, 4}, "20.0"}; obsolete_1(crypto, des_cfb_decrypt, 3) -> - {deprecated, {crypto, block_decrypt, 4}}; + {removed, {crypto, block_decrypt, 4}, "20.0"}; obsolete_1(crypto, des3_cfb_decrypt, 5) -> - {deprecated, {crypto, block_decrypt, 4}}; + {removed, {crypto, block_decrypt, 4}, "20.0"}; obsolete_1(crypto, blowfish_ecb_decrypt, 2) -> - {deprecated, {crypto, block_decrypt, 3}}; + {removed, {crypto, block_decrypt, 3}, "20.0"}; obsolete_1(crypto, blowfish_cbc_decrypt, 3) -> - {deprecated, {crypto, block_decrypt, 4}}; + {removed, {crypto, block_decrypt, 4}, "20.0"}; obsolete_1(crypto, blowfish_cfb64_decrypt, 3) -> - {deprecated, {crypto, block_decrypt, 4}}; + {removed, {crypto, block_decrypt, 4}, "20.0"}; obsolete_1(crypto, blowfish_ofb64_decrypt, 3) -> - {deprecated, {crypto, block_decrypt, 4}}; + {removed, {crypto, block_decrypt, 4}, "20.0"}; obsolete_1(crypto, aes_cfb_128_decrypt, 3) -> - {deprecated, {crypto, block_decrypt, 4}}; + {removed, {crypto, block_decrypt, 4}, "20.0"}; obsolete_1(crypto, aes_cbc_128_decrypt, 3) -> - {deprecated, {crypto, block_decrypt, 4}}; + {removed, {crypto, block_decrypt, 4}, "20.0"}; obsolete_1(crypto, aes_cbc_256_decrypt, 3) -> - {deprecated, {crypto, block_decrypt, 4}}; + {removed, {crypto, block_decrypt, 4}, "20.0"}; obsolete_1(crypto,rc2_cbc_decrypt, 3) -> - {deprecated, {crypto, block_decrypt, 4}}; + {removed, {crypto, block_decrypt, 4}, "20.0"}; obsolete_1(crypto,rc2_40_cbc_decrypt, 3) -> - {deprecated, {crypto, block_decrypt, 4}}; + {removed, {crypto, block_decrypt, 4}, "20.0"}; obsolete_1(crypto, aes_ctr_stream_decrypt, 2) -> - {deprecated, {crypto, stream_decrypt, 2}}; + {removed, {crypto, stream_decrypt, 2}, "20.0"}; obsolete_1(crypto, aes_ctr_stream_encrypt, 2) -> - {deprecated, {crypto, stream_encrypt, 2}}; + {removed, {crypto, stream_encrypt, 2}, "20.0"}; obsolete_1(crypto, aes_ctr_decrypt, 3) -> - {deprecated, {crypto, stream_decrypt, 2}}; + {removed, {crypto, stream_decrypt, 2}, "20.0"}; obsolete_1(crypto, aes_ctr_encrypt, 3) -> - {deprecated, {crypto, stream_encrypt, 2}}; + {removed, {crypto, stream_encrypt, 2}, "20.0"}; obsolete_1(crypto, rc4_encrypt, 2) -> - {deprecated, {crypto, stream_encrypt, 2}}; + {removed, {crypto, stream_encrypt, 2}, "20.0"}; obsolete_1(crypto, rc4_encrypt_with_state, 2) -> - {deprecated, {crypto, stream_encrypt, 2}}; + {removed, {crypto, stream_encrypt, 2}, "20.0"}; obsolete_1(crypto, aes_ctr_stream_init, 2) -> - {deprecated, {crypto, stream_init, 3}}; + {removed, {crypto, stream_init, 3}, "20.0"}; obsolete_1(crypto, rc4_set_key, 1) -> - {deprecated, {crypto, stream_init, 2}}; + {removed, {crypto, stream_init, 2}, "20.0"}; obsolete_1(crypto, rsa_private_decrypt, 3) -> - {deprecated, {crypto, private_decrypt, 4}}; + {removed, {crypto, private_decrypt, 4}, "20.0"}; obsolete_1(crypto, rsa_public_decrypt, 3) -> - {deprecated, {crypto, public_decrypt, 4}}; + {removed, {crypto, public_decrypt, 4}, "20.0"}; obsolete_1(crypto, rsa_private_encrypt, 3) -> - {deprecated, {crypto, private_encrypt, 4}}; + {removed, {crypto, private_encrypt, 4}, "20.0"}; obsolete_1(crypto, rsa_public_encrypt, 3) -> - {deprecated, {crypto, public_encrypt, 4}}; + {removed, {crypto, public_encrypt, 4}, "20.0"}; obsolete_1(crypto, des_cfb_ivec, 2) -> - {deprecated, {crypto, next_iv, 3}}; + {removed, {crypto, next_iv, 3}, "20.0"}; obsolete_1(crypto,des_cbc_ivec, 1) -> - {deprecated, {crypto, next_iv, 2}}; + {removed, {crypto, next_iv, 2}, "20.0"}; obsolete_1(crypto, aes_cbc_ivec, 1) -> - {deprecated, {crypto, next_iv, 2}}; + {removed, {crypto, next_iv, 2}, "20.0"}; obsolete_1(crypto,info, 0) -> - {deprecated, {crypto, module_info, 0}}; + {removed, {crypto, module_info, 0}, "20.0"}; obsolete_1(crypto, strong_rand_mpint, 3) -> - {deprecated, "needed only by deprecated functions"}; + {removed, "removed in 20.0; only needed by removed functions"}; obsolete_1(crypto, erlint, 1) -> - {deprecated, "needed only by deprecated functions"}; + {removed, "removed in 20.0; only needed by removed functions"}; obsolete_1(crypto, mpint, 1) -> - {deprecated, "needed only by deprecated functions"}; + {removed, "removed in 20.0; only needed by removed functions"}; %% *** SNMP *** @@ -387,13 +392,13 @@ obsolete_1(erlang, concat_binary, 1) -> %% Added in R14A. obsolete_1(ssl, peercert, 2) -> - {deprecated,"deprecated (will be removed in R15A); use ssl:peercert/1 and public_key:pkix_decode_cert/2 instead"}; + {removed ,"removed in R15A; use ssl:peercert/1 and public_key:pkix_decode_cert/2 instead"}; %% Added in R14B. obsolete_1(public_key, pem_to_der, 1) -> - {deprecated,"deprecated (will be removed in R15A); use file:read_file/1 and public_key:pem_decode/1"}; + {removed,"removed in R15A; use file:read_file/1 and public_key:pem_decode/1"}; obsolete_1(public_key, decode_private_key, A) when A =:= 1; A =:= 2 -> - {deprecated,{public_key,pem_entry_decode,1},"R15A"}; + {removed, "removed in R15A; use public_key:pem_entry_decode/1"}; %% Added in R14B03. obsolete_1(docb_gen, _, _) -> @@ -415,10 +420,10 @@ obsolete_1(inviso, _, _) -> obsolete_1(gs, _, _) -> {removed,"the gs application has been removed; use the wx application instead"}; obsolete_1(ssh, sign_data, 2) -> - {deprecated,"deprecated (will be removed in R16A); use public_key:pem_decode/1, public_key:pem_entry_decode/1 " + {removed,"removed in R16A; use public_key:pem_decode/1, public_key:pem_entry_decode/1 " "and public_key:sign/3 instead"}; obsolete_1(ssh, verify_data, 3) -> - {deprecated,"deprecated (will be removed in R16A); use public_key:ssh_decode/1, and public_key:verify/4 instead"}; + {removed,"removed in R16A; use public_key:ssh_decode/1, and public_key:verify/4 instead"}; %% Added in R16 obsolete_1(wxCalendarCtrl, enableYearChange, _) -> %% wx bug documented? @@ -515,10 +520,9 @@ obsolete_1(erl_parse, get_attribute, 2) -> obsolete_1(erl_lint, modify_line, 2) -> {removed,{erl_parse,map_anno,2},"19.0"}; obsolete_1(ssl, negotiated_next_protocol, 1) -> - {deprecated,{ssl,negotiated_protocol,1}}; - + {removed,"removed in 20.0; use ssl:negotiated_protocol/1 instead"}; obsolete_1(ssl, connection_info, 1) -> - {deprecated, "deprecated; use connection_information/[1,2] instead"}; + {removed, "removed in 20.0; use ssl:connection_information/[1,2] instead"}; obsolete_1(httpd_conf, check_enum, 2) -> {deprecated, "deprecated; use lists:member/2 instead"}; diff --git a/lib/stdlib/src/rand.erl b/lib/stdlib/src/rand.erl index cef83da287..ab9731180f 100644 --- a/lib/stdlib/src/rand.erl +++ b/lib/stdlib/src/rand.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2015-2016. All Rights Reserved. +%% Copyright Ericsson AB 2015-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. @@ -20,6 +20,9 @@ %% ===================================================================== %% Multiple PRNG module for Erlang/OTP %% Copyright (c) 2015-2016 Kenji Rikitake +%% +%% exrop (xoroshiro116+) added and statistical distribution +%% improvements by the Erlang/OTP team 2017 %% ===================================================================== -module(rand). @@ -32,33 +35,175 @@ ]). -compile({inline, [exs64_next/1, exsplus_next/1, - exsplus_jump/1, exs1024_next/1, exs1024_calc/2, - exs1024_jump/1, + exrop_next/1, exrop_next_s/2, get_52/1, normal_kiwi/1]}). --define(DEFAULT_ALG_HANDLER, exsplus). +-define(DEFAULT_ALG_HANDLER, exrop). -define(SEED_DICT, rand_seed). %% ===================================================================== +%% Bit fiddling macros +%% ===================================================================== + +-define(BIT(Bits), (1 bsl (Bits))). +-define(MASK(Bits), (?BIT(Bits) - 1)). +-define(MASK(Bits, X), ((X) band ?MASK(Bits))). +-define( + BSL(Bits, X, N), + %% N is evaluated 2 times + (?MASK((Bits)-(N), (X)) bsl (N))). +-define( + ROTL(Bits, X, N), + %% Bits is evaluated 2 times + %% X is evaluated 2 times + %% N i evaluated 3 times + (?BSL((Bits), (X), (N)) bor ((X) bsr ((Bits)-(N))))). + +%%-define(TWO_POW_MINUS53, (math:pow(2, -53))). +-define(TWO_POW_MINUS53, 1.11022302462515657e-16). + +%% ===================================================================== %% Types %% ===================================================================== +-type uint64() :: 0..?MASK(64). +-type uint58() :: 0..?MASK(58). + %% This depends on the algorithm handler function --type alg_seed() :: exs64_state() | exsplus_state() | exs1024_state(). -%% This is the algorithm handler function within this module --type alg_handler() :: #{type := alg(), - max := integer(), - next := fun(), - uniform := fun(), - uniform_n := fun(), - jump := fun()}. - -%% Internal state --opaque state() :: {alg_handler(), alg_seed()}. --type alg() :: exs64 | exsplus | exs1024. --opaque export_state() :: {alg(), alg_seed()}. --export_type([alg/0, state/0, export_state/0]). +-type alg_state() :: + exs64_state() | exsplus_state() | exs1024_state() | + exrop_state() | term(). + +%% This is the algorithm handling definition within this module, +%% and the type to use for plugins. +%% +%% The 'type' field must be recognized by the module that implements +%% the algorithm, to interpret an exported state. +%% +%% The 'bits' field indicates how many bits the integer +%% returned from 'next' has got, i.e 'next' shall return +%% an random integer in the range 0..(2^Bits - 1). +%% At least 53 bits is required for the floating point +%% producing fallbacks. This field is only used when +%% the 'uniform' or 'uniform_n' fields are not defined. +%% +%% The fields 'next', 'uniform' and 'uniform_n' +%% implement the algorithm. If 'uniform' or 'uinform_n' +%% is not present there is a fallback using 'next' and either +%% 'bits' or the deprecated 'max'. +%% +-type alg_handler() :: + #{type := alg(), + bits => non_neg_integer(), + weak_low_bits => non_neg_integer(), + max => non_neg_integer(), % Deprecated + next := + fun ((alg_state()) -> {non_neg_integer(), alg_state()}), + uniform => + fun ((state()) -> {float(), state()}), + uniform_n => + fun ((pos_integer(), state()) -> {pos_integer(), state()}), + jump => + fun ((state()) -> state())}. + +%% Algorithm state +-type state() :: {alg_handler(), alg_state()}. +-type builtin_alg() :: exs64 | exsplus | exsp | exs1024 | exs1024s | exrop. +-type alg() :: builtin_alg() | atom(). +-type export_state() :: {alg(), alg_state()}. +-export_type( + [builtin_alg/0, alg/0, alg_handler/0, alg_state/0, + state/0, export_state/0]). +-export_type( + [exs64_state/0, exsplus_state/0, exs1024_state/0, exrop_state/0]). + +%% ===================================================================== +%% Range macro and helper +%% ===================================================================== + +-define( + uniform_range(Range, Alg, R, V, MaxMinusRange, I), + if + 0 =< (MaxMinusRange) -> + if + %% Really work saving in odd cases; + %% large ranges in particular + (V) < (Range) -> + {(V) + 1, {(Alg), (R)}}; + true -> + (I) = (V) rem (Range), + if + (V) - (I) =< (MaxMinusRange) -> + {(I) + 1, {(Alg), (R)}}; + true -> + %% V in the truncated top range + %% - try again + ?FUNCTION_NAME((Range), {(Alg), (R)}) + end + end; + true -> + uniform_range((Range), (Alg), (R), (V)) + end). + +%% For ranges larger than the algorithm bit size +uniform_range(Range, #{next:=Next, bits:=Bits} = Alg, R, V) -> + WeakLowBits = + case Alg of + #{weak_low_bits:=WLB} -> WLB; + #{} -> 0 + end, + %% Maybe waste the lowest bit(s) when shifting in new bits + Shift = Bits - WeakLowBits, + ShiftMask = bnot ?MASK(WeakLowBits), + RangeMinus1 = Range - 1, + if + (Range band RangeMinus1) =:= 0 -> % Power of 2 + %% Generate at least the number of bits for the range + {V1, R1, _} = + uniform_range( + Range bsr Bits, Next, R, V, ShiftMask, Shift, Bits), + {(V1 band RangeMinus1) + 1, {Alg, R1}}; + true -> + %% Generate a value with at least two bits more than the range + %% and try that for a fit, otherwise recurse + %% + %% Just one bit more should ensure that the generated + %% number range is at least twice the size of the requested + %% range, which would make the probability to draw a good + %% number better than 0.5. And repeating that until + %% success i guess would take 2 times statistically amortized. + %% But since the probability for fairly many attemtpts + %% is not that low, use two bits more than the range which + %% should make the probability to draw a bad number under 0.25, + %% which decreases the bad case probability a lot. + {V1, R1, B} = + uniform_range( + Range bsr (Bits - 2), Next, R, V, ShiftMask, Shift, Bits), + I = V1 rem Range, + if + (V1 - I) =< (1 bsl B) - Range -> + {I + 1, {Alg, R1}}; + true -> + %% V1 drawn from the truncated top range + %% - try again + {V2, R2} = Next(R1), + uniform_range(Range, Alg, R2, V2) + end + end. +%% +uniform_range(Range, Next, R, V, ShiftMask, Shift, B) -> + if + Range =< 1 -> + {V, R, B}; + true -> + {V1, R1} = Next(R), + %% Waste the lowest bit(s) when shifting in new bits + uniform_range( + Range bsr Shift, Next, R1, + ((V band ShiftMask) bsl Shift) bor V1, + ShiftMask, Shift, B + Shift) + end. %% ===================================================================== %% API @@ -72,7 +217,7 @@ export_seed() -> _ -> undefined end. --spec export_seed_s(state()) -> export_state(). +-spec export_seed_s(State :: state()) -> export_state(). export_seed_s({#{type:=Alg}, Seed}) -> {Alg, Seed}. %% seed(Alg) seeds RNG with runtime dependent values @@ -81,27 +226,37 @@ export_seed_s({#{type:=Alg}, Seed}) -> {Alg, Seed}. %% seed({Alg,Seed}) setup RNG with a previously exported seed %% and return the NEW state --spec seed(AlgOrExpState::alg() | export_state()) -> state(). +-spec seed( + AlgOrStateOrExpState :: builtin_alg() | state() | export_state()) -> + state(). seed(Alg) -> seed_put(seed_s(Alg)). --spec seed_s(AlgOrExpState::alg() | export_state()) -> state(). -seed_s(Alg) when is_atom(Alg) -> - seed_s(Alg, {erlang:phash2([{node(),self()}]), - erlang:system_time(), - erlang:unique_integer()}); +-spec seed_s( + AlgOrStateOrExpState :: builtin_alg() | state() | export_state()) -> + state(). +seed_s({AlgHandler, _Seed} = State) when is_map(AlgHandler) -> + State; seed_s({Alg0, Seed}) -> {Alg,_SeedFun} = mk_alg(Alg0), - {Alg, Seed}. + {Alg, Seed}; +seed_s(Alg) -> + seed_s(Alg, {erlang:phash2([{node(),self()}]), + erlang:system_time(), + erlang:unique_integer()}). %% seed/2: seeds RNG with the algorithm and given values %% and returns the NEW state. --spec seed(Alg :: alg(), {integer(), integer(), integer()}) -> state(). +-spec seed( + Alg :: builtin_alg(), Seed :: {integer(), integer(), integer()}) -> + state(). seed(Alg0, S0) -> seed_put(seed_s(Alg0, S0)). --spec seed_s(Alg :: alg(), {integer(), integer(), integer()}) -> state(). +-spec seed_s( + Alg :: builtin_alg(), Seed :: {integer(), integer(), integer()}) -> + state(). seed_s(Alg0, S0 = {_, _, _}) -> {Alg, Seed} = mk_alg(Alg0), AS = Seed(S0), @@ -113,7 +268,7 @@ seed_s(Alg0, S0 = {_, _, _}) -> %% uniform/0: returns a random float X where 0.0 < X < 1.0, %% updating the state in the process dictionary. --spec uniform() -> X::float(). +-spec uniform() -> X :: float(). uniform() -> {X, Seed} = uniform_s(seed_get()), _ = seed_put(Seed), @@ -123,7 +278,7 @@ uniform() -> %% uniform/1 returns a random integer X where 1 =< X =< N, %% updating the state in the process dictionary. --spec uniform(N :: pos_integer()) -> X::pos_integer(). +-spec uniform(N :: pos_integer()) -> X :: pos_integer(). uniform(N) -> {X, Seed} = uniform_s(N, seed_get()), _ = seed_put(Seed), @@ -133,39 +288,64 @@ uniform(N) -> %% returns a random float X where 0.0 < X < 1.0, %% and a new state. --spec uniform_s(state()) -> {X::float(), NewS :: state()}. +-spec uniform_s(State :: state()) -> {X :: float(), NewState :: state()}. uniform_s(State = {#{uniform:=Uniform}, _}) -> - Uniform(State). + Uniform(State); +uniform_s({#{bits:=Bits, next:=Next} = Alg, R0}) -> + {V, R1} = Next(R0), + %% Produce floats on the form N * 2^(-53) + {(V bsr (Bits - 53)) * ?TWO_POW_MINUS53, {Alg, R1}}; +uniform_s({#{max:=Max, next:=Next} = Alg, R0}) -> + {V, R1} = Next(R0), + %% Old broken algorithm with non-uniform density + {V / (Max + 1), {Alg, R1}}. + %% uniform_s/2: given an integer N >= 1 and a state, uniform_s/2 %% uniform_s/2 returns a random integer X where 1 =< X =< N, %% and a new state. --spec uniform_s(N::pos_integer(), state()) -> {X::pos_integer(), NewS::state()}. -uniform_s(N, State = {#{uniform_n:=Uniform, max:=Max}, _}) - when 0 < N, N =< Max -> - Uniform(N, State); -uniform_s(N, State0 = {#{uniform:=Uniform}, _}) - when is_integer(N), 0 < N -> - {F, State} = Uniform(State0), - {trunc(F * N) + 1, State}. +-spec uniform_s(N :: pos_integer(), State :: state()) -> + {X :: pos_integer(), NewState :: state()}. +uniform_s(N, State = {#{uniform_n:=UniformN}, _}) + when is_integer(N), 1 =< N -> + UniformN(N, State); +uniform_s(N, {#{bits:=Bits, next:=Next} = Alg, R0}) + when is_integer(N), 1 =< N -> + {V, R1} = Next(R0), + MaxMinusN = ?BIT(Bits) - N, + ?uniform_range(N, Alg, R1, V, MaxMinusN, I); +uniform_s(N, {#{max:=Max, next:=Next} = Alg, R0}) + when is_integer(N), 1 =< N -> + %% Old broken algorithm with skewed probability + %% and gap in ranges > Max + {V, R1} = Next(R0), + if + N =< Max -> + {(V rem N) + 1, {Alg, R1}}; + true -> + F = V / (Max + 1), + {trunc(F * N) + 1, {Alg, R1}} + end. %% jump/1: given a state, jump/1 %% returns a new state which is equivalent to that %% after a large number of call defined for each algorithm. %% The large number is algorithm dependent. --spec jump(state()) -> NewS :: state(). +-spec jump(state()) -> NewState :: state(). jump(State = {#{jump:=Jump}, _}) -> - Jump(State). + Jump(State); +jump({#{}, _}) -> + erlang:error(not_implemented). + %% jump/0: read the internal state and %% apply the jump function for the state as in jump/1 %% and write back the new value to the internal state, %% then returns the new value. --spec jump() -> NewS :: state(). - +-spec jump() -> NewState :: state(). jump() -> seed_put(jump(seed_get())). @@ -189,10 +369,10 @@ normal(Mean, Variance) -> %% The Ziggurat Method for generating random variables - Marsaglia and Tsang %% Paper and reference code: http://www.jstatsoft.org/v05/i08/ --spec normal_s(state()) -> {float(), NewS :: state()}. +-spec normal_s(State :: state()) -> {float(), NewState :: state()}. normal_s(State0) -> {Sign, R, State} = get_52(State0), - Idx = R band 16#FF, + Idx = ?MASK(8, R), Idx1 = Idx+1, {Ki, Wi} = normal_kiwi(Idx1), X = R * Wi, @@ -215,16 +395,6 @@ normal_s(Mean, Variance, State0) when Variance > 0 -> %% ===================================================================== %% Internal functions --define(UINT21MASK, 16#00000000001fffff). --define(UINT32MASK, 16#00000000ffffffff). --define(UINT33MASK, 16#00000001ffffffff). --define(UINT39MASK, 16#0000007fffffffff). --define(UINT58MASK, 16#03ffffffffffffff). --define(UINT64MASK, 16#ffffffffffffffff). - --type uint64() :: 0..16#ffffffffffffffff. --type uint58() :: 0..16#03ffffffffffffff. - -spec seed_put(state()) -> state(). seed_put(Seed) -> put(?SEED_DICT, Seed), @@ -238,20 +408,30 @@ seed_get() -> %% Setup alg record mk_alg(exs64) -> - {#{type=>exs64, max=>?UINT64MASK, next=>fun exs64_next/1, - uniform=>fun exs64_uniform/1, uniform_n=>fun exs64_uniform/2, - jump=>fun exs64_jump/1}, + {#{type=>exs64, max=>?MASK(64), next=>fun exs64_next/1}, fun exs64_seed/1}; mk_alg(exsplus) -> - {#{type=>exsplus, max=>?UINT58MASK, next=>fun exsplus_next/1, - uniform=>fun exsplus_uniform/1, uniform_n=>fun exsplus_uniform/2, + {#{type=>exsplus, max=>?MASK(58), next=>fun exsplus_next/1, + jump=>fun exsplus_jump/1}, + fun exsplus_seed/1}; +mk_alg(exsp) -> + {#{type=>exsp, bits=>58, weak_low_bits=>1, next=>fun exsplus_next/1, + uniform=>fun exsp_uniform/1, uniform_n=>fun exsp_uniform/2, jump=>fun exsplus_jump/1}, fun exsplus_seed/1}; mk_alg(exs1024) -> - {#{type=>exs1024, max=>?UINT64MASK, next=>fun exs1024_next/1, - uniform=>fun exs1024_uniform/1, uniform_n=>fun exs1024_uniform/2, + {#{type=>exs1024, max=>?MASK(64), next=>fun exs1024_next/1, jump=>fun exs1024_jump/1}, - fun exs1024_seed/1}. + fun exs1024_seed/1}; +mk_alg(exs1024s) -> + {#{type=>exs1024s, bits=>64, weak_low_bits=>3, next=>fun exs1024_next/1, + jump=>fun exs1024_jump/1}, + fun exs1024_seed/1}; +mk_alg(exrop) -> + {#{type=>exrop, bits=>58, weak_low_bits=>1, next=>fun exrop_next/1, + uniform=>fun exrop_uniform/1, uniform_n=>fun exrop_uniform/2, + jump=>fun exrop_jump/1}, + fun exrop_seed/1}. %% ===================================================================== %% exs64 PRNG: Xorshift64* @@ -259,32 +439,21 @@ mk_alg(exs1024) -> %% Reference URL: http://xorshift.di.unimi.it/ %% ===================================================================== --type exs64_state() :: uint64(). +-opaque exs64_state() :: uint64(). exs64_seed({A1, A2, A3}) -> - {V1, _} = exs64_next(((A1 band ?UINT32MASK) * 4294967197 + 1)), - {V2, _} = exs64_next(((A2 band ?UINT32MASK) * 4294967231 + 1)), - {V3, _} = exs64_next(((A3 band ?UINT32MASK) * 4294967279 + 1)), - ((V1 * V2 * V3) rem (?UINT64MASK - 1)) + 1. + {V1, _} = exs64_next((?MASK(32, A1) * 4294967197 + 1)), + {V2, _} = exs64_next((?MASK(32, A2) * 4294967231 + 1)), + {V3, _} = exs64_next((?MASK(32, A3) * 4294967279 + 1)), + ((V1 * V2 * V3) rem (?MASK(64) - 1)) + 1. %% Advance xorshift64* state for one step and generate 64bit unsigned integer -spec exs64_next(exs64_state()) -> {uint64(), exs64_state()}. exs64_next(R) -> R1 = R bxor (R bsr 12), - R2 = R1 bxor ((R1 band ?UINT39MASK) bsl 25), + R2 = R1 bxor ?BSL(64, R1, 25), R3 = R2 bxor (R2 bsr 27), - {(R3 * 2685821657736338717) band ?UINT64MASK, R3}. - -exs64_uniform({Alg, R0}) -> - {V, R1} = exs64_next(R0), - {V / 18446744073709551616, {Alg, R1}}. - -exs64_uniform(Max, {Alg, R}) -> - {V, R1} = exs64_next(R), - {(V rem Max) + 1, {Alg, R1}}. - -exs64_jump(_) -> - erlang:error(not_implemented). + {?MASK(64, R3 * 2685821657736338717), R3}. %% ===================================================================== %% exsplus PRNG: Xorshift116+ @@ -294,15 +463,17 @@ exs64_jump(_) -> %% Modification of the original Xorshift128+ algorithm to 116 %% by Sebastiano Vigna, a lot of thanks for his help and work. %% ===================================================================== --type exsplus_state() :: nonempty_improper_list(uint58(), uint58()). +-opaque exsplus_state() :: nonempty_improper_list(uint58(), uint58()). -dialyzer({no_improper_lists, exsplus_seed/1}). exsplus_seed({A1, A2, A3}) -> - {_, R1} = exsplus_next([(((A1 * 4294967197) + 1) band ?UINT58MASK)| - (((A2 * 4294967231) + 1) band ?UINT58MASK)]), - {_, R2} = exsplus_next([(((A3 * 4294967279) + 1) band ?UINT58MASK)| - tl(R1)]), + {_, R1} = exsplus_next( + [?MASK(58, (A1 * 4294967197) + 1)| + ?MASK(58, (A2 * 4294967231) + 1)]), + {_, R2} = exsplus_next( + [?MASK(58, (A3 * 4294967279) + 1)| + tl(R1)]), R2. -dialyzer({no_improper_lists, exsplus_next/1}). @@ -311,17 +482,22 @@ exsplus_seed({A1, A2, A3}) -> -spec exsplus_next(exsplus_state()) -> {uint58(), exsplus_state()}. exsplus_next([S1|S0]) -> %% Note: members s0 and s1 are swapped here - S11 = (S1 bxor (S1 bsl 24)) band ?UINT58MASK, + S11 = S1 bxor ?BSL(58, S1, 24), S12 = S11 bxor S0 bxor (S11 bsr 11) bxor (S0 bsr 41), - {(S0 + S12) band ?UINT58MASK, [S0|S12]}. + {?MASK(58, S0 + S12), [S0|S12]}. + -exsplus_uniform({Alg, R0}) -> +exsp_uniform({Alg, R0}) -> {I, R1} = exsplus_next(R0), - {I / (?UINT58MASK+1), {Alg, R1}}. + %% Waste the lowest bit since it is of lower + %% randomness quality than the others + {(I bsr (58-53)) * ?TWO_POW_MINUS53, {Alg, R1}}. -exsplus_uniform(Max, {Alg, R}) -> +exsp_uniform(Range, {Alg, R}) -> {V, R1} = exsplus_next(R), - {(V rem Max) + 1, {Alg, R1}}. + MaxMinusRange = ?BIT(58) - Range, + ?uniform_range(Range, Alg, R1, V, MaxMinusRange, I). + %% This is the jump function for the exsplus generator, equivalent %% to 2^64 calls to next/1; it can be used to generate 2^52 @@ -349,7 +525,7 @@ exsplus_jump(S, AS, _, 0) -> {S, AS}; exsplus_jump(S, [AS0|AS1], J, N) -> {_, NS} = exsplus_next(S), - case (J band 1) of + case ?MASK(1, J) of 1 -> [S0|S1] = S, exsplus_jump(NS, [(AS0 bxor S0)|(AS1 bxor S1)], J bsr 1, N-1); @@ -363,12 +539,12 @@ exsplus_jump(S, [AS0|AS1], J, N) -> %% Reference URL: http://xorshift.di.unimi.it/ %% ===================================================================== --type exs1024_state() :: {list(uint64()), list(uint64())}. +-opaque exs1024_state() :: {list(uint64()), list(uint64())}. exs1024_seed({A1, A2, A3}) -> - B1 = (((A1 band ?UINT21MASK) + 1) * 2097131) band ?UINT21MASK, - B2 = (((A2 band ?UINT21MASK) + 1) * 2097133) band ?UINT21MASK, - B3 = (((A3 band ?UINT21MASK) + 1) * 2097143) band ?UINT21MASK, + B1 = ?MASK(21, (?MASK(21, A1) + 1) * 2097131), + B2 = ?MASK(21, (?MASK(21, A2) + 1) * 2097133), + B3 = ?MASK(21, (?MASK(21, A3) + 1) * 2097143), {exs1024_gen1024((B1 bsl 43) bor (B2 bsl 22) bor (B3 bsl 1) bor 1), []}. @@ -391,11 +567,11 @@ exs1024_gen1024(N, R, L) -> %% X: random number output -spec exs1024_calc(uint64(), uint64()) -> {uint64(), uint64()}. exs1024_calc(S0, S1) -> - S11 = S1 bxor ((S1 band ?UINT33MASK) bsl 31), + S11 = S1 bxor ?BSL(64, S1, 31), S12 = S11 bxor (S11 bsr 11), S01 = S0 bxor (S0 bsr 30), NS1 = S01 bxor S12, - {(NS1 * 1181783497276652981) band ?UINT64MASK, NS1}. + {?MASK(64, NS1 * 1181783497276652981), NS1}. %% Advance xorshift1024* state for one step and generate 64bit unsigned integer -spec exs1024_next(exs1024_state()) -> {uint64(), exs1024_state()}. @@ -406,13 +582,6 @@ exs1024_next({[H], RL}) -> NL = [H|lists:reverse(RL)], exs1024_next({NL, []}). -exs1024_uniform({Alg, R0}) -> - {V, R1} = exs1024_next(R0), - {V / 18446744073709551616, {Alg, R1}}. - -exs1024_uniform(Max, {Alg, R}) -> - {V, R1} = exs1024_next(R), - {(V rem Max) + 1, {Alg, R1}}. %% This is the jump function for the exs1024 generator, equivalent %% to 2^512 calls to next(); it can be used to generate 2^512 @@ -459,7 +628,7 @@ exs1024_jump(S, AS, [H|T], _, 0, TN) -> exs1024_jump(S, AS, T, H, ?JUMPELEMLEN, TN); exs1024_jump({L, RL}, AS, JL, J, N, TN) -> {_, NS} = exs1024_next({L, RL}), - case (J band 1) of + case ?MASK(1, J) of 1 -> AS2 = lists:zipwith(fun(X, Y) -> X bxor Y end, AS, L ++ lists:reverse(RL)), @@ -469,15 +638,149 @@ exs1024_jump({L, RL}, AS, JL, J, N, TN) -> end. %% ===================================================================== +%% exrop PRNG: Xoroshiro116+ +%% +%% Reference URL: http://xorshift.di.unimi.it/ +%% +%% 58 bits fits into an immediate on 64bits Erlang and is thus much faster. +%% In fact, an immediate number is 60 bits signed in Erlang so you can +%% add two positive 58 bit numbers and get a 59 bit number that still is +%% a positive immediate, which is a property we utilize here... +%% +%% Modification of the original Xororhiro128+ algorithm to 116 bits +%% by Sebastiano Vigna. A lot of thanks for his help and work. +%% ===================================================================== +%% (a, b, c) = (24, 2, 35) +%% JUMP Polynomial = 0x9863200f83fcd4a11293241fcb12a (116 bit) +%% +%% From http://xoroshiro.di.unimi.it/xoroshiro116plus.c: +%% --------------------------------------------------------------------- +%% /* Written in 2017 by Sebastiano Vigna ([email protected]). +%% +%% To the extent possible under law, the author has dedicated all copyright +%% and related and neighboring rights to this software to the public domain +%% worldwide. This software is distributed without any warranty. +%% +%% See <http://creativecommons.org/publicdomain/zero/1.0/>. */ +%% +%% #include <stdint.h> +%% +%% #define UINT58MASK (uint64_t)((UINT64_C(1) << 58) - 1) +%% +%% uint64_t s[2]; +%% +%% static inline uint64_t rotl58(const uint64_t x, int k) { +%% return (x << k) & UINT58MASK | (x >> (58 - k)); +%% } +%% +%% uint64_t next(void) { +%% uint64_t s1 = s[1]; +%% const uint64_t s0 = s[0]; +%% const uint64_t result = (s0 + s1) & UINT58MASK; +%% +%% s1 ^= s0; +%% s[0] = rotl58(s0, 24) ^ s1 ^ ((s1 << 2) & UINT58MASK); // a, b +%% s[1] = rotl58(s1, 35); // c +%% return result; +%% } +%% +%% void jump(void) { +%% static const uint64_t JUMP[] = +%% { 0x4a11293241fcb12a, 0x0009863200f83fcd }; +%% +%% uint64_t s0 = 0; +%% uint64_t s1 = 0; +%% for(int i = 0; i < sizeof JUMP / sizeof *JUMP; i++) +%% for(int b = 0; b < 64; b++) { +%% if (JUMP[i] & UINT64_C(1) << b) { +%% s0 ^= s[0]; +%% s1 ^= s[1]; +%% } +%% next(); +%% } +%% s[0] = s0; +%% s[1] = s1; +%% } + +-opaque exrop_state() :: nonempty_improper_list(uint58(), uint58()). + +-dialyzer({no_improper_lists, exrop_seed/1}). +exrop_seed({A1, A2, A3}) -> + [_|S1] = + exrop_next_s( + ?MASK(58, (A1 * 4294967197) + 1), + ?MASK(58, (A2 * 4294967231) + 1)), + exrop_next_s(?MASK(58, (A3 * 4294967279) + 1), S1). + +-dialyzer({no_improper_lists, exrop_next_s/2}). +%% Advance xoroshiro116+ state one step +%% [a, b, c] = [24, 2, 35] +-define( + exrop_next_s(S0, S1, S1_a), + begin + S1_a = S1 bxor S0, + [?ROTL(58, S0, 24) bxor S1_a bxor ?BSL(58, S1_a, 2)| % a, b + ?ROTL(58, S1_a, 35)] % c + end). +exrop_next_s(S0, S1) -> + ?exrop_next_s(S0, S1, S1_a). + +-dialyzer({no_improper_lists, exrop_next/1}). +%% Advance xoroshiro116+ state one step, generate 58 bit unsigned integer, +%% and waste the lowest bit since it is of lower randomness quality +exrop_next([S0|S1]) -> + {?MASK(58, S0 + S1), ?exrop_next_s(S0, S1, S1_a)}. + +exrop_uniform({Alg, R}) -> + {V, R1} = exrop_next(R), + %% Waste the lowest bit since it is of lower + %% randomness quality than the others + {(V bsr (58-53)) * ?TWO_POW_MINUS53, {Alg, R1}}. + +exrop_uniform(Range, {Alg, R}) -> + {V, R1} = exrop_next(R), + MaxMinusRange = ?BIT(58) - Range, + ?uniform_range(Range, Alg, R1, V, MaxMinusRange, I). + +%% Split a 116 bit constant into two '1'++58 bit words, +%% the top '1' marks the top of the word +-define( + JUMP_116(Jump), + [?BIT(58) bor ?MASK(58, (Jump)),?BIT(58) bor ((Jump) bsr 58)]). +%% +exrop_jump({Alg,S}) -> + [J|Js] = ?JUMP_116(16#9863200f83fcd4a11293241fcb12a), + {Alg, exrop_jump(S, 0, 0, J, Js)}. +%% +-dialyzer({no_improper_lists, exrop_jump/5}). +exrop_jump(_S, S0, S1, 1, []) -> % End of jump constant + [S0|S1]; +exrop_jump(S, S0, S1, 1, [J|Js]) -> % End of the word + exrop_jump(S, S0, S1, J, Js); +exrop_jump([S__0|S__1] = _S, S0, S1, J, Js) -> + case ?MASK(1, J) of + 1 -> + NewS = exrop_next_s(S__0, S__1), + exrop_jump(NewS, S0 bxor S__0, S1 bxor S__1, J bsr 1, Js); + 0 -> + NewS = exrop_next_s(S__0, S__1), + exrop_jump(NewS, S0, S1, J bsr 1, Js) + end. + +%% ===================================================================== %% Ziggurat cont %% ===================================================================== -define(NOR_R, 3.6541528853610087963519472518). -define(NOR_INV_R, 1/?NOR_R). %% return a {sign, Random51bits, State} +get_52({Alg=#{bits:=Bits, next:=Next}, S0}) -> + %% Use the high bits + {Int,S1} = Next(S0), + {?BIT(Bits - 51 - 1) band Int, Int bsr (Bits - 51), {Alg, S1}}; get_52({Alg=#{next:=Next}, S0}) -> {Int,S1} = Next(S0), - {((1 bsl 51) band Int), Int band ((1 bsl 51)-1), {Alg, S1}}. + {?BIT(51) band Int, ?MASK(51, Int), {Alg, S1}}. %% Slow path normal_s(0, Sign, X0, State0) -> diff --git a/lib/stdlib/src/re.erl b/lib/stdlib/src/re.erl index 52d3c35608..28aab7b590 100644 --- a/lib/stdlib/src/re.erl +++ b/lib/stdlib/src/re.erl @@ -33,7 +33,12 @@ %%% BIFs --export([compile/1, compile/2, run/2, run/3, inspect/2]). +-export([version/0, compile/1, compile/2, run/2, run/3, inspect/2]). + +-spec version() -> binary(). + +version() -> + erlang:nif_error(undef). -spec compile(Regexp) -> {ok, MP} | {error, ErrSpec} when Regexp :: iodata(), diff --git a/lib/stdlib/src/shell.erl b/lib/stdlib/src/shell.erl index 28f37ef8bf..394f4f2fa4 100644 --- a/lib/stdlib/src/shell.erl +++ b/lib/stdlib/src/shell.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2016. 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. @@ -349,10 +349,16 @@ default_prompt(N) -> %% Don't bother flattening the list irrespective of what the %% I/O-protocol states. case is_alive() of - true -> io_lib:format(<<"(~s)~w> ">>, [node(), N]); + true -> io_lib:format(<<"(~ts)~w> ">>, [node_string(), N]); false -> io_lib:format(<<"~w> ">>, [N]) end. +node_string() -> + case encoding() of + latin1 -> io_lib:write_atom_as_latin1(node()); + _ -> io_lib:write_atom(node()) + end. + %% expand_hist(Expressions, CommandNumber) %% Preprocess the expression list replacing all history list commands %% with their expansions. @@ -967,10 +973,11 @@ local_func(f, [{var,_,Name}], Bs, _Shell, _RT, _Lf, _Ef) -> {value,ok,erl_eval:del_binding(Name, Bs)}; local_func(f, [_Other], _Bs, _Shell, _RT, _Lf, _Ef) -> erlang:raise(error, function_clause, [{shell,f,1}]); -local_func(rd, [{atom,_,RecName},RecDef0], Bs, _Shell, RT, _Lf, _Ef) -> +local_func(rd, [{atom,_,RecName0},RecDef0], Bs, _Shell, RT, _Lf, _Ef) -> RecDef = expand_value(RecDef0), RDs = lists:flatten(erl_pp:expr(RecDef)), - Attr = lists:concat(["-record('", RecName, "',", RDs, ")."]), + RecName = io_lib:write_atom_as_latin1(RecName0), + Attr = lists:concat(["-record(", RecName, ",", RDs, ")."]), {ok, Tokens, _} = erl_scan:string(Attr), case erl_parse:parse_form(Tokens) of {ok,AttrForm} -> @@ -1417,9 +1424,11 @@ columns() -> {ok,N} -> N; _ -> 80 end. + encoding() -> [{encoding, Encoding}] = enc(), Encoding. + enc() -> case lists:keyfind(encoding, 1, io:getopts()) of false -> [{encoding,latin1}]; % should never happen |