diff options
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r-- | lib/stdlib/src/binary.erl | 192 | ||||
-rw-r--r-- | lib/stdlib/src/ets.erl | 438 | ||||
-rw-r--r-- | lib/stdlib/src/lists.erl | 62 | ||||
-rw-r--r-- | lib/stdlib/src/math.erl | 112 | ||||
-rw-r--r-- | lib/stdlib/src/qlc_pt.erl | 4 | ||||
-rw-r--r-- | lib/stdlib/src/re.erl | 66 | ||||
-rw-r--r-- | lib/stdlib/src/stdlib.appup.src | 12 | ||||
-rw-r--r-- | lib/stdlib/src/string.erl | 26 | ||||
-rw-r--r-- | lib/stdlib/src/unicode.erl | 48 |
9 files changed, 866 insertions, 94 deletions
diff --git a/lib/stdlib/src/binary.erl b/lib/stdlib/src/binary.erl index cb1e12ae46..0e95372a76 100644 --- a/lib/stdlib/src/binary.erl +++ b/lib/stdlib/src/binary.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2010-2011. All Rights Reserved. +%% Copyright Ericsson AB 2010-2012. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -18,29 +18,185 @@ %% -module(binary). %% -%% The following functions implemented as BIF's -%% binary:compile_pattern/1 -%% binary:match/{2,3} -%% binary:matches/{2,3} -%% binary:longest_common_prefix/1 -%% binary:longest_common_suffix/1 -%% binary:first/1 -%% binary:last/1 -%% binary:at/2 -%% binary:part/{2,3} -%% binary:bin_to_list/{1,2,3} -%% binary:list_to_bin/1 -%% binary:copy/{1,2} -%% binary:referenced_byte_size/1 -%% binary:decode_unsigned/{1,2} -%% - Not yet: -%% %% Implemented in this module: -export([split/2,split/3,replace/3,replace/4]). -opaque cp() :: tuple(). -type part() :: {Start :: non_neg_integer(), Length :: integer()}. +%%% BIFs. + +-export([at/2, bin_to_list/1, bin_to_list/2, bin_to_list/3, + compile_pattern/1, copy/1, copy/2, decode_unsigned/1, + decode_unsigned/2, encode_unsigned/1, encode_unsigned/2, + first/1, last/1, list_to_bin/1, longest_common_prefix/1, + longest_common_suffix/1, match/2, match/3, matches/2, + matches/3, part/2, part/3, referenced_byte_size/1]). + +-spec at(Subject, Pos) -> byte() when + Subject :: binary(), + Pos :: non_neg_integer(). + +at(_, _) -> + erlang:nif_error(undef). + +-spec bin_to_list(Subject) -> [byte()] when + Subject :: binary(). + +bin_to_list(_) -> + erlang:nif_error(undef). + +-spec bin_to_list(Subject, PosLen) -> [byte()] when + Subject :: binary(), + PosLen :: part(). + +bin_to_list(_, _) -> + erlang:nif_error(undef). + +-spec bin_to_list(Subject, Pos, Len) -> [byte()] when + Subject :: binary(), + Pos :: non_neg_integer(), + Len :: non_neg_integer(). + +bin_to_list(_, _, _) -> + erlang:nif_error(undef). + +-spec compile_pattern(Pattern) -> cp() when + Pattern :: binary() | [binary()]. + +compile_pattern(_) -> + erlang:nif_error(undef). + +-spec copy(Subject) -> binary() when + Subject :: binary(). + +copy(_) -> + erlang:nif_error(undef). + +-spec copy(Subject, N) -> binary() when + Subject :: binary(), + N :: non_neg_integer(). + +copy(_, _) -> + erlang:nif_error(undef). + +-spec decode_unsigned(Subject) -> Unsigned when + Subject :: binary(), + Unsigned :: non_neg_integer(). + +decode_unsigned(_) -> + erlang:nif_error(undef). + +-spec decode_unsigned(Subject, Endianess) -> Unsigned when + Subject :: binary(), + Endianess :: big | little, + Unsigned :: non_neg_integer(). + +decode_unsigned(_, _) -> + erlang:nif_error(undef). + +-spec encode_unsigned(Unsigned) -> binary() when + Unsigned :: non_neg_integer(). + +encode_unsigned(_) -> + erlang:nif_error(undef). + +-spec encode_unsigned(Unsigned, Endianess) -> binary() when + Unsigned :: non_neg_integer(), + Endianess :: big | little. + +encode_unsigned(_, _) -> + erlang:nif_error(undef). + +-spec first(Subject) -> byte() when + Subject :: binary(). + +first(_) -> + erlang:nif_error(undef). + +-spec last(Subject) -> byte() when + Subject :: binary(). + +last(_) -> + erlang:nif_error(undef). + +-spec list_to_bin(ByteList) -> binary() when + ByteList :: iodata(). + +list_to_bin(_) -> + erlang:nif_error(undef). + +-spec longest_common_prefix(Binaries) -> non_neg_integer() when + Binaries :: [binary()]. + +longest_common_prefix(_) -> + erlang:nif_error(undef). + +-spec longest_common_suffix(Binaries) -> non_neg_integer() when + Binaries :: [binary()]. + +longest_common_suffix(_) -> + erlang:nif_error(undef). + +-spec match(Subject, Pattern) -> Found | nomatch when + Subject :: binary(), + Pattern :: binary() | [binary()] | cp(), + Found :: part(). + +match(_, _) -> + erlang:nif_error(undef). + +-spec match(Subject, Pattern, Options) -> Found | nomatch when + Subject :: binary(), + Pattern :: binary() | [binary()] | cp(), + Found :: part(), + Options :: [Option], + Option :: {scope, part()}. + +match(_, _, _) -> + erlang:nif_error(undef). + +-spec matches(Subject, Pattern) -> Found when + Subject :: binary(), + Pattern :: binary() | [binary()] | cp(), + Found :: [part()]. + +matches(_, _) -> + erlang:nif_error(undef). + +-spec matches(Subject, Pattern, Options) -> Found when + Subject :: binary(), + Pattern :: binary() | [binary()] | cp(), + Found :: [part()], + Options :: [Option], + Option :: {scope, part()}. + +matches(_, _, _) -> + erlang:nif_error(undef). + +-spec part(Subject, PosLen) -> binary() when + Subject :: binary(), + PosLen :: part(). + +part(_, _) -> + erlang:nif_error(undef). + +-spec part(Subject, Pos, Len) -> binary() when + Subject :: binary(), + Pos :: non_neg_integer(), + Len :: non_neg_integer(). + +part(_, _, _) -> + erlang:nif_error(undef). + +-spec referenced_byte_size(Binary) -> non_neg_integer() when + Binary :: binary(). + +referenced_byte_size(_) -> + erlang:nif_error(undef). + +%%% End of BIFs. + %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %% split %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% diff --git a/lib/stdlib/src/ets.erl b/lib/stdlib/src/ets.erl index afa914a456..817b397cc4 100644 --- a/lib/stdlib/src/ets.erl +++ b/lib/stdlib/src/ets.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2011. All Rights Reserved. +%% Copyright Ericsson AB 1996-2012. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -46,7 +46,12 @@ %%----------------------------------------------------------------------------- +-type access() :: public | protected | private. -type tab() :: atom() | tid(). +-type type() :: set | ordered_set | bag | duplicate_bag. +-type continuation() :: '$end_of_table' + | {tab(),integer(),integer(),binary(),list(),integer()} + | {tab(),_,_,integer(),binary(),list(),integer(),integer()}. %% a similar definition is also in erl_types -opaque tid() :: integer(). @@ -57,59 +62,398 @@ %%----------------------------------------------------------------------------- -%% The following functions used to be found in this module, but -%% are now BIFs (i.e. implemented in C). -%% -%% all/0 -%% new/2 -%% delete/1 -%% delete/2 -%% first/1 -%% info/1 -%% info/2 -%% safe_fixtable/2 -%% lookup/2 -%% lookup_element/3 -%% insert/2 -%% is_compiled_ms/1 -%% last/1 -%% member/2 -%% next/2 -%% prev/2 -%% rename/2 -%% slot/2 -%% match/1 -%% match/2 -%% match/3 -%% match_object/1 -%% match_object/2 -%% match_object/3 -%% match_spec_compile/1 -%% match_spec_run_r/3 -%% select/1 -%% select/2 -%% select/3 -%% select_count/2 -%% select_reverse/1 -%% select_reverse/2 -%% select_reverse/3 -%% select_delete/2 -%% setopts/2 -%% update_counter/3 -%% update_element/3 -%% +%%% BIFs + +-export([all/0, delete/1, delete/2, delete_all_objects/1, + delete_object/2, first/1, give_away/3, info/1, info/2, + insert/2, insert_new/2, is_compiled_ms/1, last/1, lookup/2, + lookup_element/3, match/1, match/2, match/3, match_object/1, + 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_reverse/2, select_reverse/3, setopts/2, slot/2, + update_counter/3, update_element/3]). + +-spec all() -> [Tab] when + Tab :: tab(). + +all() -> + erlang:nif_error(undef). + +-spec delete(Tab) -> true when + Tab :: tab(). + +delete(_) -> + erlang:nif_error(undef). + +-spec delete(Tab, Key) -> true when + Tab :: tab(), + Key :: term(). + +delete(_, _) -> + erlang:nif_error(undef). + +-spec delete_all_objects(Tab) -> true when + Tab :: tab(). + +delete_all_objects(_) -> + erlang:nif_error(undef). + +-spec delete_object(Tab, Object) -> true when + Tab :: tab(), + Object :: tuple(). + +delete_object(_, _) -> + erlang:nif_error(undef). + +-spec first(Tab) -> Key | '$end_of_table' when + Tab :: tab(), + Key :: term(). + +first(_) -> + erlang:nif_error(undef). + +-spec give_away(Tab, Pid, GiftData) -> true when + Tab :: tab(), + Pid :: pid(), + GiftData :: term(). + +give_away(_, _, _) -> + erlang:nif_error(undef). + +-spec info(Tab) -> InfoList | undefined when + Tab :: tab(), + InfoList :: [InfoTuple], + InfoTuple :: {compressed, boolean()} + | {heir, pid() | none} + | {keypos, pos_integer()} + | {memory, non_neg_integer()} + | {name, atom()} + | {named_table, boolean()} + | {node, node()} + | {owner, pid()} + | {protection, access()} + | {size, non_neg_integer()} + | {type, type()}. + +info(_) -> + erlang:nif_error(undef). + +-spec info(Tab, Item) -> Value | undefined when + Tab :: tab(), + Item :: compressed | fixed | heir | keypos | memory + | name | named_table | node | owner | protection + | safe_fixed | size | stats | type, + Value :: term(). + +info(_, _) -> + erlang:nif_error(undef). + +-spec insert(Tab, ObjectOrObjects) -> true when + Tab :: tab(), + ObjectOrObjects :: tuple() | [tuple()]. + +insert(_, _) -> + erlang:nif_error(undef). + +-spec insert_new(Tab, ObjectOrObjects) -> boolean() when + Tab :: tab(), + ObjectOrObjects :: tuple() | [tuple()]. + +insert_new(_, _) -> + erlang:nif_error(undef). + +-spec is_compiled_ms(Term) -> boolean() when + Term :: term(). + +is_compiled_ms(_) -> + erlang:nif_error(undef). + +-spec last(Tab) -> Key | '$end_of_table' when + Tab :: tab(), + Key :: term(). + +last(_) -> + erlang:nif_error(undef). + +-spec lookup(Tab, Key) -> [Object] when + Tab :: tab(), + Key :: term(), + Object :: tuple(). + +lookup(_, _) -> + erlang:nif_error(undef). + +-spec lookup_element(Tab, Key, Pos) -> Elem when + Tab :: tab(), + Key :: term(), + Pos :: pos_integer(), + Elem :: term() | [term()]. + +lookup_element(_, _, _) -> + erlang:nif_error(undef). + +-spec match(Tab, Pattern) -> [Match] when + Tab :: tab(), + Pattern :: match_pattern(), + Match :: [term()]. + +match(_, _) -> + erlang:nif_error(undef). + +-spec match(Tab, Pattern, Limit) -> {[Match], Continuation} | + '$end_of_table' when + Tab :: tab(), + Pattern :: match_pattern(), + Limit :: pos_integer(), + Match :: [term()], + Continuation :: continuation(). + +match(_, _, _) -> + erlang:nif_error(undef). + +-spec match(Continuation) -> {[Match], Continuation} | + '$end_of_table' when + Match :: [term()], + Continuation :: continuation(). + +match(_) -> + erlang:nif_error(undef). + +-spec match_object(Tab, Pattern) -> [Object] when + Tab :: tab(), + Pattern :: match_pattern(), + Object :: tuple(). + +match_object(_, _) -> + erlang:nif_error(undef). + +-spec match_object(Tab, Pattern, Limit) -> {[Match], Continuation} | + '$end_of_table' when + Tab :: tab(), + Pattern :: match_pattern(), + Limit :: pos_integer(), + Match :: [term()], + Continuation :: continuation(). + +match_object(_, _, _) -> + erlang:nif_error(undef). + +-spec match_object(Continuation) -> {[Match], Continuation} | + '$end_of_table' when + Match :: [term()], + Continuation :: continuation(). + +match_object(_) -> + erlang:nif_error(undef). + +-spec match_spec_compile(MatchSpec) -> CompiledMatchSpec when + MatchSpec :: match_spec(), + CompiledMatchSpec :: comp_match_spec(). + +match_spec_compile(_) -> + erlang:nif_error(undef). + +-spec match_spec_run_r(List, CompiledMatchSpec, list()) -> list() when + List :: [tuple()], + CompiledMatchSpec :: comp_match_spec(). + +match_spec_run_r(_, _, _) -> + erlang:nif_error(undef). + +-spec member(Tab, Key) -> boolean() when + Tab :: tab(), + Key :: term(). + +member(_, _) -> + erlang:nif_error(undef). + +-spec new(Name, Options) -> tid() | atom() when + Name :: atom(), + Options :: [Option], + Option :: Type | Access | named_table | {keypos,Pos} + | {heir, Pid :: pid(), HeirData} | {heir, none} | Tweaks, + Type :: type(), + Access :: access(), + Tweaks :: {write_concurrency, boolean()} + | {read_concurrency, boolean()} + | compressed, + Pos :: pos_integer(), + HeirData :: term(). + +new(_, _) -> + erlang:nif_error(undef). + +-spec next(Tab, Key1) -> Key2 | '$end_of_table' when + Tab :: tab(), + Key1 :: term(), + Key2 :: term(). + +next(_, _) -> + erlang:nif_error(undef). + +-spec prev(Tab, Key1) -> Key2 | '$end_of_table' when + Tab :: tab(), + Key1 :: term(), + Key2 :: term(). + +prev(_, _) -> + erlang:nif_error(undef). + +%% Shadowed by erl_bif_types: ets:rename/2 +-spec rename(Tab, Name) -> Name when + Tab :: tab(), + Name :: atom(). + +rename(_, _) -> + erlang:nif_error(undef). + +-spec safe_fixtable(Tab, Fix) -> true when + Tab :: tab(), + Fix :: boolean(). + +safe_fixtable(_, _) -> + erlang:nif_error(undef). + +-spec select(Tab, MatchSpec) -> [Match] when + Tab :: tab(), + MatchSpec :: match_spec(), + Match :: term(). + +select(_, _) -> + erlang:nif_error(undef). + +-spec select(Tab, MatchSpec, Limit) -> {[Match],Continuation} | + '$end_of_table' when + Tab :: tab(), + MatchSpec :: match_spec(), + Limit :: pos_integer(), + Match :: term(), + Continuation :: continuation(). + +select(_, _, _) -> + erlang:nif_error(undef). + +-spec select(Continuation) -> {[Match],Continuation} | '$end_of_table' when + Match :: term(), + Continuation :: continuation(). + +select(_) -> + erlang:nif_error(undef). + +-spec select_count(Tab, MatchSpec) -> NumMatched when + Tab :: tab(), + MatchSpec :: match_spec(), + NumMatched :: non_neg_integer(). + +select_count(_, _) -> + erlang:nif_error(undef). + +-spec select_delete(Tab, MatchSpec) -> NumDeleted when + Tab :: tab(), + MatchSpec :: match_spec(), + NumDeleted :: non_neg_integer(). + +select_delete(_, _) -> + erlang:nif_error(undef). + +-spec select_reverse(Tab, MatchSpec) -> [Match] when + Tab :: tab(), + MatchSpec :: match_spec(), + Match :: term(). + +select_reverse(_, _) -> + erlang:nif_error(undef). + +-spec select_reverse(Tab, MatchSpec, Limit) -> {[Match],Continuation} | + '$end_of_table' when + Tab :: tab(), + MatchSpec :: match_spec(), + Limit :: pos_integer(), + Match :: term(), + Continuation :: continuation(). + +select_reverse(_, _, _) -> + erlang:nif_error(undef). + +-spec select_reverse(Continuation) -> {[Match],Continuation} | + '$end_of_table' when + Continuation :: continuation(), + Match :: term(). + +select_reverse(_) -> + erlang:nif_error(undef). + +-spec setopts(Tab, Opts) -> true when + Tab :: tab(), + Opts :: Opt | [Opt], + Opt :: {heir, pid(), HeirData} | {heir,none}, + HeirData :: term(). + +setopts(_, _) -> + erlang:nif_error(undef). + +-spec slot(Tab, I) -> [Object] | '$end_of_table' when + Tab :: tab(), + I :: non_neg_integer(), + Object :: tuple(). + +slot(_, _) -> + erlang:nif_error(undef). + +-spec update_counter(Tab, Key, UpdateOp) -> Result when + Tab :: tab(), + Key :: term(), + UpdateOp :: {Pos, Incr} | {Pos, Incr, Threshold, SetValue}, + Pos :: integer(), + Incr :: integer(), + Threshold :: integer(), + SetValue :: integer(), + Result :: integer(); + (Tab, Key, [UpdateOp]) -> [Result] when + Tab :: tab(), + Key :: term(), + UpdateOp :: {Pos, Incr} | {Pos, Incr, Threshold, SetValue}, + Pos :: integer(), + Incr :: integer(), + Threshold :: integer(), + SetValue :: integer(), + Result :: integer(); + (Tab, Key, Incr) -> Result when + Tab :: tab(), + Key :: term(), + Incr :: integer(), + Result :: integer(). + +update_counter(_, _, _) -> + erlang:nif_error(undef). + +-spec update_element(Tab, Key, ElementSpec :: {Pos, Value}) -> boolean() when + Tab :: tab(), + Key :: term(), + Pos :: pos_integer(), + Value :: term(); + (Tab, Key, ElementSpec :: [{Pos, Value}]) -> boolean() when + Tab :: tab(), + Key :: term(), + Pos :: pos_integer(), + Value :: term(). + +update_element(_, _, _) -> + erlang:nif_error(undef). + +%%% End of BIFs -opaque comp_match_spec() :: any(). %% this one is REALLY opaque --spec match_spec_run([tuple()], comp_match_spec()) -> [term()]. +-spec match_spec_run(List, CompiledMatchSpec) -> list() when + List :: [tuple()], + CompiledMatchSpec :: comp_match_spec(). match_spec_run(List, CompiledMS) -> lists:reverse(ets:match_spec_run_r(List, CompiledMS, [])). --type continuation() :: '$end_of_table' - | {tab(),integer(),integer(),binary(),list(),integer()} - | {tab(),_,_,integer(),binary(),list(),integer(),integer()}. - -spec repair_continuation(Continuation, MatchSpec) -> Continuation when Continuation :: continuation(), MatchSpec :: match_spec(). diff --git a/lib/stdlib/src/lists.erl b/lib/stdlib/src/lists.erl index e73c087753..eb527471d5 100644 --- a/lib/stdlib/src/lists.erl +++ b/lib/stdlib/src/lists.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2011. All Rights Reserved. +%% Copyright Ericsson AB 1996-2012. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -33,9 +33,6 @@ keysort/2, keymerge/3, rkeymerge/3, rukeymerge/3, ukeysort/2, ukeymerge/3, keymap/3]). -%% Bifs: member/2, reverse/2 -%% Bifs: keymember/3, keysearch/3, keyfind/3 - -export([merge/3, rmerge/3, sort/2, umerge/3, rumerge/3, usort/2]). -export([all/2,any/2,map/2,flatmap/2,foldl/3,foldr/3,filter/2, @@ -43,6 +40,60 @@ mapfoldl/3,mapfoldr/3,foreach/2,takewhile/2,dropwhile/2,splitwith/2, split/2]). +%%% BIFs +-export([keyfind/3, keymember/3, keysearch/3, member/2, reverse/2]). + +%% Shadowed by erl_bif_types: lists:keyfind/3 +-spec keyfind(Key, N, TupleList) -> Tuple | false when + Key :: term(), + N :: pos_integer(), + TupleList :: [Tuple], + Tuple :: tuple(). + +keyfind(_, _, _) -> + erlang:nif_error(undef). + +%% Shadowed by erl_bif_types: lists:keymember/3 +-spec keymember(Key, N, TupleList) -> boolean() when + Key :: term(), + N :: pos_integer(), + TupleList :: [Tuple], + Tuple :: tuple(). + +keymember(_, _, _) -> + erlang:nif_error(undef). + +%% Shadowed by erl_bif_types: lists:keysearch/3 +-spec keysearch(Key, N, TupleList) -> {value, Tuple} | false when + Key :: term(), + N :: pos_integer(), + TupleList :: [Tuple], + Tuple :: tuple(). + +keysearch(_, _, _) -> + erlang:nif_error(undef). + +%% Shadowed by erl_bif_types: lists:member/2 +-spec member(Elem, List) -> boolean() when + Elem :: T, + List :: [T], + T :: term(). + +member(_, _) -> + erlang:nif_error(undef). + +%% Shadowed by erl_bif_types: lists:reverse/2 +-spec reverse(List1, Tail) -> List2 when + List1 :: [T], + Tail :: term(), + List2 :: [T], + T :: term(). + +reverse(_, _) -> + erlang:nif_error(undef). + +%%% End of BIFs + %% member(X, L) -> (true | false) %% test if X is a member of the list L %% Now a BIF! @@ -84,7 +135,7 @@ append([]) -> []. subtract(L1, L2) -> L1 -- L2. -%% reverse(L) reverse all elements in the list L. Is now a BIF! +%% reverse(L) reverse all elements in the list L. reverse/2 is now a BIF! -spec reverse(List1) -> List2 when List1 :: [T], @@ -581,6 +632,7 @@ flatlength([_|T], L) -> flatlength([], L) -> L. %% keymember(Key, Index, [Tuple]) Now a BIF! +%% keyfind(Key, Index, [Tuple]) A BIF! %% keysearch(Key, Index, [Tuple]) Now a BIF! %% keydelete(Key, Index, [Tuple]) %% keyreplace(Key, Index, [Tuple], NewTuple) diff --git a/lib/stdlib/src/math.erl b/lib/stdlib/src/math.erl index b2ea6195c5..c3fb684ec3 100644 --- a/lib/stdlib/src/math.erl +++ b/lib/stdlib/src/math.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. +%% Copyright Ericsson AB 1996-2012. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -20,6 +20,116 @@ -export([pi/0]). +%%% BIFs + +-export([sin/1, cos/1, tan/1, asin/1, acos/1, atan/1, atan2/2, sinh/1, + cosh/1, tanh/1, asinh/1, acosh/1, atanh/1, exp/1, log/1, + log10/1, pow/2, sqrt/1, erf/1, erfc/1]). + +-spec acos(X) -> float() when + X :: number(). +acos(_) -> + erlang:nif_error(undef). + +-spec acosh(X) -> float() when + X :: number(). +acosh(_) -> + erlang:nif_error(undef). + +-spec asin(X) -> float() when + X :: number(). +asin(_) -> + erlang:nif_error(undef). + +-spec asinh(X) -> float() when + X :: number(). +asinh(_) -> + erlang:nif_error(undef). + +-spec atan(X) -> float() when + X :: number(). +atan(_) -> + erlang:nif_error(undef). + +-spec atan2(X, Y) -> float() when + X :: number(), + Y :: number(). +atan2(_, _) -> + erlang:nif_error(undef). + +-spec atanh(X) -> float() when + X :: number(). +atanh(_) -> + erlang:nif_error(undef). + +-spec cos(X) -> float() when + X :: number(). +cos(_) -> + erlang:nif_error(undef). + +-spec cosh(X) -> float() when + X :: number(). +cosh(_) -> + erlang:nif_error(undef). + +-spec erf(X) -> float() when + X :: number(). +erf(_) -> + erlang:nif_error(undef). + +-spec erfc(X) -> float() when + X :: number(). +erfc(_) -> + erlang:nif_error(undef). + +-spec exp(X) -> float() when + X :: number(). +exp(_) -> + erlang:nif_error(undef). + +-spec log(X) -> float() when + X :: number(). +log(_) -> + erlang:nif_error(undef). + +-spec log10(X) -> float() when + X :: number(). +log10(_) -> + erlang:nif_error(undef). + +-spec pow(X, Y) -> float() when + X :: number(), + Y :: number(). +pow(_, _) -> + erlang:nif_error(undef). + +-spec sin(X) -> float() when + X :: number(). +sin(_) -> + erlang:nif_error(undef). + +-spec sinh(X) -> float() when + X :: number(). +sinh(_) -> + erlang:nif_error(undef). + +-spec sqrt(X) -> float() when + X :: number(). +sqrt(_) -> + erlang:nif_error(undef). + +-spec tan(X) -> float() when + X :: number(). +tan(_) -> + erlang:nif_error(undef). + +-spec tanh(X) -> float() when + X :: number(). +tanh(_) -> + erlang:nif_error(undef). + +%%% End of BIFs + -spec pi() -> float(). pi() -> 3.1415926535897932. diff --git a/lib/stdlib/src/qlc_pt.erl b/lib/stdlib/src/qlc_pt.erl index 21504d707b..ad25fd559c 100644 --- a/lib/stdlib/src/qlc_pt.erl +++ b/lib/stdlib/src/qlc_pt.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2004-2011. All Rights Reserved. +%% Copyright Ericsson AB 2004-2012. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -2186,7 +2186,7 @@ try_ms(E, P, Fltr, State) -> {function,L,foo,0,[{clause,L,[],[],[MS0]}]} = lists:last(X), MS = erl_parse:normalise(var2const(MS0)), XMS = ets:match_spec_compile(MS), - true = is_binary(XMS), + true = ets:is_compiled_ms(XMS), {ok, MS, MS0} end of {'EXIT', _Reason} -> diff --git a/lib/stdlib/src/re.erl b/lib/stdlib/src/re.erl index 246d535943..359afc8c14 100644 --- a/lib/stdlib/src/re.erl +++ b/lib/stdlib/src/re.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2008-2011. All Rights Reserved. +%% Copyright Ericsson AB 2008-2012. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -30,11 +30,65 @@ | {newline, nl_spec()}| bsr_anycrlf | bsr_unicode. -%% Emulator builtins in this module: -%% re:compile/1 -%% re:compile/2 -%% re:run/2 -%% re:run/3 +%%% BIFs + +-export([compile/1, compile/2, run/2, run/3]). + +-spec compile(Regexp) -> {ok, MP} | {error, ErrSpec} when + Regexp :: iodata(), + MP :: mp(), + ErrSpec :: {ErrString :: string(), Position :: non_neg_integer()}. + +compile(_) -> + erlang:nif_error(undef). + +-spec compile(Regexp, Options) -> {ok, MP} | {error, ErrSpec} when + Regexp :: iodata() | unicode:charlist(), + Options :: [Option], + Option :: compile_option(), + MP :: mp(), + ErrSpec :: {ErrString :: string(), Position :: non_neg_integer()}. + +compile(_, _) -> + erlang:nif_error(undef). + +-spec run(Subject, RE) -> {match, Captured} | nomatch when + Subject :: iodata() | unicode:charlist(), + RE :: mp() | iodata(), + Captured :: [CaptureData], + CaptureData :: {integer(), integer()}. + +run(_, _) -> + erlang:nif_error(undef). + +-spec run(Subject, RE, Options) -> {match, Captured} | + match | + nomatch when + Subject :: iodata() | unicode:charlist(), + RE :: mp() | iodata() | unicode:charlist(), + Options :: [Option], + Option :: anchored | global | notbol | noteol | notempty + | {offset, non_neg_integer()} | + {newline, NLSpec :: nl_spec()} | + bsr_anycrlf | bsr_unicode | {capture, ValueSpec} | + {capture, ValueSpec, Type} | CompileOpt, + Type :: index | list | binary, + ValueSpec :: all | all_but_first | first | none | ValueList, + ValueList :: [ValueID], + ValueID :: integer() | string() | atom(), + CompileOpt :: compile_option(), + Captured :: [CaptureData] | [[CaptureData]], + CaptureData :: {integer(), integer()} + | ListConversionData + | binary(), + ListConversionData :: string() + | {error, string(), binary()} + | {incomplete, string(), binary()}. + +run(_, _, _) -> + erlang:nif_error(undef). + +%%% End of BIFs -spec split(Subject, RE) -> SplitList when Subject :: iodata() | unicode:charlist(), diff --git a/lib/stdlib/src/stdlib.appup.src b/lib/stdlib/src/stdlib.appup.src index 94e81188b5..55c8087475 100644 --- a/lib/stdlib/src/stdlib.appup.src +++ b/lib/stdlib/src/stdlib.appup.src @@ -17,11 +17,11 @@ %% %CopyrightEnd% {"%VSN%", %% Up from - max two major revisions back - [{<<"1\\.18(\\.[0-9]+)*">>,[restart_new_emulator]}, %% R15 - {<<"1\\.17(\\.[0-9]+)*">>,[restart_new_emulator]}, %% R14 - {<<"1\\.16(\\.[0-9]+)*">>,[restart_new_emulator]}],%% R13 + [{<<"1\\.19(\\.[0-9]+)*">>,[restart_new_emulator]}, %% R16 + {<<"1\\.18(\\.[0-9]+)*">>,[restart_new_emulator]}, %% R15 + {<<"1\\.17(\\.[0-9]+)*">>,[restart_new_emulator]}],%% R14 %% Down to - max two major revisions back - [{<<"1\\.18(\\.[0-9]+)*">>,[restart_new_emulator]}, %% R15 - {<<"1\\.17(\\.[0-9]+)*">>,[restart_new_emulator]}, %% R14 - {<<"1\\.16(\\.[0-9]+)*">>,[restart_new_emulator]}] %% R13 + [{<<"1\\.19(\\.[0-9]+)*">>,[restart_new_emulator]}, %% R16 + {<<"1\\.18(\\.[0-9]+)*">>,[restart_new_emulator]}, %% R15 + {<<"1\\.17(\\.[0-9]+)*">>,[restart_new_emulator]}] %% R14 }. diff --git a/lib/stdlib/src/string.erl b/lib/stdlib/src/string.erl index 30eac4f07d..fc029a582f 100644 --- a/lib/stdlib/src/string.erl +++ b/lib/stdlib/src/string.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2011. All Rights Reserved. +%% Copyright Ericsson AB 1996-2012. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -29,6 +29,30 @@ %%--------------------------------------------------------------------------- +%%% BIFs + +-export([to_float/1, to_integer/1]). + +-spec to_float(String) -> {Float, Rest} | {error, Reason} when + String :: string(), + Float :: float(), + Rest :: string(), + Reason :: no_float | not_a_list. + +to_float(_) -> + erlang:nif_error(undef). + +-spec to_integer(String) -> {Int, Rest} | {error, Reason} when + String :: string(), + Int :: integer(), + Rest :: string(), + Reason :: no_integer | not_a_list. + +to_integer(_) -> + erlang:nif_error(undef). + +%%% End of BIFs + %% Robert's bit %% len(String) diff --git a/lib/stdlib/src/unicode.erl b/lib/stdlib/src/unicode.erl index e9b90befe6..8b9412fb1b 100644 --- a/lib/stdlib/src/unicode.erl +++ b/lib/stdlib/src/unicode.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2008-2011. All Rights Reserved. +%% Copyright Ericsson AB 2008-2012. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -18,13 +18,6 @@ %% -module(unicode). -%% Implemented in the emulator: -%% characters_to_binary/2 (will trap to characters_to_binary_int/2 -%% if InEncoding is not {latin1 | unicode | utf8}) -%% characters_to_list/2 (will trap to characters_to_list_int/2 if -%% InEncoding is not {latin1 | unicode | utf8}) -%% - -export([characters_to_list/1, characters_to_list_int/2, characters_to_binary/1, characters_to_binary_int/2, characters_to_binary/3, @@ -52,6 +45,45 @@ -type latin1_charlist() :: [latin1_char() | latin1_binary() | latin1_charlist()]. +%%% BIFs +%%% +%%% characters_to_binary/2 (will trap to characters_to_binary_int/2 +%%% if InEncoding is not {latin1 | unicode | utf8}) +%%% characters_to_list/2 (will trap to characters_to_list_int/2 if +%%% InEncoding is not {latin1 | unicode | utf8}) + +-export([bin_is_7bit/1, characters_to_binary/2, characters_to_list/2]). + +-spec bin_is_7bit(Binary) -> boolean() when + Binary :: binary(). + +bin_is_7bit(_) -> + erlang:nif_error(undef). + +-spec characters_to_binary(Data, InEncoding) -> Result when + Data :: latin1_chardata() | chardata() | external_chardata(), + InEncoding :: encoding(), + Result :: binary() + | {error, binary(), RestData} + | {incomplete, binary(), binary()}, + RestData :: latin1_chardata() | chardata() | external_chardata(). + +characters_to_binary(_, _) -> + erlang:nif_error(undef). + +-spec characters_to_list(Data, InEncoding) -> Result when + Data :: latin1_chardata() | chardata() | external_chardata(), + InEncoding :: encoding(), + Result :: list() + | {error, list(), RestData} + | {incomplete, list(), binary()}, + RestData :: latin1_chardata() | chardata() | external_chardata(). + +characters_to_list(_, _) -> + erlang:nif_error(undef). + +%%% End of BIFs + -spec characters_to_list(Data) -> Result when Data :: latin1_chardata() | chardata() | external_chardata(), Result :: list() |