diff options
Diffstat (limited to 'lib/stdlib/src')
73 files changed, 7927 insertions, 2775 deletions
diff --git a/lib/stdlib/src/Makefile b/lib/stdlib/src/Makefile index 237818c08b..600303d7e1 100644 --- a/lib/stdlib/src/Makefile +++ b/lib/stdlib/src/Makefile @@ -43,6 +43,7 @@ MODULES= \ array \ base64 \ beam_lib \ + binary \ c \ calendar \ dets \ diff --git a/lib/stdlib/src/array.erl b/lib/stdlib/src/array.erl index 83576c9fd3..2f69e2b0a4 100644 --- a/lib/stdlib/src/array.erl +++ b/lib/stdlib/src/array.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2007-2009. All Rights Reserved. +%% Copyright Ericsson AB 2007-2011. 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 @@ -163,17 +163,17 @@ -type array_indx() :: non_neg_integer(). --type array_opt() :: 'fixed' | non_neg_integer() - | {'default', term()} | {'fixed', boolean()} - | {'size', non_neg_integer()}. +-type array_opt() :: {'fixed', boolean()} | 'fixed' + | {'default', Value :: term()} + | {'size', N :: non_neg_integer()} + | (N :: non_neg_integer()). -type array_opts() :: array_opt() | [array_opt()]. --type indx_pair() :: {array_indx(), term()}. +-type indx_pair() :: {Index :: array_indx(), Value :: term()}. -type indx_pairs() :: [indx_pair()]. %%-------------------------------------------------------------------------- -%% @spec () -> array() %% @doc Create a new, extendible array with initial size zero. %% @equiv new([]) %% @@ -185,7 +185,6 @@ new() -> new([]). -%% @spec (Options::term()) -> array() %% @doc Create a new array according to the given options. By default, %% the array is extendible and has initial size zero. Array indices %% start at 0. @@ -224,12 +223,11 @@ new() -> %% @see from_list/2 %% @see fix/1 --spec new(array_opts()) -> array(). +-spec new(Options :: array_opts()) -> array(). new(Options) -> new_0(Options, 0, false). -%% @spec (Size::integer(), Options::term()) -> array() %% @doc Create a new array according to the given size and options. If %% `Size' is not a nonnegative integer, the call fails with reason %% `badarg'. By default, the array has fixed size. Note that any size @@ -245,7 +243,7 @@ new(Options) -> %% %% @see new/1 --spec new(non_neg_integer(), array_opts()) -> array(). +-spec new(Size :: non_neg_integer(), Options :: array_opts()) -> array(). new(Size, Options) when is_integer(Size), Size >= 0 -> new_0(Options, Size, true); @@ -293,13 +291,12 @@ find_max(_I, M) -> M. -%% @spec (X::term()) -> boolean() %% @doc Returns `true' if `X' appears to be an array, otherwise `false'. %% Note that the check is only shallow; there is no guarantee that `X' %% is a well-formed array representation even if this function returns %% `true'. --spec is_array(term()) -> boolean(). +-spec is_array(X :: term()) -> boolean(). is_array(#array{size = Size, max = Max}) when is_integer(Size), is_integer(Max) -> @@ -308,25 +305,23 @@ is_array(_) -> false. -%% @spec (array()) -> integer() %% @doc Get the number of entries in the array. Entries are numbered %% from 0 to `size(Array)-1'; hence, this is also the index of the first %% entry that is guaranteed to not have been previously set. %% @see set/3 %% @see sparse_size/1 --spec size(array()) -> non_neg_integer(). +-spec size(Array :: array()) -> non_neg_integer(). size(#array{size = N}) -> N; size(_) -> erlang:error(badarg). -%% @spec (array()) -> term() %% @doc Get the value used for uninitialized entries. %% %% @see new/2 --spec default(array()) -> term(). +-spec default(Array :: array()) -> term(). default(#array{default = D}) -> D; default(_) -> erlang:error(badarg). @@ -405,23 +400,21 @@ new_test_() -> -endif. -%% @spec (array()) -> array() %% @doc Fix the size of the array. This prevents it from growing %% automatically upon insertion; see also {@link set/3}. %% @see relax/1 --spec fix(array()) -> array(). +-spec fix(Array :: array()) -> array(). fix(#array{}=A) -> A#array{max = 0}. -%% @spec (array()) -> boolean() %% @doc Check if the array has fixed size. %% Returns `true' if the array is fixed, otherwise `false'. %% @see fix/1 --spec is_fix(array()) -> boolean(). +-spec is_fix(Array :: array()) -> boolean(). is_fix(#array{max = 0}) -> true; is_fix(#array{}) -> false. @@ -455,12 +448,11 @@ fix_test_() -> -endif. -%% @spec (array()) -> array() %% @doc Make the array resizable. (Reverses the effects of {@link %% fix/1}.) %% @see fix/1 --spec relax(array()) -> array(). +-spec relax(Array :: array()) -> array(). relax(#array{size = N}=A) -> A#array{max = find_max(N-1, ?LEAFSIZE)}. @@ -481,12 +473,11 @@ relax_test_() -> -endif. -%% @spec (integer(), array()) -> array() %% @doc Change the size of the array. If `Size' is not a nonnegative %% integer, the call fails with reason `badarg'. If the given array has %% fixed size, the resulting array will also have fixed size. --spec resize(non_neg_integer(), array()) -> array(). +-spec resize(Size :: non_neg_integer(), Array :: array()) -> array(). resize(Size, #array{size = N, max = M, elements = E}=A) when is_integer(Size), Size >= 0 -> @@ -510,8 +501,6 @@ resize(_Size, _) -> erlang:error(badarg). -%% @spec (array()) -> array() - %% @doc Change the size of the array to that reported by {@link %% sparse_size/1}. If the given array has fixed size, the resulting %% array will also have fixed size. @@ -519,7 +508,7 @@ resize(_Size, _) -> %% @see resize/2 %% @see sparse_size/1 --spec resize(array()) -> array(). +-spec resize(Array :: array()) -> array(). resize(Array) -> resize(sparse_size(Array), Array). @@ -559,7 +548,6 @@ resize_test_() -> -endif. -%% @spec (integer(), term(), array()) -> array() %% @doc Set entry `I' of the array to `Value'. If `I' is not a %% nonnegative integer, or if the array has fixed size and `I' is larger %% than the maximum index, the call fails with reason `badarg'. @@ -570,7 +558,7 @@ resize_test_() -> %% @see get/2 %% @see reset/2 --spec set(array_indx(), term(), array()) -> array(). +-spec set(I :: array_indx(), Value :: term(), Array :: array()) -> array(). set(I, Value, #array{size = N, max = M, default = D, elements = E}=A) when is_integer(I), I >= 0 -> @@ -624,7 +612,6 @@ expand(I, _S, X, D) -> setelement(I+1, ?NEW_LEAF(D), X). -%% @spec (integer(), array()) -> term() %% @doc Get the value of entry `I'. If `I' is not a nonnegative %% integer, or if the array has fixed size and `I' is larger than the %% maximum index, the call fails with reason `badarg'. @@ -634,7 +621,7 @@ expand(I, _S, X, D) -> %% @see set/3 --spec get(array_indx(), array()) -> term(). +-spec get(I :: array_indx(), Array :: array()) -> term(). get(I, #array{size = N, max = M, elements = E, default = D}) when is_integer(I), I >= 0 -> @@ -660,7 +647,6 @@ get_1(I, E, _D) -> element(I+1, E). -%% @spec (integer(), array()) -> array() %% @doc Reset entry `I' to the default value for the array. %% If the value of entry `I' is the default value the array will be %% returned unchanged. Reset will never change size of the array. @@ -675,7 +661,7 @@ get_1(I, E, _D) -> %% TODO: a reset_range function --spec reset(array_indx(), array()) -> array(). +-spec reset(I :: array_indx(), Array :: array()) -> array(). reset(I, #array{size = N, max = M, default = D, elements = E}=A) when is_integer(I), I >= 0 -> @@ -756,13 +742,12 @@ set_get_test_() -> -endif. -%% @spec (array()) -> list() %% @doc Converts the array to a list. %% %% @see from_list/2 %% @see sparse_to_list/1 --spec to_list(array()) -> list(). +-spec to_list(Array :: array()) -> list(). to_list(#array{size = 0}) -> []; @@ -831,12 +816,11 @@ to_list_test_() -> -endif. -%% @spec (array()) -> list() %% @doc Converts the array to a list, skipping default-valued entries. %% %% @see to_list/1 --spec sparse_to_list(array()) -> list(). +-spec sparse_to_list(Array :: array()) -> list(). sparse_to_list(#array{size = 0}) -> []; @@ -901,15 +885,13 @@ sparse_to_list_test_() -> -endif. -%% @spec (list()) -> array() %% @equiv from_list(List, undefined) --spec from_list(list()) -> array(). +-spec from_list(List :: list()) -> array(). from_list(List) -> from_list(List, undefined). -%% @spec (list(), term()) -> array() %% @doc Convert a list to an extendible array. `Default' is used as the value %% for uninitialized entries of the array. If `List' is not a proper list, %% the call fails with reason `badarg'. @@ -917,7 +899,7 @@ from_list(List) -> %% @see new/2 %% @see to_list/1 --spec from_list(list(), term()) -> array(). +-spec from_list(List :: list(), Default :: term()) -> array(). from_list([], Default) -> new({default,Default}); @@ -1011,13 +993,12 @@ from_list_test_() -> -endif. -%% @spec (array()) -> [{Index::integer(), Value::term()}] %% @doc Convert the array to an ordered list of pairs `{Index, Value}'. %% %% @see from_orddict/2 %% @see sparse_to_orddict/1 --spec to_orddict(array()) -> indx_pairs(). +-spec to_orddict(Array :: array()) -> indx_pairs(). to_orddict(#array{size = 0}) -> []; @@ -1104,13 +1085,12 @@ to_orddict_test_() -> -endif. -%% @spec (array()) -> [{Index::integer(), Value::term()}] %% @doc Convert the array to an ordered list of pairs `{Index, Value}', %% skipping default-valued entries. %% %% @see to_orddict/1 --spec sparse_to_orddict(array()) -> indx_pairs(). +-spec sparse_to_orddict(Array :: array()) -> indx_pairs(). sparse_to_orddict(#array{size = 0}) -> []; @@ -1188,15 +1168,13 @@ sparse_to_orddict_test_() -> -endif. -%% @spec (list()) -> array() %% @equiv from_orddict(Orddict, undefined) --spec from_orddict(indx_pairs()) -> array(). +-spec from_orddict(Orddict :: indx_pairs()) -> array(). from_orddict(Orddict) -> from_orddict(Orddict, undefined). -%% @spec (list(), term()) -> array() %% @doc Convert an ordered list of pairs `{Index, Value}' to a %% corresponding extendible array. `Default' is used as the value for %% uninitialized entries of the array. If `List' is not a proper, @@ -1206,7 +1184,7 @@ from_orddict(Orddict) -> %% @see new/2 %% @see to_orddict/1 --spec from_orddict(indx_pairs(), term()) -> array(). +-spec from_orddict(Orddict :: indx_pairs(), Default :: term()) -> array(). from_orddict([], Default) -> new({default,Default}); @@ -1392,7 +1370,6 @@ from_orddict_test_() -> -endif. -%% @spec (Function, array()) -> array() %% Function = (Index::integer(), Value::term()) -> term() %% @doc Map the given function onto each element of the array. The %% elements are visited in order from the lowest index to the highest. @@ -1402,7 +1379,8 @@ from_orddict_test_() -> %% @see foldr/3 %% @see sparse_map/2 --spec map(fun((array_indx(), _) -> _), array()) -> array(). +-spec map(Function, Array :: array()) -> array() when + Function :: fun((Index :: array_indx(), Value :: _) -> _). map(Function, Array=#array{size = N, elements = E, default = D}) when is_function(Function, 2) -> @@ -1485,7 +1463,6 @@ map_test_() -> -endif. -%% @spec (Function, array()) -> array() %% Function = (Index::integer(), Value::term()) -> term() %% @doc Map the given function onto each element of the array, skipping %% default-valued entries. The elements are visited in order from the @@ -1494,7 +1471,8 @@ map_test_() -> %% %% @see map/2 --spec sparse_map(fun((array_indx(), _) -> _), array()) -> array(). +-spec sparse_map(Function, Array :: array()) -> array() when + Function :: fun((Index :: array_indx(), Value :: _) -> _). sparse_map(Function, Array=#array{size = N, elements = E, default = D}) when is_function(Function, 2) -> @@ -1580,9 +1558,6 @@ sparse_map_test_() -> -endif. -%% @spec (Function, InitialAcc::term(), array()) -> term() -%% Function = (Index::integer(), Value::term(), Acc::term()) -> -%% term() %% @doc Fold the elements of the array using the given function and %% initial accumulator value. The elements are visited in order from the %% lowest index to the highest. If `Function' is not a function, the @@ -1592,7 +1567,8 @@ sparse_map_test_() -> %% @see map/2 %% @see sparse_foldl/3 --spec foldl(fun((array_indx(), _, A) -> B), A, array()) -> B. +-spec foldl(Function, InitialAcc :: A, Array :: array()) -> B when + Function :: fun((Index :: array_indx(), Value :: _, Acc :: A) -> B). foldl(Function, A, #array{size = N, elements = E, default = D}) when is_function(Function, 3) -> @@ -1656,9 +1632,6 @@ foldl_test_() -> -endif. -%% @spec (Function, InitialAcc::term(), array()) -> term() -%% Function = (Index::integer(), Value::term(), Acc::term()) -> -%% term() %% @doc Fold the elements of the array using the given function and %% initial accumulator value, skipping default-valued entries. The %% elements are visited in order from the lowest index to the highest. @@ -1667,7 +1640,8 @@ foldl_test_() -> %% @see foldl/3 %% @see sparse_foldr/3 --spec sparse_foldl(fun((array_indx(), _, A) -> B), A, array()) -> B. +-spec sparse_foldl(Function, InitialAcc :: A, Array :: array()) -> B when + Function :: fun((Index :: array_indx(), Value :: _, Acc :: A) -> B). sparse_foldl(Function, A, #array{size = N, elements = E, default = D}) when is_function(Function, 3) -> @@ -1735,9 +1709,6 @@ sparse_foldl_test_() -> -endif. -%% @spec (Function, InitialAcc::term(), array()) -> term() -%% Function = (Index::integer(), Value::term(), Acc::term()) -> -%% term() %% @doc Fold the elements of the array right-to-left using the given %% function and initial accumulator value. The elements are visited in %% order from the highest index to the lowest. If `Function' is not a @@ -1746,7 +1717,8 @@ sparse_foldl_test_() -> %% @see foldl/3 %% @see map/2 --spec foldr(fun((array_indx(), _, A) -> B), A, array()) -> B. +-spec foldr(Function, InitialAcc :: A, Array :: array()) -> B when + Function :: fun((Index :: array_indx(), Value :: _, Acc :: A) -> B). foldr(Function, A, #array{size = N, elements = E, default = D}) when is_function(Function, 3) -> @@ -1815,9 +1787,6 @@ foldr_test_() -> -endif. -%% @spec (Function, InitialAcc::term(), array()) -> term() -%% Function = (Index::integer(), Value::term(), Acc::term()) -> -%% term() %% @doc Fold the elements of the array right-to-left using the given %% function and initial accumulator value, skipping default-valued %% entries. The elements are visited in order from the highest index to @@ -1827,7 +1796,8 @@ foldr_test_() -> %% @see foldr/3 %% @see sparse_foldl/3 --spec sparse_foldr(fun((array_indx(), _, A) -> B), A, array()) -> B. +-spec sparse_foldr(Function, InitialAcc :: A, Array :: array()) -> B when + Function :: fun((Index :: array_indx(), Value :: _, Acc :: A) -> B). sparse_foldr(Function, A, #array{size = N, elements = E, default = D}) when is_function(Function, 3) -> @@ -1870,7 +1840,6 @@ sparse_foldr_3(I, T, Ix, A, F, D) -> end. -%% @spec (array()) -> integer() %% @doc Get the number of entries in the array up until the last %% non-default valued entry. In other words, returns `I+1' if `I' is the %% last non-default valued entry in the array, or zero if no such entry @@ -1878,7 +1847,7 @@ sparse_foldr_3(I, T, Ix, A, F, D) -> %% @see size/1 %% @see resize/1 --spec sparse_size(array()) -> non_neg_integer(). +-spec sparse_size(Array :: array()) -> non_neg_integer(). sparse_size(A) -> F = fun (I, _V, _A) -> throw({value, I}) end, diff --git a/lib/stdlib/src/base64.erl b/lib/stdlib/src/base64.erl index ebef998ee1..5d800e87b8 100644 --- a/lib/stdlib/src/base64.erl +++ b/lib/stdlib/src/base64.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2007-2009. All Rights Reserved. +%% Copyright Ericsson AB 2007-2011. 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 @@ -38,7 +38,9 @@ %% Description: Encodes a plain ASCII string (or binary) into base64. %%------------------------------------------------------------------------- --spec encode_to_string(string() | binary()) -> ascii_string(). +-spec encode_to_string(Data) -> Base64String when + Data :: string() | binary(), + Base64String :: ascii_string(). encode_to_string(Bin) when is_binary(Bin) -> encode_to_string(binary_to_list(Bin)); @@ -53,7 +55,9 @@ encode_to_string(List) when is_list(List) -> %% Description: Encodes a plain ASCII string (or binary) into base64. %%------------------------------------------------------------------------- --spec encode(string() | binary()) -> binary(). +-spec encode(Data) -> Base64 when + Data :: string() | binary(), + Base64 :: binary(). encode(Bin) when is_binary(Bin) -> encode_binary(Bin); @@ -102,19 +106,23 @@ encode_binary(Bin) -> %% whereas decode crashes if an illegal character is found %%------------------------------------------------------------------------- --spec decode(string() | binary()) -> binary(). +-spec decode(Base64) -> Data when + Base64 :: string() | binary(), + Data :: binary(). decode(Bin) when is_binary(Bin) -> decode_binary(<<>>, Bin); decode(List) when is_list(List) -> list_to_binary(decode_l(List)). --spec mime_decode(string() | binary()) -> binary(). +-spec mime_decode(Base64) -> Data when + Base64 :: string() | binary(), + Data :: binary(). mime_decode(Bin) when is_binary(Bin) -> mime_decode_binary(<<>>, Bin); mime_decode(List) when is_list(List) -> - list_to_binary(mime_decode_l(List)). + mime_decode(list_to_binary(List)). -spec decode_l(string()) -> string(). @@ -125,7 +133,7 @@ decode_l(List) -> -spec mime_decode_l(string()) -> string(). mime_decode_l(List) -> - L = strip_illegal(List, []), + L = strip_illegal(List, [], 0), decode(L, []). %%------------------------------------------------------------------------- @@ -139,14 +147,18 @@ mime_decode_l(List) -> %% whereas decode crashes if an illegal character is found %%------------------------------------------------------------------------- --spec decode_to_string(string() | binary()) -> string(). +-spec decode_to_string(Base64) -> DataString when + Base64 :: string() | binary(), + DataString :: string(). decode_to_string(Bin) when is_binary(Bin) -> decode_to_string(binary_to_list(Bin)); decode_to_string(List) when is_list(List) -> decode_l(List). --spec mime_decode_to_string(string() | binary()) -> string(). +-spec mime_decode_to_string(Base64) -> DataString when + Base64 :: string() | binary(), + DataString :: string(). mime_decode_to_string(Bin) when is_binary(Bin) -> mime_decode_to_string(binary_to_list(Bin)); @@ -198,6 +210,9 @@ decode_binary(Result, <<>>) -> true = is_binary(Result), Result. +%% Skipping pad character if not at end of string. Also liberal about +%% excess padding and skipping of other illegal (non-base64 alphabet) +%% characters. See section 3.3 of RFC4648 mime_decode_binary(Result, <<0:8,T/bits>>) -> mime_decode_binary(Result, T); mime_decode_binary(Result0, <<C:8,T/bits>>) -> @@ -205,15 +220,27 @@ mime_decode_binary(Result0, <<C:8,T/bits>>) -> Bits when is_integer(Bits) -> mime_decode_binary(<<Result0/bits,Bits:6>>, T); eq -> - case tail_contains_equal(T) of - true -> - Split = byte_size(Result0) - 1, - <<Result:Split/bytes,_:4>> = Result0, - Result; - false -> - Split = byte_size(Result0) - 1, - <<Result:Split/bytes,_:2>> = Result0, - Result + case tail_contains_more(T, false) of + {<<>>, Eq} -> + %% No more valid data. + case bit_size(Result0) rem 8 of + 0 -> + %% '====' is not uncommon. + Result0; + 4 when Eq -> + %% enforce at least one more '=' only ignoring illegals and spacing + Split = byte_size(Result0) - 1, + <<Result:Split/bytes,_:4>> = Result0, + Result; + 2 -> + %% remove 2 bits + Split = byte_size(Result0) - 1, + <<Result:Split/bytes,_:2>> = Result0, + Result + end; + {More, _} -> + %% More valid data, skip the eq as invalid + mime_decode_binary(Result0, More) end; _ -> mime_decode_binary(Result0, T) @@ -262,31 +289,63 @@ strip_ws(<<$\s,T/binary>>) -> strip_ws(T); strip_ws(T) -> T. -strip_illegal([0|Cs], A) -> - strip_illegal(Cs, A); -strip_illegal([C|Cs], A) -> +%% Skipping pad character if not at end of string. Also liberal about +%% excess padding and skipping of other illegal (non-base64 alphabet) +%% characters. See section 3.3 of RFC4648 +strip_illegal([], A, _Cnt) -> + A; +strip_illegal([0|Cs], A, Cnt) -> + strip_illegal(Cs, A, Cnt); +strip_illegal([C|Cs], A, Cnt) -> case element(C, ?DECODE_MAP) of - bad -> strip_illegal(Cs, A); - ws -> strip_illegal(Cs, A); - eq -> strip_illegal_end(Cs, [$=|A]); - _ -> strip_illegal(Cs, [C|A]) - end; -strip_illegal([], A) -> A. + bad -> + strip_illegal(Cs, A, Cnt); + ws -> + strip_illegal(Cs, A, Cnt); + eq -> + case {tail_contains_more(Cs, false), Cnt rem 4} of + {{[], _}, 0} -> + A; %% Ignore extra = + {{[], true}, 2} -> + [$=|[$=|A]]; %% 'XX==' + {{[], _}, 3} -> + [$=|A]; %% 'XXX=' + {{[H|T], _}, _} -> + %% more data, skip equals + strip_illegal(T, [H|A], Cnt+1) + end; + _ -> + strip_illegal(Cs, [C|A], Cnt+1) + end. -strip_illegal_end([0|Cs], A) -> - strip_illegal_end(Cs, A); -strip_illegal_end([C|Cs], A) -> +%% Search the tail for more valid data and remember if we saw +%% another equals along the way. +tail_contains_more([], Eq) -> + {[], Eq}; +tail_contains_more(<<>>, Eq) -> + {<<>>, Eq}; +tail_contains_more([C|T]=More, Eq) -> case element(C, ?DECODE_MAP) of - bad -> strip_illegal(Cs, A); - ws -> strip_illegal(Cs, A); - eq -> [C|A]; - _ -> strip_illegal(Cs, [C|A]) + bad -> + tail_contains_more(T, Eq); + ws -> + tail_contains_more(T, Eq); + eq -> + tail_contains_more(T, true); + _ -> + {More, Eq} end; -strip_illegal_end([], A) -> A. - -tail_contains_equal(<<$=,_/binary>>) -> true; -tail_contains_equal(<<_,T/binary>>) -> tail_contains_equal(T); -tail_contains_equal(<<>>) -> false. +tail_contains_more(<<C:8,T/bits>> =More, Eq) -> + case element(C, ?DECODE_MAP) of + bad -> + tail_contains_more(T, Eq); + ws -> + tail_contains_more(T, Eq); + eq -> + tail_contains_more(T, true); + _ -> + {More, Eq} + end. %% accessors b64e(X) -> diff --git a/lib/stdlib/src/beam_lib.erl b/lib/stdlib/src/beam_lib.erl index 820afd3739..fdfbb2e998 100644 --- a/lib/stdlib/src/beam_lib.erl +++ b/lib/stdlib/src/beam_lib.erl @@ -1,24 +1,28 @@ %% %% %CopyrightBegin% -%% -%% Copyright Ericsson AB 2000-2009. All Rights Reserved. -%% +%% +%% Copyright Ericsson AB 2000-2011. 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 %% compliance with the License. You should have received a copy of the %% Erlang Public License along with this software. If not, it can be %% retrieved online at http://www.erlang.org/. -%% +%% %% Software distributed under the License is distributed on an "AS IS" %% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See %% the License for the specific language governing rights and limitations %% under the License. -%% +%% %% %CopyrightEnd% %% -module(beam_lib). -behaviour(gen_server). +%% Avoid warning for local function error/1 clashing with autoimported BIF. +-compile({no_auto_import,[error/1]}). +%% Avoid warning for local function error/2 clashing with autoimported BIF. +-compile({no_auto_import,[error/2]}). -export([info/1, cmp/2, cmp_dirs/2, @@ -41,23 +45,18 @@ terminate/2,code_change/3]). -export([make_crypto_key/2, get_crypto_key/1]). %Utilities used by compiler +-export_type([attrib_entry/0, compinfo_entry/0, labeled_entry/0]). + -import(lists, [append/1, delete/2, foreach/2, keysort/2, member/2, reverse/1, sort/1, splitwith/2]). --include_lib("kernel/include/file.hrl"). --include("erl_compile.hrl"). - %%------------------------------------------------------------------------- -type beam() :: module() | file:filename() | binary(). -%% XXX: THE FOLLOWING SHOULD BE IMPORTED FROM SOMEWHERE ELSE --type forms() :: term(). +-type forms() :: [erl_parse:abstract_form()]. --type abst_vsn() :: atom(). --type abst_code() :: {abst_vsn(), forms()} | 'no_abstract_code'. --type attribute() :: atom(). --type attrvalue() :: term(). +-type abst_code() :: {AbstVersion :: atom(), forms()} | 'no_abstract_code'. -type dataB() :: binary(). -type index() :: non_neg_integer(). -type label() :: integer(). @@ -71,9 +70,9 @@ | 'atoms'. -type chunkref() :: chunkname() | chunkid(). --type attrib_entry() :: {attribute(), [attrvalue()]}. --type compinfo_entry() :: {atom(), term()}. --type labeled_entry() :: {atom(), arity(), label()}. +-type attrib_entry() :: {Attribute :: atom(), [AttributeValue :: term()]}. +-type compinfo_entry() :: {InfoKey :: atom(), term()}. +-type labeled_entry() :: {Function :: atom(), arity(), label()}. -type chunkdata() :: {chunkid(), dataB()} | {'abstract_code', abst_code()} @@ -82,20 +81,17 @@ | {'exports', [{atom(), arity()}]} | {'labeled_exports', [labeled_entry()]} | {'imports', [mfa()]} - | {'indexed_imports', [{index(), module(), atom(), arity()}]} + | {'indexed_imports', [{index(), module(), Function :: atom(), arity()}]} | {'locals', [{atom(), arity()}]} | {'labeled_locals', [labeled_entry()]} | {'atoms', [{integer(), atom()}]}. --type info_pair() :: {'file', file:filename()} - | {'binary', binary()} - | {'module', module()} - | {'chunks', [{chunkid(), integer(), integer()}]}. - %% Error reasons -type info_rsn() :: {'chunk_too_big', file:filename(), - chunkid(), integer(), integer()} - | {'invalid_beam_file', file:filename(), integer()} + chunkid(), ChunkSize :: non_neg_integer(), + FileSize :: non_neg_integer()} + | {'invalid_beam_file', file:filename(), + Position :: non_neg_integer()} | {'invalid_chunk', file:filename(), chunkid()} | {'missing_chunk', file:filename(), chunkid()} | {'not_a_beam_file', file:filename()} @@ -106,6 +102,7 @@ | info_rsn(). -type cmp_rsn() :: {'modules_different', module(), module()} | {'chunks_different', chunkid()} + | 'different_chunks' | info_rsn(). %%------------------------------------------------------------------------- @@ -114,20 +111,34 @@ %% Exported functions %% --spec info(beam()) -> [info_pair()] | {'error', 'beam_lib', info_rsn()}. +-spec info(Beam) -> [InfoPair] | {'error', 'beam_lib', info_rsn()} when + Beam :: beam(), + InfoPair :: {'file', Filename :: file:filename()} + | {'binary', Binary :: binary()} + | {'module', Module :: module()} + | {'chunks', [{ChunkId :: chunkid(), + Pos :: non_neg_integer(), + Size :: non_neg_integer()}]}. info(File) -> read_info(beam_filename(File)). --spec chunks(beam(), [chunkref()]) -> - {'ok', {module(), [chunkdata()]}} | {'error', 'beam_lib', chnk_rsn()}. +-spec chunks(Beam, ChunkRefs) -> + {'ok', {module(), [chunkdata()]}} | + {'error', 'beam_lib', chnk_rsn()} when + Beam :: beam(), + ChunkRefs :: [chunkref()]. chunks(File, Chunks) -> read_chunk_data(File, Chunks). --spec chunks(beam(), [chunkref()], ['allow_missing_chunks']) -> - {'ok', {module(), [{chunkref(), chunkdata() | 'missing_chunk'}]}} - | {'error', 'beam_lib', chnk_rsn()}. +-spec chunks(Beam, ChunkRefs, Options) -> + {'ok', {module(), [ChunkResult]}} | + {'error', 'beam_lib', chnk_rsn()} when + Beam :: beam(), + ChunkRefs :: [chunkref()], + Options :: ['allow_missing_chunks'], + ChunkResult :: chunkdata() | {ChunkRef :: chunkref(), 'missing_chunk'}. chunks(File, Chunks, Options) -> try read_chunk_data(File, Chunks, Options) @@ -138,49 +149,65 @@ chunks(File, Chunks, Options) -> all_chunks(File) -> read_all_chunks(File). --spec cmp(beam(), beam()) -> 'ok' | {'error', 'beam_lib', cmp_rsn()}. +-spec cmp(Beam1, Beam2) -> 'ok' | {'error', 'beam_lib', cmp_rsn()} when + Beam1 :: beam(), + Beam2 :: beam(). cmp(File1, File2) -> try cmp_files(File1, File2) catch Error -> Error end. --spec cmp_dirs(atom() | file:filename(), atom() | file:filename()) -> - {[file:filename()], [file:filename()], - [{file:filename(), file:filename()}]} - | {'error', 'beam_lib', {'not_a_directory', term()} | info_rsn()}. +-spec cmp_dirs(Dir1, Dir2) -> + {Only1, Only2, Different} | {'error', 'beam_lib', Reason} when + Dir1 :: atom() | file:filename(), + Dir2 :: atom() | file:filename(), + Only1 :: [file:filename()], + Only2 :: [file:filename()], + Different :: [{Filename1 :: file:filename(), Filename2 :: file:filename()}], + Reason :: {'not_a_directory', term()} | info_rsn(). cmp_dirs(Dir1, Dir2) -> catch compare_dirs(Dir1, Dir2). --spec diff_dirs(atom() | file:filename(), atom() | file:filename()) -> - 'ok' | {'error', 'beam_lib', {'not_a_directory', term()} | info_rsn()}. +-spec diff_dirs(Dir1, Dir2) -> 'ok' | {'error', 'beam_lib', Reason} when + Dir1 :: atom() | file:filename(), + Dir2 :: atom() | file:filename(), + Reason :: {'not_a_directory', term()} | info_rsn(). diff_dirs(Dir1, Dir2) -> catch diff_directories(Dir1, Dir2). --spec strip(beam()) -> - {'ok', {module(), beam()}} | {'error', 'beam_lib', info_rsn()}. +-spec strip(Beam1) -> + {'ok', {module(), Beam2}} | {'error', 'beam_lib', info_rsn()} when + Beam1 :: beam(), + Beam2 :: beam(). strip(FileName) -> try strip_file(FileName) catch Error -> Error end. --spec strip_files([beam()]) -> - {'ok', [{module(), beam()}]} | {'error', 'beam_lib', info_rsn()}. +-spec strip_files(Files) -> + {'ok', [{module(), Beam}]} | {'error', 'beam_lib', info_rsn()} when + Files :: [beam()], + Beam :: beam(). strip_files(Files) when is_list(Files) -> try strip_fils(Files) catch Error -> Error end. --spec strip_release(atom() | file:filename()) -> +-spec strip_release(Dir) -> {'ok', [{module(), file:filename()}]} - | {'error', 'beam_lib', {'not_a_directory', term()} | info_rsn()}. + | {'error', 'beam_lib', Reason} when + Dir :: atom() | file:filename(), + Reason :: {'not_a_directory', term()} | info_rsn(). strip_release(Root) -> catch strip_rel(Root). --spec version(beam()) -> - {'ok', {module(), [term()]}} | {'error', 'beam_lib', chnk_rsn()}. +-spec version(Beam) -> + {'ok', {module(), [Version :: term()]}} | + {'error', 'beam_lib', chnk_rsn()} when + Beam :: beam(). version(File) -> case catch read_chunk_data(File, [attributes]) of @@ -191,8 +218,10 @@ version(File) -> Error end. --spec md5(beam()) -> - {'ok', {module(), binary()}} | {'error', 'beam_lib', chnk_rsn()}. +-spec md5(Beam) -> + {'ok', {module(), MD5}} | {'error', 'beam_lib', chnk_rsn()} when + Beam :: beam(), + MD5 :: binary(). md5(File) -> case catch read_significant_chunks(File) of @@ -203,7 +232,8 @@ md5(File) -> Error end. --spec format_error(term()) -> [char() | string()]. +-spec format_error(Reason) -> io_lib:chars() when + Reason :: term(). format_error({error, Error}) -> format_error(Error); @@ -256,12 +286,15 @@ format_error(E) -> | {'debug_info', mode(), module(), file:filename()}. -type crypto_fun() :: fun((crypto_fun_arg()) -> term()). --spec crypto_key_fun(crypto_fun()) -> 'ok' | {'error', term()}. +-spec crypto_key_fun(CryptoKeyFun) -> 'ok' | {'error', Reason} when + CryptoKeyFun :: crypto_fun(), + Reason :: badfun | exists | term(). crypto_key_fun(F) -> call_crypto_server({crypto_key_fun, F}). --spec clear_crypto_key_fun() -> 'undefined' | {'ok', term()}. +-spec clear_crypto_key_fun() -> 'undefined' | {'ok', Result} when + Result :: 'undefined' | term(). clear_crypto_key_fun() -> call_crypto_server(clear_crypto_key_fun). @@ -331,13 +364,11 @@ beam_files(Dir) -> %% -> ok | throw(Error) cmp_files(File1, File2) -> - {ok, {M1, L1}} = read_significant_chunks(File1), - {ok, {M2, L2}} = read_significant_chunks(File2), + {ok, {M1, L1}} = read_all_but_useless_chunks(File1), + {ok, {M2, L2}} = read_all_but_useless_chunks(File2), if M1 =:= M2 -> - List1 = filter_funtab(L1), - List2 = filter_funtab(L2), - cmp_lists(List1, List2); + cmp_lists(L1, L2); true -> error({modules_different, M1, M2}) end. @@ -408,6 +439,20 @@ pad(Size) -> end. %% -> {ok, {Module, Chunks}} | throw(Error) +read_all_but_useless_chunks(File0) when is_atom(File0); + is_list(File0); + is_binary(File0) -> + File = beam_filename(File0), + {ok, Module, ChunkIds0} = scan_beam(File, info), + ChunkIds = [Name || {Name,_,_} <- ChunkIds0, + not is_useless_chunk(Name)], + {ok, Module, Chunks} = scan_beam(File, ChunkIds), + {ok, {Module, lists:reverse(Chunks)}}. + +is_useless_chunk("CInf") -> true; +is_useless_chunk(_) -> false. + +%% -> {ok, {Module, Chunks}} | throw(Error) read_significant_chunks(File) -> case read_chunk_data(File, significant_chunks(), [allow_missing_chunks]) of {ok, {Module, Chunks0}} -> @@ -848,13 +893,17 @@ call_crypto_server(Req) -> gen_server:call(?CRYPTO_KEY_SERVER, Req, infinity) catch exit:{noproc,_} -> - start_crypto_server(), - erlang:yield(), - call_crypto_server(Req) + %% Not started. + call_crypto_server_1(Req); + exit:{normal,_} -> + %% The process finished just as we called it. + call_crypto_server_1(Req) end. -start_crypto_server() -> - gen_server:start({local,?CRYPTO_KEY_SERVER}, ?MODULE, [], []). +call_crypto_server_1(Req) -> + gen_server:start({local,?CRYPTO_KEY_SERVER}, ?MODULE, [], []), + erlang:yield(), + call_crypto_server(Req). -spec init([]) -> {'ok', #state{}}. diff --git a/lib/stdlib/src/binary.erl b/lib/stdlib/src/binary.erl new file mode 100644 index 0000000000..cb1e12ae46 --- /dev/null +++ b/lib/stdlib/src/binary.erl @@ -0,0 +1,212 @@ +%% +%% %CopyrightBegin% +%% +%% Copyright Ericsson AB 2010-2011. 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 +%% compliance with the License. You should have received a copy of the +%% Erlang Public License along with this software. If not, it can be +%% retrieved online at http://www.erlang.org/. +%% +%% Software distributed under the License is distributed on an "AS IS" +%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See +%% the License for the specific language governing rights and limitations +%% under the License. +%% +%% %CopyrightEnd% +%% +-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()}. + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +%% split +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +-spec split(Subject, Pattern) -> Parts when + Subject :: binary(), + Pattern :: binary() | [binary()] | cp(), + Parts :: [binary()]. + +split(H,N) -> + split(H,N,[]). + +-spec split(Subject, Pattern, Options) -> Parts when + Subject :: binary(), + Pattern :: binary() | [binary()] | cp(), + Options :: [Option], + Option :: {scope, part()} | trim | global, + Parts :: [binary()]. + +split(Haystack,Needles,Options) -> + try + {Part,Global,Trim} = get_opts_split(Options,{no,false,false}), + Moptlist = case Part of + no -> + []; + {A,B} -> + [{scope,{A,B}}] + end, + MList = if + Global -> + binary:matches(Haystack,Needles,Moptlist); + true -> + case binary:match(Haystack,Needles,Moptlist) of + nomatch -> []; + Match -> [Match] + end + end, + do_split(Haystack,MList,0,Trim) + catch + _:_ -> + erlang:error(badarg) + end. + +do_split(H,[],N,true) when N >= byte_size(H) -> + []; +do_split(H,[],N,_) -> + [binary:part(H,{N,byte_size(H)-N})]; +do_split(H,[{A,B}|T],N,Trim) -> + case binary:part(H,{N,A-N}) of + <<>> -> + Rest = do_split(H,T,A+B,Trim), + case {Trim, Rest} of + {true,[]} -> + []; + _ -> + [<<>> | Rest] + end; + Oth -> + [Oth | do_split(H,T,A+B,Trim)] + end. + + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +%% replace +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +-spec replace(Subject, Pattern, Replacement) -> Result when + Subject :: binary(), + Pattern :: binary() | [ binary() ] | cp(), + Replacement :: binary(), + Result :: binary(). + +replace(H,N,R) -> + replace(H,N,R,[]). + +-spec replace(Subject, Pattern, Replacement, Options) -> Result when + Subject :: binary(), + Pattern :: binary() | [ binary() ] | cp(), + Replacement :: binary(), + Options :: [Option], + Option :: global | {scope, part()} | {insert_replaced, InsPos}, + InsPos :: OnePos | [ OnePos ], + OnePos :: non_neg_integer(), + Result :: binary(). + +replace(Haystack,Needles,Replacement,Options) -> + try + true = is_binary(Replacement), % Make badarg instead of function clause + {Part,Global,Insert} = get_opts_replace(Options,{no,false,[]}), + Moptlist = case Part of + no -> + []; + {A,B} -> + [{scope,{A,B}}] + end, + MList = if + Global -> + binary:matches(Haystack,Needles,Moptlist); + true -> + case binary:match(Haystack,Needles,Moptlist) of + nomatch -> []; + Match -> [Match] + end + end, + ReplList = case Insert of + [] -> + Replacement; + Y when is_integer(Y) -> + splitat(Replacement,0,[Y]); + Li when is_list(Li) -> + splitat(Replacement,0,lists:sort(Li)) + end, + erlang:iolist_to_binary(do_replace(Haystack,MList,ReplList,0)) + catch + _:_ -> + erlang:error(badarg) + end. + + +do_replace(H,[],_,N) -> + [binary:part(H,{N,byte_size(H)-N})]; +do_replace(H,[{A,B}|T],Replacement,N) -> + [binary:part(H,{N,A-N}), + if + is_list(Replacement) -> + do_insert(Replacement, binary:part(H,{A,B})); + true -> + Replacement + end + | do_replace(H,T,Replacement,A+B)]. + +do_insert([X],_) -> + [X]; +do_insert([H|T],R) -> + [H,R|do_insert(T,R)]. + +splitat(H,N,[]) -> + [binary:part(H,{N,byte_size(H)-N})]; +splitat(H,N,[I|T]) -> + [binary:part(H,{N,I-N})|splitat(H,I,T)]. + + + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +%% Simple helper functions +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% + +get_opts_split([],{Part,Global,Trim}) -> + {Part,Global,Trim}; +get_opts_split([{scope,{A,B}} | T],{_Part,Global,Trim}) -> + get_opts_split(T,{{A,B},Global,Trim}); +get_opts_split([global | T],{Part,_Global,Trim}) -> + get_opts_split(T,{Part,true,Trim}); +get_opts_split([trim | T],{Part,Global,_Trim}) -> + get_opts_split(T,{Part,Global,true}); +get_opts_split(_,_) -> + throw(badopt). + +get_opts_replace([],{Part,Global,Insert}) -> + {Part,Global,Insert}; +get_opts_replace([{scope,{A,B}} | T],{_Part,Global,Insert}) -> + get_opts_replace(T,{{A,B},Global,Insert}); +get_opts_replace([global | T],{Part,_Global,Insert}) -> + get_opts_replace(T,{Part,true,Insert}); +get_opts_replace([{insert_replaced,N} | T],{Part,Global,_Insert}) -> + get_opts_replace(T,{Part,Global,N}); +get_opts_replace(_,_) -> + throw(badopt). + diff --git a/lib/stdlib/src/c.erl b/lib/stdlib/src/c.erl index 433833e233..febfdd6285 100644 --- a/lib/stdlib/src/c.erl +++ b/lib/stdlib/src/c.erl @@ -1,25 +1,27 @@ %% %% %CopyrightBegin% -%% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. -%% +%% +%% Copyright Ericsson AB 1996-2011. 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 %% compliance with the License. You should have received a copy of the %% Erlang Public License along with this software. If not, it can be %% retrieved online at http://www.erlang.org/. -%% +%% %% Software distributed under the License is distributed on an "AS IS" %% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See %% the License for the specific language governing rights and limitations %% under the License. -%% +%% %% %CopyrightEnd% %% -module(c). %% Utilities to use from shell. +%% Avoid warning for local function error/2 clashing with autoimported BIF. +-compile({no_auto_import,[error/2]}). -export([help/0,lc/1,c/1,c/2,nc/1,nc/2, nl/1,l/1,i/0,i/1,ni/0, y/1, y/2, lc_batch/0, lc_batch/1, @@ -31,42 +33,55 @@ -export([display_info/1]). -export([appcall/4]). --import(lists, [reverse/1,flatten/1,sublist/3,sort/1,keysearch/3,keysort/2, +-import(lists, [reverse/1,flatten/1,sublist/3,sort/1,keysort/2, concat/1,max/1,min/1,foreach/2,foldl/3,flatmap/2]). -import(io, [format/1, format/2]). +%%----------------------------------------------------------------------- + +-spec help() -> 'ok'. + help() -> - format("bt(Pid) -- stack backtrace for a process\n" - "c(File) -- compile and load code in <File>\n" - "cd(Dir) -- change working directory\n" - "flush() -- flush any messages sent to the shell\n" - "help() -- help info\n" - "i() -- information about the system\n" - "ni() -- information about the networked system\n" - "i(X,Y,Z) -- information about pid <X,Y,Z>\n" - "l(Module) -- load or reload module\n" - "lc([File]) -- compile a list of Erlang modules\n" - "ls() -- list files in the current directory\n" - "ls(Dir) -- list files in directory <Dir>\n" - "m() -- which modules are loaded\n" - "m(Mod) -- information about module <Mod>\n" - "memory() -- memory allocation information\n" - "memory(T) -- memory allocation information of type <T>\n" - "nc(File) -- compile and load code in <File> on all nodes\n" - "nl(Module) -- load module on all nodes\n" - "pid(X,Y,Z) -- convert X,Y,Z to a Pid\n" - "pwd() -- print working directory\n" - "q() -- quit - shorthand for init:stop()\n" - "regs() -- information about registered processes\n" - "nregs() -- information about all registered processes\n" - "xm(M) -- cross reference check a module\n" - "y(File) -- generate a Yecc parser\n"). + io:put_chars(<<"bt(Pid) -- stack backtrace for a process\n" + "c(File) -- compile and load code in <File>\n" + "cd(Dir) -- change working directory\n" + "flush() -- flush any messages sent to the shell\n" + "help() -- help info\n" + "i() -- information about the system\n" + "ni() -- information about the networked system\n" + "i(X,Y,Z) -- information about pid <X,Y,Z>\n" + "l(Module) -- load or reload module\n" + "lc([File]) -- compile a list of Erlang modules\n" + "ls() -- list files in the current directory\n" + "ls(Dir) -- list files in directory <Dir>\n" + "m() -- which modules are loaded\n" + "m(Mod) -- information about module <Mod>\n" + "memory() -- memory allocation information\n" + "memory(T) -- memory allocation information of type <T>\n" + "nc(File) -- compile and load code in <File> on all nodes\n" + "nl(Module) -- load module on all nodes\n" + "pid(X,Y,Z) -- convert X,Y,Z to a Pid\n" + "pwd() -- print working directory\n" + "q() -- quit - shorthand for init:stop()\n" + "regs() -- information about registered processes\n" + "nregs() -- information about all registered processes\n" + "xm(M) -- cross reference check a module\n" + "y(File) -- generate a Yecc parser\n">>). %% c(FileName) %% Compile a file/module. +-spec c(File) -> {'ok', Module} | 'error' when + File :: file:name(), + Module :: module(). + c(File) -> c(File, []). +-spec c(File, Options) -> {'ok', Module} | 'error' when + File :: file:name(), + Options :: [compile:option()], + Module :: module(). + c(File, Opts0) when is_list(Opts0) -> Opts = [report_errors,report_warnings|Opts0], case compile:file(File, Opts) of @@ -82,6 +97,8 @@ c(File, Opt) -> %%% Obtain the 'outdir' option from the argument. Return "." if no %%% such option was given. +-spec outdir([compile:option()]) -> file:filename(). + outdir([]) -> "."; outdir([Opt|Rest]) -> @@ -118,8 +135,8 @@ machine_load(Mod, File, Opts) -> %%% loaded from some other place than current directory. %%% Now, loading from other than current directory is supposed to work. %%% so this function does nothing special. -check_load({error, R}, _) -> {error, R}; -check_load(_, X) -> {ok, X}. +check_load({error, _R} = Error, _) -> Error; +check_load(_, Mod) -> {ok, Mod}. %% Compile a list of modules %% enables the nice unix shell cmd @@ -128,6 +145,9 @@ check_load(_, X) -> {ok, X}. %% with constant c2 defined, c1=v1 (v1 must be a term!), include dir %% IDir, outdir ODir. +-spec lc(Files) -> 'ok' | 'error' when + Files :: [File :: erl_compile:cmd_line_arg()]. + lc(Args) -> case catch split(Args, [], []) of error -> error; @@ -145,7 +165,7 @@ lc_batch() -> io:format("Error: no files to compile~n"), halt(1). --spec lc_batch([_]) -> no_return(). +-spec lc_batch([erl_compile:cmd_line_arg()]) -> no_return(). lc_batch(Args) -> try split(Args, [], []) of @@ -191,8 +211,18 @@ make_term(Str) -> throw(error) end. +-spec nc(File) -> {'ok', Module} | 'error' when + File :: file:name(), + Module :: module(). + nc(File) -> nc(File, []). +-spec nc(File, Options) -> {'ok', Module} | 'error' when + File :: file:name(), + Options :: [Option] | Option, + Option:: compile:option(), + Module :: module(). + nc(File, Opts0) when is_list(Opts0) -> Opts = Opts0 ++ [report_errors, report_warnings], case compile:file(File, Opts) of @@ -215,26 +245,40 @@ nc(File, Opt) when is_atom(Opt) -> %% l(Mod) %% Reload module Mod from file of same name +-spec l(Module) -> code:load_ret() when + Module :: module(). l(Mod) -> code:purge(Mod), code:load_file(Mod). %% Network version of l/1 +-spec nl(Module) -> abcast | error when + Module :: module(). + nl(Mod) -> case code:get_object_code(Mod) of {_Module, Bin, Fname} -> - rpc:eval_everywhere(code,load_binary,[Mod,Fname,Bin]); + rpc:eval_everywhere(code, load_binary, [Mod, Fname, Bin]); Other -> Other end. +-spec i() -> 'ok'. + i() -> i(processes()). + +-spec ni() -> 'ok'. + ni() -> i(all_procs()). +-spec i([pid()]) -> 'ok'. + i(Ps) -> i(Ps, length(Ps)). +-spec i([pid()], non_neg_integer()) -> 'ok'. + i(Ps, N) when N =< 100 -> iformat("Pid", "Initial Call", "Heap", "Reds", "Msgs"), @@ -275,7 +319,6 @@ paged_i(Ps, Acc, N, Page) -> paged_i([], NewAcc, 0, Page) end. - choice(F) -> case get_line('(c)ontinue (q)uit -->', "c\n") of "c\n" -> @@ -285,7 +328,6 @@ choice(F) -> _ -> choice(F) end. - get_line(P, Default) -> case io:get_line(P) of @@ -305,7 +347,6 @@ mfa_string({M,F,A}) -> mfa_string(X) -> w(X). - display_info(Pid) -> case pinfo(Pid) of undefined -> {0,0,0,0}; @@ -317,7 +358,7 @@ display_info(Pid) -> Other -> Other end, - Reds = fetch(reductions, Info), + Reds = fetch(reductions, Info), LM = length(fetch(messages, Info)), HS = fetch(heap_size, Info), SS = fetch(stack_size, Info), @@ -364,21 +405,36 @@ pinfo(Pid) -> end. fetch(Key, Info) -> - case keysearch(Key, 1, Info) of - {value, {_, Val}} -> Val; + case lists:keyfind(Key, 1, Info) of + {_, Val} -> Val; false -> 0 end. -pid(X,Y,Z) -> +-spec pid(X, Y, Z) -> pid() when + X :: non_neg_integer(), + Y :: non_neg_integer(), + Z :: non_neg_integer(). + +pid(X, Y, Z) -> list_to_pid("<" ++ integer_to_list(X) ++ "." ++ integer_to_list(Y) ++ "." ++ integer_to_list(Z) ++ ">"). -i(X,Y,Z) -> pinfo(pid(X,Y,Z)). +-spec i(X, Y, Z) -> [{atom(), term()}] when + X :: non_neg_integer(), + Y :: non_neg_integer(), + Z :: non_neg_integer(). + +i(X, Y, Z) -> pinfo(pid(X, Y, Z)). + +-spec q() -> no_return(). q() -> init:stop(). +-spec bt(Pid) -> 'ok' | 'undefined' when + Pid :: pid(). + bt(Pid) -> case catch erlang:process_display(Pid, backtrace) of {'EXIT', _} -> @@ -387,6 +443,8 @@ bt(Pid) -> ok end. +-spec m() -> 'ok'. + m() -> mformat("Module", "File"), foreach(fun ({Mod,File}) -> mformat(Mod, File) end, sort(code:all_loaded())). @@ -414,8 +472,8 @@ error(Fmt, Args) -> f_p_e(P, F) -> case file:path_eval(P, F) of - {error, enoent} -> - {error, enoent}; + {error, enoent} = Enoent -> + Enoent; {error, E={Line, _Mod, _Term}} -> error("file:path_eval(~p,~p): error on line ~p: ~s~n", [P, F, Line, file:format_error(E)]), @@ -438,10 +496,12 @@ bi(I) -> %% %% Short and nice form of module info %% +-spec m(Module) -> 'ok' when + Module :: module(). m(M) -> L = M:module_info(), - {value,{exports,E}} = keysearch(exports, 1, L), + {exports,E} = lists:keyfind(exports, 1, L), Time = get_compile_time(L), COpts = get_compile_options(L), format("Module ~w compiled: ",[M]), print_time(Time), @@ -470,10 +530,10 @@ get_compile_options(L) -> end. get_compile_info(L, Tag) -> - case keysearch(compile, 1, L) of - {value, {compile, I}} -> - case keysearch(Tag, 1, I) of - {value, {Tag, Val}} -> {ok,Val}; + case lists:keyfind(compile, 1, L) of + {compile, I} -> + case lists:keyfind(Tag, 1, I) of + {Tag, Val} -> {ok,Val}; false -> error end; false -> error @@ -523,6 +583,8 @@ month(11) -> "November"; month(12) -> "December". %% Just because we can't eval receive statements... +-spec flush() -> 'ok'. + flush() -> receive X -> @@ -533,9 +595,13 @@ flush() -> end. %% Print formatted info about all registered names in the system +-spec nregs() -> 'ok'. + nregs() -> foreach(fun (N) -> print_node_regs(N) end, all_regs()). +-spec regs() -> 'ok'. + regs() -> print_node_regs({node(),registered()}). @@ -609,14 +675,19 @@ portformat(Name, Id, Cmd) -> %% cd(Directory) %% These are just wrappers around the file:get/set_cwd functions. +-spec pwd() -> 'ok'. + pwd() -> case file:get_cwd() of {ok, Str} -> - ok = io:format("~s\n", [Str]); + ok = io:format("~ts\n", [fixup_one_bin(Str)]); {error, _} -> ok = io:format("Cannot determine current directory\n") end. +-spec cd(Dir) -> 'ok' when + Dir :: file:name(). + cd(Dir) -> file:set_cwd(Dir), pwd(). @@ -625,17 +696,38 @@ cd(Dir) -> %% ls(Directory) %% The strategy is to print in fixed width files. +-spec ls() -> 'ok'. + ls() -> ls("."). +-spec ls(Dir) -> 'ok' when + Dir :: file:name(). + ls(Dir) -> case file:list_dir(Dir) of {ok, Entries} -> - ls_print(sort(Entries)); + ls_print(sort(fixup_bin(Entries))); {error,_E} -> format("Invalid directory\n") end. +fixup_one_bin(X) when is_binary(X) -> + L = binary_to_list(X), + [ if + El > 127 -> + $?; + true -> + El + end || El <- L]; +fixup_one_bin(X) -> + X. +fixup_bin([H|T]) -> + [fixup_one_bin(H) | fixup_bin(T)]; +fixup_bin([]) -> + []. + + ls_print([]) -> ok; ls_print(L) -> Width = min([max(lengths(L, [])), 40]) + 5, @@ -645,7 +737,7 @@ ls_print(X, Width, Len) when Width + Len >= 80 -> io:nl(), ls_print(X, Width, 0); ls_print([H|T], Width, Len) -> - io:format("~-*s",[Width,H]), + io:format("~-*ts",[Width,H]), ls_print(T, Width, Len+Width); ls_print([], _, _) -> io:nl(). @@ -660,24 +752,38 @@ w(X) -> %% memory/[0,1] %% -memory() -> erlang:memory(). +-spec memory() -> [{Type, Size}] when + Type :: atom(), + Size :: non_neg_integer(). + +memory() -> erlang:memory(). + +-spec memory(Type) -> Size when + Type :: atom(), + Size :: non_neg_integer() + ; (Types) -> [{Type, Size}] when + Types :: [Type], + Type :: atom(), + Size :: non_neg_integer(). + memory(TypeSpec) -> erlang:memory(TypeSpec). %% %% Cross Reference Check %% - +%%-spec xm(module() | file:filename()) -> xref:m/1 return xm(M) -> appcall(tools, xref, m, [M]). %% %% Call yecc %% - +%%-spec y(file:name()) -> yecc:file/2 return y(File) -> y(File, []). +%%-spec y(file:name(), [yecc:option()]) -> yecc:file/2 return y(File, Opts) -> - appcall(parsetools, yecc, file, [File,Opts]). + appcall(parsetools, yecc, file, [File, Opts]). %% @@ -699,4 +805,3 @@ appcall(App, M, F, Args) -> erlang:raise(error, undef, Stk) end end. - diff --git a/lib/stdlib/src/calendar.erl b/lib/stdlib/src/calendar.erl index ddc0666f77..0320e0cd0e 100644 --- a/lib/stdlib/src/calendar.erl +++ b/lib/stdlib/src/calendar.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. +%% Copyright Ericsson AB 1996-2011. 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 @@ -28,6 +28,8 @@ gregorian_days_to_date/1, gregorian_seconds_to_datetime/1, is_leap_year/1, + iso_week_number/0, + iso_week_number/1, last_day_of_the_month/2, local_time/0, local_time_to_universal_time/1, @@ -61,6 +63,8 @@ %% Types %%---------------------------------------------------------------------- +-export_type([date/0, time/0, datetime/0, datetime1970/0]). + -type year() :: non_neg_integer(). -type year1970() :: 1970..10000. % should probably be 1970.. -type month() :: 1..12. @@ -70,13 +74,13 @@ -type second() :: 0..59. -type daynum() :: 1..7. -type ldom() :: 28 | 29 | 30 | 31. % last day of month +-type weeknum() :: 1..53. --type t_now() :: {non_neg_integer(),non_neg_integer(),non_neg_integer()}. - --type t_date() :: {year(),month(),day()}. --type t_time() :: {hour(),minute(),second()}. --type t_datetime() :: {t_date(),t_time()}. --type t_datetime1970() :: {{year1970(),month(),day()},t_time()}. +-type date() :: {year(),month(),day()}. +-type time() :: {hour(),minute(),second()}. +-type datetime() :: {date(),time()}. +-type datetime1970() :: {{year1970(),month(),day()},time()}. +-type yearweeknum() :: {year(),weeknum()}. %%---------------------------------------------------------------------- @@ -102,7 +106,11 @@ %% January 1st. %% %% df/2 catches the case Year<0 --spec date_to_gregorian_days(year(),month(),day()) -> non_neg_integer(). +-spec date_to_gregorian_days(Year, Month, Day) -> Days when + Year :: year(), + Month :: month(), + Day :: day(), + Days :: non_neg_integer(). date_to_gregorian_days(Year, Month, Day) when is_integer(Day), Day > 0 -> Last = last_day_of_the_month(Year, Month), if @@ -110,7 +118,9 @@ date_to_gregorian_days(Year, Month, Day) when is_integer(Day), Day > 0 -> dy(Year) + dm(Month) + df(Year, Month) + Day - 1 end. --spec date_to_gregorian_days(t_date()) -> non_neg_integer(). +-spec date_to_gregorian_days(Date) -> Days when + Date :: date(), + Days :: non_neg_integer(). date_to_gregorian_days({Year, Month, Day}) -> date_to_gregorian_days(Year, Month, Day). @@ -120,7 +130,9 @@ date_to_gregorian_days({Year, Month, Day}) -> %% Computes the total number of seconds starting from year 0, %% January 1st. %% --spec datetime_to_gregorian_seconds(t_datetime()) -> non_neg_integer(). +-spec datetime_to_gregorian_seconds(DateTime) -> Seconds when + DateTime :: datetime(), + Seconds :: non_neg_integer(). datetime_to_gregorian_seconds({Date, Time}) -> ?SECONDS_PER_DAY*date_to_gregorian_days(Date) + time_to_seconds(Time). @@ -131,18 +143,23 @@ datetime_to_gregorian_seconds({Date, Time}) -> %% %% Returns: 1 | .. | 7. Monday = 1, Tuesday = 2, ..., Sunday = 7. %% --spec day_of_the_week(year(), month(), day()) -> daynum(). +-spec day_of_the_week(Year, Month, Day) -> daynum() when + Year :: year(), + Month :: month(), + Day :: day(). day_of_the_week(Year, Month, Day) -> (date_to_gregorian_days(Year, Month, Day) + 5) rem 7 + 1. --spec day_of_the_week(t_date()) -> daynum(). +-spec day_of_the_week(Date) -> daynum() when + Date:: date(). day_of_the_week({Year, Month, Day}) -> day_of_the_week(Year, Month, Day). %% gregorian_days_to_date(Days) = {Year, Month, Day} %% --spec gregorian_days_to_date(non_neg_integer()) -> t_date(). +-spec gregorian_days_to_date(Days) -> date() when + Days :: non_neg_integer(). gregorian_days_to_date(Days) -> {Year, DayOfYear} = day_to_year(Days), {Month, DayOfMonth} = year_day_to_date(Year, DayOfYear), @@ -151,7 +168,8 @@ gregorian_days_to_date(Days) -> %% gregorian_seconds_to_datetime(Secs) %% --spec gregorian_seconds_to_datetime(non_neg_integer()) -> t_datetime(). +-spec gregorian_seconds_to_datetime(Seconds) -> datetime() when + Seconds :: non_neg_integer(). gregorian_seconds_to_datetime(Secs) when Secs >= 0 -> Days = Secs div ?SECONDS_PER_DAY, Rest = Secs rem ?SECONDS_PER_DAY, @@ -160,7 +178,8 @@ gregorian_seconds_to_datetime(Secs) when Secs >= 0 -> %% is_leap_year(Year) = true | false %% --spec is_leap_year(year()) -> boolean(). +-spec is_leap_year(Year) -> boolean() when + Year :: year(). is_leap_year(Y) when is_integer(Y), Y >= 0 -> is_leap_year1(Y). @@ -172,11 +191,51 @@ is_leap_year1(Year) when Year rem 400 =:= 0 -> is_leap_year1(_) -> false. +%% +%% Calculates the iso week number for the current date. +%% +-spec iso_week_number() -> yearweeknum(). +iso_week_number() -> + {Date, _} = local_time(), + iso_week_number(Date). + + +%% +%% Calculates the iso week number for the given date. +%% +-spec iso_week_number(Date) -> yearweeknum() when + Date :: date(). +iso_week_number({Year, Month, Day}) -> + D = date_to_gregorian_days({Year, Month, Day}), + W01_1_Year = gregorian_days_of_iso_w01_1(Year), + W01_1_NextYear = gregorian_days_of_iso_w01_1(Year + 1), + if W01_1_Year =< D andalso D < W01_1_NextYear -> + % Current Year Week 01..52(,53) + {Year, (D - W01_1_Year) div 7 + 1}; + D < W01_1_Year -> + % Previous Year 52 or 53 + PWN = case day_of_the_week(Year - 1, 1, 1) of + 4 -> 53; + _ -> case day_of_the_week(Year - 1, 12, 31) of + 4 -> 53; + _ -> 52 + end + end, + {Year - 1, PWN}; + W01_1_NextYear =< D -> + % Next Year, Week 01 + {Year + 1, 1} + end. + + %% last_day_of_the_month(Year, Month) %% %% Returns the number of days in a month. %% --spec last_day_of_the_month(year(), month()) -> ldom(). +-spec last_day_of_the_month(Year, Month) -> LastDay when + Year :: year(), + Month :: month(), + LastDay :: ldom(). last_day_of_the_month(Y, M) when is_integer(Y), Y >= 0 -> last_day_of_the_month1(Y, M). @@ -197,24 +256,28 @@ last_day_of_the_month1(_, M) when is_integer(M), M > 0, M < 13 -> %% local_time() %% %% Returns: {date(), time()}, date() = {Y, M, D}, time() = {H, M, S}. --spec local_time() -> t_datetime(). +-spec local_time() -> datetime(). local_time() -> erlang:localtime(). %% local_time_to_universal_time(DateTime) %% --spec local_time_to_universal_time(t_datetime1970()) -> t_datetime1970(). +-spec local_time_to_universal_time(DateTime1) -> DateTime2 when + DateTime1 :: datetime1970(), + DateTime2 :: datetime1970(). local_time_to_universal_time(DateTime) -> erlang:localtime_to_universaltime(DateTime). --spec local_time_to_universal_time(t_datetime1970(), +-spec local_time_to_universal_time(datetime1970(), 'true' | 'false' | 'undefined') -> - t_datetime1970(). + datetime1970(). local_time_to_universal_time(DateTime, IsDst) -> erlang:localtime_to_universaltime(DateTime, IsDst). --spec local_time_to_universal_time_dst(t_datetime1970()) -> [t_datetime1970()]. +-spec local_time_to_universal_time_dst(DateTime1) -> [DateTime] when + DateTime1 :: datetime1970(), + DateTime :: datetime1970(). local_time_to_universal_time_dst(DateTime) -> UtDst = erlang:localtime_to_universaltime(DateTime, true), Ut = erlang:localtime_to_universaltime(DateTime, false), @@ -242,12 +305,14 @@ local_time_to_universal_time_dst(DateTime) -> %% = MilliSec = integer() %% Returns: {date(), time()}, date() = {Y, M, D}, time() = {H, M, S}. %% --spec now_to_datetime(t_now()) -> t_datetime1970(). +-spec now_to_datetime(Now) -> datetime1970() when + Now :: erlang:timestamp(). now_to_datetime({MSec, Sec, _uSec}) -> Sec0 = MSec*1000000 + Sec + ?DAYS_FROM_0_TO_1970*?SECONDS_PER_DAY, gregorian_seconds_to_datetime(Sec0). --spec now_to_universal_time(t_now()) -> t_datetime1970(). +-spec now_to_universal_time(Now) -> datetime1970() when + Now :: erlang:timestamp(). now_to_universal_time(Now) -> now_to_datetime(Now). @@ -256,7 +321,8 @@ now_to_universal_time(Now) -> %% %% Args: Now = now() %% --spec now_to_local_time(t_now()) -> t_datetime1970(). +-spec now_to_local_time(Now) -> datetime1970() when + Now :: erlang:timestamp(). now_to_local_time({MSec, Sec, _uSec}) -> erlang:universaltime_to_localtime( now_to_universal_time({MSec, Sec, _uSec})). @@ -265,7 +331,10 @@ now_to_local_time({MSec, Sec, _uSec}) -> %% seconds_to_daystime(Secs) = {Days, {Hour, Minute, Second}} %% --spec seconds_to_daystime(integer()) -> {integer(), t_time()}. +-spec seconds_to_daystime(Seconds) -> {Days, Time} when + Seconds :: integer(), + Days :: integer(), + Time :: time(). seconds_to_daystime(Secs) -> Days0 = Secs div ?SECONDS_PER_DAY, Secs0 = Secs rem ?SECONDS_PER_DAY, @@ -283,7 +352,8 @@ seconds_to_daystime(Secs) -> %% Wraps. %% -type secs_per_day() :: 0..?SECONDS_PER_DAY. --spec seconds_to_time(secs_per_day()) -> t_time(). +-spec seconds_to_time(Seconds) -> time() when + Seconds :: secs_per_day(). seconds_to_time(Secs) when Secs >= 0, Secs < ?SECONDS_PER_DAY -> Secs0 = Secs rem ?SECONDS_PER_DAY, Hour = Secs0 div ?SECONDS_PER_HOUR, @@ -300,8 +370,11 @@ seconds_to_time(Secs) when Secs >= 0, Secs < ?SECONDS_PER_DAY -> %% Date = {Year, Month, Day}, Time = {Hour, Minute, Sec}, %% Year = Month = Day = Hour = Minute = Sec = integer() %% --type timediff() :: {integer(), t_time()}. --spec time_difference(t_datetime(), t_datetime()) -> timediff(). +-spec time_difference(T1, T2) -> {Days, Time} when + T1 :: datetime(), + T2 :: datetime(), + Days :: integer(), + Time :: time(). time_difference({{Y1, Mo1, D1}, {H1, Mi1, S1}}, {{Y2, Mo2, D2}, {H2, Mi2, S2}}) -> Secs = datetime_to_gregorian_seconds({{Y2, Mo2, D2}, {H2, Mi2, S2}}) - @@ -312,7 +385,8 @@ time_difference({{Y1, Mo1, D1}, {H1, Mi1, S1}}, %% %% time_to_seconds(Time) %% --spec time_to_seconds(t_time()) -> secs_per_day(). +-spec time_to_seconds(Time) -> secs_per_day() when + Time :: time(). time_to_seconds({H, M, S}) when is_integer(H), is_integer(M), is_integer(S) -> H * ?SECONDS_PER_HOUR + M * ?SECONDS_PER_MINUTE + S. @@ -321,14 +395,15 @@ time_to_seconds({H, M, S}) when is_integer(H), is_integer(M), is_integer(S) -> %% universal_time() %% %% Returns: {date(), time()}, date() = {Y, M, D}, time() = {H, M, S}. --spec universal_time() -> t_datetime(). +-spec universal_time() -> datetime(). universal_time() -> erlang:universaltime(). %% universal_time_to_local_time(DateTime) %% --spec universal_time_to_local_time(t_datetime()) -> t_datetime(). +-spec universal_time_to_local_time(DateTime) -> datetime() when + DateTime :: datetime1970(). universal_time_to_local_time(DateTime) -> erlang:universaltime_to_localtime(DateTime). @@ -336,7 +411,10 @@ universal_time_to_local_time(DateTime) -> %% valid_date(Year, Month, Day) = true | false %% valid_date({Year, Month, Day}) = true | false %% --spec valid_date(integer(), integer(), integer()) -> boolean(). +-spec valid_date(Year, Month, Day) -> boolean() when + Year :: integer(), + Month :: integer(), + Day :: integer(). valid_date(Y, M, D) when is_integer(Y), is_integer(M), is_integer(D) -> valid_date1(Y, M, D). @@ -346,7 +424,8 @@ valid_date1(Y, M, D) when Y >= 0, M > 0, M < 13, D > 0 -> valid_date1(_, _, _) -> false. --spec valid_date({integer(),integer(),integer()}) -> boolean(). +-spec valid_date(Date) -> boolean() when + Date :: date(). valid_date({Y, M, D}) -> valid_date(Y, M, D). @@ -377,6 +456,19 @@ dty(Y, D1, D2) when D1 < D2 -> dty(Y, _D1, D2) -> {Y, D2}. +%% +%% The Gregorian days of the iso week 01 day 1 for a given year. +%% +-spec gregorian_days_of_iso_w01_1(year()) -> non_neg_integer(). +gregorian_days_of_iso_w01_1(Year) -> + D0101 = date_to_gregorian_days(Year, 1, 1), + DOW = day_of_the_week(Year, 1, 1), + if DOW =< 4 -> + D0101 - DOW + 1; + true -> + D0101 + 7 - DOW + 1 + end. + %% year_day_to_date(Year, DayOfYear) = {Month, DayOfMonth} %% %% Note: 1 is the first day of the month. diff --git a/lib/stdlib/src/dets.erl b/lib/stdlib/src/dets.erl index 7f1c13770b..fa0641ffd9 100644 --- a/lib/stdlib/src/dets.erl +++ b/lib/stdlib/src/dets.erl @@ -1,19 +1,19 @@ %% %% %CopyrightBegin% -%% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. -%% +%% +%% Copyright Ericsson AB 1996-2011. 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 %% compliance with the License. You should have received a copy of the %% Erlang Public License along with this software. If not, it can be %% retrieved online at http://www.erlang.org/. -%% +%% %% Software distributed under the License is distributed on an "AS IS" %% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See %% the License for the specific language governing rights and limitations %% under the License. -%% +%% %% %CopyrightEnd% %% -module(dets). @@ -88,6 +88,7 @@ %% Not documented, or not ready for publication. -export([lookup_keys/2]). +-export_type([tab_name/0]). -compile({inline, [{einval,2},{badarg,2},{undefined,1}, {badarg_exit,2},{lookup_reply,2}]}). @@ -96,10 +97,6 @@ -include("dets.hrl"). --type object() :: tuple(). --type pattern() :: atom() | tuple(). --type tab_name() :: atom() | reference(). - %%% This is the implementation of the mnesia file storage. Each (non %%% ram-copy) table is maintained in a corresponding .DAT file. The %%% dat file is organized as a segmented linear hashlist. The head of @@ -146,6 +143,7 @@ bin, % small chunk not consumed, or 'eof' at end-of-file alloc, % the part of the file not yet scanned, mostly a binary tab, + proc, % the pid of the Dets process match_program % true | compiled_match_spec() | undefined }). @@ -177,6 +175,21 @@ %%-define(PROFILE(C), C). -define(PROFILE(C), void). +-type access() :: 'read' | 'read_write'. +-type auto_save() :: 'infinity' | non_neg_integer(). +-opaque bindings_cont() :: #dets_cont{}. +-opaque cont() :: #dets_cont{}. +-type keypos() :: pos_integer(). +-type match_spec() :: ets:match_spec(). +-type object() :: tuple(). +-type no_slots() :: non_neg_integer() | 'default'. +-opaque object_cont() :: #dets_cont{}. +-type pattern() :: atom() | tuple(). +-opaque select_cont() :: #dets_cont{}. +-type tab_name() :: term(). +-type type() :: 'bag' | 'duplicate_bag' | 'set'. +-type version() :: 8 | 9 | 'default'. + %%% Some further debug code was added in R12B-1 (stdlib-1.15.1): %%% - there is a new open_file() option 'debug'; %%% - there is a new OS environment variable 'DETS_DEBUG'; @@ -201,20 +214,24 @@ add_user(Pid, Tab, Args) -> all() -> dets_server:all(). --type cont() :: #dets_cont{}. --spec bchunk(tab_name(), 'start' | cont()) -> - {cont(), binary() | tuple()} | '$end_of_table' | {'error', term()}. +-spec bchunk(Name, Continuation) -> + {Continuation2, Data} | '$end_of_table' | {'error', Reason} when + Name :: tab_name(), + Continuation :: 'start' | cont(), + Continuation2 :: cont(), + Data :: binary() | tuple(), + Reason :: term(). bchunk(Tab, start) -> badarg(treq(Tab, {bchunk_init, Tab}), [Tab, start]); -bchunk(Tab, #dets_cont{bin = eof, tab = Tab}) -> - '$end_of_table'; bchunk(Tab, #dets_cont{what = bchunk, tab = Tab} = State) -> badarg(treq(Tab, {bchunk, State}), [Tab, State]); bchunk(Tab, Term) -> erlang:error(badarg, [Tab, Term]). --spec close(tab_name()) -> 'ok' | {'error', term()}. +-spec close(Name) -> 'ok' | {'error', Reason} when + Name :: tab_name(), + Reason :: term(). close(Tab) -> case dets_server:close(Tab) of @@ -224,12 +241,17 @@ close(Tab) -> Reply end. --spec delete(tab_name(), term()) -> 'ok' | {'error', term()}. +-spec delete(Name, Key) -> 'ok' | {'error', Reason} when + Name :: tab_name(), + Key :: term(), + Reason :: term(). delete(Tab, Key) -> badarg(treq(Tab, {delete_key, [Key]}), [Tab, Key]). --spec delete_all_objects(tab_name()) -> 'ok' | {'error', term()}. +-spec delete_all_objects(Name) -> 'ok' | {'error', Reason} when + Name :: tab_name(), + Reason :: term(). delete_all_objects(Tab) -> case treq(Tab, delete_all_objects) of @@ -241,7 +263,10 @@ delete_all_objects(Tab) -> Reply end. --spec delete_object(tab_name(), object()) -> 'ok' | {'error', term()}. +-spec delete_object(Name, Object) -> 'ok' | {'error', Reason} when + Name :: tab_name(), + Object :: object(), + Reason :: term(). delete_object(Tab, O) -> badarg(treq(Tab, {delete_object, [O]}), [Tab, O]). @@ -264,23 +289,42 @@ fsck(Fname, Version) -> end end. --spec first(tab_name()) -> term() | '$end_of_table'. +-spec first(Name) -> Key | '$end_of_table' when + Name :: tab_name(), + Key :: term(). first(Tab) -> badarg_exit(treq(Tab, first), [Tab]). --spec foldr(fun((object(), Acc) -> Acc), Acc, tab_name()) -> Acc | {'error', term()}. +-spec foldr(Function, Acc0, Name) -> Acc | {'error', Reason} when + Name :: tab_name(), + Function :: fun((Object :: object(), AccIn) -> AccOut), + Acc0 :: term(), + Acc :: term(), + AccIn :: term(), + AccOut :: term(), + Reason :: term(). foldr(Fun, Acc, Tab) -> foldl(Fun, Acc, Tab). --spec foldl(fun((object(), Acc) -> Acc), Acc, tab_name()) -> Acc | {'error', term()}. +-spec foldl(Function, Acc0, Name) -> Acc | {'error', Reason} when + Name :: tab_name(), + Function :: fun((Object :: object(), AccIn) -> AccOut), + Acc0 :: term(), + Acc :: term(), + AccIn :: term(), + AccOut :: term(), + Reason :: term(). foldl(Fun, Acc, Tab) -> Ref = make_ref(), do_traverse(Fun, Acc, Tab, Ref). --spec from_ets(tab_name(), ets:tab()) -> 'ok' | {'error', term()}. +-spec from_ets(Name, EtsTab) -> 'ok' | {'error', Reason} when + Name :: tab_name(), + EtsTab :: ets:tab(), + Reason :: term(). from_ets(DTab, ETab) -> ets:safe_fixtable(ETab, true), @@ -304,6 +348,15 @@ from_ets_fun(LC, ETab) -> {L, from_ets_fun(ets:select(C), ETab)} end. +-spec info(Name) -> InfoList | 'undefined' when + Name :: tab_name(), + InfoList :: [InfoTuple], + InfoTuple :: {'file_size', non_neg_integer()} + | {'filename', file:name()} + | {'keypos', keypos()} + | {'size', non_neg_integer()} + | {'type', type()}. + info(Tab) -> case catch dets_server:get_pid(Tab) of {'EXIT', _Reason} -> @@ -312,6 +365,14 @@ info(Tab) -> undefined(req(Pid, info)) end. +-spec info(Name, Item) -> Value | 'undefined' when + Name :: tab_name(), + Item :: 'access' | 'auto_save' | 'bchunk_format' + | 'hash' | 'file_size' | 'filename' | 'keypos' | 'memory' + | 'no_keys' | 'no_objects' | 'no_slots' | 'owner' | 'ram_file' + | 'safe_fixed' | 'size' | 'type' | 'version', + Value :: term(). + info(Tab, owner) -> case catch dets_server:get_pid(Tab) of Pid when is_pid(Pid) -> @@ -334,9 +395,27 @@ info(Tab, Tag) -> undefined(req(Pid, {info, Tag})) end. +-spec init_table(Name, InitFun) -> ok | {'error', Reason} when + Name :: tab_name(), + InitFun :: fun((Arg) -> Res), + Arg :: read | close, + Res :: end_of_input | {[object()], InitFun} | {Data, InitFun} | term(), + Reason :: term(), + Data :: binary() | tuple(). + init_table(Tab, InitFun) -> init_table(Tab, InitFun, []). +-spec init_table(Name, InitFun, Options) -> ok | {'error', Reason} when + Name :: tab_name(), + InitFun :: fun((Arg) -> Res), + Arg :: read | close, + Res :: end_of_input | {[object()], InitFun} | {Data, InitFun} | term(), + Options :: Option | [Option], + Option :: {min_no_slots,no_slots()} | {format,term | bchunk}, + Reason :: term(), + Data :: binary() | tuple(). + init_table(Tab, InitFun, Options) when is_function(InitFun) -> case options(Options, [format, min_no_slots]) of {badarg,_} -> @@ -350,11 +429,20 @@ init_table(Tab, InitFun, Options) when is_function(InitFun) -> init_table(Tab, InitFun, Options) -> erlang:error(badarg, [Tab, InitFun, Options]). +-spec insert(Name, Objects) -> 'ok' | {'error', Reason} when + Name :: tab_name(), + Objects :: object() | [object()], + Reason :: term(). + insert(Tab, Objs) when is_list(Objs) -> badarg(treq(Tab, {insert, Objs}), [Tab, Objs]); insert(Tab, Obj) -> badarg(treq(Tab, {insert, [Obj]}), [Tab, Obj]). +-spec insert_new(Name, Objects) -> boolean() when + Name :: tab_name(), + Objects :: object() | [object()]. + insert_new(Tab, Objs) when is_list(Objs) -> badarg(treq(Tab, {insert_new, Objs}), [Tab, Objs]); insert_new(Tab, Obj) -> @@ -366,9 +454,17 @@ internal_close(Pid) -> internal_open(Pid, Ref, Args) -> req(Pid, {internal_open, Ref, Args}). +-spec is_compatible_bchunk_format(Name, BchunkFormat) -> boolean() when + Name :: tab_name(), + BchunkFormat :: binary(). + is_compatible_bchunk_format(Tab, Term) -> badarg(treq(Tab, {is_compatible_bchunk_format, Term}), [Tab, Term]). +-spec is_dets_file(Filename) -> boolean() | {'error', Reason} when + Filename :: file:name(), + Reason :: term(). + is_dets_file(FileName) -> case catch read_file_header(FileName, read, false) of {ok, Fd, FH} -> @@ -382,6 +478,12 @@ is_dets_file(FileName) -> Other end. +-spec lookup(Name, Key) -> Objects | {'error', Reason} when + Name :: tab_name(), + Key :: term(), + Objects :: [object()], + Reason :: term(). + lookup(Tab, Key) -> badarg(treq(Tab, {lookup_keys, [Key]}), [Tab, Key]). @@ -394,19 +496,43 @@ lookup_keys(Tab, Keys) -> erlang:error(badarg, [Tab, Keys]) end. +-spec match(Name, Pattern) -> [Match] | {'error', Reason} when + Name :: tab_name(), + Pattern :: pattern(), + Match :: [term()], + Reason :: term(). + match(Tab, Pat) -> badarg(safe_match(Tab, Pat, bindings), [Tab, Pat]). +-spec match(Name, Pattern, N) -> + {[Match], Continuation} | '$end_of_table' | {'error', Reason} when + Name :: tab_name(), + Pattern :: pattern(), + N :: 'default' | non_neg_integer(), + Continuation :: bindings_cont(), + Match :: [term()], + Reason :: term(). + match(Tab, Pat, N) -> badarg(init_chunk_match(Tab, Pat, bindings, N), [Tab, Pat, N]). +-spec match(Continuation) -> + {[Match], Continuation2} | '$end_of_table' | {'error', Reason} when + Continuation :: bindings_cont(), + Continuation2 :: bindings_cont(), + Match :: [term()], + Reason :: term(). + match(State) when State#dets_cont.what =:= bindings -> badarg(chunk_match(State), [State]); match(Term) -> erlang:error(badarg, [Term]). --spec match_delete(tab_name(), pattern()) -> - non_neg_integer() | 'ok' | {'error', term()}. +-spec match_delete(Name, Pattern) -> 'ok' | {'error', Reason} when + Name :: tab_name(), + Pattern :: pattern(), + Reason :: term(). match_delete(Tab, Pat) -> badarg(match_delete(Tab, Pat, delete), [Tab, Pat]). @@ -434,23 +560,60 @@ do_match_delete(Tab, _Proc, Error, _What, _N) -> safe_fixtable(Tab, false), Error. +-spec match_object(Name, Pattern) -> Objects | {'error', Reason} when + Name :: tab_name(), + Pattern :: pattern(), + Objects :: [object()], + Reason :: term(). + match_object(Tab, Pat) -> badarg(safe_match(Tab, Pat, object), [Tab, Pat]). +-spec match_object(Name, Pattern, N) -> + {Objects, Continuation} | '$end_of_table' | {'error', Reason} when + Name :: tab_name(), + Pattern :: pattern(), + N :: 'default' | non_neg_integer(), + Continuation :: object_cont(), + Objects :: [object()], + Reason :: term(). + match_object(Tab, Pat, N) -> badarg(init_chunk_match(Tab, Pat, object, N), [Tab, Pat, N]). +-spec match_object(Continuation) -> + {Objects, Continuation2} | '$end_of_table' | {'error', Reason} when + Continuation :: object_cont(), + Continuation2 :: object_cont(), + Objects :: [object()], + Reason :: term(). + match_object(State) when State#dets_cont.what =:= object -> badarg(chunk_match(State), [State]); match_object(Term) -> erlang:error(badarg, [Term]). +-spec member(Name, Key) -> boolean() | {'error', Reason} when + Name :: tab_name(), + Key :: term(), + Reason :: term(). + member(Tab, Key) -> badarg(treq(Tab, {member, Key}), [Tab, Key]). +-spec next(Name, Key1) -> Key2 | '$end_of_table' when + Name :: tab_name(), + Key1 :: term(), + Key2 :: term(). + next(Tab, Key) -> badarg_exit(treq(Tab, {next, Key}), [Tab, Key]). +-spec open_file(Filename) -> {'ok', Reference} | {'error', Reason} when + Filename :: file:name(), + Reference :: reference(), + Reason :: term(). + %% Assuming that a file already exists, open it with the %% parameters as already specified in the file itself. %% Return a ref leading to the file. @@ -462,6 +625,22 @@ open_file(File) -> einval(Reply, [File]) end. +-spec open_file(Name, Args) -> {'ok', Name} | {'error', Reason} when + Name :: tab_name(), + Args :: [OpenArg], + OpenArg :: {'access', access()} + | {'auto_save', auto_save()} + | {'estimated_no_objects', non_neg_integer()} + | {'file', file:name()} + | {'max_no_slots', no_slots()} + | {'min_no_slots', no_slots()} + | {'keypos', keypos()} + | {'ram_file', boolean()} + | {'repair', boolean() | 'force'} + | {'type', type()} + | {'version', version()}, + Reason :: term(). + open_file(Tab, Args) when is_list(Args) -> case catch defaults(Tab, Args) of OpenArgs when is_record(OpenArgs, open_args) -> @@ -477,12 +656,21 @@ open_file(Tab, Args) when is_list(Args) -> open_file(Tab, Arg) -> open_file(Tab, [Arg]). +-spec pid2name(Pid) -> {'ok', Name} | 'undefined' when + Pid :: pid(), + Name :: tab_name(). + pid2name(Pid) -> dets_server:pid2name(Pid). remove_user(Pid, From) -> req(Pid, {close, From}). +-spec repair_continuation(Continuation, MatchSpec) -> Continuation2 when + Continuation :: select_cont(), + Continuation2 :: select_cont(), + MatchSpec :: match_spec(). + repair_continuation(#dets_cont{match_program = B}=Cont, MS) when is_binary(B) -> case ets:is_compiled_ms(B) of @@ -496,25 +684,63 @@ repair_continuation(#dets_cont{}=Cont, _MS) -> repair_continuation(T, MS) -> erlang:error(badarg, [T, MS]). +-spec safe_fixtable(Name, Fix) -> 'ok' when + Name :: tab_name(), + Fix :: boolean(). + safe_fixtable(Tab, Bool) when Bool; not Bool -> badarg(treq(Tab, {safe_fixtable, Bool}), [Tab, Bool]); safe_fixtable(Tab, Term) -> erlang:error(badarg, [Tab, Term]). +-spec select(Name, MatchSpec) -> Selection | {'error', Reason} when + Name :: tab_name(), + MatchSpec :: match_spec(), + Selection :: [term()], + Reason :: term(). + select(Tab, Pat) -> badarg(safe_match(Tab, Pat, select), [Tab, Pat]). +-spec select(Name, MatchSpec, N) -> + {Selection, Continuation} | '$end_of_table' | {'error', Reason} when + Name :: tab_name(), + MatchSpec :: match_spec(), + N :: 'default' | non_neg_integer(), + Continuation :: select_cont(), + Selection :: [term()], + Reason :: term(). + select(Tab, Pat, N) -> badarg(init_chunk_match(Tab, Pat, select, N), [Tab, Pat, N]). +-spec select(Continuation) -> + {Selection, Continuation2} | '$end_of_table' | {'error', Reason} when + Continuation :: select_cont(), + Continuation2 :: select_cont(), + Selection :: [term()], + Reason :: term(). + select(State) when State#dets_cont.what =:= select -> badarg(chunk_match(State), [State]); select(Term) -> erlang:error(badarg, [Term]). +-spec select_delete(Name, MatchSpec) -> N | {'error', Reason} when + Name :: tab_name(), + MatchSpec :: match_spec(), + N :: non_neg_integer(), + Reason :: term(). + select_delete(Tab, Pat) -> badarg(match_delete(Tab, Pat, select), [Tab, Pat]). +-spec slot(Name, I) -> '$end_of_table' | Objects | {'error', Reason} when + Name :: tab_name(), + I :: non_neg_integer(), + Objects :: [object()], + Reason :: term(). + slot(Tab, Slot) when is_integer(Slot), Slot >= 0 -> badarg(treq(Tab, {slot, Slot}), [Tab, Slot]); slot(Tab, Term) -> @@ -529,12 +755,29 @@ stop() -> istart_link(Server) -> {ok, proc_lib:spawn_link(dets, init, [self(), Server])}. +-spec sync(Name) -> 'ok' | {'error', Reason} when + Name :: tab_name(), + Reason :: term(). + sync(Tab) -> badarg(treq(Tab, sync), [Tab]). +-spec table(Name) -> QueryHandle when + Name :: tab_name(), + QueryHandle :: qlc:query_handle(). + table(Tab) -> table(Tab, []). +-spec table(Name, Options) -> QueryHandle when + Name :: tab_name(), + Options :: Option | [Option], + Option :: {'n_objects', Limit} + | {'traverse', TraverseMethod}, + Limit :: 'default' | pos_integer(), + TraverseMethod :: 'first_next' | 'select' | {'select', match_spec()}, + QueryHandle :: qlc:query_handle(). + table(Tab, Opts) -> case options(Opts, [traverse, n_objects]) of {badarg,_} -> @@ -612,6 +855,11 @@ table_info(_Tab, _) -> %% End of table/2. +-spec to_ets(Name, EtsTab) -> EtsTab | {'error', Reason} when + Name :: tab_name(), + EtsTab :: ets:tab(), + Reason :: term(). + to_ets(DTab, ETab) -> case ets:info(ETab, protection) of undefined -> @@ -621,6 +869,20 @@ to_ets(DTab, ETab) -> foldl(Fun, ETab, DTab) end. +-spec traverse(Name, Fun) -> Return | {'error', Reason} when + Name :: tab_name(), + Fun :: fun((Object) -> FunReturn), + Object :: object(), + FunReturn :: 'continue' + | {'continue', Val} + | {'done', Value} + | OtherValue, + Return :: [term()] | OtherValue, + Val :: term(), + Value :: term(), + OtherValue :: term(), + Reason :: term(). + traverse(Tab, Fun) -> Ref = make_ref(), TFun = @@ -638,6 +900,14 @@ traverse(Tab, Fun) -> end, do_traverse(TFun, [], Tab, Ref). +-spec update_counter(Name, Key, Increment) -> Result when + Name :: tab_name(), + Key :: term(), + Increment :: {Pos, Incr} | Incr, + Pos :: integer(), + Incr :: integer(), + Result :: integer(). + update_counter(Tab, Key, C) -> badarg(treq(Tab, {update_counter, Key, C}), [Tab, Key, C]). @@ -721,11 +991,14 @@ init_chunk_match(Tab, Pat, What, N) when is_integer(N), N >= 0; N =:= default -> case compile_match_spec(What, Pat) of {Spec, MP} -> - case req(dets_server:get_pid(Tab), {match, MP, Spec, N}) of + Proc = dets_server:get_pid(Tab), + case req(Proc, {match, MP, Spec, N}) of {done, L} -> - {L, #dets_cont{tab = Tab, what = What, bin = eof}}; + {L, #dets_cont{tab = Tab, proc = Proc, what = What, + bin = eof}}; {cont, State} -> - chunk_match(State#dets_cont{what = What, tab = Tab}); + chunk_match(State#dets_cont{what = What, tab = Tab, + proc = Proc}); Error -> Error end; @@ -735,34 +1008,28 @@ init_chunk_match(Tab, Pat, What, N) when is_integer(N), N >= 0; init_chunk_match(_Tab, _Pat, _What, _) -> badarg. -chunk_match(State) -> - case catch dets_server:get_pid(State#dets_cont.tab) of - {'EXIT', _Reason} -> - badarg; - _Proc when State#dets_cont.bin =:= eof -> - '$end_of_table'; - Proc -> - case req(Proc, {match_init, State}) of - {cont, {Bins, NewState}} -> - MP = NewState#dets_cont.match_program, - case catch do_foldl_bins(Bins, MP) of - {'EXIT', _} -> - case ets:is_compiled_ms(MP) of - true -> - Bad = dets_utils:bad_object(chunk_match, - Bins), - req(Proc, {corrupt, Bad}); - false -> - badarg - end; - [] -> - chunk_match(NewState); - Terms -> - {Terms, NewState} - end; - Error -> - Error - end +chunk_match(#dets_cont{proc = Proc}=State) -> + case req(Proc, {match_init, State}) of + '$end_of_table'=Reply -> + Reply; + {cont, {Bins, NewState}} -> + MP = NewState#dets_cont.match_program, + case catch do_foldl_bins(Bins, MP) of + {'EXIT', _} -> + case ets:is_compiled_ms(MP) of + true -> + Bad = dets_utils:bad_object(chunk_match, Bins), + req(Proc, {corrupt, Bad}); + false -> + badarg + end; + [] -> + chunk_match(NewState); + Terms -> + {Terms, NewState} + end; + Error -> + Error end. do_foldl_bins(Bins, true) -> @@ -1093,7 +1360,9 @@ do_apply_op(Op, From, Head, N) -> {N2, H2} when is_record(H2, head), is_integer(N2) -> open_file_loop(H2, N2); H2 when is_record(H2, head) -> - open_file_loop(H2, N) + open_file_loop(H2, N); + {{more,From1,Op1,N1}, NewHead} -> + do_apply_op(Op1, From1, NewHead, N1) catch exit:normal -> exit(normal); @@ -1362,37 +1631,35 @@ start_auto_save_timer(Head) -> %% lookup requests in parallel. Evalute delete_object, delete and %% insert as well. stream_op(Op, Pid, Pids, Head, N) -> - stream_op(Head, Pids, [], N, Pid, Op, Head#head.fixed). + #head{fixed = Fxd, update_mode = M} = Head, + stream_op(Head, Pids, [], N, Pid, Op, Fxd, M). -stream_loop(Head, Pids, C, N, false = Fxd) -> +stream_loop(Head, Pids, C, N, false = Fxd, M) -> receive ?DETS_CALL(From, Message) -> - stream_op(Head, Pids, C, N, From, Message, Fxd) + stream_op(Head, Pids, C, N, From, Message, Fxd, M) after 0 -> stream_end(Head, Pids, C, N, no_more) end; -stream_loop(Head, Pids, C, N, _Fxd) -> +stream_loop(Head, Pids, C, N, _Fxd, _M) -> stream_end(Head, Pids, C, N, no_more). -stream_op(Head, Pids, C, N, Pid, {lookup_keys,Keys}, Fxd) -> +stream_op(Head, Pids, C, N, Pid, {lookup_keys,Keys}, Fxd, M) -> NC = [{{lookup,Pid},Keys} | C], - stream_loop(Head, Pids, NC, N, Fxd); -stream_op(Head, Pids, C, N, Pid, {insert, _Objects} = Op, Fxd) -> - NC = [Op | C], - stream_loop(Head, [Pid | Pids], NC, N, Fxd); -stream_op(Head, Pids, C, N, Pid, {insert_new, _Objects} = Op, Fxd) -> + stream_loop(Head, Pids, NC, N, Fxd, M); +stream_op(Head, Pids, C, N, Pid, {insert, _Objects} = Op, Fxd, dirty = M) -> NC = [Op | C], - stream_loop(Head, [Pid | Pids], NC, N, Fxd); -stream_op(Head, Pids, C, N, Pid, {delete_key, _Keys} = Op, Fxd) -> + stream_loop(Head, [Pid | Pids], NC, N, Fxd, M); +stream_op(Head, Pids, C, N, Pid, {delete_key, _Keys} = Op, Fxd, dirty = M) -> NC = [Op | C], - stream_loop(Head, [Pid | Pids], NC, N, Fxd); -stream_op(Head, Pids, C, N, Pid, {delete_object, _Objects} = Op, Fxd) -> + stream_loop(Head, [Pid | Pids], NC, N, Fxd, M); +stream_op(Head, Pids, C, N, Pid, {delete_object, _Os} = Op, Fxd, dirty = M) -> NC = [Op | C], - stream_loop(Head, [Pid | Pids], NC, N, Fxd); -stream_op(Head, Pids, C, N, Pid, {member, Key}, Fxd) -> + stream_loop(Head, [Pid | Pids], NC, N, Fxd, M); +stream_op(Head, Pids, C, N, Pid, {member, Key}, Fxd, M) -> NC = [{{lookup,[Pid]},[Key]} | C], - stream_loop(Head, Pids, NC, N, Fxd); -stream_op(Head, Pids, C, N, Pid, Op, _Fxd) -> + stream_loop(Head, Pids, NC, N, Fxd, M); +stream_op(Head, Pids, C, N, Pid, Op, _Fxd, _M) -> stream_end(Head, Pids, C, N, {Pid,Op}). stream_end(Head, Pids0, C, N, Next) -> @@ -1437,7 +1704,7 @@ stream_end2([], Ps, no_more, N, C, Head, _Reply) -> penalty(Head, Ps, C), {N, Head}; stream_end2([], _Ps, {From, Op}, N, _C, Head, _Reply) -> - apply_op(Op, From, Head, N). + {{more,From,Op,N},Head}. penalty(H, _Ps, _C) when H#head.fixed =:= false -> ok; @@ -1577,13 +1844,18 @@ do_bchunk_init(Head, Tab) -> L = dets_utils:all_allocated(H2), C0 = #dets_cont{no_objs = default, bin = <<>>, alloc = L}, BinParms = term_to_binary(Parms), - {H2, {C0#dets_cont{tab = Tab, what = bchunk}, [BinParms]}} + {H2, {C0#dets_cont{tab = Tab, proc = self(),what = bchunk}, + [BinParms]}} end; {NewHead, _} = HeadError when is_record(NewHead, head) -> HeadError end. %% -> {NewHead, {cont(), [binary()]}} | {NewHead, Error} +do_bchunk(Head, #dets_cont{proc = Proc}) when Proc =/= self() -> + {Head, badarg}; +do_bchunk(Head, #dets_cont{bin = eof}) -> + {Head, '$end_of_table'}; do_bchunk(Head, State) -> case dets_v9:read_bchunks(Head, State#dets_cont.alloc) of {error, Reason} -> @@ -1953,6 +2225,8 @@ flookup_keys(Head, Keys) -> end. %% -> {NewHead, Result} +fmatch_init(Head, #dets_cont{bin = eof}) -> + {Head, '$end_of_table'}; fmatch_init(Head, C) -> case scan(Head, C) of {scan_error, Reason} -> diff --git a/lib/stdlib/src/dets.hrl b/lib/stdlib/src/dets.hrl index 6e59770753..fbffc9d008 100644 --- a/lib/stdlib/src/dets.hrl +++ b/lib/stdlib/src/dets.hrl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2001-2009. All Rights Reserved. +%% Copyright Ericsson AB 2001-2010. 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,7 +18,7 @@ %% -define(DEFAULT_MIN_NO_SLOTS, 256). --define(DEFAULT_MAX_NO_SLOTS, 2*1024*1024). +-define(DEFAULT_MAX_NO_SLOTS, 32*1024*1024). -define(DEFAULT_AUTOSAVE, 3). % minutes -define(DEFAULT_CACHE, {3000, 14000}). % {delay,size} in {milliseconds,bytes} diff --git a/lib/stdlib/src/dets_sup.erl b/lib/stdlib/src/dets_sup.erl index 5c6caa787d..8ea2ba9b3f 100644 --- a/lib/stdlib/src/dets_sup.erl +++ b/lib/stdlib/src/dets_sup.erl @@ -1,19 +1,19 @@ %% %% %CopyrightBegin% -%% -%% Copyright Ericsson AB 2002-2009. All Rights Reserved. -%% +%% +%% Copyright Ericsson AB 2002-2010. 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 %% compliance with the License. You should have received a copy of the %% Erlang Public License along with this software. If not, it can be %% retrieved online at http://www.erlang.org/. -%% +%% %% Software distributed under the License is distributed on an "AS IS" %% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See %% the License for the specific language governing rights and limitations %% under the License. -%% +%% %% %CopyrightEnd% %% -module(dets_sup). @@ -22,9 +22,16 @@ -export([start_link/0, init/1]). +-spec start_link() -> {'ok', pid()} | 'ignore' | {'error', term()}. + start_link() -> supervisor:start_link({local, dets_sup}, dets_sup, []). +-spec init([]) -> + {'ok', {{'simple_one_for_one', 4, 3600}, + [{'dets', {'dets', 'istart_link', []}, + 'temporary', 30000, 'worker', ['dets']}]}}. + init([]) -> SupFlags = {simple_one_for_one, 4, 3600}, Child = {dets, {dets, istart_link, []}, temporary, 30000, worker, [dets]}, diff --git a/lib/stdlib/src/dets_v8.erl b/lib/stdlib/src/dets_v8.erl index 1f9f84cd27..cdd38d5604 100644 --- a/lib/stdlib/src/dets_v8.erl +++ b/lib/stdlib/src/dets_v8.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2001-2010. All Rights Reserved. +%% Copyright Ericsson AB 2001-2011. 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 @@ -163,7 +163,7 @@ %% The 8(c) version uses a different hashing algorithm, erlang:phash %% (former versions use erlang:hash). %% Version 8(b) files are only converted to version 8(c) if repair is -%% done, so we need compatability with 8(b) for a _long_ time. +%% done, so we need compatibility with 8(b) for a _long_ time. %% %% There are known bugs due to the fact that keys and objects are %% sometimes compared (==) and sometimes matched (=:=). The version @@ -1074,6 +1074,8 @@ wl([], _Type, Del, Lookup, I, Objs) -> [{Del, Lookup, Objs} | I]. %% -> {NewHead, ok} | {NewHead, Error} +may_grow(Head, 0, once) -> + {Head, ok}; may_grow(Head, _N, _How) when Head#head.fixed =/= false -> {Head, ok}; may_grow(#head{access = read}=Head, _N, _How) -> diff --git a/lib/stdlib/src/dets_v9.erl b/lib/stdlib/src/dets_v9.erl index 53238e962f..132af01f79 100644 --- a/lib/stdlib/src/dets_v9.erl +++ b/lib/stdlib/src/dets_v9.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2001-2009. All Rights Reserved. +%% Copyright Ericsson AB 2001-2010. 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 @@ -1908,6 +1908,9 @@ write_cache(Head) -> end. %% -> {NewHead, ok} | {NewHead, Error} +may_grow(Head, 0, once) -> + %% Do not re-hash if there is a chance that the file is not dirty. + {Head, ok}; may_grow(Head, _N, _How) when Head#head.fixed =/= false -> {Head, ok}; may_grow(#head{access = read}=Head, _N, _How) -> diff --git a/lib/stdlib/src/dict.erl b/lib/stdlib/src/dict.erl index 7e51141098..2e9eba4bfa 100644 --- a/lib/stdlib/src/dict.erl +++ b/lib/stdlib/src/dict.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2000-2009. All Rights Reserved. +%% Copyright Ericsson AB 2000-2011. 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 @@ -80,7 +80,9 @@ new() -> Empty = mk_seg(?seg_size), #dict{empty=Empty,segs={Empty}}. --spec is_key(term(), dict()) -> boolean(). +-spec is_key(Key, Dict) -> boolean() when + Key :: term(), + Dict :: dict(). is_key(Key, D) -> Slot = get_slot(D, Key), @@ -91,21 +93,29 @@ find_key(K, [?kv(K,_Val)|_]) -> true; find_key(K, [_|Bkt]) -> find_key(K, Bkt); find_key(_, []) -> false. --spec to_list(dict()) -> [{term(), term()}]. +-spec to_list(Dict) -> List when + Dict :: dict(), + List :: [{Key :: term(), Value :: term()}]. to_list(D) -> fold(fun (Key, Val, List) -> [{Key,Val}|List] end, [], D). --spec from_list([{term(), term()}]) -> dict(). +-spec from_list(List) -> Dict when + List :: [{Key :: term(), Value :: term()}], + Dict :: dict(). from_list(L) -> lists:foldl(fun ({K,V}, D) -> store(K, V, D) end, new(), L). --spec size(dict()) -> non_neg_integer(). +-spec size(Dict) -> non_neg_integer() when + Dict :: dict(). size(#dict{size=N}) when is_integer(N), N >= 0 -> N. --spec fetch(term(), dict()) -> term(). +-spec fetch(Key, Dict) -> Value when + Key :: term(), + Dict :: dict(), + Value :: term(). fetch(Key, D) -> Slot = get_slot(D, Key), @@ -119,7 +129,10 @@ fetch_val(K, [?kv(K,Val)|_]) -> Val; fetch_val(K, [_|Bkt]) -> fetch_val(K, Bkt); fetch_val(_, []) -> throw(badarg). --spec find(term(), dict()) -> {'ok', term()} | 'error'. +-spec find(Key, Dict) -> {'ok', Value} | 'error' when + Key :: term(), + Dict :: dict(), + Value :: term(). find(Key, D) -> Slot = get_slot(D, Key), @@ -130,12 +143,17 @@ find_val(K, [?kv(K,Val)|_]) -> {ok,Val}; find_val(K, [_|Bkt]) -> find_val(K, Bkt); find_val(_, []) -> error. --spec fetch_keys(dict()) -> [term()]. +-spec fetch_keys(Dict) -> Keys when + Dict :: dict(), + Keys :: [term()]. fetch_keys(D) -> fold(fun (Key, _Val, Keys) -> [Key|Keys] end, [], D). --spec erase(term(), dict()) -> dict(). +-spec erase(Key, Dict1) -> Dict2 when + Key :: term(), + Dict1 :: dict(), + Dict2 :: dict(). %% Erase all elements with key Key. erase(Key, D0) -> @@ -150,7 +168,11 @@ erase_key(Key, [E|Bkt0]) -> {[E|Bkt1],Dc}; erase_key(_, []) -> {[],0}. --spec store(term(), term(), dict()) -> dict(). +-spec store(Key, Value, Dict1) -> Dict2 when + Key :: term(), + Value :: term(), + Dict1 :: dict(), + Dict2 :: dict(). store(Key, Val, D0) -> Slot = get_slot(D0, Key), @@ -166,7 +188,11 @@ store_bkt_val(Key, New, [Other|Bkt0]) -> {[Other|Bkt1],Ic}; store_bkt_val(Key, New, []) -> {[?kv(Key,New)],1}. --spec append(term(), term(), dict()) -> dict(). +-spec append(Key, Value, Dict1) -> Dict2 when + Key :: term(), + Value :: term(), + Dict1 :: dict(), + Dict2 :: dict(). append(Key, Val, D0) -> Slot = get_slot(D0, Key), @@ -182,7 +208,11 @@ append_bkt(Key, Val, [Other|Bkt0]) -> {[Other|Bkt1],Ic}; append_bkt(Key, Val, []) -> {[?kv(Key,[Val])],1}. --spec append_list(term(), [term()], dict()) -> dict(). +-spec append_list(Key, ValList, Dict1) -> Dict2 when + Key :: term(), + ValList :: [Value :: term()], + Dict1 :: dict(), + Dict2 :: dict(). append_list(Key, L, D0) -> Slot = get_slot(D0, Key), @@ -252,7 +282,11 @@ app_list_bkt(Key, L, []) -> {[?kv(Key,L)],1}. %% {Bkt1,Dc} = on_key_bkt(Key, F, Bkt0), %% {[Other|Bkt1],Dc}. --spec update(term(), fun((term()) -> term()), dict()) -> dict(). +-spec update(Key, Fun, Dict1) -> Dict2 when + Key :: term(), + Fun :: fun((Value1 :: term()) -> Value2 :: term()), + Dict1 :: dict(), + Dict2 :: dict(). update(Key, F, D0) -> Slot = get_slot(D0, Key), @@ -271,7 +305,12 @@ update_bkt(Key, F, [Other|Bkt0]) -> update_bkt(_Key, _F, []) -> throw(badarg). --spec update(term(), fun((term()) -> term()), term(), dict()) -> dict(). +-spec update(Key, Fun, Initial, Dict1) -> Dict2 when + Key :: term(), + Initial :: term(), + Fun :: fun((Value1 :: term()) -> Value2 :: term()), + Dict1 :: dict(), + Dict2 :: dict(). update(Key, F, Init, D0) -> Slot = get_slot(D0, Key), @@ -286,7 +325,11 @@ update_bkt(Key, F, I, [Other|Bkt0]) -> {[Other|Bkt1],Ic}; update_bkt(Key, F, I, []) when is_function(F, 1) -> {[?kv(Key,I)],1}. --spec update_counter(term(), number(), dict()) -> dict(). +-spec update_counter(Key, Increment, Dict1) -> Dict2 when + Key :: term(), + Increment :: number(), + Dict1 :: dict(), + Dict2 :: dict(). update_counter(Key, Incr, D0) when is_number(Incr) -> Slot = get_slot(D0, Key), @@ -301,20 +344,38 @@ counter_bkt(Key, I, [Other|Bkt0]) -> {[Other|Bkt1],Ic}; counter_bkt(Key, I, []) -> {[?kv(Key,I)],1}. --spec fold(fun((term(), term(), term()) -> term()), term(), dict()) -> term(). +-spec fold(Fun, Acc0, Dict) -> Acc1 when + Fun :: fun((Key, Value, AccIn) -> AccOut), + Key :: term(), + Value :: term(), + Acc0 :: term(), + Acc1 :: term(), + AccIn :: term(), + AccOut :: term(), + Dict :: dict(). %% Fold function Fun over all "bags" in Table and return Accumulator. fold(F, Acc, D) -> fold_dict(F, Acc, D). --spec map(fun((term(), term()) -> term()), dict()) -> dict(). +-spec map(Fun, Dict1) -> Dict2 when + Fun :: fun((Key :: term(), Value1 :: term()) -> Value2 :: term()), + Dict1 :: dict(), + Dict2 :: dict(). map(F, D) -> map_dict(F, D). --spec filter(fun((term(), term()) -> boolean()), dict()) -> dict(). +-spec filter(Pred, Dict1) -> Dict2 when + Pred :: fun((Key :: term(), Value :: term()) -> boolean()), + Dict1 :: dict(), + Dict2 :: dict(). filter(F, D) -> filter_dict(F, D). --spec merge(fun((term(), term(), term()) -> term()), dict(), dict()) -> dict(). +-spec merge(Fun, Dict1, Dict2) -> Dict3 when + Fun :: fun((Key :: term(), Value1 :: term(), Value2 :: term()) -> Value :: term()), + Dict1 :: dict(), + Dict2 :: dict(), + Dict3 :: dict(). merge(F, D1, D2) when D1#dict.size < D2#dict.size -> fold_dict(fun (K, V1, D) -> diff --git a/lib/stdlib/src/digraph.erl b/lib/stdlib/src/digraph.erl index 9bdea671a9..e3f87d2c57 100644 --- a/lib/stdlib/src/digraph.erl +++ b/lib/stdlib/src/digraph.erl @@ -1,19 +1,19 @@ %% %% %CopyrightBegin% -%% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. -%% +%% +%% Copyright Ericsson AB 1996-2011. 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 %% compliance with the License. You should have received a copy of the %% Erlang Public License along with this software. If not, it can be %% retrieved online at http://www.erlang.org/. -%% +%% %% Software distributed under the License is distributed on an "AS IS" %% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See %% the License for the specific language governing rights and limitations %% under the License. -%% +%% %% %CopyrightEnd% %% -module(digraph). @@ -36,6 +36,8 @@ -export([get_short_path/3, get_short_cycle/2]). +-export_type([digraph/0, d_type/0, vertex/0]). + -record(digraph, {vtab = notable :: ets:tab(), etab = notable :: ets:tab(), ntab = notable :: ets:tab(), @@ -51,7 +53,8 @@ -type label() :: term(). -type vertex() :: term(). --type add_edge_err_rsn() :: {'bad_edge', [vertex()]} | {'bad_vertex', vertex()}. +-type add_edge_err_rsn() :: {'bad_edge', Path :: [vertex()]} + | {'bad_vertex', V :: vertex()}. %% %% Type is a list of @@ -68,7 +71,8 @@ new() -> new([]). --spec new([d_type()]) -> digraph(). +-spec new(Type) -> digraph() when + Type :: [d_type()]. new(Type) -> case check_type(Type, protected, []) of @@ -111,16 +115,20 @@ set_type([], G) -> G. %% Data access functions --spec delete(digraph()) -> 'true'. +-spec delete(G) -> 'true' when + G :: digraph(). delete(G) -> ets:delete(G#digraph.vtab), ets:delete(G#digraph.etab), ets:delete(G#digraph.ntab). --spec info(digraph()) -> [{'cyclicity', d_cyclicity()} | - {'memory', non_neg_integer()} | - {'protection', d_protection()}]. +-spec info(G) -> InfoList when + G :: digraph(), + InfoList :: [{'cyclicity', Cyclicity :: d_cyclicity()} | + {'memory', NoWords :: non_neg_integer()} | + {'protection', Protection :: d_protection()}]. + info(G) -> VT = G#digraph.vtab, ET = G#digraph.etab, @@ -133,32 +141,45 @@ info(G) -> Memory = ets:info(VT, memory) + ets:info(ET, memory) + ets:info(NT, memory), [{cyclicity, Cyclicity}, {memory, Memory}, {protection, Protection}]. --spec add_vertex(digraph()) -> vertex(). +-spec add_vertex(G) -> vertex() when + G :: digraph(). add_vertex(G) -> do_add_vertex({new_vertex_id(G), []}, G). --spec add_vertex(digraph(), vertex()) -> vertex(). +-spec add_vertex(G, V) -> vertex() when + G :: digraph(), + V :: vertex(). add_vertex(G, V) -> do_add_vertex({V, []}, G). --spec add_vertex(digraph(), vertex(), label()) -> vertex(). +-spec add_vertex(G, V, Label) -> vertex() when + G :: digraph(), + V :: vertex(), + Label :: label(). add_vertex(G, V, D) -> do_add_vertex({V, D}, G). --spec del_vertex(digraph(), vertex()) -> 'true'. +-spec del_vertex(G, V) -> 'true' when + G :: digraph(), + V :: vertex(). del_vertex(G, V) -> do_del_vertex(V, G). --spec del_vertices(digraph(), [vertex()]) -> 'true'. +-spec del_vertices(G, Vertices) -> 'true' when + G :: digraph(), + Vertices :: [vertex()]. del_vertices(G, Vs) -> do_del_vertices(Vs, G). --spec vertex(digraph(), vertex()) -> {vertex(), label()} | 'false'. +-spec vertex(G, V) -> {V, Label} | 'false' when + G :: digraph(), + V :: vertex(), + Label :: label(). vertex(G, V) -> case ets:lookup(G#digraph.vtab, V) of @@ -166,12 +187,15 @@ vertex(G, V) -> [Vertex] -> Vertex end. --spec no_vertices(digraph()) -> non_neg_integer(). +-spec no_vertices(G) -> non_neg_integer() when + G :: digraph(). no_vertices(G) -> ets:info(G#digraph.vtab, size). --spec vertices(digraph()) -> [vertex()]. +-spec vertices(G) -> Vertices when + G :: digraph(), + Vertices :: [vertex()]. vertices(G) -> ets:select(G#digraph.vtab, [{{'$1', '_'}, [], ['$1']}]). @@ -186,85 +210,125 @@ source_vertices(G) -> sink_vertices(G) -> collect_vertices(G, out). --spec in_degree(digraph(), vertex()) -> non_neg_integer(). +-spec in_degree(G, V) -> non_neg_integer() when + G :: digraph(), + V :: vertex(). in_degree(G, V) -> length(ets:lookup(G#digraph.ntab, {in, V})). --spec in_neighbours(digraph(), vertex()) -> [vertex()]. +-spec in_neighbours(G, V) -> Vertex when + G :: digraph(), + V :: vertex(), + Vertex :: [vertex()]. in_neighbours(G, V) -> ET = G#digraph.etab, NT = G#digraph.ntab, collect_elems(ets:lookup(NT, {in, V}), ET, 2). --spec in_edges(digraph(), vertex()) -> [edge()]. +-spec in_edges(G, V) -> Edges when + G :: digraph(), + V :: vertex(), + Edges :: [edge()]. in_edges(G, V) -> ets:select(G#digraph.ntab, [{{{in, V}, '$1'}, [], ['$1']}]). --spec out_degree(digraph(), vertex()) -> non_neg_integer(). +-spec out_degree(G, V) -> non_neg_integer() when + G :: digraph(), + V :: vertex(). out_degree(G, V) -> length(ets:lookup(G#digraph.ntab, {out, V})). --spec out_neighbours(digraph(), vertex()) -> [vertex()]. +-spec out_neighbours(G, V) -> Vertices when + G :: digraph(), + V :: vertex(), + Vertices :: [vertex()]. out_neighbours(G, V) -> ET = G#digraph.etab, NT = G#digraph.ntab, collect_elems(ets:lookup(NT, {out, V}), ET, 3). --spec out_edges(digraph(), vertex()) -> [edge()]. +-spec out_edges(G, V) -> Edges when + G :: digraph(), + V :: vertex(), + Edges :: [edge()]. out_edges(G, V) -> ets:select(G#digraph.ntab, [{{{out, V}, '$1'}, [], ['$1']}]). --spec add_edge(digraph(), vertex(), vertex()) -> - edge() | {'error', add_edge_err_rsn()}. +-spec add_edge(G, V1, V2) -> edge() | {'error', add_edge_err_rsn()} when + G :: digraph(), + V1 :: vertex(), + V2 :: vertex(). add_edge(G, V1, V2) -> do_add_edge({new_edge_id(G), V1, V2, []}, G). --spec add_edge(digraph(), vertex(), vertex(), label()) -> - edge() | {'error', add_edge_err_rsn()}. +-spec add_edge(G, V1, V2, Label) -> edge() | {'error', add_edge_err_rsn()} when + G :: digraph(), + V1 :: vertex(), + V2 :: vertex(), + Label :: label(). add_edge(G, V1, V2, D) -> do_add_edge({new_edge_id(G), V1, V2, D}, G). --spec add_edge(digraph(), edge(), vertex(), vertex(), label()) -> - edge() | {'error', add_edge_err_rsn()}. +-spec add_edge(G, E, V1, V2, Label) -> edge() | {'error', add_edge_err_rsn()} when + G :: digraph(), + E :: edge(), + V1 :: vertex(), + V2 :: vertex(), + Label :: label(). add_edge(G, E, V1, V2, D) -> do_add_edge({E, V1, V2, D}, G). --spec del_edge(digraph(), edge()) -> 'true'. +-spec del_edge(G, E) -> 'true' when + G :: digraph(), + E :: edge(). del_edge(G, E) -> do_del_edges([E], G). --spec del_edges(digraph(), [edge()]) -> 'true'. +-spec del_edges(G, Edges) -> 'true' when + G :: digraph(), + Edges :: [edge()]. del_edges(G, Es) -> do_del_edges(Es, G). --spec no_edges(digraph()) -> non_neg_integer(). +-spec no_edges(G) -> non_neg_integer() when + G :: digraph(). no_edges(G) -> ets:info(G#digraph.etab, size). --spec edges(digraph()) -> [edge()]. +-spec edges(G) -> Edges when + G :: digraph(), + Edges :: [edge()]. edges(G) -> ets:select(G#digraph.etab, [{{'$1', '_', '_', '_'}, [], ['$1']}]). --spec edges(digraph(), vertex()) -> [edge()]. +-spec edges(G, V) -> Edges when + G :: digraph(), + V :: vertex(), + Edges :: [edge()]. edges(G, V) -> ets:select(G#digraph.ntab, [{{{out, V},'$1'}, [], ['$1']}, {{{in, V}, '$1'}, [], ['$1']}]). --spec edge(digraph(), edge()) -> {edge(),vertex(),vertex(),label()} | 'false'. +-spec edge(G, E) -> {E, V1, V2, Label} | 'false' when + G :: digraph(), + E :: edge(), + V1 :: vertex(), + V2 :: vertex(), + Label :: label(). edge(G, E) -> case ets:lookup(G#digraph.etab,E) of @@ -275,7 +339,7 @@ edge(G, E) -> %% %% Generate a "unique" edge identifier (relative to this graph) %% --spec new_edge_id(digraph()) -> nonempty_improper_list('$e', non_neg_integer()). +-spec new_edge_id(digraph()) -> edge(). new_edge_id(G) -> NT = G#digraph.ntab, @@ -287,7 +351,7 @@ new_edge_id(G) -> %% %% Generate a "unique" vertex identifier (relative to this graph) %% --spec new_vertex_id(digraph()) -> nonempty_improper_list('$v', non_neg_integer()). +-spec new_vertex_id(digraph()) -> vertex(). new_vertex_id(G) -> NT = G#digraph.ntab, @@ -442,7 +506,10 @@ acyclic_add_edge(E, V1, V2, Label, G) -> %% Delete all paths from vertex V1 to vertex V2 %% --spec del_path(digraph(), vertex(), vertex()) -> 'true'. +-spec del_path(G, V1, V2) -> 'true' when + G :: digraph(), + V1 :: vertex(), + V2 :: vertex(). del_path(G, V1, V2) -> case get_path(G, V1, V2) of @@ -461,7 +528,10 @@ del_path(G, V1, V2) -> %% been searched. %% --spec get_cycle(digraph(), vertex()) -> [vertex(),...] | 'false'. +-spec get_cycle(G, V) -> Vertices | 'false' when + G :: digraph(), + V :: vertex(), + Vertices :: [vertex(),...]. get_cycle(G, V) -> case one_path(out_neighbours(G, V), V, [], [V], [V], 2, G, 1) of @@ -479,7 +549,11 @@ get_cycle(G, V) -> %% if no path exists false is returned %% --spec get_path(digraph(), vertex(), vertex()) -> [vertex(),...] | 'false'. +-spec get_path(G, V1, V2) -> Vertices | 'false' when + G :: digraph(), + V1 :: vertex(), + V2 :: vertex(), + Vertices :: [vertex(),...]. get_path(G, V1, V2) -> one_path(out_neighbours(G, V1), V2, [], [V1], [V1], 1, G, 1). @@ -514,7 +588,10 @@ one_path([], _, [], _, _, _, _, _Counter) -> false. %% Like get_cycle/2, but a cycle of length one is preferred. %% --spec get_short_cycle(digraph(), vertex()) -> [vertex(),...] | 'false'. +-spec get_short_cycle(G, V) -> Vertices | 'false' when + G :: digraph(), + V :: vertex(), + Vertices :: [vertex(),...]. get_short_cycle(G, V) -> get_short_path(G, V, V). @@ -524,7 +601,11 @@ get_short_cycle(G, V) -> %% to find a short path. %% --spec get_short_path(digraph(), vertex(), vertex()) -> [vertex(),...] | 'false'. +-spec get_short_path(G, V1, V2) -> Vertices | 'false' when + G :: digraph(), + V1 :: vertex(), + V2 :: vertex(), + Vertices :: [vertex(),...]. get_short_path(G, V1, V2) -> T = new(), diff --git a/lib/stdlib/src/digraph_utils.erl b/lib/stdlib/src/digraph_utils.erl index 080cae4742..e221be15a1 100644 --- a/lib/stdlib/src/digraph_utils.erl +++ b/lib/stdlib/src/digraph_utils.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1999-2009. All Rights Reserved. +%% Copyright Ericsson AB 1999-2011. 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 @@ -38,48 +38,66 @@ %% A convenient type alias %% --type vertices() :: [digraph:vertex()]. - %% %% Exported functions %% --spec components(digraph()) -> vertices(). +-spec components(Digraph) -> [Component] when + Digraph :: digraph(), + Component :: [digraph:vertex()]. components(G) -> forest(G, fun inout/3). --spec strong_components(digraph()) -> vertices(). +-spec strong_components(Digraph) -> [StrongComponent] when + Digraph :: digraph(), + StrongComponent :: [digraph:vertex()]. strong_components(G) -> forest(G, fun in/3, revpostorder(G)). --spec cyclic_strong_components(digraph()) -> vertices(). +-spec cyclic_strong_components(Digraph) -> [StrongComponent] when + Digraph :: digraph(), + StrongComponent :: [digraph:vertex()]. cyclic_strong_components(G) -> remove_singletons(strong_components(G), G, []). --spec reachable(vertices(), digraph()) -> vertices(). +-spec reachable(Vertices, Digraph) -> Reachable when + Digraph :: digraph(), + Vertices :: [digraph:vertex()], + Reachable :: [digraph:vertex()]. reachable(Vs, G) when is_list(Vs) -> lists:append(forest(G, fun out/3, Vs, first)). --spec reachable_neighbours(vertices(), digraph()) -> vertices(). +-spec reachable_neighbours(Vertices, Digraph) -> Reachable when + Digraph :: digraph(), + Vertices :: [digraph:vertex()], + Reachable :: [digraph:vertex()]. reachable_neighbours(Vs, G) when is_list(Vs) -> lists:append(forest(G, fun out/3, Vs, not_first)). --spec reaching(vertices(), digraph()) -> vertices(). +-spec reaching(Vertices, Digraph) -> Reaching when + Digraph :: digraph(), + Vertices :: [digraph:vertex()], + Reaching :: [digraph:vertex()]. reaching(Vs, G) when is_list(Vs) -> lists:append(forest(G, fun in/3, Vs, first)). --spec reaching_neighbours(vertices(), digraph()) -> vertices(). +-spec reaching_neighbours(Vertices, Digraph) -> Reaching when + Digraph :: digraph(), + Vertices :: [digraph:vertex()], + Reaching :: [digraph:vertex()]. reaching_neighbours(Vs, G) when is_list(Vs) -> lists:append(forest(G, fun in/3, Vs, not_first)). --spec topsort(digraph()) -> vertices() | 'false'. +-spec topsort(Digraph) -> Vertices | 'false' when + Digraph :: digraph(), + Vertices :: [digraph:vertex()]. topsort(G) -> L = revpostorder(G), @@ -88,12 +106,15 @@ topsort(G) -> false -> false end. --spec is_acyclic(digraph()) -> boolean(). +-spec is_acyclic(Digraph) -> boolean() when + Digraph :: digraph(). is_acyclic(G) -> loop_vertices(G) =:= [] andalso topsort(G) =/= false. --spec arborescence_root(digraph()) -> 'no' | {'yes', digraph:vertex()}. +-spec arborescence_root(Digraph) -> 'no' | {'yes', Root} when + Digraph :: digraph(), + Root :: digraph:vertex(). arborescence_root(G) -> case digraph:no_edges(G) =:= digraph:no_vertices(G) - 1 of @@ -114,23 +135,30 @@ arborescence_root(G) -> no end. --spec is_arborescence(digraph()) -> boolean(). +-spec is_arborescence(Digraph) -> boolean() when + Digraph :: digraph(). is_arborescence(G) -> arborescence_root(G) =/= no. --spec is_tree(digraph()) -> boolean(). +-spec is_tree(Digraph) -> boolean() when + Digraph :: digraph(). is_tree(G) -> (digraph:no_edges(G) =:= digraph:no_vertices(G) - 1) andalso (length(components(G)) =:= 1). --spec loop_vertices(digraph()) -> vertices(). +-spec loop_vertices(Digraph) -> Vertices when + Digraph :: digraph(), + Vertices :: [digraph:vertex()]. loop_vertices(G) -> [V || V <- digraph:vertices(G), is_reflexive_vertex(V, G)]. --spec subgraph(digraph(), vertices()) -> digraph(). +-spec subgraph(Digraph, Vertices) -> SubGraph when + Digraph :: digraph(), + Vertices :: [digraph:vertex()], + SubGraph :: digraph(). subgraph(G, Vs) -> try @@ -140,10 +168,12 @@ subgraph(G, Vs) -> erlang:error(badarg) end. --type option() :: {'type', 'inherit' | [digraph:d_type()]} - | {'keep_labels', boolean()}. - --spec subgraph(digraph(), vertices(), [option()]) -> digraph(). +-spec subgraph(Digraph, Vertices, Options) -> SubGraph when + Digraph :: digraph(), + SubGraph :: digraph(), + Vertices :: [digraph:vertex()], + Options :: [{'type', SubgraphType} | {'keep_labels', boolean()}], + SubgraphType :: 'inherit' | [digraph:d_type()]. subgraph(G, Vs, Opts) -> try @@ -153,7 +183,9 @@ subgraph(G, Vs, Opts) -> erlang:error(badarg) end. --spec condensation(digraph()) -> digraph(). +-spec condensation(Digraph) -> CondensedDigraph when + Digraph :: digraph(), + CondensedDigraph :: digraph(). condensation(G) -> SCs = strong_components(G), @@ -176,12 +208,16 @@ condensation(G) -> ets:delete(I2C), SCG. --spec preorder(digraph()) -> vertices(). +-spec preorder(Digraph) -> Vertices when + Digraph :: digraph(), + Vertices :: [digraph:vertex()]. preorder(G) -> lists:reverse(revpreorder(G)). --spec postorder(digraph()) -> vertices(). +-spec postorder(Digraph) -> Vertices when + Digraph :: digraph(), + Vertices :: [digraph:vertex()]. postorder(G) -> lists:reverse(revpostorder(G)). diff --git a/lib/stdlib/src/edlin.erl b/lib/stdlib/src/edlin.erl index 6cb441dbed..026bd9038f 100644 --- a/lib/stdlib/src/edlin.erl +++ b/lib/stdlib/src/edlin.erl @@ -24,6 +24,7 @@ -export([init/0,start/1,edit_line/2,prefix_arg/1]). -export([erase_line/1,erase_inp/1,redraw_line/1]). -export([length_before/1,length_after/1,prompt/1]). +-export([current_line/1]). %%-export([expand/1]). -export([edit_line1/2]). @@ -421,6 +422,7 @@ over_paren_auto([], _, _, _) -> %% length_before(Line) %% length_after(Line) %% prompt(Line) +%% current_line(Line) %% Various functions for accessing bits of a line. erase_line({line,Pbs,{Bef,Aft},_}) -> @@ -447,6 +449,9 @@ length_after({line,_,{_Bef,Aft},_}) -> prompt({line,Pbs,_,_}) -> Pbs. +current_line({line,_,{Bef, Aft},_}) -> + reverse(Bef, Aft ++ "\n"). + %% %% expand(CurrentBefore) -> %% %% {yes,Expansion} | no %% %% Try to expand the word before as either a module name or a function diff --git a/lib/stdlib/src/epp.erl b/lib/stdlib/src/epp.erl index 424aed3d2e..d804c1dee5 100644 --- a/lib/stdlib/src/epp.erl +++ b/lib/stdlib/src/epp.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2010. All Rights Reserved. +%% Copyright Ericsson AB 1996-2011. 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,11 +29,14 @@ %%------------------------------------------------------------------------ -type macros() :: [{atom(), term()}]. +-type epp_handle() :: pid(). %% Epp state record. -record(epp, {file, %Current file location, %Current location + delta, %Offset from Location (-file) name="", %Current file name + name2="", %-"-, modified by -file istk=[], %Ifdef stack sstk=[], %State stack path=[], %Include-path @@ -59,14 +62,23 @@ %% parse_file(FileName, IncludePath, PreDefMacros) %% macro_defs(Epp) --spec open(file:name(), [file:name()]) -> - {'ok', pid()} | {'error', term()}. +-spec open(FileName, IncludePath) -> + {'ok', Epp} | {'error', ErrorDescriptor} when + FileName :: file:name(), + IncludePath :: [DirectoryName :: file:name()], + Epp :: epp_handle(), + ErrorDescriptor :: term(). open(Name, Path) -> open(Name, Path, []). --spec open(file:name(), [file:name()], macros()) -> - {'ok', pid()} | {'error', term()}. +-spec open(FileName, IncludePath, PredefMacros) -> + {'ok', Epp} | {'error', ErrorDescriptor} when + FileName :: file:name(), + IncludePath :: [DirectoryName :: file:name()], + PredefMacros :: macros(), + Epp :: epp_handle(), + ErrorDescriptor :: term(). open(Name, Path, Pdm) -> Self = self(), @@ -78,7 +90,8 @@ open(Name, File, StartLocation, Path, Pdm) -> Epp = spawn(fun() -> server(Self, Name, File, StartLocation,Path,Pdm) end), epp_request(Epp). --spec close(pid()) -> 'ok'. +-spec close(Epp) -> 'ok' when + Epp :: epp_handle(). close(Epp) -> %% Make sure that close is synchronous as a courtesy to test @@ -91,6 +104,13 @@ close(Epp) -> scan_erl_form(Epp) -> epp_request(Epp, scan_erl_form). +-spec parse_erl_form(Epp) -> + {'ok', AbsForm} | {'eof', Line} | {error, ErrorInfo} when + Epp :: epp_handle(), + AbsForm :: erl_parse:abstract_form(), + Line :: erl_scan:line(), + ErrorInfo :: erl_scan:error_info() | erl_parse:error_info(). + parse_erl_form(Epp) -> case epp_request(Epp, scan_erl_form) of {ok,Toks} -> @@ -105,10 +125,17 @@ macro_defs(Epp) -> %% format_error(ErrorDescriptor) -> String %% Return a string describing the error. +-spec format_error(ErrorDescriptor) -> io_lib:chars() when + ErrorDescriptor :: term(). + format_error(cannot_parse) -> io_lib:format("cannot parse file, giving up", []); format_error({bad,W}) -> io_lib:format("badly formed '~s'", [W]); +format_error(missing_parenthesis) -> + io_lib:format("badly formed define: missing closing right parenthesis",[]); +format_error(premature_end) -> + "premature end"; format_error({call,What}) -> io_lib:format("illegal macro call '~s'",[What]); format_error({undefined,M,none}) -> @@ -140,6 +167,16 @@ format_error(E) -> file:format_error(E). %% parse_file(FileName, IncludePath, [PreDefMacro]) -> %% {ok,[Form]} | {error,OpenError} +-spec parse_file(FileName, IncludePath, PredefMacros) -> + {'ok', [Form]} | {error, OpenError} when + FileName :: file:name(), + IncludePath :: [DirectoryName :: file:name()], + Form :: erl_parse:abstract_form() | {'error', ErrorInfo} | {'eof',Line}, + PredefMacros :: macros(), + Line :: erl_scan:line(), + ErrorInfo :: erl_scan:error_info() | erl_parse:error_info(), + OpenError :: file:posix() | badarg | system_limit. + parse_file(Ifile, Path, Predefs) -> case open(Ifile, Path, Predefs) of {ok,Epp} -> @@ -161,7 +198,7 @@ parse_file(Epp) -> case normalize_typed_record_fields(Fields) of {typed, NewFields} -> [{attribute, La, record, {Record, NewFields}}, - {attribute, La, type, + {attribute, La, type, {{record, Record}, Fields, []}} |parse_file(Epp)]; not_typed -> @@ -176,6 +213,8 @@ parse_file(Epp) -> [{eof,Location}] end. +normalize_typed_record_fields([]) -> + {typed, []}; normalize_typed_record_fields(Fields) -> normalize_typed_record_fields(Fields, [], false). @@ -184,7 +223,7 @@ normalize_typed_record_fields([], NewFields, Typed) -> true -> {typed, lists:reverse(NewFields)}; false -> not_typed end; -normalize_typed_record_fields([{typed_record_field,Field,_}|Rest], +normalize_typed_record_fields([{typed_record_field,Field,_}|Rest], NewFields, _Typed) -> normalize_typed_record_fields(Rest, [Field|NewFields], true); normalize_typed_record_fields([Field|Rest], NewFields, Typed) -> @@ -228,8 +267,8 @@ init_server(Pid, Name, File, AtLocation, Path, Pdm, Pre) -> case user_predef(Pdm, Ms0) of {ok,Ms1} -> epp_reply(Pid, {ok,self()}), - St = #epp{file=File, location=AtLocation, name=Name, - path=Path, macs=Ms1, pre_opened = Pre}, + St = #epp{file=File, location=AtLocation, delta=0, name=Name, + name2=Name, path=Path, macs=Ms1, pre_opened = Pre}, From = wait_request(St), enter_file_reply(From, Name, AtLocation, AtLocation), wait_req_scan(St); @@ -320,7 +359,7 @@ wait_req_scan(St) -> wait_req_skip(St, Sis) -> From = wait_request(St), skip_toks(From, St, Sis). - + %% enter_file(Path, FileName, IncludeToken, From, EppState) %% leave_file(From, EppState) %% Handle entering and leaving included files. Notify caller when the @@ -352,8 +391,8 @@ enter_file2(NewF, Pname, From, St, AtLocation, ExtraPath) -> enter_file_reply(From, Pname, Loc, AtLocation), Ms = dict:store({atom,'FILE'}, {none,[{string,Loc,Pname}]}, St#epp.macs), Path = St#epp.path ++ ExtraPath, - #epp{location=Loc,file=NewF, - name=Pname,sstk=[St|St#epp.sstk],path=Path,macs=Ms}. + #epp{file=NewF,location=Loc,name=Pname,delta=0, + sstk=[St|St#epp.sstk],path=Path,macs=Ms}. enter_file_reply(From, Name, Location, AtLocation) -> Attr = loc_attr(AtLocation), @@ -376,23 +415,32 @@ file_name(N) when is_atom(N) -> leave_file(From, St) -> case St#epp.istk of - [I|Cis] -> + [I|Cis] -> epp_reply(From, - {error,{St#epp.location,epp, + {error,{St#epp.location,epp, {illegal,"unterminated",I}}}), leave_file(wait_request(St),St#epp{istk=Cis}); [] -> case St#epp.sstk of [OldSt|Sts] -> close_file(St), - enter_file_reply(From, OldSt#epp.name, - OldSt#epp.location, OldSt#epp.location), + #epp{location=OldLoc, delta=Delta, name=OldName, + name2=OldName2} = OldSt, + CurrLoc = add_line(OldLoc, Delta), Ms = dict:store({atom,'FILE'}, - {none, - [{string,OldSt#epp.location, - OldSt#epp.name}]}, + {none,[{string,CurrLoc,OldName2}]}, St#epp.macs), - wait_req_scan(OldSt#epp{sstk=Sts,macs=Ms}); + NextSt = OldSt#epp{sstk=Sts,macs=Ms}, + enter_file_reply(From, OldName, CurrLoc, CurrLoc), + case OldName2 =:= OldName of + true -> + From; + false -> + NFrom = wait_request(NextSt), + enter_file_reply(NFrom, OldName2, OldLoc, + neg_line(CurrLoc)) + end, + wait_req_scan(NextSt); [] -> epp_reply(From, {eof,St#epp.location}), wait_req_scan(St) @@ -413,7 +461,7 @@ scan_toks(From, St) -> leave_file(From, St#epp{location=Cl}); {error,_E} -> epp_reply(From, {error,{St#epp.location,epp,cannot_parse}}), - leave_file(From, St) %This serious, just exit! + leave_file(wait_request(St), St) %This serious, just exit! end. scan_toks([{'-',_Lh},{atom,_Ld,define}=Define|Toks], From, St) -> @@ -487,28 +535,34 @@ scan_extends(_Ts, _As, Ms) -> Ms. %% scan_define(Tokens, DefineToken, From, EppState) -scan_define([{'(',_Lp},{Type,_Lm,M}=Mac,{',',_Lc}|Toks], _Def, From, St) +scan_define([{'(',_Lp},{Type,_Lm,M}=Mac,{',',Lc}|Toks], _Def, From, St) when Type =:= atom; Type =:= var -> - case dict:find({atom,M}, St#epp.macs) of - {ok, Defs} when is_list(Defs) -> - %% User defined macros: can be overloaded - case proplists:is_defined(none, Defs) of - true -> - epp_reply(From, {error,{loc(Mac),epp,{redefine,M}}}), + case catch macro_expansion(Toks, Lc) of + Expansion when is_list(Expansion) -> + case dict:find({atom,M}, St#epp.macs) of + {ok, Defs} when is_list(Defs) -> + %% User defined macros: can be overloaded + case proplists:is_defined(none, Defs) of + true -> + epp_reply(From, {error,{loc(Mac),epp,{redefine,M}}}), + wait_req_scan(St); + false -> + scan_define_cont(From, St, + {atom, M}, + {none, {none,Expansion}}) + end; + {ok, _PreDef} -> + %% Predefined macros: cannot be overloaded + epp_reply(From, {error,{loc(Mac),epp,{redefine_predef,M}}}), wait_req_scan(St); - false -> + error -> scan_define_cont(From, St, {atom, M}, - {none, {none,macro_expansion(Toks)}}) + {none, {none,Expansion}}) end; - {ok, _PreDef} -> - %% Predefined macros: cannot be overloaded - epp_reply(From, {error,{loc(Mac),epp,{redefine_predef,M}}}), - wait_req_scan(St); - error -> - scan_define_cont(From, St, - {atom, M}, - {none, {none,macro_expansion(Toks)}}) + {error,ErrL,What} -> + epp_reply(From, {error,{ErrL,epp,What}}), + wait_req_scan(St) end; scan_define([{'(',_Lp},{Type,_Lm,M}=Mac,{'(',_Lc}|Toks], Def, From, St) when Type =:= atom; Type =:= var -> @@ -534,6 +588,9 @@ scan_define([{'(',_Lp},{Type,_Lm,M}=Mac,{'(',_Lc}|Toks], Def, From, St) error -> scan_define_cont(From, St, {atom, M}, {Len, {As, Me}}) end; + {error,ErrL,What} -> + epp_reply(From, {error,{ErrL,epp,What}}), + wait_req_scan(St); _ -> epp_reply(From, {error,{loc(Def),epp,{bad,define}}}), wait_req_scan(St) @@ -595,7 +652,7 @@ scan_undef(_Toks, Undef, From, St) -> %% scan_include(Tokens, IncludeToken, From, St) -scan_include([{'(',_Llp},{string,_Lf,NewName0},{')',_Lrp},{dot,_Ld}], Inc, +scan_include([{'(',_Llp},{string,_Lf,NewName0},{')',_Lrp},{dot,_Ld}], Inc, From, St) -> NewName = expand_var(NewName0), enter_file(St#epp.path, NewName, Inc, From, St); @@ -631,7 +688,7 @@ scan_include_lib([{'(',_Llp},{string,_Lf,NewName0},{')',_Lrp},{dot,_Ld}], case file:open(LibName, [read]) of {ok,NewF} -> ExtraPath = [filename:dirname(LibName)], - wait_req_scan(enter_file2(NewF, LibName, From, + wait_req_scan(enter_file2(NewF, LibName, From, St, Loc, ExtraPath)); {error,_E2} -> epp_reply(From, @@ -753,14 +810,15 @@ scan_file([{'(',_Llp},{string,_Ls,Name},{',',_Lc},{integer,_Li,Ln},{')',_Lrp}, Ms = dict:store({atom,'FILE'}, {none,[{string,1,Name}]}, St#epp.macs), Locf = loc(Tf), NewLoc = new_location(Ln, St#epp.location, Locf), - scan_toks(From, St#epp{name=Name,location=NewLoc,macs=Ms}); + Delta = abs(get_line(element(2, Tf)))-Ln + St#epp.delta, + wait_req_scan(St#epp{name2=Name,location=NewLoc,delta=Delta,macs=Ms}); scan_file(_Toks, Tf, From, St) -> epp_reply(From, {error,{loc(Tf),epp,{bad,file}}}), wait_req_scan(St). new_location(Ln, Le, Lf) when is_integer(Lf) -> Ln+(Le-Lf); -new_location(Ln, {Le,_}, {Lf,_}) -> +new_location(Ln, {Le,_}, {Lf,_}) -> {Ln+(Le-Lf),1}. %% skip_toks(From, EppState, SkipIstack) @@ -787,7 +845,7 @@ skip_toks(From, St, [I|Sis]) -> leave_file(From, St#epp{location=Cl,istk=[I|Sis]}); {error,_E} -> epp_reply(From, {error,{St#epp.location,epp,cannot_parse}}), - leave_file(From, St) %This serious, just exit! + leave_file(wait_request(St), St) %This serious, just exit! end; skip_toks(From, St, []) -> scan_toks(From, St). @@ -801,22 +859,23 @@ skip_else(_Else, From, St, Sis) -> skip_toks(From, St, Sis). %% macro_pars(Tokens, ArgStack) -%% macro_expansion(Tokens) +%% macro_expansion(Tokens, Line) %% Extract the macro parameters and the expansion from a macro definition. -macro_pars([{')',_Lp}, {',',_Ld}|Ex], Args) -> - {ok, {lists:reverse(Args), macro_expansion(Ex)}}; -macro_pars([{var,_,Name}, {')',_Lp}, {',',_Ld}|Ex], Args) -> +macro_pars([{')',_Lp}, {',',Ld}|Ex], Args) -> + {ok, {lists:reverse(Args), macro_expansion(Ex, Ld)}}; +macro_pars([{var,_,Name}, {')',_Lp}, {',',Ld}|Ex], Args) -> false = lists:member(Name, Args), %Prolog is nice - {ok, {lists:reverse([Name|Args]), macro_expansion(Ex)}}; + {ok, {lists:reverse([Name|Args]), macro_expansion(Ex, Ld)}}; macro_pars([{var,_L,Name}, {',',_}|Ts], Args) -> - false = lists:member(Name, Args), + false = lists:member(Name, Args), macro_pars(Ts, [Name|Args]). -macro_expansion([{')',_Lp},{dot,_Ld}]) -> []; -macro_expansion([{dot,_Ld}]) -> []; %Be nice, allow no right paren! -macro_expansion([T|Ts]) -> - [T|macro_expansion(Ts)]. +macro_expansion([{')',_Lp},{dot,_Ld}], _L0) -> []; +macro_expansion([{dot,Ld}], _L0) -> throw({error,Ld,missing_parenthesis}); +macro_expansion([T|Ts], _L0) -> + [T|macro_expansion(Ts, element(2, T))]; +macro_expansion([], L0) -> throw({error,L0,premature_end}). %% expand_macros(Tokens, Macros) %% expand_macro(Tokens, MacroToken, RestTokens) @@ -1071,11 +1130,11 @@ epp_reply(From, Rep) -> wait_epp_reply(Epp, Mref) -> receive - {epp_reply,Epp,Rep} -> + {epp_reply,Epp,Rep} -> erlang:demonitor(Mref), receive {'DOWN',Mref,_,_,_} -> ok after 0 -> ok end, Rep; - {'DOWN',Mref,_,_,E} -> + {'DOWN',Mref,_,_,E} -> receive {epp_reply,Epp,Rep} -> Rep after 0 -> exit(E) end @@ -1116,6 +1175,9 @@ neg_line(L) -> abs_line(L) -> erl_scan:set_attribute(line, L, fun(Line) -> abs(Line) end). +add_line(L, Offset) -> + erl_scan:set_attribute(line, L, fun(Line) -> Line+Offset end). + start_loc(Line) when is_integer(Line) -> 1; start_loc({_Line, _Column}) -> @@ -1132,7 +1194,7 @@ get_line({Line,_Column}) -> %% mainly aimed at yecc, the parser generator, which uses the -file %% attribute to get correct lines in messages referring to code %% supplied by the user (actions etc in .yrl files). -%% +%% %% In a perfect world (read: perfectly implemented applications such %% as Xref, Cover, Debugger, etc.) it would not be necessary to %% distinguish -file attributes from epp and the input file. The @@ -1152,7 +1214,7 @@ get_line({Line,_Column}) -> %% have been output by epp (corresponding to -include and %% -include_lib) are kept, but the user's -file attributes are %% removed. This seems sufficient for now. -%% +%% %% It turns out to be difficult to distinguish -file attributes in the %% input file from the ones added by epp unless some action is taken. %% The (less than perfect) solution employed is to let epp assign @@ -1164,7 +1226,7 @@ get_line({Line,_Column}) -> interpret_file_attribute(Forms) -> interpret_file_attr(Forms, 0, []). -interpret_file_attr([{attribute,Loc,file,{File,Line}}=Form | Forms], +interpret_file_attr([{attribute,Loc,file,{File,Line}}=Form | Forms], Delta, Fs) -> {line, L} = erl_scan:attributes_info(Loc, line), if @@ -1175,10 +1237,10 @@ interpret_file_attr([{attribute,Loc,file,{File,Line}}=Form | Forms], %% -include or -include_lib % true = L =:= Line, case Fs of - [_, Delta1, File | Fs1] -> % end of included file - [Form | interpret_file_attr(Forms, Delta1, [File | Fs1])]; + [_, File | Fs1] -> % end of included file + [Form | interpret_file_attr(Forms, 0, [File | Fs1])]; _ -> % start of included file - [Form | interpret_file_attr(Forms, 0, [File, Delta | Fs])] + [Form | interpret_file_attr(Forms, 0, [File | Fs])] end end; interpret_file_attr([Form0 | Forms], Delta, Fs) -> diff --git a/lib/stdlib/src/erl_compile.erl b/lib/stdlib/src/erl_compile.erl index d9d15e05f8..ff032b129c 100644 --- a/lib/stdlib/src/erl_compile.erl +++ b/lib/stdlib/src/erl_compile.erl @@ -1,19 +1,19 @@ %% %% %CopyrightBegin% -%% -%% Copyright Ericsson AB 1997-2009. All Rights Reserved. -%% +%% +%% Copyright Ericsson AB 1997-2011. 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 %% compliance with the License. You should have received a copy of the %% Erlang Public License along with this software. If not, it can be %% retrieved online at http://www.erlang.org/. -%% +%% %% Software distributed under the License is distributed on an "AS IS" %% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See %% the License for the specific language governing rights and limitations %% under the License. -%% +%% %% %CopyrightEnd% %% -module(erl_compile). @@ -23,6 +23,8 @@ -export([compile_cmdline/1]). +-export_type([cmd_line_arg/0]). + %% Mapping from extension to {M,F} to run the correct compiler. compiler(".erl") -> {compile, compile}; @@ -39,7 +41,6 @@ compiler(".idl") -> {ic, compile}; compiler(".asn1") -> {asn1ct, compile_asn1}; compiler(".asn") -> {asn1ct, compile_asn}; compiler(".py") -> {asn1ct, compile_py}; -compiler(".xml") -> {xmerl_scan, process}; compiler(_) -> no. %% Entry from command line. diff --git a/lib/stdlib/src/erl_eval.erl b/lib/stdlib/src/erl_eval.erl index ea1b179ee5..515ea2ebb7 100644 --- a/lib/stdlib/src/erl_eval.erl +++ b/lib/stdlib/src/erl_eval.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. +%% Copyright Ericsson AB 1996-2011. 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 @@ -34,6 +34,37 @@ -import(lists, [reverse/1,foldl/3,member/2]). +-export_type([binding_struct/0]). + +-type(expression() :: erl_parse:abstract_expr()). +-type(expressions() :: [erl_parse:abstract_expr()]). +-type(expression_list() :: [expression()]). +-type(clauses() :: [erl_parse:abstract_clause()]). +-type(name() :: term()). +-type(value() :: term()). +-type(bindings() :: [{name(), value()}]). +-type(binding_struct() :: orddict:orddict()). + +-type(lfun_value_handler() :: fun((Name :: atom(), + Arguments :: [term()]) -> + Value :: value())). +-type(lfun_eval_handler() :: fun((Name :: atom(), + Arguments :: expression_list(), + Bindings :: binding_struct()) -> + {value, + Value :: value(), + NewBindings :: binding_struct()})). +-type(local_function_handler() :: {value, lfun_value_handler()} + | {eval, lfun_eval_handler()} + | none). + +-type(func_spec() :: {Module :: module(), Function :: atom()} | function()). +-type(nlfun_handler() :: fun((FuncSpec :: func_spec(), + Arguments :: [term()]) -> + term())). +-type(non_local_function_handler() :: {value, nlfun_handler()} + | none). + %% exprs(ExpressionSeq, Bindings) %% exprs(ExpressionSeq, Bindings, LocalFuncHandler) %% exprs(ExpressionSeq, Bindings, LocalFuncHandler, ExternalFuncHandler) @@ -45,6 +76,11 @@ %% that there are valid constructs in Expression to be taken care of %% by a function handler but considerad errors by erl_lint. +-spec(exprs(Expressions, Bindings) -> {value, Value, NewBindings} when + Expressions :: expressions(), + Bindings :: binding_struct(), + Value :: value(), + NewBindings :: binding_struct()). exprs(Exprs, Bs) -> case check_command(Exprs, Bs) of ok -> @@ -53,9 +89,25 @@ exprs(Exprs, Bs) -> erlang:raise(error, Error, [{?MODULE,exprs,2}]) end. +-spec(exprs(Expressions, Bindings, LocalFunctionHandler) -> + {value, Value, NewBindings} when + Expressions :: expressions(), + Bindings :: binding_struct(), + LocalFunctionHandler :: local_function_handler(), + Value :: value(), + NewBindings :: binding_struct()). exprs(Exprs, Bs, Lf) -> exprs(Exprs, Bs, Lf, none, none). +-spec(exprs(Expressions, Bindings, LocalFunctionHandler, + NonLocalFunctionHandler) -> + {value, Value, NewBindings} when + Expressions :: expressions(), + Bindings :: binding_struct(), + LocalFunctionHandler :: local_function_handler(), + NonLocalFunctionHandler :: non_local_function_handler(), + Value :: value(), + NewBindings :: binding_struct()). exprs(Exprs, Bs, Lf, Ef) -> exprs(Exprs, Bs, Lf, Ef, none). @@ -75,6 +127,11 @@ exprs([E|Es], Bs0, Lf, Ef, RBs) -> %% %% Only expr/2 checks the command by calling erl_lint. See exprs/2. +-spec(expr(Expression, Bindings) -> {value, Value, NewBindings} when + Expression :: expression(), + Bindings :: binding_struct(), + Value :: value(), + NewBindings :: binding_struct()). expr(E, Bs) -> case check_command([E], Bs) of ok -> @@ -83,9 +140,25 @@ expr(E, Bs) -> erlang:raise(error, Error, [{?MODULE,expr,2}]) end. +-spec(expr(Expression, Bindings, LocalFunctionHandler) -> + {value, Value, NewBindings} when + Expression :: expression(), + Bindings :: binding_struct(), + LocalFunctionHandler :: local_function_handler(), + Value :: value(), + NewBindings :: binding_struct()). expr(E, Bs, Lf) -> expr(E, Bs, Lf, none, none). +-spec(expr(Expression, Bindings, LocalFunctionHandler, + NonLocalFunctionHandler) -> + {value, Value, NewBindings} when + Expression :: expression(), + Bindings :: binding_struct(), + LocalFunctionHandler :: local_function_handler(), + NonLocalFunctionHandler :: non_local_function_handler(), + Value :: value(), + NewBindings :: binding_struct()). expr(E, Bs, Lf, Ef) -> expr(E, Bs, Lf, Ef, none). @@ -114,6 +187,16 @@ fun_data(F) when is_function(F) -> fun_data(_T) -> false. +-spec(expr(Expression, Bindings, LocalFunctionHandler, + NonLocalFunctionHandler, ReturnFormat) -> + {value, Value, NewBindings} | Value when + Expression :: expression(), + Bindings :: binding_struct(), + LocalFunctionHandler :: local_function_handler(), + NonLocalFunctionHandler :: non_local_function_handler(), + ReturnFormat :: none | value, + Value :: value(), + NewBindings :: binding_struct()). expr({var,_,V}, Bs, _Lf, _Ef, RBs) -> case binding(V, Bs) of {value,Val} -> @@ -384,12 +467,9 @@ local_func(Func, As0, Bs0, {value,F}, value) -> local_func(Func, As0, Bs0, {value,F}, RBs) -> {As1,Bs1} = expr_list(As0, Bs0, {value,F}), ret_expr(F(Func, As1), Bs1, RBs); -local_func(Func, As0, Bs0, {value,F,Eas}, value) -> - {As1,_Bs1} = expr_list(As0, Bs0, {value,F,Eas}), - apply(F, [Func,As1|Eas]); local_func(Func, As0, Bs0, {value,F,Eas}, RBs) -> - {As1,Bs1} = expr_list(As0, Bs0, {value,F,Eas}), - ret_expr(apply(F, [Func,As1|Eas]), Bs1, RBs); + Fun = fun(Name, Args) -> apply(F, [Name,Args|Eas]) end, + local_func(Func, As0, Bs0, {value, Fun}, RBs); local_func(Func, As, Bs, {eval,F}, RBs) -> local_func2(F(Func, As, Bs), RBs); local_func(Func, As, Bs, {eval,F,Eas}, RBs) -> @@ -613,12 +693,33 @@ eval_fun([], As, _Bs, _Lf, _Ef, _RBs) -> %% expr_list(ExpressionList, Bindings, LocalFuncHandler, ExternalFuncHandler) %% Evaluate a list of expressions "in parallel" at the same level. +-spec(expr_list(ExpressionList, Bindings) -> {ValueList, NewBindings} when + ExpressionList :: expression_list(), + Bindings :: binding_struct(), + ValueList :: [value()], + NewBindings :: binding_struct()). expr_list(Es, Bs) -> expr_list(Es, Bs, none, none). +-spec(expr_list(ExpressionList, Bindings, LocalFunctionHandler) -> + {ValueList, NewBindings} when + ExpressionList :: expression_list(), + Bindings :: binding_struct(), + LocalFunctionHandler :: local_function_handler(), + ValueList :: [value()], + NewBindings :: binding_struct()). expr_list(Es, Bs, Lf) -> expr_list(Es, Bs, Lf, none). +-spec(expr_list(ExpressionList, Bindings, LocalFunctionHandler, + NonLocalFunctionHandler) -> + {ValueList, NewBindings} when + ExpressionList :: expression_list(), + Bindings :: binding_struct(), + LocalFunctionHandler :: local_function_handler(), + NonLocalFunctionHandler :: non_local_function_handler(), + ValueList :: [value()], + NewBindings :: binding_struct()). expr_list(Es, Bs, Lf, Ef) -> expr_list(Es, [], Bs, Bs, Lf, Ef). @@ -757,6 +858,15 @@ send_all([], _) -> true. %% match_clause -> {Body, Bindings} or nomatch +-spec(match_clause(Clauses, ValueList, Bindings, LocalFunctionHandler) -> + {Body, NewBindings} | nomatch when + Clauses :: clauses(), + ValueList :: [value()], + Bindings :: binding_struct(), + LocalFunctionHandler :: local_function_handler(), + Body :: expression_list(), + NewBindings :: binding_struct()). + match_clause(Cs, Vs, Bs, Lf) -> match_clause(Cs, Vs, Bs, Lf, none). @@ -973,18 +1083,30 @@ match_list(_, _, _Bs, _BBs) -> %% add_binding(Name, Value, Bindings) %% del_binding(Name, Bindings) +-spec(new_bindings() -> binding_struct()). new_bindings() -> orddict:new(). +-spec(bindings(BindingStruct :: binding_struct()) -> bindings()). bindings(Bs) -> orddict:to_list(Bs). +-spec(binding(Name, BindingStruct) -> {value, value()} | unbound when + Name :: name(), + BindingStruct :: binding_struct()). binding(Name, Bs) -> case orddict:find(Name, Bs) of {ok,Val} -> {value,Val}; error -> unbound end. +-spec(add_binding(Name, Value, BindingStruct) -> binding_struct() when + Name :: name(), + Value :: value(), + BindingStruct :: binding_struct()). add_binding(Name, Val, Bs) -> orddict:store(Name, Val, Bs). +-spec(del_binding(Name, BindingStruct) -> binding_struct() when + Name :: name(), + BindingStruct :: binding_struct()). del_binding(Name, Bs) -> orddict:erase(Name, Bs). add_bindings(Bs1, Bs2) -> diff --git a/lib/stdlib/src/erl_expand_records.erl b/lib/stdlib/src/erl_expand_records.erl index 6fa77f2c3b..20fd247cea 100644 --- a/lib/stdlib/src/erl_expand_records.erl +++ b/lib/stdlib/src/erl_expand_records.erl @@ -1,19 +1,19 @@ %% %% %CopyrightBegin% -%% -%% Copyright Ericsson AB 2005-2009. All Rights Reserved. -%% +%% +%% Copyright Ericsson AB 2005-2011. 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 %% compliance with the License. You should have received a copy of the %% Erlang Public License along with this software. If not, it can be %% retrieved online at http://www.erlang.org/. -%% +%% %% Software distributed under the License is distributed on an "AS IS" %% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See %% the License for the specific language governing rights and limitations %% under the License. -%% +%% %% %CopyrightEnd% %% %% Purpose : Expand records into tuples. @@ -35,9 +35,13 @@ trecords=sets:new(), % Typed records uses_types=false, % Are there -spec or -type in the module strict_ra=[], % strict record accesses - checked_ra=[] % succesfully accessed records + checked_ra=[] % successfully accessed records }). +-spec(module(AbsForms, CompileOptions) -> AbsForms when + AbsForms :: [erl_parse:abstract_form()], + CompileOptions :: [compile:option()]). + %% Is is assumed that Fs is a valid list of forms. It should pass %% erl_lint without errors. module(Fs0, Opts0) -> @@ -95,8 +99,9 @@ forms([F | Fs0], St0) -> forms([], St) -> {[],St}. clauses([{clause,Line,H0,G0,B0} | Cs0], St0) -> - {H,St1} = head(H0, St0), - {G,St2} = guard(G0, St1), + {H1,St1} = head(H0, St0), + {G1,St2} = guard(G0, St1), + {H,G} = optimize_is_record(H1, G1, St2), {B,St3} = exprs(B0, St2), {Cs,St4} = clauses(Cs0, St3), {[{clause,Line,H,G,B} | Cs],St4}; @@ -191,7 +196,6 @@ guard_test1(Test, St) -> normalise_test(atom, 1) -> is_atom; normalise_test(binary, 1) -> is_binary; -normalise_test(constant, 1) -> is_constant; normalise_test(float, 1) -> is_float; normalise_test(function, 1) -> is_function; normalise_test(integer, 1) -> is_integer; @@ -346,9 +350,6 @@ expr({'fun',Line,{clauses,Cs0}}, St0) -> {{'fun',Line,{clauses,Cs}},St1}; expr({call,Line,{atom,_,is_record},[A,{atom,_,Name}]}, St) -> record_test(Line, A, Name, St); -expr({'cond',Line,Cs0}, St0) -> - {Cs,St1} = clauses(Cs0, St0), - {{'cond',Line,Cs},St1}; expr({call,Line,{remote,_,{atom,_,erlang},{atom,_,is_record}}, [A,{atom,_,Name}]}, St) -> record_test(Line, A, Name, St); @@ -804,5 +805,137 @@ imported(F, A, St) -> error -> no end. +%%% +%%% Replace is_record/3 in guards with matching if possible. +%%% + +optimize_is_record(H0, G0, #exprec{compile=Opts}) -> + case opt_rec_vars(G0) of + [] -> + {H0,G0}; + Rs0 -> + case lists:member(no_is_record_optimization, Opts) of + true -> + {H0,G0}; + false -> + {H,Rs} = opt_pattern_list(H0, Rs0), + G = opt_remove(G0, Rs), + {H,G} + end + end. + + +%% opt_rec_vars(Guards) -> Vars. +%% Search through the guard expression, looking for +%% variables referenced in those is_record/3 calls that +%% will fail the entire guard if they evaluate to 'false' +%% +%% In the following code +%% +%% f(X, Y, Z) when is_record(X, r1) andalso +%% (is_record(Y, r2) orelse is_record(Z, r3)) +%% +%% the entire guard will be false if the record test for +%% X fails, and the clause can be rewritten to: +%% +%% f({r1,...}=X, Y, Z) when true andalso +%% (is_record(Y, r2) or is_record(Z, r3)) +%% +opt_rec_vars([G|Gs]) -> + Rs = opt_rec_vars_1(G, orddict:new()), + opt_rec_vars(Gs, Rs); +opt_rec_vars([]) -> orddict:new(). + +opt_rec_vars([G|Gs], Rs0) -> + Rs1 = opt_rec_vars_1(G, orddict:new()), + Rs = ordsets:intersection(Rs0, Rs1), + opt_rec_vars(Gs, Rs); +opt_rec_vars([], Rs) -> Rs. + +opt_rec_vars_1([T|Ts], Rs0) -> + Rs = opt_rec_vars_2(T, Rs0), + opt_rec_vars_1(Ts, Rs); +opt_rec_vars_1([], Rs) -> Rs. + +opt_rec_vars_2({op,_,'and',A1,A2}, Rs) -> + opt_rec_vars_1([A1,A2], Rs); +opt_rec_vars_2({op,_,'andalso',A1,A2}, Rs) -> + opt_rec_vars_1([A1,A2], Rs); +opt_rec_vars_2({op,_,'orelse',Arg,{atom,_,fail}}, Rs) -> + %% Since the second argument guarantees failure, + %% it is safe to inspect the first argument. + opt_rec_vars_2(Arg, Rs); +opt_rec_vars_2({call,_,{remote,_,{atom,_,erlang},{atom,_,is_record}}, + [{var,_,V},{atom,_,Tag},{integer,_,Sz}]}, Rs) -> + orddict:store(V, {Tag,Sz}, Rs); +opt_rec_vars_2({call,_,{atom,_,is_record}, + [{var,_,V},{atom,_,Tag},{integer,_,Sz}]}, Rs) -> + orddict:store(V, {Tag,Sz}, Rs); +opt_rec_vars_2(_, Rs) -> Rs. + +opt_pattern_list(Ps, Rs) -> + opt_pattern_list(Ps, Rs, []). + +opt_pattern_list([P0|Ps], Rs0, Acc) -> + {P,Rs} = opt_pattern(P0, Rs0), + opt_pattern_list(Ps, Rs, [P|Acc]); +opt_pattern_list([], Rs, Acc) -> + {reverse(Acc),Rs}. + +opt_pattern({var,_,V}=Var, Rs0) -> + case orddict:find(V, Rs0) of + {ok,{Tag,Sz}} -> + Rs = orddict:store(V, {remove,Tag,Sz}, Rs0), + {opt_var(Var, Tag, Sz),Rs}; + _ -> + {Var,Rs0} + end; +opt_pattern({cons,Line,H0,T0}, Rs0) -> + {H,Rs1} = opt_pattern(H0, Rs0), + {T,Rs} = opt_pattern(T0, Rs1), + {{cons,Line,H,T},Rs}; +opt_pattern({tuple,Line,Es0}, Rs0) -> + {Es,Rs} = opt_pattern_list(Es0, Rs0), + {{tuple,Line,Es},Rs}; +opt_pattern({match,Line,Pa0,Pb0}, Rs0) -> + {Pa,Rs1} = opt_pattern(Pa0, Rs0), + {Pb,Rs} = opt_pattern(Pb0, Rs1), + {{match,Line,Pa,Pb},Rs}; +opt_pattern(P, Rs) -> {P,Rs}. + +opt_var({var,Line,_}=Var, Tag, Sz) -> + Rp = record_pattern(2, -1, ignore, Sz, Line, [{atom,Line,Tag}]), + {match,Line,{tuple,Line,Rp},Var}. + +opt_remove(Gs, Rs) -> + [opt_remove_1(G, Rs) || G <- Gs]. + +opt_remove_1(Ts, Rs) -> + [opt_remove_2(T, Rs) || T <- Ts]. + +opt_remove_2({op,L,'and'=Op,A1,A2}, Rs) -> + {op,L,Op,opt_remove_2(A1, Rs),opt_remove_2(A2, Rs)}; +opt_remove_2({op,L,'andalso'=Op,A1,A2}, Rs) -> + {op,L,Op,opt_remove_2(A1, Rs),opt_remove_2(A2, Rs)}; +opt_remove_2({op,L,'orelse',A1,A2}, Rs) -> + {op,L,'orelse',opt_remove_2(A1, Rs),A2}; +opt_remove_2({call,Line,{remote,_,{atom,_,erlang},{atom,_,is_record}}, + [{var,_,V},{atom,_,Tag},{integer,_,Sz}]}=A, Rs) -> + case orddict:find(V, Rs) of + {ok,{remove,Tag,Sz}} -> + {atom,Line,true}; + _ -> + A + end; +opt_remove_2({call,Line,{atom,_,is_record}, + [{var,_,V},{atom,_,Tag},{integer,_,Sz}]}=A, Rs) -> + case orddict:find(V, Rs) of + {ok,{remove,Tag,Sz}} -> + {atom,Line,true}; + _ -> + A + end; +opt_remove_2(A, _) -> A. + neg_line(L) -> erl_parse:set_line(L, fun(Line) -> -abs(Line) end). diff --git a/lib/stdlib/src/erl_internal.erl b/lib/stdlib/src/erl_internal.erl index 16173d8210..3073fc0fb5 100644 --- a/lib/stdlib/src/erl_internal.erl +++ b/lib/stdlib/src/erl_internal.erl @@ -1,19 +1,19 @@ %% %% %CopyrightBegin% -%% -%% Copyright Ericsson AB 1998-2009. All Rights Reserved. -%% +%% +%% Copyright Ericsson AB 1998-2011. 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 %% compliance with the License. You should have received a copy of the %% Erlang Public License along with this software. If not, it can be %% retrieved online at http://www.erlang.org/. -%% +%% %% Software distributed under the License is distributed on an "AS IS" %% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See %% the License for the specific language governing rights and limitations %% under the License. -%% +%% %% %CopyrightEnd% %% -module(erl_internal). @@ -48,13 +48,15 @@ %% -export([bif/2,bif/3,guard_bif/2, - type_test/2,new_type_test/2,old_type_test/2]). + type_test/2,new_type_test/2,old_type_test/2,old_bif/2]). -export([arith_op/2,bool_op/2,comp_op/2,list_op/2,send_op/2,op_type/2]). %%--------------------------------------------------------------------------- %% Erlang builtin functions allowed in guards. --spec guard_bif(Name::atom(), Arity::arity()) -> boolean(). +-spec guard_bif(Name, Arity) -> boolean() when + Name :: atom(), + Arity :: arity(). guard_bif(abs, 1) -> true; guard_bif(float, 1) -> true; @@ -87,10 +89,14 @@ guard_bif(is_reference, 1) -> true; guard_bif(is_tuple, 1) -> true; guard_bif(is_record, 2) -> true; guard_bif(is_record, 3) -> true; +guard_bif(binary_part, 2) -> true; +guard_bif(binary_part, 3) -> true; guard_bif(Name, A) when is_atom(Name), is_integer(A) -> false. %% Erlang type tests. --spec type_test(Name::atom(), Arity::arity()) -> boolean(). +-spec type_test(Name, Arity) -> boolean() when + Name :: atom(), + Arity :: arity(). type_test(Name, Arity) -> new_type_test(Name, Arity) orelse old_type_test(Name, Arity). @@ -133,7 +139,9 @@ old_type_test(record, 2) -> true; old_type_test(function, 1) -> true; old_type_test(Name, A) when is_atom(Name), is_integer(A) -> false. --spec arith_op(Op::atom(), Arity::arity()) -> boolean(). +-spec arith_op(OpName, Arity) -> boolean() when + OpName :: atom(), + Arity :: arity(). arith_op('+', 1) -> true; arith_op('-', 1) -> true; @@ -151,7 +159,9 @@ arith_op('bsl', 2) -> true; arith_op('bsr', 2) -> true; arith_op(Op, A) when is_atom(Op), is_integer(A) -> false. --spec bool_op(Op::atom(), Arity::arity()) -> boolean(). +-spec bool_op(OpName, Arity) -> boolean() when + OpName :: atom(), + Arity :: arity(). bool_op('not', 1) -> true; bool_op('and', 2) -> true; @@ -159,7 +169,9 @@ bool_op('or', 2) -> true; bool_op('xor', 2) -> true; bool_op(Op, A) when is_atom(Op), is_integer(A) -> false. --spec comp_op(Op::atom(), Arity::arity()) -> boolean(). +-spec comp_op(OpName, Arity) -> boolean() when + OpName :: atom(), + Arity :: arity(). comp_op('==', 2) -> true; comp_op('/=', 2) -> true; @@ -171,18 +183,25 @@ comp_op('=:=', 2) -> true; comp_op('=/=', 2) -> true; comp_op(Op, A) when is_atom(Op), is_integer(A) -> false. --spec list_op(Op::atom(), Arity::arity()) -> boolean(). +-spec list_op(OpName, Arity) -> boolean() when + OpName :: atom(), + Arity :: arity(). list_op('++', 2) -> true; list_op('--', 2) -> true; list_op(Op, A) when is_atom(Op), is_integer(A) -> false. --spec send_op(Op::atom(), Arity::arity()) -> boolean(). +-spec send_op(OpName, Arity) -> boolean() when + OpName :: atom(), + Arity :: arity(). send_op('!', 2) -> true; send_op(Op, A) when is_atom(Op), is_integer(A) -> false. --spec op_type(atom(), arity()) -> 'arith' | 'bool' | 'comp' | 'list' | 'send'. +-spec op_type(OpName, Arity) -> Type when + OpName :: atom(), + Arity :: arity(), + Type :: 'arith' | 'bool' | 'comp' | 'list' | 'send'. op_type('+', 1) -> arith; op_type('-', 1) -> arith; @@ -219,7 +238,9 @@ op_type('!', 2) -> send. bif(erlang, Name, Arity) -> bif(Name, Arity); bif(M, F, A) when is_atom(M), is_atom(F), is_integer(A) -> false. --spec bif(Name::atom(), Arity::arity()) -> boolean(). +-spec bif(Name, Arity) -> boolean() when + Name :: atom(), + Arity::arity(). %% Returns true if erlang:Name/Arity is an auto-imported BIF, false otherwise. %% Use erlang:is_bultin(Mod, Name, Arity) to find whether a function is a BIF %% (meaning implemented in C) or not. @@ -229,23 +250,31 @@ bif(apply, 2) -> true; bif(apply, 3) -> true; bif(atom_to_binary, 2) -> true; bif(atom_to_list, 1) -> true; +bif(binary_part, 2) -> true; +bif(binary_part, 3) -> true; bif(binary_to_atom, 2) -> true; bif(binary_to_existing_atom, 2) -> true; bif(binary_to_list, 1) -> true; bif(binary_to_list, 3) -> true; bif(binary_to_term, 1) -> true; +bif(binary_to_term, 2) -> true; bif(bitsize, 1) -> true; bif(bit_size, 1) -> true; bif(bitstring_to_list, 1) -> true; bif(byte_size, 1) -> true; +bif(check_old_code, 1) -> true; bif(check_process_code, 2) -> true; bif(concat_binary, 1) -> true; bif(date, 0) -> true; bif(delete_module, 1) -> true; +bif(demonitor, 1) -> true; +bif(demonitor, 2) -> true; bif(disconnect_node, 1) -> true; bif(element, 2) -> true; bif(erase, 0) -> true; bif(erase, 1) -> true; +bif(error, 1) -> true; +bif(error, 2) -> true; bif(exit, 1) -> true; bif(exit, 2) -> true; bif(float, 1) -> true; @@ -261,6 +290,7 @@ bif(halt, 0) -> true; bif(halt, 1) -> true; bif(hd, 1) -> true; bif(integer_to_list, 1) -> true; +bif(integer_to_list, 2) -> true; bif(iolist_size, 1) -> true; bif(iolist_to_binary, 1) -> true; bif(is_alive, 0) -> true; @@ -290,11 +320,16 @@ bif(list_to_bitstring, 1) -> true; bif(list_to_existing_atom, 1) -> true; bif(list_to_float, 1) -> true; bif(list_to_integer, 1) -> true; +bif(list_to_integer, 2) -> true; bif(list_to_pid, 1) -> true; bif(list_to_tuple, 1) -> true; bif(load_module, 2) -> true; bif(make_ref, 0) -> true; +bif(max,2) -> true; +bif(min,2) -> true; bif(module_loaded, 1) -> true; +bif(monitor, 2) -> true; +bif(monitor, 3) -> true; bif(monitor_node, 2) -> true; bif(node, 0) -> true; bif(node, 1) -> true; @@ -305,6 +340,7 @@ bif(open_port, 2) -> true; bif(pid_to_list, 1) -> true; bif(port_close, 1) -> true; bif(port_command, 2) -> true; +bif(port_command, 3) -> true; bif(port_connect, 2) -> true; bif(port_control, 3) -> true; bif(pre_loaded, 0) -> true; @@ -349,3 +385,134 @@ bif(unlink, 1) -> true; bif(unregister, 1) -> true; bif(whereis, 1) -> true; bif(Name, A) when is_atom(Name), is_integer(A) -> false. + +-spec old_bif(Name::atom(), Arity::arity()) -> boolean(). +%% Returns true if erlang:Name/Arity is an old (pre R14) auto-imported BIF, false otherwise. +%% Use erlang:is_bultin(Mod, Name, Arity) to find whether a function is a BIF +%% (meaning implemented in C) or not. + +old_bif(abs, 1) -> true; +old_bif(apply, 2) -> true; +old_bif(apply, 3) -> true; +old_bif(atom_to_binary, 2) -> true; +old_bif(atom_to_list, 1) -> true; +old_bif(binary_to_atom, 2) -> true; +old_bif(binary_to_existing_atom, 2) -> true; +old_bif(binary_to_list, 1) -> true; +old_bif(binary_to_list, 3) -> true; +old_bif(binary_to_term, 1) -> true; +old_bif(bitsize, 1) -> true; +old_bif(bit_size, 1) -> true; +old_bif(bitstring_to_list, 1) -> true; +old_bif(byte_size, 1) -> true; +old_bif(check_process_code, 2) -> true; +old_bif(concat_binary, 1) -> true; +old_bif(date, 0) -> true; +old_bif(delete_module, 1) -> true; +old_bif(disconnect_node, 1) -> true; +old_bif(element, 2) -> true; +old_bif(erase, 0) -> true; +old_bif(erase, 1) -> true; +old_bif(exit, 1) -> true; +old_bif(exit, 2) -> true; +old_bif(float, 1) -> true; +old_bif(float_to_list, 1) -> true; +old_bif(garbage_collect, 0) -> true; +old_bif(garbage_collect, 1) -> true; +old_bif(get, 0) -> true; +old_bif(get, 1) -> true; +old_bif(get_keys, 1) -> true; +old_bif(group_leader, 0) -> true; +old_bif(group_leader, 2) -> true; +old_bif(halt, 0) -> true; +old_bif(halt, 1) -> true; +old_bif(hd, 1) -> true; +old_bif(integer_to_list, 1) -> true; +old_bif(iolist_size, 1) -> true; +old_bif(iolist_to_binary, 1) -> true; +old_bif(is_alive, 0) -> true; +old_bif(is_process_alive, 1) -> true; +old_bif(is_atom, 1) -> true; +old_bif(is_boolean, 1) -> true; +old_bif(is_binary, 1) -> true; +old_bif(is_bitstr, 1) -> true; +old_bif(is_bitstring, 1) -> true; +old_bif(is_float, 1) -> true; +old_bif(is_function, 1) -> true; +old_bif(is_function, 2) -> true; +old_bif(is_integer, 1) -> true; +old_bif(is_list, 1) -> true; +old_bif(is_number, 1) -> true; +old_bif(is_pid, 1) -> true; +old_bif(is_port, 1) -> true; +old_bif(is_reference, 1) -> true; +old_bif(is_tuple, 1) -> true; +old_bif(is_record, 2) -> true; +old_bif(is_record, 3) -> true; +old_bif(length, 1) -> true; +old_bif(link, 1) -> true; +old_bif(list_to_atom, 1) -> true; +old_bif(list_to_binary, 1) -> true; +old_bif(list_to_bitstring, 1) -> true; +old_bif(list_to_existing_atom, 1) -> true; +old_bif(list_to_float, 1) -> true; +old_bif(list_to_integer, 1) -> true; +old_bif(list_to_pid, 1) -> true; +old_bif(list_to_tuple, 1) -> true; +old_bif(load_module, 2) -> true; +old_bif(make_ref, 0) -> true; +old_bif(module_loaded, 1) -> true; +old_bif(monitor_node, 2) -> true; +old_bif(node, 0) -> true; +old_bif(node, 1) -> true; +old_bif(nodes, 0) -> true; +old_bif(nodes, 1) -> true; +old_bif(now, 0) -> true; +old_bif(open_port, 2) -> true; +old_bif(pid_to_list, 1) -> true; +old_bif(port_close, 1) -> true; +old_bif(port_command, 2) -> true; +old_bif(port_connect, 2) -> true; +old_bif(port_control, 3) -> true; +old_bif(pre_loaded, 0) -> true; +old_bif(process_flag, 2) -> true; +old_bif(process_flag, 3) -> true; +old_bif(process_info, 1) -> true; +old_bif(process_info, 2) -> true; +old_bif(processes, 0) -> true; +old_bif(purge_module, 1) -> true; +old_bif(put, 2) -> true; +old_bif(register, 2) -> true; +old_bif(registered, 0) -> true; +old_bif(round, 1) -> true; +old_bif(self, 0) -> true; +old_bif(setelement, 3) -> true; +old_bif(size, 1) -> true; +old_bif(spawn, 1) -> true; +old_bif(spawn, 2) -> true; +old_bif(spawn, 3) -> true; +old_bif(spawn, 4) -> true; +old_bif(spawn_link, 1) -> true; +old_bif(spawn_link, 2) -> true; +old_bif(spawn_link, 3) -> true; +old_bif(spawn_link, 4) -> true; +old_bif(spawn_monitor, 1) -> true; +old_bif(spawn_monitor, 3) -> true; +old_bif(spawn_opt, 2) -> true; +old_bif(spawn_opt, 3) -> true; +old_bif(spawn_opt, 4) -> true; +old_bif(spawn_opt, 5) -> true; +old_bif(split_binary, 2) -> true; +old_bif(statistics, 1) -> true; +old_bif(term_to_binary, 1) -> true; +old_bif(term_to_binary, 2) -> true; +old_bif(throw, 1) -> true; +old_bif(time, 0) -> true; +old_bif(tl, 1) -> true; +old_bif(trunc, 1) -> true; +old_bif(tuple_size, 1) -> true; +old_bif(tuple_to_list, 1) -> true; +old_bif(unlink, 1) -> true; +old_bif(unregister, 1) -> true; +old_bif(whereis, 1) -> true; +old_bif(Name, A) when is_atom(Name), is_integer(A) -> false. diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index 91f7641af7..dd0b9bc2ab 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -2,7 +2,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2010. All Rights Reserved. +%% Copyright Ericsson AB 1996-2011. 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 @@ -40,7 +40,7 @@ %% Value. %% The option handling functions. --spec bool_option(atom(), atom(), boolean(), [_]) -> boolean(). +-spec bool_option(atom(), atom(), boolean(), [compile:option()]) -> boolean(). bool_option(On, Off, Default, Opts) -> foldl(fun (Opt, _Def) when Opt =:= On -> true; @@ -60,6 +60,10 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) -> (_Opt, Def) -> Def end, Default, Opts). +%% The maximum number of arguments allowed for a function. + +-define(MAX_ARGUMENTS, 255). + %% The error and warning info structures, {Line,Module,Descriptor}, %% are kept in their seperate fields in the lint state record together %% with the name of the file (when a new file is entered, marked by @@ -72,6 +76,10 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) -> %%-define(DEBUGF(X,Y), io:format(X, Y)). -define(DEBUGF(X,Y), void). +-type line() :: erl_scan:line(). % a convenient alias +-type fa() :: {atom(), arity()}. % function+arity +-type ta() :: {atom(), arity()}. % type+arity + %% Usage of records, functions, and imports. The variable table, which %% is passed on as an argument, holds the usage of variables. -record(usage, { @@ -94,9 +102,11 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) -> mod_imports=dict:new() :: dict(), %Module Imports compile=[], %Compile flags records=dict:new() :: dict(), %Record definitions + locals=gb_sets:empty() :: gb_set(), %All defined functions (prescanned) + no_auto=gb_sets:empty() :: gb_set(), %Functions explicitly not autoimported defined=gb_sets:empty() :: gb_set(), %Defined fuctions - on_load=[] :: [{atom(),integer()}], %On-load function - on_load_line=0 :: integer(), %Line for on_load + on_load=[] :: [fa()], %On-load function + on_load_line=0 :: line(), %Line for on_load clashes=[], %Exported functions named as BIFs not_deprecated=[], %Not considered deprecated func=[], %Current function @@ -110,17 +120,23 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) -> %outside any fun or lc xqlc= false :: boolean(), %true if qlc.hrl included new = false :: boolean(), %Has user-defined 'new/N' - called= [], %Called functions + called= [] :: [{fa(),line()}], %Called functions usage = #usage{} :: #usage{}, specs = dict:new() :: dict(), %Type specifications - types = dict:new() :: dict() %Type definitions + types = dict:new() :: dict(), %Type definitions + exp_types=gb_sets:empty():: gb_set() %Exported types }). -type lint_state() :: #lint{}. +-type error_description() :: term(). +-type error_info() :: {erl_scan:line(), module(), error_description()}. %% format_error(Error) %% Return a string describing the error. +-spec format_error(ErrorDescriptor) -> io_lib:chars() when + ErrorDescriptor :: error_description(). + format_error(undefined_module) -> "no module definition"; format_error({bad_module_name, M}) -> @@ -161,6 +177,9 @@ format_error({bad_nowarn_unused_function,{F,A}}) -> io_lib:format("function ~w/~w undefined", [F,A]); format_error({bad_nowarn_bif_clash,{F,A}}) -> io_lib:format("function ~w/~w undefined", [F,A]); +format_error(disallowed_nowarn_bif_clash) -> + io_lib:format("compile directive nowarn_bif_clash is no longer allowed,~n" + " - use explicit module names or -compile({no_auto_import, [F/A]})", []); format_error({bad_nowarn_deprecated_function,{M,F,A}}) -> io_lib:format("~w:~w/~w is not a deprecated function", [M,F,A]); format_error({bad_on_load,Term}) -> @@ -186,13 +205,21 @@ format_error({define_import,{F,A}}) -> io_lib:format("defining imported function ~w/~w", [F,A]); format_error({unused_function,{F,A}}) -> io_lib:format("function ~w/~w is unused", [F,A]); -format_error({redefine_bif,{F,A}}) -> - io_lib:format("defining BIF ~w/~w", [F,A]); format_error({call_to_redefined_bif,{F,A}}) -> - io_lib:format("call to ~w/~w will call erlang:~w/~w; " - "not ~w/~w in this module \n" - " (add an explicit module name to the call to avoid this error)", - [F,A,F,A,F,A]); + io_lib:format("ambiguous call of overridden auto-imported BIF ~w/~w~n" + " - use erlang:~w/~w or \"-compile({no_auto_import,[~w/~w]}).\" " + "to resolve name clash", [F,A,F,A,F,A]); +format_error({call_to_redefined_old_bif,{F,A}}) -> + io_lib:format("ambiguous call of overridden pre R14 auto-imported BIF ~w/~w~n" + " - use erlang:~w/~w or \"-compile({no_auto_import,[~w/~w]}).\" " + "to resolve name clash", [F,A,F,A,F,A]); +format_error({redefine_old_bif_import,{F,A}}) -> + io_lib:format("import directive overrides pre R14 auto-imported BIF ~w/~w~n" + " - use \"-compile({no_auto_import,[~w/~w]}).\" " + "to resolve name clash", [F,A,F,A]); +format_error({redefine_bif_import,{F,A}}) -> + io_lib:format("import directive overrides auto-imported BIF ~w/~w~n" + " - use \"-compile({no_auto_import,[~w/~w]}).\" to resolve name clash", [F,A,F,A]); format_error({deprecated, MFA, ReplacementMFA, Rel}) -> io_lib:format("~s is deprecated and will be removed in ~s; use ~s", @@ -208,11 +235,17 @@ format_error({obsolete_guard, {F, A}}) -> io_lib:format("~p/~p obsolete", [F, A]); format_error({reserved_for_future,K}) -> io_lib:format("atom ~w: future reserved keyword - rename or quote", [K]); +format_error({too_many_arguments,Arity}) -> + io_lib:format("too many arguments (~w) - " + "maximum allowed is ~w", [Arity,?MAX_ARGUMENTS]); %% --- patterns and guards --- format_error(illegal_pattern) -> "illegal pattern"; format_error(illegal_bin_pattern) -> "binary patterns cannot be matched in parallel using '='"; format_error(illegal_expr) -> "illegal expression"; +format_error({illegal_guard_local_call, {F,A}}) -> + io_lib:format("call to local/imported function ~w/~w is illegal in guard", + [F,A]); format_error(illegal_guard_expr) -> "illegal guard expression"; %% --- exports --- format_error({explicit_export,F,A}) -> @@ -242,10 +275,10 @@ format_error({untyped_record,T}) -> format_error({unbound_var,V}) -> io_lib:format("variable ~w is unbound", [V]); format_error({unsafe_var,V,{What,Where}}) -> - io_lib:format("variable ~w unsafe in ~w ~s", + io_lib:format("variable ~w unsafe in ~w ~s", [V,What,format_where(Where)]); format_error({exported_var,V,{What,Where}}) -> - io_lib:format("variable ~w exported from ~w ~s", + io_lib:format("variable ~w exported from ~w ~s", [V,What,format_where(Where)]); format_error({shadowed_var,V,In}) -> io_lib:format("variable ~w shadowed in ~w", [V,In]); @@ -290,22 +323,26 @@ format_error({ill_defined_behaviour_callbacks,Behaviour}) -> %% --- types and specs --- format_error({singleton_typevar, Name}) -> io_lib:format("type variable ~w is only used once (is unbound)", [Name]); +format_error({bad_export_type, _ETs}) -> + io_lib:format("bad export_type declaration", []); +format_error({duplicated_export_type, {T, A}}) -> + io_lib:format("type ~w/~w already exported", [T, A]); format_error({undefined_type, {TypeName, Arity}}) -> io_lib:format("type ~w~s undefined", [TypeName, gen_type_paren(Arity)]); format_error({unused_type, {TypeName, Arity}}) -> io_lib:format("type ~w~s is unused", [TypeName, gen_type_paren(Arity)]); format_error({new_builtin_type, {TypeName, Arity}}) -> io_lib:format("type ~w~s is a new builtin type; " - "its (re)definition is allowed only until the next release", + "its (re)definition is allowed only until the next release", [TypeName, gen_type_paren(Arity)]); format_error({builtin_type, {TypeName, Arity}}) -> - io_lib:format("type ~w~s is a builtin type; it cannot be redefined", + io_lib:format("type ~w~s is a builtin type; it cannot be redefined", [TypeName, gen_type_paren(Arity)]); format_error({renamed_type, OldName, NewName}) -> io_lib:format("type ~w() is now called ~w(); " "please use the new name instead", [OldName, NewName]); format_error({redefine_type, {TypeName, Arity}}) -> - io_lib:format("type ~w~s already defined", + io_lib:format("type ~w~s already defined", [TypeName, gen_type_paren(Arity)]); format_error({type_syntax, Constr}) -> io_lib:format("bad ~w type", [Constr]); @@ -354,7 +391,7 @@ pseudolocals() -> %% %% Used by erl_eval.erl to check commands. -%% +%% exprs(Exprs, BindingsList) -> exprs_opt(Exprs, BindingsList, []). @@ -362,7 +399,7 @@ exprs_opt(Exprs, BindingsList, Opts) -> {St0,Vs} = foldl(fun({{record,_SequenceNumber,_Name},Attr0}, {St1,Vs1}) -> Attr = zip_file_and_line(Attr0, "none"), {attribute_state(Attr, St1),Vs1}; - ({V,_}, {St1,Vs1}) -> + ({V,_}, {St1,Vs1}) -> {St1,[{V,{bound,unused,[]}} | Vs1]} end, {start("nofile",Opts),[]}, BindingsList), Vt = orddict:from_list(Vs), @@ -387,16 +424,39 @@ used_vars(Exprs, BindingsList) -> %% apply_lambda/2 has been called to shut lint up. N.B. these lists are %% really all ordsets! +-spec(module(AbsForms) -> {ok, Warnings} | {error, Errors, Warnings} when + AbsForms :: [erl_parse:abstract_form()], + Warnings :: [{file:filename(),[ErrorInfo]}], + Errors :: [{FileName2 :: file:filename(),[ErrorInfo]}], + ErrorInfo :: error_info()). + module(Forms) -> Opts = compiler_options(Forms), St = forms(Forms, start("nofile", Opts)), return_status(St). - + +-spec(module(AbsForms, FileName) -> + {ok, Warnings} | {error, Errors, Warnings} when + AbsForms :: [erl_parse:abstract_form()], + FileName :: atom() | string(), + Warnings :: [{file:filename(),[ErrorInfo]}], + Errors :: [{FileName2 :: file:filename(),[ErrorInfo]}], + ErrorInfo :: error_info()). + module(Forms, FileName) -> Opts = compiler_options(Forms), St = forms(Forms, start(FileName, Opts)), return_status(St). +-spec(module(AbsForms, FileName, CompileOptions) -> + {ok, Warnings} | {error, Errors, Warnings} when + AbsForms :: [erl_parse:abstract_form()], + FileName :: atom() | string(), + CompileOptions :: [compile:option()], + Warnings :: [{file:filename(),[ErrorInfo]}], + Errors :: [{FileName2 :: file:filename(),[ErrorInfo]}], + ErrorInfo :: error_info()). + module(Forms, FileName, Opts0) -> %% We want the options given on the command line to take %% precedence over options in the module. @@ -506,7 +566,7 @@ pack_errors(Es) -> %% Sort on line number. pack_warnings(Ws) -> - [{File,lists:sort([W || {F,W} <- Ws, F =:= File])} || + [{File,lists:sort([W || {F,W} <- Ws, F =:= File])} || File <- lists:usort([F || {F,_} <- Ws])]. %% add_error(ErrorDescriptor, State) -> State' @@ -516,13 +576,13 @@ pack_warnings(Ws) -> add_error(E, St) -> St#lint{errors=[{St#lint.file,E}|St#lint.errors]}. -add_error(FileLine, E, St) -> +add_error(FileLine, E, St) -> {File,Location} = loc(FileLine), add_error({Location,erl_lint,E}, St#lint{file = File}). add_warning(W, St) -> St#lint{warnings=[{St#lint.file,W}|St#lint.warnings]}. -add_warning(FileLine, W, St) -> +add_warning(FileLine, W, St) -> {File,Location} = loc(FileLine), add_warning({Location,erl_lint,W}, St#lint{file = File}). @@ -538,8 +598,12 @@ loc(L) -> forms(Forms0, St0) -> Forms = eval_file_attribute(Forms0, St0), + Locals = local_functions(Forms), + AutoImportSuppressed = auto_import_suppressed(St0#lint.compile), + StDeprecated = disallowed_compile_flags(Forms,St0), %% Line numbers are from now on pairs {File,Line}. - St1 = includes_qlc_hrl(Forms, St0), + St1 = includes_qlc_hrl(Forms, StDeprecated#lint{locals = Locals, + no_auto = AutoImportSuppressed}), St2 = bif_clashes(Forms, St1), St3 = not_deprecated(Forms, St2), St4 = foldl(fun form/2, pre_scan(Forms, St3), Forms), @@ -561,7 +625,7 @@ pre_scan([_ | Fs], St) -> pre_scan(Fs, St); pre_scan([], St) -> St. - + includes_qlc_hrl(Forms, St) -> %% QLC calls erl_lint several times, sometimes with the compile %% attribute removed. The file attribute, however, is left as is. @@ -667,6 +731,8 @@ attribute_state({attribute,L,extends,_M}, St) -> add_error(L, invalid_extends, St); attribute_state({attribute,L,export,Es}, St) -> export(L, Es, St); +attribute_state({attribute,L,export_type,Es}, St) -> + export_type(L, Es, St); attribute_state({attribute,L,import,Is}, St) -> import(L, Is, St); attribute_state({attribute,L,record,{Name,Fields}}, St) -> @@ -724,27 +790,38 @@ bif_clashes(Forms, St) -> Clashes = ordsets:subtract(ordsets:from_list(Clashes0), Nowarn), St#lint{clashes=Clashes}. --spec is_bif_clash(atom(), byte(), lint_state()) -> boolean(). - -is_bif_clash(_Name, _Arity, #lint{clashes=[]}) -> - false; -is_bif_clash(Name, Arity, #lint{clashes=Clashes}) -> - ordsets:is_element({Name,Arity}, Clashes). - %% not_deprecated(Forms, State0) -> State not_deprecated(Forms, St0) -> %% There are no line numbers in St0#lint.compile. - MFAsL = [{MFA,L} || + MFAsL = [{MFA,L} || {attribute, L, compile, Args} <- Forms, {nowarn_deprecated_function, MFAs0} <- lists:flatten([Args]), MFA <- lists:flatten([MFAs0])], Nowarn = [MFA || {MFA,_L} <- MFAsL], - Bad = [MFAL || {{M,F,A},_L}=MFAL <- MFAsL, + Bad = [MFAL || {{M,F,A},_L}=MFAL <- MFAsL, otp_internal:obsolete(M, F, A) =:= no], St1 = func_line_warning(bad_nowarn_deprecated_function, Bad, St0), St1#lint{not_deprecated = ordsets:from_list(Nowarn)}. +%% The nowarn_bif_clash directive is not only deprecated, it's actually an error from R14A +disallowed_compile_flags(Forms, St0) -> + %% There are (still) no line numbers in St0#lint.compile. + Errors0 = [ {St0#lint.file,{L,erl_lint,disallowed_nowarn_bif_clash}} || + {attribute,[{line,{_,L}}],compile,nowarn_bif_clash} <- Forms ], + Errors1 = [ {St0#lint.file,{L,erl_lint,disallowed_nowarn_bif_clash}} || + {attribute,[{line,{_,L}}],compile,{nowarn_bif_clash, {_,_}}} <- Forms ], + Disabled = (not is_warn_enabled(bif_clash, St0)), + Errors = if + Disabled andalso Errors0 =:= [] -> + [{St0#lint.file,{erl_lint,disallowed_nowarn_bif_clash}} | St0#lint.errors]; + Disabled -> + Errors0 ++ Errors1 ++ St0#lint.errors; + true -> + Errors1 ++ St0#lint.errors + end, + St0#lint{errors=Errors}. + %% post_traversal_check(Forms, State0) -> State. %% Do some further checking after the forms have been traversed and %% data about calls etc. have been collected. @@ -862,7 +939,7 @@ check_deprecated(Forms, St0) -> Bad = [{E,L} || {attribute, L, deprecated, Depr} <- Forms, D <- lists:flatten([Depr]), E <- depr_cat(D, X, Mod)], - foldl(fun ({E,L}, St1) -> + foldl(fun ({E,L}, St1) -> add_error(L, E, St1) end, St0, Bad). @@ -912,7 +989,7 @@ check_imports(Forms, St0) -> true -> Usage = St0#lint.usage, Unused = ordsets:subtract(St0#lint.imports, Usage#usage.imported), - Imports = [{{FA,list_to_atom(package_to_string(Mod))},L} + Imports = [{{FA,list_to_atom(package_to_string(Mod))},L} || {attribute,L,import,{Mod,Fs}} <- Forms, FA <- lists:usort(Fs)], Bad = [{FM,L} || FM <- Unused, {FM2,L} <- Imports, FM =:= FM2], @@ -932,7 +1009,7 @@ check_unused_functions(Forms, St0) -> Opts = St1#lint.compile, case member(export_all, Opts) orelse not is_warn_enabled(unused_function, St1) of - true -> + true -> St1; false -> Nowarn = nowarn_function(nowarn_unused_function, Opts), @@ -1003,12 +1080,13 @@ check_option_functions(Forms, Tag0, Type, St0) -> {Tag, FAs0} <- lists:flatten([Args]), Tag0 =:= Tag, FA <- lists:flatten([FAs0])], - DefFunctions = gb_sets:to_list(St0#lint.defined) -- pseudolocals(), + DefFunctions = (gb_sets:to_list(St0#lint.defined) -- pseudolocals()) ++ + [{F,A} || {{F,A},_} <- orddict:to_list(St0#lint.imports)], Bad = [{FA,L} || {FA,L} <- FAsL, not member(FA, DefFunctions)], func_line_error(Type, Bad, St0). nowarn_function(Tag, Opts) -> - ordsets:from_list([FA || {Tag1,FAs} <- Opts, + ordsets:from_list([FA || {Tag1,FAs} <- Opts, Tag1 =:= Tag, FA <- lists:flatten([FAs])]). @@ -1021,11 +1099,8 @@ func_line_error(Type, Fs, St) -> check_untyped_records(Forms, St0) -> case is_warn_enabled(untyped_record, St0) of true -> - %% One possibility is to use the names of all records - %% RecNames = dict:fetch_keys(St0#lint.records), - %% but I think it's better to keep those that are used by the file - Usage = St0#lint.usage, - UsedRecNames = sets:to_list(Usage#usage.used_records), + %% Use the names of all records *defined* in the module (not used) + RecNames = dict:fetch_keys(St0#lint.records), %% these are the records with field(s) containing type info TRecNames = [Name || {attribute,_,type,{{record,Name},Fields,_}} <- Forms, @@ -1038,7 +1113,7 @@ check_untyped_records(Forms, St0) -> [] -> St; % exclude records with no fields [_|_] -> add_warning(L, {untyped_record, N}, St) end - end, St0, UsedRecNames -- TRecNames); + end, St0, RecNames -- TRecNames); false -> St0 end. @@ -1051,10 +1126,10 @@ check_unused_records(Forms, St0) -> %% functions count. Usage = St0#lint.usage, UsedRecords = sets:to_list(Usage#usage.used_records), - URecs = foldl(fun (Used, Recs) -> - dict:erase(Used, Recs) + URecs = foldl(fun (Used, Recs) -> + dict:erase(Used, Recs) end, St0#lint.records, UsedRecords), - Unused = [{Name,FileLine} || + Unused = [{Name,FileLine} || {Name,{FileLine,_Fields}} <- dict:to_list(URecs), element(1, loc(FileLine)) =:= FirstFile], foldl(fun ({N,L}, St) -> @@ -1064,18 +1139,19 @@ check_unused_records(Forms, St0) -> St0 end. -%% For storing the import list we use the orddict module. +%% For storing the import list we use the orddict module. %% We know an empty set is []. -%% export(Line, Exports, State) -> State. +-spec export(line(), [fa()], lint_state()) -> lint_state(). %% Mark functions as exported, also as called from the export line. export(Line, Es, #lint{exports = Es0, called = Called} = St0) -> - {Es1,C1,St1} = + {Es1,C1,St1} = foldl(fun (NA, {E,C,St2}) -> St = case gb_sets:is_element(NA, E) of true -> - add_warning(Line, {duplicated_export, NA}, St2); + Warn = {duplicated_export,NA}, + add_warning(Line, Warn, St2); false -> St2 end, @@ -1084,8 +1160,31 @@ export(Line, Es, #lint{exports = Es0, called = Called} = St0) -> {Es0,Called,St0}, Es), St1#lint{exports = Es1, called = C1}. -%% import(Line, Imports, State) -> State. -%% imported(Name, Arity, State) -> {yes,Module} | no. +-spec export_type(line(), [ta()], lint_state()) -> lint_state(). +%% Mark types as exported; also mark them as used from the export line. + +export_type(Line, ETs, #lint{usage = Usage, exp_types = ETs0} = St0) -> + UTs0 = Usage#usage.used_types, + try foldl(fun ({T,A}=TA, {E,U,St2}) when is_atom(T), is_integer(A) -> + St = case gb_sets:is_element(TA, E) of + true -> + Warn = {duplicated_export_type,TA}, + add_warning(Line, Warn, St2); + false -> + St2 + end, + {gb_sets:add_element(TA, E), dict:store(TA, Line, U), St} + end, + {ETs0,UTs0,St0}, ETs) of + {ETs1,UTs1,St1} -> + St1#lint{usage = Usage#usage{used_types = UTs1}, exp_types = ETs1} + catch + error:_ -> + add_error(Line, {bad_export_type, ETs}, St0) + end. + +-type import() :: {module(), [fa()]} | module(). +-spec import(line(), import(), lint_state()) -> lint_state(). import(Line, {Mod,Fs}, St) -> Mod1 = package_to_string(Mod), @@ -1097,11 +1196,41 @@ import(Line, {Mod,Fs}, St) -> St#lint{imports=add_imports(list_to_atom(Mod1), Mfs, St#lint.imports)}; Efs -> - foldl(fun (Ef, St0) -> - add_error(Line, {redefine_import,Ef}, - St0) + {Err, St1} = + foldl(fun ({bif,{F,A},_}, {Err,St0}) -> + %% BifClash - import directive + Warn = is_warn_enabled(bif_clash, St0) + and (not bif_clash_specifically_disabled(St0,{F,A})), + AutoImpSup = is_autoimport_suppressed(St0#lint.no_auto,{F,A}), + OldBif = erl_internal:old_bif(F,A), + {Err,if + Warn and (not AutoImpSup) and OldBif -> + add_error + (Line, + {redefine_old_bif_import, {F,A}}, + St0); + Warn and (not AutoImpSup) -> + add_warning + (Line, + {redefine_bif_import, {F,A}}, + St0); + true -> + St0 + end}; + (Ef, {_Err,St0}) -> + {true,add_error(Line, + {redefine_import,Ef}, + St0)} end, - St, Efs) + {false,St}, Efs), + if + not Err -> + St1#lint{imports= + add_imports(list_to_atom(Mod1), Mfs, + St#lint.imports)}; + true -> + St1 + end end; false -> add_error(Line, {bad_module_name, Mod1}, St) @@ -1144,13 +1273,15 @@ check_imports(_Line, Fs, Is) -> add_imports(Mod, Fs, Is) -> foldl(fun (F, Is0) -> orddict:store(F, Mod, Is0) end, Is, Fs). +-spec imported(atom(), arity(), lint_state()) -> {'yes',module()} | 'no'. + imported(F, A, St) -> case orddict:find({F,A}, St#lint.imports) of {ok,Mod} -> {yes,Mod}; error -> no end. -%% on_load(Line, Val, State) -> State. +-spec on_load(line(), fa(), lint_state()) -> lint_state(). %% Check an on_load directive and remember it. on_load(Line, {Name,Arity}=Fa, #lint{on_load=OnLoad0}=St0) @@ -1182,7 +1313,7 @@ check_on_load(#lint{defined=Defined,on_load=[{_,0}=Fa], end; check_on_load(St) -> St. -%% call_function(Line, Name, Arity, State) -> State. +-spec call_function(line(), atom(), arity(), lint_state()) -> lint_state(). %% Add to both called and calls. call_function(Line, F, A, #lint{usage=Usage0,called=Cd,func=Func}=St) -> @@ -1194,12 +1325,6 @@ call_function(Line, F, A, #lint{usage=Usage0,called=Cd,func=Func}=St) -> end, St#lint{called=[{NA,Line}|Cd], usage=Usage}. -%% is_function_exported(Name, Arity, State) -> false|true. - -is_function_exported(Name, Arity, #lint{exports=Exports,compile=Compile}) -> - gb_sets:is_element({Name,Arity}, Exports) orelse - member(export_all, Compile). - %% function(Line, Name, Arity, Clauses, State) -> State. function(Line, instance, _Arity, _Cs, St) when St#lint.global_vt =/= [] -> @@ -1208,7 +1333,7 @@ function(Line, Name, Arity, Cs, St0) -> St1 = define_function(Line, Name, Arity, St0#lint{func={Name,Arity}}), clauses(Cs, St1#lint.global_vt, St1). -%% define_function(Line, Name, Arity, State) -> State. +-spec define_function(line(), atom(), arity(), lint_state()) -> lint_state(). define_function(Line, Name, Arity, St0) -> St1 = keyword_warning(Line, Name, St0), @@ -1217,18 +1342,18 @@ define_function(Line, Name, Arity, St0) -> true -> add_error(Line, {redefine_function,NA}, St1); false -> - St2 = St1#lint{defined=gb_sets:add_element(NA, St1#lint.defined)}, - St = case erl_internal:bif(Name, Arity) andalso - not is_function_exported(Name, Arity, St2) of - true -> add_warning(Line, {redefine_bif,NA}, St2); - false -> St2 - end, - case imported(Name, Arity, St) of - {yes,_M} -> add_error(Line, {define_import,NA}, St); - no -> St + St2 = function_check_max_args(Line, Arity, St1), + St3 = St2#lint{defined=gb_sets:add_element(NA, St2#lint.defined)}, + case imported(Name, Arity, St3) of + {yes,_M} -> add_error(Line, {define_import,NA}, St3); + no -> St3 end end. +function_check_max_args(Line, Arity, St) when Arity > ?MAX_ARGUMENTS -> + add_error(Line, {too_many_arguments,Arity}, St); +function_check_max_args(_, _, St) -> St. + %% clauses([Clause], VarTable, State) -> {VarTable, State}. clauses(Cs, Vt, St) -> @@ -1261,7 +1386,7 @@ head([P|Ps], Vt, Old, St0) -> {vtmerge_pat(Pvt, Psvt),vtmerge_pat(Bvt1,Bvt2),St2}; head([], _Vt, _Env, St) -> {[],[],St}. -%% pattern(Pattern, VarTable, Old, BinVarTable, State) -> +%% pattern(Pattern, VarTable, Old, BinVarTable, State) -> %% {UpdVarTable,BinVarTable,State}. %% Check pattern return variables. Old is the set of variables used for %% deciding whether an occurrence is a binding occurrence or a use, and @@ -1279,7 +1404,7 @@ pattern(P, Vt, St) -> pattern({var,_Line,'_'}, _Vt, _Old, _Bvt, St) -> {[],[],St}; %Ignore anonymous variable -pattern({var,Line,V}, _Vt, Old, Bvt, St) -> +pattern({var,Line,V}, _Vt, Old, Bvt, St) -> pat_var(V, Line, Old, Bvt, St); pattern({char,_Line,_C}, _Vt, _Old, _Bvt, St) -> {[],[],St}; pattern({integer,_Line,_I}, _Vt, _Old, _Bvt, St) -> {[],[],St}; @@ -1297,7 +1422,7 @@ pattern({tuple,_Line,Ps}, Vt, Old, Bvt, St) -> %%pattern({struct,_Line,_Tag,Ps}, Vt, Old, Bvt, St) -> %% pattern_list(Ps, Vt, Old, Bvt, St); pattern({record_index,Line,Name,Field}, _Vt, _Old, _Bvt, St) -> - {Vt1,St1} = + {Vt1,St1} = check_record(Line, Name, St, fun (Dfs, St1) -> pattern_field(Field, Name, Dfs, St1) @@ -1312,7 +1437,7 @@ pattern({record_field,Line,_,_}=M, _Vt, _Old, _Bvt, St0) -> end; pattern({record,Line,Name,Pfs}, Vt, Old, Bvt, St) -> case dict:find(Name, St#lint.records) of - {ok,{_Line,Fields}} -> + {ok,{_Line,Fields}} -> St1 = used_record(Name, St), pattern_fields(Pfs, Name, Fields, Vt, Old, Bvt, St1); error -> {[],[],add_error(Line, {undefined_record,Name}, St)} @@ -1372,7 +1497,7 @@ reject_bin_alias({cons,_,H1,T1}, {cons,_,H2,T2}, St0) -> reject_bin_alias(T1, T2, St); reject_bin_alias({tuple,_,Es1}, {tuple,_,Es2}, St) -> reject_bin_alias_list(Es1, Es2, St); -reject_bin_alias({record,_,Name1,Pfs1}, {record,_,Name2,Pfs2}, +reject_bin_alias({record,_,Name1,Pfs1}, {record,_,Name2,Pfs2}, #lint{records=Recs}=St) -> case {dict:find(Name1, Recs),dict:find(Name2, Recs)} of {{ok,{_Line1,Fields1}},{ok,{_Line2,Fields2}}} -> @@ -1454,7 +1579,7 @@ is_pattern_expr_1({op,_Line,Op,A1,A2}) -> erl_internal:arith_op(Op, 2) andalso all(fun is_pattern_expr/1, [A1,A2]); is_pattern_expr_1(_Other) -> false. -%% pattern_bin([Element], VarTable, Old, BinVarTable, State) -> +%% pattern_bin([Element], VarTable, Old, BinVarTable, State) -> %% {UpdVarTable,UpdBinVarTable,State}. %% Check a pattern group. BinVarTable are used binsize variables. @@ -1501,7 +1626,7 @@ good_string_size_type(default, Ts) -> end, Ts); good_string_size_type(_, _) -> false. -%% pat_bit_expr(Pattern, OldVarTable, BinVarTable,State) -> +%% pat_bit_expr(Pattern, OldVarTable, BinVarTable,State) -> %% {UpdVarTable,UpdBinVarTable,State}. %% Check pattern bit expression, only allow really valid patterns! @@ -1516,7 +1641,7 @@ pat_bit_expr(P, _Old, _Bvt, St) -> false -> {[],[],add_error(element(2, P), illegal_pattern, St)} end. -%% pat_bit_size(Size, VarTable, BinVarTable, State) -> +%% pat_bit_size(Size, VarTable, BinVarTable, State) -> %% {Value,UpdVarTable,UpdBinVarTable,State}. %% Check pattern size expression, only allow really valid sizes! @@ -1599,7 +1724,7 @@ bit_size_check(Line, Size, #bittype{type=Type,unit=Unit}, St) -> Sz = Unit * Size, %Total number of bits! St2 = elemtype_check(Line, Type, Sz, St), {Sz,St2}. - + elemtype_check(_Line, float, 32, St) -> St; elemtype_check(_Line, float, 64, St) -> St; elemtype_check(Line, float, _Size, St) -> @@ -1681,8 +1806,6 @@ gexpr({cons,_Line,H,T}, Vt, St) -> gexpr_list([H,T], Vt, St); gexpr({tuple,_Line,Es}, Vt, St) -> gexpr_list(Es, Vt, St); -%%gexpr({struct,_Line,_Tag,Es}, Vt, St) -> -%% gexpr_list(Es, Vt, St); gexpr({record_index,Line,Name,Field}, _Vt, St) -> check_record(Line, Name, St, fun (Dfs, St1) -> record_field(Field, Name, Dfs, St1) end ); @@ -1713,7 +1836,7 @@ gexpr({call,_Line,{atom,_Lr,is_record},[E,{atom,Ln,Name}]}, Vt, St0) -> gexpr({call,Line,{atom,_Lr,is_record},[E,R]}, Vt, St0) -> {Asvt,St1} = gexpr_list([E,R], Vt, St0), {Asvt,add_error(Line, illegal_guard_expr, St1)}; -gexpr({call,Line,{remote,_Lr,{atom,_Lm,erlang},{atom,Lf,is_record}},[E,A]}, +gexpr({call,Line,{remote,_Lr,{atom,_Lm,erlang},{atom,Lf,is_record}},[E,A]}, Vt, St0) -> gexpr({call,Line,{atom,Lf,is_record},[E,A]}, Vt, St0); gexpr({call,_Line,{atom,_Lr,is_record},[E,{atom,_,_Name},{integer,_,_}]}, @@ -1728,14 +1851,22 @@ gexpr({call,Line,{remote,_,{atom,_,erlang},{atom,_,is_record}=Isr},[_,_,_]=Args} gexpr({call,Line,{atom,_La,F},As}, Vt, St0) -> {Asvt,St1} = gexpr_list(As, Vt, St0), A = length(As), - case erl_internal:guard_bif(F, A) of + %% BifClash - Function called in guard + case erl_internal:guard_bif(F, A) andalso no_guard_bif_clash(St1,{F,A}) of true -> %% Also check that it is auto-imported. case erl_internal:bif(F, A) of true -> {Asvt,St1}; false -> {Asvt,add_error(Line, {explicit_export,F,A}, St1)} end; - false -> {Asvt,add_error(Line, illegal_guard_expr, St1)} + false -> + case is_local_function(St1#lint.locals,{F,A}) orelse + is_imported_function(St1#lint.imports,{F,A}) of + true -> + {Asvt,add_error(Line, {illegal_guard_local_call,{F,A}}, St1)}; + _ -> + {Asvt,add_error(Line, illegal_guard_expr, St1)} + end end; gexpr({call,Line,{remote,_Lr,{atom,_Lm,erlang},{atom,_Lf,F}},As}, Vt, St0) -> {Asvt,St1} = gexpr_list(As, Vt, St0), @@ -1774,13 +1905,16 @@ gexpr_list(Es, Vt, St) -> %% is_guard_test(Expression) -> boolean(). %% Test if a general expression is a guard test. +-spec is_guard_test(Expr) -> boolean() when + Expr :: erl_parse:abstract_expr(). + is_guard_test(E) -> is_guard_test2(E, dict:new()). %% is_guard_test(Expression, Forms) -> boolean(). is_guard_test(Expression, Forms) -> RecordAttributes = [A || A = {attribute, _, record, _D} <- Forms], - St0 = foldl(fun(Attr0, St1) -> + St0 = foldl(fun(Attr0, St1) -> Attr = zip_file_and_line(Attr0, "none"), attribute_state(Attr, St1) end, start(), RecordAttributes), @@ -1801,7 +1935,7 @@ is_guard_test2(G, RDs) -> %% is_guard_expr(Expression) -> boolean(). %% Test if an expression is a guard expression. -is_guard_expr(E) -> is_gexpr(E, []). +is_guard_expr(E) -> is_gexpr(E, []). is_gexpr({var,_L,_V}, _RDs) -> true; is_gexpr({char,_L,_C}, _RDs) -> true; @@ -1823,7 +1957,7 @@ is_gexpr({record_field,_L,Rec,_Name,Field}, RDs) -> is_gexpr({record,L,Name,Inits}, RDs) -> is_gexpr_fields(Inits, L, Name, RDs); is_gexpr({bin,_L,Fs}, RDs) -> - all(fun ({bin_element,_Line,E,Sz,_Ts}) -> + all(fun ({bin_element,_Line,E,Sz,_Ts}) -> is_gexpr(E, RDs) and (Sz =:= default orelse is_gexpr(Sz, RDs)) end, Fs); is_gexpr({call,_L,{atom,_Lf,F},As}, RDs) -> @@ -1898,15 +2032,13 @@ expr({bc,_Line,E,Qs}, Vt0, St0) -> {vtold(Vt,Vt0),St}; %Don't export local variables expr({tuple,_Line,Es}, Vt, St) -> expr_list(Es, Vt, St); -%%expr({struct,Line,Tag,Es}, Vt, St) -> -%% expr_list(Es, Vt, St); expr({record_index,Line,Name,Field}, _Vt, St) -> check_record(Line, Name, St, fun (Dfs, St1) -> record_field(Field, Name, Dfs, St1) end); expr({record,Line,Name,Inits}, Vt, St) -> check_record(Line, Name, St, - fun (Dfs, St1) -> - init_fields(Inits, Line, Name, Dfs, Vt, St1) + fun (Dfs, St1) -> + init_fields(Inits, Line, Name, Dfs, Vt, St1) end); expr({record_field,Line,_,_}=M, _Vt, St0) -> case expand_package(M, St0) of @@ -1943,8 +2075,6 @@ expr({'case',Line,E,Cs}, Vt, St0) -> {Evt,St1} = expr(E, Vt, St0), {Cvt,St2} = icrt_clauses(Cs, {'case',Line}, vtupdate(Evt, Vt), St1), {vtmerge(Evt, Cvt),St2}; -expr({'cond',Line,Cs}, Vt, St) -> - cond_clauses(Cs,{'cond',Line}, Vt, St); expr({'receive',Line,Cs}, Vt, St) -> icrt_clauses(Cs, {'receive',Line}, Vt, St); expr({'receive',Line,Cs,To,ToEs}, Vt, St0) -> @@ -1963,8 +2093,11 @@ expr({'fun',Line,Body}, Vt, St) -> {Bvt, St1} = fun_clauses(Cs, Vt, St), {vtupdate(Bvt, Vt), St1}; {function,F,A} -> + %% BifClash - Fun expression %% N.B. Only allows BIFs here as well, NO IMPORTS!! - case erl_internal:bif(F, A) of + case ((not is_local_function(St#lint.locals,{F,A})) andalso + (erl_internal:bif(F, A) andalso + (not is_autoimport_suppressed(St#lint.no_auto,{F,A})))) of true -> {[],St}; false -> {[],call_function(Line, F, A, St)} end; @@ -1974,7 +2107,7 @@ expr({'fun',Line,Body}, Vt, St) -> expr({call,_Line,{atom,_Lr,is_record},[E,{atom,Ln,Name}]}, Vt, St0) -> {Rvt,St1} = expr(E, Vt, St0), {Rvt,exist_record(Ln, Name, St1)}; -expr({call,Line,{remote,_Lr,{atom,_Lm,erlang},{atom,Lf,is_record}},[E,A]}, +expr({call,Line,{remote,_Lr,{atom,_Lm,erlang},{atom,Lf,is_record}},[E,A]}, Vt, St0) -> expr({call,Line,{atom,Lf,is_record},[E,A]}, Vt, St0); expr({call,L,{tuple,Lt,[{atom,Lm,erlang},{atom,Lf,is_record}]},As}, Vt, St) -> @@ -1997,29 +2130,54 @@ expr({call,Line,{atom,La,F},As}, Vt, St0) -> St1 = keyword_warning(La, F, St0), {Asvt,St2} = expr_list(As, Vt, St1), A = length(As), - case erl_internal:bif(F, A) of + IsLocal = is_local_function(St2#lint.locals,{F,A}), + IsAutoBif = erl_internal:bif(F, A), + AutoSuppressed = is_autoimport_suppressed(St2#lint.no_auto,{F,A}), + Warn = is_warn_enabled(bif_clash, St2) and (not bif_clash_specifically_disabled(St2,{F,A})), + Imported = imported(F, A, St2), + case ((not IsLocal) andalso (Imported =:= no) andalso + IsAutoBif andalso (not AutoSuppressed)) of true -> St3 = deprecated_function(Line, erlang, F, As, St2), - {Asvt,case is_warn_enabled(bif_clash, St3) andalso - is_bif_clash(F, A, St3) of - false -> - St3; - true -> - add_error(Line, {call_to_redefined_bif,{F,A}}, St3) - end}; + {Asvt,St3}; false -> - {Asvt,case imported(F, A, St2) of + {Asvt,case Imported of {yes,M} -> St3 = check_remote_function(Line, M, F, As, St2), U0 = St3#lint.usage, Imp = ordsets:add_element({{F,A},M},U0#usage.imported), St3#lint{usage=U0#usage{imported = Imp}}; no -> - case {F,A} of - {record_info,2} -> + case {F,A} of + {record_info,2} -> check_record_info_call(Line,La,As,St2); - N when N =:= St2#lint.func -> St2; - _ -> call_function(Line, F, A, St2) + N -> + %% BifClash - function call + %% Issue these warnings/errors even if it's a recursive call + St3 = if + (not AutoSuppressed) andalso IsAutoBif andalso Warn -> + case erl_internal:old_bif(F,A) of + true -> + add_error + (Line, + {call_to_redefined_old_bif, {F,A}}, + St2); + false -> + add_warning + (Line, + {call_to_redefined_bif, {F,A}}, + St2) + end; + true -> + St2 + end, + %% ...but don't lint recursive calls + if + N =:= St3#lint.func -> + St3; + true -> + call_function(Line, F, A, St3) + end end end} end; @@ -2160,7 +2318,7 @@ def_fields(Fs0, Name, St0) -> foldl(fun ({record_field,Lf,{atom,La,F},V}, {Fs,St}) -> case exist_field(F, Fs) of true -> {Fs,add_error(Lf, {redefine_field,Name,F}, St)}; - false -> + false -> St1 = St#lint{recdef_top = true}, {_,St2} = expr(V, [], St1), %% Warnings and errors found are kept, but @@ -2311,7 +2469,7 @@ init_fields(Ifs, Line, Name, Dfs, Vt0, St0) -> Defs = init_fields(Ifs, Line, Dfs), {_,St2} = check_fields(Defs, Name, Dfs, Vt1, St1, fun expr/3), {Vt1,St1#lint{usage = St2#lint.usage}}. - + ginit_fields(Ifs, Line, Name, Dfs, Vt0, St0) -> {Vt1,St1} = check_fields(Ifs, Name, Dfs, Vt0, St0, fun gexpr/3), Defs = init_fields(Ifs, Line, Dfs), @@ -2321,7 +2479,7 @@ ginit_fields(Ifs, Line, Name, Dfs, Vt0, St0) -> IllErrs = [E || {_File,{_Line,erl_lint,illegal_guard_expr}}=E <- Errors], St4 = St1#lint{usage = Usage, errors = IllErrs ++ St1#lint.errors}, {Vt1,St4}. - + %% Default initializations to be carried out init_fields(Ifs, Line, Dfs) -> [ {record_field,Lf,{atom,La,F},copy_expr(Di, Line)} || @@ -2399,7 +2557,7 @@ check_type({ann_type, _L, [_Var, Type]}, SeenVars, St) -> check_type(Type, SeenVars, St); check_type({paren_type, _L, [Type]}, SeenVars, St) -> check_type(Type, SeenVars, St); -check_type({remote_type, L, [{atom, _, Mod}, {atom, _, Name}, Args]}, +check_type({remote_type, L, [{atom, _, Mod}, {atom, _, Name}, Args]}, SeenVars, #lint{module=CurrentMod} = St) -> St1 = case (dict:is_key({Name, length(Args)}, default_types()) @@ -2437,7 +2595,7 @@ check_type({type, L, 'fun', [Dom, Range]}, SeenVars, St) -> check_type({type, -1, product, [Dom, Range]}, SeenVars, St1); check_type({type, L, range, [From, To]}, SeenVars, St) -> St1 = - case {From, To} of + case {erl_eval:partial_eval(From), erl_eval:partial_eval(To)} of {{integer, _, X}, {integer, _, Y}} when X < Y -> St; _ -> add_error(L, {type_syntax, range}, St) end, @@ -2446,8 +2604,8 @@ check_type({type, _L, tuple, any}, SeenVars, St) -> {SeenVars, St}; check_type({type, _L, any}, SeenVars, St) -> {SeenVars, St}; check_type({type, L, binary, [Base, Unit]}, SeenVars, St) -> St1 = - case {Base, Unit} of - {{integer, _, BaseVal}, + case {erl_eval:partial_eval(Base), erl_eval:partial_eval(Unit)} of + {{integer, _, BaseVal}, {integer, _, UnitVal}} when BaseVal >= 0, UnitVal >= 0 -> St; _ -> add_error(L, {type_syntax, binary}, St) end, @@ -2472,7 +2630,13 @@ check_type({type, La, TypeName, Args}, SeenVars, #lint{usage=Usage} = St) -> UsedTypes = dict:store({TypeName, Arity}, La, OldUsed), St#lint{usage=Usage#usage{used_types=UsedTypes}} end, - check_type({type, -1, product, Args}, SeenVars, St1). + check_type({type, -1, product, Args}, SeenVars, St1); +check_type(I, SeenVars, St) -> + case erl_eval:partial_eval(I) of + {integer,_ILn,_Integer} -> {SeenVars, St}; + _Other -> + {SeenVars, add_error(element(2, I), {type_syntax, integer}, St)} + end. check_record_types(Line, Name, Fields, SeenVars, St) -> case dict:find(Name, St#lint.records) of @@ -2480,12 +2644,12 @@ check_record_types(Line, Name, Fields, SeenVars, St) -> case lists:all(fun({type, _, field_type, _}) -> true; (_) -> false end, Fields) of - true -> + true -> check_record_types(Fields, Name, DefFields, SeenVars, St, []); false -> {SeenVars, add_error(Line, {type_syntax, record}, St)} end; - error -> + error -> {SeenVars, add_error(Line, {undefined_record, Name}, St)} end. @@ -2568,7 +2732,6 @@ default_types() -> {set, 0}, {string, 0}, {term, 0}, - {tid, 0}, {timeout, 0}, {var, 1}], dict:from_list([{T, -1} || T <- DefTypes]). @@ -2590,7 +2753,6 @@ is_newly_introduced_builtin_type({gb_tree, 0}) -> true; % opaque is_newly_introduced_builtin_type({iodata, 0}) -> true; is_newly_introduced_builtin_type({queue, 0}) -> true; % opaque is_newly_introduced_builtin_type({set, 0}) -> true; % opaque -is_newly_introduced_builtin_type({tid, 0}) -> true; % opaque %% R13B01 is_newly_introduced_builtin_type({boolean, 0}) -> true; is_newly_introduced_builtin_type({Name, _}) when is_atom(Name) -> false. @@ -2611,7 +2773,7 @@ spec_decl(Line, MFA0, TypeSpecs, St0 = #lint{specs = Specs, module = Mod}) -> check_specs([FunType|Left], Arity, St0) -> {FunType1, CTypes} = case FunType of - {type, _, bounded_fun, [FT = {type, _, 'fun', _}, Cs]} -> + {type, _, bounded_fun, [FT = {type, _, 'fun', _}, Cs]} -> Types0 = [T || {type, _, constraint, [_, T]} <- Cs], {FT, lists:append(Types0)}; {type, _, 'fun', _} = FT -> {FT, []} @@ -2671,10 +2833,12 @@ add_missing_spec_warnings(Forms, St0, Type) -> add_warning(L, {missing_spec,FA}, St) end, St0, Warns). -check_unused_types(Forms, St = #lint{usage=Usage, types=Types}) -> +check_unused_types(Forms, #lint{usage=Usage, types=Ts, exp_types=ExpTs}=St) -> case [File || {attribute,_L,file,{File,_Line}} <- Forms] of [FirstFile|_] -> - UsedTypes = Usage#usage.used_types, + D = Usage#usage.used_types, + L = gb_sets:to_list(ExpTs) ++ dict:fetch_keys(D), + UsedTypes = gb_sets:from_list(L), FoldFun = fun(_Type, -1, AccSt) -> %% Default type @@ -2682,19 +2846,18 @@ check_unused_types(Forms, St = #lint{usage=Usage, types=Types}) -> (Type, FileLine, AccSt) -> case loc(FileLine) of {FirstFile, _} -> - case dict:is_key(Type, UsedTypes) of + case gb_sets:is_member(Type, UsedTypes) of true -> AccSt; - false -> - add_warning(FileLine, - {unused_type, Type}, - AccSt) + false -> + Warn = {unused_type,Type}, + add_warning(FileLine, Warn, AccSt) end; _ -> - %% Don't warn about unused types in include file + %% No warns about unused types in include files AccSt end end, - dict:fold(FoldFun, St, Types); + dict:fold(FoldFun, St, Ts); [] -> St end. @@ -2720,45 +2883,6 @@ icrt_clause({clause,_Line,H,G,B}, Vt0, St0) -> {Bvt,St3} = exprs(B, Vt2, St2), {vtupdate(Bvt, Vt2),St3}. -%% The tests of 'cond' clauses are normal expressions - not guards. -%% Variables bound in a test is visible both in the corresponding body -%% and in the tests and bodies of subsequent clauses: a 'cond' is -%% *equivalent* to nested case-switches on boolean expressions. - -cond_clauses([C], In, Vt, St) -> - last_cond_clause(C, In, Vt, St); -cond_clauses([C | Cs], In, Vt, St) -> - cond_clause(C, Cs, In, Vt, St). - -%% see expr/3 for 'case' -cond_clause({clause,_L,[],[[E]],B}, Cs, In, Vt, St0) -> - {Evt,St1} = expr(E, Vt, St0), - {Cvt, St2} = cond_cases(B, Cs, In, vtupdate(Evt, Vt), St1), - Mvt = vtmerge(Evt, Cvt), - {Mvt,St2}. - -%% see icrt_clauses/4 -cond_cases(B, Cs, In, Vt, St0) -> - %% note that Vt is used for both cases - {Bvt,St1} = exprs(B, Vt, St0), % true case - Vt1 = vtupdate(Bvt, Vt), - {Cvt, St2} = cond_clauses(Cs, In, Vt, St1), % false case - Vt2 = vtupdate(Cvt, Vt), - %% and this also uses Vt - icrt_export([Vt1,Vt2], Vt, In, St2). - -%% last case must call icrt_export/4 with only one vartable -last_cond_clause({clause,_L,[],[[E]],B}, In, Vt, St0) -> - {Evt,St1} = expr(E, Vt, St0), - {Cvt, St2} = last_cond_case(B, In, vtupdate(Evt, Vt), St1), - Mvt = vtmerge(Evt, Cvt), - {Mvt,St2}. - -last_cond_case(B, In, Vt, St0) -> - {Bvt,St1} = exprs(B, Vt, St0), - Vt1 = vtupdate(Bvt, Vt), - icrt_export([Vt1], Vt, In, St1). - icrt_export(Csvt, Vt, In, St) -> Vt1 = vtmerge(Csvt), All = ordsets:subtract(vintersection(Csvt), vtnames(Vt)), @@ -2878,7 +3002,7 @@ fun_clause({clause,_Line,H,G,B}, Vt0, St0) -> %% %% used variable has been used %% unused variable has been bound but not used -%% +%% %% Lines is a list of line numbers where the variable was bound. %% %% Report variable errors/warnings as soon as possible and then change @@ -2908,9 +3032,9 @@ pat_var(V, Line, Vt, Bvt, St) -> case orddict:find(V, Bvt) of {ok, {bound,_Usage,Ls}} -> {[],[{V,{bound,used,Ls}}],St}; - error -> + error -> case orddict:find(V, Vt) of - {ok,{bound,_Usage,Ls}} -> + {ok,{bound,_Usage,Ls}} -> {[{V,{bound,used,Ls}}],[],St}; {ok,{{unsafe,In},_Usage,Ls}} -> {[{V,{bound,used,Ls}}],[], @@ -2963,7 +3087,7 @@ pat_binsize_var(V, Line, Vt, Bvt, St) -> expr_var(V, Line, Vt, St0) -> case orddict:find(V, Vt) of - {ok,{bound,_Usage,Ls}} -> + {ok,{bound,_Usage,Ls}} -> {[{V,{bound,used,Ls}}],St0}; {ok,{{unsafe,In},_Usage,Ls}} -> {[{V,{bound,used,Ls}}], @@ -3001,7 +3125,7 @@ check_old_unused_vars(Vt, Vt0, St0) -> warn_unused_vars(U, Vt, St0). unused_vars(Vt, Vt0, _St0) -> - U0 = orddict:filter(fun (V, {_State,unused,_Ls}) -> + U0 = orddict:filter(fun (V, {_State,unused,_Ls}) -> case atom_to_list(V) of "_"++_ -> false; _ -> true @@ -3017,7 +3141,7 @@ warn_unused_vars(U, Vt, St0) -> false -> St0; true -> foldl(fun ({V,{_,unused,Ls}}, St) -> - foldl(fun (L, St2) -> + foldl(fun (L, St2) -> add_warning(L, {unused_var,V}, St2) end, St, Ls) @@ -3117,7 +3241,7 @@ vt_no_unsafe(Vt) -> [V || {_,{S,_U,_L}}=V <- Vt, -ifdef(NOTUSED). vunion(Vs1, Vs2) -> ordsets:union(vtnames(Vs1), vtnames(Vs2)). -vunion(Vss) -> foldl(fun (Vs, Uvs) -> +vunion(Vss) -> foldl(fun (Vs, Uvs) -> ordsets:union(vtnames(Vs), Uvs) end, [], Vss). @@ -3147,7 +3271,7 @@ modify_line(T, F0) -> %% Forms. modify_line1({function,F,A}, _Mf) -> {function,F,A}; modify_line1({function,M,F,A}, _Mf) -> {function,M,F,A}; -modify_line1({attribute,L,record,{Name,Fields}}, Mf) -> +modify_line1({attribute,L,record,{Name,Fields}}, Mf) -> {attribute,Mf(L),record,{Name,modify_line1(Fields, Mf)}}; modify_line1({attribute,L,spec,{Fun,Types}}, Mf) -> {attribute,Mf(L),spec,{Fun,modify_line1(Types, Mf)}}; @@ -3162,7 +3286,7 @@ modify_line1({warning,W}, _Mf) -> {warning,W}; modify_line1({error,W}, _Mf) -> {error,W}; %% Expressions. modify_line1({clauses,Cs}, Mf) -> {clauses,modify_line1(Cs, Mf)}; -modify_line1({typed_record_field,Field,Type}, Mf) -> +modify_line1({typed_record_field,Field,Type}, Mf) -> {typed_record_field,modify_line1(Field, Mf),modify_line1(Type, Mf)}; modify_line1({Tag,L}, Mf) -> {Tag,Mf(L)}; modify_line1({Tag,L,E1}, Mf) -> @@ -3198,7 +3322,7 @@ check_record_info_call(Line,_La,_As,St) -> has_wildcard_field([{record_field,_Lf,{var,_La,'_'},_Val}|_Fs]) -> true; has_wildcard_field([_|Fs]) -> has_wildcard_field(Fs); has_wildcard_field([]) -> false. - + %% check_remote_function(Line, ModuleName, FuncName, [Arg], State) -> State. %% Perform checks on known remote calls. @@ -3214,7 +3338,7 @@ check_remote_function(Line, M, F, As, St0) -> check_qlc_hrl(Line, M, F, As, St) -> Arity = length(As), case As of - [{lc,_L,_E,_Qs}|_] when M =:= qlc, F =:= q, + [{lc,_L,_E,_Qs}|_] when M =:= qlc, F =:= q, Arity < 3, not St#lint.xqlc -> add_warning(Line, {missing_qlc_hrl, Arity}, St); _ -> @@ -3399,11 +3523,11 @@ extract_sequence(3, [$.,_|Fmt], Need) -> extract_sequence(4, Fmt, Need); extract_sequence(3, Fmt, Need) -> extract_sequence(4, Fmt, Need); -extract_sequence(4, [$t, $c | Fmt], Need) -> - extract_sequence(5, [$c|Fmt], Need); -extract_sequence(4, [$t, $s | Fmt], Need) -> - extract_sequence(5, [$s|Fmt], Need); -extract_sequence(4, [$t, C | _Fmt], _Need) -> +extract_sequence(4, [$t, $c | Fmt], Need) -> + extract_sequence(5, [$c|Fmt], Need); +extract_sequence(4, [$t, $s | Fmt], Need) -> + extract_sequence(5, [$s|Fmt], Need); +extract_sequence(4, [$t, C | _Fmt], _Need) -> {error,"invalid control ~t" ++ [C]}; extract_sequence(4, Fmt, Need) -> extract_sequence(5, Fmt, Need); @@ -3481,3 +3605,56 @@ expand_package(M, St0) -> {error, St1} end end. + + +%% Prebuild set of local functions (to override auto-import) +local_functions(Forms) -> + gb_sets:from_list([ {Func,Arity} || {function,_,Func,Arity,_} <- Forms ]). +%% Predicate to find out if the function is locally defined +is_local_function(LocalSet,{Func,Arity}) -> + gb_sets:is_element({Func,Arity},LocalSet). +%% Predicate to see if a function is explicitly imported +is_imported_function(ImportSet,{Func,Arity}) -> + case orddict:find({Func,Arity}, ImportSet) of + {ok,_Mod} -> true; + error -> false + end. +%% Predicate to see if a function is explicitly imported from the erlang module +is_imported_from_erlang(ImportSet,{Func,Arity}) -> + case orddict:find({Func,Arity}, ImportSet) of + {ok,erlang} -> true; + _ -> false + end. +%% Build set of functions where auto-import is explicitly supressed +auto_import_suppressed(CompileFlags) -> + L0 = [ X || {no_auto_import,X} <- CompileFlags ], + L1 = [ {Y,Z} || {Y,Z} <- lists:flatten(L0), is_atom(Y), is_integer(Z) ], + gb_sets:from_list(L1). +%% Predicate to find out if autoimport is explicitly supressed for a function +is_autoimport_suppressed(NoAutoSet,{Func,Arity}) -> + gb_sets:is_element({Func,Arity},NoAutoSet). +%% Predicate to find out if a function specific bif-clash supression (old deprecated) is present +bif_clash_specifically_disabled(St,{F,A}) -> + Nowarn = nowarn_function(nowarn_bif_clash, St#lint.compile), + lists:member({F,A},Nowarn). + +%% Predicate to find out if an autoimported guard_bif is not overriden in some way +%% Guard Bif without module name is disallowed if +%% * It is overridden by local function +%% * It is overridden by -import and that import is not of itself (i.e. from module erlang) +%% * The autoimport is suppressed or it's not reimported by -import directive +%% Otherwise it's OK (given that it's actually a guard bif and actually is autoimported) +no_guard_bif_clash(St,{F,A}) -> + ( + (not is_local_function(St#lint.locals,{F,A})) + andalso + ( + (not is_imported_function(St#lint.imports,{F,A})) orelse + is_imported_from_erlang(St#lint.imports,{F,A}) + ) + andalso + ( + (not is_autoimport_suppressed(St#lint.no_auto, {F,A})) orelse + is_imported_from_erlang(St#lint.imports,{F,A}) + ) + ). diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl index fd5d905797..bd5d65a1e1 100644 --- a/lib/stdlib/src/erl_parse.yrl +++ b/lib/stdlib/src/erl_parse.yrl @@ -1,20 +1,20 @@ %% -*- erlang -*- %% %% %CopyrightBegin% -%% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. -%% +%% +%% Copyright Ericsson AB 1996-2011. 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 %% compliance with the License. You should have received a copy of the %% Erlang Public License along with this software. If not, it can be %% retrieved online at http://www.erlang.org/. -%% +%% %% Software distributed under the License is distributed on an "AS IS" %% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See %% the License for the specific language governing rights and limitations %% under the License. -%% +%% %% %CopyrightEnd% %% @@ -30,14 +30,12 @@ expr_600 expr_700 expr_800 expr_900 expr_max list tail list_comprehension lc_expr lc_exprs -binary_comprehension +binary_comprehension tuple -atom1 %struct record_expr record_tuple record_field record_fields if_expr if_clause if_clauses case_expr cr_clause cr_clauses receive_expr fun_expr fun_clause fun_clauses -%% cond_expr cond_clause cond_clauses try_expr try_catch try_clause try_clauses query_expr function_call argument_list exprs guard @@ -49,22 +47,22 @@ opt_bit_size_expr bit_size_expr opt_bit_type_list bit_type_list bit_type top_type top_type_100 top_types type typed_expr typed_attr_val type_sig type_sigs type_guard type_guards fun_type fun_type_100 binary_type type_spec spec_fun typed_exprs typed_record_fields field_types field_type -bin_base_type bin_unit_type int_type. +bin_base_type bin_unit_type type_200 type_300 type_400 type_500. Terminals char integer float atom string var '(' ')' ',' '->' ':-' '{' '}' '[' ']' '|' '||' '<-' ';' ':' '#' '.' 'after' 'begin' 'case' 'try' 'catch' 'end' 'fun' 'if' 'of' 'receive' 'when' -'andalso' 'orelse' 'query' 'spec' -%% 'cond' +'andalso' 'orelse' 'query' 'bnot' 'not' '*' '/' 'div' 'rem' 'band' 'and' '+' '-' 'bor' 'bxor' 'bsl' 'bsr' 'or' 'xor' '++' '--' '==' '/=' '=<' '<' '>=' '>' '=:=' '=/=' '<=' '<<' '>>' -'!' '=' '::' +'!' '=' '::' '..' '...' +'spec' % helper dot. Expect 2. @@ -79,19 +77,16 @@ attribute -> '-' atom attr_val : build_attribute('$2', '$3'). attribute -> '-' atom typed_attr_val : build_typed_attribute('$2','$3'). attribute -> '-' atom '(' typed_attr_val ')' : build_typed_attribute('$2','$4'). attribute -> '-' 'spec' type_spec : build_type_spec('$2', '$3'). - -atom1 -> 'spec' : {atom, ?line('$1'), 'spec'}. -atom1 -> atom : '$1'. type_spec -> spec_fun type_sigs : {'$1', '$2'}. type_spec -> '(' spec_fun type_sigs ')' : {'$2', '$3'}. -spec_fun -> atom1 : '$1'. -spec_fun -> atom1 ':' atom1 : {'$1', '$3'}. +spec_fun -> atom : '$1'. +spec_fun -> atom ':' atom : {'$1', '$3'}. %% The following two are retained only for backwards compatibility; %% they are not part of the EEP syntax and should be removed. -spec_fun -> atom1 '/' integer '::' : {'$1', '$3'}. -spec_fun -> atom1 ':' atom1 '/' integer '::' : {'$1', '$3', '$5'}. +spec_fun -> atom '/' integer '::' : {'$1', '$3'}. +spec_fun -> atom ':' atom '/' integer '::' : {'$1', '$3', '$5'}. typed_attr_val -> expr ',' typed_record_fields : {typed_record, '$1', '$3'}. typed_attr_val -> expr '::' top_type : {type_def, '$1', '$3'}. @@ -109,14 +104,15 @@ type_sigs -> type_sig : ['$1']. type_sigs -> type_sig ';' type_sigs : ['$1'|'$3']. type_sig -> fun_type : '$1'. -type_sig -> fun_type 'when' type_guards : {type, ?line('$1'), bounded_fun, +type_sig -> fun_type 'when' type_guards : {type, ?line('$1'), bounded_fun, ['$1','$3']}. type_guards -> type_guard : ['$1']. type_guards -> type_guard ',' type_guards : ['$1'|'$3']. -type_guard -> atom1 '(' top_types ')' : {type, ?line('$1'), constraint, +type_guard -> atom '(' top_types ')' : {type, ?line('$1'), constraint, ['$1', '$3']}. +type_guard -> var '::' top_type : build_def('$1', '$3'). top_types -> top_type : ['$1']. top_types -> top_type ',' top_types : ['$1'|'$3']. @@ -124,58 +120,68 @@ top_types -> top_type ',' top_types : ['$1'|'$3']. top_type -> var '::' top_type_100 : {ann_type, ?line('$1'), ['$1','$3']}. top_type -> top_type_100 : '$1'. -top_type_100 -> type : '$1'. -top_type_100 -> type '|' top_type_100 : lift_unions('$1','$3'). +top_type_100 -> type_200 : '$1'. +top_type_100 -> type_200 '|' top_type_100 : lift_unions('$1','$3'). + +type_200 -> type_300 '..' type_300 : {type, ?line('$1'), range, + [skip_paren('$1'), + skip_paren('$3')]}. +type_200 -> type_300 : '$1'. + +type_300 -> type_300 add_op type_400 : ?mkop2(skip_paren('$1'), + '$2', skip_paren('$3')). +type_300 -> type_400 : '$1'. + +type_400 -> type_400 mult_op type_500 : ?mkop2(skip_paren('$1'), + '$2', skip_paren('$3')). +type_400 -> type_500 : '$1'. + +type_500 -> prefix_op type : ?mkop1('$1', skip_paren('$2')). +type_500 -> type : '$1'. type -> '(' top_type ')' : {paren_type, ?line('$2'), ['$2']}. type -> var : '$1'. -type -> atom1 : '$1'. -type -> atom1 '(' ')' : build_gen_type('$1'). -type -> atom1 '(' top_types ')' : {type, ?line('$1'), +type -> atom : '$1'. +type -> atom '(' ')' : build_gen_type('$1'). +type -> atom '(' top_types ')' : {type, ?line('$1'), normalise('$1'), '$3'}. -type -> atom1 ':' atom1 '(' ')' : {remote_type, ?line('$1'), +type -> atom ':' atom '(' ')' : {remote_type, ?line('$1'), ['$1', '$3', []]}. -type -> atom1 ':' atom1 '(' top_types ')' : {remote_type, ?line('$1'), +type -> atom ':' atom '(' top_types ')' : {remote_type, ?line('$1'), ['$1', '$3', '$5']}. type -> '[' ']' : {type, ?line('$1'), nil, []}. type -> '[' top_type ']' : {type, ?line('$1'), list, ['$2']}. -type -> '[' top_type ',' '.' '.' '.' ']' : {type, ?line('$1'), +type -> '[' top_type ',' '...' ']' : {type, ?line('$1'), nonempty_list, ['$2']}. type -> '{' '}' : {type, ?line('$1'), tuple, []}. type -> '{' top_types '}' : {type, ?line('$1'), tuple, '$2'}. -type -> '#' atom1 '{' '}' : {type, ?line('$1'), record, ['$2']}. -type -> '#' atom1 '{' field_types '}' : {type, ?line('$1'), +type -> '#' atom '{' '}' : {type, ?line('$1'), record, ['$2']}. +type -> '#' atom '{' field_types '}' : {type, ?line('$1'), record, ['$2'|'$4']}. type -> binary_type : '$1'. -type -> int_type : '$1'. -type -> int_type '.' '.' int_type : {type, ?line('$1'), range, - ['$1', '$4']}. +type -> integer : '$1'. type -> 'fun' '(' ')' : {type, ?line('$1'), 'fun', []}. type -> 'fun' '(' fun_type_100 ')' : '$3'. -int_type -> integer : '$1'. -int_type -> '-' integer : abstract(-normalise('$2'), - ?line('$2')). - -fun_type_100 -> '(' '.' '.' '.' ')' '->' top_type +fun_type_100 -> '(' '...' ')' '->' top_type : {type, ?line('$1'), 'fun', - [{type, ?line('$1'), any}, '$7']}. + [{type, ?line('$1'), any}, '$5']}. fun_type_100 -> fun_type : '$1'. fun_type -> '(' ')' '->' top_type : {type, ?line('$1'), 'fun', [{type, ?line('$1'), product, []}, '$4']}. -fun_type -> '(' top_types ')' '->' top_type +fun_type -> '(' top_types ')' '->' top_type : {type, ?line('$1'), 'fun', [{type, ?line('$1'), product, '$2'},'$5']}. field_types -> field_type : ['$1']. field_types -> field_type ',' field_types : ['$1'|'$3']. -field_type -> atom1 '::' top_type : {type, ?line('$1'), field_type, +field_type -> atom '::' top_type : {type, ?line('$1'), field_type, ['$1', '$3']}. -binary_type -> '<<' '>>' : {type, ?line('$1'),binary, - [abstract(0, ?line('$1')), +binary_type -> '<<' '>>' : {type, ?line('$1'),binary, + [abstract(0, ?line('$1')), abstract(0, ?line('$1'))]}. binary_type -> '<<' bin_base_type '>>' : {type, ?line('$1'),binary, ['$2', abstract(0, ?line('$1'))]}. @@ -184,9 +190,9 @@ binary_type -> '<<' bin_unit_type '>>' : {type, ?line('$1'),binary, binary_type -> '<<' bin_base_type ',' bin_unit_type '>>' : {type, ?line('$1'), binary, ['$2', '$4']}. -bin_base_type -> var ':' integer : build_bin_type(['$1'], '$3'). +bin_base_type -> var ':' type : build_bin_type(['$1'], '$3'). -bin_unit_type -> var ':' var '*' integer : build_bin_type(['$1', '$3'], '$5'). +bin_unit_type -> var ':' var '*' type : build_bin_type(['$1', '$3'], '$5'). attr_val -> expr : ['$1']. attr_val -> expr ',' exprs : ['$1' | '$3']. @@ -197,7 +203,7 @@ function -> function_clauses : build_function('$1'). function_clauses -> function_clause : ['$1']. function_clauses -> function_clause ';' function_clauses : ['$1'|'$3']. -function_clause -> atom1 clause_args clause_guard clause_body : +function_clause -> atom clause_args clause_guard clause_body : {clause,?line('$1'),element(3, '$1'),'$2','$3','$4'}. @@ -250,9 +256,9 @@ expr_800 -> expr_900 ':' expr_max : {remote,?line('$2'),'$1','$3'}. expr_800 -> expr_900 : '$1'. -expr_900 -> '.' atom1 : +expr_900 -> '.' atom : {record_field,?line('$1'),{atom,?line('$1'),''},'$2'}. -expr_900 -> expr_900 '.' atom1 : +expr_900 -> expr_900 '.' atom : {record_field,?line('$2'),'$1','$3'}. expr_900 -> expr_max : '$1'. @@ -270,7 +276,6 @@ expr_max -> if_expr : '$1'. expr_max -> case_expr : '$1'. expr_max -> receive_expr : '$1'. expr_max -> fun_expr : '$1'. -%%expr_max -> cond_expr : '$1'. expr_max -> try_expr : '$1'. expr_max -> query_expr : '$1'. @@ -304,8 +309,8 @@ opt_bit_type_list -> '$empty' : default. bit_type_list -> bit_type '-' bit_type_list : ['$1' | '$3']. bit_type_list -> bit_type : ['$1']. -bit_type -> atom1 : element(3,'$1'). -bit_type -> atom1 ':' integer : { element(3,'$1'), element(3,'$3') }. +bit_type -> atom : element(3,'$1'). +bit_type -> atom ':' integer : { element(3,'$1'), element(3,'$3') }. bit_size_expr -> expr_max : '$1'. @@ -325,7 +330,7 @@ tuple -> '{' '}' : {tuple,?line('$1'),[]}. tuple -> '{' exprs '}' : {tuple,?line('$1'),'$2'}. -%%struct -> atom1 tuple : +%%struct -> atom tuple : %% {struct,?line('$1'),element(3, '$1'),element(3, '$2')}. @@ -333,13 +338,17 @@ tuple -> '{' exprs '}' : {tuple,?line('$1'),'$2'}. %% N.B. Field names are returned as the complete object, even if they are %% always atoms for the moment, this might change in the future. -record_expr -> '#' atom1 '.' atom1 : +record_expr -> '#' atom '.' atom : {record_index,?line('$1'),element(3, '$2'),'$4'}. -record_expr -> '#' atom1 record_tuple : +record_expr -> '#' atom record_tuple : {record,?line('$1'),element(3, '$2'),'$3'}. -record_expr -> expr_max '#' atom1 '.' atom1 : +record_expr -> expr_max '#' atom '.' atom : + {record_field,?line('$2'),'$1',element(3, '$3'),'$5'}. +record_expr -> expr_max '#' atom record_tuple : + {record,?line('$2'),'$1',element(3, '$3'),'$4'}. +record_expr -> record_expr '#' atom '.' atom : {record_field,?line('$2'),'$1',element(3, '$3'),'$5'}. -record_expr -> expr_max '#' atom1 record_tuple : +record_expr -> record_expr '#' atom record_tuple : {record,?line('$2'),'$1',element(3, '$3'),'$4'}. record_tuple -> '{' '}' : []. @@ -349,7 +358,7 @@ record_fields -> record_field : ['$1']. record_fields -> record_field ',' record_fields : ['$1' | '$3']. record_field -> var '=' expr : {record_field,?line('$1'),'$1','$3'}. -record_field -> atom1 '=' expr : {record_field,?line('$1'),'$1','$3'}. +record_field -> atom '=' expr : {record_field,?line('$1'),'$1','$3'}. %% N.B. This is called from expr_700. @@ -383,9 +392,9 @@ receive_expr -> 'receive' cr_clauses 'after' expr clause_body 'end' : {'receive',?line('$1'),'$2','$4','$5'}. -fun_expr -> 'fun' atom1 '/' integer : +fun_expr -> 'fun' atom '/' integer : {'fun',?line('$1'),{function,element(3, '$2'),element(3, '$4')}}. -fun_expr -> 'fun' atom1 ':' atom1 '/' integer : +fun_expr -> 'fun' atom ':' atom '/' integer : {'fun',?line('$1'),{function,element(3, '$2'),element(3, '$4'),element(3,'$6')}}. fun_expr -> 'fun' fun_clauses 'end' : build_fun(?line('$1'), '$2'). @@ -415,21 +424,13 @@ try_clauses -> try_clause ';' try_clauses : ['$1' | '$3']. try_clause -> expr clause_guard clause_body : L = ?line('$1'), {clause,L,[{tuple,L,[{atom,L,throw},'$1',{var,L,'_'}]}],'$2','$3'}. -try_clause -> atom1 ':' expr clause_guard clause_body : +try_clause -> atom ':' expr clause_guard clause_body : L = ?line('$1'), {clause,L,[{tuple,L,['$1','$3',{var,L,'_'}]}],'$4','$5'}. try_clause -> var ':' expr clause_guard clause_body : L = ?line('$1'), {clause,L,[{tuple,L,['$1','$3',{var,L,'_'}]}],'$4','$5'}. -%%cond_expr -> 'cond' cond_clauses 'end' : {'cond',?line('$1'),'$2'}. - -%%cond_clauses -> cond_clause : ['$1']. -%%cond_clauses -> cond_clause ';' cond_clauses : ['$1' | '$3']. - -%%cond_clause -> expr clause_body : -%% {clause,?line('$1'),[],[['$1']],'$2'}. - query_expr -> 'query' list_comprehension 'end' : {'query',?line('$1'),'$2'}. @@ -447,7 +448,7 @@ guard -> exprs ';' guard : ['$1'|'$3']. atomic -> char : '$1'. atomic -> integer : '$1'. atomic -> float : '$1'. -atomic -> atom1 : '$1'. +atomic -> atom : '$1'. atomic -> strings : '$1'. strings -> string : '$1'. @@ -492,7 +493,7 @@ rule -> rule_clauses : build_rule('$1'). rule_clauses -> rule_clause : ['$1']. rule_clauses -> rule_clause ';' rule_clauses : ['$1'|'$3']. -rule_clause -> atom1 clause_args clause_guard rule_body : +rule_clause -> atom clause_args clause_guard rule_body : {clause,?line('$1'),element(3, '$1'),'$2','$3','$4'}. rule_body -> ':-' lc_exprs: '$2'. @@ -510,12 +511,21 @@ Erlang code. %% of the generated .erl file by the HiPE compiler. Please do not remove. -compile([{hipe,[{regalloc,linear_scan}]}]). +-export_type([abstract_clause/0, abstract_expr/0, abstract_form/0, + error_info/0]). + +-type abstract_clause() :: term(). +-type abstract_expr() :: term(). +-type abstract_form() :: term(). +-type error_description() :: term(). +-type error_info() :: {erl_scan:line(), module(), error_description()}. +-type token() :: {Tag :: atom(), Line :: erl_scan:line()}. %% mkop(Op, Arg) -> {op,Line,Op,Arg}. %% mkop(Left, Op, Right) -> {op,Line,Op,Left,Right}. --define(mkop2(L, OpPos, R), - begin +-define(mkop2(L, OpPos, R), + begin {Op,Pos} = OpPos, {op,Pos,Op,L,R} end). @@ -533,9 +543,19 @@ Erlang code. %% These really suck and are only here until Calle gets multiple %% entry points working. +-spec parse_form(Tokens) -> {ok, AbsForm} | {error, ErrorInfo} when + Tokens :: [token()], + AbsForm :: abstract_form(), + ErrorInfo :: error_info(). +parse_form([{'-',L1},{atom,L2,spec}|Tokens]) -> + parse([{'-',L1},{'spec',L2}|Tokens]); parse_form(Tokens) -> parse(Tokens). +-spec parse_exprs(Tokens) -> {ok, ExprList} | {error, ErrorInfo} when + Tokens :: [token()], + ExprList :: [abstract_expr()], + ErrorInfo :: error_info(). parse_exprs(Tokens) -> case parse([{atom,0,f},{'(',0},{')',0},{'->',0}|Tokens]) of {ok,{function,_Lf,f,0,[{clause,_Lc,[],[],Exprs}]}} -> @@ -543,6 +563,10 @@ parse_exprs(Tokens) -> {error,_} = Err -> Err end. +-spec parse_term(Tokens) -> {ok, Term} | {error, ErrorInfo} when + Tokens :: [token()], + Term :: term(), + ErrorInfo :: error_info(). parse_term(Tokens) -> case parse([{atom,0,f},{'(',0},{')',0},{'->',0}|Tokens]) of {ok,{function,_Lf,f,0,[{clause,_Lc,[],[],[Expr]}]}} -> @@ -559,7 +583,7 @@ parse_term(Tokens) -> -type attributes() :: 'export' | 'file' | 'import' | 'module' | 'opaque' | 'record' | 'type'. -build_typed_attribute({atom,La,record}, +build_typed_attribute({atom,La,record}, {typed_record, {atom,_Ln,RecordName}, RecTuple}) -> {attribute,La,record,{RecordName,record_tuple(RecTuple)}}; build_typed_attribute({atom,La,Attr}, @@ -582,7 +606,7 @@ build_typed_attribute({atom,La,Attr},_) -> build_type_spec({spec,La}, {SpecFun, TypeSpecs}) -> NewSpecFun = case SpecFun of - {atom, _, Fun} -> + {atom, _, Fun} -> {Fun, find_arity_from_specs(TypeSpecs)}; {{atom,_, Mod}, {atom,_, Fun}} -> {Mod,Fun,find_arity_from_specs(TypeSpecs)}; @@ -605,11 +629,20 @@ find_arity_from_specs([Spec|_]) -> {type, _, 'fun', [{type, _, product, Args},_]} = Fun, length(Args). +build_def(LHS, Types) -> + IsSubType = {atom, ?line(LHS), is_subtype}, + {type, ?line(LHS), constraint, [IsSubType, [LHS, Types]]}. + lift_unions(T1, {type, _La, union, List}) -> {type, ?line(T1), union, [T1|List]}; lift_unions(T1, T2) -> {type, ?line(T1), union, [T1, T2]}. +skip_paren({paren_type,_L,[Type]}) -> + skip_paren(Type); +skip_paren(Type) -> + Type. + build_gen_type({atom, La, tuple}) -> {type, La, tuple, any}; build_gen_type({atom, La, Name}) -> @@ -618,7 +651,7 @@ build_gen_type({atom, La, Name}) -> build_bin_type([{var, _, '_'}|Left], Int) -> build_bin_type(Left, Int); build_bin_type([], Int) -> - Int; + skip_paren(Int); build_bin_type([{var, La, _}|_], _) -> ret_err(La, "Bad binary type"). @@ -716,7 +749,7 @@ attribute_farity(Other) -> Other. attribute_farity_list(Args) -> [attribute_farity(A) || A <- Args]. - + -spec error_bad_decl(integer(), attributes()) -> no_return(). error_bad_decl(L, S) -> @@ -739,17 +772,39 @@ record_fields([{match,_Lm,{atom,La,A},Expr}|Fields]) -> [{record_field,La,{atom,La,A},Expr}|record_fields(Fields)]; record_fields([{typed,Expr,TypeInfo}|Fields]) -> [Field] = record_fields([Expr]), - TypeInfo1 = + TypeInfo1 = case Expr of {match, _, _, _} -> TypeInfo; %% If we have an initializer. - {atom, La, _} -> - lift_unions(abstract(undefined, La), TypeInfo) - end, + {atom, La, _} -> + case has_undefined(TypeInfo) of + false -> + TypeInfo2 = maybe_add_paren(TypeInfo), + lift_unions(abstract(undefined, La), TypeInfo2); + true -> + TypeInfo + end + end, [{typed_record_field,Field,TypeInfo1}|record_fields(Fields)]; record_fields([Other|_Fields]) -> ret_err(?line(Other), "bad record field"); record_fields([]) -> []. +has_undefined({atom,_,undefined}) -> + true; +has_undefined({ann_type,_,[_,T]}) -> + has_undefined(T); +has_undefined({paren_type,_,[T]}) -> + has_undefined(T); +has_undefined({type,_,union,Ts}) -> + lists:any(fun has_undefined/1, Ts); +has_undefined(_) -> + false. + +maybe_add_paren({ann_type,L,T}) -> + {paren_type,L,[{ann_type,L,T}]}; +maybe_add_paren(T) -> + T. + term(Expr) -> try normalise(Expr) catch _:_R -> ret_err(?line(Expr), "bad attribute") @@ -796,6 +851,7 @@ check_clauses(Cs, Name, Arity) -> build_try(L,Es,Scs,{Ccs,As}) -> {'try',L,Es,Scs,Ccs,As}. +-spec ret_err(_, _) -> no_return(). ret_err(L, S) -> {location,Location} = get_attribute(L, location), return_error(Location, S). @@ -812,10 +868,11 @@ mapl(F, [H|T]) -> mapl(_, []) -> []. -%% normalise(AbsTerm) -%% abstract(Term) %% Convert between the abstract form of a term and a term. +-spec normalise(AbsTerm) -> Data when + AbsTerm :: abstract_expr(), + Data :: term(). normalise({char,_,C}) -> C; normalise({integer,_,I}) -> I; normalise({float,_,F}) -> F; @@ -853,6 +910,9 @@ normalise_list([H|T]) -> normalise_list([]) -> []. +-spec abstract(Data) -> AbsTerm when + Data :: term(), + AbsTerm :: abstract_expr(). abstract(T) when is_integer(T) -> {integer,0,T}; abstract(T) when is_float(T) -> {float,0,T}; abstract(T) when is_atom(T) -> {atom,0,T}; @@ -921,13 +981,18 @@ abstract_list([H|T], Line) -> abstract_list([], _Line) -> []. -%% tokens(AbsTerm) -> [Token] -%% tokens(AbsTerm, More) -> [Token] %% Generate a list of tokens representing the abstract term. +-spec tokens(AbsTerm) -> Tokens when + AbsTerm :: abstract_expr(), + Tokens :: [token()]. tokens(Abs) -> tokens(Abs, []). +-spec tokens(AbsTerm, MoreTokens) -> Tokens when + AbsTerm :: abstract_expr(), + MoreTokens :: [token()], + Tokens :: [token()]. tokens({char,L,C}, More) -> [{char,L,C}|More]; tokens({integer,L,N}, More) -> [{integer,L,N}|More]; tokens({float,L,F}, More) -> [{float,L,F}|More]; @@ -989,7 +1054,7 @@ inop_prec('#') -> {800,700,800}; inop_prec(':') -> {900,800,900}; inop_prec('.') -> {900,900,1000}. --type pre_op() :: 'catch' | '+' | '-' | 'bnot' | '#'. +-type pre_op() :: 'catch' | '+' | '-' | 'bnot' | 'not' | '#'. -spec preop_prec(pre_op()) -> {0 | 600 | 700, 100 | 700 | 800}. diff --git a/lib/stdlib/src/erl_posix_msg.erl b/lib/stdlib/src/erl_posix_msg.erl index fe981b23a7..909cc1d102 100644 --- a/lib/stdlib/src/erl_posix_msg.erl +++ b/lib/stdlib/src/erl_posix_msg.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1997-2009. All Rights Reserved. +%% Copyright Ericsson AB 1997-2010. 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 @@ -24,143 +24,146 @@ -spec message(atom()) -> string(). -message(e2big) -> "argument list too long"; -message(eacces) -> "permission denied"; -message(eaddrinuse) -> "address already in use"; -message(eaddrnotavail) -> "can't assign requested address"; -message(eadv) -> "advertise error"; -message(eafnosupport) -> "address family not supported by protocol family"; -message(eagain) -> "resource temporarily unavailable"; -message(ealign) -> "EALIGN"; -message(ealready) -> "operation already in progress"; -message(ebade) -> "bad exchange descriptor"; -message(ebadf) -> "bad file number"; -message(ebadfd) -> "file descriptor in bad state"; -message(ebadmsg) -> "not a data message"; -message(ebadr) -> "bad request descriptor"; -message(ebadrpc) -> "RPC structure is bad"; -message(ebadrqc) -> "bad request code"; -message(ebadslt) -> "invalid slot"; -message(ebfont) -> "bad font file format"; -message(ebusy) -> "file busy"; -message(echild) -> "no children"; -message(echrng) -> "channel number out of range"; -message(ecomm) -> "communication error on send"; -message(econnaborted) -> "software caused connection abort"; -message(econnrefused) -> "connection refused"; -message(econnreset) -> "connection reset by peer"; -message(edeadlk) -> "resource deadlock avoided"; -message(edeadlock) -> "resource deadlock avoided"; -message(edestaddrreq) -> "destination address required"; -message(edirty) -> "mounting a dirty fs w/o force"; -message(edom) -> "math argument out of range"; -message(edotdot) -> "cross mount point"; -message(edquot) -> "disk quota exceeded"; -message(eduppkg) -> "duplicate package name"; -message(eexist) -> "file already exists"; -message(efault) -> "bad address in system call argument"; -message(efbig) -> "file too large"; -message(ehostdown) -> "host is down"; -message(ehostunreach) -> "host is unreachable"; -message(eidrm) -> "identifier removed"; -message(einit) -> "initialization error"; -message(einprogress) -> "operation now in progress"; -message(eintr) -> "interrupted system call"; -message(einval) -> "invalid argument"; -message(eio) -> "I/O error"; -message(eisconn) -> "socket is already connected"; -message(eisdir) -> "illegal operation on a directory"; -message(eisnam) -> "is a name file"; -message(elbin) -> "ELBIN"; -message(el2hlt) -> "level 2 halted"; -message(el2nsync) -> "level 2 not synchronized"; -message(el3hlt) -> "level 3 halted"; -message(el3rst) -> "level 3 reset"; -message(elibacc) -> "can not access a needed shared library"; -message(elibbad) -> "accessing a corrupted shared library"; -message(elibexec) -> "can not exec a shared library directly"; -message(elibmax) -> - "attempting to link in more shared libraries than system limit"; -message(elibscn) -> ".lib section in a.out corrupted"; -message(elnrng) -> "link number out of range"; -message(eloop) -> "too many levels of symbolic links"; -message(emfile) -> "too many open files"; -message(emlink) -> "too many links"; -message(emsgsize) -> "message too long"; -message(emultihop) -> "multihop attempted"; -message(enametoolong) -> "file name too long"; -message(enavail) -> "not available"; -message(enet) -> "ENET"; -message(enetdown) -> "network is down"; -message(enetreset) -> "network dropped connection on reset"; -message(enetunreach) -> "network is unreachable"; -message(enfile) -> "file table overflow"; -message(enoano) -> "anode table overflow"; -message(enobufs) -> "no buffer space available"; -message(enocsi) -> "no CSI structure available"; -message(enodata) -> "no data available"; -message(enodev) -> "no such device"; -message(enoent) -> "no such file or directory"; -message(enoexec) -> "exec format error"; -message(enolck) -> "no locks available"; -message(enolink) -> "link has be severed"; -message(enomem) -> "not enough memory"; -message(enomsg) -> "no message of desired type"; -message(enonet) -> "machine is not on the network"; -message(enopkg) -> "package not installed"; -message(enoprotoopt) -> "bad proocol option"; -message(enospc) -> "no space left on device"; -message(enosr) -> "out of stream resources or not a stream device"; -message(enosym) -> "unresolved symbol name"; -message(enosys) -> "function not implemented"; -message(enotblk) -> "block device required"; -message(enotconn) -> "socket is not connected"; -message(enotdir) -> "not a directory"; -message(enotempty) -> "directory not empty"; -message(enotnam) -> "not a name file"; -message(enotsock) -> "socket operation on non-socket"; -message(enotsup) -> "operation not supported"; -message(enotty) -> "inappropriate device for ioctl"; -message(enotuniq) -> "name not unique on network"; -message(enxio) -> "no such device or address"; -message(eopnotsupp) -> "operation not supported on socket"; -message(eperm) -> "not owner"; -message(epfnosupport) -> "protocol family not supported"; -message(epipe) -> "broken pipe"; -message(eproclim) -> "too many processes"; -message(eprocunavail) -> "bad procedure for program"; -message(eprogmismatch) -> "program version wrong"; -message(eprogunavail) -> "RPC program not available"; -message(eproto) -> "protocol error"; -message(eprotonosupport) -> "protocol not suppored"; -message(eprototype) -> "protocol wrong type for socket"; -message(erange) -> "math result unrepresentable"; -message(erefused) -> "EREFUSED"; -message(eremchg) -> "remote address changed"; -message(eremdev) -> "remote device"; -message(eremote) -> "pathname hit remote file system"; -message(eremoteio) -> "remote i/o error"; -message(eremoterelease) -> "EREMOTERELEASE"; -message(erofs) -> "read-only file system"; -message(erpcmismatch) -> "RPC version is wrong"; -message(erremote) -> "object is remote"; -message(eshutdown) -> "can't send after socket shutdown"; -message(esocktnosupport) -> "socket type not supported"; -message(espipe) -> "invalid seek"; -message(esrch) -> "no such process"; -message(esrmnt) -> "srmount error"; -message(estale) -> "stale remote file handle"; -message(esuccess) -> "Error 0"; -message(etime) -> "timer expired"; -message(etimedout) -> "connection timed out"; -message(etoomanyrefs) -> "too many references: can't splice"; -message(etxtbsy) -> "text file or pseudo-device busy"; -message(euclean) -> "structure needs cleaning"; -message(eunatch) -> "protocol driver not attached"; -message(eusers) -> "too many users"; -message(eversion) -> "version mismatch"; -message(ewouldblock) -> "operation would block"; -message(exdev) -> "cross-domain link"; -message(exfull) -> "message tables full"; -message(nxdomain) -> "non-existing domain"; -message(_) -> "unknown POSIX error". +message(T) -> + binary_to_list(message_1(T)). + +message_1(e2big) -> <<"argument list too long">>; +message_1(eacces) -> <<"permission denied">>; +message_1(eaddrinuse) -> <<"address already in use">>; +message_1(eaddrnotavail) -> <<"can't assign requested address">>; +message_1(eadv) -> <<"advertise error">>; +message_1(eafnosupport) -> <<"address family not supported by protocol family">>; +message_1(eagain) -> <<"resource temporarily unavailable">>; +message_1(ealign) -> <<"EALIGN">>; +message_1(ealready) -> <<"operation already in progress">>; +message_1(ebade) -> <<"bad exchange descriptor">>; +message_1(ebadf) -> <<"bad file number">>; +message_1(ebadfd) -> <<"file descriptor in bad state">>; +message_1(ebadmsg) -> <<"not a data message">>; +message_1(ebadr) -> <<"bad request descriptor">>; +message_1(ebadrpc) -> <<"RPC structure is bad">>; +message_1(ebadrqc) -> <<"bad request code">>; +message_1(ebadslt) -> <<"invalid slot">>; +message_1(ebfont) -> <<"bad font file format">>; +message_1(ebusy) -> <<"file busy">>; +message_1(echild) -> <<"no children">>; +message_1(echrng) -> <<"channel number out of range">>; +message_1(ecomm) -> <<"communication error on send">>; +message_1(econnaborted) -> <<"software caused connection abort">>; +message_1(econnrefused) -> <<"connection refused">>; +message_1(econnreset) -> <<"connection reset by peer">>; +message_1(edeadlk) -> <<"resource deadlock avoided">>; +message_1(edeadlock) -> <<"resource deadlock avoided">>; +message_1(edestaddrreq) -> <<"destination address required">>; +message_1(edirty) -> <<"mounting a dirty fs w/o force">>; +message_1(edom) -> <<"math argument out of range">>; +message_1(edotdot) -> <<"cross mount point">>; +message_1(edquot) -> <<"disk quota exceeded">>; +message_1(eduppkg) -> <<"duplicate package name">>; +message_1(eexist) -> <<"file already exists">>; +message_1(efault) -> <<"bad address in system call argument">>; +message_1(efbig) -> <<"file too large">>; +message_1(ehostdown) -> <<"host is down">>; +message_1(ehostunreach) -> <<"host is unreachable">>; +message_1(eidrm) -> <<"identifier removed">>; +message_1(einit) -> <<"initialization error">>; +message_1(einprogress) -> <<"operation now in progress">>; +message_1(eintr) -> <<"interrupted system call">>; +message_1(einval) -> <<"invalid argument">>; +message_1(eio) -> <<"I/O error">>; +message_1(eisconn) -> <<"socket is already connected">>; +message_1(eisdir) -> <<"illegal operation on a directory">>; +message_1(eisnam) -> <<"is a name file">>; +message_1(elbin) -> <<"ELBIN">>; +message_1(el2hlt) -> <<"level 2 halted">>; +message_1(el2nsync) -> <<"level 2 not synchronized">>; +message_1(el3hlt) -> <<"level 3 halted">>; +message_1(el3rst) -> <<"level 3 reset">>; +message_1(elibacc) -> <<"can not access a needed shared library">>; +message_1(elibbad) -> <<"accessing a corrupted shared library">>; +message_1(elibexec) -> <<"can not exec a shared library directly">>; +message_1(elibmax) -> + <<"attempting to link in more shared libraries than system limit">>; +message_1(elibscn) -> <<".lib section in a.out corrupted">>; +message_1(elnrng) -> <<"link number out of range">>; +message_1(eloop) -> <<"too many levels of symbolic links">>; +message_1(emfile) -> <<"too many open files">>; +message_1(emlink) -> <<"too many links">>; +message_1(emsgsize) -> <<"message too long">>; +message_1(emultihop) -> <<"multihop attempted">>; +message_1(enametoolong) -> <<"file name too long">>; +message_1(enavail) -> <<"not available">>; +message_1(enet) -> <<"ENET">>; +message_1(enetdown) -> <<"network is down">>; +message_1(enetreset) -> <<"network dropped connection on reset">>; +message_1(enetunreach) -> <<"network is unreachable">>; +message_1(enfile) -> <<"file table overflow">>; +message_1(enoano) -> <<"anode table overflow">>; +message_1(enobufs) -> <<"no buffer space available">>; +message_1(enocsi) -> <<"no CSI structure available">>; +message_1(enodata) -> <<"no data available">>; +message_1(enodev) -> <<"no such device">>; +message_1(enoent) -> <<"no such file or directory">>; +message_1(enoexec) -> <<"exec format error">>; +message_1(enolck) -> <<"no locks available">>; +message_1(enolink) -> <<"link has be severed">>; +message_1(enomem) -> <<"not enough memory">>; +message_1(enomsg) -> <<"no message of desired type">>; +message_1(enonet) -> <<"machine is not on the network">>; +message_1(enopkg) -> <<"package not installed">>; +message_1(enoprotoopt) -> <<"bad proocol option">>; +message_1(enospc) -> <<"no space left on device">>; +message_1(enosr) -> <<"out of stream resources or not a stream device">>; +message_1(enosym) -> <<"unresolved symbol name">>; +message_1(enosys) -> <<"function not implemented">>; +message_1(enotblk) -> <<"block device required">>; +message_1(enotconn) -> <<"socket is not connected">>; +message_1(enotdir) -> <<"not a directory">>; +message_1(enotempty) -> <<"directory not empty">>; +message_1(enotnam) -> <<"not a name file">>; +message_1(enotsock) -> <<"socket operation on non-socket">>; +message_1(enotsup) -> <<"operation not supported">>; +message_1(enotty) -> <<"inappropriate device for ioctl">>; +message_1(enotuniq) -> <<"name not unique on network">>; +message_1(enxio) -> <<"no such device or address">>; +message_1(eopnotsupp) -> <<"operation not supported on socket">>; +message_1(eperm) -> <<"not owner">>; +message_1(epfnosupport) -> <<"protocol family not supported">>; +message_1(epipe) -> <<"broken pipe">>; +message_1(eproclim) -> <<"too many processes">>; +message_1(eprocunavail) -> <<"bad procedure for program">>; +message_1(eprogmismatch) -> <<"program version wrong">>; +message_1(eprogunavail) -> <<"RPC program not available">>; +message_1(eproto) -> <<"protocol error">>; +message_1(eprotonosupport) -> <<"protocol not suppored">>; +message_1(eprototype) -> <<"protocol wrong type for socket">>; +message_1(erange) -> <<"math result unrepresentable">>; +message_1(erefused) -> <<"EREFUSED">>; +message_1(eremchg) -> <<"remote address changed">>; +message_1(eremdev) -> <<"remote device">>; +message_1(eremote) -> <<"pathname hit remote file system">>; +message_1(eremoteio) -> <<"remote i/o error">>; +message_1(eremoterelease) -> <<"EREMOTERELEASE">>; +message_1(erofs) -> <<"read-only file system">>; +message_1(erpcmismatch) -> <<"RPC version is wrong">>; +message_1(erremote) -> <<"object is remote">>; +message_1(eshutdown) -> <<"can't send after socket shutdown">>; +message_1(esocktnosupport) -> <<"socket type not supported">>; +message_1(espipe) -> <<"invalid seek">>; +message_1(esrch) -> <<"no such process">>; +message_1(esrmnt) -> <<"srmount error">>; +message_1(estale) -> <<"stale remote file handle">>; +message_1(esuccess) -> <<"Error 0">>; +message_1(etime) -> <<"timer expired">>; +message_1(etimedout) -> <<"connection timed out">>; +message_1(etoomanyrefs) -> <<"too many references: can't splice">>; +message_1(etxtbsy) -> <<"text file or pseudo-device busy">>; +message_1(euclean) -> <<"structure needs cleaning">>; +message_1(eunatch) -> <<"protocol driver not attached">>; +message_1(eusers) -> <<"too many users">>; +message_1(eversion) -> <<"version mismatch">>; +message_1(ewouldblock) -> <<"operation would block">>; +message_1(exdev) -> <<"cross-domain link">>; +message_1(exfull) -> <<"message tables full">>; +message_1(nxdomain) -> <<"non-existing domain">>; +message_1(_) -> <<"unknown POSIX error">>. diff --git a/lib/stdlib/src/erl_pp.erl b/lib/stdlib/src/erl_pp.erl index b1b5bad294..7dc19f2e9b 100644 --- a/lib/stdlib/src/erl_pp.erl +++ b/lib/stdlib/src/erl_pp.erl @@ -1,19 +1,19 @@ %% %% %CopyrightBegin% -%% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. -%% +%% +%% Copyright Ericsson AB 1996-2011. 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 %% compliance with the License. You should have received a copy of the %% Erlang Public License along with this software. If not, it can be %% retrieved online at http://www.erlang.org/. -%% +%% %% Software distributed under the License is distributed on an "AS IS" %% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See %% the License for the specific language governing rights and limitations %% under the License. -%% +%% %% %CopyrightEnd% %% -module(erl_pp). @@ -31,25 +31,53 @@ -define(MAXLINE, 72). +-type(hook_function() :: none + | fun((Expr :: erl_parse:abstract_expr(), + CurrentIndentation :: integer(), + CurrentPrecedence :: non_neg_integer(), + HookFunction :: hook_function()) -> + io_lib:chars())). + %%% %%% Exported functions %%% +-spec(form(Form) -> io_lib:chars() when + Form :: erl_parse:abstract_form()). + form(Thing) -> form(Thing, none). +-spec(form(Form, HookFunction) -> io_lib:chars() when + Form :: erl_parse:abstract_form(), + HookFunction :: hook_function()). + form(Thing, Hook) -> frmt(lform(Thing, Hook)). +-spec(attribute(Attribute) -> io_lib:chars() when + Attribute :: erl_parse:abstract_form()). + attribute(Thing) -> attribute(Thing, none). +-spec(attribute(Attribute, HookFunction) -> io_lib:chars() when + Attribute :: erl_parse:abstract_form(), + HookFunction :: hook_function()). + attribute(Thing, Hook) -> frmt(lattribute(Thing, Hook)). +-spec(function(Function) -> io_lib:chars() when + Function :: erl_parse:abstract_form()). + function(F) -> function(F, none). +-spec(function(Function, HookFunction) -> io_lib:chars() when + Function :: erl_parse:abstract_form(), + HookFunction :: hook_function()). + function(F, Hook) -> frmt(lfunction(F, Hook)). @@ -59,30 +87,67 @@ rule(R) -> rule(R, Hook) -> frmt(lrule(R, Hook)). +-spec(guard(Guard) -> io_lib:chars() when + Guard :: [erl_parse:abstract_expr()]). + guard(Gs) -> guard(Gs, none). +-spec(guard(Guard, HookFunction) -> io_lib:chars() when + Guard :: [erl_parse:abstract_expr()], + HookFunction :: hook_function()). + guard(Gs, Hook) -> frmt(lguard(Gs, Hook)). +-spec(exprs(Expressions) -> io_lib:chars() when + Expressions :: [erl_parse:abstract_expr()]). + exprs(Es) -> exprs(Es, 0, none). +-spec(exprs(Expressions, HookFunction) -> io_lib:chars() when + Expressions :: [erl_parse:abstract_expr()], + HookFunction :: hook_function()). + exprs(Es, Hook) -> exprs(Es, 0, Hook). +-spec(exprs(Expressions, Indent, HookFunction) -> io_lib:chars() when + Expressions :: [erl_parse:abstract_expr()], + Indent :: integer(), + HookFunction :: hook_function()). + exprs(Es, I, Hook) -> frmt({seq,[],[],[$,],lexprs(Es, Hook)}, I). +-spec(expr(Expression) -> io_lib:chars() when + Expression :: erl_parse:abstract_expr()). + expr(E) -> frmt(lexpr(E, 0, none)). +-spec(expr(Expression, HookFunction) -> io_lib:chars() when + Expression :: erl_parse:abstract_expr(), + HookFunction :: hook_function()). + expr(E, Hook) -> frmt(lexpr(E, 0, Hook)). +-spec(expr(Expression, Indent, HookFunction) -> io_lib:chars() when + Expression :: erl_parse:abstract_expr(), + Indent :: integer(), + HookFunction :: hook_function()). + expr(E, I, Hook) -> frmt(lexpr(E, 0, Hook), I). +-spec(expr(Expression, Indent, Precedence, HookFunction) -> io_lib:chars() when + Expression :: erl_parse:abstract_expr(), + Indent :: integer(), + Precedence :: non_neg_integer(), + HookFunction :: hook_function()). + expr(E, I, P, Hook) -> frmt(lexpr(E, P, Hook), I). @@ -115,7 +180,7 @@ lattribute({attribute,_Line,Name,Arg}, Hook) -> lattribute(module, {M,Vs}, _Hook) -> attr("module",[{var,0,pname(M)}, - foldr(fun(V, C) -> {cons,0,{var,0,V},C} + foldr(fun(V, C) -> {cons,0,{var,0,V},C} end, {nil,0}, Vs)]); lattribute(module, M, _Hook) -> attr("module", [{var,0,pname(M)}]); @@ -140,7 +205,7 @@ typeattr(Tag, {TypeName,Type,Args}, _Hook) -> ltype({ann_type,_Line,[V,T]}) -> typed(lexpr(V, none), T); ltype({paren_type,_Line,[T]}) -> - [$(,ltype(T),$)]; + [$(,ltype(T),$)]; ltype({type,_Line,union,Ts}) -> {seq,[],[],[' |'],ltypes(Ts)}; ltype({type,_Line,list,[T]}) -> @@ -153,7 +218,7 @@ ltype({type,Line,tuple,any}) -> simple_type({atom,Line,tuple}, []); ltype({type,_Line,tuple,Ts}) -> tuple_type(Ts, fun ltype/1); -ltype({type,_Line,record,[N|Fs]}) -> +ltype({type,_Line,record,[{atom,_,N}|Fs]}) -> record_type(N, Fs); ltype({type,_Line,range,[_I1,_I2]=Es}) -> expr_list(Es, '..', fun lexpr/2, none); @@ -161,24 +226,28 @@ ltype({type,_Line,binary,[I1,I2]}) -> binary_type(I1, I2); % except binary() ltype({type,_Line,'fun',[]}) -> leaf("fun()"); -ltype({type,_Line,'fun',_}=FunType) -> +ltype({type,_,'fun',[{type,_,any},_]}=FunType) -> + [fun_type(['fun',$(], FunType),$)]; +ltype({type,_Line,'fun',[{type,_,product,_},_]}=FunType) -> [fun_type(['fun',$(], FunType),$)]; ltype({type,Line,T,Ts}) -> simple_type({atom,Line,T}, Ts); ltype({remote_type,Line,[M,F,Ts]}) -> simple_type({remote,Line,M,F}, Ts); ltype({atom,_,T}) -> - %% Follow the convention to always quote atoms (in types): - leaf([$',atom_to_list(T),$']); + leaf(write(T)); ltype(E) -> lexpr(E, 0, none). -binary_type({integer,_,Int1}=I1, {integer,_,Int2}=I2) -> - E1 = [[leaf("_:"),lexpr(I1, 0, none)] || Int1 =/= 0], - E2 = [[leaf("_:_*"),lexpr(I2, 0, none)] || Int2 =/= 0], +binary_type(I1, I2) -> + B = [[] || {integer,_,0} <- [I1]] =:= [], + U = [[] || {integer,_,0} <- [I2]] =:= [], + P = max_prec(), + E1 = [[leaf("_:"),lexpr(I1, P, none)] || B], + E2 = [[leaf("_:_*"),lexpr(I2, P, none)] || U], {seq,'<<','>>',[$,],E1++E2}. -record_type({atom,_,Name}, Fields) -> +record_type(Name, Fields) -> {first,[record_name(Name)],field_types(Fields)}. field_types(Fs) -> @@ -442,7 +511,7 @@ lexpr({op,_,Op,Arg}, Prec, Hook) -> Ol = leaf(format("~s ", [Op])), El = [Ol,lexpr(Arg, R, Hook)], maybe_paren(P, Prec, El); -lexpr({op,_,Op,Larg,Rarg}, Prec, Hook) when Op =:= 'orelse'; +lexpr({op,_,Op,Larg,Rarg}, Prec, Hook) when Op =:= 'orelse'; Op =:= 'andalso' -> %% Breaks lines since R12B. {L,P,R} = inop_prec(Op), @@ -554,17 +623,11 @@ record_field({typed_record_field,{record_field,_,F,Val},Type}, Hook) -> Fl = lexpr(F, L, Hook), Vl = typed(lexpr(Val, R, Hook), Type), {list,[{cstep,[Fl,' ='],Vl}]}; -record_field({typed_record_field,Field,Type0}, Hook) -> - Type = remove_undefined(Type0), +record_field({typed_record_field,Field,Type}, Hook) -> typed(record_field(Field, Hook), Type); record_field({record_field,_,F}, Hook) -> lexpr(F, 0, Hook). -remove_undefined({type,L,union,[{atom,_,undefined}|T]}) -> - {type,L,union,T}; -remove_undefined(T) -> % cannot happen - T. - list({cons,_,H,T}, Es, Hook) -> list(T, [H|Es], Hook); list({nil,_}, Es, Hook) -> @@ -726,15 +789,15 @@ frmt(Item, I) -> %%% and indentation are inserted between IPs. %%% - {first,I,IP2}: IP2 follows after I, and is output with an indentation %%% updated with the width of I. -%%% - {seq,Before,After,Separator,IPs}: a sequence of Is separated by -%%% Separator. Before is output before IPs, and the indentation of IPs +%%% - {seq,Before,After,Separator,IPs}: a sequence of Is separated by +%%% Separator. Before is output before IPs, and the indentation of IPs %%% is updated with the width of Before. After follows after IPs. %%% - {force_nl,ExtraInfo,I}: fun-info (a comment) forces linebreak before I. %%% - {prefer_nl,Sep,IPs}: forces linebreak between Is unlesss negative %%% indentation. %%% - {string,S}: a string. %%% - {hook,...}, {ehook,...}: hook expressions. -%%% +%%% %%% list, first, seq, force_nl, and prefer_nl all accept IPs, where each %%% element is either an item or a tuple {step|cstep,I1,I2}. step means %%% that I2 is output after linebreak and an incremented indentation. @@ -760,7 +823,7 @@ f({seq,Before,After,Sep,LItems}, I0, ST, WT) -> {CharsL,SizeL} = unz(CharsSizeL), {BCharsL,BSizeL} = unz1([BCharsSize]), Sizes = BSizeL ++ SizeL, - NSepChars = if + NSepChars = if is_list(Sep), Sep =/= [] -> erlang:max(0, length(CharsL)-1); true -> @@ -875,7 +938,7 @@ nl_indent(I, T) when I > 0 -> [$\n|spaces(I, T)]. same_line(I0, SizeL, NSepChars) -> - try + try Size = lists:sum(SizeL) + NSepChars, true = incr(I0, Size) =< ?MAXLINE, {yes,Size} @@ -955,9 +1018,9 @@ write_a_string(S, N, Len) -> -define(N_SPACES, 30). spacetab() -> - {[_|L],_} = mapfoldl(fun(_, A) -> {A,[$\s|A]} + {[_|L],_} = mapfoldl(fun(_, A) -> {A,[$\s|A]} end, [], lists:seq(0, ?N_SPACES)), - list_to_tuple(L). + list_to_tuple(L). spaces(N, T) when N =< ?N_SPACES -> element(N, T); @@ -965,7 +1028,7 @@ spaces(N, T) -> [element(?N_SPACES, T)|spaces(N-?N_SPACES, T)]. wordtable() -> - L = [begin {leaf,Sz,S} = leaf(W), {S,Sz} end || + L = [begin {leaf,Sz,S} = leaf(W), {S,Sz} end || W <- [" ->"," =","<<",">>","[]","after","begin","case","catch", "end","fun","if","of","receive","try","when"," ::","..", " |"]], diff --git a/lib/stdlib/src/erl_scan.erl b/lib/stdlib/src/erl_scan.erl index 52ec81a78b..10b2ed2e49 100644 --- a/lib/stdlib/src/erl_scan.erl +++ b/lib/stdlib/src/erl_scan.erl @@ -1,19 +1,19 @@ %% %% %CopyrightBegin% -%% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. -%% +%% +%% Copyright Ericsson AB 1996-2011. 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 %% compliance with the License. You should have received a copy of the %% Erlang Public License along with this software. If not, it can be %% retrieved online at http://www.erlang.org/. -%% +%% %% Software distributed under the License is distributed on an "AS IS" %% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See %% the License for the specific language governing rights and limitations %% under the License. -%% +%% %% %CopyrightEnd% %% @@ -48,25 +48,20 @@ -module(erl_scan). -%%% External exports +%%% External exports -export([string/1,string/2,string/3,tokens/3,tokens/4, format_error/1,reserved_word/1, token_info/1,token_info/2, attributes_info/1,attributes_info/2,set_attribute/3]). -%%% Local record. --record(erl_scan, - {resword_fun=fun reserved_word/1, - ws=false, - comment=false, - text=false}). +-export_type([error_info/0, line/0, tokens_result/0]). %%% -%%% Exported functions +%%% Defines and type definitions %%% --define(COLUMN(C), is_integer(C), C >= 1). +-define(COLUMN(C), (is_integer(C) andalso C >= 1)). %% Line numbers less than zero have always been allowed: -define(ALINE(L), is_integer(L)). -define(STRING(S), is_list(S)). @@ -95,86 +90,126 @@ -type error_description() :: term(). -type error_info() :: {location(), module(), error_description()}. --spec format_error(Error :: term()) -> string(). +%%% Local record. +-record(erl_scan, + {resword_fun = fun reserved_word/1 :: resword_fun(), + ws = false :: boolean(), + comment = false :: boolean(), + text = false :: boolean()}). + +%%---------------------------------------------------------------------------- + +-spec format_error(ErrorDescriptor) -> string() when + ErrorDescriptor :: error_description(). format_error({string,Quote,Head}) -> lists:flatten(["unterminated " ++ string_thing(Quote) ++ - " starting with " ++ + " starting with " ++ io_lib:write_unicode_string(Head, Quote)]); -format_error({illegal,Type}) -> +format_error({illegal,Type}) -> lists:flatten(io_lib:fwrite("illegal ~w", [Type])); format_error(char) -> "unterminated character"; -format_error({base,Base}) -> +format_error({base,Base}) -> lists:flatten(io_lib:fwrite("illegal base '~w'", [Base])); -format_error(Other) -> +format_error(Other) -> lists:flatten(io_lib:write(Other)). --type string_return() :: {'ok', tokens(), location()} - | {'error', error_info(), location()}. - --spec string(String :: string()) -> string_return(). +-spec string(String) -> Return when + String :: string(), + Return :: {'ok', Tokens :: tokens(), EndLocation} + | {'error', ErrorInfo :: error_info(), ErrorLocation}, + EndLocation :: location(), + ErrorLocation :: location(). string(String) -> string(String, 1, []). --spec string(String :: string(), StartLocation :: location()) -> - string_return(). +-spec string(String, StartLocation) -> Return when + String :: string(), + Return :: {'ok', Tokens :: tokens(), EndLocation} + | {'error', ErrorInfo :: error_info(), ErrorLocation}, + StartLocation :: location(), + EndLocation :: location(), + ErrorLocation :: location(). string(String, StartLocation) -> string(String, StartLocation, []). --spec string(String :: string(), StartLocation :: location(), - Options :: options()) -> string_return(). +-spec string(String, StartLocation, Options) -> Return when + String :: string(), + Options :: options(), + Return :: {'ok', Tokens :: tokens(), EndLocation} + | {'error', ErrorInfo :: error_info(), ErrorLocation}, + StartLocation :: location(), + EndLocation :: location(), + ErrorLocation :: location(). string(String, Line, Options) when ?STRING(String), ?ALINE(Line) -> string1(String, options(Options), Line, no_col, []); string(String, {Line,Column}, Options) when ?STRING(String), - ?ALINE(Line), + ?ALINE(Line), ?COLUMN(Column) -> string1(String, options(Options), Line, Column, []). -type char_spec() :: string() | 'eof'. -type cont_fun() :: fun((char_spec(), #erl_scan{}, line(), column(), tokens(), any()) -> any()). --opaque return_cont() :: {string(), column(), tokens(), line(), - #erl_scan{}, cont_fun(), any()}. --type cont() :: return_cont() | []. --type tokens_result() :: {'ok', tokens(), location()} - | {'eof', location()} - | {'error', error_info(), location()}. --type tokens_return() :: {'done', tokens_result(), char_spec()} - | {'more', return_cont()}. - --spec tokens(Cont :: cont(), CharSpec :: char_spec(), - StartLocation :: location()) -> tokens_return(). +-opaque return_cont() :: {erl_scan_continuation, + string(), column(), tokens(), line(), + #erl_scan{}, any(), cont_fun()}. +-type tokens_result() :: {'ok', Tokens :: tokens(), EndLocation :: location()} + | {'eof', EndLocation :: location()} + | {'error', ErrorInfo :: error_info(), + EndLocation :: location()}. + +-spec tokens(Continuation, CharSpec, StartLocation) -> Return when + Continuation :: return_cont() | [], + CharSpec :: char_spec(), + StartLocation :: location(), + Return :: {'done',Result :: tokens_result(),LeftOverChars :: char_spec()} + | {'more', Continuation1 :: return_cont()}. tokens(Cont, CharSpec, StartLocation) -> tokens(Cont, CharSpec, StartLocation, []). --spec tokens(Cont :: cont(), CharSpec :: char_spec(), - StartLocation :: location(), Options :: options()) -> - tokens_return(). +-spec tokens(Continuation, CharSpec, StartLocation, Options) -> Return when + Continuation :: return_cont() | [], + CharSpec :: char_spec(), + StartLocation :: location(), + Options :: options(), + Return :: {'done',Result :: tokens_result(),LeftOverChars :: char_spec()} + | {'more', Continuation1 :: return_cont()}. tokens([], CharSpec, Line, Options) when ?ALINE(Line) -> tokens1(CharSpec, options(Options), Line, no_col, [], fun scan/6, []); tokens([], CharSpec, {Line,Column}, Options) when ?ALINE(Line), ?COLUMN(Column) -> tokens1(CharSpec, options(Options), Line, Column, [], fun scan/6, []); -tokens({Cs,Col,Toks,Line,St,Any,Fun}, CharSpec, _Loc, _Opts) -> +tokens({erl_scan_continuation,Cs,Col,Toks,Line,St,Any,Fun}, + CharSpec, _Loc, _Opts) -> tokens1(Cs++CharSpec, St, Line, Col, Toks, Fun, Any). --type attribute_item() :: 'column' | 'length' | 'line' +-type attribute_item() :: 'column' | 'length' | 'line' | 'location' | 'text'. -type info_location() :: location() | term(). --type attribute_info() :: {'column', column()}| {'length', pos_integer()} - | {'line', info_line()} +-type attribute_info() :: {'column', column()}| {'length', pos_integer()} + | {'line', info_line()} | {'location', info_location()} | {'text', string()}. -type token_item() :: 'category' | 'symbol' | attribute_item(). --type token_info() :: {'category', category()} | {'symbol', symbol()} +-type token_info() :: {'category', category()} | {'symbol', symbol()} | attribute_info(). --spec token_info(token()) -> [token_info()]. +-spec token_info(Token) -> TokenInfo when + Token :: token(), + TokenInfo :: [TokenInfoTuple :: token_info()]. token_info(Token) -> Items = [category,column,length,line,symbol,text], % undefined order token_info(Token, Items). --spec token_info(token(), token_item()) -> token_info() | 'undefined'; - (token(), [token_item()]) -> [token_info()]. +-spec token_info(Token, TokenItem) -> TokenInfo | 'undefined' when + Token :: token(), + TokenItem :: token_item(), + TokenInfo :: TokenInfoTuple :: token_info(); + (Token, TokenItems) -> [TokenInfo] when + Token :: token(), + TokenItems :: [TokenItem], + TokenItem :: token_item(), + TokenInfo :: [TokenInfoTuple :: token_info()]. token_info(_Token, []) -> []; token_info(Token, [Item|Items]) when is_atom(Item) -> @@ -197,14 +232,23 @@ token_info({_Category,Attrs}, Item) -> token_info({_Category,Attrs,_Symbol}, Item) -> attributes_info(Attrs, Item). --spec attributes_info(attributes()) -> [attribute_info()]. +-spec attributes_info(Attributes) -> AttributesInfo when + Attributes :: attributes(), + AttributesInfo :: [AttributeInfoTuple :: attribute_info()]. attributes_info(Attributes) -> Items = [column,length,line,text], % undefined order attributes_info(Attributes, Items). --spec attributes_info(attributes(), attribute_item()) -> - attribute_info() | 'undefined'; - (attributes(), [attribute_item()]) -> [attribute_info()]. +-spec attributes_info(Attributes, AttributeItem) -> + AttributeInfo | 'undefined' when + Attributes :: attributes(), + AttributeItem :: attribute_item(), + AttributeInfo :: AttributeInfoTuple :: attribute_info(); + (Attributes, AttributeItems) -> [AttributeInfo] when + Attributes :: attributes(), + AttributeItems :: [AttributeItem], + AttributeItem :: attribute_item(), + AttributeInfo :: [AttributeInfoTuple :: attribute_info()]. attributes_info(_Attrs, []) -> []; attributes_info(Attrs, [A|As]) when is_atom(A) -> @@ -214,7 +258,7 @@ attributes_info(Attrs, [A|As]) when is_atom(A) -> AttributeInfo when is_tuple(AttributeInfo) -> [AttributeInfo|attributes_info(Attrs, As)] end; -attributes_info({Line,Column}, column=Item) when ?ALINE(Line), +attributes_info({Line,Column}, column=Item) when ?ALINE(Line), ?COLUMN(Column) -> {Item,Column}; attributes_info(Line, column) when ?ALINE(Line) -> @@ -230,12 +274,12 @@ attributes_info(Attrs, length=Item) -> end; attributes_info(Line, line=Item) when ?ALINE(Line) -> {Item,Line}; -attributes_info({Line,Column}, line=Item) when ?ALINE(Line), +attributes_info({Line,Column}, line=Item) when ?ALINE(Line), ?COLUMN(Column) -> {Item,Line}; attributes_info(Attrs, line=Item) -> attr_info(Attrs, Item); -attributes_info({Line,Column}=Location, location=Item) when ?ALINE(Line), +attributes_info({Line,Column}=Location, location=Item) when ?ALINE(Line), ?COLUMN(Column) -> {Item,Location}; attributes_info(Line, location=Item) when ?ALINE(Line) -> @@ -261,9 +305,10 @@ attributes_info(Attrs, text=Item) -> attributes_info(T1, T2) -> erlang:error(badarg, [T1,T2]). --type setlineattr_fun() :: fun((info_line()) -> info_line()). - --spec set_attribute('line', attributes(), setlineattr_fun()) -> attributes(). +-spec set_attribute(AttributeItem, Attributes, SetAttributeFun) -> Attributes when + AttributeItem :: 'line', + Attributes :: attributes(), + SetAttributeFun :: fun((info_line()) -> info_line()). set_attribute(Tag, Attributes, Fun) when ?SETATTRFUN(Fun) -> set_attr(Tag, Attributes, Fun). @@ -289,11 +334,11 @@ string_thing(_) -> "string". options(Opts0) when is_list(Opts0) -> Opts = lists:foldr(fun expand_opt/2, [], Opts0), - [RW_fun] = + [RW_fun] = case opts(Opts, [reserved_word_fun], []) of badarg -> erlang:error(badarg, [Opts0]); - R -> + R -> R end, Comment = proplists:get_bool(return_comments, Opts), @@ -307,10 +352,10 @@ options(Opt) -> options([Opt]). opts(Options, [Key|Keys], L) -> - V = case lists:keysearch(Key, 1, Options) of - {value,{reserved_word_fun,F}} when ?RESWORDFUN(F) -> + V = case lists:keyfind(Key, 1, Options) of + {reserved_word_fun,F} when ?RESWORDFUN(F) -> {ok,F}; - {value,{Key,_}} -> + {Key,_} -> badarg; false -> {ok,default_option(Key)} @@ -333,12 +378,13 @@ expand_opt(O, Os) -> [O|Os]. attr_info(Attrs, Item) -> - case catch lists:keysearch(Item, 1, Attrs) of - {value,{Item,Value}} -> - {Item,Value}; - false -> - undefined; - _ -> + try lists:keyfind(Item, 1, Attrs) of + {_Item, _Value} = T -> + T; + false -> + undefined + catch + _:_ -> erlang:error(badarg, [Attrs, Item]) end. @@ -362,14 +408,19 @@ set_attr(line, {Line,Column}, Fun) when ?ALINE(Line), ?COLUMN(Column) -> end; set_attr(line=Tag, Attrs, Fun) when is_list(Attrs) -> {line,Line} = lists:keyfind(Tag, 1, Attrs), - lists:keyreplace(Tag, 1, Attrs, {line,Fun(Line)}); + case lists:keyreplace(Tag, 1, Attrs, {line,Fun(Line)}) of + [{line,Ln}] when ?ALINE(Ln) -> + Ln; + As -> + As + end; set_attr(T1, T2, T3) -> erlang:error(badarg, [T1,T2,T3]). tokens1(Cs, St, Line, Col, Toks, Fun, Any) when ?STRING(Cs); Cs =:= eof -> case Fun(Cs, St, Line, Col, Toks, Any) of {more,{Cs0,Ncol,Ntoks,Nline,Nany,Nfun}} -> - {more,{Cs0,Ncol,Ntoks,Nline,St,Nany,Nfun}}; + {more,{erl_scan_continuation,Cs0,Ncol,Ntoks,Nline,St,Nany,Nfun}}; {ok,Toks0,eof,Nline,Ncol} -> Res = case Toks0 of [] -> @@ -442,6 +493,14 @@ scan1([$\%=C|Cs], St, Line, Col, Toks) -> scan_comment(Cs, St, Line, Col, Toks, [C]); scan1([C|Cs], St, Line, Col, Toks) when ?DIGIT(C) -> scan_number(Cs, St, Line, Col, Toks, [C]); +scan1("..."++Cs, St, Line, Col, Toks) -> + tok2(Cs, St, Line, Col, Toks, "...", '...', 3); +scan1(".."=Cs, _St, Line, Col, Toks) -> + {more,{Cs,Col,Toks,Line,[],fun scan/6}}; +scan1(".."++Cs, St, Line, Col, Toks) -> + tok2(Cs, St, Line, Col, Toks, "..", '..', 2); +scan1("."=Cs, _St, Line, Col, Toks) -> + {more,{Cs,Col,Toks,Line,[],fun scan/6}}; scan1([$.=C|Cs], St, Line, Col, Toks) -> scan_dot(Cs, St, Line, Col, Toks, [C]); scan1([$"|Cs], St, Line, Col, Toks) -> %" Emacs @@ -591,12 +650,12 @@ scan_atom(Cs0, St, Line, Col, Toks, Ncs0) -> case catch list_to_atom(Wcs) of Name when is_atom(Name) -> case (St#erl_scan.resword_fun)(Name) of - true -> + true -> tok2(Cs, St, Line, Col, Toks, Wcs, Name); - false -> + false -> tok3(Cs, St, Line, Col, Toks, atom, Wcs, Name) end; - _Error -> + _Error -> Ncol = incr_column(Col, length(Wcs)), scan_error({illegal,atom}, Line, Col, Line, Ncol, Cs) end @@ -610,7 +669,7 @@ scan_variable(Cs0, St, Line, Col, Toks, Ncs0) -> case catch list_to_atom(Wcs) of Name when is_atom(Name) -> tok3(Cs, St, Line, Col, Toks, var, Wcs, Name); - _Error -> + _Error -> Ncol = incr_column(Col, length(Wcs)), scan_error({illegal,var}, Line, Col, Line, Ncol, Cs) end @@ -644,8 +703,6 @@ scan_dot([$\n=C|Cs], St, Line, Col, Toks, Ncs) -> scan_dot([C|Cs], St, Line, Col, Toks, Ncs) when ?WHITE_SPACE(C) -> Attrs = attributes(Line, Col, St, Ncs++[C]), {ok,[{dot,Attrs}|Toks],Cs,Line,incr_column(Col, 2)}; -scan_dot([]=Cs, _St, Line, Col, Toks, Ncs) -> - {more,{Cs,Col,Toks,Line,Ncs,fun scan_dot/6}}; scan_dot(eof=Cs, St, Line, Col, Toks, Ncs) -> Attrs = attributes(Line, Col, St, Ncs), {ok,[{dot,Attrs}|Toks],Cs,Line,incr_column(Col, 1)}; @@ -690,7 +747,7 @@ scan_nl_spcs([]=Cs, _St, Line, Col, Toks, N) -> {more,{Cs,Col,Toks,Line,N,fun scan_nl_spcs/6}}; scan_nl_spcs(Cs, St, Line, Col, Toks, N) -> newline_end(Cs, St, Line, Col, Toks, N, nl_spcs(N)). - + scan_nl_tabs([$\t|Cs], St, Line, Col, Toks, N) when N < 11 -> scan_nl_tabs(Cs, St, Line, Col, Toks, N+1); scan_nl_tabs([]=Cs, _St, Line, Col, Toks, N) -> @@ -701,7 +758,7 @@ scan_nl_tabs(Cs, St, Line, Col, Toks, N) -> %% Note: returning {more,Cont} is meaningless here; one could just as %% well return several tokens. But since tokens() scans up to a full %% stop anyway, nothing is gained by not collecting all white spaces. -scan_nl_white_space([$\n|Cs], #erl_scan{text = false}=St, Line, no_col=Col, +scan_nl_white_space([$\n|Cs], #erl_scan{text = false}=St, Line, no_col=Col, Toks0, Ncs) -> Toks = [{white_space,Line,lists:reverse(Ncs)}|Toks0], scan_newline(Cs, St, Line+1, Col, Toks); @@ -714,7 +771,7 @@ scan_nl_white_space([C|Cs], St, Line, Col, Toks, Ncs) when ?WHITE_SPACE(C) -> scan_nl_white_space(Cs, St, Line, Col, Toks, [C|Ncs]); scan_nl_white_space([]=Cs, _St, Line, Col, Toks, Ncs) -> {more,{Cs,Col,Toks,Line,Ncs,fun scan_nl_white_space/6}}; -scan_nl_white_space(Cs, #erl_scan{text = false}=St, Line, no_col=Col, +scan_nl_white_space(Cs, #erl_scan{text = false}=St, Line, no_col=Col, Toks, Ncs) -> scan1(Cs, St, Line+1, Col, [{white_space,Line,lists:reverse(Ncs)}|Toks]); scan_nl_white_space(Cs, St, Line, Col, Toks, Ncs0) -> @@ -723,7 +780,7 @@ scan_nl_white_space(Cs, St, Line, Col, Toks, Ncs0) -> Token = {white_space,Attrs,Ncs}, scan1(Cs, St, Line+1, new_column(Col, length(Ncs)), [Token|Toks]). -newline_end(Cs, #erl_scan{text = false}=St, Line, no_col=Col, +newline_end(Cs, #erl_scan{text = false}=St, Line, no_col=Col, Toks, _N, Ncs) -> scan1(Cs, St, Line+1, Col, [{white_space,Line,Ncs}|Toks]); newline_end(Cs, St, Line, Col, Toks, N, Ncs) -> @@ -789,7 +846,7 @@ scan_char([$\\|Cs]=Cs0, St, Line, Col, Toks) -> Ntoks = [{char,Attrs,Val}|Toks], scan1(Ncs, St, Line, Ncol, Ntoks) end; -scan_char([$\n=C|Cs], St, Line, Col, Toks) -> +scan_char([$\n=C|Cs], St, Line, Col, Toks) -> Attrs = attributes(Line, Col, St, [$$,C]), scan1(Cs, St, Line+1, new_column(Col, 1), [{char,Attrs,C}|Toks]); scan_char([C|Cs], St, Line, Col, Toks) when ?CHAR(C) -> @@ -896,7 +953,7 @@ scan_string_no_col([Q|Cs], Line, Col, Q, Wcs, Uni) -> {Cs,Line,Col,_DontCare=[],lists:reverse(Wcs),Uni}; scan_string_no_col([$\n=C|Cs], Line, Col, Q, Wcs, Uni) -> scan_string_no_col(Cs, Line+1, Col, Q, [C|Wcs], Uni); -scan_string_no_col([C|Cs], Line, Col, Q, Wcs, Uni) when C =/= $\\, +scan_string_no_col([C|Cs], Line, Col, Q, Wcs, Uni) when C =/= $\\, ?CHAR(C), ?UNI255(C) -> scan_string_no_col(Cs, Line, Col, Q, [C|Wcs], Uni); scan_string_no_col(Cs, Line, Col, Q, Wcs, Uni) -> @@ -909,7 +966,7 @@ scan_string_col([Q|Cs], Line, Col, Q, Wcs0, Uni) -> {Cs,Line,Col+1,Str,Wcs,Uni}; scan_string_col([$\n=C|Cs], Line, _xCol, Q, Wcs, Uni) -> scan_string_col(Cs, Line+1, 1, Q, [C|Wcs], Uni); -scan_string_col([C|Cs], Line, Col, Q, Wcs, Uni) when C =/= $\\, +scan_string_col([C|Cs], Line, Col, Q, Wcs, Uni) when C =/= $\\, ?CHAR(C), ?UNI255(C) -> scan_string_col(Cs, Line, Col+1, Q, [C|Wcs], Uni); scan_string_col(Cs, Line, Col, Q, Wcs, Uni) -> @@ -970,8 +1027,8 @@ scan_string1(eof, Line, Col, _Q, _Str, Wcs, _Uni) -> {error,Line,Col,lists:reverse(Wcs),eof}. -define(OCT(C), C >= $0, C =< $7). --define(HEX(C), C >= $0 andalso C =< $9 orelse - C >= $A andalso C =< $F orelse +-define(HEX(C), C >= $0 andalso C =< $9 orelse + C >= $A andalso C =< $F orelse C >= $a andalso C =< $f). %% \<1-3> octal digits @@ -1086,7 +1143,7 @@ scan_number(Cs, St, Line, Col, Toks, Ncs0) -> Ncol = incr_column(Col, length(Ncs)), scan_error({illegal,integer}, Line, Col, Line, Ncol, Cs) end. - + scan_based_int([C|Cs], St, Line, Col, Toks, {B,Ncs,Bcs}) when ?DIGIT(C), C < $0+B -> scan_based_int(Cs, St, Line, Col, Toks, {B,[C|Ncs],Bcs}); @@ -1262,7 +1319,7 @@ nl_tabs(8) -> "\n\t\t\t\t\t\t\t"; nl_tabs(9) -> "\n\t\t\t\t\t\t\t\t"; nl_tabs(10) -> "\n\t\t\t\t\t\t\t\t\t"; nl_tabs(11) -> "\n\t\t\t\t\t\t\t\t\t\t". - + tabs(1) -> "\t"; tabs(2) -> "\t\t"; tabs(3) -> "\t\t\t"; @@ -1274,7 +1331,7 @@ tabs(8) -> "\t\t\t\t\t\t\t\t"; tabs(9) -> "\t\t\t\t\t\t\t\t\t"; tabs(10) -> "\t\t\t\t\t\t\t\t\t\t". --spec reserved_word(atom()) -> boolean(). +-spec reserved_word(Atom :: atom()) -> boolean(). reserved_word('after') -> true; reserved_word('begin') -> true; reserved_word('case') -> true; @@ -1303,5 +1360,4 @@ reserved_word('bsl') -> true; reserved_word('bsr') -> true; reserved_word('or') -> true; reserved_word('xor') -> true; -reserved_word('spec') -> true; reserved_word(_) -> false. diff --git a/lib/stdlib/src/erl_tar.erl b/lib/stdlib/src/erl_tar.erl index fd85c7aef5..306834e845 100644 --- a/lib/stdlib/src/erl_tar.erl +++ b/lib/stdlib/src/erl_tar.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1997-2009. All Rights Reserved. +%% Copyright Ericsson AB 1997-2011. 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 @@ -798,30 +798,10 @@ set_extracted_file_info(Name, #tar_header{mode=Mode, mtime=Mtime}) -> %% Makes all directories leading up to the file. -make_dirs(Name, Type) -> - make_dirs1(filename:split(Name), Type). - -make_dirs1([Dir, Next|Rest], Type) -> - case file:read_file_info(Dir) of - {ok, #file_info{type=directory}} -> - make_dirs1([filename:join(Dir, Next)|Rest], Type); - {ok, #file_info{}} -> - throw({error, enotdir}); - {error, _} -> - case file:make_dir(Dir) of - ok -> - make_dirs1([filename:join(Dir, Next)|Rest], Type); - {error, Reason} -> - throw({error, Reason}) - end - end; -make_dirs1([_], file) -> ok; -make_dirs1([Dir], dir) -> - file:make_dir(Dir); -make_dirs1([], _) -> - %% There must be something wrong here. The list was not supposed - %% to be empty. - throw({error, enoent}). +make_dirs(Name, file) -> + filelib:ensure_dir(Name); +make_dirs(Name, dir) -> + filelib:ensure_dir(filename:join(Name,"*")). %% Prints the message on if the verbose option is given (for reading). diff --git a/lib/stdlib/src/escript.erl b/lib/stdlib/src/escript.erl index 5958a58d7c..cd1bacd2f5 100644 --- a/lib/stdlib/src/escript.erl +++ b/lib/stdlib/src/escript.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2007-2010. All Rights Reserved. +%% Copyright Ericsson AB 2007-2011. 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 @@ -19,102 +19,254 @@ -module(escript). %% Useful functions that can be called from scripts. --export([script_name/0, foldl/3]). +-export([script_name/0, create/2, extract/2]). %% Internal API. -export([start/0, start/1]). --record(state, {file, - module, +%%----------------------------------------------------------------------- + +-define(SHEBANG, "/usr/bin/env escript"). +-define(COMMENT, "This is an -*- erlang -*- file"). + +%%----------------------------------------------------------------------- + +-type mode() :: 'native' | 'compile' | 'debug' | 'interpret' | 'run'. +-type source() :: 'archive' | 'beam' | 'text'. + +-record(state, {file :: file:filename(), + module :: module(), forms_or_bin, - source, - n_errors, - mode, - exports_main, - has_records}). - + source :: source(), + n_errors :: non_neg_integer(), + mode :: mode(), + exports_main :: boolean(), + has_records :: boolean()}). + +-type shebang() :: string(). +-type comment() :: string(). +-type emu_args() :: string(). + +-record(sections, {type, + shebang :: shebang(), + comment :: comment(), + emu_args :: emu_args(), + body}). + +-record(extract_options, {compile_source}). + +-type zip_file() :: + file:filename() + | {file:filename(), binary()} + | {file:filename(), binary(), file:file_info()}. +-type zip_create_option() :: term(). +-type section() :: + shebang + | {shebang, shebang() | default | undefined} + | comment + | {comment, comment() | default | undefined} + | {emu_args, emu_args() | undefined} + | {source, file:filename() | binary()} + | {beam, file:filename() | binary()} + | {archive, file:filename() | binary()} + | {archive, [zip_file()], [zip_create_option()]}. + +%%----------------------------------------------------------------------- + +%% Create a complete escript file with both header and body +-spec create(file:filename() | binary, [section()]) -> + ok | {ok, binary()} | {error, term()}. + +create(File, Options) when is_list(Options) -> + try + S = prepare(Options, #sections{}), + BinList = + [Section || Section <- [S#sections.shebang, + S#sections.comment, + S#sections.emu_args, + S#sections.body], + Section =/= undefined], + case File of + binary -> + {ok, list_to_binary(BinList)}; + _ -> + case file:write_file(File, BinList) of + ok -> + ok; + {error, Reason} -> + {error, {Reason, File}} + end + end + catch + throw:PrepareReason -> + {error, PrepareReason} + end. + +prepare([H | T], S) -> + case H of + {shebang, undefined} -> + prepare(T, S); + shebang -> + prepare(T, S#sections{shebang = "#!" ++ ?SHEBANG ++ "\n"}); + {shebang, default} -> + prepare(T, S#sections{shebang = "#!" ++ ?SHEBANG ++ "\n"}); + {shebang, Shebang} when is_list(Shebang) -> + prepare(T, S#sections{shebang = "#!" ++ Shebang ++ "\n"}); + {comment, undefined} -> + prepare(T, S); + comment -> + prepare(T, S#sections{comment = "%% " ++ ?COMMENT ++ "\n"}); + {comment, default} -> + prepare(T, S#sections{comment = "%% " ++ ?COMMENT ++ "\n"}); + {comment, Comment} when is_list(Comment) -> + prepare(T, S#sections{comment = "%% " ++ Comment ++ "\n"}); + {emu_args, undefined} -> + prepare(T, S); + {emu_args, Args} when is_list(Args) -> + prepare(T, S#sections{emu_args = "%%!" ++ Args ++ "\n"}); + {Type, File} when is_list(File) -> + case file:read_file(File) of + {ok, Bin} -> + prepare(T, S#sections{type = Type, body = Bin}); + {error, Reason} -> + throw({Reason, H}) + end; + {Type, Bin} when is_binary(Bin) -> + prepare(T, S#sections{type = Type, body = Bin}); + {archive = Type, ZipFiles, ZipOptions} + when is_list(ZipFiles), is_list(ZipOptions) -> + File = "dummy.zip", + case zip:create(File, ZipFiles, ZipOptions ++ [memory]) of + {ok, {File, ZipBin}} -> + prepare(T, S#sections{type = Type, body = ZipBin}); + {error, Reason} -> + throw({Reason, H}) + end; + _ -> + throw({badarg, H}) + end; +prepare([], #sections{body = undefined}) -> + throw(missing_body); +prepare([], #sections{type = Type} = S) + when Type =:= source; Type =:= beam; Type =:= archive -> + S; +prepare([], #sections{type = Type}) -> + throw({illegal_type, Type}); +prepare(BadOptions, _) -> + throw({badarg, BadOptions}). + +-type section_name() :: shebang | comment | emu_args | body . +-type extract_option() :: compile_source | {section, [section_name()]}. +-spec extract(file:filename(), [extract_option()]) -> + {ok, [section()]} | {error, term()}. + +extract(File, Options) when is_list(File), is_list(Options) -> + try + EO = parse_extract_options(Options, + #extract_options{compile_source = false}), + {HeaderSz, NextLineNo, Fd, Sections} = + parse_header(File, not EO#extract_options.compile_source), + Type = Sections#sections.type, + case {Type, EO#extract_options.compile_source} of + {source, true} -> + Bin = compile_source(Type, File, Fd, NextLineNo, HeaderSz); + {_, _} -> + ok = file:close(Fd), + case file:read_file(File) of + {ok, <<_Header:HeaderSz/binary, Bin/binary>>} -> + ok; + {error, ReadReason} -> + Bin = get_rid_of_compiler_warning, + throw(ReadReason) + end + end, + return_sections(Sections, Bin) + catch + throw:Reason -> + {error, Reason} + end. + +parse_extract_options([H | T], EO) -> + case H of + compile_source -> + EO2 = EO#extract_options{compile_source = true}, + parse_extract_options(T, EO2); + _ -> + throw({badarg, H}) + end; +parse_extract_options([], EO) -> + EO. + +compile_source(Type, File, Fd, NextLineNo, HeaderSz) -> + {text, _Module, Forms, _HasRecs, _Mode} = + do_parse_file(Type, File, Fd, NextLineNo, HeaderSz, false), + ok = file:close(Fd), + case compile:forms(Forms, [return_errors, debug_info]) of + {ok, _, BeamBin} -> + BeamBin; + {error, Errors, Warnings} -> + throw({compile, [{errors, format_errors(Errors)}, + {warnings, format_errors(Warnings)}]}) + end. + +format_errors(CompileErrors) -> + [lists:flatten([File, ":", integer_to_list(LineNo), ": ", + Mod:format_error(Error)]) || + {File, FileErrors} <- CompileErrors, + {LineNo, Mod, Error} <- FileErrors]. + +return_sections(S, Bin) -> + {ok, [normalize_section(shebang, S#sections.shebang), + normalize_section(comment, S#sections.comment), + normalize_section(emu_args, S#sections.emu_args), + normalize_section(S#sections.type, Bin)]}. + +normalize_section(Name, undefined) -> + {Name, undefined}; +normalize_section(shebang, "#!" ++ Chars) -> + Chopped = string:strip(Chars, right, $\n), + Stripped = string:strip(Chopped, both), + if + Stripped =:= ?SHEBANG -> + {shebang, default}; + true -> + {shebang, Stripped} + end; +normalize_section(comment, Chars) -> + Chopped = string:strip(Chars, right, $\n), + Stripped = string:strip(string:strip(Chopped, left, $%), both), + if + Stripped =:= ?COMMENT -> + {comment, default}; + true -> + {comment, Stripped} + end; +normalize_section(emu_args, "%%!" ++ Chars) -> + Chopped = string:strip(Chars, right, $\n), + Stripped = string:strip(Chopped, both), + {emu_args, Stripped}; +normalize_section(Name, Chars) -> + {Name, Chars}. + +-spec script_name() -> string(). + script_name() -> [ScriptName|_] = init:get_plain_arguments(), ScriptName. -%% Apply Fun(Name, GetInfo, GetBin, Acc) for each file in the escript. -%% -%% Fun/2 must return a new accumulator which is passed to the next call. -%% The function returns the final value of the accumulator. Acc0 is -%% returned if the escript contain an empty archive. -%% -%% GetInfo/0 is a fun that returns a #file_info{} record for the file. -%% GetBin/0 is a fun that returns a the contents of the file as a binary. -%% -%% An escript may contain erlang code, beam code or an archive: -%% -%% archive - the Fun/2 will be applied for each file in the archive -%% beam - the Fun/2 will be applied once and GetInfo/0 returns the file -%% info for the (entire) escript file -%% erl - the Fun/2 will be applied once, GetInfo/0 returns the file -%% info for the (entire) escript file and the GetBin returns -%% the compiled beam code - -%%-spec foldl(fun((string(), -%% fun(() -> #file_info()), -%% fun(() -> binary() -> term()), -%% term()) -> term()), -%% term(), -%% string()). -foldl(Fun, Acc0, File) when is_function(Fun, 4) -> - case parse_file(File, false) of - {text, _, Forms, _HasRecs, _Mode} when is_list(Forms) -> - GetInfo = fun() -> file:read_file_info(File) end, - GetBin = - fun() -> - case compile:forms(Forms, [return_errors, debug_info]) of - {ok, _, BeamBin} -> - BeamBin; - {error, _Errors, _Warnings} -> - fatal("There were compilation errors.") - end - end, - try - {ok, Fun(".", GetInfo, GetBin, Acc0)} - catch - throw:Reason -> - {error, Reason} - end; - {beam, _, BeamBin, _HasRecs, _Mode} when is_binary(BeamBin) -> - GetInfo = fun() -> file:read_file_info(File) end, - GetBin = fun() -> BeamBin end, - try - {ok, Fun(".", GetInfo, GetBin, Acc0)} - catch - throw:Reason -> - {error, Reason} - end; - {archive, _, ArchiveBin, _HasRecs, _Mode} when is_binary(ArchiveBin) -> - ZipFun = - fun({Name, GetInfo, GetBin}, A) -> - A2 = Fun(Name, GetInfo, GetBin, A), - {true, false, A2} - end, - case prim_zip:open(ZipFun, Acc0, {File, ArchiveBin}) of - {ok, PrimZip, Res} -> - ok = prim_zip:close(PrimZip), - {ok, Res}; - {error, bad_eocd} -> - {error, "Not an archive file"}; - {error, Reason} -> - {error, Reason} - end - end. - %% %% Internal API. %% +-spec start() -> no_return(). + start() -> start([]). +-spec start([string()]) -> no_return(). + start(EscriptOptions) -> - try + try %% Commands run using -run or -s are run in a process %% trap_exit set to false. Because this behaviour is %% surprising for users of escript, make sure to reset @@ -143,16 +295,20 @@ parse_and_run(File, Args, Options) -> parse_file(File, CheckOnly), Mode2 = case lists:member("d", Options) of - true -> + true -> debug; false -> case lists:member("c", Options) of - true -> + true -> compile; false -> case lists:member("i", Options) of true -> interpret; - false -> Mode + false -> + case lists:member("n", Options) of + true -> native; + false -> Mode + end end end end, @@ -169,6 +325,14 @@ parse_and_run(File, Args, Options) -> _Other -> fatal("There were compilation errors.") end; + native -> + case compile:forms(FormsOrBin, [report,native]) of + {ok, Module, BeamBin} -> + {module, Module} = code:load_binary(Module, File, BeamBin), + run(Module, Args); + _Other -> + fatal("There were compilation errors.") + end; debug -> case compile:forms(FormsOrBin, [report, debug_info]) of {ok,Module,BeamBin} -> @@ -177,7 +341,7 @@ parse_and_run(File, Args, Options) -> _Other -> fatal("There were compilation errors.") end - end; + end; is_binary(FormsOrBin) -> case Source of archive -> @@ -190,11 +354,13 @@ parse_and_run(File, Args, Options) -> true -> my_halt(0); false -> - Text = lists:concat(["Function ", Module, ":main/1 is not exported"]), + Text = lists:concat(["Function ", Module, + ":main/1 is not exported"]), fatal(Text) end; _ -> - Text = lists:concat(["Cannot load module ", Module, " from archive"]), + Text = lists:concat(["Cannot load module ", Module, + " from archive"]), fatal(Text) end; ok -> @@ -212,7 +378,7 @@ parse_and_run(File, Args, Options) -> run -> {module, Module} = code:load_binary(Module, File, FormsOrBin), run(Module, Args); - debug -> + debug -> [Base | Rest] = lists:reverse(filename:split(File)), Base2 = filename:basename(Base, code:objfile_extension()), Rest2 = @@ -222,8 +388,8 @@ parse_and_run(File, Args, Options) -> end, SrcFile = filename:join(lists:reverse([Base2 ++ ".erl" | Rest2])), debug(Module, {Module, SrcFile, File, FormsOrBin}, Args) - end - end + end + end end. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% @@ -231,25 +397,19 @@ parse_and_run(File, Args, Options) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% parse_file(File, CheckOnly) -> - S = #state{file = File, - n_errors = 0, - mode = interpret, - exports_main = false, - has_records = false}, - {ok, Fd} = - case file:open(File, [read]) of - {ok, Fd0} -> - {ok, Fd0}; - {error, R} -> - fatal(lists:concat([file:format_error(R), ": '", File, "'"])) - end, - {HeaderSz, StartLine, ScriptType} = skip_header(Fd, 1), + {HeaderSz, NextLineNo, Fd, Sections} = + parse_header(File, false), + do_parse_file(Sections#sections.type, + File, Fd, NextLineNo, HeaderSz, CheckOnly). + +do_parse_file(Type, File, Fd, NextLineNo, HeaderSz, CheckOnly) -> + S = initial_state(File), #state{mode = Mode, source = Source, module = Module, forms_or_bin = FormsOrBin, has_records = HasRecs} = - case ScriptType of + case Type of archive -> %% Archive file ok = file:close(Fd), @@ -260,63 +420,101 @@ parse_file(File, CheckOnly) -> parse_beam(S, File, HeaderSz, CheckOnly); source -> %% Source code - parse_source(S, File, Fd, StartLine, HeaderSz, CheckOnly) + parse_source(S, File, Fd, NextLineNo, HeaderSz, CheckOnly) end, {Source, Module, FormsOrBin, HasRecs, Mode}. +initial_state(File) -> + #state{file = File, + n_errors = 0, + mode = interpret, + exports_main = false, + has_records = false}. + %% Skip header and make a heuristic guess about the script type -skip_header(P, LineNo) -> +parse_header(File, KeepFirst) -> + LineNo = 1, + {ok, Fd} = + case file:open(File, [read]) of + {ok, Fd0} -> + {ok, Fd0}; + {error, R} -> + fatal(lists:concat([file:format_error(R), ": '", File, "'"])) + end, + %% Skip shebang on first line - {ok, HeaderSz0} = file:position(P, cur), - Line1 = get_line(P), + {ok, HeaderSz0} = file:position(Fd, cur), + Line1 = get_line(Fd), case classify_line(Line1) of shebang -> - find_first_body_line(P, LineNo); + find_first_body_line(Fd, HeaderSz0, LineNo, KeepFirst, + #sections{shebang = Line1}); archive -> - {HeaderSz0, LineNo, archive}; + {HeaderSz0, LineNo, Fd, + #sections{type = archive}}; beam -> - {HeaderSz0, LineNo, beam}; + {HeaderSz0, LineNo, Fd, + #sections{type = beam}}; _ -> - find_first_body_line(P, LineNo) + find_first_body_line(Fd, HeaderSz0, LineNo, KeepFirst, + #sections{}) end. -find_first_body_line(P, LineNo) -> - {ok, HeaderSz1} = file:position(P, cur), +find_first_body_line(Fd, HeaderSz0, LineNo, KeepFirst, Sections) -> + {ok, HeaderSz1} = file:position(Fd, cur), %% Look for special comment on second line - Line2 = get_line(P), - {ok, HeaderSz2} = file:position(P, cur), + Line2 = get_line(Fd), + {ok, HeaderSz2} = file:position(Fd, cur), case classify_line(Line2) of emu_args -> %% Skip special comment on second line - Line3 = get_line(P), - {HeaderSz2, LineNo + 2, guess_type(Line3)}; - _ -> + Line3 = get_line(Fd), + {HeaderSz2, LineNo + 2, Fd, + Sections#sections{type = guess_type(Line3), + comment = undefined, + emu_args = Line2}}; + Line2Type -> %% Look for special comment on third line - Line3 = get_line(P), - {ok, HeaderSz3} = file:position(P, cur), - case classify_line(Line3) of - emu_args -> + Line3 = get_line(Fd), + {ok, HeaderSz3} = file:position(Fd, cur), + Line3Type = classify_line(Line3), + if + Line3Type =:= emu_args -> %% Skip special comment on third line - Line4 = get_line(P), - {HeaderSz3, LineNo + 3, guess_type(Line4)}; - _ -> + Line4 = get_line(Fd), + {HeaderSz3, LineNo + 3, Fd, + Sections#sections{type = guess_type(Line4), + comment = Line2, + emu_args = Line3}}; + Sections#sections.shebang =:= undefined, + KeepFirst =:= true -> + %% No shebang. Use the entire file + {HeaderSz0, LineNo, Fd, + Sections#sections{type = guess_type(Line2)}}; + Sections#sections.shebang =:= undefined -> + %% No shebang. Skip the first line + {HeaderSz1, LineNo, Fd, + Sections#sections{type = guess_type(Line2)}}; + Line2Type =:= comment -> + %% Skip shebang on first line and comment on second + {HeaderSz2, LineNo + 2, Fd, + Sections#sections{type = guess_type(Line3), + comment = Line2}}; + true -> %% Just skip shebang on first line - {HeaderSz1, LineNo + 1, guess_type(Line2)} + {HeaderSz1, LineNo + 1, Fd, + Sections#sections{type = guess_type(Line2)}} end end. - + classify_line(Line) -> case Line of - [$\#, $\! | _] -> - shebang; - [$P, $K | _] -> - archive; - [$F, $O, $R, $1 | _] -> - beam; - [$\%, $\%, $\! | _] -> - emu_args; - _ -> - undefined + "#!" ++ _ -> shebang; + "PK" ++ _ -> archive; + "FOR1" ++ _ -> beam; + "%%!" ++ _ -> emu_args; + "%" ++ _ -> comment; + _ -> undefined end. guess_type(Line) -> @@ -336,8 +534,8 @@ get_line(P) -> parse_archive(S, File, HeaderSz) -> case file:read_file(File) of - {ok, <<_FirstLine:HeaderSz/binary, Bin/binary>>} -> - Mod = + {ok, <<_Header:HeaderSz/binary, Bin/binary>>} -> + Mod = case init:get_argument(escript) of {ok, [["main", M]]} -> %% Use explicit module name @@ -345,14 +543,13 @@ parse_archive(S, File, HeaderSz) -> _ -> %% Use escript name without extension as module name RevBase = lists:reverse(filename:basename(File)), - RevBase2 = + RevBase2 = case lists:dropwhile(fun(X) -> X =/= $. end, RevBase) of [$. | Rest] -> Rest; [] -> RevBase end, list_to_atom(lists:reverse(RevBase2)) end, - S#state{source = archive, mode = run, module = Mod, @@ -365,7 +562,7 @@ parse_archive(S, File, HeaderSz) -> parse_beam(S, File, HeaderSz, CheckOnly) -> - {ok, <<_FirstLine:HeaderSz/binary, Bin/binary>>} = + {ok, <<_Header:HeaderSz/binary, Bin/binary>>} = file:read_file(File), case beam_lib:chunks(Bin, [exports]) of {ok, {Module, [{exports, Exports}]}} -> @@ -385,9 +582,7 @@ parse_beam(S, File, HeaderSz, CheckOnly) -> forms_or_bin = Bin} end; {error, beam_lib, Reason} when is_tuple(Reason) -> - fatal(element(1, Reason)); - {error, beam_lib, Reason} -> - fatal(Reason) + fatal(element(1, Reason)) end. parse_source(S, File, Fd, StartLine, HeaderSz, CheckOnly) -> @@ -399,7 +594,7 @@ parse_source(S, File, Fd, StartLine, HeaderSz, CheckOnly) -> {ok, FileForm} = epp:parse_erl_form(Epp), OptModRes = epp:parse_erl_form(Epp), S2 = S#state{source = text, module = Module}, - S3 = + S3 = case OptModRes of {ok, {attribute,_, module, M} = Form} -> epp_parse_file(Epp, S2#state{module = M}, [Form, FileForm]); @@ -408,8 +603,8 @@ parse_source(S, File, Fd, StartLine, HeaderSz, CheckOnly) -> epp_parse_file2(Epp, S2, [ModForm, FileForm], OptModRes); {error, _} -> epp_parse_file2(Epp, S2, [FileForm], OptModRes); - {eof,LastLine} -> - S#state{forms_or_bin = [FileForm, {eof,LastLine}]} + {eof, _LastLine} = Eof -> + S#state{forms_or_bin = [FileForm, Eof]} end, ok = epp:close(Epp), ok = file:close(Fd), @@ -448,12 +643,12 @@ check_source(S, CheckOnly) -> pre_def_macros(File) -> {MegaSecs, Secs, MicroSecs} = erlang:now(), - Replace = fun(Char) -> + Replace = fun(Char) -> case Char of $\. -> $\_; _ -> Char end - end, + end, CleanBase = lists:map(Replace, filename:basename(File)), ModuleStr = CleanBase ++ "__" ++ @@ -481,7 +676,7 @@ epp_parse_file2(Epp, S, Forms, Parsed) -> {attribute,Ln,mode,NewMode} -> S2 = S#state{mode = NewMode}, if - NewMode =:= compile; NewMode =:= interpret; NewMode =:= debug -> + NewMode =:= compile; NewMode =:= interpret; NewMode =:= debug; NewMode =:= native -> epp_parse_file(Epp, S2, [Form | Forms]); true -> Args = lists:flatten(io_lib:format("illegal mode attribute: ~p", [NewMode])), @@ -504,8 +699,8 @@ epp_parse_file2(Epp, S, Forms, Parsed) -> io:format("~s:~w: ~s\n", [S#state.file,Ln,Mod:format_error(Args)]), epp_parse_file(Epp, S#state{n_errors = S#state.n_errors + 1}, [Form | Forms]); - {eof,LastLine} -> - S#state{forms_or_bin = lists:reverse([{eof, LastLine} | Forms])} + {eof, _LastLine} = Eof -> + S#state{forms_or_bin = lists:reverse([Eof | Forms])} end. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% @@ -642,8 +837,8 @@ eval_exprs([E|Es], Bs0, Lf, Ef, RBs) -> eval_exprs(Es, Bs, Lf, Ef, RBs). format_exception(Class, Reason) -> - PF = fun(Term, I) -> - io_lib:format("~." ++ integer_to_list(I) ++ "P", [Term, 50]) + PF = fun(Term, I) -> + io_lib:format("~." ++ integer_to_list(I) ++ "P", [Term, 50]) end, StackTrace = erlang:get_stacktrace(), StackFun = fun(M, _F, _A) -> (M =:= erl_eval) or (M =:= ?MODULE) end, @@ -651,7 +846,7 @@ format_exception(Class, Reason) -> fatal(Str) -> throw(Str). - + my_halt(Reason) -> case process_info(group_leader(), status) of {_,waiting} -> @@ -675,7 +870,7 @@ hidden_apply(App, M, F, Args) -> Arity = length(Args), Text = io_lib:format("Call to ~w:~w/~w in application ~w failed.\n", [M, F, Arity, App]), - fatal(Text); + fatal(Text); Stk -> erlang:raise(error, undef, Stk) end diff --git a/lib/stdlib/src/ets.erl b/lib/stdlib/src/ets.erl index 9f84e3639f..afa914a456 100644 --- a/lib/stdlib/src/ets.erl +++ b/lib/stdlib/src/ets.erl @@ -1,19 +1,19 @@ %% %% %CopyrightBegin% -%% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. -%% +%% +%% Copyright Ericsson AB 1996-2011. 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 %% compliance with the License. You should have received a copy of the %% Erlang Public License along with this software. If not, it can be %% retrieved online at http://www.erlang.org/. -%% +%% %% Software distributed under the License is distributed on an "AS IS" %% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See %% the License for the specific language governing rights and limitations %% under the License. -%% +%% %% %CopyrightEnd% %% -module(ets). @@ -42,28 +42,20 @@ -export([i/0, i/1, i/2, i/3]). -%%------------------------------------------------------------------------------ +-export_type([tab/0, tid/0, match_spec/0]). --type tab() :: atom() | tid(). +%%----------------------------------------------------------------------------- --type ext_info() :: 'md5sum' | 'object_count'. --type protection() :: 'private' | 'protected' | 'public'. --type type() :: 'bag' | 'duplicate_bag' | 'ordered_set' | 'set'. +-type tab() :: atom() | tid(). --type table_info() :: {'name', atom()} - | {'type', type()} - | {'protection', protection()} - | {'named_table', boolean()} - | {'keypos', non_neg_integer()} - | {'size', non_neg_integer()} - | {'extended_info', [ext_info()]} - | {'version', {non_neg_integer(), non_neg_integer()}}. +%% a similar definition is also in erl_types +-opaque tid() :: integer(). %% these ones are also defined in erl_bif_types -type match_pattern() :: atom() | tuple(). --type match_specs() :: [{match_pattern(), [_], [_]}]. +-type match_spec() :: [{match_pattern(), [_], [_]}]. -%%------------------------------------------------------------------------------ +%%----------------------------------------------------------------------------- %% The following functions used to be found in this module, but %% are now BIFs (i.e. implemented in C). @@ -81,6 +73,7 @@ %% insert/2 %% is_compiled_ms/1 %% last/1 +%% member/2 %% next/2 %% prev/2 %% rename/2 @@ -96,11 +89,14 @@ %% 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 %% -opaque comp_match_spec() :: any(). %% this one is REALLY opaque @@ -114,7 +110,9 @@ match_spec_run(List, CompiledMS) -> | {tab(),integer(),integer(),binary(),list(),integer()} | {tab(),_,_,integer(),binary(),list(),integer(),integer()}. --spec repair_continuation(continuation(), match_specs()) -> continuation(). +-spec repair_continuation(Continuation, MatchSpec) -> Continuation when + Continuation :: continuation(), + MatchSpec :: match_spec(). %% $end_of_table is an allowed continuation in ets... repair_continuation('$end_of_table', _) -> @@ -148,7 +146,9 @@ repair_continuation(Untouched = {Table,N1,N2,Bin,L,N3}, MS) {Table,N1,N2,ets:match_spec_compile(MS),L,N3} end. --spec fun2ms(function()) -> match_specs(). +-spec fun2ms(LiteralFun) -> MatchSpec when + LiteralFun :: function(), + MatchSpec :: match_spec(). fun2ms(ShellFun) when is_function(ShellFun) -> %% Check that this is really a shell fun... @@ -172,7 +172,13 @@ fun2ms(ShellFun) when is_function(ShellFun) -> shell]}}) end. --spec foldl(fun((_, term()) -> term()), term(), tab()) -> term(). +-spec foldl(Function, Acc0, Tab) -> Acc1 when + Function :: fun((Element :: term(), AccIn) -> AccOut), + Tab :: tab(), + Acc0 :: term(), + Acc1 :: term(), + AccIn :: term(), + AccOut :: term(). foldl(F, Accu, T) -> ets:safe_fixtable(T, true), @@ -193,7 +199,13 @@ do_foldl(F, Accu0, Key, T) -> ets:next(T, Key), T) end. --spec foldr(fun((_, term()) -> term()), term(), tab()) -> term(). +-spec foldr(Function, Acc0, Tab) -> Acc1 when + Function :: fun((Element :: term(), AccIn) -> AccOut), + Tab :: tab(), + Acc0 :: term(), + Acc1 :: term(), + AccIn :: term(), + AccOut :: term(). foldr(F, Accu, T) -> ets:safe_fixtable(T, true), @@ -214,7 +226,9 @@ do_foldr(F, Accu0, Key, T) -> ets:prev(T, Key), T) end. --spec from_dets(tab(), dets:tab_name()) -> 'true'. +-spec from_dets(Tab, DetsTab) -> 'true' when + Tab :: tab(), + DetsTab :: dets:tab_name(). from_dets(EtsTable, DetsTable) -> case (catch dets:to_ets(DetsTable, EtsTable)) of @@ -230,7 +244,9 @@ from_dets(EtsTable, DetsTable) -> erlang:error(Unexpected,[EtsTable,DetsTable]) end. --spec to_dets(tab(), dets:tab_name()) -> tab(). +-spec to_dets(Tab, DetsTab) -> DetsTab when + Tab :: tab(), + DetsTab :: dets:tab_name(). to_dets(EtsTable, DetsTable) -> case (catch dets:from_ets(DetsTable, EtsTable)) of @@ -246,8 +262,11 @@ to_dets(EtsTable, DetsTable) -> erlang:error(Unexpected,[EtsTable,DetsTable]) end. --spec test_ms(tuple(), match_specs()) -> - {'ok', term()} | {'error', [{'warning'|'error', string()}]}. +-spec test_ms(Tuple, MatchSpec) -> {'ok', Result} | {'error', Errors} when + Tuple :: tuple(), + MatchSpec :: match_spec(), + Result :: term(), + Errors :: [{'warning'|'error', string()}]. test_ms(Term, MS) -> case erlang:match_spec_test(Term, MS, table) of @@ -257,7 +276,11 @@ test_ms(Term, MS) -> Error end. --spec init_table(tab(), fun(('read' | 'close') -> term())) -> 'true'. +-spec init_table(Tab, InitFun) -> 'true' when + Tab :: tab(), + InitFun :: fun((Arg) -> Res), + Arg :: 'read' | 'close', + Res :: 'end_of_input' | {Objects :: [term()], InitFun} | term(). init_table(Table, Fun) -> ets:delete_all_objects(Table), @@ -282,7 +305,9 @@ init_table_sub(Table, [H|T]) -> ets:insert(Table, H), init_table_sub(Table, T). --spec match_delete(tab(), match_pattern()) -> 'true'. +-spec match_delete(Tab, Pattern) -> 'true' when + Tab :: tab(), + Pattern :: match_pattern(). match_delete(Table, Pattern) -> ets:select_delete(Table, [{Pattern,[],[true]}]), @@ -290,7 +315,9 @@ match_delete(Table, Pattern) -> %% Produce a list of tuples from a table --spec tab2list(tab()) -> [tuple()]. +-spec tab2list(Tab) -> [Object] when + Tab :: tab(), + Object :: tuple(). tab2list(T) -> ets:match_object(T, '_'). @@ -329,15 +356,21 @@ do_filter(Tab, Key, F, A, Ack) -> md5sum = false :: boolean() }). --type fname() :: string() | atom(). --type t2f_option() :: {'extended_info', [ext_info()]}. - --spec tab2file(tab(), fname()) -> 'ok' | {'error', term()}. +-spec tab2file(Tab, Filename) -> 'ok' | {'error', Reason} when + Tab :: tab(), + Filename :: file:name(), + Reason :: term(). tab2file(Tab, File) -> tab2file(Tab, File, []). --spec tab2file(tab(), fname(), [t2f_option()]) -> 'ok' | {'error', term()}. +-spec tab2file(Tab, Filename, Options) -> 'ok' | {'error', Reason} when + Tab :: tab(), + Filename :: file:name(), + Options :: [Option], + Option :: {'extended_info', [ExtInfo]}, + ExtInfo :: 'md5sum' | 'object_count', + Reason :: term(). tab2file(Tab, File, Options) -> try @@ -496,18 +529,24 @@ parse_ft_info_options(_,Malformed) -> %% Opt := {verify,boolean()} %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% --type f2t_option() :: {'verify', boolean()}. - --spec file2tab(fname()) -> {'ok', tab()} | {'error', term()}. +-spec file2tab(Filename) -> {'ok', Tab} | {'error', Reason} when + Filename :: file:name(), + Tab :: tab(), + Reason :: term(). file2tab(File) -> file2tab(File, []). --spec file2tab(fname(), [f2t_option()]) -> {'ok', tab()} | {'error', term()}. +-spec file2tab(Filename, Options) -> {'ok', Tab} | {'error', Reason} when + Filename :: file:name(), + Tab :: tab(), + Options :: [Option], + Option :: {'verify', boolean()}, + Reason :: term(). file2tab(File, Opts) -> try - {ok,Verify} = parse_f2t_opts(Opts,false), + {ok,Verify,TabArg} = parse_f2t_opts(Opts,false,[]), Name = make_ref(), {ok, Major, Minor, FtOptions, MD5State, FullHeader, DLContext} = case disk_log:open([{name, Name}, @@ -535,7 +574,7 @@ file2tab(File, Opts) -> true -> ok end, - {ok, Tab, HeadCount} = create_tab(FullHeader), + {ok, Tab, HeadCount} = create_tab(FullHeader, TabArg), StrippedOptions = case Verify of true -> @@ -622,14 +661,14 @@ do_read_and_verify(ReadFun,InitState,Tab,FtOptions,HeadCount,Verify) -> end, {ok,Tab}; {ok,{FinalMD5State,FinalCount,['$end_of_table',LastInfo],_}} -> - ECount = case lists:keysearch(count,1,LastInfo) of - {value,{count,N}} -> + ECount = case lists:keyfind(count,1,LastInfo) of + {count,N} -> N; _ -> false end, - EMD5 = case lists:keysearch(md5,1,LastInfo) of - {value,{md5,M}} -> + EMD5 = case lists:keyfind(md5,1,LastInfo) of + {md5,M} -> M; _ -> false @@ -671,15 +710,17 @@ do_read_and_verify(ReadFun,InitState,Tab,FtOptions,HeadCount,Verify) -> {ok,Tab} end. -parse_f2t_opts([],Verify) -> - {ok,Verify}; -parse_f2t_opts([{verify, true}|T],_OV) -> - parse_f2t_opts(T,true); -parse_f2t_opts([{verify,false}|T],OV) -> - parse_f2t_opts(T,OV); -parse_f2t_opts([Unexpected|_],_) -> +parse_f2t_opts([],Verify,Tab) -> + {ok,Verify,Tab}; +parse_f2t_opts([{verify, true}|T],_OV,Tab) -> + parse_f2t_opts(T,true,Tab); +parse_f2t_opts([{verify,false}|T],OV,Tab) -> + parse_f2t_opts(T,OV,Tab); +parse_f2t_opts([{table,Tab}|T],OV,[]) -> + parse_f2t_opts(T,OV,Tab); +parse_f2t_opts([Unexpected|_],_,_) -> throw({unknown_option,Unexpected}); -parse_f2t_opts(Malformed,_) -> +parse_f2t_opts(Malformed,_,_) -> throw({malformed_option,Malformed}). count_mandatory([]) -> @@ -742,22 +783,21 @@ get_header_data(Name,true) -> false -> throw(badfile); true -> - Major = case lists:keysearch(major,1,L) of - {value,{major,Maj}} -> + Major = case lists:keyfind(major,1,L) of + {major,Maj} -> Maj; _ -> 0 end, - Minor = case lists:keysearch(minor,1,L) of - {value,{minor,Min}} -> + Minor = case lists:keyfind(minor,1,L) of + {minor,Min} -> Min; _ -> 0 end, FtOptions = - case lists:keysearch(extended_info,1,L) of - {value,{extended_info,I}} - when is_list(I) -> + case lists:keyfind(extended_info,1,L) of + {extended_info,I} when is_list(I) -> #filetab_options { object_count = @@ -786,29 +826,28 @@ get_header_data(Name,true) -> end; get_header_data(Name, false) -> - case wrap_chunk(Name,start,1,false) of + case wrap_chunk(Name, start, 1, false) of {C,[Tup]} when is_tuple(Tup) -> L = tuple_to_list(Tup), case verify_header_mandatory(L) of false -> throw(badfile); true -> - Major = case lists:keysearch(major_version,1,L) of - {value,{major_version,Maj}} -> + Major = case lists:keyfind(major_version, 1, L) of + {major_version, Maj} -> Maj; _ -> 0 end, - Minor = case lists:keysearch(minor_version,1,L) of - {value,{minor_version,Min}} -> + Minor = case lists:keyfind(minor_version, 1, L) of + {minor_version, Min} -> Min; _ -> 0 end, FtOptions = - case lists:keysearch(extended_info,1,L) of - {value,{extended_info,I}} - when is_list(I) -> + case lists:keyfind(extended_info, 1, L) of + {extended_info, I} when is_list(I) -> #filetab_options { object_count = @@ -825,25 +864,26 @@ get_header_data(Name, false) -> throw(badfile) end. -md5_and_convert([],MD5State,Count) -> +md5_and_convert([], MD5State, Count) -> {[],MD5State,Count,[]}; -md5_and_convert([H|T],MD5State,Count) when is_binary(H) -> +md5_and_convert([H|T], MD5State, Count) when is_binary(H) -> case (catch binary_to_term(H)) of {'EXIT', _} -> md5_and_convert(T,MD5State,Count); - ['$end_of_table',Dat] -> - {[],MD5State,Count,['$end_of_table',Dat]}; + ['$end_of_table',_Dat] = L -> + {[],MD5State,Count,L}; Term -> - X = erlang:md5_update(MD5State,H), - {Rest,NewMD5,NewCount,NewLast} = md5_and_convert(T,X,Count+1), + X = erlang:md5_update(MD5State, H), + {Rest,NewMD5,NewCount,NewLast} = md5_and_convert(T, X, Count+1), {[Term | Rest],NewMD5,NewCount,NewLast} end. -scan_for_endinfo([],Count) -> + +scan_for_endinfo([], Count) -> {[],Count,[]}; -scan_for_endinfo([['$end_of_table',Dat]],Count) -> +scan_for_endinfo([['$end_of_table',Dat]], Count) -> {['$end_of_table',Dat],Count,[]}; -scan_for_endinfo([Term|T],Count) -> - {NewLast,NCount,Rest} = scan_for_endinfo(T,Count+1), +scan_for_endinfo([Term|T], Count) -> + {NewLast,NCount,Rest} = scan_for_endinfo(T, Count+1), {NewLast,NCount,[Term | Rest]}. load_table(ReadFun, State, Tab) -> @@ -852,23 +892,32 @@ load_table(ReadFun, State, Tab) -> [] -> {ok,NewState}; List -> - ets:insert(Tab,List), - load_table(ReadFun,NewState,Tab) + ets:insert(Tab, List), + load_table(ReadFun, NewState, Tab) end. -create_tab(I) -> - {value, {name, Name}} = lists:keysearch(name, 1, I), - {value, {type, Type}} = lists:keysearch(type, 1, I), - {value, {protection, P}} = lists:keysearch(protection, 1, I), - {value, {named_table, Val}} = lists:keysearch(named_table, 1, I), - {value, {keypos, Kp}} = lists:keysearch(keypos, 1, I), - {value, {size, Sz}} = lists:keysearch(size, 1, I), - try - Tab = ets:new(Name, [Type, P, {keypos, Kp} | named_table(Val)]), - {ok, Tab, Sz} - catch - _:_ -> - throw(cannot_create_table) +create_tab(I, TabArg) -> + {name, Name} = lists:keyfind(name, 1, I), + {type, Type} = lists:keyfind(type, 1, I), + {protection, P} = lists:keyfind(protection, 1, I), + {named_table, Val} = lists:keyfind(named_table, 1, I), + {keypos, _Kp} = Keypos = lists:keyfind(keypos, 1, I), + {size, Sz} = lists:keyfind(size, 1, I), + Comp = case lists:keyfind(compressed, 1, I) of + {compressed, true} -> [compressed]; + {compressed, false} -> []; + false -> [] + end, + case TabArg of + [] -> + try + Tab = ets:new(Name, [Type, P, Keypos] ++ named_table(Val) ++ Comp), + {ok, Tab, Sz} + catch _:_ -> + throw(cannot_create_table) + end; + _ -> + {ok, TabArg, Sz} end. named_table(true) -> [named_table]; @@ -880,7 +929,22 @@ named_table(false) -> []. %% information %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% --spec tabfile_info(fname()) -> {'ok', [table_info()]} | {'error', term()}. +-spec tabfile_info(Filename) -> {'ok', TableInfo} | {'error', Reason} when + Filename :: file:name(), + TableInfo :: [InfoItem], + InfoItem :: {'name', atom()} + | {'type', Type} + | {'protection', Protection} + | {'named_table', boolean()} + | {'keypos', non_neg_integer()} + | {'size', non_neg_integer()} + | {'extended_info', [ExtInfo]} + | {'version', {Major :: non_neg_integer(), + Minor :: non_neg_integer()}}, + ExtInfo :: 'md5sum' | 'object_count', + Type :: 'bag' | 'duplicate_bag' | 'ordered_set' | 'set', + Protection :: 'private' | 'protected' | 'public', + Reason :: term(). tabfile_info(File) when is_list(File) ; is_atom(File) -> try @@ -905,9 +969,9 @@ tabfile_info(File) when is_list(File) ; is_atom(File) -> {value, Val} = lists:keysearch(named_table, 1, FullHeader), {value, Kp} = lists:keysearch(keypos, 1, FullHeader), {value, Sz} = lists:keysearch(size, 1, FullHeader), - Ei = case lists:keysearch(extended_info, 1, FullHeader) of - {value, Ei0} -> Ei0; - _ -> {extended_info, []} + Ei = case lists:keyfind(extended_info, 1, FullHeader) of + false -> {extended_info, []}; + Ei0 -> Ei0 end, {ok, [N,Type,P,Val,Kp,Sz,Ei,{version,{Major,Minor}}]} catch @@ -917,20 +981,22 @@ tabfile_info(File) when is_list(File) ; is_atom(File) -> {error,ExReason} end. --type qlc__query_handle() :: term(). %% XXX: belongs in 'qlc' - --type num_objects() :: 'default' | pos_integer(). --type trav_method() :: 'first_next' | 'last_prev' - | 'select' | {'select', match_specs()}. --type table_option() :: {'n_objects', num_objects()} - | {'traverse', trav_method()}. - --spec table(tab()) -> qlc__query_handle(). +-spec table(Tab) -> QueryHandle when + Tab :: tab(), + QueryHandle :: qlc:query_handle(). table(Tab) -> table(Tab, []). --spec table(tab(), table_option() | [table_option()]) -> qlc__query_handle(). +-spec table(Tab, Options) -> QueryHandle when + Tab :: tab(), + QueryHandle :: qlc:query_handle(), + Options :: [Option] | Option, + Option :: {'n_objects', NObjects} + | {'traverse', TraverseMethod}, + NObjects :: 'default' | pos_integer(), + TraverseMethod :: 'first_next' | 'last_prev' + | 'select' | {'select', MatchSpec :: match_spec()}. table(Tab, Opts) -> case options(Opts, [traverse, n_objects]) of @@ -1021,21 +1087,20 @@ options(Option, Keys) -> options([Option], Keys, []). options(Options, [Key | Keys], L) when is_list(Options) -> - V = case lists:keysearch(Key, 1, Options) of - {value, {n_objects, default}} -> + V = case lists:keyfind(Key, 1, Options) of + {n_objects, default} -> {ok, default_option(Key)}; - {value, {n_objects, NObjs}} when is_integer(NObjs), - NObjs >= 1 -> + {n_objects, NObjs} when is_integer(NObjs), NObjs >= 1 -> {ok, NObjs}; - {value, {traverse, select}} -> + {traverse, select} -> {ok, select}; - {value, {traverse, {select, MS}}} -> - {ok, {select, MS}}; - {value, {traverse, first_next}} -> + {traverse, {select, _MS} = Select} -> + {ok, Select}; + {traverse, first_next} -> {ok, first_next}; - {value, {traverse, last_prev}} -> + {traverse, last_prev} -> {ok, last_prev}; - {value, {Key, _}} -> + {Key, _} -> badarg; false -> Default = default_option(Key), @@ -1121,7 +1186,8 @@ to_string(X) -> lists:flatten(io_lib:format("~p", [X])). %% view a specific table --spec i(tab()) -> 'ok'. +-spec i(Tab) -> 'ok' when + Tab :: tab(). i(Tab) -> i(Tab, 40). diff --git a/lib/stdlib/src/eval_bits.erl b/lib/stdlib/src/eval_bits.erl index 3671aecdcb..1ffa6ea328 100644 --- a/lib/stdlib/src/eval_bits.erl +++ b/lib/stdlib/src/eval_bits.erl @@ -2,7 +2,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1999-2009. All Rights Reserved. +%% Copyright Ericsson AB 1999-2011. 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 @@ -19,6 +19,8 @@ %% -module(eval_bits). +%% Avoid warning for local function error/1 clashing with autoimported BIF. +-compile({no_auto_import,[error/1]}). -export([expr_grp/3,expr_grp/5,match_bits/6, match_bits/7,bin_gen/6]). @@ -32,12 +34,12 @@ %% @type matchfun(). A closure which performs a match given a value, a %% pattern and an environment %% -%% @type field() represents a field in a "bin" +%% @type field(). Represents a field in a "bin". %%% Part 1: expression evaluation (binary construction) %% @spec expr_grp(Fields::[field()], Bindings::bindings(), -%% EvalFun::evalfun()) -> +%% EvalFun::evalfun(), term(), term()) -> %% {value, binary(), bindings()} %% %% @doc Returns a tuple with {value,Bin,Bs} where Bin is the binary @@ -190,9 +192,9 @@ bin_gen_field({bin_element,Line,VE,Size0,Options0}, end. %%% Part 3: binary pattern matching -%% @spec match_bits(Fields::[field()], Bin::binary() +%% @spec match_bits(Fields::[field()], Bin::binary(), %% GlobalEnv::bindings(), LocalEnv::bindings(), -%% MatchFun::matchfun(),EvalFun::evalfun()) -> +%% MatchFun::matchfun(),EvalFun::evalfun(), term()) -> %% {match, bindings()} %% @doc Used to perform matching. If the match succeeds a new %% environment is returned. If the match have some syntactic or diff --git a/lib/stdlib/src/file_sorter.erl b/lib/stdlib/src/file_sorter.erl index e21a0c88f3..3f31852afc 100644 --- a/lib/stdlib/src/file_sorter.erl +++ b/lib/stdlib/src/file_sorter.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2001-2010. All Rights Reserved. +%% Copyright Ericsson AB 2001-2011. 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,6 +18,8 @@ %% -module(file_sorter). +%% Avoid warning for local function error/2 clashing with autoimported BIF. +-compile({no_auto_import,[error/2]}). -export([sort/1, sort/2, sort/3, keysort/2, keysort/3, keysort/4, merge/2, merge/3, @@ -48,12 +50,68 @@ %%% Exported functions %%% +-export_type([reason/0]). + +-type(file_name() :: file:name()). +-type(file_names() :: [file:name()]). +-type(i_command() :: read | close). +-type(i_reply() :: end_of_input | {end_of_input, value()} + | {[object()], infun()} | input_reply()). +-type(infun() :: fun((i_command()) -> i_reply())). +-type(input() :: file_names() | infun()). +-type(input_reply() :: term()). +-type(o_command() :: {value, value()} | [object()] | close). +-type(o_reply() :: outfun() | output_reply()). +-type(object() :: term() | binary()). +-type(outfun() :: fun((o_command()) -> o_reply())). +-type(output() :: file_name() | outfun()). +-type(output_reply() :: term()). +-type(value() :: term()). + +-type(options() :: [option()] | option()). +-type(option() :: {compressed, boolean()} + | {header, header_length()} + | {format, format()} + | {no_files, no_files()} + | {order, order()} + | {size, size()} + | {tmpdir, tmp_directory()} + | {unique, boolean()}). +-type(format() :: binary_term | term | binary | format_fun()). +-type(format_fun() :: fun((binary()) -> term())). +-type(header_length() :: pos_integer()). +-type(key_pos() :: pos_integer() | [pos_integer()]). +-type(no_files() :: pos_integer()). % > 1 +-type(order() :: ascending | descending | order_fun()). +-type(order_fun() :: fun((term(), term()) -> boolean())). +-type(size() :: non_neg_integer()). +-type(tmp_directory() :: [] | file:name()). + +-type(reason() :: bad_object + | {bad_object, file_name()} + | {bad_term, file_name()} + | {file_error, file_name(), + file:posix() | badarg | system_limit} + | {premature_eof, file_name()}). + +-spec(sort(FileName) -> Reply when + FileName :: file_name(), + Reply :: ok | {error, reason()} | input_reply() | output_reply()). sort(FileName) -> sort([FileName], FileName). +-spec(sort(Input, Output) -> Reply when + Input :: input(), + Output :: output(), + Reply :: ok | {error, reason()} | input_reply() | output_reply()). sort(Input, Output) -> sort(Input, Output, []). +-spec(sort(Input, Output, Options) -> Reply when + Input :: input(), + Output :: output(), + Options :: options(), + Reply :: ok | {error, reason()} | input_reply() | output_reply()). sort(Input0, Output0, Options) -> case {is_input(Input0), maybe_output(Output0), options(Options)} of {{true,Input}, {true,Output}, #opts{}=Opts} -> @@ -62,12 +120,27 @@ sort(Input0, Output0, Options) -> badarg(culprit(tuple_to_list(T)), [Input0, Output0, Options]) end. +-spec(keysort(KeyPos, FileName) -> Reply when + KeyPos :: key_pos(), + FileName :: file_name(), + Reply :: ok | {error, reason()} | input_reply() | output_reply()). keysort(KeyPos, FileName) -> keysort(KeyPos, [FileName], FileName). +-spec(keysort(KeyPos, Input, Output) -> Reply when + KeyPos :: key_pos(), + Input :: input(), + Output :: output(), + Reply :: ok | {error, reason()} | input_reply() | output_reply()). keysort(KeyPos, Input, Output) -> keysort(KeyPos, Input, Output, []). +-spec(keysort(KeyPos, Input, Output, Options) -> Reply when + KeyPos :: key_pos(), + Input :: input(), + Output :: output(), + Options :: options(), + Reply :: ok | {error, reason()} | input_reply() | output_reply()). keysort(KeyPos, Input0, Output0, Options) -> R = case {is_keypos(KeyPos), is_input(Input0), maybe_output(Output0), options(Options)} of @@ -87,9 +160,18 @@ keysort(KeyPos, Input0, Output0, Options) -> badarg(culprit(O), [KeyPos, Input0, Output0, Options]) end. +-spec(merge(FileNames, Output) -> Reply when + FileNames :: file_names(), + Output :: output(), + Reply :: ok | {error, reason()} | output_reply()). merge(Files, Output) -> merge(Files, Output, []). +-spec(merge(FileNames, Output, Options) -> Reply when + FileNames :: file_names(), + Output :: output(), + Options :: options(), + Reply :: ok | {error, reason()} | output_reply()). merge(Files0, Output0, Options) -> case {is_files(Files0), maybe_output(Output0), options(Options)} of %% size not used @@ -99,9 +181,20 @@ merge(Files0, Output0, Options) -> badarg(culprit(tuple_to_list(T)), [Files0, Output0, Options]) end. +-spec(keymerge(KeyPos, FileNames, Output) -> Reply when + KeyPos :: key_pos(), + FileNames :: file_names(), + Output :: output(), + Reply :: ok | {error, reason()} | output_reply()). keymerge(KeyPos, Files, Output) -> keymerge(KeyPos, Files, Output, []). +-spec(keymerge(KeyPos, FileNames, Output, Options) -> Reply when + KeyPos :: key_pos(), + FileNames :: file_names(), + Output :: output(), + Options :: options(), + Reply :: ok | {error, reason()} | output_reply()). keymerge(KeyPos, Files0, Output0, Options) -> R = case {is_keypos(KeyPos), is_files(Files0), maybe_output(Output0), options(Options)} of @@ -121,9 +214,21 @@ keymerge(KeyPos, Files0, Output0, Options) -> badarg(culprit(O), [KeyPos, Files0, Output0, Options]) end. +-spec(check(FileName) -> Reply when + FileName :: file_name(), + Reply :: {ok, [Result]} | {error, reason()}, + Result :: {FileName, TermPosition, term()}, + TermPosition :: pos_integer()). check(FileName) -> check([FileName], []). +-spec(check(FileNames, Options) -> Reply when + FileNames :: file_names(), + Options :: options(), + Reply :: {ok, [Result]} | {error, reason()}, + Result :: {FileName, TermPosition, term()}, + FileName :: file_name(), + TermPosition :: pos_integer()). check(Files0, Options) -> case {is_files(Files0), options(Options)} of {{true,Files}, #opts{}=Opts} -> @@ -132,9 +237,23 @@ check(Files0, Options) -> badarg(culprit(tuple_to_list(T)), [Files0, Options]) end. +-spec(keycheck(KeyPos, FileName) -> Reply when + KeyPos :: key_pos(), + FileName :: file_name(), + Reply :: {ok, [Result]} | {error, reason()}, + Result :: {FileName, TermPosition, term()}, + TermPosition :: pos_integer()). keycheck(KeyPos, FileName) -> keycheck(KeyPos, [FileName], []). +-spec(keycheck(KeyPos, FileNames, Options) -> Reply when + KeyPos :: key_pos(), + FileNames :: file_names(), + Options :: options(), + Reply :: {ok, [Result]} | {error, reason()}, + Result :: {FileName, TermPosition, term()}, + FileName :: file_name(), + TermPosition :: pos_integer()). keycheck(KeyPos, Files0, Options) -> R = case {is_keypos(KeyPos), is_files(Files0), options(Options)} of {_, _, #opts{format = binary}} -> @@ -191,7 +310,7 @@ options([{format, Format} | L], Opts) when Format =:= binary; options([{format, binary_term} | L], Opts) -> options(L, Opts#opts{format = binary_term_fun()}); options([{size, Size} | L], Opts) when is_integer(Size), Size >= 0 -> - options(L, Opts#opts{size = max(Size, 1)}); + options(L, Opts#opts{size = erlang:max(Size, 1)}); options([{no_files, NoFiles} | L], Opts) when is_integer(NoFiles), NoFiles > 1 -> options(L, Opts#opts{no_files = NoFiles}); @@ -997,10 +1116,10 @@ close_read_fun(Fd, FileName, fsort) -> file:delete(FileName). read_objs(Fd, FileName, I, L, Bin0, Size0, LSz, W) -> - Max = max(Size0, ?CHUNKSIZE), + Max = erlang:max(Size0, ?CHUNKSIZE), BSz0 = byte_size(Bin0), Min = Size0 - BSz0 + W#w.hdlen, % Min > 0 - NoBytes = max(Min, Max), + NoBytes = erlang:max(Min, Max), case read(Fd, FileName, NoBytes, W) of {ok, Bin} -> BSz = byte_size(Bin), @@ -1180,9 +1299,6 @@ make_key2([Kp], T) -> make_key2([Kp | Kps], T) -> [element(Kp, T) | make_key2(Kps, T)]. -max(A, B) when A < B -> B; -max(A, _) -> A. - infun(W) -> W1 = W#w{in = undefined}, try (W#w.in)(read) of diff --git a/lib/stdlib/src/filelib.erl b/lib/stdlib/src/filelib.erl index 74c5172137..d532cea187 100644 --- a/lib/stdlib/src/filelib.erl +++ b/lib/stdlib/src/filelib.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1997-2010. All Rights Reserved. +%% Copyright Ericsson AB 1997-2011. 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,8 @@ %% File utilities. +%% Avoid warning for local function error/1 clashing with autoimported BIF. +-compile({no_auto_import,[error/1]}). -export([wildcard/1, wildcard/2, is_dir/1, is_file/1, is_regular/1, compile_wildcard/1]). -export([fold_files/5, last_modified/1, file_size/1, ensure_dir/1]). @@ -38,68 +40,85 @@ erlang:error(UnUsUalVaRiAbLeNaMe) end). +-type filename() :: file:name(). +-type dirname() :: filename(). + %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% --spec wildcard(name()) -> [file:filename()]. +-spec wildcard(Wildcard) -> [file:filename()] when + Wildcard :: filename() | dirname(). wildcard(Pattern) when is_list(Pattern) -> ?HANDLE_ERROR(do_wildcard(Pattern, file)). --spec wildcard(name(), name() | atom()) -> [file:filename()]. -wildcard(Pattern, Cwd) when is_list(Pattern), is_list(Cwd) -> +-spec wildcard(Wildcard, Cwd) -> [file:filename()] when + Wildcard :: filename() | dirname(), + Cwd :: dirname(). +wildcard(Pattern, Cwd) when is_list(Pattern), (is_list(Cwd) or is_binary(Cwd)) -> ?HANDLE_ERROR(do_wildcard(Pattern, Cwd, file)); wildcard(Pattern, Mod) when is_list(Pattern), is_atom(Mod) -> ?HANDLE_ERROR(do_wildcard(Pattern, Mod)). --spec wildcard(name(), name(), atom()) -> [file:filename()]. +-spec wildcard(file:name(), file:name(), atom()) -> [file:filename()]. wildcard(Pattern, Cwd, Mod) - when is_list(Pattern), is_list(Cwd), is_atom(Mod) -> + when is_list(Pattern), (is_list(Cwd) or is_binary(Cwd)), is_atom(Mod) -> ?HANDLE_ERROR(do_wildcard(Pattern, Cwd, Mod)). --spec is_dir(name()) -> boolean(). +-spec is_dir(Name) -> boolean() when + Name :: filename() | dirname(). is_dir(Dir) -> do_is_dir(Dir, file). --spec is_dir(name(), atom()) -> boolean(). +-spec is_dir(file:name(), atom()) -> boolean(). is_dir(Dir, Mod) when is_atom(Mod) -> do_is_dir(Dir, Mod). --spec is_file(name()) -> boolean(). +-spec is_file(Name) -> boolean() when + Name :: filename() | dirname(). is_file(File) -> do_is_file(File, file). --spec is_file(name(), atom()) -> boolean(). +-spec is_file(file:name(), atom()) -> boolean(). is_file(File, Mod) when is_atom(Mod) -> do_is_file(File, Mod). --spec is_regular(name()) -> boolean(). +-spec is_regular(Name) -> boolean() when + Name :: filename(). is_regular(File) -> do_is_regular(File, file). --spec is_regular(name(), atom()) -> boolean(). +-spec is_regular(file:name(), atom()) -> boolean(). is_regular(File, Mod) when is_atom(Mod) -> do_is_regular(File, Mod). --spec fold_files(name(), string(), boolean(), fun((_,_) -> _), _) -> _. +-spec fold_files(Dir, RegExp, Recursive, Fun, AccIn) -> AccOut when + Dir :: dirname(), + RegExp :: string(), + Recursive :: boolean(), + Fun :: fun((F :: file:filename(), AccIn) -> AccOut), + AccIn :: term(), + AccOut :: term(). fold_files(Dir, RegExp, Recursive, Fun, Acc) -> do_fold_files(Dir, RegExp, Recursive, Fun, Acc, file). --spec fold_files(name(), string(), boolean(), fun((_,_) -> _), _, atom()) -> _. +-spec fold_files(file:name(), string(), boolean(), fun((_,_) -> _), _, atom()) -> _. fold_files(Dir, RegExp, Recursive, Fun, Acc, Mod) when is_atom(Mod) -> do_fold_files(Dir, RegExp, Recursive, Fun, Acc, Mod). --spec last_modified(name()) -> date_time() | 0. +-spec last_modified(Name) -> file:date_time() | 0 when + Name :: filename() | dirname(). last_modified(File) -> do_last_modified(File, file). --spec last_modified(name(), atom()) -> date_time() | 0. +-spec last_modified(file:name(), atom()) -> file:date_time() | 0. last_modified(File, Mod) when is_atom(Mod) -> do_last_modified(File, Mod). --spec file_size(name()) -> non_neg_integer(). +-spec file_size(Filename) -> non_neg_integer() when + Filename :: filename(). file_size(File) -> do_file_size(File, file). --spec file_size(name(), atom()) -> non_neg_integer(). +-spec file_size(file:name(), atom()) -> non_neg_integer(). file_size(File, Mod) when is_atom(Mod) -> do_file_size(File, Mod). @@ -116,7 +135,7 @@ do_wildcard_comp({compiled_wildcard,{exists,File}}, Mod) -> do_wildcard_comp({compiled_wildcard,[Base|Rest]}, Mod) -> do_wildcard_1([Base], Rest, Mod). -do_wildcard(Pattern, Cwd, Mod) when is_list(Pattern), is_list(Cwd) -> +do_wildcard(Pattern, Cwd, Mod) when is_list(Pattern), (is_list(Cwd) or is_binary(Cwd)) -> do_wildcard_comp(do_compile_wildcard(Pattern), Cwd, Mod). do_wildcard_comp({compiled_wildcard,{exists,File}}, Cwd, Mod) -> @@ -125,9 +144,18 @@ do_wildcard_comp({compiled_wildcard,{exists,File}}, Cwd, Mod) -> _ -> [] end; do_wildcard_comp({compiled_wildcard,[current|Rest]}, Cwd0, Mod) -> - Cwd = filename:join([Cwd0]), %Slash away redundant slashes. - PrefixLen = length(Cwd)+1, - [lists:nthtail(PrefixLen, N) || N <- do_wildcard_1([Cwd], Rest, Mod)]; + {Cwd,PrefixLen} = case filename:join([Cwd0]) of + Bin when is_binary(Bin) -> {Bin,byte_size(Bin)+1}; + Other -> {Other,length(Other)+1} + end, %Slash away redundant slashes. + [ + if + is_binary(N) -> + <<_:PrefixLen/binary,Res/binary>> = N, + Res; + true -> + lists:nthtail(PrefixLen, N) + end || N <- do_wildcard_1([Cwd], Rest, Mod)]; do_wildcard_comp({compiled_wildcard,[Base|Rest]}, _Cwd, Mod) -> do_wildcard_1([Base], Rest, Mod). @@ -164,36 +192,44 @@ do_is_regular(File, Mod) -> %% If <Recursive> is true all sub-directories to <Dir> are processed do_fold_files(Dir, RegExp, Recursive, Fun, Acc, Mod) -> - {ok, Re1} = re:compile(RegExp), - do_fold_files1(Dir, Re1, Recursive, Fun, Acc, Mod). + {ok, Re1} = re:compile(RegExp,[unicode]), + do_fold_files1(Dir, Re1, RegExp, Recursive, Fun, Acc, Mod). -do_fold_files1(Dir, RegExp, Recursive, Fun, Acc, Mod) -> +do_fold_files1(Dir, RegExp, OrigRE, Recursive, Fun, Acc, Mod) -> case eval_list_dir(Dir, Mod) of - {ok, Files} -> do_fold_files2(Files, Dir, RegExp, Recursive, Fun, Acc, Mod); + {ok, Files} -> do_fold_files2(Files, Dir, RegExp, OrigRE, + Recursive, Fun, Acc, Mod); {error, _} -> Acc end. -do_fold_files2([], _Dir, _RegExp, _Recursive, _Fun, Acc, _Mod) -> +%% OrigRE is not to be compiled as it's for non conforming filenames, +%% i.e. for filenames that does not comply to the current encoding, which should +%% be very rare. We use it only in those cases and do not want to precompile. +do_fold_files2([], _Dir, _RegExp, _OrigRE, _Recursive, _Fun, Acc, _Mod) -> Acc; -do_fold_files2([File|T], Dir, RegExp, Recursive, Fun, Acc0, Mod) -> +do_fold_files2([File|T], Dir, RegExp, OrigRE, Recursive, Fun, Acc0, Mod) -> FullName = filename:join(Dir, File), case do_is_regular(FullName, Mod) of true -> - case re:run(File, RegExp, [{capture,none}]) of + case (catch re:run(File, if is_binary(File) -> OrigRE; + true -> RegExp end, + [{capture,none}])) of match -> Acc = Fun(FullName, Acc0), - do_fold_files2(T, Dir, RegExp, Recursive, Fun, Acc, Mod); + do_fold_files2(T, Dir, RegExp, OrigRE, Recursive, Fun, Acc, Mod); + {'EXIT',_} -> + do_fold_files2(T, Dir, RegExp, OrigRE, Recursive, Fun, Acc0, Mod); nomatch -> - do_fold_files2(T, Dir, RegExp, Recursive, Fun, Acc0, Mod) + do_fold_files2(T, Dir, RegExp, OrigRE, Recursive, Fun, Acc0, Mod) end; false -> case Recursive andalso do_is_dir(FullName, Mod) of true -> - Acc1 = do_fold_files1(FullName, RegExp, Recursive, + Acc1 = do_fold_files1(FullName, RegExp, OrigRE, Recursive, Fun, Acc0, Mod), - do_fold_files2(T, Dir, RegExp, Recursive, Fun, Acc1, Mod); + do_fold_files2(T, Dir, RegExp, OrigRE, Recursive, Fun, Acc1, Mod); false -> - do_fold_files2(T, Dir, RegExp, Recursive, Fun, Acc0, Mod) + do_fold_files2(T, Dir, RegExp, OrigRE, Recursive, Fun, Acc0, Mod) end end. @@ -218,7 +254,9 @@ do_file_size(File, Mod) -> %% +type X = filename() | dirname() %% ensures that the directory name required to create D exists --spec ensure_dir(name()) -> 'ok' | {'error', posix()}. +-spec ensure_dir(Name) -> 'ok' | {'error', Reason} when + Name :: filename() | dirname(), + Reason :: file:posix(). ensure_dir("/") -> ok; ensure_dir(F) -> @@ -266,6 +304,13 @@ do_wildcard_3(Base, [Pattern|Rest], Result, Mod) -> do_wildcard_3(Base, [], Result, _Mod) -> [Base|Result]. +wildcard_4(Pattern, [File|Rest], Base, Result) when is_binary(File) -> + case wildcard_5(Pattern, binary_to_list(File)) of + true -> + wildcard_4(Pattern, Rest, Base, [join(Base, File)|Result]); + false -> + wildcard_4(Pattern, Rest, Base, Result) + end; wildcard_4(Pattern, [File|Rest], Base, Result) -> case wildcard_5(Pattern, File) of true -> diff --git a/lib/stdlib/src/filename.erl b/lib/stdlib/src/filename.erl index cd26b2e219..1cb9e4a25e 100644 --- a/lib/stdlib/src/filename.erl +++ b/lib/stdlib/src/filename.erl @@ -1,19 +1,19 @@ %% %% %CopyrightBegin% -%% -%% Copyright Ericsson AB 1997-2009. All Rights Reserved. -%% +%% +%% Copyright Ericsson AB 1997-2011. 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 %% compliance with the License. You should have received a copy of the %% Erlang Public License along with this software. If not, it can be %% retrieved online at http://www.erlang.org/. -%% +%% %% Software distributed under the License is distributed on an "AS IS" %% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See %% the License for the specific language governing rights and limitations %% under the License. -%% +%% %% %CopyrightEnd% %% -module(filename). @@ -41,6 +41,9 @@ -include_lib("kernel/include/file.hrl"). +-define(IS_DRIVELETTER(Letter),(((Letter >= $A) andalso (Letter =< $Z)) orelse + ((Letter >= $a) andalso (Letter =< $z)))). + %% Converts a relative filename to an absolute filename %% or the filename itself if it already is an absolute filename %% Note that no attempt is made to create the most beatiful @@ -57,12 +60,21 @@ %% (for Unix) : absname("/") -> "/" %% (for WIN32): absname("/") -> "D:/" --spec absname(name()) -> string(). + +-spec absname(Filename) -> file:filename() when + Filename :: file:name(). absname(Name) -> {ok, Cwd} = file:get_cwd(), absname(Name, Cwd). --spec absname(name(), string()) -> string(). +-spec absname(Filename, Dir) -> file:filename() when + Filename :: file:name(), + Dir :: file:filename(). +absname(Name, AbsBase) when is_binary(Name), is_list(AbsBase) -> + absname(Name,filename_string_to_binary(AbsBase)); +absname(Name, AbsBase) when is_list(Name), is_binary(AbsBase) -> + absname(filename_string_to_binary(Name),AbsBase); + absname(Name, AbsBase) -> case pathtype(Name) of relative -> @@ -77,6 +89,20 @@ absname(Name, AbsBase) -> %% Handles volumerelative names (on Windows only). +absname_vr([<<"/">>|Rest1], [Volume|_], _AbsBase) -> + %% Absolute path on current drive. + join([Volume|Rest1]); +absname_vr([<<X, $:>>|Rest1], [<<X,_/binary>>|_], AbsBase) -> + %% Relative to current directory on current drive. + absname(join(Rest1), AbsBase); +absname_vr([<<X, $:>>|Name], _, _AbsBase) -> + %% Relative to current directory on another drive. + Dcwd = + case file:get_cwd([X, $:]) of + {ok, Dir} -> filename_string_to_binary(Dir); + {error, _} -> <<X, $:, $/>> + end, + absname(join(Name), Dcwd); absname_vr(["/"|Rest1], [Volume|_], _AbsBase) -> %% Absolute path on current drive. join([Volume|Rest1]); @@ -92,41 +118,15 @@ absname_vr([[X, $:]|Name], _, _AbsBase) -> end, absname(join(Name), Dcwd). -%% Joins a relative filename to an absolute base. For VxWorks the -%% resulting name is fixed to minimize the length by collapsing -%% ".." directories. -%% For other systems this is just a join/2, but assumes that +%% Joins a relative filename to an absolute base. +%% This is just a join/2, but assumes that %% AbsBase must be absolute and Name must be relative. --spec absname_join(string(), name()) -> string(). +-spec absname_join(Dir, Filename) -> file:filename() when + Dir :: file:filename(), + Filename :: file:name(). absname_join(AbsBase, Name) -> - case major_os_type() of - vxworks -> - absname_pretty(AbsBase, split(Name), lists:reverse(split(AbsBase))); - _Else -> - join(AbsBase, flatten(Name)) - end. - -%% Handles absolute filenames for VxWorks - these are 'pretty-printed', -%% since a C function call chdir("/erlang/lib/../bin") really sets -%% cwd to '/erlang/lib/../bin' which also works, but the long term -%% effect is potentially not so good ... -%% -%% absname_pretty("../bin", "/erlang/lib") -> "/erlang/bin" -%% absname_pretty("../../../..", "/erlang") -> "/erlang" - -absname_pretty(Abspath, Relpath, []) -> - %% AbsBase _must_ begin with a vxworks device name - {device, _Rest, Dev} = vxworks_first(Abspath), - absname_pretty(Abspath, Relpath, [lists:reverse(Dev)]); -absname_pretty(_Abspath, [], AbsBase) -> - join(lists:reverse(AbsBase)); -absname_pretty(Abspath, [[$.]|Rest], AbsBase) -> - absname_pretty(Abspath, Rest, AbsBase); -absname_pretty(Abspath, [[$.,$.]|Rest], [_|AbsRest]) -> - absname_pretty(Abspath, Rest, AbsRest); -absname_pretty(Abspath, [First|Rest], AbsBase) -> - absname_pretty(Abspath, Rest, [First|AbsBase]). + join(AbsBase, flatten(Name)). %% Returns the part of the filename after the last directory separator, %% or the filename itself if it has no separators. @@ -136,18 +136,41 @@ absname_pretty(Abspath, [First|Rest], AbsBase) -> %% basename("/usr/foo/") -> "foo" (trailing slashes ignored) %% basename("/") -> [] --spec basename(name()) -> string(). +-spec basename(Filename) -> file:filename() when + Filename :: file:name(). +basename(Name) when is_binary(Name) -> + case os:type() of + {win32,_} -> + win_basenameb(Name); + _ -> + basenameb(Name,[<<"/">>]) + end; + basename(Name0) -> Name = flatten(Name0), {DirSep2, DrvSep} = separators(), basename1(skip_prefix(Name, DrvSep), [], DirSep2). +win_basenameb(<<Letter,$:,Rest/binary>>) when ?IS_DRIVELETTER(Letter) -> + basenameb(Rest,[<<"/">>,<<"\\">>]); +win_basenameb(O) -> + basenameb(O,[<<"/">>,<<"\\">>]). +basenameb(Bin,Sep) -> + Parts = [ X || X <- binary:split(Bin,Sep,[global]), + X =/= <<>> ], + if + Parts =:= [] -> + <<>>; + true -> + lists:last(Parts) + end. + + + basename1([$/|[]], Tail, DirSep2) -> basename1([], Tail, DirSep2); basename1([$/|Rest], _Tail, DirSep2) -> basename1(Rest, [], DirSep2); -basename1([[_|_]=List|Rest], Tail, DirSep2) -> - basename1(List++Rest, Tail, DirSep2); basename1([DirSep2|Rest], Tail, DirSep2) when is_integer(DirSep2) -> basename1([$/|Rest], Tail, DirSep2); basename1([Char|Rest], Tail, DirSep2) when is_integer(Char) -> @@ -155,26 +178,11 @@ basename1([Char|Rest], Tail, DirSep2) when is_integer(Char) -> basename1([], Tail, _DirSep2) -> lists:reverse(Tail). -skip_prefix(Name, false) -> % No prefix for unix, but for VxWorks. - case major_os_type() of - vxworks -> - case vxworks_first(Name) of - {device, Rest, _Device} -> - Rest; - {not_device, _Rest, _First} -> - Name - end; - _Else -> - Name - end; -skip_prefix(Name, DrvSep) -> - skip_prefix1(Name, DrvSep). - -skip_prefix1([L, DrvSep|Name], DrvSep) when is_integer(L) -> +skip_prefix(Name, false) -> + Name; +skip_prefix([L, DrvSep|Name], DrvSep) when ?IS_DRIVELETTER(L) -> Name; -skip_prefix1([L], _) when is_integer(L) -> - [L]; -skip_prefix1(Name, _) -> +skip_prefix(Name, _) -> Name. %% Returns the last component of the filename, with the given @@ -190,7 +198,31 @@ skip_prefix1(Name, _) -> %% rootname(basename("xxx.jam")) -> "xxx" %% rootname(basename("xxx.erl")) -> "xxx" --spec basename(name(), name()) -> string(). +-spec basename(Filename, Ext) -> file:filename() when + Filename :: file:name(), + Ext :: file:name(). +basename(Name, Ext) when is_binary(Name), is_list(Ext) -> + basename(Name,filename_string_to_binary(Ext)); +basename(Name, Ext) when is_list(Name), is_binary(Ext) -> + basename(filename_string_to_binary(Name),Ext); +basename(Name, Ext) when is_binary(Name), is_binary(Ext) -> + BName = basename(Name), + LAll = byte_size(Name), + LN = byte_size(BName), + LE = byte_size(Ext), + case LN - LE of + Neg when Neg < 0 -> + BName; + Pos -> + StartLen = LAll - Pos - LE, + case Name of + <<_:StartLen/binary,Part:Pos/binary,Ext/binary>> -> + Part; + _Other -> + BName + end + end; + basename(Name0, Ext0) -> Name = flatten(Name0), Ext = flatten(Ext0), @@ -204,7 +236,7 @@ basename([$/|[]], Ext, Tail, DrvSep2) -> basename([], Ext, Tail, DrvSep2); basename([$/|Rest], Ext, _Tail, DrvSep2) -> basename(Rest, Ext, [], DrvSep2); -basename([$\\|Rest], Ext, Tail, DirSep2) when is_integer(DirSep2) -> +basename([DirSep2|Rest], Ext, Tail, DirSep2) when is_integer(DirSep2) -> basename([$/|Rest], Ext, Tail, DirSep2); basename([Char|Rest], Ext, Tail, DrvSep2) when is_integer(Char) -> basename(Rest, Ext, [Char|Tail], DrvSep2); @@ -216,24 +248,45 @@ basename([], _Ext, Tail, _DrvSep2) -> %% Example: dirname("/usr/src/kalle.erl") -> "/usr/src", %% dirname("kalle.erl") -> "." --spec dirname(name()) -> string(). +-spec dirname(Filename) -> file:filename() when + Filename :: file:name(). +dirname(Name) when is_binary(Name) -> + {Dsep,Drivesep} = separators(), + SList = case Dsep of + Sep when is_integer(Sep) -> + [ <<Sep>> ]; + _ -> + [] + end, + {XPart0,Dirs} = case Drivesep of + X when is_integer(X) -> + case Name of + <<DL,X,Rest/binary>> when ?IS_DRIVELETTER(DL) -> + {<<DL,X>>,Rest}; + _ -> + {<<>>,Name} + end; + _ -> + {<<>>,Name} + end, + Parts0 = binary:split(Dirs,[<<"/">>|SList],[global]), + %% Fairly short lists of parts, OK to reverse twice... + Parts = case Parts0 of + [] -> []; + _ -> lists:reverse(fstrip(tl(lists:reverse(Parts0)))) + end, + XPart = case {Parts,XPart0} of + {[],<<>>} -> + <<".">>; + _ -> + XPart0 + end, + dirjoin(Parts,XPart,<<"/">>); + dirname(Name0) -> Name = flatten(Name0), - case os:type() of - vxworks -> - {Devicep, Restname, FirstComp} = vxworks_first(Name), - case Devicep of - device -> - dirname(Restname, FirstComp, [], separators()); - _ -> - dirname(Name, [], [], separators()) - end; - _ -> - dirname(Name, [], [], separators()) - end. + dirname(Name, [], [], separators()). -dirname([[_|_]=List|Rest], Dir, File, Seps) -> - dirname(List++Rest, Dir, File, Seps); dirname([$/|Rest], Dir, File, Seps) -> dirname(Rest, File++Dir, [$/], Seps); dirname([DirSep|Rest], Dir, File, {DirSep,_}=Seps) when is_integer(DirSep) -> @@ -258,6 +311,26 @@ dirname([], [DrvSep,Dl], File, {_,DrvSep}) -> end; dirname([], Dir, _, _) -> lists:reverse(Dir). + +%% Compatibility with lists variant, remove trailing slashes +fstrip([<<>>,X|Y]) -> + fstrip([X|Y]); +fstrip(A) -> + A. + + +dirjoin([<<>>|T],Acc,Sep) -> + dirjoin1(T,<<Acc/binary,"/">>,Sep); +dirjoin(A,B,C) -> + dirjoin1(A,B,C). + +dirjoin1([],Acc,_) -> + Acc; +dirjoin1([One],Acc,_) -> + <<Acc/binary,One/binary>>; +dirjoin1([H|T],Acc,Sep) -> + dirjoin(T,<<Acc/binary,H/binary,Sep/binary>>,Sep). + %% Given a filename string, returns the file extension, %% including the period. Returns an empty list if there @@ -268,7 +341,30 @@ dirname([], Dir, _, _) -> %% %% On Windows: fn:dirname("\\usr\\src/kalle.erl") -> "/usr/src" --spec extension(name()) -> string(). +-spec extension(Filename) -> file:filename() when + Filename :: file:name(). +extension(Name) when is_binary(Name) -> + {Dsep,_} = separators(), + SList = case Dsep of + Sep when is_integer(Sep) -> + [ <<Sep>> ]; + _ -> + [] + end, + case binary:matches(Name,[<<".">>]) of + [] -> + <<>>; + List -> + {Pos,_} = lists:last(List), + <<_:Pos/binary,Part/binary>> = Name, + case binary:match(Part,[<<"/">>|SList]) of + nomatch -> + Part; + _ -> + <<>> + end + end; + extension(Name0) -> Name = flatten(Name0), extension(Name, [], major_os_type()). @@ -281,8 +377,6 @@ extension([$/|Rest], _Result, OsType) -> extension(Rest, [], OsType); extension([$\\|Rest], _Result, win32) -> extension(Rest, [], win32); -extension([$\\|Rest], _Result, vxworks) -> - extension(Rest, [], vxworks); extension([Char|Rest], Result, OsType) when is_integer(Char) -> extension(Rest, [Char|Result], OsType); extension([], Result, _OsType) -> @@ -290,23 +384,39 @@ extension([], Result, _OsType) -> %% Joins a list of filenames with directory separators. --spec join([string()]) -> string(). +-spec join(Components) -> file:filename() when + Components :: [file:filename()]. join([Name1, Name2|Rest]) -> join([join(Name1, Name2)|Rest]); join([Name]) when is_list(Name) -> join1(Name, [], [], major_os_type()); +join([Name]) when is_binary(Name) -> + join1b(Name, <<>>, [], major_os_type()); join([Name]) when is_atom(Name) -> join([atom_to_list(Name)]). %% Joins two filenames with directory separators. --spec join(string(), string()) -> string(). +-spec join(Name1, Name2) -> file:filename() when + Name1 :: file:filename(), + Name2 :: file:filename(). join(Name1, Name2) when is_list(Name1), is_list(Name2) -> OsType = major_os_type(), case pathtype(Name2) of relative -> join1(Name1, Name2, [], OsType); _Other -> join1(Name2, [], [], OsType) end; +join(Name1, Name2) when is_binary(Name1), is_list(Name2) -> + join(Name1,filename_string_to_binary(Name2)); +join(Name1, Name2) when is_list(Name1), is_binary(Name2) -> + join(filename_string_to_binary(Name1),Name2); +join(Name1, Name2) when is_binary(Name1), is_binary(Name2) -> + OsType = major_os_type(), + case pathtype(Name2) of + relative -> join1b(Name1, Name2, [], OsType); + _Other -> join1b(Name2, <<>>, [], OsType) + end; + join(Name1, Name2) when is_atom(Name1) -> join(atom_to_list(Name1), Name2); join(Name1, Name2) when is_atom(Name2) -> @@ -321,8 +431,6 @@ when is_integer(UcLetter), UcLetter >= $A, UcLetter =< $Z -> join1(Rest, RelativeName, [$:, UcLetter+$a-$A], win32); join1([$\\|Rest], RelativeName, Result, win32) -> join1([$/|Rest], RelativeName, Result, win32); -join1([$\\|Rest], RelativeName, Result, vxworks) -> - join1([$/|Rest], RelativeName, Result, vxworks); join1([$/|Rest], RelativeName, [$., $/|Result], OsType) -> join1(Rest, RelativeName, [$/|Result], OsType); join1([$/|Rest], RelativeName, [$/|Result], OsType) -> @@ -344,6 +452,26 @@ join1([Char|Rest], RelativeName, Result, OsType) when is_integer(Char) -> join1([Atom|Rest], RelativeName, Result, OsType) when is_atom(Atom) -> join1(atom_to_list(Atom)++Rest, RelativeName, Result, OsType). +join1b(<<UcLetter, $:, Rest/binary>>, RelativeName, [], win32) +when is_integer(UcLetter), UcLetter >= $A, UcLetter =< $Z -> + join1b(Rest, RelativeName, [$:, UcLetter+$a-$A], win32); +join1b(<<$\\,Rest/binary>>, RelativeName, Result, win32) -> + join1b(<<$/,Rest/binary>>, RelativeName, Result, win32); +join1b(<<$/,Rest/binary>>, RelativeName, [$., $/|Result], OsType) -> + join1b(Rest, RelativeName, [$/|Result], OsType); +join1b(<<$/,Rest/binary>>, RelativeName, [$/|Result], OsType) -> + join1b(Rest, RelativeName, [$/|Result], OsType); +join1b(<<>>, <<>>, Result, OsType) -> + list_to_binary(maybe_remove_dirsep(Result, OsType)); +join1b(<<>>, RelativeName, [$:|Rest], win32) -> + join1b(RelativeName, <<>>, [$:|Rest], win32); +join1b(<<>>, RelativeName, [$/|Result], OsType) -> + join1b(RelativeName, <<>>, [$/|Result], OsType); +join1b(<<>>, RelativeName, Result, OsType) -> + join1b(RelativeName, <<>>, [$/|Result], OsType); +join1b(<<Char,Rest/binary>>, RelativeName, Result, OsType) when is_integer(Char) -> + join1b(Rest, RelativeName, [Char|Result], OsType). + maybe_remove_dirsep([$/, $:, Letter], win32) -> [Letter, $:, $/]; maybe_remove_dirsep([$/], _) -> @@ -357,7 +485,13 @@ maybe_remove_dirsep(Name, _) -> %% a given base directory, which is is assumed to be normalised %% by a previous call to join/{1,2}. --spec append(string(), name()) -> string(). +-spec append(file:filename(), file:name()) -> file:filename(). +append(Dir, Name) when is_binary(Dir), is_binary(Name) -> + <<Dir/binary,$/:8,Name/binary>>; +append(Dir, Name) when is_binary(Dir) -> + append(Dir,filename_string_to_binary(Name)); +append(Dir, Name) when is_binary(Name) -> + append(filename_string_to_binary(Dir),Name); append(Dir, Name) -> Dir ++ [$/|Name]. @@ -373,22 +507,18 @@ append(Dir, Name) -> %% current working volume. (Windows only) %% Example: a:bar.erl, /temp/foo.erl --spec pathtype(name()) -> 'absolute' | 'relative' | 'volumerelative'. +-spec pathtype(Path) -> 'absolute' | 'relative' | 'volumerelative' when + Path :: file:name(). pathtype(Atom) when is_atom(Atom) -> pathtype(atom_to_list(Atom)); -pathtype(Name) when is_list(Name) -> +pathtype(Name) when is_list(Name) or is_binary(Name) -> case os:type() of {unix, _} -> unix_pathtype(Name); - {win32, _} -> win32_pathtype(Name); - vxworks -> case vxworks_first(Name) of - {device, _Rest, _Dev} -> - absolute; - _ -> - relative - end; - {ose,_} -> unix_pathtype(Name) + {win32, _} -> win32_pathtype(Name) end. +unix_pathtype(<<$/,_/binary>>) -> + absolute; unix_pathtype([$/|_]) -> absolute; unix_pathtype([List|Rest]) when is_list(List) -> @@ -404,6 +534,15 @@ win32_pathtype([Atom|Rest]) when is_atom(Atom) -> win32_pathtype(atom_to_list(Atom)++Rest); win32_pathtype([Char, List|Rest]) when is_list(List) -> win32_pathtype([Char|List++Rest]); +win32_pathtype(<<$/, $/, _/binary>>) -> absolute; +win32_pathtype(<<$\\, $/, _/binary>>) -> absolute; +win32_pathtype(<<$/, $\\, _/binary>>) -> absolute; +win32_pathtype(<<$\\, $\\, _/binary>>) -> absolute; +win32_pathtype(<<$/, _/binary>>) -> volumerelative; +win32_pathtype(<<$\\, _/binary>>) -> volumerelative; +win32_pathtype(<<_Letter, $:, $/, _/binary>>) -> absolute; +win32_pathtype(<<_Letter, $:, $\\, _/binary>>) -> absolute; +win32_pathtype(<<_Letter, $:, _/binary>>) -> volumerelative; win32_pathtype([$/, $/|_]) -> absolute; win32_pathtype([$\\, $/|_]) -> absolute; win32_pathtype([$/, $\\|_]) -> absolute; @@ -422,7 +561,10 @@ win32_pathtype(_) -> relative. %% Examples: rootname("/jam.src/kalle") -> "/jam.src/kalle" %% rootname("/jam.src/foo.erl") -> "/jam.src/foo" --spec rootname(name()) -> string(). +-spec rootname(Filename) -> file:filename() when + Filename :: file:name(). +rootname(Name) when is_binary(Name) -> + list_to_binary(rootname(binary_to_list(Name))); % No need to handle unicode, . is < 128 rootname(Name0) -> Name = flatten(Name0), rootname(Name, [], [], major_os_type()). @@ -431,8 +573,6 @@ rootname([$/|Rest], Root, Ext, OsType) -> rootname(Rest, [$/]++Ext++Root, [], OsType); rootname([$\\|Rest], Root, Ext, win32) -> rootname(Rest, [$/]++Ext++Root, [], win32); -rootname([$\\|Rest], Root, Ext, vxworks) -> - rootname(Rest, [$/]++Ext++Root, [], vxworks); rootname([$.|Rest], Root, [], OsType) -> rootname(Rest, Root, ".", OsType); rootname([$.|Rest], Root, Ext, OsType) -> @@ -451,7 +591,15 @@ rootname([], Root, _Ext, _OsType) -> %% Examples: rootname("/jam.src/kalle.jam", ".erl") -> "/jam.src/kalle.jam" %% rootname("/jam.src/foo.erl", ".erl") -> "/jam.src/foo" --spec rootname(name(), name()) -> string(). +-spec rootname(Filename, Ext) -> file:filename() when + Filename :: file:name(), + Ext :: file:name(). +rootname(Name, Ext) when is_binary(Name), is_binary(Ext) -> + list_to_binary(rootname(binary_to_list(Name),binary_to_list(Ext))); +rootname(Name, Ext) when is_binary(Name) -> + rootname(Name,filename_string_to_binary(Ext)); +rootname(Name, Ext) when is_binary(Ext) -> + rootname(filename_string_to_binary(Name),Ext); rootname(Name0, Ext0) -> Name = flatten(Name0), Ext = flatten(Ext0), @@ -471,27 +619,57 @@ rootname2([Char|Rest], Ext, Result) when is_integer(Char) -> %% split("foo/bar") -> ["foo", "bar"] %% split("a:\\msdev\\include") -> ["a:/", "msdev", "include"] --spec split(name()) -> [string()]. +-spec split(Filename) -> Components when + Filename :: file:name(), + Components :: [file:filename()]. +split(Name) when is_binary(Name) -> + case os:type() of + {win32, _} -> win32_splitb(Name); + _ -> unix_splitb(Name) + end; + split(Name0) -> Name = flatten(Name0), case os:type() of - {unix, _} -> unix_split(Name); {win32, _} -> win32_split(Name); - vxworks -> vxworks_split(Name); - {ose,_} -> unix_split(Name) + _ -> unix_split(Name) end. -%% If a VxWorks filename starts with '[/\].*[^/\]' '[/\].*:' or '.*:' -%% that part of the filename is considered a device. -%% The rest of the name is interpreted exactly as for win32. -%% XXX - dirty solution to make filename:split([]) return the same thing on -%% VxWorks as on unix and win32. -vxworks_split([]) -> - []; -vxworks_split(L) -> - {_Devicep, Rest, FirstComp} = vxworks_first(L), - split(Rest, [], [lists:reverse(FirstComp)], win32). +unix_splitb(Name) -> + L = binary:split(Name,[<<"/">>],[global]), + LL = case L of + [<<>>|Rest] -> + [<<"/">>|Rest]; + _ -> + L + end, + [ X || X <- LL, X =/= <<>>]. + + +fix_driveletter(Letter0) -> + if + Letter0 >= $A, Letter0 =< $Z -> + Letter0+$a-$A; + true -> + Letter0 + end. +win32_splitb(<<Letter0,$:, Slash, Rest/binary>>) when (((Slash =:= $\\) orelse (Slash =:= $/)) andalso + ?IS_DRIVELETTER(Letter0)) -> + Letter = fix_driveletter(Letter0), + L = binary:split(Rest,[<<"/">>,<<"\\">>],[global]), + [<<Letter,$:,$/>> | [ X || X <- L, X =/= <<>> ]]; +win32_splitb(<<Letter0,$:,Rest/binary>>) when ?IS_DRIVELETTER(Letter0) -> + Letter = fix_driveletter(Letter0), + L = binary:split(Rest,[<<"/">>,<<"\\">>],[global]), + [<<Letter,$:>> | [ X || X <- L, X =/= <<>> ]]; +win32_splitb(<<Slash,Rest/binary>>) when ((Slash =:= $\\) orelse (Slash =:= $/)) -> + L = binary:split(Rest,[<<"/">>,<<"\\">>],[global]), + [<<$/>> | [ X || X <- L, X =/= <<>> ]]; +win32_splitb(Name) -> + L = binary:split(Name,[<<"/">>,<<"\\">>],[global]), + [ X || X <- L, X =/= <<>> ]. + unix_split(Name) -> split(Name, [], unix). @@ -502,8 +680,6 @@ win32_split([X, $\\|Rest]) when is_integer(X) -> win32_split([X, $/|Rest]); win32_split([X, Y, $\\|Rest]) when is_integer(X), is_integer(Y) -> win32_split([X, Y, $/|Rest]); -win32_split([$/, $/|Rest]) -> - split(Rest, [], [[$/, $/]]); win32_split([UcLetter, $:|Rest]) when UcLetter >= $A, UcLetter =< $Z -> win32_split([UcLetter+$a-$A, $:|Rest]); win32_split([Letter, $:, $/|Rest]) -> @@ -528,8 +704,6 @@ split([$/|Rest], Comp, Components, OsType) -> split(Rest, [], [lists:reverse(Comp)|Components], OsType); split([Char|Rest], Comp, Components, OsType) when is_integer(Char) -> split(Rest, [Char|Comp], Components, OsType); -split([List|Rest], Comp, Components, OsType) when is_list(List) -> - split(List++Rest, Comp, Components, OsType); split([], [], Components, _OsType) -> lists:reverse(Components); split([], Comp, Components, OsType) -> @@ -540,7 +714,8 @@ split([], Comp, Components, OsType) -> %% will be converted to backslashes. On all platforms, the %% name will be normalized as done by join/1. --spec nativename(string()) -> string(). +-spec nativename(Path) -> file:filename() when + Path :: file:filename(). nativename(Name0) -> Name = join([Name0]), %Normalize. case os:type() of @@ -557,13 +732,12 @@ win32_nativename([]) -> separators() -> case os:type() of - {unix, _} -> {false, false}; {win32, _} -> {$\\, $:}; - vxworks -> {$\\, false}; - {ose,_} -> {false, false} + _ -> {false, false} end. + %% find_src(Module) -- %% find_src(Module, Rules) -- %% @@ -593,12 +767,17 @@ separators() -> %% The paths in the {outdir, Path} and {i, Path} options are guaranteed %% to be absolute. --type rule() :: {string(), string()}. --type ecode() :: 'non_existing' | 'preloaded' | 'interpreted'. --type option() :: {'i', string()} | {'outdir', string()} | {'d', atom()}. - --spec find_src(atom() | string()) -> - {string(), [option()]} | {'error', {ecode(), atom()}}. +-spec find_src(Beam) -> {SourceFile, Options} + | {error, {ErrorReason, Module}} when + Beam :: Module | Filename, + Filename :: atom() | string(), + Module :: module(), + SourceFile :: string(), + Options :: [Option], + Option :: {'i', Path :: string()} + | {'outdir', Path :: string()} + | {'d', atom()}, + ErrorReason :: 'non_existing' | 'preloaded' | 'interpreted'. find_src(Mod) -> Default = [{"", ""}, {"ebin", "src"}, {"ebin", "esrc"}], Rules = @@ -609,8 +788,18 @@ find_src(Mod) -> end, find_src(Mod, Rules). --spec find_src(atom() | string(), [rule()]) -> - {string(), [option()]} | {'error', {ecode(), atom()}}. +-spec find_src(Beam, Rules) -> {SourceFile, Options} + | {error, {ErrorReason, Module}} when + Beam :: Module | Filename, + Filename :: atom() | string(), + Rules :: [{BinSuffix :: string(), SourceSuffix :: string()}], + Module :: module(), + SourceFile :: string(), + Options :: [Option], + Option :: {'i', Path :: string()} + | {'outdir', Path :: string()} + | {'d', atom()}, + ErrorReason :: 'non_existing' | 'preloaded' | 'interpreted'. find_src(Mod, Rules) when is_atom(Mod) -> find_src(atom_to_list(Mod), Rules); find_src(File0, Rules) when is_list(File0) -> @@ -733,45 +922,13 @@ major_os_type() -> OsT -> OsT end. -%% Need to take care of the first pathname component separately -%% due to VxWorks less than good device naming rules. -%% (i.e. this is VxWorks specific ...) -%% The following four all starts with device names -%% elrond:/foo -> elrond: -%% elrond:\\foo.bar -> elrond: -%% /DISK1:foo -> /DISK1: -%% /usr/include -> /usr -%% This one doesn't: -%% foo/bar - -vxworks_first([]) -> - {not_device, [], []}; -vxworks_first([$/|T]) -> - vxworks_first2(device, T, [$/]); -vxworks_first([$\\|T]) -> - vxworks_first2(device, T, [$/]); -vxworks_first([H|T]) when is_list(H) -> - vxworks_first(H++T); -vxworks_first([H|T]) -> - vxworks_first2(not_device, T, [H]). - -vxworks_first2(Devicep, [], FirstComp) -> - {Devicep, [], FirstComp}; -vxworks_first2(Devicep, [$/|T], FirstComp) -> - {Devicep, [$/|T], FirstComp}; -vxworks_first2(Devicep, [$\\|T], FirstComp) -> - {Devicep, [$/|T], FirstComp}; -vxworks_first2(_Devicep, [$:|T], FirstComp)-> - {device, T, [$:|FirstComp]}; -vxworks_first2(Devicep, [H|T], FirstComp) when is_list(H) -> - vxworks_first2(Devicep, H++T, FirstComp); -vxworks_first2(Devicep, [H|T], FirstComp) -> - vxworks_first2(Devicep, T, [H|FirstComp]). - %% flatten(List) %% Flatten a list, also accepting atoms. --spec flatten(name()) -> string(). +-spec flatten(Filename) -> file:filename() when + Filename :: file:name(). +flatten(Bin) when is_binary(Bin) -> + Bin; flatten(List) -> do_flatten(List, []). @@ -785,3 +942,12 @@ do_flatten([], Tail) -> Tail; do_flatten(Atom, Tail) when is_atom(Atom) -> atom_to_list(Atom) ++ flatten(Tail). + +filename_string_to_binary(List) -> + case unicode:characters_to_binary(flatten(List),unicode,file:native_name_encoding()) of + {error,_,_} -> + erlang:error(badarg); + Bin when is_binary(Bin) -> + Bin + end. + diff --git a/lib/stdlib/src/gb_sets.erl b/lib/stdlib/src/gb_sets.erl index 086dc79b46..91d21d869c 100644 --- a/lib/stdlib/src/gb_sets.erl +++ b/lib/stdlib/src/gb_sets.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2001-2009. All Rights Reserved. +%% Copyright Ericsson AB 2001-2011. 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 @@ -197,6 +197,7 @@ %% Some types. -type gb_set_node() :: 'nil' | {term(), _, _}. +-opaque iter() :: [gb_set_node()]. %% A declaration equivalent to the following is currently hard-coded %% in erl_types.erl @@ -205,38 +206,47 @@ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% --spec empty() -> gb_set(). +-spec empty() -> Set when + Set :: gb_set(). empty() -> {0, nil}. --spec new() -> gb_set(). +-spec new() -> Set when + Set :: gb_set(). new() -> empty(). --spec is_empty(gb_set()) -> boolean(). +-spec is_empty(Set) -> boolean() when + Set :: gb_set(). is_empty({0, nil}) -> true; is_empty(_) -> false. --spec size(gb_set()) -> non_neg_integer(). +-spec size(Set) -> non_neg_integer() when + Set :: gb_set(). size({Size, _}) -> Size. --spec singleton(term()) -> gb_set(). +-spec singleton(Element) -> gb_set() when + Element :: term(). singleton(Key) -> {1, {Key, nil, nil}}. --spec is_element(term(), gb_set()) -> boolean(). +-spec is_element(Element, Set) -> boolean() when + Element :: term(), + Set :: gb_set(). is_element(Key, S) -> is_member(Key, S). --spec is_member(term(), gb_set()) -> boolean(). +-spec is_member(Element, Set) -> boolean() when + Element :: term(), + Set :: gb_set(). is_member(Key, {_, T}) -> is_member_1(Key, T). @@ -250,7 +260,10 @@ is_member_1(_, {_, _, _}) -> is_member_1(_, nil) -> false. --spec insert(term(), gb_set()) -> gb_set(). +-spec insert(Element, Set1) -> Set2 when + Element :: term(), + Set1 :: gb_set(), + Set2 :: gb_set(). insert(Key, {S, T}) -> S1 = S + 1, @@ -306,7 +319,9 @@ count({_, Sm, Bi}) -> count(nil) -> {1, 0}. --spec balance(gb_set()) -> gb_set(). +-spec balance(Set1) -> Set2 when + Set1 :: gb_set(), + Set2 :: gb_set(). balance({S, T}) -> {S, balance(T, S)}. @@ -331,12 +346,18 @@ balance_list_1([Key | L], 1) -> balance_list_1(L, 0) -> {nil, L}. --spec add_element(term(), gb_set()) -> gb_set(). +-spec add_element(Element, Set1) -> Set2 when + Element :: term(), + Set1 :: gb_set(), + Set2 :: gb_set(). add_element(X, S) -> add(X, S). --spec add(term(), gb_set()) -> gb_set(). +-spec add(Element, Set1) -> Set2 when + Element :: term(), + Set1 :: gb_set(), + Set2 :: gb_set(). add(X, S) -> case is_member(X, S) of @@ -346,23 +367,33 @@ add(X, S) -> insert(X, S) end. --spec from_list([term()]) -> gb_set(). +-spec from_list(List) -> Set when + List :: [term()], + Set :: gb_set(). from_list(L) -> from_ordset(ordsets:from_list(L)). --spec from_ordset([term()]) -> gb_set(). +-spec from_ordset(List) -> Set when + List :: [term()], + Set :: gb_set(). from_ordset(L) -> S = length(L), {S, balance_list(L, S)}. --spec del_element(term(), gb_set()) -> gb_set(). +-spec del_element(Element, Set1) -> Set2 when + Element :: term(), + Set1 :: gb_set(), + Set2 :: gb_set(). del_element(Key, S) -> delete_any(Key, S). --spec delete_any(term(), gb_set()) -> gb_set(). +-spec delete_any(Element, Set1) -> Set2 when + Element :: term(), + Set1 :: gb_set(), + Set2 :: gb_set(). delete_any(Key, S) -> case is_member(Key, S) of @@ -372,7 +403,10 @@ delete_any(Key, S) -> S end. --spec delete(term(), gb_set()) -> gb_set(). +-spec delete(Element, Set1) -> Set2 when + Element :: term(), + Set1 :: gb_set(), + Set2 :: gb_set(). delete(Key, {S, T}) -> {S - 1, delete_1(Key, T)}. @@ -394,7 +428,10 @@ merge(Smaller, Larger) -> {Key, Larger1} = take_smallest1(Larger), {Key, Smaller, Larger1}. --spec take_smallest(gb_set()) -> {term(), gb_set()}. +-spec take_smallest(Set1) -> {Element, Set2} when + Set1 :: gb_set(), + Set2 :: gb_set(), + Element :: term(). take_smallest({S, T}) -> {Key, Larger} = take_smallest1(T), @@ -406,7 +443,8 @@ take_smallest1({Key, Smaller, Larger}) -> {Key1, Smaller1} = take_smallest1(Smaller), {Key1, {Key, Smaller1, Larger}}. --spec smallest(gb_set()) -> term(). +-spec smallest(Set) -> term() when + Set :: gb_set(). smallest({_, T}) -> smallest_1(T). @@ -416,7 +454,10 @@ smallest_1({Key, nil, _Larger}) -> smallest_1({_Key, Smaller, _Larger}) -> smallest_1(Smaller). --spec take_largest(gb_set()) -> {term(), gb_set()}. +-spec take_largest(Set1) -> {Element, Set2} when + Set1 :: gb_set(), + Set2 :: gb_set(), + Element :: term(). take_largest({S, T}) -> {Key, Smaller} = take_largest1(T), @@ -428,7 +469,8 @@ take_largest1({Key, Smaller, Larger}) -> {Key1, Larger1} = take_largest1(Larger), {Key1, {Key, Smaller, Larger1}}. --spec largest(gb_set()) -> term(). +-spec largest(Set) -> term() when + Set :: gb_set(). largest({_, T}) -> largest_1(T). @@ -438,7 +480,9 @@ largest_1({Key, _Smaller, nil}) -> largest_1({_Key, _Smaller, Larger}) -> largest_1(Larger). --spec to_list(gb_set()) -> [term()]. +-spec to_list(Set) -> List when + Set :: gb_set(), + List :: [term()]. to_list({_, T}) -> to_list(T, []). @@ -449,7 +493,9 @@ to_list({Key, Small, Big}, L) -> to_list(Small, [Key | to_list(Big, L)]); to_list(nil, L) -> L. --spec iterator(gb_set()) -> [term()]. +-spec iterator(Set) -> Iter when + Set :: gb_set(), + Iter :: iter(). iterator({_, T}) -> iterator(T, []). @@ -464,7 +510,10 @@ iterator({_, L, _} = T, As) -> iterator(nil, As) -> As. --spec next([term()]) -> {term(), [term()]} | 'none'. +-spec next(Iter1) -> {Element, Iter2} | 'none' when + Iter1 :: iter(), + Iter2 :: iter(), + Element :: term(). next([{X, _, T} | As]) -> {X, iterator(T, As)}; @@ -494,7 +543,10 @@ next([]) -> %% traversing the elements can be devised, but they all have higher %% overhead. --spec union(gb_set(), gb_set()) -> gb_set(). +-spec union(Set1, Set2) -> Set3 when + Set1 :: gb_set(), + Set2 :: gb_set(), + Set3 :: gb_set(). union({N1, T1}, {N2, T2}) when N2 < N1 -> union(to_list_1(T2), N2, T1, N1); @@ -596,7 +648,9 @@ balance_revlist_1([Key | L], 1) -> balance_revlist_1(L, 0) -> {nil, L}. --spec union([gb_set()]) -> gb_set(). +-spec union(SetList) -> Set when + SetList :: [gb_set(),...], + Set :: gb_set(). union([S | Ss]) -> union_list(S, Ss); @@ -609,7 +663,10 @@ union_list(S, []) -> S. %% The rest is modelled on the above. --spec intersection(gb_set(), gb_set()) -> gb_set(). +-spec intersection(Set1, Set2) -> Set3 when + Set1 :: gb_set(), + Set2 :: gb_set(), + Set3 :: gb_set(). intersection({N1, T1}, {N2, T2}) when N2 < N1 -> intersection(to_list_1(T2), N2, T1, N1); @@ -657,7 +714,9 @@ intersection_2([], _, As, S) -> intersection_2(_, [], As, S) -> {S, balance_revlist(As, S)}. --spec intersection([gb_set()]) -> gb_set(). +-spec intersection(SetList) -> Set when + SetList :: [gb_set(),...], + Set :: gb_set(). intersection([S | Ss]) -> intersection_list(S, Ss). @@ -666,7 +725,9 @@ intersection_list(S, [S1 | Ss]) -> intersection_list(intersection(S, S1), Ss); intersection_list(S, []) -> S. --spec is_disjoint(gb_set(), gb_set()) -> boolean(). +-spec is_disjoint(Set1, Set2) -> boolean() when + Set1 :: gb_set(), + Set2 :: gb_set(). is_disjoint({N1, T1}, {N2, T2}) when N1 < N2 -> is_disjoint_1(T1, T2); @@ -694,12 +755,18 @@ is_disjoint_1(_, nil) -> %% the sets. Therefore, we always build a new tree, and thus we need to %% traverse the whole element list of the left operand. --spec subtract(gb_set(), gb_set()) -> gb_set(). +-spec subtract(Set1, Set2) -> Set3 when + Set1 :: gb_set(), + Set2 :: gb_set(), + Set3 :: gb_set(). subtract(S1, S2) -> difference(S1, S2). --spec difference(gb_set(), gb_set()) -> gb_set(). +-spec difference(Set1, Set2) -> Set3 when + Set1 :: gb_set(), + Set2 :: gb_set(), + Set3 :: gb_set(). difference({N1, T1}, {N2, T2}) -> difference(to_list_1(T1), N1, T2, N2). @@ -747,7 +814,9 @@ difference_2(Xs, [], As, S) -> %% Subset testing is much the same thing as set difference, but %% without the construction of a new set. --spec is_subset(gb_set(), gb_set()) -> boolean(). +-spec is_subset(Set1, Set2) -> boolean() when + Set1 :: gb_set(), + Set2 :: gb_set(). is_subset({N1, T1}, {N2, T2}) -> is_subset(to_list_1(T1), N1, T2, N2). @@ -788,18 +857,28 @@ is_subset_2(_, []) -> %% For compatibility with `sets': --spec is_set(term()) -> boolean(). +-spec is_set(Term) -> boolean() when + Term :: term(). is_set({0, nil}) -> true; is_set({N, {_, _, _}}) when is_integer(N), N >= 0 -> true; is_set(_) -> false. --spec filter(fun((term()) -> boolean()), gb_set()) -> gb_set(). +-spec filter(Pred, Set1) -> Set2 when + Pred :: fun((E :: term()) -> boolean()), + Set1 :: gb_set(), + Set2 :: gb_set(). filter(F, S) -> from_ordset([X || X <- to_list(S), F(X)]). --spec fold(fun((term(), term()) -> term()), term(), gb_set()) -> term(). +-spec fold(Function, Acc0, Set) -> Acc1 when + Function :: fun((E :: term(), AccIn) -> AccOut), + Acc0 :: term(), + Acc1 :: term(), + AccIn :: term(), + AccOut :: term(), + Set :: gb_set(). fold(F, A, {_, T}) when is_function(F, 2) -> fold_1(F, A, T). diff --git a/lib/stdlib/src/gb_trees.erl b/lib/stdlib/src/gb_trees.erl index d37786a100..6ad861ff5b 100644 --- a/lib/stdlib/src/gb_trees.erl +++ b/lib/stdlib/src/gb_trees.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2001-2009. All Rights Reserved. +%% Copyright Ericsson AB 2001-2011. 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 @@ -153,6 +153,7 @@ %% Some types. -type gb_tree_node() :: 'nil' | {_, _, _, _}. +-opaque iter() :: [gb_tree_node()]. %% A declaration equivalent to the following is currently hard-coded %% in erl_types.erl @@ -166,21 +167,26 @@ empty() -> {0, nil}. --spec is_empty(gb_tree()) -> boolean(). +-spec is_empty(Tree) -> boolean() when + Tree :: gb_tree(). is_empty({0, nil}) -> true; is_empty(_) -> false. --spec size(gb_tree()) -> non_neg_integer(). +-spec size(Tree) -> non_neg_integer() when + Tree :: gb_tree(). size({Size, _}) when is_integer(Size), Size >= 0 -> Size. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% --spec lookup(term(), gb_tree()) -> 'none' | {'value', term()}. +-spec lookup(Key, Tree) -> 'none' | {'value', Val} when + Key :: term(), + Val :: term(), + Tree :: gb_tree(). lookup(Key, {_, T}) -> lookup_1(Key, T). @@ -205,7 +211,9 @@ lookup_1(_, nil) -> %% This is a specialized version of `lookup'. --spec is_defined(term(), gb_tree()) -> boolean(). +-spec is_defined(Key, Tree) -> boolean() when + Key :: term(), + Tree :: gb_tree(). is_defined(Key, {_, T}) -> is_defined_1(Key, T). @@ -223,7 +231,10 @@ is_defined_1(_, nil) -> %% This is a specialized version of `lookup'. --spec get(term(), gb_tree()) -> term(). +-spec get(Key, Tree) -> Val when + Key :: term(), + Tree :: gb_tree(), + Val :: term(). get(Key, {_, T}) -> get_1(Key, T). @@ -237,7 +248,11 @@ get_1(_, {_, Value, _, _}) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% --spec update(term(), term(), gb_tree()) -> gb_tree(). +-spec update(Key, Val, Tree1) -> Tree2 when + Key :: term(), + Val :: term(), + Tree1 :: gb_tree(), + Tree2 :: gb_tree(). update(Key, Val, {S, T}) -> T1 = update_1(Key, Val, T), @@ -254,7 +269,11 @@ update_1(Key, Value, {_, _, Smaller, Bigger}) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% --spec insert(term(), term(), gb_tree()) -> gb_tree(). +-spec insert(Key, Val, Tree1) -> Tree2 when + Key :: term(), + Val :: term(), + Tree1 :: gb_tree(), + Tree2 :: gb_tree(). insert(Key, Val, {S, T}) when is_integer(S) -> S1 = S+1, @@ -303,7 +322,11 @@ insert_1(Key, _, _, _) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% --spec enter(term(), term(), gb_tree()) -> gb_tree(). +-spec enter(Key, Val, Tree1) -> Tree2 when + Key :: term(), + Val :: term(), + Tree1 :: gb_tree(), + Tree2 :: gb_tree(). enter(Key, Val, T) -> case is_defined(Key, T) of @@ -326,7 +349,9 @@ count(nil) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% --spec balance(gb_tree()) -> gb_tree(). +-spec balance(Tree1) -> Tree2 when + Tree1 :: gb_tree(), + Tree2 :: gb_tree(). balance({S, T}) -> {S, balance(T, S)}. @@ -351,7 +376,9 @@ balance_list_1([{Key, Val} | L], 1) -> balance_list_1(L, 0) -> {nil, L}. --spec from_orddict([{_,_}]) -> gb_tree(). +-spec from_orddict(List) -> Tree when + List :: [{Key :: term(), Val :: term()}], + Tree :: gb_tree(). from_orddict(L) -> S = length(L), @@ -359,7 +386,10 @@ from_orddict(L) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% --spec delete_any(term(), gb_tree()) -> gb_tree(). +-spec delete_any(Key, Tree1) -> Tree2 when + Key :: term(), + Tree1 :: gb_tree(), + Tree2 :: gb_tree(). delete_any(Key, T) -> case is_defined(Key, T) of @@ -371,7 +401,10 @@ delete_any(Key, T) -> %%% delete. Assumes that key is present. --spec delete(term(), gb_tree()) -> gb_tree(). +-spec delete(Key, Tree1) -> Tree2 when + Key :: term(), + Tree1 :: gb_tree(), + Tree2 :: gb_tree(). delete(Key, {S, T}) when is_integer(S), S >= 0 -> {S - 1, delete_1(Key, T)}. @@ -397,7 +430,11 @@ merge(Smaller, Larger) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% --spec take_smallest(gb_tree()) -> {term(), term(), gb_tree()}. +-spec take_smallest(Tree1) -> {Key, Val, Tree2} when + Tree1 :: gb_tree(), + Tree2 :: gb_tree(), + Key :: term(), + Val :: term(). take_smallest({Size, Tree}) when is_integer(Size), Size >= 0 -> {Key, Value, Larger} = take_smallest1(Tree), @@ -409,7 +446,10 @@ take_smallest1({Key, Value, Smaller, Larger}) -> {Key1, Value1, Smaller1} = take_smallest1(Smaller), {Key1, Value1, {Key, Value, Smaller1, Larger}}. --spec smallest(gb_tree()) -> {term(), term()}. +-spec smallest(Tree) -> {Key, Val} when + Tree :: gb_tree(), + Key :: term(), + Val :: term(). smallest({_, Tree}) -> smallest_1(Tree). @@ -419,7 +459,11 @@ smallest_1({Key, Value, nil, _Larger}) -> smallest_1({_Key, _Value, Smaller, _Larger}) -> smallest_1(Smaller). --spec take_largest(gb_tree()) -> {term(), term(), gb_tree()}. +-spec take_largest(Tree1) -> {Key, Val, Tree2} when + Tree1 :: gb_tree(), + Tree2 :: gb_tree(), + Key :: term(), + Val :: term(). take_largest({Size, Tree}) when is_integer(Size), Size >= 0 -> {Key, Value, Smaller} = take_largest1(Tree), @@ -431,7 +475,10 @@ take_largest1({Key, Value, Smaller, Larger}) -> {Key1, Value1, Larger1} = take_largest1(Larger), {Key1, Value1, {Key, Value, Smaller, Larger1}}. --spec largest(gb_tree()) -> {term(), term()}. +-spec largest(Tree) -> {Key, Val} when + Tree :: gb_tree(), + Key :: term(), + Val :: term(). largest({_, Tree}) -> largest_1(Tree). @@ -443,7 +490,10 @@ largest_1({_Key, _Value, _Smaller, Larger}) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% --spec to_list(gb_tree()) -> [{term(), term()}]. +-spec to_list(Tree) -> [{Key, Val}] when + Tree :: gb_tree(), + Key :: term(), + Val :: term(). to_list({_, T}) -> to_list(T, []). @@ -456,7 +506,9 @@ to_list(nil, L) -> L. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% --spec keys(gb_tree()) -> [term()]. +-spec keys(Tree) -> [Key] when + Tree :: gb_tree(), + Key :: term(). keys({_, T}) -> keys(T, []). @@ -467,7 +519,9 @@ keys(nil, L) -> L. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% --spec values(gb_tree()) -> [term()]. +-spec values(Tree) -> [Val] when + Tree :: gb_tree(), + Val :: term(). values({_, T}) -> values(T, []). @@ -478,7 +532,9 @@ values(nil, L) -> L. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% --spec iterator(gb_tree()) -> [gb_tree_node()]. +-spec iterator(Tree) -> Iter when + Tree :: gb_tree(), + Iter :: iter(). iterator({_, T}) -> iterator_1(T). @@ -496,7 +552,11 @@ iterator({_, _, L, _} = T, As) -> iterator(nil, As) -> As. --spec next([gb_tree_node()]) -> 'none' | {term(), term(), [gb_tree_node()]}. +-spec next(Iter1) -> 'none' | {Key, Val, Iter2} when + Iter1 :: iter(), + Iter2 :: iter(), + Key :: term(), + Val :: term(). next([{X, V, _, T} | As]) -> {X, V, iterator(T, As)}; @@ -505,7 +565,10 @@ next([]) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% --spec map(fun((term(), term()) -> term()), gb_tree()) -> gb_tree(). +-spec map(Function, Tree1) -> Tree2 when + Function :: fun((K :: term(), V1 :: term()) -> V2 :: term()), + Tree1 :: gb_tree(), + Tree2 :: gb_tree(). map(F, {Size, Tree}) when is_function(F, 2) -> {Size, map_1(F, Tree)}. diff --git a/lib/stdlib/src/gen.erl b/lib/stdlib/src/gen.erl index 5aab547644..574146b1cd 100644 --- a/lib/stdlib/src/gen.erl +++ b/lib/stdlib/src/gen.erl @@ -1,19 +1,19 @@ %% %% %CopyrightBegin% -%% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. -%% +%% +%% Copyright Ericsson AB 1996-2010. 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 %% compliance with the License. You should have received a copy of the %% Erlang Public License along with this software. If not, it can be %% retrieved online at http://www.erlang.org/. -%% +%% %% Software distributed under the License is distributed on an "AS IS" %% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See %% the License for the specific language governing rights and limitations %% under the License. -%% +%% %% %CopyrightEnd% %% -module(gen). @@ -29,6 +29,8 @@ -export([init_it/6, init_it/7]). +-export([format_status_header/2]). + -define(default_timeout, 5000). %%----------------------------------------------------------------- @@ -212,7 +214,22 @@ do_call(Process, Label, Request, Timeout) -> catch erlang:send(Process, {Label, {self(), Mref}, Request}, [noconnect]), - wait_resp_mon(Node, Mref, Timeout) + receive + {Mref, Reply} -> + erlang:demonitor(Mref, [flush]), + {ok, Reply}; + {'DOWN', Mref, _, _, noconnection} -> + exit({nodedown, Node}); + {'DOWN', Mref, _, _, Reason} -> + exit(Reason) + after Timeout -> + erlang:demonitor(Mref), + receive + {'DOWN', Mref, _, _, _} -> true + after 0 -> true + end, + exit(timeout) + end catch error:_ -> %% Node (C/Java?) is not supporting the monitor. @@ -233,24 +250,6 @@ do_call(Process, Label, Request, Timeout) -> end end. -wait_resp_mon(Node, Mref, Timeout) -> - receive - {Mref, Reply} -> - erlang:demonitor(Mref, [flush]), - {ok, Reply}; - {'DOWN', Mref, _, _, noconnection} -> - exit({nodedown, Node}); - {'DOWN', Mref, _, _, Reason} -> - exit(Reason) - after Timeout -> - erlang:demonitor(Mref), - receive - {'DOWN', Mref, _, _, _} -> true - after 0 -> true - end, - exit(timeout) - end. - wait_resp(Node, Tag, Timeout) -> receive {Tag, Reply} -> @@ -318,3 +317,10 @@ debug_options(Opts) -> {ok, Options} -> sys:debug_options(Options); _ -> [] end. + +format_status_header(TagLine, Pid) when is_pid(Pid) -> + lists:concat([TagLine, " ", pid_to_list(Pid)]); +format_status_header(TagLine, RegName) when is_atom(RegName) -> + lists:concat([TagLine, " ", RegName]); +format_status_header(TagLine, Name) -> + {TagLine, Name}. diff --git a/lib/stdlib/src/gen_event.erl b/lib/stdlib/src/gen_event.erl index 1b30aaf5eb..1c4a73680b 100644 --- a/lib/stdlib/src/gen_event.erl +++ b/lib/stdlib/src/gen_event.erl @@ -1,19 +1,19 @@ %% %% %CopyrightBegin% -%% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. -%% +%% +%% Copyright Ericsson AB 1996-2011. 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 %% compliance with the License. You should have received a copy of the %% Erlang Public License along with this software. If not, it can be %% retrieved online at http://www.erlang.org/. -%% +%% %% Software distributed under the License is distributed on an "AS IS" %% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See %% the License for the specific language governing rights and limitations %% under the License. -%% +%% %% %CopyrightEnd% %% -module(gen_event). @@ -42,9 +42,11 @@ system_continue/3, system_terminate/4, system_code_change/4, - print_event/3, format_status/2]). +-export_type([handler/0, handler_args/0, add_handler_ret/0, + del_handler_ret/0]). + -import(error_logger, [error_msg/2]). -define(reply(X), From ! {element(2,Tag), X}). @@ -114,7 +116,11 @@ behaviour_info(_Other) -> %%--------------------------------------------------------------------------- --type handler() :: atom() | {atom(), term()}. +-type handler() :: atom() | {atom(), term()}. +-type handler_args() :: term(). +-type add_handler_ret() :: ok | term() | {'EXIT',term()}. +-type del_handler_ret() :: ok | term() | {'EXIT',term()}. + -type emgr_name() :: {'local', atom()} | {'global', atom()}. -type emgr_ref() :: atom() | {atom(), atom()} | {'global', atom()} | pid(). -type start_ret() :: {'ok', pid()} | {'error', term()}. @@ -239,7 +245,7 @@ fetch_msg(Parent, ServerName, MSL, Debug, Hib) -> Msg when Debug =:= [] -> handle_msg(Msg, Parent, ServerName, MSL, []); Msg -> - Debug1 = sys:handle_debug(Debug, {?MODULE, print_event}, + Debug1 = sys:handle_debug(Debug, fun print_event/3, ServerName, {in, Msg}), handle_msg(Msg, Parent, ServerName, MSL, Debug1) end. @@ -678,12 +684,23 @@ report_error(Handler, Reason, State, LastIn, SName) -> _ -> Reason end, + Mod = Handler#handler.module, + FmtState = case erlang:function_exported(Mod, format_status, 2) of + true -> + Args = [get(), State], + case catch Mod:format_status(terminate, Args) of + {'EXIT', _} -> State; + Else -> Else + end; + _ -> + State + end, error_msg("** gen_event handler ~p crashed.~n" "** Was installed in ~p~n" "** Last event was: ~p~n" "** When handler state == ~p~n" "** Reason == ~p~n", - [handler(Handler),SName,LastIn,State,Reason1]). + [handler(Handler),SName,LastIn,FmtState,Reason1]). handler(Handler) when not Handler#handler.id -> Handler#handler.module; @@ -712,10 +729,21 @@ get_modules(MSL) -> %%----------------------------------------------------------------- %% Status information %%----------------------------------------------------------------- -format_status(_Opt, StatusData) -> - [_PDict, SysState, Parent, _Debug, [ServerName, MSL, _Hib]] = StatusData, - Header = lists:concat(["Status for event handler ", ServerName]), +format_status(Opt, StatusData) -> + [PDict, SysState, Parent, _Debug, [ServerName, MSL, _Hib]] = StatusData, + Header = gen:format_status_header("Status for event handler", + ServerName), + FmtMSL = [case erlang:function_exported(Mod, format_status, 2) of + true -> + Args = [PDict, State], + case catch Mod:format_status(Opt, Args) of + {'EXIT', _} -> MSL; + Else -> MS#handler{state = Else} + end; + _ -> + MS + end || #handler{module = Mod, state = State} = MS <- MSL], [{header, Header}, {data, [{"Status", SysState}, {"Parent", Parent}]}, - {items, {"Installed handlers", MSL}}]. + {items, {"Installed handlers", FmtMSL}}]. diff --git a/lib/stdlib/src/gen_fsm.erl b/lib/stdlib/src/gen_fsm.erl index ba0275ae2b..f2f1365d3d 100644 --- a/lib/stdlib/src/gen_fsm.erl +++ b/lib/stdlib/src/gen_fsm.erl @@ -1,19 +1,19 @@ %% %% %CopyrightBegin% -%% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. -%% +%% +%% Copyright Ericsson AB 1996-2010. 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 %% compliance with the License. You should have received a copy of the %% Erlang Public License along with this software. If not, it can be %% retrieved online at http://www.erlang.org/. -%% +%% %% Software distributed under the License is distributed on an "AS IS" %% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See %% the License for the specific language governing rights and limitations %% under the License. -%% +%% %% %CopyrightEnd% %% -module(gen_fsm). @@ -116,7 +116,7 @@ -export([behaviour_info/1]). %% Internal exports --export([init_it/6, print_event/3, +-export([init_it/6, system_continue/3, system_terminate/4, system_code_change/4, @@ -376,7 +376,7 @@ decode_msg(Msg,Parent, Name, StateName, StateData, Mod, Time, Debug, Hib) -> _Msg when Debug =:= [] -> handle_msg(Msg, Parent, Name, StateName, StateData, Mod, Time); _Msg -> - Debug1 = sys:handle_debug(Debug, {?MODULE, print_event}, + Debug1 = sys:handle_debug(Debug, fun print_event/3, {Name, StateName}, {in, Msg}), handle_msg(Msg, Parent, Name, StateName, StateData, Mod, Time, Debug1) @@ -466,11 +466,11 @@ handle_msg(Msg, Parent, Name, StateName, StateData, Mod, _Time, Debug) -> From = from(Msg), case catch dispatch(Msg, Mod, StateName, StateData) of {next_state, NStateName, NStateData} -> - Debug1 = sys:handle_debug(Debug, {?MODULE, print_event}, + Debug1 = sys:handle_debug(Debug, fun print_event/3, {Name, NStateName}, return), loop(Parent, Name, NStateName, NStateData, Mod, infinity, Debug1); {next_state, NStateName, NStateData, Time1} -> - Debug1 = sys:handle_debug(Debug, {?MODULE, print_event}, + Debug1 = sys:handle_debug(Debug, fun print_event/3, {Name, NStateName}, return), loop(Parent, Name, NStateName, NStateData, Mod, Time1, Debug1); {reply, Reply, NStateName, NStateData} when From =/= undefined -> @@ -519,7 +519,7 @@ reply({To, Tag}, Reply) -> reply(Name, {To, Tag}, Reply, Debug, StateName) -> reply({To, Tag}, Reply), - sys:handle_debug(Debug, {?MODULE, print_event}, Name, + sys:handle_debug(Debug, fun print_event/3, Name, {out, Reply, To, StateName}). %%% --------------------------------------------------- @@ -542,7 +542,18 @@ terminate(Reason, Name, Msg, Mod, StateName, StateData, Debug) -> {shutdown,_}=Shutdown -> exit(Shutdown); _ -> - error_info(Reason, Name, Msg, StateName, StateData, Debug), + FmtStateData = + case erlang:function_exported(Mod, format_status, 2) of + true -> + Args = [get(), StateData], + case catch Mod:format_status(terminate, Args) of + {'EXIT', _} -> StateData; + Else -> Else + end; + _ -> + StateData + end, + error_info(Reason,Name,Msg,StateName,FmtStateData,Debug), exit(Reason) end end. @@ -603,22 +614,20 @@ get_msg(Msg) -> Msg. format_status(Opt, StatusData) -> [PDict, SysState, Parent, Debug, [Name, StateName, StateData, Mod, _Time]] = StatusData, - NameTag = if is_pid(Name) -> - pid_to_list(Name); - is_atom(Name) -> - Name - end, - Header = lists:concat(["Status for state machine ", NameTag]), + Header = gen:format_status_header("Status for state machine", + Name), Log = sys:get_debug(log, Debug, []), - Specfic = + DefaultStatus = [{data, [{"StateData", StateData}]}], + Specfic = case erlang:function_exported(Mod, format_status, 2) of true -> case catch Mod:format_status(Opt,[PDict,StateData]) of - {'EXIT', _} -> [{data, [{"StateData", StateData}]}]; - Else -> Else + {'EXIT', _} -> DefaultStatus; + StatusList when is_list(StatusList) -> StatusList; + Else -> [Else] end; _ -> - [{data, [{"StateData", StateData}]}] + DefaultStatus end, [{header, Header}, {data, [{"Status", SysState}, diff --git a/lib/stdlib/src/gen_server.erl b/lib/stdlib/src/gen_server.erl index f1a9a31c63..09d94a9c40 100644 --- a/lib/stdlib/src/gen_server.erl +++ b/lib/stdlib/src/gen_server.erl @@ -1,19 +1,19 @@ %% %% %CopyrightBegin% -%% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. -%% +%% +%% Copyright Ericsson AB 1996-2010. 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 %% compliance with the License. You should have received a copy of the %% Erlang Public License along with this software. If not, it can be %% retrieved online at http://www.erlang.org/. -%% +%% %% Software distributed under the License is distributed on an "AS IS" %% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See %% the License for the specific language governing rights and limitations %% under the License. -%% +%% %% %CopyrightEnd% %% -module(gen_server). @@ -103,7 +103,7 @@ format_status/2]). %% Internal exports --export([init_it/6, print_event/3]). +-export([init_it/6]). -import(error_logger, [format/2]). @@ -353,7 +353,7 @@ decode_msg(Msg, Parent, Name, State, Mod, Time, Debug, Hib) -> _Msg when Debug =:= [] -> handle_msg(Msg, Parent, Name, State, Mod); _Msg -> - Debug1 = sys:handle_debug(Debug, {?MODULE, print_event}, + Debug1 = sys:handle_debug(Debug, fun print_event/3, Name, {in, Msg}), handle_msg(Msg, Parent, Name, State, Mod, Debug1) end. @@ -589,11 +589,11 @@ handle_msg({'$gen_call', From, Msg}, Parent, Name, State, Mod, Debug) -> Debug1 = reply(Name, From, Reply, NState, Debug), loop(Parent, Name, NState, Mod, Time1, Debug1); {noreply, NState} -> - Debug1 = sys:handle_debug(Debug, {?MODULE, print_event}, Name, + Debug1 = sys:handle_debug(Debug, fun print_event/3, Name, {noreply, NState}), loop(Parent, Name, NState, Mod, infinity, Debug1); {noreply, NState, Time1} -> - Debug1 = sys:handle_debug(Debug, {?MODULE, print_event}, Name, + Debug1 = sys:handle_debug(Debug, fun print_event/3, Name, {noreply, NState}), loop(Parent, Name, NState, Mod, Time1, Debug1); {stop, Reason, Reply, NState} -> @@ -625,11 +625,11 @@ handle_common_reply(Reply, Parent, Name, Msg, Mod, State) -> handle_common_reply(Reply, Parent, Name, Msg, Mod, State, Debug) -> case Reply of {noreply, NState} -> - Debug1 = sys:handle_debug(Debug, {?MODULE, print_event}, Name, + Debug1 = sys:handle_debug(Debug, fun print_event/3, Name, {noreply, NState}), loop(Parent, Name, NState, Mod, infinity, Debug1); {noreply, NState, Time1} -> - Debug1 = sys:handle_debug(Debug, {?MODULE, print_event}, Name, + Debug1 = sys:handle_debug(Debug, fun print_event/3, Name, {noreply, NState}), loop(Parent, Name, NState, Mod, Time1, Debug1); {stop, Reason, NState} -> @@ -642,7 +642,7 @@ handle_common_reply(Reply, Parent, Name, Msg, Mod, State, Debug) -> reply(Name, {To, Tag}, Reply, State, Debug) -> reply({To, Tag}, Reply), - sys:handle_debug(Debug, {?MODULE, print_event}, Name, + sys:handle_debug(Debug, fun print_event/3, Name, {out, Reply, To, State} ). @@ -705,7 +705,18 @@ terminate(Reason, Name, Msg, Mod, State, Debug) -> {shutdown,_}=Shutdown -> exit(Shutdown); _ -> - error_info(Reason, Name, Msg, State, Debug), + FmtState = + case erlang:function_exported(Mod, format_status, 2) of + true -> + Args = [get(), State], + case catch Mod:format_status(terminate, Args) of + {'EXIT', _} -> State; + Else -> Else + end; + _ -> + State + end, + error_info(Reason, Name, Msg, FmtState, Debug), exit(Reason) end end. @@ -829,22 +840,20 @@ name_to_pid(Name) -> %%----------------------------------------------------------------- format_status(Opt, StatusData) -> [PDict, SysState, Parent, Debug, [Name, State, Mod, _Time]] = StatusData, - NameTag = if is_pid(Name) -> - pid_to_list(Name); - is_atom(Name) -> - Name - end, - Header = lists:concat(["Status for generic server ", NameTag]), + Header = gen:format_status_header("Status for generic server", + Name), Log = sys:get_debug(log, Debug, []), - Specfic = + DefaultStatus = [{data, [{"State", State}]}], + Specfic = case erlang:function_exported(Mod, format_status, 2) of true -> case catch Mod:format_status(Opt, [PDict, State]) of - {'EXIT', _} -> [{data, [{"State", State}]}]; - Else -> Else + {'EXIT', _} -> DefaultStatus; + StatusList when is_list(StatusList) -> StatusList; + Else -> [Else] end; _ -> - [{data, [{"State", State}]}] + DefaultStatus end, [{header, Header}, {data, [{"Status", SysState}, diff --git a/lib/stdlib/src/io.erl b/lib/stdlib/src/io.erl index 1f8076e864..9f65bbfa3a 100644 --- a/lib/stdlib/src/io.erl +++ b/lib/stdlib/src/io.erl @@ -1,19 +1,19 @@ %% %% %CopyrightBegin% -%% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. -%% +%% +%% Copyright Ericsson AB 1996-2011. 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 %% compliance with the License. You should have received a copy of the %% Erlang Public License along with this software. If not, it can be %% retrieved online at http://www.erlang.org/. -%% +%% %% Software distributed under the License is distributed on an "AS IS" %% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See %% the License for the specific language governing rights and limitations %% under the License. -%% +%% %% %CopyrightEnd% %% -module(io). @@ -32,12 +32,16 @@ parse_erl_form/1,parse_erl_form/2,parse_erl_form/3]). -export([request/1,request/2,requests/1,requests/2]). +-export_type([device/0, format/0]). %%------------------------------------------------------------------------- -type device() :: atom() | pid(). -type prompt() :: atom() | string(). +-type error_description() :: term(). % Whatever the io-server sends. +-type request_error() :: {'error',error_description()}. + %% XXX: Some uses of line() in this file may need to read erl_scan:location() -type line() :: pos_integer(). @@ -52,37 +56,26 @@ to_tuple(T) when is_tuple(T) -> T; to_tuple(T) -> {T}. -%% Problem: the variables Other, Name and Args may collide with surrounding -%% ones. -%% Give extra args to macro, being the variables to use. --define(O_REQUEST(Io, Request), - case request(Io, Request) of - {error, Reason} -> - [Name | Args] = tuple_to_list(to_tuple(Request)), - erlang:error(conv_reason(Name, Reason), [Name, Io | Args]); - Other -> - Other - end). - o_request(Io, Request, Func) -> case request(Io, Request) of {error, Reason} -> [_Name | Args] = tuple_to_list(to_tuple(Request)), - {'EXIT',{undef,[_Current|Mfas]}} = (catch erlang:error(undef)), - MFA = {io, Func, [Io | Args]}, - exit({conv_reason(Func, Reason),[MFA|Mfas]}); -% erlang:error(conv_reason(Name, Reason), [Name, Io | Args]); + {'EXIT',{get_stacktrace,[_Current|Mfas]}} = (catch erlang:error(get_stacktrace)), + erlang:raise(error, conv_reason(Func, Reason), [{io, Func, [Io | Args]}|Mfas]); Other -> Other end. %% Put chars takes mixed *unicode* list from R13 onwards. --spec put_chars(iodata()) -> 'ok'. +-spec put_chars(CharData) -> 'ok' when + CharData :: unicode:chardata(). put_chars(Chars) -> put_chars(default_output(), Chars). --spec put_chars(device(), iodata()) -> 'ok'. +-spec put_chars(IoDevice, IoData) -> 'ok' when + IoDevice :: device(), + IoData :: unicode:chardata(). put_chars(Io, Chars) -> o_request(Io, {put_chars,unicode,Chars}, put_chars). @@ -92,7 +85,8 @@ put_chars(Io, Chars) -> nl() -> nl(default_output()). --spec nl(device()) -> 'ok'. +-spec nl(IoDevice) -> 'ok' when + IoDevice :: device(). nl(Io) -> % o_request(Io, {put_chars,io_lib:nl()}). @@ -103,7 +97,8 @@ nl(Io) -> columns() -> columns(default_output()). --spec columns(device()) -> {'ok', pos_integer()} | {'error', 'enotsup'}. +-spec columns(IoDevice) -> {'ok', pos_integer()} | {'error', 'enotsup'} when + IoDevice :: device(). columns(Io) -> case request(Io, {get_geometry,columns}) of @@ -118,7 +113,8 @@ columns(Io) -> rows() -> rows(default_output()). --spec rows(device()) -> {'ok', pos_integer()} | {'error', 'enotsup'}. +-spec rows(IoDevice) -> {'ok', pos_integer()} | {'error', 'enotsup'} when + IoDevice :: device(). rows(Io) -> case request(Io,{get_geometry,rows}) of @@ -128,22 +124,36 @@ rows(Io) -> {error,enotsup} end. --spec get_chars(prompt(), non_neg_integer()) -> iodata() | 'eof'. +-spec get_chars(Prompt, Count) -> Data | 'eof' when + Prompt :: prompt(), + Count :: non_neg_integer(), + Data :: [unicode:unicode_char()] | unicode:unicode_binary(). get_chars(Prompt, N) -> get_chars(default_input(), Prompt, N). --spec get_chars(device(), prompt(), non_neg_integer()) -> iodata() | 'eof'. +-spec get_chars(IoDevice, Prompt, Count) -> Data | 'eof' | {error, Reason} when + IoDevice :: device(), + Prompt :: prompt(), + Count :: non_neg_integer(), + Reason :: term(), + Data :: [unicode:unicode_char()] | unicode:unicode_binary(). get_chars(Io, Prompt, N) when is_integer(N), N >= 0 -> request(Io, {get_chars,unicode,Prompt,N}). --spec get_line(prompt()) -> iodata() | 'eof' | {'error', term()}. +-spec get_line(Prompt) -> Data | 'eof' | {'error', Reason} when + Prompt :: prompt(), + Reason :: term(), + Data :: [unicode:unicode_char()] | unicode:unicode_binary(). get_line(Prompt) -> get_line(default_input(), Prompt). --spec get_line(device(), prompt()) -> iodata() | 'eof' | {'error', term()}. +-spec get_line(IoDevice, Prompt) -> Data | 'eof' | {'error', term()} when + IoDevice :: device(), + Prompt :: prompt(), + Data :: [unicode:unicode_char()] | unicode:unicode_binary(). get_line(Io, Prompt) -> request(Io, {get_line,unicode,Prompt}). @@ -167,46 +177,62 @@ get_password(Io) -> getopts() -> getopts(default_input()). --spec getopts(device()) -> [opt_pair()]. +-spec getopts(IoDevice) -> [opt_pair()] when + IoDevice :: device(). getopts(Io) -> request(Io, getopts). -type setopt() :: 'binary' | 'list' | opt_pair(). --spec setopts([setopt()]) -> 'ok' | {'error', term()}. +-spec setopts(Opts) -> 'ok' | {'error', Reason} when + Opts :: [setopt()], + Reason :: term(). setopts(Opts) -> setopts(default_input(), Opts). --spec setopts(device(), [setopt()]) -> 'ok' | {'error', term()}. +-spec setopts(IoDevice, Opts) -> 'ok' | {'error', Reason} when + IoDevice :: device(), + Opts :: [setopt()], + Reason :: term(). setopts(Io, Opts) -> request(Io, {setopts, Opts}). %% Writing and reading Erlang terms. --spec write(term()) -> 'ok'. +-spec write(Term) -> 'ok' when + Term :: term(). write(Term) -> write(default_output(), Term). --spec write(device(), term()) -> 'ok'. +-spec write(IoDevice, Term) -> 'ok' when + IoDevice :: device(), + Term :: term(). write(Io, Term) -> o_request(Io, {write,Term}, write). --spec read(prompt()) -> - {'ok', term()} | 'eof' | {'error', erl_scan:error_info()}. +-spec read(Prompt) -> Result when + Prompt :: prompt(), + Result :: {'ok', Term :: term()} + | 'eof' + | {'error', ErrorInfo :: erl_scan:error_info()}. % Read does not use get_until as erl_scan does not work with unicode % XXX:PaN fixme? read(Prompt) -> read(default_input(), Prompt). --spec read(device(), prompt()) -> - {'ok', term()} | 'eof' | {'error', erl_scan:error_info()}. +-spec read(IoDevice, Prompt) -> Result when + IoDevice :: device(), + Prompt :: prompt(), + Result :: {'ok', Term :: term()} + | 'eof' + | {'error', ErrorInfo :: erl_scan:error_info()}. read(Io, Prompt) -> case request(Io, {get_until,unicode,Prompt,erl_scan,tokens,[1]}) of @@ -222,9 +248,13 @@ read(Io, Prompt) -> Other end. --spec read(device(), prompt(), line()) -> - {'ok', term(), line()} | {'eof', line()} | - {'error', erl_scan:error_info(), line()}. +-spec read(IoDevice, Prompt, StartLine) -> Result when + IoDevice :: device(), + Prompt :: prompt(), + StartLine :: line(), + Result :: {'ok', Term :: term(), EndLine :: line()} + | {'eof', EndLine :: line()} + | {'error', ErrorInfo :: erl_scan:error_info(), ErrorLine :: line()}. read(Io, Prompt, StartLine) when is_integer(StartLine) -> case request(Io, {get_until,unicode,Prompt,erl_scan,tokens,[StartLine]}) of @@ -250,28 +280,40 @@ conv_reason(_, _Reason) -> badarg. -type format() :: atom() | string() | binary(). --spec fwrite(format()) -> 'ok'. +-spec fwrite(Format) -> 'ok' when + Format :: format(). fwrite(Format) -> format(Format). --spec fwrite(format(), [term()]) -> 'ok'. +-spec fwrite(Format, Data) -> 'ok' when + Format :: format(), + Data :: [term()]. fwrite(Format, Args) -> format(Format, Args). --spec fwrite(device(), format(), [term()]) -> 'ok'. +-spec fwrite(IoDevice, Format, Data) -> 'ok' when + IoDevice :: device(), + Format :: format(), + Data :: [term()]. fwrite(Io, Format, Args) -> format(Io, Format, Args). --spec fread(prompt(), format()) -> {'ok', [term()]} | 'eof' | {'error',term()}. +-spec fread(Prompt, Format) -> Result when + Prompt :: prompt(), + Format :: format(), + Result :: {'ok', Terms :: [term()]} | 'eof' | {'error', What :: term()}. fread(Prompt, Format) -> fread(default_input(), Prompt, Format). --spec fread(device(), prompt(), format()) -> - {'ok', [term()]} | 'eof' | {'error',term()}. +-spec fread(IoDevice, Prompt, Format) -> Result when + IoDevice :: device(), + Prompt :: prompt(), + Format :: format(), + Result :: {'ok', Terms :: [term()]} | 'eof' | {'error', What :: term()}. fread(Io, Prompt, Format) -> case request(Io, {fread,Prompt,Format}) of @@ -281,72 +323,104 @@ fread(Io, Prompt, Format) -> Other end. --spec format(format()) -> 'ok'. +-spec format(Format) -> 'ok' when + Format :: format(). format(Format) -> format(Format, []). --spec format(format(), [term()]) -> 'ok'. +-spec format(Format, Data) -> 'ok' when + Format :: format(), + Data :: [term()]. format(Format, Args) -> format(default_output(), Format, Args). --spec format(device(), format(), [term()]) -> 'ok'. +-spec format(IoDevice, Format, Data) -> 'ok' when + IoDevice :: device(), + Format :: format(), + Data :: [term()]. format(Io, Format, Args) -> o_request(Io, {format,Format,Args}, format). %% Scanning Erlang code. --spec scan_erl_exprs(prompt()) -> erl_scan:tokens_result(). +-spec scan_erl_exprs(Prompt) -> Result when + Prompt :: prompt(), + Result :: erl_scan:tokens_result() | request_error(). scan_erl_exprs(Prompt) -> scan_erl_exprs(default_input(), Prompt, 1). --spec scan_erl_exprs(device(), prompt()) -> erl_scan:tokens_result(). +-spec scan_erl_exprs(Device, Prompt) -> Result when + Device :: device(), + Prompt :: prompt(), + Result :: erl_scan:tokens_result() | request_error(). scan_erl_exprs(Io, Prompt) -> scan_erl_exprs(Io, Prompt, 1). --spec scan_erl_exprs(device(), prompt(), line()) -> erl_scan:tokens_result(). +-spec scan_erl_exprs(Device, Prompt, StartLine) -> Result when + Device :: device(), + Prompt :: prompt(), + StartLine :: line(), + Result :: erl_scan:tokens_result() | request_error(). scan_erl_exprs(Io, Prompt, Pos0) -> request(Io, {get_until,unicode,Prompt,erl_scan,tokens,[Pos0]}). --spec scan_erl_form(prompt()) -> erl_scan:tokens_result(). +-spec scan_erl_form(Prompt) -> Result when + Prompt :: prompt(), + Result :: erl_scan:tokens_result() | request_error(). scan_erl_form(Prompt) -> scan_erl_form(default_input(), Prompt, 1). --spec scan_erl_form(device(), prompt()) -> erl_scan:tokens_result(). +-spec scan_erl_form(IoDevice, Prompt) -> Result when + IoDevice :: device(), + Prompt :: prompt(), + Result :: erl_scan:tokens_result() | request_error(). scan_erl_form(Io, Prompt) -> scan_erl_form(Io, Prompt, 1). --spec scan_erl_form(device(), prompt(), line()) -> erl_scan:tokens_result(). +-spec scan_erl_form(IoDevice, Prompt, StartLine) -> Result when + IoDevice :: device(), + Prompt :: prompt(), + StartLine :: line(), + Result :: erl_scan:tokens_result() | request_error(). scan_erl_form(Io, Prompt, Pos0) -> request(Io, {get_until,unicode,Prompt,erl_scan,tokens,[Pos0]}). %% Parsing Erlang code. --type erl_parse_expr_list() :: [_]. %% XXX: should be imported from erl_parse - --type parse_ret() :: {'ok', erl_parse_expr_list(), line()} - | {'eof', line()} - | {'error', erl_scan:error_info(), line()}. +-type parse_ret() :: {'ok', ExprList :: erl_parse:abstract_expr(), EndLine :: line()} + | {'eof', EndLine :: line()} + | {'error', ErrorInfo :: erl_scan:error_info(), ErrorLine :: line()} + | request_error(). --spec parse_erl_exprs(prompt()) -> parse_ret(). +-spec parse_erl_exprs(Prompt) -> Result when + Prompt :: prompt(), + Result :: parse_ret(). parse_erl_exprs(Prompt) -> parse_erl_exprs(default_input(), Prompt, 1). --spec parse_erl_exprs(device(), prompt()) -> parse_ret(). +-spec parse_erl_exprs(IoDevice, Prompt) -> Result when + IoDevice :: device(), + Prompt :: prompt(), + Result :: parse_ret(). parse_erl_exprs(Io, Prompt) -> parse_erl_exprs(Io, Prompt, 1). --spec parse_erl_exprs(device(), prompt(), line()) -> parse_ret(). +-spec parse_erl_exprs(IoDevice, Prompt, StartLine) -> Result when + IoDevice :: device(), + Prompt :: prompt(), + StartLine :: line(), + Result :: parse_ret(). parse_erl_exprs(Io, Prompt, Pos0) -> case request(Io, {get_until,unicode,Prompt,erl_scan,tokens,[Pos0]}) of @@ -359,23 +433,31 @@ parse_erl_exprs(Io, Prompt, Pos0) -> Other end. --type erl_parse_absform() :: _. %% XXX: should be imported from erl_parse - --type parse_form_ret() :: {'ok', erl_parse_absform(), line()} - | {'eof', line()} - | {'error', erl_scan:error_info(), line()}. +-type parse_form_ret() :: {'ok', AbsForm :: erl_parse:abstract_form(), EndLine :: line()} + | {'eof', EndLine :: line()} + | {'error', ErrorInfo :: erl_scan:error_info(), ErrorLine :: line()} + | request_error(). --spec parse_erl_form(prompt()) -> parse_form_ret(). +-spec parse_erl_form(Prompt) -> Result when + Prompt :: prompt(), + Result :: parse_form_ret(). parse_erl_form(Prompt) -> parse_erl_form(default_input(), Prompt, 1). --spec parse_erl_form(device(), prompt()) -> parse_form_ret(). +-spec parse_erl_form(IoDevice, Prompt) -> Result when + IoDevice :: device(), + Prompt :: prompt(), + Result :: parse_form_ret(). parse_erl_form(Io, Prompt) -> parse_erl_form(Io, Prompt, 1). --spec parse_erl_form(device(), prompt(), line()) -> parse_form_ret(). +-spec parse_erl_form(IoDevice, Prompt, StartLine) -> Result when + IoDevice :: device(), + Prompt :: prompt(), + StartLine :: line(), + Result :: parse_form_ret(). parse_erl_form(Io, Prompt, Pos0) -> case request(Io, {get_until,unicode,Prompt,erl_scan,tokens,[Pos0]}) of diff --git a/lib/stdlib/src/io_lib.erl b/lib/stdlib/src/io_lib.erl index 26f6ec8931..0252cdf742 100644 --- a/lib/stdlib/src/io_lib.erl +++ b/lib/stdlib/src/io_lib.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2010. All Rights Reserved. +%% Copyright Ericsson AB 1996-2011. 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 @@ -75,33 +75,57 @@ collect_line/2, collect_line/3, collect_line/4, get_until/3, get_until/4]). +-export_type([chars/0, continuation/0]). + %%---------------------------------------------------------------------- - %% XXX: overapproximates a deep list of (unicode) characters --type chars() :: [_]. +-type chars() :: [char() | chars()]. -type depth() :: -1 | non_neg_integer(). +-opaque continuation() :: {_, _, _, _}. % XXX: refine + %%---------------------------------------------------------------------- %% Interface calls to sub-modules. --spec fwrite(io:format(), [term()]) -> chars(). +-spec fwrite(Format, Data) -> chars() | UnicodeList when + Format :: io:format(), + Data :: [term()], + UnicodeList :: [unicode:unicode_char()], + Data :: [term()]. fwrite(Format, Args) -> format(Format, Args). --spec fread(string(), string()) -> io_lib_fread:fread_2_ret(). +-spec fread(Format, String) -> Result when + Format :: string(), + String :: string(), + Result :: {'ok', InputList :: [term()], LeftOverChars :: string()} + | {'more', RestFormat :: string(), + Nchars :: non_neg_integer(), + InputStack :: chars()} + | {'error', What :: term()}. fread(Chars, Format) -> io_lib_fread:fread(Chars, Format). --spec fread(io_lib_fread:continuation(), string(), string()) -> - io_lib_fread:fread_3_ret(). +-spec fread(Continuation, CharSpec, Format) -> Return when + Continuation :: continuation() | [], + CharSpec :: string() | eof, + Format :: string(), + Return :: {'more', Continuation1 :: continuation()} + | {'done', Result, LeftOverChars :: string()}, + Result :: {'ok', InputList :: [term()]} + | 'eof' + | {'error', What :: term()}. fread(Cont, Chars, Format) -> io_lib_fread:fread(Cont, Chars, Format). --spec format(io:format(), [term()]) -> chars(). +-spec format(Format, Data) -> chars() | UnicodeList when + Format :: io:format(), + Data :: [term()], + UnicodeList :: [unicode:unicode_char()]. format(Format, Args) -> case catch io_lib_format:fwrite(Format, Args) of @@ -111,17 +135,24 @@ format(Format, Args) -> Other end. --spec print(term()) -> chars(). +-spec print(Term) -> chars() when + Term :: term(). print(Term) -> io_lib_pretty:print(Term). --spec print(term(), non_neg_integer(), non_neg_integer(), depth()) -> chars(). +-spec print(Term, Column, LineLength, Depth) -> chars() when + Term :: term(), + Column :: non_neg_integer(), + LineLength :: non_neg_integer(), + Depth :: depth(). print(Term, Column, LineLength, Depth) -> io_lib_pretty:print(Term, Column, LineLength, Depth). --spec indentation(string(), integer()) -> integer(). +-spec indentation(String, StartIndent) -> integer() when + String :: string(), + StartIndent :: integer(). indentation(Chars, Current) -> io_lib_format:indentation(Chars, Current). @@ -156,7 +187,8 @@ format_prompt(Format, Args) -> %% Return a (non-flattened) list of characters giving a printed %% representation of the term. write/3 is for backward compatibility. --spec write(term()) -> chars(). +-spec write(Term) -> chars() when + Term :: term(). write(Term) -> write(Term, -1). @@ -167,7 +199,9 @@ write(Term, D, true) -> write(Term, D, false) -> write(Term, D). --spec write(term(), depth()) -> chars(). +-spec write(Term, Depth) -> chars() when + Term :: term(), + Depth :: depth(). write(_Term, 0) -> "..."; write(Term, _D) when is_integer(Term) -> integer_to_list(Term); @@ -232,7 +266,8 @@ write_binary_body(B, _D) -> %% write_atom(Atom) -> [Char] %% Generate the list of characters needed to print an atom. --spec write_atom(atom()) -> chars(). +-spec write_atom(Atom) -> chars() when + Atom :: atom(). write_atom(Atom) -> Chars = atom_to_list(Atom), @@ -281,7 +316,8 @@ name_char(_) -> false. %% write_string([Char]) -> [Char] %% Generate the list of characters needed to print a string. --spec write_string(string()) -> chars(). +-spec write_string(String) -> chars() when + String :: string(). write_string(S) -> write_string(S, $"). %" @@ -328,7 +364,8 @@ string_char(_,C, _, Tail) when C < $\240-> %Other control characters. %% Generate the list of characters needed to print a character constant. %% Must special case SPACE, $\s, here. --spec write_char(char()) -> chars(). +-spec write_char(Char) -> chars() when + Char :: char(). write_char($\s) -> "$\\s"; %Must special case this. write_char(C) when is_integer(C), C >= $\000, C =< $\377 -> @@ -344,7 +381,8 @@ write_unicode_char(Uni) -> %% Return true if CharList is a (possibly deep) list of characters, else %% false. --spec char_list(term()) -> boolean(). +-spec char_list(Term) -> boolean() when + Term :: term(). char_list([C|Cs]) when is_integer(C), C >= $\000, C =< $\377 -> char_list(Cs); @@ -360,7 +398,8 @@ unicode_char_list([C|Cs]) when is_integer(C), C >= 0, C < 16#D800; unicode_char_list([]) -> true; unicode_char_list(_) -> false. %Everything else is false --spec deep_char_list(term()) -> boolean(). +-spec deep_char_list(Term) -> boolean() when + Term :: term(). deep_char_list(Cs) -> deep_char_list(Cs, []). @@ -397,7 +436,8 @@ deep_unicode_char_list(_, _More) -> %Everything else is false %% Return true if CharList is a list of printable characters, else %% false. --spec printable_list(term()) -> boolean(). +-spec printable_list(Term) -> boolean() when + Term :: term(). printable_list([C|Cs]) when is_integer(C), C >= $\040, C =< $\176 -> printable_list(Cs); diff --git a/lib/stdlib/src/io_lib_format.erl b/lib/stdlib/src/io_lib_format.erl index eb1885021d..49a00a4ec7 100644 --- a/lib/stdlib/src/io_lib_format.erl +++ b/lib/stdlib/src/io_lib_format.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. +%% Copyright Ericsson AB 1996-2011. 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 @@ -558,28 +558,30 @@ iolist_to_chars(B) when is_binary(B) -> string(S, none, _Adj, none, _Pad) -> S; string(S, F, Adj, none, Pad) -> - N = lists:flatlength(S), - if N > F -> flat_trunc(S, F); - N =:= F -> S; - true -> adjust(S, chars(Pad, F-N), Adj) - end; + string_field(S, F, Adj, lists:flatlength(S), Pad); string(S, none, _Adj, P, Pad) -> + string_field(S, P, left, lists:flatlength(S), Pad); +string(S, F, Adj, P, Pad) when F >= P -> N = lists:flatlength(S), - if N > P -> flat_trunc(S, P); - N =:= P -> S; - true -> [S|chars(Pad, P-N)] - end; -string(S, F, Adj, F, Pad) -> - string(S, none, Adj, F, Pad); -string(S, F, Adj, P, Pad) when F > P -> - N = lists:flatlength(S), - if N > F -> flat_trunc(S, F); - N =:= F -> S; - N > P -> adjust(flat_trunc(S, P), chars(Pad, F-P), Adj); - N =:= P -> adjust(S, chars(Pad, F-P), Adj); - true -> adjust([S|chars(Pad, P-N)], chars(Pad, F-P), Adj) + if F > P -> + if N > P -> + adjust(flat_trunc(S, P), chars(Pad, F-P), Adj); + N < P -> + adjust([S|chars(Pad, P-N)], chars(Pad, F-P), Adj); + true -> % N == P + adjust(S, chars(Pad, F-P), Adj) + end; + true -> % F == P + string_field(S, F, Adj, N, Pad) end. +string_field(S, F, _Adj, N, _Pad) when N > F -> + flat_trunc(S, F); +string_field(S, F, Adj, N, Pad) when N < F -> + adjust(S, chars(Pad, F-N), Adj); +string_field(S, _, _, _, _) -> % N == F + S. + %% unprefixed_integer(Int, Field, Adjust, Base, PadChar, Lowercase) %% -> [Char]. @@ -624,8 +626,8 @@ newline(F, right, _P, _Pad) -> chars($\n, F). %% adjust(Data, [], _) -> Data; -adjust(Data, Pad, left) -> [Data,Pad]; -adjust(Data, Pad, right) -> [Pad,Data]. +adjust(Data, Pad, left) -> [Data|Pad]; +adjust(Data, Pad, right) -> [Pad|Data]. %% Flatten and truncate a deep list to at most N elements. diff --git a/lib/stdlib/src/io_lib_fread.erl b/lib/stdlib/src/io_lib_fread.erl index 74316dc730..ded1346097 100644 --- a/lib/stdlib/src/io_lib_fread.erl +++ b/lib/stdlib/src/io_lib_fread.erl @@ -1,19 +1,19 @@ %% %% %CopyrightBegin% -%% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. -%% +%% +%% Copyright Ericsson AB 1996-2011. 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 %% compliance with the License. You should have received a copy of the %% Erlang Public License along with this software. If not, it can be %% retrieved online at http://www.erlang.org/. -%% +%% %% Software distributed under the License is distributed on an "AS IS" %% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See %% the License for the specific language governing rights and limitations %% under the License. -%% +%% %% %CopyrightEnd% %% -module(io_lib_fread). @@ -24,23 +24,9 @@ -import(lists, [reverse/1,reverse/2]). -%%----------------------------------------------------------------------- -%% Local types -%%----------------------------------------------------------------------- - --type done_arg2() :: {'ok', io_lib:chars()} | 'eof' | {'error', term()}. - -%%----------------------------------------------------------------------- -%% Types also used in other files -%%----------------------------------------------------------------------- - --type continuation() :: [] | {_, _, _, _}. % XXX: refine - --type fread_2_ret() :: {'ok', io_lib:chars(), string()} - | {'more', string(), non_neg_integer(), io_lib:chars()} - | {'error', term()}. --type fread_3_ret() :: {'more', continuation()} - | {'done', done_arg2(), string()}. +-define(is_whitespace(C), + ((C) =:= $\s orelse (C) =:= $\t + orelse (C) =:= $\r orelse (C) =:= $\n)). %%----------------------------------------------------------------------- @@ -49,7 +35,15 @@ %% repeatedly collects lines and calls fread/2 to format the input until %% all the format string has been used. And it counts the characters. --spec fread(io_lib_fread:continuation(), string(), string()) -> fread_3_ret(). +-spec fread(Continuation, String, Format) -> Return when + Continuation :: io_lib:continuation() | [], + String :: string(), + Format :: string(), + Return :: {'more', Continuation1 :: io_lib:continuation()} + | {'done', Result, LeftOverChars :: string()}, + Result :: {'ok', InputList :: io_lib:chars()} + | 'eof' + | {'error', What :: term()}. fread([], Chars, Format) -> %%io:format("FREAD: ~w `~s'~n", [Format,Chars]), @@ -104,36 +98,39 @@ fread_line(Format0, Line, N0, Results0, More, Newline) -> %% WHITE Skip white space %% X Literal X --spec fread(string(), string()) -> fread_2_ret(). +-spec fread(Format, String) -> Result when + Format :: string(), + String :: string(), + Result :: {'ok', InputList :: io_lib:chars(), LeftOverChars :: string()} + | {'more', RestFormat :: string(), + Nchars :: non_neg_integer(), + InputStack :: io_lib:chars()} + | {'error', What :: term()}. fread(Format, Line) -> fread(Format, Line, 0, []). -fread([$~|Format0], Line, N, Results) -> +fread([$~|Format0]=AllFormat, Line, N, Results) -> {Format,F,Sup,Unicode} = fread_field(Format0), - fread1(Format, F, Sup, Unicode, Line, N, Results, Format0); -fread([$\s|Format], Line, N, Results) -> - fread_skip_white(Format, Line, N, Results); -fread([$\t|Format], Line, N, Results) -> - fread_skip_white(Format, Line, N, Results); -fread([$\r|Format], Line, N, Results) -> - fread_skip_white(Format, Line, N, Results); -fread([$\n|Format], Line, N, Results) -> + fread1(Format, F, Sup, Unicode, Line, N, Results, AllFormat); +fread([C|Format], Line, N, Results) when ?is_whitespace(C) -> fread_skip_white(Format, Line, N, Results); fread([C|Format], [C|Line], N, Results) -> fread(Format, Line, N+1, Results); fread([_F|_Format], [_C|_Line], _N, _Results) -> fread_error(input); +fread([_|_]=Format, [], N, Results) -> + {more,Format,N,Results}; +fread([_|_], eof, 0, []) -> + %% This is at start of input so no error. + eof; +fread([_|_], eof, _N, _Results) -> + %% This is an error as there is no more input. + fread_error(input); fread([], Line, _N, Results) -> {ok,reverse(Results),Line}. -fread_skip_white(Format, [$\s|Line], N, Results) -> - fread_skip_white(Format, Line, N+1, Results); -fread_skip_white(Format, [$\t|Line], N, Results) -> - fread_skip_white(Format, Line, N+1, Results); -fread_skip_white(Format, [$\r|Line], N, Results) -> - fread_skip_white(Format, Line, N+1, Results); -fread_skip_white(Format, [$\n|Line], N, Results) -> +fread_skip_white(Format, [C|Line], N, Results) when ?is_whitespace(C) -> fread_skip_white(Format, Line, N+1, Results); fread_skip_white(Format, Line, N, Results) -> fread(Format, Line, N, Results). @@ -169,9 +166,9 @@ fread1([$l|Format], _F, Sup, _U, Line, N, Res, _AllFormat) -> fread(Format, Line, N, fread_result(Sup, N, Res)); fread1(_Format, _F, _Sup, _U, [], N, Res, AllFormat) -> %% Need more input here. - {more,[$~|AllFormat],N,Res}; -fread1(_Format, _F, _Sup, _U, eof, _N, [], _AllFormat) -> - %% This is at start of format string so no error. + {more,AllFormat,N,Res}; +fread1(_Format, _F, _Sup, _U, eof, 0, [], _AllFormat) -> + %% This is at start of input so no error. eof; fread1(_Format, _F, _Sup, _U, eof, _N, _Res, _AllFormat) -> %% This is an error as there is no more input. @@ -389,26 +386,16 @@ fread_string_cs(Line0, N0, true) -> %% fread_digits(Line, N, Base, Characters) %% Read segments of things, return "thing" characters in reverse order. -fread_skip_white([$\s|Line]) -> fread_skip_white(Line); -fread_skip_white([$\t|Line]) -> fread_skip_white(Line); -fread_skip_white([$\r|Line]) -> fread_skip_white(Line); -fread_skip_white([$\n|Line]) -> fread_skip_white(Line); +fread_skip_white([C|Line]) when ?is_whitespace(C) -> + fread_skip_white(Line); fread_skip_white(Line) -> Line. -fread_skip_white([$\s|Line], N) -> - fread_skip_white(Line, N+1); -fread_skip_white([$\t|Line], N) -> - fread_skip_white(Line, N+1); -fread_skip_white([$\r|Line], N) -> - fread_skip_white(Line, N+1); -fread_skip_white([$\n|Line], N) -> +fread_skip_white([C|Line], N) when ?is_whitespace(C) -> fread_skip_white(Line, N+1); fread_skip_white(Line, N) -> {Line,N}. -fread_skip_latin1_nonwhite([$\s|Line], N, Cs) -> {[$\s|Line],N,Cs}; -fread_skip_latin1_nonwhite([$\t|Line], N, Cs) -> {[$\t|Line],N,Cs}; -fread_skip_latin1_nonwhite([$\r|Line], N, Cs) -> {[$\r|Line],N,Cs}; -fread_skip_latin1_nonwhite([$\n|Line], N, Cs) -> {[$\n|Line],N,Cs}; +fread_skip_latin1_nonwhite([C|Line], N, Cs) when ?is_whitespace(C) -> + {[C|Line],N,Cs}; fread_skip_latin1_nonwhite([C|Line], N, []) when C > 255 -> {[C|Line],N,error}; fread_skip_latin1_nonwhite([C|Line], N, Cs) when C > 255 -> @@ -417,10 +404,8 @@ fread_skip_latin1_nonwhite([C|Line], N, Cs) -> fread_skip_latin1_nonwhite(Line, N+1, [C|Cs]); fread_skip_latin1_nonwhite([], N, Cs) -> {[],N,Cs}. -fread_skip_nonwhite([$\s|Line], N, Cs) -> {[$\s|Line],N,Cs}; -fread_skip_nonwhite([$\t|Line], N, Cs) -> {[$\t|Line],N,Cs}; -fread_skip_nonwhite([$\r|Line], N, Cs) -> {[$\r|Line],N,Cs}; -fread_skip_nonwhite([$\n|Line], N, Cs) -> {[$\n|Line],N,Cs}; +fread_skip_nonwhite([C|Line], N, Cs) when ?is_whitespace(C) -> + {[C|Line],N,Cs}; fread_skip_nonwhite([C|Line], N, Cs) -> fread_skip_nonwhite(Line, N+1, [C|Cs]); fread_skip_nonwhite([], N, Cs) -> {[],N,Cs}. diff --git a/lib/stdlib/src/lib.erl b/lib/stdlib/src/lib.erl index b2cfb00de9..c303ae60b5 100644 --- a/lib/stdlib/src/lib.erl +++ b/lib/stdlib/src/lib.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. +%% Copyright Ericsson AB 1996-2011. 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 @@ -38,7 +38,9 @@ flush_receive() -> %% %% Functions for doing standard system format i/o. %% --spec error_message(atom() | string() | binary(), [term()]) -> 'ok'. +-spec error_message(Format, Args) -> 'ok' when + Format :: io:format(), + Args :: [term()]. error_message(Format, Args) -> io:format(<<"** ~s **\n">>, [io_lib:format(Format, Args)]). @@ -55,17 +57,23 @@ progname() -> no_prog_name end. --spec nonl(string()) -> string(). +-spec nonl(String1) -> String2 when + String1 :: string(), + String2 :: string(). nonl([10]) -> []; nonl([]) -> []; nonl([H|T]) -> [H|nonl(T)]. --spec send(pid() | atom() | {atom(), node()}, term()) -> term(). +-spec send(To, Msg) -> Msg when + To :: pid() | atom() | {atom(), node()}, + Msg :: term(). send(To, Msg) -> To ! Msg. --spec sendw(pid() | atom() | {atom(), node()}, term()) -> term(). +-spec sendw(To, Msg) -> Msg when + To :: pid() | atom() | {atom(), node()}, + Msg :: term(). sendw(To, Msg) -> To ! {self(), Msg}, @@ -89,7 +97,7 @@ eval_str(Str) when is_list(Str) -> true -> case erl_parse:parse_exprs(Toks) of {ok, Exprs} -> - case catch erl_eval:exprs(Exprs, []) of + case catch erl_eval:exprs(Exprs, erl_eval:new_bindings()) of {value, Val, _} -> {ok, Val}; Other -> diff --git a/lib/stdlib/src/lists.erl b/lib/stdlib/src/lists.erl index e1f8d1c200..bba46e4cb6 100644 --- a/lib/stdlib/src/lists.erl +++ b/lib/stdlib/src/lists.erl @@ -1,23 +1,26 @@ %% %% %CopyrightBegin% -%% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. -%% +%% +%% Copyright Ericsson AB 1996-2011. 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 %% compliance with the License. You should have received a copy of the %% Erlang Public License along with this software. If not, it can be %% retrieved online at http://www.erlang.org/. -%% +%% %% Software distributed under the License is distributed on an "AS IS" %% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See %% the License for the specific language governing rights and limitations %% under the License. -%% +%% %% %CopyrightEnd% %% -module(lists). +-compile({no_auto_import,[max/2]}). +-compile({no_auto_import,[min/2]}). + -export([append/2, append/1, subtract/2, reverse/1, nth/2, nthtail/2, prefix/2, suffix/2, last/1, seq/2, seq/3, sum/1, duplicate/2, min/1, max/1, sublist/2, sublist/3, @@ -25,7 +28,7 @@ unzip/1, unzip3/1, zip/2, zip3/3, zipwith/3, zipwith3/4, sort/1, merge/1, merge/2, rmerge/2, merge3/3, rmerge3/3, usort/1, umerge/1, umerge3/3, umerge/2, rumerge3/3, rumerge/2, - concat/1, flatten/1, flatten/2, flat_length/1, flatlength/1, + concat/1, flatten/1, flatten/2, flatlength/1, keydelete/3, keyreplace/4, keytake/3, keystore/4, keysort/2, keymerge/3, rkeymerge/3, rukeymerge/3, ukeysort/2, ukeymerge/3, keymap/3]). @@ -40,8 +43,6 @@ mapfoldl/3,mapfoldr/3,foreach/2,takewhile/2,dropwhile/2,splitwith/2, split/2]). --deprecated([flat_length/1]). - %% member(X, L) -> (true | false) %% test if X is a member of the list L %% Now a BIF! @@ -53,13 +54,21 @@ %% append(X, Y) appends lists X and Y --spec append([T], [T]) -> [T]. +-spec append(List1, List2) -> List3 when + List1 :: [T], + List2 :: [T], + List3 :: [T], + T :: term(). append(L1, L2) -> L1 ++ L2. %% append(L) appends the list of lists L --spec append([[T]]) -> [T]. +-spec append(ListOfLists) -> List1 when + ListOfLists :: [List], + List :: [T], + List1 :: [T], + T :: term(). append([E]) -> E; append([H|T]) -> H ++ append(T); @@ -67,13 +76,20 @@ append([]) -> []. %% subtract(List1, List2) subtract elements in List2 form List1. --spec subtract([T], [T]) -> [T]. +-spec subtract(List1, List2) -> List3 when + List1 :: [T], + List2 :: [T], + List3 :: [T], + T :: term(). subtract(L1, L2) -> L1 -- L2. %% reverse(L) reverse all elements in the list L. Is now a BIF! --spec reverse([T]) -> [T]. +-spec reverse(List1) -> List2 when + List1 :: [T], + List2 :: [T], + T :: term(). reverse([] = L) -> L; @@ -92,13 +108,21 @@ reverse([A, B | L]) -> %% nth(N, L) returns the N`th element of the list L %% nthtail(N, L) returns the N`th tail of the list L --spec nth(pos_integer(), [T,...]) -> T. +-spec nth(N, List) -> Elem when + N :: pos_integer(), + List :: [T,...], + Elem :: T, + T :: term(). nth(1, [H|_]) -> H; nth(N, [_|T]) when N > 1 -> nth(N - 1, T). --spec nthtail(non_neg_integer(), [T,...]) -> [T]. +-spec nthtail(N, List) -> Tail when + N :: non_neg_integer(), + List :: [T,...], + Tail :: [T], + T :: term(). nthtail(1, [_|T]) -> T; nthtail(N, [_|T]) when N > 1 -> @@ -107,7 +131,10 @@ nthtail(0, L) when is_list(L) -> L. %% prefix(Prefix, List) -> (true | false) --spec prefix([T], [T]) -> boolean(). +-spec prefix(List1, List2) -> boolean() when + List1 :: [T], + List2 :: [T], + T :: term(). prefix([X|PreTail], [X|Tail]) -> prefix(PreTail, Tail); @@ -116,7 +143,10 @@ prefix([_|_], List) when is_list(List) -> false. %% suffix(Suffix, List) -> (true | false) --spec suffix([T], [T]) -> boolean(). +-spec suffix(List1, List2) -> boolean() when + List1 :: [T], + List2 :: [T], + T :: term(). suffix(Suffix, List) -> Delta = length(List) - length(Suffix), @@ -124,7 +154,10 @@ suffix(Suffix, List) -> %% last(List) returns the last element in a list. --spec last([T,...]) -> T. +-spec last(List) -> Last when + List :: [T,...], + Last :: T, + T :: term(). last([E|Es]) -> last(E, Es). @@ -136,7 +169,10 @@ last(E, []) -> E. %% returns the sequence Min..Max %% Min <= Max and Min and Max must be integers --spec seq(integer(), integer()) -> [integer()]. +-spec seq(From, To) -> Seq when + From :: integer(), + To :: integer(), + Seq :: [integer()]. seq(First, Last) when is_integer(First), is_integer(Last), First-1 =< Last -> @@ -151,7 +187,11 @@ seq_loop(1, X, L) -> seq_loop(0, _, L) -> L. --spec seq(integer(), integer(), integer()) -> [integer()]. +-spec seq(From, To, Incr) -> Seq when + From :: integer(), + To :: integer(), + Incr :: integer(), + Seq :: [integer()]. seq(First, Last, Inc) when is_integer(First), is_integer(Last), is_integer(Inc) -> @@ -177,7 +217,8 @@ seq_loop(0, _, _, L) -> %% sum(L) returns the sum of the elements in L --spec sum([number()]) -> number(). +-spec sum(List) -> number() when + List :: [number()]. sum(L) -> sum(L, 0). @@ -187,7 +228,11 @@ sum([], Sum) -> Sum. %% duplicate(N, X) -> [X,X,X,.....,X] (N times) %% return N copies of X --spec duplicate(non_neg_integer(), T) -> [T]. +-spec duplicate(N, Elem) -> List when + N :: non_neg_integer(), + Elem :: T, + List :: [T], + T :: term(). duplicate(N, X) when is_integer(N), N >= 0 -> duplicate(N, X, []). @@ -196,7 +241,10 @@ duplicate(N, X, L) -> duplicate(N-1, X, [X|L]). %% min(L) -> returns the minimum element of the list L --spec min([T,...]) -> T. +-spec min(List) -> Min when + List :: [T,...], + Min :: T, + T :: term(). min([H|T]) -> min(T, H). @@ -206,7 +254,10 @@ min([], Min) -> Min. %% max(L) -> returns the maximum element of the list L --spec max([T,...]) -> T. +-spec max(List) -> Max when + List :: [T,...], + Max :: T, + T :: term(). max([H|T]) -> max(T, H). @@ -217,12 +268,21 @@ max([], Max) -> Max. %% sublist(List, Start, Length) %% Returns the sub-list starting at Start of length Length. --spec sublist([T], pos_integer(), non_neg_integer()) -> [T]. +-spec sublist(List1, Start, Len) -> List2 when + List1 :: [T], + List2 :: [T], + Start :: pos_integer(), + Len :: non_neg_integer(), + T :: term(). sublist(List, S, L) when is_integer(L), L >= 0 -> sublist(nthtail(S-1, List), L). --spec sublist([T], non_neg_integer()) -> [T]. +-spec sublist(List1, Len) -> List2 when + List1 :: [T], + List2 :: [T], + Len :: non_neg_integer(), + T :: term(). sublist(List, L) when is_integer(L), is_list(List) -> sublist_2(List, L). @@ -237,7 +297,11 @@ sublist_2(List, L) when is_list(List), L > 0 -> %% delete(Item, List) -> List' %% Delete the first occurrence of Item from the list L. --spec delete(T, [T]) -> [T]. +-spec delete(Elem, List1) -> List2 when + Elem :: T, + List1 :: [T], + List2 :: [T], + T :: term(). delete(Item, [Item|Rest]) -> Rest; delete(Item, [H|Rest]) -> @@ -247,7 +311,12 @@ delete(_, []) -> []. %% Return [{X0, Y0}, {X1, Y1}, ..., {Xn, Yn}] for lists [X0, X1, ..., %% Xn] and [Y0, Y1, ..., Yn]. --spec zip([A], [B]) -> [{A, B}]. +-spec zip(List1, List2) -> List3 when + List1 :: [A], + List2 :: [B], + List3 :: [{A, B}], + A :: term(), + B :: term(). zip([X | Xs], [Y | Ys]) -> [{X, Y} | zip(Xs, Ys)]; zip([], []) -> []. @@ -255,7 +324,12 @@ zip([], []) -> []. %% Return {[X0, X1, ..., Xn], [Y0, Y1, ..., Yn]}, for a list [{X0, Y0}, %% {X1, Y1}, ..., {Xn, Yn}]. --spec unzip([{A, B}]) -> {[A], [B]}. +-spec unzip(List1) -> {List2, List3} when + List1 :: [{A, B}], + List2 :: [A], + List3 :: [B], + A :: term(), + B :: term(). unzip(Ts) -> unzip(Ts, [], []). @@ -265,7 +339,14 @@ unzip([], Xs, Ys) -> {reverse(Xs), reverse(Ys)}. %% Return [{X0, Y0, Z0}, {X1, Y1, Z1}, ..., {Xn, Yn, Zn}] for lists [X0, %% X1, ..., Xn], [Y0, Y1, ..., Yn] and [Z0, Z1, ..., Zn]. --spec zip3([A], [B], [C]) -> [{A, B, C}]. +-spec zip3(List1, List2, List3) -> List4 when + List1 :: [A], + List2 :: [B], + List3 :: [C], + List4 :: [{A, B, C}], + A :: term(), + B :: term(), + C :: term(). zip3([X | Xs], [Y | Ys], [Z | Zs]) -> [{X, Y, Z} | zip3(Xs, Ys, Zs)]; zip3([], [], []) -> []. @@ -273,7 +354,14 @@ zip3([], [], []) -> []. %% Return {[X0, X1, ..., Xn], [Y0, Y1, ..., Yn], [Z0, Z1, ..., Zn]}, for %% a list [{X0, Y0, Z0}, {X1, Y1, Z1}, ..., {Xn, Yn, Zn}]. --spec unzip3([{A, B, C}]) -> {[A], [B], [C]}. +-spec unzip3(List1) -> {List2, List3, List4} when + List1 :: [{A, B, C}], + List2 :: [A], + List3 :: [B], + List4 :: [C], + A :: term(), + B :: term(), + C :: term(). unzip3(Ts) -> unzip3(Ts, [], [], []). @@ -285,7 +373,14 @@ unzip3([], Xs, Ys, Zs) -> %% Return [F(X0, Y0), F(X1, Y1), ..., F(Xn, Yn)] for lists [X0, X1, ..., %% Xn] and [Y0, Y1, ..., Yn]. --spec zipwith(fun((X, Y) -> R), [X], [Y]) -> [R]. +-spec zipwith(Combine, List1, List2) -> List3 when + Combine :: fun((X, Y) -> T), + List1 :: [X], + List2 :: [Y], + List3 :: [T], + X :: term(), + Y :: term(), + T :: term(). zipwith(F, [X | Xs], [Y | Ys]) -> [F(X, Y) | zipwith(F, Xs, Ys)]; zipwith(F, [], []) when is_function(F, 2) -> []. @@ -293,7 +388,16 @@ zipwith(F, [], []) when is_function(F, 2) -> []. %% Return [F(X0, Y0, Z0), F(X1, Y1, Z1), ..., F(Xn, Yn, Zn)] for lists %% [X0, X1, ..., Xn], [Y0, Y1, ..., Yn] and [Z0, Z1, ..., Zn]. --spec zipwith3(fun((X, Y, Z) -> R), [X], [Y], [Z]) -> [R]. +-spec zipwith3(Combine, List1, List2, List3) -> List4 when + Combine :: fun((X, Y, Z) -> T), + List1 :: [X], + List2 :: [Y], + List3 :: [Z], + List4 :: [T], + X :: term(), + Y :: term(), + Z :: term(), + T :: term(). zipwith3(F, [X | Xs], [Y | Ys], [Z | Zs]) -> [F(X, Y, Z) | zipwith3(F, Xs, Ys, Zs)]; @@ -302,7 +406,10 @@ zipwith3(F, [], [], []) when is_function(F, 3) -> []. %% sort(List) -> L %% sorts the list L --spec sort([T]) -> [T]. +-spec sort(List1) -> List2 when + List1 :: [T], + List2 :: [T], + T :: term(). sort([X, Y | L] = L0) when X =< Y -> case L of @@ -349,7 +456,11 @@ sort_1(X, [], R) -> %% merge(List) -> L %% merges a list of sorted lists --spec merge([T]) -> [T]. +-spec merge(ListOfLists) -> List1 when + ListOfLists :: [List], + List :: [T], + List1 :: [T], + T :: term(). merge(L) -> mergel(L, []). @@ -357,7 +468,14 @@ merge(L) -> %% merge3(X, Y, Z) -> L %% merges three sorted lists X, Y and Z --spec merge3([_], [_], [_]) -> [_]. +-spec merge3(List1, List2, List3) -> List4 when + List1 :: [X], + List2 :: [Y], + List3 :: [Z], + List4 :: [(X | Y | Z)], + X :: term(), + Y :: term(), + Z :: term(). merge3(L1, [], L3) -> merge(L1, L3); @@ -369,7 +487,7 @@ merge3(L1, [H2 | T2], [H3 | T3]) -> %% rmerge3(X, Y, Z) -> L %% merges three reversed sorted lists X, Y and Z --spec rmerge3([_], [_], [_]) -> [_]. +-spec rmerge3([X], [Y], [Z]) -> [(X | Y | Z)]. rmerge3(L1, [], L3) -> rmerge(L1, L3); @@ -381,7 +499,12 @@ rmerge3(L1, [H2 | T2], [H3 | T3]) -> %% merge(X, Y) -> L %% merges two sorted lists X and Y --spec merge([_], [_]) -> [_]. +-spec merge(List1, List2) -> List3 when + List1 :: [X], + List2 :: [Y], + List3 :: [(X | Y)], + X :: term(), + Y :: term(). merge(T1, []) -> T1; @@ -393,7 +516,7 @@ merge(T1, [H2 | T2]) -> %% reverse(rmerge(reverse(A),reverse(B))) is equal to merge(I,A,B). --spec rmerge([_], [_]) -> [_]. +-spec rmerge([X], [Y]) -> [(X | Y)]. rmerge(T1, []) -> T1; @@ -404,8 +527,9 @@ rmerge(T1, [H2 | T2]) -> %% in L - the elements in L can be atoms, numbers of strings. %% Returns a list of characters. --type concat_thing() :: atom() | integer() | float() | string(). --spec concat([concat_thing()]) -> string(). +-spec concat(Things) -> string() when + Things :: [Thing], + Thing :: atom() | integer() | float() | string(). concat(List) -> flatmap(fun thing_to_list/1, List). @@ -419,12 +543,17 @@ thing_to_list(X) when is_list(X) -> X. %Assumed to be a string %% flatten(List, Tail) %% Flatten a list, adding optional tail. --spec flatten([_]) -> [_]. +-spec flatten(DeepList) -> List when + DeepList :: [term() | DeepList], + List :: [term()]. flatten(List) when is_list(List) -> do_flatten(List, []). --spec flatten([_], [_]) -> [_]. +-spec flatten(DeepList, Tail) -> List when + DeepList :: [term() | DeepList], + Tail :: [term()], + List :: [term()]. flatten(List, Tail) when is_list(List), is_list(Tail) -> do_flatten(List, Tail). @@ -436,17 +565,11 @@ do_flatten([H|T], Tail) -> do_flatten([], Tail) -> Tail. -%% flat_length(List) (undocumented can be removed later) -%% Calculate the length of a list of lists. - --spec flat_length([_]) -> non_neg_integer(). - -flat_length(List) -> flatlength(List). - %% flatlength(List) %% Calculate the length of a list of lists. --spec flatlength([_]) -> non_neg_integer(). +-spec flatlength(DeepList) -> non_neg_integer() when + DeepList :: [term() | DeepList]. flatlength(List) -> flatlength(List, 0). @@ -487,7 +610,12 @@ flatlength([], L) -> L. % keysearch3(Key, N, T); %keysearch3(Key, N, []) -> false. --spec keydelete(_, pos_integer(), [T]) -> [T]. +-spec keydelete(Key, N, TupleList1) -> TupleList2 when + Key :: term(), + N :: pos_integer(), + TupleList1 :: [Tuple], + TupleList2 :: [Tuple], + Tuple :: tuple(). keydelete(K, N, L) when is_integer(N), N > 0 -> keydelete3(K, N, L). @@ -497,7 +625,12 @@ keydelete3(Key, N, [H|T]) -> [H|keydelete3(Key, N, T)]; keydelete3(_, _, []) -> []. --spec keyreplace(_, pos_integer(), [_], tuple()) -> [_]. +-spec keyreplace(Key, N, TupleList1, NewTuple) -> TupleList2 when + Key :: term(), + N :: pos_integer(), + TupleList1 :: [tuple()], + TupleList2 :: [tuple()], + NewTuple :: tuple(). keyreplace(K, N, L, New) when is_integer(N), N > 0, is_tuple(New) -> keyreplace3(K, N, L, New). @@ -508,7 +641,12 @@ keyreplace3(Key, Pos, [H|T], New) -> [H|keyreplace3(Key, Pos, T, New)]; keyreplace3(_, _, [], _) -> []. --spec keytake(_, pos_integer(), [_]) -> {'value', tuple(), [_]} | 'false'. +-spec keytake(Key, N, TupleList1) -> {value, Tuple, TupleList2} | false when + Key :: term(), + N :: pos_integer(), + TupleList1 :: [tuple()], + TupleList2 :: [tuple()], + Tuple :: tuple(). keytake(Key, N, L) when is_integer(N), N > 0 -> keytake(Key, N, L, []). @@ -519,7 +657,13 @@ keytake(Key, N, [H|T], L) -> keytake(Key, N, T, [H|L]); keytake(_K, _N, [], _L) -> false. --spec keystore(_, pos_integer(), [_], tuple()) -> [_]. +-spec keystore(Key, N, TupleList1, NewTuple) -> TupleList2 when + Key :: term(), + N :: pos_integer(), + TupleList1 :: [tuple()], + TupleList2 :: [tuple(), ...], + NewTuple :: tuple(). + keystore(K, N, L, New) when is_integer(N), N > 0, is_tuple(New) -> keystore2(K, N, L, New). @@ -530,7 +674,11 @@ keystore2(Key, N, [H|T], New) -> keystore2(_Key, _N, [], New) -> [New]. --spec keysort(pos_integer(), [T]) -> [T] when is_subtype(T, tuple()). +-spec keysort(N, TupleList1) -> TupleList2 when + N :: pos_integer(), + TupleList1 :: [Tuple], + TupleList2 :: [Tuple], + Tuple :: tuple(). keysort(I, L) when is_integer(I), I > 0 -> case L of @@ -587,8 +735,13 @@ keysort_1(I, X, EX, [Y | L], R) -> keysort_1(_I, X, _EX, [], R) -> lists:reverse(R, [X]). --spec keymerge(pos_integer(), [X], [Y]) -> - [R] when is_subtype(X, tuple()), is_subtype(Y, tuple()), is_subtype(R, tuple()). +-spec keymerge(N, TupleList1, TupleList2) -> TupleList3 when + N :: pos_integer(), + TupleList1 :: [T1], + TupleList2 :: [T2], + TupleList3 :: [(T1 | T2)], + T1 :: tuple(), + T2 :: tuple(). keymerge(Index, T1, L2) when is_integer(Index), Index > 0 -> case L2 of @@ -603,7 +756,7 @@ keymerge(Index, T1, L2) when is_integer(Index), Index > 0 -> %% reverse(rkeymerge(I,reverse(A),reverse(B))) is equal to keymerge(I,A,B). -spec rkeymerge(pos_integer(), [X], [Y]) -> - [R] when is_subtype(X, tuple()), is_subtype(Y, tuple()), is_subtype(R, tuple()). + [R] when X :: tuple(), Y :: tuple(), R :: tuple(). rkeymerge(Index, T1, L2) when is_integer(Index), Index > 0 -> case L2 of @@ -615,7 +768,11 @@ rkeymerge(Index, T1, L2) when is_integer(Index), Index > 0 -> lists:reverse(M, []) end. --spec ukeysort(pos_integer(), [T]) -> [T] when is_subtype(T, tuple()). +-spec ukeysort(N, TupleList1) -> TupleList2 when + N :: pos_integer(), + TupleList1 :: [Tuple], + TupleList2 :: [Tuple], + Tuple :: tuple(). ukeysort(I, L) when is_integer(I), I > 0 -> case L of @@ -680,8 +837,13 @@ ukeysort_1(I, X, EX, [Y | L]) -> ukeysort_1(_I, X, _EX, []) -> [X]. --spec ukeymerge(pos_integer(), [X], [Y]) -> - [(X | Y)] when is_subtype(X, tuple()), is_subtype(Y, tuple()). +-spec ukeymerge(N, TupleList1, TupleList2) -> TupleList3 when + N :: pos_integer(), + TupleList1 :: [T1], + TupleList2 :: [T2], + TupleList3 :: [(T1 | T2)], + T1 :: tuple(), + T2 :: tuple(). ukeymerge(Index, L1, T2) when is_integer(Index), Index > 0 -> case L1 of @@ -696,7 +858,7 @@ ukeymerge(Index, L1, T2) when is_integer(Index), Index > 0 -> %% reverse(rukeymerge(I,reverse(A),reverse(B))) is equal to ukeymerge(I,A,B). -spec rukeymerge(pos_integer(), [X], [Y]) -> - [(X | Y)] when is_subtype(X, tuple()), is_subtype(Y, tuple()). + [(X | Y)] when X :: tuple(), Y :: tuple(). rukeymerge(Index, T1, L2) when is_integer(Index), Index > 0 -> case L2 of @@ -708,7 +870,11 @@ rukeymerge(Index, T1, L2) when is_integer(Index), Index > 0 -> lists:reverse(M, []) end. --spec keymap(fun((_) -> _), pos_integer(), [tuple()]) -> [tuple()]. +-spec keymap(Fun, N, TupleList1) -> TupleList2 when + Fun :: fun((Term1 :: term()) -> Term2 :: term()), + N :: pos_integer(), + TupleList1 :: [tuple()], + TupleList2 :: [tuple()]. keymap(Fun, Index, [Tup|Tail]) -> [setelement(Index, Tup, Fun(element(Index, Tup)))|keymap(Fun, Index, Tail)]; @@ -717,7 +883,11 @@ keymap(Fun, Index, []) when is_integer(Index), Index >= 1, %%% Suggestion from OTP-2948: sort and merge with Fun. --spec sort(fun((T, T) -> boolean()), [T]) -> [T]. +-spec sort(Fun, List1) -> List2 when + Fun :: fun((A :: T, B :: T) -> boolean()), + List1 :: [T], + List2 :: [T], + T :: term(). sort(Fun, []) when is_function(Fun, 2) -> []; @@ -731,7 +901,13 @@ sort(Fun, [X, Y | T]) -> fsplit_2(Y, X, Fun, T, [], []) end. --spec merge(fun((X, Y) -> boolean()), [X], [Y]) -> [_]. +-spec merge(Fun, List1, List2) -> List3 when + Fun :: fun((A, B) -> boolean()), + List1 :: [A], + List2 :: [B], + List3 :: [(A | B)], + A :: term(), + B :: term(). merge(Fun, T1, [H2 | T2]) when is_function(Fun, 2) -> lists:reverse(fmerge2_1(T1, H2, Fun, T2, []), []); @@ -740,14 +916,18 @@ merge(Fun, T1, []) when is_function(Fun, 2) -> %% reverse(rmerge(F,reverse(A),reverse(B))) is equal to merge(F,A,B). --spec rmerge(fun((X, Y) -> boolean()), [X], [Y]) -> [_]. +-spec rmerge(fun((X, Y) -> boolean()), [X], [Y]) -> [(X | Y)]. rmerge(Fun, T1, [H2 | T2]) when is_function(Fun, 2) -> lists:reverse(rfmerge2_1(T1, H2, Fun, T2, []), []); rmerge(Fun, T1, []) when is_function(Fun, 2) -> T1. --spec usort(fun((T, T) -> boolean()), [T]) -> [T]. +-spec usort(Fun, List1) -> List2 when + Fun :: fun((T, T) -> boolean()), + List1 :: [T], + List2 :: [T], + T :: term(). usort(Fun, [_] = L) when is_function(Fun, 2) -> L; @@ -774,7 +954,13 @@ usort_1(Fun, X, [Y | L]) -> ufsplit_2(Y, L, Fun, [X]) end. --spec umerge(fun((X, Y) -> boolean()), [X], [Y]) -> [_]. +-spec umerge(Fun, List1, List2) -> List3 when + Fun :: fun((A, B) -> boolean()), + List1 :: [A], + List2 :: [B], + List3 :: [(A | B)], + A :: term(), + B :: term(). umerge(Fun, [], T2) when is_function(Fun, 2) -> T2; @@ -783,7 +969,7 @@ umerge(Fun, [H1 | T1], T2) when is_function(Fun, 2) -> %% reverse(rumerge(F,reverse(A),reverse(B))) is equal to umerge(F,A,B). --spec rumerge(fun((X, Y) -> boolean()), [X], [Y]) -> [_]. +-spec rumerge(fun((X, Y) -> boolean()), [X], [Y]) -> [(X | Y)]. rumerge(Fun, T1, []) when is_function(Fun, 2) -> T1; @@ -793,7 +979,10 @@ rumerge(Fun, T1, [H2 | T2]) when is_function(Fun, 2) -> %% usort(List) -> L %% sorts the list L, removes duplicates --spec usort([T]) -> [T]. +-spec usort(List1) -> List2 when + List1 :: [T], + List2 :: [T], + T :: term(). usort([X, Y | L] = L0) when X < Y -> case L of @@ -848,7 +1037,11 @@ usort_1(X, []) -> %% umerge(List) -> L %% merges a list of sorted lists without duplicates, removes duplicates --spec umerge([T]) -> [T]. +-spec umerge(ListOfLists) -> List1 when + ListOfLists :: [List], + List :: [T], + List1 :: [T], + T :: term(). umerge(L) -> umergel(L). @@ -857,7 +1050,14 @@ umerge(L) -> %% merges three sorted lists X, Y and Z without duplicates, %% removes duplicates --spec umerge3([_], [_], [_]) -> [_]. +-spec umerge3(List1, List2, List3) -> List4 when + List1 :: [X], + List2 :: [Y], + List3 :: [Z], + List4 :: [(X | Y | Z)], + X :: term(), + Y :: term(), + Z :: term(). umerge3(L1, [], L3) -> umerge(L1, L3); @@ -870,7 +1070,7 @@ umerge3(L1, [H2 | T2], [H3 | T3]) -> %% merges three reversed sorted lists X, Y and Z without duplicates, %% removes duplicates --spec rumerge3([_], [_], [_]) -> [_]. +-spec rumerge3([X], [Y], [Z]) -> [(X | Y | Z)]. rumerge3(L1, [], L3) -> rumerge(L1, L3); @@ -882,7 +1082,12 @@ rumerge3(L1, [H2 | T2], [H3 | T3]) -> %% umerge(X, Y) -> L %% merges two sorted lists X and Y without duplicates, removes duplicates --spec umerge([_], [_]) -> [_]. +-spec umerge(List1, List2) -> List3 when + List1 :: [X], + List2 :: [Y], + List3 :: [(X | Y)], + X :: term(), + Y :: term(). umerge([], T2) -> T2; @@ -895,7 +1100,7 @@ umerge([H1 | T1], T2) -> %% reverse(rumerge(reverse(A),reverse(B))) is equal to umerge(I,A,B). --spec rumerge([_], [_]) -> [_]. +-spec rumerge([X], [Y]) -> [(X | Y)]. rumerge(T1, []) -> T1; @@ -928,7 +1133,10 @@ rumerge(T1, [H2 | T2]) -> %% There are also versions with an extra argument, ExtraArgs, which is a %% list of extra arguments to each call. --spec all(fun((T) -> boolean()), [T]) -> boolean(). +-spec all(Pred, List) -> boolean() when + Pred :: fun((Elem :: T) -> boolean()), + List :: [T], + T :: term(). all(Pred, [Hd|Tail]) -> case Pred(Hd) of @@ -937,7 +1145,10 @@ all(Pred, [Hd|Tail]) -> end; all(Pred, []) when is_function(Pred, 1) -> true. --spec any(fun((T) -> boolean()), [T]) -> boolean(). +-spec any(Pred, List) -> boolean() when + Pred :: fun((Elem :: T) -> boolean()), + List :: [T], + T :: term(). any(Pred, [Hd|Tail]) -> case Pred(Hd) of @@ -946,31 +1157,59 @@ any(Pred, [Hd|Tail]) -> end; any(Pred, []) when is_function(Pred, 1) -> false. --spec map(fun((D) -> R), [D]) -> [R]. +-spec map(Fun, List1) -> List2 when + Fun :: fun((A) -> B), + List1 :: [A], + List2 :: [B], + A :: term(), + B :: term(). map(F, [H|T]) -> [F(H)|map(F, T)]; map(F, []) when is_function(F, 1) -> []. --spec flatmap(fun((D) -> [R]), [D]) -> [R]. +-spec flatmap(Fun, List1) -> List2 when + Fun :: fun((A) -> [B]), + List1 :: [A], + List2 :: [B], + A :: term(), + B :: term(). flatmap(F, [Hd|Tail]) -> F(Hd) ++ flatmap(F, Tail); flatmap(F, []) when is_function(F, 1) -> []. --spec foldl(fun((T, _) -> _), _, [T]) -> _. +-spec foldl(Fun, Acc0, List) -> Acc1 when + Fun :: fun((Elem :: T, AccIn) -> AccOut), + Acc0 :: term(), + Acc1 :: term(), + AccIn :: term(), + AccOut :: term(), + List :: [T], + T :: term(). foldl(F, Accu, [Hd|Tail]) -> foldl(F, F(Hd, Accu), Tail); foldl(F, Accu, []) when is_function(F, 2) -> Accu. --spec foldr(fun((T, _) -> _), _, [T]) -> _. +-spec foldr(Fun, Acc0, List) -> Acc1 when + Fun :: fun((Elem :: T, AccIn) -> AccOut), + Acc0 :: term(), + Acc1 :: term(), + AccIn :: term(), + AccOut :: term(), + List :: [T], + T :: term(). foldr(F, Accu, [Hd|Tail]) -> F(Hd, foldr(F, Accu, Tail)); foldr(F, Accu, []) when is_function(F, 2) -> Accu. --spec filter(Pred :: fun((T) -> boolean()), List :: [T]) -> [T]. +-spec filter(Pred, List1) -> List2 when + Pred :: fun((Elem :: T) -> boolean()), + List1 :: [T], + List2 :: [T], + T :: term(). filter(Pred, List) when is_function(Pred, 1) -> [ E || E <- List, Pred(E) ]. @@ -978,7 +1217,12 @@ filter(Pred, List) when is_function(Pred, 1) -> %% Equivalent to {filter(F, L), filter(NotF, L)}, if NotF = 'fun(X) -> %% not F(X) end'. --spec partition(Pred :: fun((T) -> boolean()), List :: [T]) -> {[T], [T]}. +-spec partition(Pred, List) -> {Satisfying, NotSatisfying} when + Pred :: fun((Elem :: T) -> boolean()), + List :: [T], + Satisfying :: [T], + NotSatisfying :: [T], + T :: term(). partition(Pred, L) -> partition(Pred, L, [], []). @@ -1004,14 +1248,26 @@ zf(F, [Hd|Tail]) -> end; zf(F, []) when is_function(F, 1) -> []. --spec foreach(F :: fun((T) -> _), List :: [T]) -> 'ok'. +-spec foreach(Fun, List) -> ok when + Fun :: fun((Elem :: T) -> term()), + List :: [T], + T :: term(). foreach(F, [Hd|Tail]) -> F(Hd), foreach(F, Tail); foreach(F, []) when is_function(F, 1) -> ok. --spec mapfoldl(fun((T, _) -> {_, _}), _, [T]) -> {[_], _}. +-spec mapfoldl(Fun, Acc0, List1) -> {List2, Acc1} when + Fun :: fun((A, AccIn) -> {B, AccOut}), + Acc0 :: term(), + Acc1 :: term(), + AccIn :: term(), + AccOut :: term(), + List1 :: [A], + List2 :: [B], + A :: term(), + B :: term(). mapfoldl(F, Accu0, [Hd|Tail]) -> {R,Accu1} = F(Hd, Accu0), @@ -1019,7 +1275,16 @@ mapfoldl(F, Accu0, [Hd|Tail]) -> {[R|Rs],Accu2}; mapfoldl(F, Accu, []) when is_function(F, 2) -> {[],Accu}. --spec mapfoldr(fun((T, _) -> {_, _}), _, [T]) -> {[_], _}. +-spec mapfoldr(Fun, Acc0, List1) -> {List2, Acc1} when + Fun :: fun((A, AccIn) -> {B, AccOut}), + Acc0 :: term(), + Acc1 :: term(), + AccIn :: term(), + AccOut :: term(), + List1 :: [A], + List2 :: [B], + A :: term(), + B :: term(). mapfoldr(F, Accu0, [Hd|Tail]) -> {Rs,Accu1} = mapfoldr(F, Accu0, Tail), @@ -1027,7 +1292,11 @@ mapfoldr(F, Accu0, [Hd|Tail]) -> {[R|Rs],Accu2}; mapfoldr(F, Accu, []) when is_function(F, 2) -> {[],Accu}. --spec takewhile(fun((T) -> boolean()), [T]) -> [T]. +-spec takewhile(Pred, List1) -> List2 when + Pred :: fun((Elem :: T) -> boolean()), + List1 :: [T], + List2 :: [T], + T :: term(). takewhile(Pred, [Hd|Tail]) -> case Pred(Hd) of @@ -1036,7 +1305,11 @@ takewhile(Pred, [Hd|Tail]) -> end; takewhile(Pred, []) when is_function(Pred, 1) -> []. --spec dropwhile(fun((T) -> boolean()), [T]) -> [T]. +-spec dropwhile(Pred, List1) -> List2 when + Pred :: fun((Elem :: T) -> boolean()), + List1 :: [T], + List2 :: [T], + T :: term(). dropwhile(Pred, [Hd|Tail]=Rest) -> case Pred(Hd) of @@ -1045,7 +1318,12 @@ dropwhile(Pred, [Hd|Tail]=Rest) -> end; dropwhile(Pred, []) when is_function(Pred, 1) -> []. --spec splitwith(fun((T) -> boolean()), [T]) -> {[T], [T]}. +-spec splitwith(Pred, List) -> {List1, List2} when + Pred :: fun((T) -> boolean()), + List :: [T], + List1 :: [T], + List2 :: [T], + T :: term(). splitwith(Pred, List) when is_function(Pred, 1) -> splitwith(Pred, List, []). @@ -1058,7 +1336,12 @@ splitwith(Pred, [Hd|Tail], Taken) -> splitwith(Pred, [], Taken) when is_function(Pred, 1) -> {reverse(Taken),[]}. --spec split(non_neg_integer(), [T]) -> {[T], [T]}. +-spec split(N, List1) -> {List2, List3} when + N :: non_neg_integer(), + List1 :: [T], + List2 :: [T], + List3 :: [T], + T :: term(). split(N, List) when is_integer(N), N >= 0, is_list(List) -> case split(N, List, []) of diff --git a/lib/stdlib/src/log_mf_h.erl b/lib/stdlib/src/log_mf_h.erl index 2729f27e51..f7f128dac7 100644 --- a/lib/stdlib/src/log_mf_h.erl +++ b/lib/stdlib/src/log_mf_h.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. +%% Copyright Ericsson AB 1996-2011. 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 @@ -27,14 +27,13 @@ %%----------------------------------------------------------------- --type dir() :: file:filename(). -type b() :: non_neg_integer(). -type f() :: 1..255. -type pred() :: fun((term()) -> boolean()). %%----------------------------------------------------------------- --record(state, {dir :: dir(), +-record(state, {dir :: file:filename(), maxB :: b(), maxF :: f(), curB :: b(), @@ -67,11 +66,23 @@ %% EventMgr = pid() | atom(). %%----------------------------------------------------------------- --spec init(dir(), b(), f()) -> {dir(), b(), f(), pred()}. +-opaque args() :: {file:filename(), b(), f(), pred()}. + + +-spec init(Dir, MaxBytes, MaxFiles) -> Args when + Dir :: file:filename(), + MaxBytes :: non_neg_integer(), % b() + MaxFiles :: 1..255, % f() + Args :: args(). init(Dir, MaxB, MaxF) -> init(Dir, MaxB, MaxF, fun(_) -> true end). --spec init(dir(), b(), f(), pred()) -> {dir(), b(), f(), pred()}. +-spec init(Dir, MaxBytes, MaxFiles, Pred) -> Args when + Dir :: file:filename(), + MaxBytes :: non_neg_integer(), % b() + MaxFiles :: 1..255, % f() + Pred :: fun((Event :: term()) -> boolean()), % pred() + Args :: args(). init(Dir, MaxB, MaxF, Pred) -> {Dir, MaxB, MaxF, Pred}. @@ -79,7 +90,7 @@ init(Dir, MaxB, MaxF, Pred) -> {Dir, MaxB, MaxF, Pred}. %% Call-back functions from gen_event %%----------------------------------------------------------------- --spec init({dir(), b(), f(), pred()}) -> {'ok', #state{}} | {'error', term()}. +-spec init({file:filename(), non_neg_integer(), f(), pred()}) -> {'ok', #state{}} | {'error', term()}. init({Dir, MaxB, MaxF, Pred}) when is_integer(MaxF), MaxF > 0, MaxF < 256 -> First = @@ -185,13 +196,19 @@ read_index_file(Dir) -> %%----------------------------------------------------------------- %% Write the index file. This file contains one binary with %% the last used filename (an integer). +%% Write a temporary file and rename it in order to make the update +%% atomic. %%----------------------------------------------------------------- write_index_file(Dir, Index) -> - case file:open(Dir ++ "/index", [raw, write]) of + File = Dir ++ "/index", + TmpFile = File ++ ".tmp", + case file:open(TmpFile, [raw, write]) of {ok, Fd} -> - file:write(Fd, [Index]), - ok = file:close(Fd); + ok = file:write(Fd, [Index]), + ok = file:close(Fd), + ok = file:rename(TmpFile,File), + ok; _ -> exit(open_index_file) end. diff --git a/lib/stdlib/src/ms_transform.erl b/lib/stdlib/src/ms_transform.erl index 78b1de6e16..48e22e53fa 100644 --- a/lib/stdlib/src/ms_transform.erl +++ b/lib/stdlib/src/ms_transform.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2002-2009. All Rights Reserved. +%% Copyright Ericsson AB 2002-2011. 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 @@ -43,6 +43,7 @@ -define(ERR_GENREMOTECALL,22). -define(ERR_GENBINCONSTRUCT,23). -define(ERR_GENDISALLOWEDOP,24). +-define(WARN_SHADOW_VAR,50). -define(ERR_GUARDMATCH,?ERR_GENMATCH+?ERROR_BASE_GUARD). -define(ERR_BODYMATCH,?ERR_GENMATCH+?ERROR_BASE_BODY). -define(ERR_GUARDLOCALCALL,?ERR_GENLOCALCALL+?ERROR_BASE_GUARD). @@ -63,8 +64,18 @@ -define(ERR_BODYDISALLOWEDOP,?ERR_GENDISALLOWEDOP+?ERROR_BASE_BODY). %% -%% Called by compiler or ets/dbg:fun2ms when errors occur +%% Called by compiler or ets/dbg:fun2ms when errors/warnings occur %% + +-spec(format_error(Error) -> Chars when + Error :: {error, module(), term()}, + Chars :: io_lib:chars()). + +format_error({?WARN_SHADOW_VAR,Name}) -> + lists:flatten( + io_lib:format("variable ~p shadowed in ms_transform fun head", + [Name])); + format_error(?ERR_NOFUN) -> "Parameter of ets/dbg:fun2ms/1 is not a literal fun"; format_error(?ERR_ETS_HEAD) -> @@ -180,9 +191,15 @@ format_error(Else) -> %% %% Called when translating in shell %% + +-spec transform_from_shell(Dialect, Clauses, BoundEnvironment) -> term() when + Dialect :: ets | dbg, + Clauses :: [erl_parse:abstract_clause()], + BoundEnvironment :: erl_eval:binding_struct(). + transform_from_shell(Dialect, Clauses, BoundEnvironment) -> SaveFilename = setup_filename(), - case catch ms_clause_list(1,Clauses,Dialect) of + case catch ms_clause_list(1,Clauses,Dialect,gb_sets:new()) of {'EXIT',Reason} -> cleanup_filename(SaveFilename), exit(Reason); @@ -205,8 +222,14 @@ transform_from_shell(Dialect, Clauses, BoundEnvironment) -> %% %% Called when translating during compiling %% + +-spec parse_transform(Forms, Options) -> Forms when + Forms :: [erl_parse:abstract_form()], + Options :: term(). + parse_transform(Forms, _Options) -> SaveFilename = setup_filename(), + %io:format("Forms: ~p~n",[Forms]), case catch forms(Forms) of {'EXIT',Reason} -> cleanup_filename(SaveFilename), @@ -215,12 +238,31 @@ parse_transform(Forms, _Options) -> {error, [{cleanup_filename(SaveFilename), [{Line, ?MODULE, R}]}], []}; Else -> - cleanup_filename(SaveFilename), + %io:format("Transformed into: ~p~n",[Else]), + case get_warnings() of + [] -> + cleanup_filename(SaveFilename), + Else; + WL -> + FName = cleanup_filename(SaveFilename) , + WList = [ {FName, [{L, ?MODULE, R}]} || {L,R} <- WL ], + {warning, Else, WList} + end + end. + +get_warnings() -> + case get(warnings) of + undefined -> + []; + Else -> Else end. +add_warning(Line,R) -> + put(warnings,[{Line,R}| get_warnings()]). + setup_filename() -> - {erase(filename),erase(records)}. + {erase(filename),erase(records),erase(warnings)}. put_filename(Name) -> put(filename,Name). @@ -235,7 +277,7 @@ get_records() -> Else -> Else end. -cleanup_filename({Old,OldRec}) -> +cleanup_filename({Old,OldRec,OldWarnings}) -> Ret = case erase(filename) of undefined -> "TOP_LEVEL"; @@ -248,6 +290,12 @@ cleanup_filename({Old,OldRec}) -> Rec -> put(records,Rec) end, + case OldWarnings of + undefined -> + erase(warnings); + Warn -> + put(warnings,Warn) + end, case Old of undefined -> Ret; @@ -285,42 +333,77 @@ form({function,Line,Name0,Arity0,Clauses0}) -> form(AnyOther) -> AnyOther. function(Name, Arity, Clauses0) -> - Clauses1 = clauses(Clauses0), + {Clauses1,_} = clauses(Clauses0,gb_sets:new()), {Name,Arity,Clauses1}. -clauses([C0|Cs]) -> - C1 = clause(C0), - [C1|clauses(Cs)]; -clauses([]) -> []. -clause({clause,Line,H0,G0,B0}) -> - B1 = copy(B0), - {clause,Line,H0,G0,B1}. +clauses([C0|Cs],Bound) -> + {C1,Bound1} = clause(C0,Bound), + {C2,Bound2} = clauses(Cs,Bound1), + {[C1|C2],Bound2}; +clauses([],Bound) -> {[],Bound}. +clause({clause,Line,H0,G0,B0},Bound) -> + {H1,Bound1} = copy(H0,Bound), + {B1,Bound2} = copy(B0,Bound1), + {{clause,Line,H1,G0,B1},Bound2}. copy({call,Line,{remote,_Line2,{atom,_Line3,ets},{atom,_Line4,fun2ms}}, - As0}) -> - transform_call(ets,Line,As0); + As0},Bound) -> + {transform_call(ets,Line,As0,Bound),Bound}; copy({call,Line,{remote,_Line2,{record_field,_Line3, {atom,_Line4,''},{atom,_Line5,ets}}, - {atom,_Line6,fun2ms}}, As0}) -> + {atom,_Line6,fun2ms}}, As0},Bound) -> %% Packages... - transform_call(ets,Line,As0); + {transform_call(ets,Line,As0,Bound),Bound}; copy({call,Line,{remote,_Line2,{atom,_Line3,dbg},{atom,_Line4,fun2ms}}, - As0}) -> - transform_call(dbg,Line,As0); -copy(T) when is_tuple(T) -> - list_to_tuple(copy_list(tuple_to_list(T))); -copy(L) when is_list(L) -> - copy_list(L); -copy(AnyOther) -> - AnyOther. + As0},Bound) -> + {transform_call(dbg,Line,As0,Bound),Bound}; +copy({match,Line,A,B},Bound) -> + {B1,Bound1} = copy(B,Bound), + {A1,Bound2} = copy(A,Bound), + {{match,Line,A1,B1},gb_sets:union(Bound1,Bound2)}; +copy({var,_Line,'_'} = VarDef,Bound) -> + {VarDef,Bound}; +copy({var,_Line,Name} = VarDef,Bound) -> + Bound1 = gb_sets:add(Name,Bound), + {VarDef,Bound1}; +copy({'fun',Line,{clauses,Clauses}},Bound) -> % Dont export bindings from funs + {NewClauses,_IgnoredBindings} = copy_list(Clauses,Bound), + {{'fun',Line,{clauses,NewClauses}},Bound}; +copy({'case',Line,Of,ClausesList},Bound) -> % Dont export bindings from funs + {NewOf,NewBind0} = copy(Of,Bound), + {NewClausesList,NewBindings} = copy_case_clauses(ClausesList,NewBind0,[]), + {{'case',Line,NewOf,NewClausesList},NewBindings}; +copy(T,Bound) when is_tuple(T) -> + {L,Bound1} = copy_list(tuple_to_list(T),Bound), + {list_to_tuple(L),Bound1}; +copy(L,Bound) when is_list(L) -> + copy_list(L,Bound); +copy(AnyOther,Bound) -> + {AnyOther,Bound}. -copy_list([H|T]) -> - [copy(H)|copy_list(T)]; -copy_list([]) -> - []. +copy_case_clauses([],Bound,AddSets) -> + ReallyAdded = gb_sets:intersection(AddSets), + {[],gb_sets:union(Bound,ReallyAdded)}; +copy_case_clauses([{clause,Line,Match,Guard,Clauses}|T],Bound,AddSets) -> + {NewMatch,MatchBinds} = copy(Match,Bound), + {NewGuard,GuardBinds} = copy(Guard,MatchBinds), %% Really no new binds + {NewClauses,AllBinds} = copy(Clauses,GuardBinds), + %% To limit the setsizes, I subtract what I had before the case clause + %% and add it in the end + AddedBinds = gb_sets:subtract(AllBinds,Bound), + {NewTail,ExportedBindings} = + copy_case_clauses(T,Bound,[AddedBinds | AddSets]), + {[{clause,Line,NewMatch,NewGuard,NewClauses}|NewTail],ExportedBindings}. -transform_call(Type,_Line,[{'fun',Line2,{clauses, ClauseList}}]) -> - ms_clause_list(Line2, ClauseList,Type); -transform_call(_Type,Line,_NoAbstractFun) -> +copy_list([H|T],Bound) -> + {C1,Bound1} = copy(H,Bound), + {C2,Bound2} = copy_list(T,Bound1), + {[C1|C2],Bound2}; +copy_list([],Bound) -> + {[],Bound}. + +transform_call(Type,_Line,[{'fun',Line2,{clauses, ClauseList}}],Bound) -> + ms_clause_list(Line2, ClauseList,Type,Bound); +transform_call(_Type,Line,_NoAbstractFun,_) -> throw({error,Line,?ERR_NOFUN}). % Fixup semicolons in guards @@ -329,18 +412,19 @@ ms_clause_expand({clause, Line, Parameters, Guard = [_,_|_], Body}) -> ms_clause_expand(_Other) -> false. -ms_clause_list(Line,[H|T],Type) -> +ms_clause_list(Line,[H|T],Type,Bound) -> case ms_clause_expand(H) of NewHead when is_list(NewHead) -> - ms_clause_list(Line,NewHead ++ T, Type); + ms_clause_list(Line,NewHead ++ T, Type, Bound); false -> - {cons, Line, ms_clause(H,Type), ms_clause_list(Line, T,Type)} + {cons, Line, ms_clause(H, Type, Bound), + ms_clause_list(Line, T, Type, Bound)} end; -ms_clause_list(Line,[],_) -> +ms_clause_list(Line,[],_,_) -> {nil,Line}. -ms_clause({clause, Line, Parameters, Guards, Body},Type) -> +ms_clause({clause, Line, Parameters, Guards, Body},Type,Bound) -> check_type(Line,Parameters,Type), - {MSHead,Bindings} = transform_head(Parameters), + {MSHead,Bindings} = transform_head(Parameters,Bound), MSGuards = transform_guards(Line, Guards, Bindings), MSBody = transform_body(Line,Body,Bindings), {tuple, Line, [MSHead,MSGuards,MSBody]}. @@ -627,29 +711,31 @@ tg(Other,B) -> Element = io_lib:format("unknown element ~w", [Other]), throw({error,unknown,{?ERR_GENELEMENT+B#tgd.eb,Element}}). -transform_head([V]) -> +transform_head([V],OuterBound) -> Bind = cre_bind(), - {NewV,NewBind} = toplevel_head_match(V,Bind), - th(NewV,NewBind). + {NewV,NewBind} = toplevel_head_match(V,Bind,OuterBound), + th(NewV,NewBind,OuterBound). -toplevel_head_match({match,_,{var,_,VName},Expr},B) -> +toplevel_head_match({match,Line,{var,_,VName},Expr},B,OB) -> + warn_var_clash(Line,VName,OB), {Expr,new_bind({VName,'$_'},B)}; -toplevel_head_match({match,_,Expr,{var,_,VName}},B) -> +toplevel_head_match({match,Line,Expr,{var,_,VName}},B,OB) -> + warn_var_clash(Line,VName,OB), {Expr,new_bind({VName,'$_'},B)}; -toplevel_head_match(Other,B) -> +toplevel_head_match(Other,B,_OB) -> {Other,B}. -th({record,Line,RName,RFields},B) -> +th({record,Line,RName,RFields},B,OB) -> % youch... RDefs = get_records(), {KeyList0,NewB} = lists:foldl(fun({record_field,_,{atom,_,Key},Value}, {L,B0}) -> - {NV,B1} = th(Value,B0), + {NV,B1} = th(Value,B0,OB), {[{Key,NV}|L],B1}; ({record_field,_,{var,_,'_'},Value}, {L,B0}) -> - {NV,B1} = th(Value,B0), + {NV,B1} = th(Value,B0,OB), {[{{default},NV}|L],B1}; (_,_) -> throw({error,Line,{?ERR_HEADBADREC, @@ -692,9 +778,9 @@ th({record,Line,RName,RFields},B) -> _ -> throw({error,Line,{?ERR_HEADBADREC,RName}}) end; -th({match,Line,_,_},_) -> +th({match,Line,_,_},_,_) -> throw({error,Line,?ERR_HEADMATCH}); -th({atom,Line,A},B) -> +th({atom,Line,A},B,_OB) -> case atom_to_list(A) of [$$|NL] -> case (catch list_to_integer(NL)) of @@ -706,10 +792,11 @@ th({atom,Line,A},B) -> _ -> {{atom,Line,A},B} end; -th({bin_element,_Line0,{var, Line, A},_,_},_) -> +th({bin_element,_Line0,{var, Line, A},_,_},_,_) -> throw({error,Line,{?ERR_HEADBINMATCH,A}}); -th({var,Line,Name},B) -> +th({var,Line,Name},B,OB) -> + warn_var_clash(Line,Name,OB), case lkup_bind(Name,B) of undefined -> NewB = new_bind(Name,B), @@ -717,16 +804,24 @@ th({var,Line,Name},B) -> Trans -> {{atom,Line,Trans},B} end; -th([H|T],B) -> - {NH,NB} = th(H,B), - {NT,NNB} = th(T,NB), +th([H|T],B,OB) -> + {NH,NB} = th(H,B,OB), + {NT,NNB} = th(T,NB,OB), {[NH|NT],NNB}; -th(T,B) when is_tuple(T) -> - {L,NB} = th(tuple_to_list(T),B), +th(T,B,OB) when is_tuple(T) -> + {L,NB} = th(tuple_to_list(T),B,OB), {list_to_tuple(L),NB}; -th(Nonstruct,B) -> +th(Nonstruct,B,_OB) -> {Nonstruct,B}. +warn_var_clash(Line,Name,OuterBound) -> + case gb_sets:is_member(Name,OuterBound) of + true -> + add_warning(Line,{?WARN_SHADOW_VAR,Name}); + _ -> + ok + end. + %% Could be more efficient... check_multi_field(_, _, [], _) -> ok; diff --git a/lib/stdlib/src/orddict.erl b/lib/stdlib/src/orddict.erl index c7b52b933e..45d3c84b3e 100644 --- a/lib/stdlib/src/orddict.erl +++ b/lib/stdlib/src/orddict.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. +%% Copyright Ericsson AB 1996-2011. 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 @@ -25,9 +25,11 @@ -export([store/3,append/3,append_list/3,update/3,update/4,update_counter/3]). -export([fold/3,map/2,filter/2,merge/3]). +-export_type([orddict/0]). + %%--------------------------------------------------------------------------- --type orddict() :: [{term(), term()}]. +-type orddict() :: [{Key :: term(), Value :: term()}]. %%--------------------------------------------------------------------------- @@ -35,45 +37,63 @@ new() -> []. --spec is_key(Key::term(), Dictionary::orddict()) -> boolean(). +-spec is_key(Key, Orddict) -> boolean() when + Key :: term(), + Orddict :: orddict(). is_key(Key, [{K,_}|_]) when Key < K -> false; is_key(Key, [{K,_}|Dict]) when Key > K -> is_key(Key, Dict); is_key(_Key, [{_K,_Val}|_]) -> true; %Key == K is_key(_, []) -> false. --spec to_list(orddict()) -> [{term(), term()}]. +-spec to_list(Orddict) -> List when + Orddict :: orddict(), + List :: [{Key :: term(), Value :: term()}]. to_list(Dict) -> Dict. --spec from_list([{term(), term()}]) -> orddict(). +-spec from_list(List) -> Orddict when + List :: [{Key :: term(), Value :: term()}], + Orddict :: orddict(). from_list(Pairs) -> lists:foldl(fun ({K,V}, D) -> store(K, V, D) end, [], Pairs). --spec size(orddict()) -> non_neg_integer(). +-spec size(Orddict) -> non_neg_integer() when + Orddict :: orddict(). size(D) -> length(D). --spec fetch(Key::term(), Dictionary::orddict()) -> term(). +-spec fetch(Key, Orddict) -> Value when + Key :: term(), + Value :: term(), + Orddict :: orddict(). fetch(Key, [{K,_}|D]) when Key > K -> fetch(Key, D); fetch(Key, [{K,Value}|_]) when Key == K -> Value. --spec find(Key::term(), Dictionary::orddict()) -> {'ok', term()} | 'error'. +-spec find(Key, Orddict) -> {'ok', Value} | 'error' when + Key :: term(), + Orddict :: orddict(), + Value :: term(). find(Key, [{K,_}|_]) when Key < K -> error; find(Key, [{K,_}|D]) when Key > K -> find(Key, D); find(_Key, [{_K,Value}|_]) -> {ok,Value}; %Key == K find(_, []) -> error. --spec fetch_keys(Dictionary::orddict()) -> [term()]. +-spec fetch_keys(Orddict) -> Keys when + Orddict :: orddict(), + Keys :: [term()]. fetch_keys([{Key,_}|Dict]) -> [Key|fetch_keys(Dict)]; fetch_keys([]) -> []. --spec erase(Key::term(), Dictionary::orddict()) -> orddict(). +-spec erase(Key, Orddict1) -> Orddict2 when + Key :: term(), + Orddict1 :: orddict(), + Orddict2 :: orddict(). erase(Key, [{K,_}=E|Dict]) when Key < K -> [E|Dict]; erase(Key, [{K,_}=E|Dict]) when Key > K -> @@ -81,7 +101,11 @@ erase(Key, [{K,_}=E|Dict]) when Key > K -> erase(_Key, [{_K,_Val}|Dict]) -> Dict; %Key == K erase(_, []) -> []. --spec store(Key::term(), Value::term(), Dictionary::orddict()) -> orddict(). +-spec store(Key, Value, Orddict1) -> Orddict2 when + Key :: term(), + Value :: term(), + Orddict1 :: orddict(), + Orddict2 :: orddict(). store(Key, New, [{K,_}=E|Dict]) when Key < K -> [{Key,New},E|Dict]; @@ -91,7 +115,11 @@ store(Key, New, [{_K,_Old}|Dict]) -> %Key == K [{Key,New}|Dict]; store(Key, New, []) -> [{Key,New}]. --spec append(Key::term(), Value::term(), Dictionary::orddict()) -> orddict(). +-spec append(Key, Value, Orddict1) -> Orddict2 when + Key :: term(), + Value :: term(), + Orddict1 :: orddict(), + Orddict2 :: orddict(). append(Key, New, [{K,_}=E|Dict]) when Key < K -> [{Key,[New]},E|Dict]; @@ -101,7 +129,11 @@ append(Key, New, [{_K,Old}|Dict]) -> %Key == K [{Key,Old ++ [New]}|Dict]; append(Key, New, []) -> [{Key,[New]}]. --spec append_list(Key::term(), ValueList::[term()], orddict()) -> orddict(). +-spec append_list(Key, ValList, Orddict1) -> Orddict2 when + Key :: term(), + ValList :: [Value :: term()], + Orddict1 :: orddict(), + Orddict2 :: orddict(). append_list(Key, NewList, [{K,_}=E|Dict]) when Key < K -> [{Key,NewList},E|Dict]; @@ -112,14 +144,23 @@ append_list(Key, NewList, [{_K,Old}|Dict]) -> %Key == K append_list(Key, NewList, []) -> [{Key,NewList}]. --spec update(Key::term(), Fun::fun((term()) -> term()), orddict()) -> orddict(). +-spec update(Key, Fun, Orddict1) -> Orddict2 when + Key :: term(), + Fun :: fun((Value1 :: term()) -> Value2 :: term()), + Orddict1 :: orddict(), + Orddict2 :: orddict(). update(Key, Fun, [{K,_}=E|Dict]) when Key > K -> [E|update(Key, Fun, Dict)]; update(Key, Fun, [{K,Val}|Dict]) when Key == K -> [{Key,Fun(Val)}|Dict]. --spec update(term(), fun((term()) -> term()), term(), orddict()) -> orddict(). +-spec update(Key, Fun, Initial, Orddict1) -> Orddict2 when + Key :: term(), + Initial :: term(), + Fun :: fun((Value1 :: term()) -> Value2 :: term()), + Orddict1 :: orddict(), + Orddict2 :: orddict(). update(Key, _, Init, [{K,_}=E|Dict]) when Key < K -> [{Key,Init},E|Dict]; @@ -129,7 +170,11 @@ update(Key, Fun, _Init, [{_K,Val}|Dict]) -> %Key == K [{Key,Fun(Val)}|Dict]; update(Key, _, Init, []) -> [{Key,Init}]. --spec update_counter(Key::term(), Incr::number(), orddict()) -> orddict(). +-spec update_counter(Key, Increment, Orddict1) -> Orddict2 when + Key :: term(), + Increment :: number(), + Orddict1 :: orddict(), + Orddict2 :: orddict(). update_counter(Key, Incr, [{K,_}=E|Dict]) when Key < K -> [{Key,Incr},E|Dict]; @@ -139,19 +184,29 @@ update_counter(Key, Incr, [{_K,Val}|Dict]) -> %Key == K [{Key,Val+Incr}|Dict]; update_counter(Key, Incr, []) -> [{Key,Incr}]. --spec fold(fun((term(),term(),term()) -> term()), term(), orddict()) -> term(). +-spec fold(Fun, Acc0, Orddict) -> Acc1 when + Fun :: fun((Key :: term(), Value :: term(), AccIn :: term()) -> AccOut :: term()), + Acc0 :: term(), + Acc1 :: term(), + Orddict :: orddict(). fold(F, Acc, [{Key,Val}|D]) -> fold(F, F(Key, Val, Acc), D); fold(F, Acc, []) when is_function(F, 3) -> Acc. --spec map(fun((term(), term()) -> term()), orddict()) -> orddict(). +-spec map(Fun, Orddict1) -> Orddict2 when + Fun :: fun((Key :: term(), Value1 :: term()) -> Value2 :: term()), + Orddict1 :: orddict(), + Orddict2 :: orddict(). map(F, [{Key,Val}|D]) -> [{Key,F(Key, Val)}|map(F, D)]; map(F, []) when is_function(F, 2) -> []. --spec filter(fun((term(), term()) -> term()), orddict()) -> orddict(). +-spec filter(Pred, Orddict1) -> Orddict2 when + Pred :: fun((Key :: term(), Value :: term()) -> boolean()), + Orddict1 :: orddict(), + Orddict2 :: orddict(). filter(F, [{Key,Val}=E|D]) -> case F(Key, Val) of @@ -160,8 +215,11 @@ filter(F, [{Key,Val}=E|D]) -> end; filter(F, []) when is_function(F, 2) -> []. --spec merge(fun((term(), term(), term()) -> term()), orddict(), orddict()) -> - orddict(). +-spec merge(Fun, Orddict1, Orddict2) -> Orddict3 when + Fun :: fun((Key :: term(), Value1 :: term(), Value2 :: term()) -> Value :: term()), + Orddict1 :: orddict(), + Orddict2 :: orddict(), + Orddict3 :: orddict(). merge(F, [{K1,_}=E1|D1], [{K2,_}=E2|D2]) when K1 < K2 -> [E1|merge(F, D1, [E2|D2])]; diff --git a/lib/stdlib/src/ordsets.erl b/lib/stdlib/src/ordsets.erl index 05041c15f1..4a8b1275b2 100644 --- a/lib/stdlib/src/ordsets.erl +++ b/lib/stdlib/src/ordsets.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. +%% Copyright Ericsson AB 1996-2011. 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 @@ -26,19 +26,22 @@ -export([subtract/2,is_subset/2]). -export([fold/3,filter/2]). +-export_type([ordset/1]). + -type ordset(T) :: [T]. %% new() -> Set. %% Return a new empty ordered set. --spec new() -> ordset(term()). +-spec new() -> []. new() -> []. %% is_set(Term) -> boolean(). %% Return 'true' if Set is an ordered set of elements, else 'false'. --spec is_set(term()) -> boolean(). +-spec is_set(Ordset) -> boolean() when + Ordset :: term(). is_set([E|Es]) -> is_set(Es, E); is_set([]) -> true; @@ -52,21 +55,26 @@ is_set([], _) -> true. %% size(OrdSet) -> int(). %% Return the number of elements in OrdSet. --spec size(ordset(_)) -> non_neg_integer(). +-spec size(Ordset) -> non_neg_integer() when + Ordset :: ordset(_). size(S) -> length(S). %% to_list(OrdSet) -> [Elem]. %% Return the elements in OrdSet as a list. --spec to_list(ordset(T)) -> [T]. +-spec to_list(Ordset) -> List when + Ordset :: ordset(T), + List :: [T]. to_list(S) -> S. %% from_list([Elem]) -> Set. %% Build an ordered set from the elements in List. --spec from_list([T]) -> ordset(T). +-spec from_list(List) -> Ordset when + List :: [T], + Ordset :: ordset(T). from_list(L) -> lists:usort(L). @@ -74,7 +82,9 @@ from_list(L) -> %% is_element(Element, OrdSet) -> boolean(). %% Return 'true' if Element is an element of OrdSet, else 'false'. --spec is_element(term(), ordset(_)) -> boolean(). +-spec is_element(Element, Ordset) -> boolean() when + Element :: term(), + Ordset :: ordset(_). is_element(E, [H|Es]) when E > H -> is_element(E, Es); is_element(E, [H|_]) when E < H -> false; @@ -84,7 +94,12 @@ is_element(_, []) -> false. %% add_element(Element, OrdSet) -> OrdSet. %% Return OrdSet with Element inserted in it. --spec add_element(term(), ordset(_)) -> ordset(_). +-spec add_element(Element, Ordset1) -> Ordset2 when + Element :: E, + Ordset1 :: ordset(T), + Ordset2 :: ordset(T | E). + +%-spec add_element(E, ordset(T)) -> [T | E,...]. add_element(E, [H|Es]) when E > H -> [H|add_element(E, Es)]; add_element(E, [H|_]=Set) when E < H -> [E|Set]; @@ -94,7 +109,10 @@ add_element(E, []) -> [E]. %% del_element(Element, OrdSet) -> OrdSet. %% Return OrdSet but with Element removed. --spec del_element(term(), ordset(_)) -> ordset(_). +-spec del_element(Element, Ordset1) -> Ordset2 when + Element :: term(), + Ordset1 :: ordset(T), + Ordset2 :: ordset(T). del_element(E, [H|Es]) when E > H -> [H|del_element(E, Es)]; del_element(E, [H|_]=Set) when E < H -> Set; @@ -104,7 +122,10 @@ del_element(_, []) -> []. %% union(OrdSet1, OrdSet2) -> OrdSet %% Return the union of OrdSet1 and OrdSet2. --spec union(ordset(_), ordset(_)) -> ordset(_). +-spec union(Ordset1, Ordset2) -> Ordset3 when + Ordset1 :: ordset(T1), + Ordset2 :: ordset(T2), + Ordset3 :: ordset(T1 | T2). union([E1|Es1], [E2|_]=Set2) when E1 < E2 -> [E1|union(Es1, Set2)]; @@ -118,7 +139,9 @@ union(Es1, []) -> Es1. %% union([OrdSet]) -> OrdSet %% Return the union of the list of ordered sets. --spec union([ordset(_)]) -> ordset(_). +-spec union(OrdsetList) -> Ordset when + OrdsetList :: [ordset(T)], + Ordset :: ordset(T). union([S1,S2|Ss]) -> union1(union(S1, S2), Ss); @@ -131,7 +154,10 @@ union1(S1, []) -> S1. %% intersection(OrdSet1, OrdSet2) -> OrdSet. %% Return the intersection of OrdSet1 and OrdSet2. --spec intersection(ordset(_), ordset(_)) -> ordset(_). +-spec intersection(Ordset1, Ordset2) -> Ordset3 when + Ordset1 :: ordset(_), + Ordset2 :: ordset(_), + Ordset3 :: ordset(_). intersection([E1|Es1], [E2|_]=Set2) when E1 < E2 -> intersection(Es1, Set2); @@ -147,7 +173,9 @@ intersection(_, []) -> %% intersection([OrdSet]) -> OrdSet. %% Return the intersection of the list of ordered sets. --spec intersection([ordset(_)]) -> ordset(_). +-spec intersection(OrdsetList) -> Ordset when + OrdsetList :: [ordset(_),...], + Ordset :: ordset(_). intersection([S1,S2|Ss]) -> intersection1(intersection(S1, S2), Ss); @@ -160,7 +188,9 @@ intersection1(S1, []) -> S1. %% is_disjoint(OrdSet1, OrdSet2) -> boolean(). %% Check whether OrdSet1 and OrdSet2 are disjoint. --spec is_disjoint(ordset(_), ordset(_)) -> boolean(). +-spec is_disjoint(Ordset1, Ordset2) -> boolean() when + Ordset1 :: ordset(_), + Ordset2 :: ordset(_). is_disjoint([E1|Es1], [E2|_]=Set2) when E1 < E2 -> is_disjoint(Es1, Set2); @@ -177,7 +207,10 @@ is_disjoint(_, []) -> %% Return all and only the elements of OrdSet1 which are not also in %% OrdSet2. --spec subtract(ordset(_), ordset(_)) -> ordset(_). +-spec subtract(Ordset1, Ordset2) -> Ordset3 when + Ordset1 :: ordset(_), + Ordset2 :: ordset(_), + Ordset3 :: ordset(_). subtract([E1|Es1], [E2|_]=Set2) when E1 < E2 -> [E1|subtract(Es1, Set2)]; @@ -192,7 +225,9 @@ subtract(Es1, []) -> Es1. %% Return 'true' when every element of OrdSet1 is also a member of %% OrdSet2, else 'false'. --spec is_subset(ordset(_), ordset(_)) -> boolean(). +-spec is_subset(Ordset1, Ordset2) -> boolean() when + Ordset1 :: ordset(_), + Ordset2 :: ordset(_). is_subset([E1|_], [E2|_]) when E1 < E2 -> %E1 not in Set2 false; @@ -206,7 +241,11 @@ is_subset(_, []) -> false. %% fold(Fun, Accumulator, OrdSet) -> Accumulator. %% Fold function Fun over all elements in OrdSet and return Accumulator. --spec fold(fun((_, _) -> _), _, ordset(_)) -> _. +-spec fold(Function, Acc0, Ordset) -> Acc1 when + Function :: fun((Element :: T, AccIn :: term()) -> AccOut :: term()), + Ordset :: ordset(T), + Acc0 :: term(), + Acc1 :: term(). fold(F, Acc, Set) -> lists:foldl(F, Acc, Set). @@ -214,7 +253,10 @@ fold(F, Acc, Set) -> %% filter(Fun, OrdSet) -> OrdSet. %% Filter OrdSet with Fun. --spec filter(fun((_) -> boolean()), ordset(_)) -> ordset(_). +-spec filter(Pred, Ordset1) -> Ordset2 when + Pred :: fun((Element :: T) -> boolean()), + Ordset1 :: ordset(T), + Ordset2 :: ordset(T). filter(F, Set) -> lists:filter(F, Set). diff --git a/lib/stdlib/src/otp_internal.erl b/lib/stdlib/src/otp_internal.erl index 7ea7de8d58..5129ba5074 100644 --- a/lib/stdlib/src/otp_internal.erl +++ b/lib/stdlib/src/otp_internal.erl @@ -1,19 +1,19 @@ %% %% %CopyrightBegin% -%% -%% Copyright Ericsson AB 1999-2009. All Rights Reserved. -%% +%% +%% Copyright Ericsson AB 1999-2011. 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 %% compliance with the License. You should have received a copy of the %% Erlang Public License along with this software. If not, it can be %% retrieved online at http://www.erlang.org/. -%% +%% %% Software distributed under the License is distributed on an "AS IS" %% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See %% the License for the specific language governing rights and limitations %% under the License. -%% +%% %% %CopyrightEnd% %% -module(otp_internal). @@ -180,6 +180,9 @@ obsolete_1(calendar, local_time_to_universal_time, 1) -> obsolete_1(rpc, safe_multi_server_call, A) when A =:= 2; A =:= 3 -> {deprecated, {rpc, multi_server_call, A}}; + +%% *** SNMP *** + obsolete_1(snmp, N, A) -> case is_snmp_agent_function(N, A) of false -> @@ -189,9 +192,100 @@ obsolete_1(snmp, N, A) -> integer_to_list(A)++" instead"} end; +obsolete_1(snmpm, agent_info, 3) -> + {deprecated, {snmpm, agent_info, 2}, "R16B"}; +obsolete_1(snmpm, update_agent_info, 5) -> + {deprecated, {snmpm, update_agent_info, 4}, "R16B"}; +obsolete_1(snmpm, g, 3) -> + {deprecated, {snmpm, sync_get, 3}, "R16B"}; +obsolete_1(snmpm, g, 4) -> + {deprecated, {snmpm, sync_get, [3,4]}, "R16B"}; +obsolete_1(snmpm, g, 5) -> + {deprecated, {snmpm, sync_get, [4,5]}, "R16B"}; +obsolete_1(snmpm, g, 6) -> + {deprecated, {snmpm, sync_get, [5,6]}, "R16B"}; +obsolete_1(snmpm, g, 7) -> + {deprecated, {snmpm, sync_get, 6}, "R16B"}; +obsolete_1(snmpm, ag, 3) -> + {deprecated, {snmpm, async_get, 3}, "R16B"}; +obsolete_1(snmpm, ag, 4) -> + {deprecated, {snmpm, async_get, [3,4]}, "R16B"}; +obsolete_1(snmpm, ag, 5) -> + {deprecated, {snmpm, async_get, [4,5]}, "R16B"}; +obsolete_1(snmpm, ag, 6) -> + {deprecated, {snmpm, async_get, [5,6]}, "R16B"}; +obsolete_1(snmpm, ag, 7) -> + {deprecated, {snmpm, async_get, 6}, "R16B"}; +obsolete_1(snmpm, gn, 3) -> + {deprecated, {snmpm, sync_get_next, 3}, "R16B"}; +obsolete_1(snmpm, gn, 4) -> + {deprecated, {snmpm, sync_get_next, [3,4]}, "R16B"}; +obsolete_1(snmpm, gn, 5) -> + {deprecated, {snmpm, sync_get_next, [4,5]}, "R16B"}; +obsolete_1(snmpm, gn, 6) -> + {deprecated, {snmpm, sync_get_next, [5,6]}, "R16B"}; +obsolete_1(snmpm, gn, 7) -> + {deprecated, {snmpm, sync_get_next, 6}, "R16B"}; +obsolete_1(snmpm, agn, 3) -> + {deprecated, {snmpm, async_get_next, 3}, "R16B"}; +obsolete_1(snmpm, agn, 4) -> + {deprecated, {snmpm, async_get_next, [3,4]}, "R16B"}; +obsolete_1(snmpm, agn, 5) -> + {deprecated, {snmpm, async_get_next, [4,5]}, "R16B"}; +obsolete_1(snmpm, agn, 6) -> + {deprecated, {snmpm, async_get_next, [5,6]}, "R16B"}; +obsolete_1(snmpm, agn, 7) -> + {deprecated, {snmpm, async_get_next, 6}, "R16B"}; +obsolete_1(snmpm, s, 3) -> + {deprecated, {snmpm, sync_set, 3}, "R16B"}; +obsolete_1(snmpm, s, 4) -> + {deprecated, {snmpm, sync_set, [3,4]}, "R16B"}; +obsolete_1(snmpm, s, 5) -> + {deprecated, {snmpm, sync_set, [4,5]}, "R16B"}; +obsolete_1(snmpm, s, 6) -> + {deprecated, {snmpm, sync_set, [5,6]}, "R16B"}; +obsolete_1(snmpm, s, 7) -> + {deprecated, {snmpm, sync_set, 6}, "R16B"}; +obsolete_1(snmpm, as, 3) -> + {deprecated, {snmpm, async_set, 3}, "R16B"}; +obsolete_1(snmpm, as, 4) -> + {deprecated, {snmpm, async_set, [3,4]}, "R16B"}; +obsolete_1(snmpm, as, 5) -> + {deprecated, {snmpm, async_set, [4,5]}, "R16B"}; +obsolete_1(snmpm, as, 6) -> + {deprecated, {snmpm, async_set, [5,6]}, "R16B"}; +obsolete_1(snmpm, as, 7) -> + {deprecated, {snmpm, async_set, 6}, "R16B"}; +obsolete_1(snmpm, gb, 5) -> + {deprecated, {snmpm, sync_get_bulk, 5}, "R16B"}; +obsolete_1(snmpm, gb, 6) -> + {deprecated, {snmpm, sync_get_bulk, [5,6]}, "R16B"}; +obsolete_1(snmpm, gb, 7) -> + {deprecated, {snmpm, sync_get_bulk, [6,7]}, "R16B"}; +obsolete_1(snmpm, gb, 8) -> + {deprecated, {snmpm, sync_get_bulk, [7,8]}, "R16B"}; +obsolete_1(snmpm, gb, 9) -> + {deprecated, {snmpm, sync_get_bulk, 8}, "R16B"}; +obsolete_1(snmpm, agb, 5) -> + {deprecated, {snmpm, async_get_bulk, 5}, "R16B"}; +obsolete_1(snmpm, agb, 6) -> + {deprecated, {snmpm, async_get_bulk, [5,6]}, "R16B"}; +obsolete_1(snmpm, agb, 7) -> + {deprecated, {snmpm, async_get_bulk, [6,7]}, "R16B"}; +obsolete_1(snmpm, agb, 8) -> + {deprecated, {snmpm, async_get_bulk, [7,8]}, "R16B"}; +obsolete_1(snmpm, agb, 9) -> + {deprecated, {snmpm, async_get_bulk, 8}, "R16B"}; + + +%% *** MEGACO *** + obsolete_1(megaco, format_versions, 1) -> {deprecated, "Deprecated; use megaco:print_version_info/0,1 instead"}; + +%% *** OS-MON-MIB *** + obsolete_1(os_mon_mib, init, 1) -> {deprecated, {os_mon_mib, load, 1}}; obsolete_1(os_mon_mib, stop, 1) -> @@ -236,109 +330,145 @@ obsolete_1(erlang, fault, 2) -> obsolete_1(file, rawopen, 2) -> {removed, "deprecated (will be removed in R13B); use file:open/2 with the raw option"}; -obsolete_1(httpd, start, 0) -> {deprecated,{inets,start,[2,3]},"R14B"}; -obsolete_1(httpd, start, 1) -> {deprecated,{inets,start,[2,3]},"R14B"}; -obsolete_1(httpd, start_link, 1) -> {deprecated,{inets,start,[2,3]},"R14B"}; -obsolete_1(httpd, start_child, 0) -> {deprecated,{inets,start,[2,3]},"R14B"}; -obsolete_1(httpd, start_child, 1) -> {deprecated,{inets,start,[2,3]},"R14B"}; -obsolete_1(httpd, stop, 0) -> {deprecated,{inets,stop,2},"R14B"}; -obsolete_1(httpd, stop, 1) -> {deprecated,{inets,stop,2},"R14B"}; -obsolete_1(httpd, stop, 2) -> {deprecated,{inets,stop,2},"R14B"}; -obsolete_1(httpd, stop_child, 0) -> {deprecated,{inets,stop,2},"R14B"}; -obsolete_1(httpd, stop_child, 1) -> {deprecated,{inets,stop,2},"R14B"}; -obsolete_1(httpd, stop_child, 2) -> {deprecated,{inets,stop,2},"R14B"}; -obsolete_1(httpd, restart, 0) -> {deprecated,{httpd,reload_config,2},"R14B"}; -obsolete_1(httpd, restart, 1) -> {deprecated,{httpd,reload_config,2},"R14B"}; -obsolete_1(httpd, restart, 2) -> {deprecated,{httpd,reload_config,2},"R14B"}; -obsolete_1(httpd, block, 0) -> {deprecated,{httpd,reload_config,2},"R14B"}; -obsolete_1(httpd, block, 1) -> {deprecated,{httpd,reload_config,2},"R14B"}; -obsolete_1(httpd, block, 2) -> {deprecated,{httpd,reload_config,2},"R14B"}; -obsolete_1(httpd, block, 3) -> {deprecated,{httpd,reload_config,2},"R14B"}; -obsolete_1(httpd, block, 4) -> {deprecated,{httpd,reload_config,2},"R14B"}; -obsolete_1(httpd, unblock, 0) -> {deprecated,{httpd,reload_config,2},"R14B"}; -obsolete_1(httpd, unblock, 1) -> {deprecated,{httpd,reload_config,2},"R14B"}; -obsolete_1(httpd, unblock, 2) -> {deprecated,{httpd,reload_config,2},"R14B"}; +obsolete_1(http, request, 1) -> {deprecated,{httpc,request,1},"R15B"}; +obsolete_1(http, request, 2) -> {deprecated,{httpc,request,2},"R15B"}; +obsolete_1(http, request, 4) -> {deprecated,{httpc,request,4},"R15B"}; +obsolete_1(http, request, 5) -> {deprecated,{httpc,request,5},"R15B"}; +obsolete_1(http, cancel_request, 1) -> {deprecated,{httpc,cancel_request,1},"R15B"}; +obsolete_1(http, cancel_request, 2) -> {deprecated,{httpc,cancel_request,2},"R15B"}; +obsolete_1(http, set_option, 2) -> {deprecated,{httpc,set_option,2},"R15B"}; +obsolete_1(http, set_option, 3) -> {deprecated,{httpc,set_option,3},"R15B"}; +obsolete_1(http, set_options, 1) -> {deprecated,{httpc,set_options,1},"R15B"}; +obsolete_1(http, set_options, 2) -> {deprecated,{httpc,set_options,2},"R15B"}; +obsolete_1(http, verify_cookies, 2) -> {deprecated,{httpc,verify_cookies,2},"R15B"}; +obsolete_1(http, verify_cookies, 3) -> {deprecated,{httpc,verify_cookies,3},"R15B"}; +obsolete_1(http, cookie_header, 1) -> {deprecated,{httpc,cookie_header,1},"R15B"}; +obsolete_1(http, cookie_header, 2) -> {deprecated,{httpc,cookie_header,2},"R15B"}; +obsolete_1(http, stream_next, 1) -> {deprecated,{httpc,stream_next,1},"R15B"}; +obsolete_1(http, default_profile, 0) -> {deprecated,{httpc,default_profile,0},"R15B"}; + +obsolete_1(httpd, start, 0) -> {removed,{inets,start,[2,3]},"R14B"}; +obsolete_1(httpd, start, 1) -> {removed,{inets,start,[2,3]},"R14B"}; +obsolete_1(httpd, start_link, 0) -> {removed,{inets,start,[2,3]},"R14B"}; +obsolete_1(httpd, start_link, 1) -> {removed,{inets,start,[2,3]},"R14B"}; +obsolete_1(httpd, start_child, 0) -> {removed,{inets,start,[2,3]},"R14B"}; +obsolete_1(httpd, start_child, 1) -> {removed,{inets,start,[2,3]},"R14B"}; +obsolete_1(httpd, stop, 0) -> {removed,{inets,stop,2},"R14B"}; +obsolete_1(httpd, stop, 1) -> {removed,{inets,stop,2},"R14B"}; +obsolete_1(httpd, stop, 2) -> {removed,{inets,stop,2},"R14B"}; +obsolete_1(httpd, stop_child, 0) -> {removed,{inets,stop,2},"R14B"}; +obsolete_1(httpd, stop_child, 1) -> {removed,{inets,stop,2},"R14B"}; +obsolete_1(httpd, stop_child, 2) -> {removed,{inets,stop,2},"R14B"}; +obsolete_1(httpd, restart, 0) -> {removed,{httpd,reload_config,2},"R14B"}; +obsolete_1(httpd, restart, 1) -> {removed,{httpd,reload_config,2},"R14B"}; +obsolete_1(httpd, restart, 2) -> {removed,{httpd,reload_config,2},"R14B"}; +obsolete_1(httpd, block, 0) -> {removed,{httpd,reload_config,2},"R14B"}; +obsolete_1(httpd, block, 1) -> {removed,{httpd,reload_config,2},"R14B"}; +obsolete_1(httpd, block, 2) -> {removed,{httpd,reload_config,2},"R14B"}; +obsolete_1(httpd, block, 3) -> {removed,{httpd,reload_config,2},"R14B"}; +obsolete_1(httpd, block, 4) -> {removed,{httpd,reload_config,2},"R14B"}; +obsolete_1(httpd, unblock, 0) -> {removed,{httpd,reload_config,2},"R14B"}; +obsolete_1(httpd, unblock, 1) -> {removed,{httpd,reload_config,2},"R14B"}; +obsolete_1(httpd, unblock, 2) -> {removed,{httpd,reload_config,2},"R14B"}; obsolete_1(httpd_util, key1search, 2) -> {removed,{proplists,get_value,2},"R13B"}; obsolete_1(httpd_util, key1search, 3) -> {removed,{proplists,get_value,3},"R13B"}; -obsolete_1(ftp, open, 3) -> {deprecated,{inets,start,[2,3]},"R14B"}; -obsolete_1(ftp, force_active, 1) -> {deprecated,{inets,start,[2,3]},"R14B"}; +obsolete_1(ftp, open, 3) -> {removed,{inets,start,[2,3]},"R14B"}; +obsolete_1(ftp, force_active, 1) -> {removed,{inets,start,[2,3]},"R14B"}; %% Added in R12B-4. obsolete_1(ssh_cm, connect, A) when 1 =< A, A =< 3 -> - {deprecated,{ssh,connect,A},"R14B"}; + {removed,{ssh,connect,A},"R14B"}; obsolete_1(ssh_cm, listen, A) when 2 =< A, A =< 4 -> - {deprecated,{ssh,daemon,A},"R14B"}; + {removed,{ssh,daemon,A},"R14B"}; obsolete_1(ssh_cm, stop_listener, 1) -> - {deprecated,{ssh,stop_listener,[1,2]},"R14B"}; + {removed,{ssh,stop_listener,[1,2]},"R14B"}; obsolete_1(ssh_cm, session_open, A) when A =:= 2; A =:= 4 -> - {deprecated,{ssh_connection,session_channel,A},"R14B"}; + {removed,{ssh_connection,session_channel,A},"R14B"}; obsolete_1(ssh_cm, direct_tcpip, A) when A =:= 6; A =:= 8 -> - {deprecated,{ssh_connection,direct_tcpip,A}}; + {removed,{ssh_connection,direct_tcpip,A}}; obsolete_1(ssh_cm, tcpip_forward, 3) -> - {deprecated,{ssh_connection,tcpip_forward,3},"R14B"}; + {removed,{ssh_connection,tcpip_forward,3},"R14B"}; obsolete_1(ssh_cm, cancel_tcpip_forward, 3) -> - {deprecated,{ssh_connection,cancel_tcpip_forward,3},"R14B"}; + {removed,{ssh_connection,cancel_tcpip_forward,3},"R14B"}; obsolete_1(ssh_cm, open_pty, A) when A =:= 3; A =:= 7; A =:= 9 -> - {deprecated,{ssh_connection,open_pty,A},"R14"}; + {removed,{ssh_connection,open_pty,A},"R14"}; obsolete_1(ssh_cm, setenv, 5) -> - {deprecated,{ssh_connection,setenv,5},"R14B"}; + {removed,{ssh_connection,setenv,5},"R14B"}; obsolete_1(ssh_cm, shell, 2) -> - {deprecated,{ssh_connection,shell,2},"R14B"}; + {removed,{ssh_connection,shell,2},"R14B"}; obsolete_1(ssh_cm, exec, 4) -> - {deprecated,{ssh_connection,exec,4},"R14B"}; + {removed,{ssh_connection,exec,4},"R14B"}; obsolete_1(ssh_cm, subsystem, 4) -> - {deprecated,{ssh_connection,subsystem,4},"R14B"}; + {removed,{ssh_connection,subsystem,4},"R14B"}; obsolete_1(ssh_cm, winch, A) when A =:= 4; A =:= 6 -> - {deprecated,{ssh_connection,window_change,A},"R14B"}; + {removed,{ssh_connection,window_change,A},"R14B"}; obsolete_1(ssh_cm, signal, 3) -> - {deprecated,{ssh_connection,signal,3},"R14B"}; + {removed,{ssh_connection,signal,3},"R14B"}; obsolete_1(ssh_cm, attach, A) when A =:= 2; A =:= 3 -> - {deprecated,{ssh,attach,A}}; + {removed,{ssh,attach,A}}; obsolete_1(ssh_cm, detach, 2) -> - {deprecated,"no longer useful; will be removed in R14B"}; + {removed,"no longer useful; will be removed in R14B"}; obsolete_1(ssh_cm, set_user_ack, 4) -> - {deprecated,"no longer useful; will be removed in R14B"}; + {removed,"no longer useful; will be removed in R14B"}; obsolete_1(ssh_cm, adjust_window, 3) -> - {deprecated,{ssh_connection,adjust_window,3},"R14B"}; + {removed,{ssh_connection,adjust_window,3},"R14B"}; obsolete_1(ssh_cm, close, 2) -> - {deprecated,{ssh_connection,close,2},"R14B"}; + {removed,{ssh_connection,close,2},"R14B"}; obsolete_1(ssh_cm, stop, 1) -> - {deprecated,{ssh,close,1},"R14B"}; + {removed,{ssh,close,1},"R14B"}; obsolete_1(ssh_cm, send_eof, 2) -> - {deprecated,{ssh_connection,send_eof,2},"R14B"}; + {removed,{ssh_connection,send_eof,2},"R14B"}; obsolete_1(ssh_cm, send, A) when A =:= 3; A =:= 4 -> - {deprecated,{ssh_connection,send,A},"R14B"}; + {removed,{ssh_connection,send,A},"R14B"}; obsolete_1(ssh_cm, send_ack, A) when 3 =< A, A =< 5 -> - {deprecated,{ssh_connection,send,[3,4]},"R14B"}; + {removed,{ssh_connection,send,[3,4]},"R14B"}; obsolete_1(ssh_ssh, connect, A) when 1 =< A, A =< 3 -> - {deprecated,{ssh,shell,A},"R14B"}; + {removed,{ssh,shell,A},"R14B"}; obsolete_1(ssh_sshd, listen, A) when 0 =< A, A =< 3 -> - {deprecated,{ssh,daemon,[1,2,3]},"R14"}; + {removed,{ssh,daemon,[1,2,3]},"R14"}; obsolete_1(ssh_sshd, stop, 1) -> - {deprecated,{ssh,stop_listener,1}}; + {removed,{ssh,stop_listener,1}}; %% Added in R13A. obsolete_1(regexp, _, _) -> {deprecated, "the regexp module is deprecated (will be removed in R15A); use the re module instead"}; obsolete_1(lists, flat_length, 1) -> - {deprecated,{lists,flatlength,1},"R14"}; + {removed,{lists,flatlength,1},"R14"}; obsolete_1(ssh_sftp, connect, A) when 1 =< A, A =< 3 -> - {deprecated,{ssh_sftp,start_channel,A},"R14B"}; + {removed,{ssh_sftp,start_channel,A},"R14B"}; obsolete_1(ssh_sftp, stop, 1) -> - {deprecated,{ssh_sftp,stop_channel,1},"R14B"}; + {removed,{ssh_sftp,stop_channel,1},"R14B"}; %% Added in R13B01. obsolete_1(ssl_pkix, decode_cert_file, A) when A =:= 1; A =:= 2 -> - {deprecated,"deprecated (will be removed in R14B); use public_key:pem_to_der/1 and public_key:pkix_decode_cert/2 instead"}; + {removed,"removed in R14A; use public_key:pem_to_der/1 and public_key:pkix_decode_cert/2 instead"}; obsolete_1(ssl_pkix, decode_cert, A) when A =:= 1; A =:= 2 -> - {deprecated,{public_key,pkix_decode_cert,2},"R14B"}; + {removed,{public_key,pkix_decode_cert,2},"R14A"}; %% Added in R13B04. obsolete_1(erlang, concat_binary, 1) -> - {deprecated,{erlang,list_to_binary,1},"R14B"}; - + {deprecated,{erlang,list_to_binary,1},"R15B"}; + +%% 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"}; + +%% 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"}; +obsolete_1(public_key, decode_private_key, A) when A =:= 1; A =:= 2 -> + {deprecated,{public_key,pem_entry_decode,1},"R15A"}; + +%% Added in R14B03. +obsolete_1(docb_gen, _, _) -> + {deprecated,"the DocBuilder application is deprecated (will be removed in R15B)"}; +obsolete_1(docb_transform, _, _) -> + {deprecated,"the DocBuilder application is deprecated (will be removed in R15B)"}; +obsolete_1(docb_xml_check, _, _) -> + {deprecated,"the DocBuilder application is deprecated (will be removed in R15B)"}; + obsolete_1(_, _, _) -> no. diff --git a/lib/stdlib/src/pg.erl b/lib/stdlib/src/pg.erl index 503654e706..ee177e4e0b 100644 --- a/lib/stdlib/src/pg.erl +++ b/lib/stdlib/src/pg.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. +%% Copyright Ericsson AB 1996-2011. 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 @@ -35,7 +35,9 @@ %% Create a brand new empty process group with the master residing %% at the local node --spec create(term()) -> 'ok' | {'error', term()}. +-spec create(PgName) -> 'ok' | {'error', Reason} when + PgName :: term(), + Reason :: 'already_created' | term(). create(PgName) -> catch begin check(PgName), @@ -46,7 +48,10 @@ create(PgName) -> %% Create a brand new empty process group with the master %% residing at Node --spec create(term(), node()) -> 'ok' | {'error', term()}. +-spec create(PgName, Node) -> 'ok' | {'error', Reason} when + PgName :: term(), + Node :: node(), + Reason :: 'already_created' | term(). create(PgName, Node) -> catch begin check(PgName), @@ -66,7 +71,10 @@ standby(_PgName, _Node) -> %% Tell process group PgName that Pid is a new member of the group %% synchronously return a list of all old members in the group --spec join(atom(), pid()) -> [pid()]. +-spec join(PgName, Pid) -> Members when + PgName :: term(), + Pid :: pid(), + Members :: [pid()]. join(PgName, Pid) when is_atom(PgName) -> global:send(PgName, {join,self(),Pid}), @@ -77,7 +85,9 @@ join(PgName, Pid) when is_atom(PgName) -> %% Multi cast Mess to all members in the group --spec send(atom() | pid(), term()) -> 'ok'. +-spec send(PgName, Msg) -> 'ok' when + PgName :: term(), + Msg :: term(). send(PgName, Mess) when is_atom(PgName) -> global:send(PgName, {send, self(), Mess}), @@ -89,7 +99,9 @@ send(Pg, Mess) when is_pid(Pg) -> %% multi cast a message to all members in the group but ourselves %% If we are a member --spec esend(atom() | pid(), term()) -> 'ok'. +-spec esend(PgName, Msg) -> 'ok' when + PgName :: term(), + Msg :: term(). esend(PgName, Mess) when is_atom(PgName) -> global:send(PgName, {esend,self(),Mess}), @@ -100,7 +112,9 @@ esend(Pg, Mess) when is_pid(Pg) -> %% Return the members of the group --spec members(atom() | pid()) -> [pid()]. +-spec members(PgName) -> Members when + PgName :: term(), + Members :: [pid()]. members(PgName) when is_atom(PgName) -> global:send(PgName, {self() ,members}), diff --git a/lib/stdlib/src/pool.erl b/lib/stdlib/src/pool.erl index 7f5f23e26d..a5eb191ab2 100644 --- a/lib/stdlib/src/pool.erl +++ b/lib/stdlib/src/pool.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. +%% Copyright Ericsson AB 1996-2011. 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 @@ -52,11 +52,16 @@ %% Start up using the .hosts.erlang file --spec start(atom()) -> [node()]. +-spec start(Name) -> Nodes when + Name :: atom(), + Nodes :: [node()]. start(Name) -> start(Name,[]). --spec start(atom(), string()) -> [node()]. +-spec start(Name, Args) -> Nodes when + Name :: atom(), + Args :: string(), + Nodes :: [node()]. start(Name, Args) when is_atom(Name) -> gen_server:start({global, pool_master}, pool, [], []), Hosts = net_adm:host_file(), @@ -71,7 +76,8 @@ start(Name, Args) when is_atom(Name) -> get_nodes() -> get_elements(2, get_nodes_and_load()). --spec attach(node()) -> 'already_attached' | 'attached'. +-spec attach(Node) -> 'already_attached' | 'attached' when + Node :: node(). attach(Node) -> gen_server:call({global, pool_master}, {attach, Node}). @@ -82,11 +88,17 @@ get_nodes_and_load() -> get_node() -> gen_server:call({global, pool_master}, get_node). --spec pspawn(module(), atom(), [term()]) -> pid(). +-spec pspawn(Mod, Fun, Args) -> pid() when + Mod :: module(), + Fun :: atom(), + Args :: [term()]. pspawn(M, F, A) -> gen_server:call({global, pool_master}, {spawn, group_leader(), M, F, A}). --spec pspawn_link(module(), atom(), [term()]) -> pid(). +-spec pspawn_link(Mod, Fun, Args) -> pid() when + Mod :: module(), + Fun :: atom(), + Args :: [term()]. pspawn_link(M, F, A) -> P = pspawn(M, F, A), link(P), @@ -95,6 +107,9 @@ pspawn_link(M, F, A) -> start_nodes([], _, _) -> []; start_nodes([Host|Tail], Name, Args) -> case slave:start(Host, Name, Args) of + {error, {already_running, Node}} -> + io:format("Can't start node on host ~w due to ~w~n",[Host, {already_running, Node}]), + [Node | start_nodes(Tail, Name, Args)]; {error, R} -> io:format("Can't start node on host ~w due to ~w~n",[Host, R]), start_nodes(Tail, Name, Args); diff --git a/lib/stdlib/src/proc_lib.erl b/lib/stdlib/src/proc_lib.erl index 9aa5e0a71e..02bcbb5a60 100644 --- a/lib/stdlib/src/proc_lib.erl +++ b/lib/stdlib/src/proc_lib.erl @@ -1,19 +1,19 @@ %% %% %CopyrightBegin% -%% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. -%% +%% +%% Copyright Ericsson AB 1996-2011. 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 %% compliance with the License. You should have received a copy of the %% Erlang Public License along with this software. If not, it can be %% retrieved online at http://www.erlang.org/. -%% +%% %% Software distributed under the License is distributed on an "AS IS" %% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See %% the License for the specific language governing rights and limitations %% under the License. -%% +%% %% %CopyrightEnd% %% -module(proc_lib). @@ -34,81 +34,114 @@ %% Internal exports. -export([wake_up/3]). +-export_type([spawn_option/0]). + %%----------------------------------------------------------------------------- -type priority_level() :: 'high' | 'low' | 'max' | 'normal'. -type spawn_option() :: 'link' + | 'monitor' | {'priority', priority_level()} | {'min_heap_size', non_neg_integer()} + | {'min_bin_vheap_size', non_neg_integer()} | {'fullsweep_after', non_neg_integer()}. --type dict_or_pid() :: pid() | [_] | {integer(), integer(), integer()}. +-type dict_or_pid() :: pid() + | (ProcInfo :: [_]) + | {X :: integer(), Y :: integer(), Z :: integer()}. %%----------------------------------------------------------------------------- --spec spawn(function()) -> pid(). +-spec spawn(Fun) -> pid() when + Fun :: function(). spawn(F) when is_function(F) -> Parent = get_my_name(), Ancestors = get_ancestors(), erlang:spawn(?MODULE, init_p, [Parent,Ancestors,F]). --spec spawn(atom(), atom(), [term()]) -> pid(). +-spec spawn(Module, Function, Args) -> pid() when + Module :: module(), + Function :: atom(), + Args :: [term()]. spawn(M,F,A) when is_atom(M), is_atom(F), is_list(A) -> Parent = get_my_name(), Ancestors = get_ancestors(), erlang:spawn(?MODULE, init_p, [Parent,Ancestors,M,F,A]). --spec spawn_link(function()) -> pid(). +-spec spawn_link(Fun) -> pid() when + Fun :: function(). spawn_link(F) when is_function(F) -> Parent = get_my_name(), Ancestors = get_ancestors(), erlang:spawn_link(?MODULE, init_p, [Parent,Ancestors,F]). --spec spawn_link(atom(), atom(), [term()]) -> pid(). +-spec spawn_link(Module, Function, Args) -> pid() when + Module :: module(), + Function :: atom(), + Args :: [term()]. spawn_link(M,F,A) when is_atom(M), is_atom(F), is_list(A) -> Parent = get_my_name(), Ancestors = get_ancestors(), erlang:spawn_link(?MODULE, init_p, [Parent,Ancestors,M,F,A]). --spec spawn(node(), function()) -> pid(). +-spec spawn(Node, Fun) -> pid() when + Node :: node(), + Fun :: function(). spawn(Node, F) when is_function(F) -> Parent = get_my_name(), Ancestors = get_ancestors(), erlang:spawn(Node, ?MODULE, init_p, [Parent,Ancestors,F]). --spec spawn(node(), atom(), atom(), [term()]) -> pid(). +-spec spawn(Node, Module, Function, Args) -> pid() when + Node :: node(), + Module :: module(), + Function :: atom(), + Args :: [term()]. + spawn(Node, M, F, A) when is_atom(M), is_atom(F), is_list(A) -> Parent = get_my_name(), Ancestors = get_ancestors(), erlang:spawn(Node, ?MODULE, init_p, [Parent,Ancestors,M,F,A]). --spec spawn_link(node(), function()) -> pid(). +-spec spawn_link(Node, Fun) -> pid() when + Node :: node(), + Fun :: function(). spawn_link(Node, F) when is_function(F) -> Parent = get_my_name(), Ancestors = get_ancestors(), erlang:spawn_link(Node, ?MODULE, init_p, [Parent,Ancestors,F]). --spec spawn_link(node(), atom(), atom(), [term()]) -> pid(). +-spec spawn_link(Node, Module, Function, Args) -> pid() when + Node :: node(), + Module :: module(), + Function :: atom(), + Args :: [term()]. spawn_link(Node, M, F, A) when is_atom(M), is_atom(F), is_list(A) -> Parent = get_my_name(), Ancestors = get_ancestors(), erlang:spawn_link(Node, ?MODULE, init_p, [Parent,Ancestors,M,F,A]). --spec spawn_opt(function(), [spawn_option()]) -> pid(). +-spec spawn_opt(Fun, SpawnOpts) -> pid() when + Fun :: function(), + SpawnOpts :: [spawn_option()]. + spawn_opt(F, Opts) when is_function(F) -> Parent = get_my_name(), Ancestors = get_ancestors(), check_for_monitor(Opts), erlang:spawn_opt(?MODULE, init_p, [Parent,Ancestors,F],Opts). --spec spawn_opt(node(), function(), [spawn_option()]) -> pid(). +-spec spawn_opt(Node, Function, SpawnOpts) -> pid() when + Node :: node(), + Function :: function(), + SpawnOpts :: [spawn_option()]. spawn_opt(Node, F, Opts) when is_function(F) -> Parent = get_my_name(), @@ -116,7 +149,11 @@ spawn_opt(Node, F, Opts) when is_function(F) -> check_for_monitor(Opts), erlang:spawn_opt(Node, ?MODULE, init_p, [Parent,Ancestors,F], Opts). --spec spawn_opt(atom(), atom(), [term()], [spawn_option()]) -> pid(). +-spec spawn_opt(Module, Function, Args, SpawnOpts) -> pid() when + Module :: module(), + Function :: atom(), + Args :: [term()], + SpawnOpts :: [spawn_option()]. spawn_opt(M, F, A, Opts) when is_atom(M), is_atom(F), is_list(A) -> Parent = get_my_name(), @@ -124,7 +161,12 @@ spawn_opt(M, F, A, Opts) when is_atom(M), is_atom(F), is_list(A) -> check_for_monitor(Opts), erlang:spawn_opt(?MODULE, init_p, [Parent,Ancestors,M,F,A], Opts). --spec spawn_opt(node(), atom(), atom(), [term()], [spawn_option()]) -> pid(). +-spec spawn_opt(Node, Module, Function, Args, SpawnOpts) -> pid() when + Node :: node(), + Module :: module(), + Function :: atom(), + Args :: [term()], + SpawnOpts :: [spawn_option()]. spawn_opt(Node, M, F, A, Opts) when is_atom(M), is_atom(F), is_list(A) -> Parent = get_my_name(), @@ -142,7 +184,10 @@ check_for_monitor(SpawnOpts) -> false end. --spec hibernate(module(), atom(), [term()]) -> no_return(). +-spec hibernate(Module, Function, Args) -> no_return() when + Module :: module(), + Function :: atom(), + Args :: [term()]. hibernate(M, F, A) when is_atom(M), is_atom(F), is_list(A) -> erlang:hibernate(?MODULE, wake_up, [M, F, A]). @@ -208,35 +253,65 @@ exit_p(Class, Reason) -> exit(Reason) end. --spec start(atom(), atom(), [term()]) -> term(). +-spec start(Module, Function, Args) -> Ret when + Module :: module(), + Function :: atom(), + Args :: [term()], + Ret :: term() | {error, Reason :: term()}. start(M, F, A) when is_atom(M), is_atom(F), is_list(A) -> start(M, F, A, infinity). --spec start(atom(), atom(), [term()], timeout()) -> term(). +-spec start(Module, Function, Args, Time) -> Ret when + Module :: module(), + Function :: atom(), + Args :: [term()], + Time :: timeout(), + Ret :: term() | {error, Reason :: term()}. start(M, F, A, Timeout) when is_atom(M), is_atom(F), is_list(A) -> Pid = ?MODULE:spawn(M, F, A), sync_wait(Pid, Timeout). --spec start(atom(), atom(), [term()], timeout(), [spawn_option()]) -> term(). +-spec start(Module, Function, Args, Time, SpawnOpts) -> Ret when + Module :: module(), + Function :: atom(), + Args :: [term()], + Time :: timeout(), + SpawnOpts :: [spawn_option()], + Ret :: term() | {error, Reason :: term()}. start(M, F, A, Timeout, SpawnOpts) when is_atom(M), is_atom(F), is_list(A) -> Pid = ?MODULE:spawn_opt(M, F, A, SpawnOpts), sync_wait(Pid, Timeout). --spec start_link(atom(), atom(), [term()]) -> term(). +-spec start_link(Module, Function, Args) -> Ret when + Module :: module(), + Function :: atom(), + Args :: [term()], + Ret :: term() | {error, Reason :: term()}. start_link(M, F, A) when is_atom(M), is_atom(F), is_list(A) -> start_link(M, F, A, infinity). --spec start_link(atom(), atom(), [term()], timeout()) -> term(). +-spec start_link(Module, Function, Args, Time) -> Ret when + Module :: module(), + Function :: atom(), + Args :: [term()], + Time :: timeout(), + Ret :: term() | {error, Reason :: term()}. start_link(M, F, A, Timeout) when is_atom(M), is_atom(F), is_list(A) -> Pid = ?MODULE:spawn_link(M, F, A), sync_wait(Pid, Timeout). --spec start_link(atom(),atom(),[term()],timeout(),[spawn_option()]) -> term(). +-spec start_link(Module, Function, Args, Time, SpawnOpts) -> Ret when + Module :: module(), + Function :: atom(), + Args :: [term()], + Time :: timeout(), + SpawnOpts :: [spawn_option()], + Ret :: term() | {error, Reason :: term()}. start_link(M,F,A,Timeout,SpawnOpts) when is_atom(M), is_atom(F), is_list(A) -> Pid = ?MODULE:spawn_opt(M, F, A, ensure_link(SpawnOpts)), @@ -265,13 +340,17 @@ flush(Pid) -> true end. --spec init_ack(pid(), term()) -> 'ok'. +-spec init_ack(Parent, Ret) -> 'ok' when + Parent :: pid(), + Ret :: term(). init_ack(Parent, Return) -> Parent ! {ack, self(), Return}, ok. --spec init_ack(term()) -> 'ok'. +-spec init_ack(Ret) -> 'ok' when + Ret :: term(). + init_ack(Return) -> [Parent|_] = get('$ancestors'), init_ack(Parent, Return). @@ -280,7 +359,11 @@ init_ack(Return) -> %% Fetch the initial call of a proc_lib spawned process. %% ----------------------------------------------------- --spec initial_call(dict_or_pid()) -> {atom(), atom(), [atom()]} | 'false'. +-spec initial_call(Process) -> {Module, Function, Args} | 'false' when + Process :: dict_or_pid(), + Module :: module(), + Function :: atom(), + Args :: [atom()]. initial_call(DictOrPid) -> case raw_initial_call(DictOrPid) of @@ -303,7 +386,11 @@ make_dummy_args(N, Acc) -> %% This function is typically called from c:i() and c:regs(). %% ----------------------------------------------------- --spec translate_initial_call(dict_or_pid()) -> mfa(). +-spec translate_initial_call(Process) -> {Module, Function, Arity} when + Process :: dict_or_pid(), + Module :: module(), + Function :: atom(), + Arity :: byte(). translate_initial_call(DictOrPid) -> case raw_initial_call(DictOrPid) of @@ -575,7 +662,8 @@ check(Res) -> Res. %%% Format (and write) a generated crash info structure. %%% ----------------------------------------------------------- --spec format([term()]) -> string(). +-spec format(CrashReport) -> string() when + CrashReport :: [term()]. format([OwnReport,LinkReport]) -> OwnFormat = format_report(OwnReport), diff --git a/lib/stdlib/src/proplists.erl b/lib/stdlib/src/proplists.erl index 35d14891f1..e3eda5d932 100644 --- a/lib/stdlib/src/proplists.erl +++ b/lib/stdlib/src/proplists.erl @@ -1,19 +1,19 @@ %% %% %CopyrightBegin% -%% -%% Copyright Ericsson AB 2001-2009. All Rights Reserved. -%% +%% +%% Copyright Ericsson AB 2001-2011. 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 %% compliance with the License. You should have received a copy of the %% Erlang Public License along with this software. If not, it can be %% retrieved online at http://www.erlang.org/. -%% +%% %% Software distributed under the License is distributed on an "AS IS" %% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See %% the License for the specific language governing rights and limitations %% under the License. -%% +%% %% %CopyrightEnd% %% %% ===================================================================== @@ -37,7 +37,7 @@ %% overriding the default settings, object properties, annotations, %% etc.</p> %% -%% @type property() = atom() | tuple() +%% % @type property() = atom() | tuple() -module(proplists). @@ -49,16 +49,13 @@ %% --------------------------------------------------------------------- --type property() :: atom() | tuple(). +-export_type([property/0, proplist/0]). --type aliases() :: [{any(), any()}]. --type negations() :: [{any(), any()}]. --type expansions() :: [{property(), [any()]}]. +-type property() :: atom() | tuple(). +-type proplist() :: [property()]. %% --------------------------------------------------------------------- -%% @spec property(P::property()) -> property() -%% %% @doc Creates a normal form (minimal) representation of a property. If %% <code>P</code> is <code>{Key, true}</code> where <code>Key</code> is %% an atom, this returns <code>Key</code>, otherwise the whole term @@ -66,7 +63,8 @@ %% %% @see property/2 --spec property(property()) -> property(). +-spec property(Property) -> Property when + Property :: property(). property({Key, true}) when is_atom(Key) -> Key; @@ -74,8 +72,6 @@ property(Property) -> Property. -%% @spec property(Key::term(), Value::term()) -> property() -%% %% @doc Creates a normal form (minimal) representation of a simple %% key/value property. Returns <code>Key</code> if <code>Value</code> is %% <code>true</code> and <code>Key</code> is an atom, otherwise a tuple @@ -83,7 +79,10 @@ property(Property) -> %% %% @see property/1 --spec property(Key::term(), Value::term()) -> atom() | {term(), term()}. +-spec property(Key, Value) -> Property when + Key :: term(), + Value :: term(), + Property :: atom() | {term(), term()}. property(Key, true) when is_atom(Key) -> Key; @@ -93,14 +92,13 @@ property(Key, Value) -> %% --------------------------------------------------------------------- -%% @spec unfold(List::[term()]) -> [term()] -%% %% @doc Unfolds all occurences of atoms in <code>List</code> to tuples %% <code>{Atom, true}</code>. %% %% @see compact/1 --spec unfold(List::[term()]) -> [term()]. +-spec unfold(List) -> List when + List :: [term()]. unfold([P | Ps]) -> if is_atom(P) -> @@ -111,15 +109,14 @@ unfold([P | Ps]) -> unfold([]) -> []. -%% @spec compact(List::[term()]) -> [term()] -%% %% @doc Minimizes the representation of all entries in the list. This is %% equivalent to <code>[property(P) || P <- List]</code>. %% %% @see unfold/1 %% @see property/1 --spec compact(List::[property()]) -> [property()]. +-spec compact(List) -> List when + List :: [property()]. compact(List) -> [property(P) || P <- List]. @@ -127,8 +124,6 @@ compact(List) -> %% --------------------------------------------------------------------- -%% @spec lookup(Key::term(), List::[term()]) -> none | tuple() -%% %% @doc Returns the first entry associated with <code>Key</code> in %% <code>List</code>, if one exists, otherwise returns %% <code>none</code>. For an atom <code>A</code> in the list, the tuple @@ -138,7 +133,9 @@ compact(List) -> %% @see get_value/2 %% @see get_bool/2 --spec lookup(Key::term(), List::[term()]) -> 'none' | tuple(). +-spec lookup(Key, List) -> 'none' | tuple() when + Key :: term(), + List :: [term()]. lookup(Key, [P | Ps]) -> if is_atom(P), P =:= Key -> @@ -152,15 +149,15 @@ lookup(Key, [P | Ps]) -> lookup(_Key, []) -> none. -%% @spec lookup_all(Key::term(), List::[term()]) -> [tuple()] -%% %% @doc Returns the list of all entries associated with <code>Key</code> %% in <code>List</code>. If no such entry exists, the result is the %% empty list. %% %% @see lookup/2 --spec lookup_all(Key::term(), List::[term()]) -> [tuple()]. +-spec lookup_all(Key, List) -> [tuple()] when + Key :: term(), + List :: [term()]. lookup_all(Key, [P | Ps]) -> if is_atom(P), P =:= Key -> @@ -176,13 +173,13 @@ lookup_all(_Key, []) -> %% --------------------------------------------------------------------- -%% @spec is_defined(Key::term(), List::[term()]) -> boolean() -%% %% @doc Returns <code>true</code> if <code>List</code> contains at least %% one entry associated with <code>Key</code>, otherwise %% <code>false</code> is returned. --spec is_defined(Key::term(), List::[term()]) -> boolean(). +-spec is_defined(Key, List) -> boolean() when + Key :: term(), + List :: [term()]. is_defined(Key, [P | Ps]) -> if is_atom(P), P =:= Key -> @@ -198,17 +195,15 @@ is_defined(_Key, []) -> %% --------------------------------------------------------------------- -%% @spec get_value(Key::term(), List::[term()]) -> term() %% @equiv get_value(Key, List, undefined) --spec get_value(Key::term(), List::[term()]) -> term(). +-spec get_value(Key, List) -> term() when + Key :: term(), + List :: List::[term()]. get_value(Key, List) -> get_value(Key, List, undefined). -%% @spec get_value(Key::term(), List::[term()], Default::term()) -> -%% term() -%% %% @doc Returns the value of a simple key/value property in %% <code>List</code>. If <code>lookup(Key, List)</code> would yield %% <code>{Key, Value}</code>, this function returns the corresponding @@ -219,7 +214,10 @@ get_value(Key, List) -> %% @see get_all_values/2 %% @see get_bool/2 --spec get_value(Key::term(), List::[term()], Default::term()) -> term(). +-spec get_value(Key, List, Default) -> term() when + Key :: term(), + List :: [term()], + Default :: term(). get_value(Key, [P | Ps], Default) -> if is_atom(P), P =:= Key -> @@ -238,8 +236,6 @@ get_value(Key, [P | Ps], Default) -> get_value(_Key, [], Default) -> Default. -%% @spec get_all_values(Key, List) -> [term()] -%% %% @doc Similar to <code>get_value/2</code>, but returns the list of %% values for <em>all</em> entries <code>{Key, Value}</code> in %% <code>List</code>. If no such entry exists, the result is the empty @@ -247,7 +243,9 @@ get_value(_Key, [], Default) -> %% %% @see get_value/2 --spec get_all_values(Key::term(), List::[term()]) -> [term()]. +-spec get_all_values(Key, List) -> [term()] when + Key :: term(), + List :: [term()]. get_all_values(Key, [P | Ps]) -> if is_atom(P), P =:= Key -> @@ -265,8 +263,6 @@ get_all_values(Key, [P | Ps]) -> get_all_values(_Key, []) -> []. -%% @spec append_values(Key::term(), List::[term()]) -> [term()] -%% %% @doc Similar to <code>get_all_values/2</code>, but each value is %% wrapped in a list unless it is already itself a list, and the %% resulting list of lists is concatenated. This is often useful for @@ -276,7 +272,9 @@ get_all_values(_Key, []) -> %% %% @see get_all_values/2 --spec append_values(Key::term(), List::[term()]) -> [term()]. +-spec append_values(Key, List) -> List when + Key :: term(), + List :: [term()]. append_values(Key, [P | Ps]) -> if is_atom(P), P =:= Key -> @@ -299,8 +297,6 @@ append_values(_Key, []) -> %% --------------------------------------------------------------------- -%% @spec get_bool(Key::term(), List::[term()]) -> boolean() -%% %% @doc Returns the value of a boolean key/value option. If %% <code>lookup(Key, List)</code> would yield <code>{Key, true}</code>, %% this function returns <code>true</code>; otherwise <code>false</code> @@ -309,7 +305,9 @@ append_values(_Key, []) -> %% @see lookup/2 %% @see get_value/2 --spec get_bool(Key::term(), List::[term()]) -> boolean(). +-spec get_bool(Key, List) -> boolean() when + Key :: term(), + List :: [term()]. get_bool(Key, [P | Ps]) -> if is_atom(P), P =:= Key -> @@ -331,12 +329,11 @@ get_bool(_Key, []) -> %% --------------------------------------------------------------------- -%% @spec get_keys(List::[term()]) -> [term()] -%% %% @doc Returns an unordered list of the keys used in <code>List</code>, %% not containing duplicates. --spec get_keys(List::[term()]) -> [term()]. +-spec get_keys(List) -> [term()] when + List :: [term()]. get_keys(Ps) -> sets:to_list(get_keys(Ps, sets:new())). @@ -355,12 +352,12 @@ get_keys([], Keys) -> %% --------------------------------------------------------------------- -%% @spec delete(Key::term(), List::[term()]) -> [term()] -%% %% @doc Deletes all entries associated with <code>Key</code> from %% <code>List</code>. --spec delete(Key::term(), List::[term()]) -> [term()]. +-spec delete(Key, List) -> List when + Key :: term(), + List::[term()]. delete(Key, [P | Ps]) -> if is_atom(P), P =:= Key -> @@ -376,11 +373,6 @@ delete(_, []) -> %% --------------------------------------------------------------------- -%% @spec substitute_aliases(Aliases, List::[term()]) -> [term()] -%% -%% Aliases = [{Key, Key}] -%% Key = term() -%% %% @doc Substitutes keys of properties. For each entry in %% <code>List</code>, if it is associated with some key <code>K1</code> %% such that <code>{K1, K2}</code> occurs in <code>Aliases</code>, the @@ -396,7 +388,10 @@ delete(_, []) -> %% @see substitute_negations/2 %% @see normalize/2 --spec substitute_aliases(aliases(), List::[term()]) -> [term()]. +-spec substitute_aliases(Aliases, List) -> List when + Aliases :: [{Key, Key}], + Key :: term(), + List::[term()]. substitute_aliases(As, Props) -> [substitute_aliases_1(As, P) || P <- Props]. @@ -415,11 +410,6 @@ substitute_aliases_1([], P) -> %% --------------------------------------------------------------------- -%% @spec substitute_negations(Negations, List::[term()]) -> [term()] -%% -%% Negations = [{Key, Key}] -%% Key = term() -%% %% @doc Substitutes keys of boolean-valued properties and simultaneously %% negates their values. For each entry in <code>List</code>, if it is %% associated with some key <code>K1</code> such that <code>{K1, @@ -441,7 +431,10 @@ substitute_aliases_1([], P) -> %% @see substitute_aliases/2 %% @see normalize/2 --spec substitute_negations(negations(), List::[term()]) -> [term()]. +-spec substitute_negations(Negations, List) -> List when + Negations :: [{Key, Key}], + Key :: term(), + List :: [term()]. substitute_negations(As, Props) -> [substitute_negations_1(As, P) || P <- Props]. @@ -470,10 +463,6 @@ substitute_negations_1([], P) -> %% --------------------------------------------------------------------- -%% @spec expand(Expansions, List::[term()]) -> [term()] -%% -%% Expansions = [{property(), [term()]}] -%% %% @doc Expands particular properties to corresponding sets of %% properties (or other terms). For each pair <code>{Property, %% Expansion}</code> in <code>Expansions</code>, if <code>E</code> is @@ -508,7 +497,9 @@ substitute_negations_1([], P) -> %% %% @see normalize/2 --spec expand(Expansions::expansions(), [term()]) -> [term()]. +-spec expand(Expansions, List) -> List when + Expansions :: [{Property :: property(), Expansion :: [term()]}], + List :: [term()]. expand(Es, Ps) when is_list(Ps) -> Es1 = [{property(P), V} || {P, V} <- Es], @@ -587,15 +578,6 @@ flatten([]) -> %% --------------------------------------------------------------------- -%% @spec normalize(List::[term()], Stages::[Operation]) -> [term()] -%% -%% Operation = {aliases, Aliases} | {negations, Negations} -%% | {expand, Expansions} -%% Aliases = [{Key, Key}] -%% Negations = [{Key, Key}] -%% Key = term() -%% Expansions = [{property(), [term()]}] -%% %% @doc Passes <code>List</code> through a sequence of %% substitution/expansion stages. For an <code>aliases</code> operation, %% the function <code>substitute_aliases/2</code> is applied using the @@ -617,11 +599,15 @@ flatten([]) -> %% @see expand/2 %% @see compact/1 --type operation() :: {'aliases', aliases()} - | {'negations', negations()} - | {'expand', expansions()}. - --spec normalize(List::[term()], Stages::[operation()]) -> [term()]. +-spec normalize(List, Stages) -> List when + List :: [term()], + Stages :: [Operation], + Operation :: {'aliases', Aliases} + | {'negations', Negations} + | {'expand', Expansions}, + Aliases :: [{Key, Key}], + Negations :: [{Key, Key}], + Expansions :: [{Property :: property(), Expansion :: [term()]}]. normalize(L, [{aliases, As} | Xs]) -> normalize(substitute_aliases(As, L), Xs); @@ -634,10 +620,6 @@ normalize(L, []) -> %% --------------------------------------------------------------------- -%% @spec split(List::[term()], Keys::[term()]) -> {Lists, Rest} -%% Lists = [[term()]] -%% Rest = [term()] -%% %% @doc Partitions <code>List</code> into a list of sublists and a %% remainder. <code>Lists</code> contains one sublist for each key in %% <code>Keys</code>, in the corresponding order. The relative order of @@ -652,7 +634,11 @@ normalize(L, []) -> %% {[[a], [{b, 5}, b],[{c, 2}, {c, 3, 4}]], [{e, 1}, d]}</pre> %% </p> --spec split(List::[term()], Keys::[term()]) -> {[[term()]], [term()]}. +-spec split(List, Keys) -> {Lists, Rest} when + List :: [term()], + Keys :: [term()], + Lists :: [[term()]], + Rest :: [term()]. split(List, Keys) -> {Store, Rest} = split(List, dict:from_list([{K, []} || K <- Keys]), []), diff --git a/lib/stdlib/src/qlc.erl b/lib/stdlib/src/qlc.erl index 6e48d95973..5ca04ff023 100644 --- a/lib/stdlib/src/qlc.erl +++ b/lib/stdlib/src/qlc.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2004-2010. All Rights Reserved. +%% Copyright Ericsson AB 2004-2011. 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 @@ -24,6 +24,8 @@ %% External exports +%% Avoid warning for local function error/1 clashing with autoimported BIF. +-compile({no_auto_import,[error/1]}). -export([parse_transform/2, transform_from_evaluator/2]). -export([q/1, q/2]). @@ -58,7 +60,7 @@ -record(qlc_table, % qlc:table/2 {trav_fun, % traverse fun - trav_MS, % bool(); true iff traverse fun takes a match spec + trav_MS, % boolean(); true iff traverse fun takes a match spec pre_fun, post_fun, info_fun, @@ -108,12 +110,12 @@ -record(qlc_cursor, {c}). -record(qlc_opt, - {unique = false, % bool() - cache = false, % bool() | list (true~ets, false~no) + {unique = false, % boolean() + cache = false, % boolean() | list (true~ets, false~no) max_lookup = -1, % int() >= 0 | -1 (represents infinity) join = any, % any | nested_loop | merge | lookup tmpdir = "", % global tmpdir - lookup = any, % any | bool() + lookup = any, % any | boolean() max_list = ?MAX_LIST_SIZE, % int() >= 0 tmpdir_usage = allowed % allowed | not_allowed % | warning_msg | error_msg | info_msg @@ -123,6 +125,8 @@ -define(THROWN_ERROR, {?MODULE, throw_error, _}). +-export_type([query_handle/0]). + %%% A query handle is a tuple {qlc_handle, Handle} where Handle is one %%% of #qlc_append, #qlc_table, #qlc_sort, and #qlc_lc. @@ -142,6 +146,35 @@ get_handle(_) -> %%% Exported functions %%% +-type(query_list_comprehension() :: term()). +-opaque(query_cursor() :: {qlc_cursor, term()}). +-opaque(query_handle() :: {qlc_handle, term()}). +-type(query_handle_or_list() :: query_handle() | list()). +-type(answers() :: [answer()]). +-type(answer() :: term()). +-type(abstract_expr() :: erl_parse:abstract_expr()). +-type(match_expression() :: ets:match_spec()). +-type(spawn_options() :: default | [proc_lib:spawn_option()]). +-type(sort_options() :: [sort_option()] | sort_option()). +-type(sort_option() :: {compressed, boolean()} + | {no_files, no_files()} + | {order, order()} + | {size, pos_integer()} + | {tmpdir, tmp_directory()} + | {unique, boolean()}). +-type(order() :: ascending | descending | order_fun()). +-type(order_fun() :: fun((term(), term()) -> boolean())). +-type(tmp_directory() :: [] | file:name()). +-type(no_files() :: pos_integer()). % > 1 +-type(key_pos() :: pos_integer() | [pos_integer()]). +-type(max_list_size() :: non_neg_integer()). +-type(cache() :: ets | list | no). +-type(tmp_file_usage() :: allowed | not_allowed | info_msg + | warning_msg | error_msg). + +-spec(append(QHL) -> QH when + QHL :: [query_handle_or_list()], + QH :: query_handle()). append(QHs) -> Hs = [case get_handle(QH) of badarg -> erlang:error(badarg, [QHs]); @@ -149,6 +182,10 @@ append(QHs) -> end || QH <- QHs], #qlc_handle{h = #qlc_append{hl = Hs}}. +-spec(append(QH1, QH2) -> QH3 when + QH1 :: query_handle_or_list(), + QH2 :: query_handle_or_list(), + QH3 :: query_handle()). append(QH1, QH2) -> Hs = [case get_handle(QH) of badarg -> erlang:error(badarg, [QH1, QH2]); @@ -156,9 +193,22 @@ append(QH1, QH2) -> end || QH <- [QH1, QH2]], #qlc_handle{h = #qlc_append{hl = Hs}}. +-spec(cursor(QH) -> Cursor when + QH :: query_handle_or_list(), + Cursor :: query_cursor()). cursor(QH) -> cursor(QH, []). +-spec(cursor(QH, Options) -> Cursor when + QH :: query_handle_or_list(), + Options :: [Option] | Option, + Option :: {cache_all, cache()} | cache_all + | {max_list_size, max_list_size()} + | {spawn_options, spawn_options()} + | {tmpdir_usage, tmp_file_usage()} + | {tmpdir, tmp_directory()} + | {unique_all, boolean()} | unique_all, + Cursor :: query_cursor()). cursor(QH, Options) -> case {options(Options, [unique_all, cache_all, tmpdir, spawn_options, max_list_size, @@ -177,6 +227,8 @@ cursor(QH, Options) -> end end. +-spec(delete_cursor(QueryCursor) -> ok when + QueryCursor :: query_cursor()). delete_cursor(#qlc_cursor{c = {_, Owner}}=C) when Owner =/= self() -> erlang:error(not_cursor_owner, [C]); delete_cursor(#qlc_cursor{c = {Pid, _}}) -> @@ -184,15 +236,47 @@ delete_cursor(#qlc_cursor{c = {Pid, _}}) -> delete_cursor(T) -> erlang:error(badarg, [T]). +-spec(e(QH) -> Answers | Error when + QH :: query_handle_or_list(), + Answers :: answers(), + Error :: {error, module(), Reason}, + Reason :: file_sorter:reason()). e(QH) -> eval(QH, []). +-spec(e(QH, Options) -> Answers | Error when + QH :: query_handle_or_list(), + Options :: [Option] | Option, + Option :: {cache_all, cache()} | cache_all + | {max_list_size, max_list_size()} + | {tmpdir_usage, tmp_file_usage()} + | {tmpdir, tmp_directory()} + | {unique_all, boolean()} | unique_all, + Answers :: answers(), + Error :: {error, module(), Reason}, + Reason :: file_sorter:reason()). e(QH, Options) -> eval(QH, Options). +-spec(eval(QH) -> Answers | Error when + QH :: query_handle_or_list(), + Answers :: answers(), + Error :: {error, module(), Reason}, + Reason :: file_sorter:reason()). eval(QH) -> eval(QH, []). +-spec(eval(QH, Options) -> Answers | Error when + QH :: query_handle_or_list(), + Answers :: answers(), + Options :: [Option] | Option, + Option :: {cache_all, cache()} | cache_all + | {max_list_size, max_list_size()} + | {tmpdir_usage, tmp_file_usage()} + | {tmpdir, tmp_directory()} + | {unique_all, boolean()} | unique_all, + Error :: {error, module(), Reason}, + Reason :: file_sorter:reason()). eval(QH, Options) -> case {options(Options, [unique_all, cache_all, tmpdir, max_list_size, tmpdir_usage]), @@ -224,9 +308,35 @@ eval(QH, Options) -> end end. +-spec(fold(Function, Acc0, QH) -> + Acc1 | Error when + QH :: query_handle_or_list(), + Function :: fun((answer(), AccIn) -> AccOut), + Acc0 :: term(), + Acc1 :: term(), + AccIn :: term(), + AccOut :: term(), + Error :: {error, module(), Reason}, + Reason :: file_sorter:reason()). fold(Fun, Acc0, QH) -> fold(Fun, Acc0, QH, []). +-spec(fold(Function, Acc0, QH, Options) -> + Acc1 | Error when + QH :: query_handle_or_list(), + Function :: fun((answer(), AccIn) -> AccOut), + Acc0 :: term(), + Acc1 :: term(), + AccIn :: term(), + AccOut :: term(), + Options :: [Option] | Option, + Option :: {cache_all, cache()} | cache_all + | {max_list_size, max_list_size()} + | {tmpdir_usage, tmp_file_usage()} + | {tmpdir, tmp_directory()} + | {unique_all, boolean()} | unique_all, + Error :: {error, module(), Reason}, + Reason :: file_sorter:reason()). fold(Fun, Acc0, QH, Options) -> case {options(Options, [unique_all, cache_all, tmpdir, max_list_size, tmpdir_usage]), @@ -256,6 +366,9 @@ fold(Fun, Acc0, QH, Options) -> end end. +-spec(format_error(Error) -> Chars when + Error :: {error, module(), term()}, + Chars :: io_lib:chars()). format_error(not_a_query_list_comprehension) -> io_lib:format("argument is not a query list comprehension", []); format_error({used_generator_variable, V}) -> @@ -293,9 +406,29 @@ format_error({error, Module, Reason}) -> format_error(E) -> io_lib:format("~p~n", [E]). +-spec(info(QH) -> Info when + QH :: query_handle_or_list(), + Info :: abstract_expr() | string()). info(QH) -> info(QH, []). +-spec(info(QH, Options) -> Info when + QH :: query_handle_or_list(), + Options :: [Option] | Option, + Option :: EvalOption | ReturnOption, + EvalOption :: {cache_all, cache()} | cache_all + | {max_list_size, max_list_size()} + | {tmpdir_usage, tmp_file_usage()} + | {tmpdir, tmp_directory()} + | {unique_all, boolean()} | unique_all, + ReturnOption :: {depth, Depth} + | {flat, boolean()} + | {format, Format} + | {n_elements, NElements}, + Depth :: infinity | non_neg_integer(), + Format :: abstract_code | string, + NElements :: infinity | pos_integer(), + Info :: abstract_expr() | string()). info(QH, Options) -> case {options(Options, [unique_all, cache_all, flat, format, n_elements, depth, tmpdir, max_list_size, tmpdir_usage]), @@ -331,9 +464,18 @@ info(QH, Options) -> end end. +-spec(keysort(KeyPos, QH1) -> QH2 when + KeyPos :: key_pos(), + QH1 :: query_handle_or_list(), + QH2 :: query_handle()). keysort(KeyPos, QH) -> keysort(KeyPos, QH, []). +-spec(keysort(KeyPos, QH1, SortOptions) -> QH2 when + KeyPos :: key_pos(), + SortOptions :: sort_options(), + QH1 :: query_handle_or_list(), + QH2 :: query_handle()). keysort(KeyPos, QH, Options) -> case {is_keypos(KeyPos), options(Options, [tmpdir, order, unique, compressed, @@ -352,9 +494,22 @@ keysort(KeyPos, QH, Options) -> -define(DEFAULT_NUM_OF_ANSWERS, 10). +-spec(next_answers(QueryCursor) -> + Answers | Error when + QueryCursor :: query_cursor(), + Answers :: answers(), + Error :: {error, module(), Reason}, + Reason :: file_sorter:reason()). next_answers(C) -> next_answers(C, ?DEFAULT_NUM_OF_ANSWERS). +-spec(next_answers(QueryCursor, NumberOfAnswers) -> + Answers | Error when + QueryCursor :: query_cursor(), + Answers :: answers(), + NumberOfAnswers :: all_remaining | pos_integer(), + Error :: {error, module(), Reason}, + Reason :: file_sorter:reason()). next_answers(#qlc_cursor{c = {_, Owner}}=C, NumOfAnswers) when Owner =/= self() -> erlang:error(not_cursor_owner, [C, NumOfAnswers]); @@ -368,14 +523,35 @@ next_answers(#qlc_cursor{c = {Pid, _}}=C, NumOfAnswers) -> next_answers(T1, T2) -> erlang:error(badarg, [T1, T2]). +-spec(parse_transform(Forms, Options) -> Forms2 when + Forms :: [erl_parse:abstract_form()], + Forms2 :: [erl_parse:abstract_form()], + Options :: [Option], + Option :: type_checker | compile:option()). + parse_transform(Forms, Options) -> qlc_pt:parse_transform(Forms, Options). %% The funcspecs qlc:q/1 and qlc:q/2 are known by erl_eval.erl and %% erl_lint.erl. +-spec(q(QLC) -> QH when + QLC :: query_list_comprehension(), + QH :: query_handle()). q(QLC_lc) -> q(QLC_lc, []). +-spec(q(QLC, Options) -> QH when + QH :: query_handle(), + Options :: [Option] | Option, + Option :: {max_lookup, MaxLookup} + | {cache, cache()} | cache + | {join, Join} + | {lookup, Lookup} + | {unique, boolean()} | unique, + MaxLookup :: non_neg_integer() | infinity, + Join :: any | lookup | merge | nested_loop, + Lookup :: boolean() | any, + QLC :: query_list_comprehension()). q(#qlc_lc{}=QLC_lc, Options) -> case options(Options, [unique, cache, max_lookup, join, lookup]) of [Unique, Cache, Max, Join, Lookup] -> @@ -388,9 +564,16 @@ q(#qlc_lc{}=QLC_lc, Options) -> q(T1, T2) -> erlang:error(badarg, [T1, T2]). +-spec(sort(QH1) -> QH2 when + QH1 :: query_handle_or_list(), + QH2 :: query_handle()). sort(QH) -> sort(QH, []). +-spec(sort(QH1, SortOptions) -> QH2 when + SortOptions :: sort_options(), + QH1 :: query_handle_or_list(), + QH2 :: query_handle()). sort(QH, Options) -> case {options(Options, [tmpdir, order, unique, compressed, size, no_files]), get_handle(QH)} of @@ -404,14 +587,47 @@ sort(QH, Options) -> end. %% Note that the generated code is evaluated by (the slow) erl_eval. +-spec(string_to_handle(QueryString) -> QH | Error when + QueryString :: string(), + QH :: query_handle(), + Error :: {error, module(), Reason}, + Reason :: erl_parse:error_info() | erl_scan:error_info()). string_to_handle(Str) -> string_to_handle(Str, []). +-spec(string_to_handle(QueryString, Options) -> QH | Error when + QueryString :: string(), + Options :: [Option] | Option, + Option :: {max_lookup, MaxLookup} + | {cache, cache()} | cache + | {join, Join} + | {lookup, Lookup} + | {unique, boolean()} | unique, + MaxLookup :: non_neg_integer() | infinity, + Join :: any | lookup | merge | nested_loop, + Lookup :: boolean() | any, + QH :: query_handle(), + Error :: {error, module(), Reason}, + Reason :: erl_parse:error_info() | erl_scan:error_info()). string_to_handle(Str, Options) -> - string_to_handle(Str, Options, []). - -string_to_handle(Str, Options, Bindings) when is_list(Str), - is_list(Bindings) -> + string_to_handle(Str, Options, erl_eval:new_bindings()). + +-spec(string_to_handle(QueryString, Options, Bindings) -> QH | Error when + QueryString :: string(), + Options :: [Option] | Option, + Option :: {max_lookup, MaxLookup} + | {cache, cache()} | cache + | {join, Join} + | {lookup, Lookup} + | {unique, boolean()} | unique, + MaxLookup :: non_neg_integer() | infinity, + Join :: any | lookup | merge | nested_loop, + Lookup :: boolean() | any, + Bindings :: erl_eval:binding_struct(), + QH :: query_handle(), + Error :: {error, module(), Reason}, + Reason :: erl_parse:error_info() | erl_scan:error_info()). +string_to_handle(Str, Options, Bindings) when is_list(Str) -> case options(Options, [unique, cache, max_lookup, join, lookup]) of badarg -> erlang:error(badarg, [Str, Options, Bindings]); @@ -445,6 +661,51 @@ string_to_handle(Str, Options, Bindings) when is_list(Str), string_to_handle(T1, T2, T3) -> erlang:error(badarg, [T1, T2, T3]). +-spec(table(TraverseFun, Options) -> QH when + TraverseFun :: TraverseFun0 | TraverseFun1, + TraverseFun0 :: fun(() -> TraverseResult), + TraverseFun1 :: fun((match_expression()) -> TraverseResult), + TraverseResult :: Objects | term(), + Objects :: [] | [term() | ObjectList], + ObjectList :: TraverseFun0 | Objects, + Options :: [Option] | Option, + Option :: {format_fun, FormatFun} + | {info_fun, InfoFun} + | {lookup_fun, LookupFun} + | {parent_fun, ParentFun} + | {post_fun, PostFun} + | {pre_fun, PreFun} + | {key_equality, KeyComparison}, + FormatFun :: undefined | fun((SelectedObjects) -> FormatedTable), + SelectedObjects :: all + | {all, NElements, DepthFun} + | {match_spec, match_expression()} + | {lookup, Position, Keys} + | {lookup, Position, Keys, NElements, DepthFun}, + NElements :: infinity | pos_integer(), + DepthFun :: fun((term()) -> term()), + FormatedTable :: {Mod, Fun, Args} + | abstract_expr() + | string(), + InfoFun :: undefined | fun((InfoTag) -> InfoValue), + InfoTag :: indices | is_unique_objects | keypos | num_of_objects, + InfoValue :: undefined | term(), + LookupFun :: undefined | fun((Position, Keys) -> LookupResult), + LookupResult :: [term()] | term(), + ParentFun :: undefined | fun(() -> ParentFunValue), + PostFun :: undefined | fun(() -> term()), + PreFun :: undefined | fun((PreArgs) -> term()), + PreArgs :: [PreArg], + PreArg :: {parent_value, ParentFunValue} | {stop_fun, StopFun}, + ParentFunValue :: undefined | term(), + StopFun :: undefined | fun(() -> term()), + KeyComparison :: '=:=' | '==', + Position :: pos_integer(), + Keys :: [term()], + Mod :: atom(), + Fun :: atom(), + Args :: [term()], + QH :: query_handle()). table(TraverseFun, Options) when is_function(TraverseFun) -> case {is_function(TraverseFun, 0), IsFun1 = is_function(TraverseFun, 1)} of @@ -470,6 +731,11 @@ table(TraverseFun, Options) when is_function(TraverseFun) -> table(T1, T2) -> erlang:error(badarg, [T1, T2]). +-spec(transform_from_evaluator(LC, Bs) -> Expr when + LC :: abstract_expr(), + Expr :: abstract_expr(), + Bs :: erl_eval:binding_struct()). + transform_from_evaluator(LC, Bs0) -> qlc_pt:transform_from_evaluator(LC, Bs0). @@ -720,8 +986,8 @@ listify(T) -> %% Optimizations to be carried out. -record(optz, - {unique = false, % bool() - cache = false, % bool() | list + {unique = false, % boolean() + cache = false, % boolean() | list join_option = any, % constraint set by the 'join' option fast_join = no, % no | #qlc_join. 'no' means nested loop. opt % #qlc_opt @@ -754,8 +1020,8 @@ listify(T) -> lu_skip_quals = [], % qualifiers to skip due to lookup join = {[],[]}, % {Lookup, Merge} n_objs = undefined, % for join (not used yet) - is_unique_objects = false, % bool() - is_cached = false % bool() (true means 'ets' or 'list') + is_unique_objects = false, % boolean() + is_cached = false % boolean() (true means 'ets' or 'list') }). %%% Cursor process functions. @@ -1141,20 +1407,20 @@ monitor_request(Pid, Req) -> %% QueryDesc = {qlc, TemplateDesc, [QualDesc], [QueryOpt]} %% | {table, TableDesc} %% | {append, [QueryDesc]} -%% | {sort, QueryDesc, [SortOption]} -%% | {keysort, KeyPos, QueryDesc, [SortOption]} +%% | {sort, QueryDesc, [sort_option()]} +%% | {keysort, key_pos(), QueryDesc, [sort_option()]} %% | {list, list()} -%% | {list, QueryDesc, MatchExpression} +%% | {list, QueryDesc, match_expression()} %% TableDesc = {Mod, Fun, Args} -%% | AbstractExpression -%% | character_list() +%% | erl_parse:abstract_expr() +%% | string() %% Mod = module() %% Fun = atom() %% Args = [term()] %% QualDesc = FilterDesc %% | {generate, PatternDesc, QueryDesc} -%% QueryOpt = {cache, bool()} | cache -%% | {unique, bool()} | unique +%% QueryOpt = {cache, boolean()} | cache +%% | {unique, boolean()} | unique %% FilterDesc = PatternDesc = TemplateDesc = binary() le_info(#prepared{qh = #simple_qlc{le = LE, p = P, line = L, optz = Optz}}, diff --git a/lib/stdlib/src/qlc_pt.erl b/lib/stdlib/src/qlc_pt.erl index 24378a0698..21504d707b 100644 --- a/lib/stdlib/src/qlc_pt.erl +++ b/lib/stdlib/src/qlc_pt.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2004-2010. All Rights Reserved. +%% Copyright Ericsson AB 2004-2011. 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 @@ -63,6 +63,12 @@ %%% Exported functions %%% +-spec(parse_transform(Forms, Options) -> Forms2 when + Forms :: [erl_parse:abstract_form()], + Forms2 :: [erl_parse:abstract_form()], + Options :: [Option], + Option :: type_checker | compile:option()). + parse_transform(Forms, Options) -> ?DEBUG("qlc Parse Transform~n", []), State = #state{imp = is_qlc_q_imported(Forms), @@ -96,10 +102,20 @@ parse_transform(Forms, Options) -> end end. +-spec(transform_from_evaluator(LC, Bs) -> Expr when + LC :: erl_parse:abstract_expr(), + Expr :: erl_parse:abstract_expr(), + Bs :: erl_eval:binding_struct()). + transform_from_evaluator(LC, Bindings) -> ?DEBUG("qlc Parse Transform (Evaluator Version)~n", []), transform_expression(LC, Bindings, false). +-spec(transform_expression(LC, Bs) -> Expr when + LC :: erl_parse:abstract_expr(), + Expr :: erl_parse:abstract_expr(), + Bs :: erl_eval:binding_struct()). + transform_expression(LC, Bindings) -> transform_expression(LC, Bindings, true). diff --git a/lib/stdlib/src/queue.erl b/lib/stdlib/src/queue.erl index c09079e8d2..afe917b151 100644 --- a/lib/stdlib/src/queue.erl +++ b/lib/stdlib/src/queue.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. +%% Copyright Ericsson AB 1996-2011. 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 @@ -56,14 +56,14 @@ new() -> {[],[]}. %{RearList,FrontList} %% O(1) --spec is_queue(term()) -> boolean(). +-spec is_queue(Term :: term()) -> boolean(). is_queue({R,F}) when is_list(R), is_list(F) -> true; is_queue(_) -> false. %% O(1) --spec is_empty(queue()) -> boolean(). +-spec is_empty(Q :: queue()) -> boolean(). is_empty({[],[]}) -> true; is_empty({In,Out}) when is_list(In), is_list(Out) -> @@ -72,14 +72,14 @@ is_empty(Q) -> erlang:error(badarg, [Q]). %% O(len(Q)) --spec len(queue()) -> non_neg_integer(). +-spec len(Q :: queue()) -> non_neg_integer(). len({R,F}) when is_list(R), is_list(F) -> length(R)+length(F); len(Q) -> erlang:error(badarg, [Q]). %% O(len(Q)) --spec to_list(queue()) -> list(). +-spec to_list(Q :: queue()) -> list(). to_list({In,Out}) when is_list(In), is_list(Out) -> Out++lists:reverse(In, []); to_list(Q) -> @@ -88,7 +88,7 @@ to_list(Q) -> %% Create queue from list %% %% O(length(L)) --spec from_list(list()) -> queue(). +-spec from_list(L :: list()) -> queue(). from_list(L) when is_list(L) -> f2r(L); from_list(L) -> @@ -97,7 +97,7 @@ from_list(L) -> %% Return true or false depending on if element is in queue %% %% O(length(Q)) worst case --spec member(term(), queue()) -> boolean(). +-spec member(Item :: term(), Q :: queue()) -> boolean(). member(X, {R,F}) when is_list(R), is_list(F) -> lists:member(X, R) orelse lists:member(X, F); member(X, Q) -> @@ -110,7 +110,7 @@ member(X, Q) -> %% Put at least one element in each list, if it is cheap %% %% O(1) --spec in(term(), queue()) -> queue(). +-spec in(Item :: term(), Q1 :: queue()) -> Q2 :: queue(). in(X, {[_]=In,[]}) -> {[X], In}; in(X, {In,Out}) when is_list(In), is_list(Out) -> @@ -122,7 +122,7 @@ in(X, Q) -> %% Put at least one element in each list, if it is cheap %% %% O(1) --spec in_r(term(), queue()) -> queue(). +-spec in_r(Item :: term(), Q1 :: queue()) -> Q2 :: queue(). in_r(X, {[],[_]=F}) -> {F,[X]}; in_r(X, {R,F}) when is_list(R), is_list(F) -> @@ -133,7 +133,9 @@ in_r(X, Q) -> %% Take from head/front %% %% O(1) amortized, O(len(Q)) worst case --spec out(queue()) -> {'empty' | {'value',term()}, queue()}. +-spec out(Q1 :: queue()) -> + {{value, Item :: term()}, Q2 :: queue()} | + {empty, Q1 :: queue()}. out({[],[]}=Q) -> {empty,Q}; out({[V],[]}) -> @@ -151,7 +153,9 @@ out(Q) -> %% Take from tail/rear %% %% O(1) amortized, O(len(Q)) worst case --spec out_r(queue()) -> {'empty' | {'value',term()}, queue()}. +-spec out_r(Q1 :: queue()) -> + {{value, Item :: term()}, Q2 :: queue()} | + {empty, Q1 :: queue()}. out_r({[],[]}=Q) -> {empty,Q}; out_r({[],[V]}) -> @@ -172,7 +176,7 @@ out_r(Q) -> %% Return the first element in the queue %% %% O(1) since the queue is supposed to be well formed --spec get(queue()) -> term(). +-spec get(Q :: queue()) -> Item :: term(). get({[],[]}=Q) -> erlang:error(empty, [Q]); get({R,F}) when is_list(R), is_list(F) -> @@ -191,7 +195,7 @@ get([_|R], []) -> % malformed queue -> O(len(Q)) %% Return the last element in the queue %% %% O(1) since the queue is supposed to be well formed --spec get_r(queue()) -> term(). +-spec get_r(Q :: queue()) -> Item :: term(). get_r({[],[]}=Q) -> erlang:error(empty, [Q]); get_r({[H|_],F}) when is_list(F) -> @@ -206,7 +210,7 @@ get_r(Q) -> %% Return the first element in the queue %% %% O(1) since the queue is supposed to be well formed --spec peek(queue()) -> 'empty' | {'value',term()}. +-spec peek(Q :: queue()) -> empty | {value,Item :: term()}. peek({[],[]}) -> empty; peek({R,[H|_]}) when is_list(R) -> @@ -221,7 +225,7 @@ peek(Q) -> %% Return the last element in the queue %% %% O(1) since the queue is supposed to be well formed --spec peek_r(queue()) -> 'empty' | {'value',term()}. +-spec peek_r(Q :: queue()) -> empty | {value,Item :: term()}. peek_r({[],[]}) -> empty; peek_r({[H|_],F}) when is_list(F) -> @@ -236,7 +240,7 @@ peek_r(Q) -> %% Remove the first element and return resulting queue %% %% O(1) amortized --spec drop(queue()) -> queue(). +-spec drop(Q1 :: queue()) -> Q2 :: queue(). drop({[],[]}=Q) -> erlang:error(empty, [Q]); drop({[_],[]}) -> @@ -254,7 +258,7 @@ drop(Q) -> %% Remove the last element and return resulting queue %% %% O(1) amortized --spec drop_r(queue()) -> queue(). +-spec drop_r(Q1 :: queue()) -> Q2 :: queue(). drop_r({[],[]}=Q) -> erlang:error(empty, [Q]); drop_r({[],[_]}) -> @@ -275,7 +279,7 @@ drop_r(Q) -> %% Return reversed queue %% %% O(1) --spec reverse(queue()) -> queue(). +-spec reverse(Q1 :: queue()) -> Q2 :: queue(). reverse({R,F}) when is_list(R), is_list(F) -> {F,R}; reverse(Q) -> @@ -285,7 +289,7 @@ reverse(Q) -> %% %% Q2 empty: O(1) %% else: O(len(Q1)) --spec join(queue(), queue()) -> queue(). +-spec join(Q1 :: queue(), Q2 :: queue()) -> Q3 :: queue(). join({R,F}=Q, {[],[]}) when is_list(R), is_list(F) -> Q; join({[],[]}, {R,F}=Q) when is_list(R), is_list(F) -> @@ -299,7 +303,8 @@ join(Q1, Q2) -> %% %% N = 0..len(Q) %% O(max(N, len(Q))) --spec split(non_neg_integer(), queue()) -> {queue(),queue()}. +-spec split(N :: non_neg_integer(), Q1 :: queue()) -> + {Q2 :: queue(),Q3 :: queue()}. split(0, {R,F}=Q) when is_list(R), is_list(F) -> {{[],[]},Q}; split(N, {R,F}=Q) when is_integer(N), N >= 1, is_list(R), is_list(F) -> @@ -340,7 +345,8 @@ split_r1_to_f2(N, [X|R1], F1, R2, F2) -> %% %% Fun(_) -> List: O(length(List) * len(Q)) %% else: O(len(Q) --spec filter(fun((term()) -> boolean() | list()), queue()) -> queue(). +-spec filter(Fun, Q1 :: queue()) -> Q2 :: queue() when + Fun :: fun((Item :: term()) -> boolean() | list()). filter(Fun, {R0,F0}) when is_function(Fun, 1), is_list(R0), is_list(F0) -> F = filter_f(Fun, F0), R = filter_r(Fun, R0), @@ -416,7 +422,7 @@ filter_r(Fun, [X|R0]) -> %% Cons to head %% --spec cons(term(), queue()) -> queue(). +-spec cons(Item :: term(), Q1 :: queue()) -> Q2 :: queue(). cons(X, Q) -> in_r(X, Q). @@ -425,7 +431,7 @@ cons(X, Q) -> %% Return the first element in the queue %% %% O(1) since the queue is supposed to be well formed --spec head(queue()) -> term(). +-spec head(Q :: queue()) -> Item :: term(). head({[],[]}=Q) -> erlang:error(empty, [Q]); head({R,F}) when is_list(R), is_list(F) -> @@ -435,7 +441,7 @@ head(Q) -> %% Remove head element and return resulting queue %% --spec tail(queue()) -> queue(). +-spec tail(Q1 :: queue()) -> Q2 :: queue(). tail(Q) -> drop(Q). @@ -443,22 +449,22 @@ tail(Q) -> %% Cons to tail %% --spec snoc(queue(), term()) -> queue(). +-spec snoc(Q1 :: queue(), Item :: term()) -> Q2 :: queue(). snoc(Q, X) -> in(X, Q). %% Return last element --spec daeh(queue()) -> term(). +-spec daeh(Q :: queue()) -> Item :: term(). daeh(Q) -> get_r(Q). --spec last(queue()) -> term(). +-spec last(Q :: queue()) -> Item :: term(). last(Q) -> get_r(Q). %% Remove last element and return resulting queue --spec liat(queue()) -> queue(). +-spec liat(Q1 :: queue()) -> Q2 :: queue(). liat(Q) -> drop_r(Q). --spec lait(queue()) -> queue(). +-spec lait(Q1 :: queue()) -> Q2 :: queue(). lait(Q) -> drop_r(Q). %% Oops, mis-spelled 'tail' reversed. Forget this one. --spec init(queue()) -> queue(). +-spec init(Q1 :: queue()) -> Q2 :: queue(). init(Q) -> drop_r(Q). %%-------------------------------------------------------------------------- diff --git a/lib/stdlib/src/random.erl b/lib/stdlib/src/random.erl index 01227c29b4..dbb524cc74 100644 --- a/lib/stdlib/src/random.erl +++ b/lib/stdlib/src/random.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. +%% Copyright Ericsson AB 1996-2011. 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 @@ -49,7 +49,10 @@ seed() -> %% seed({A1, A2, A3}) %% Seed random number generation --spec seed({integer(), integer(), integer()}) -> 'undefined' | ran(). +-spec seed({A1, A2, A3}) -> 'undefined' | ran() when + A1 :: integer(), + A2 :: integer(), + A3 :: integer(). seed({A1, A2, A3}) -> seed(A1, A2, A3). @@ -57,7 +60,10 @@ seed({A1, A2, A3}) -> %% seed(A1, A2, A3) %% Seed random number generation --spec seed(integer(), integer(), integer()) -> 'undefined' | ran(). +-spec seed(A1, A2, A3) -> 'undefined' | ran() when + A1 :: integer(), + A2 :: integer(), + A3 :: integer(). seed(A1, A2, A3) -> put(random_seed, @@ -93,7 +99,8 @@ uniform() -> %% Given an integer N >= 1, uniform(N) returns a random integer %% between 1 and N. --spec uniform(pos_integer()) -> pos_integer(). +-spec uniform(N) -> pos_integer() when + N :: pos_integer(). uniform(N) when is_integer(N), N >= 1 -> trunc(uniform() * N) + 1. @@ -104,7 +111,9 @@ uniform(N) when is_integer(N), N >= 1 -> %% uniform_s(State) -> {F, NewState} %% Returns a random float between 0 and 1. --spec uniform_s(ran()) -> {float(), ran()}. +-spec uniform_s(State0) -> {float(), State1} when + State0 :: ran(), + State1 :: ran(). uniform_s({A1, A2, A3}) -> B1 = (A1*171) rem 30269, @@ -117,7 +126,10 @@ uniform_s({A1, A2, A3}) -> %% Given an integer N >= 1, uniform(N) returns a random integer %% between 1 and N. --spec uniform_s(pos_integer(), ran()) -> {integer(), ran()}. +-spec uniform_s(N, State0) -> {integer(), State1} when + N :: pos_integer(), + State0 :: ran(), + State1 :: ran(). uniform_s(N, State0) when is_integer(N), N >= 1 -> {F, State1} = uniform_s(State0), diff --git a/lib/stdlib/src/re.erl b/lib/stdlib/src/re.erl index 296a6b3d23..e08258a535 100644 --- a/lib/stdlib/src/re.erl +++ b/lib/stdlib/src/re.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2008-2010. All Rights Reserved. +%% Copyright Ericsson AB 2008-2011. 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 @@ -19,15 +19,46 @@ -module(re). -export([grun/3,urun/3,ucompile/2,replace/3,replace/4,split/2,split/3]). +%-opaque mp() :: {re_pattern, _, _, _}. +-type mp() :: {re_pattern, _, _, _}. + +-type nl_spec() :: cr | crlf | lf | anycrlf | any. + +-type compile_option() :: unicode | anchored | caseless | dollar_endonly + | dotall | extended | firstline | multiline + | no_auto_capture | dupnames | ungreedy + | {newline, nl_spec()}| bsr_anycrlf + | bsr_unicode. + %% Emulator builtins in this module: %% re:compile/1 %% re:compile/2 %% re:run/2 %% re:run/3 +-spec split(Subject, RE) -> SplitList when + Subject :: iodata() | unicode:charlist(), + RE :: mp() | iodata(), + SplitList :: [iodata() | unicode:charlist()]. + split(Subject,RE) -> split(Subject,RE,[]). +-spec split(Subject, RE, Options) -> SplitList when + Subject :: iodata() | unicode:charlist(), + RE :: mp() | iodata() | unicode:charlist(), + Options :: [ Option ], + Option :: anchored | global | notbol | noteol | notempty + | {offset, non_neg_integer()} | {newline, nl_spec()} + | bsr_anycrlf | bsr_unicode | {return, ReturnType} + | {parts, NumParts} | group | trim | CompileOpt, + NumParts :: non_neg_integer() | infinity, + ReturnType :: iodata | list | binary, + CompileOpt :: compile_option(), + SplitList :: [RetData] | [GroupedRetData], + GroupedRetData :: [RetData], + RetData :: iodata() | unicode:charlist() | binary() | list(). + split(Subject,RE,Options) -> try {NewOpt,Convert,Unicode,Limit,Strip,Group} = @@ -37,16 +68,16 @@ split(Subject,RE,Options) -> {error,_Err} -> throw(badre); {PreCompiled, NumSub, RunOpt} -> - % OK, lets run + %% OK, lets run case re:run(FlatSubject,PreCompiled,RunOpt ++ [global]) of nomatch -> case Group of true -> convert_any_split_result([[FlatSubject]], - Convert, Unicode,true); + Convert, Unicode, true); false -> convert_any_split_result([FlatSubject], - Convert, Unicode,false) + Convert, Unicode, false) end; {match, Matches} -> Res = do_split(FlatSubject, 0, Matches, NumSub, @@ -69,7 +100,7 @@ split(Subject,RE,Options) -> erlang:error(badarg,[Subject,RE,Options]) end. -backstrip_empty(List,false) -> +backstrip_empty(List, false) -> do_backstrip_empty(List); backstrip_empty(List, true) -> do_backstrip_empty_g(List). @@ -196,41 +227,52 @@ compile_split(Pat,Options0) when not is_tuple(Pat) -> end; compile_split(_,_) -> throw(badre). - - +-spec replace(Subject, RE, Replacement) -> iodata() | unicode:charlist() when + Subject :: iodata() | unicode:charlist(), + RE :: mp() | iodata(), + Replacement :: iodata() | unicode:charlist(). replace(Subject,RE,Replacement) -> replace(Subject,RE,Replacement,[]). + +-spec replace(Subject, RE, Replacement, Options) -> iodata() | unicode:charlist() when + Subject :: iodata() | unicode:charlist(), + RE :: mp() | iodata() | unicode:charlist(), + Replacement :: iodata() | unicode:charlist(), + Options :: [Option], + Option :: anchored | global | notbol | noteol | notempty + | {offset, non_neg_integer()} | {newline, NLSpec} | bsr_anycrlf + | bsr_unicode | {return, ReturnType} | CompileOpt, + ReturnType :: iodata | list | binary, + CompileOpt :: compile_option(), + NLSpec :: cr | crlf | lf | anycrlf | any. + replace(Subject,RE,Replacement,Options) -> try {NewOpt,Convert,Unicode} = process_repl_params(Options,iodata,false), FlatSubject = to_binary(Subject, Unicode), FlatReplacement = to_binary(Replacement, Unicode), - case do_replace(FlatSubject,Subject,RE,FlatReplacement,NewOpt) of - {error,_Err} -> - throw(badre); - IoList -> - case Convert of - iodata -> - IoList; - binary -> - case Unicode of - false -> - iolist_to_binary(IoList); - true -> - unicode:characters_to_binary(IoList,unicode) - end; - list -> - case Unicode of - false -> - binary_to_list(iolist_to_binary(IoList)); - true -> - unicode:characters_to_list(IoList,unicode) - end - end - end + IoList = do_replace(FlatSubject,Subject,RE,FlatReplacement,NewOpt), + case Convert of + iodata -> + IoList; + binary -> + case Unicode of + false -> + iolist_to_binary(IoList); + true -> + unicode:characters_to_binary(IoList,unicode) + end; + list -> + case Unicode of + false -> + binary_to_list(iolist_to_binary(IoList)); + true -> + unicode:characters_to_list(IoList,unicode) + end + end catch throw:badopt -> erlang:error(badarg,[Subject,RE,Replacement,Options]); @@ -239,7 +281,7 @@ replace(Subject,RE,Replacement,Options) -> error:badarg -> erlang:error(badarg,[Subject,RE,Replacement,Options]) end. - + do_replace(FlatSubject,Subject,RE,Replacement,Options) -> case re:run(FlatSubject,RE,Options) of @@ -314,7 +356,7 @@ apply_mlist(Subject,Replacement,Mlist) -> precomp_repl(<<>>) -> []; precomp_repl(<<$\\,X,Rest/binary>>) when X < $1 ; X > $9 -> - % Escaped character + %% Escaped character case precomp_repl(Rest) of [BHead | T0] when is_binary(BHead) -> [<<X,BHead/binary>> | T0]; @@ -524,7 +566,7 @@ process_uparams([H|T],Type) -> {[H|NL],NType}; process_uparams([],Type) -> {[],Type}. - + ucompile(RE,Options) -> try @@ -548,6 +590,7 @@ urun(Subject,RE,Options) -> [Subject,RE,Options])), erlang:raise(error,AnyError,[{Mod,run,L}|Rest]) end. + urun2(Subject0,RE0,Options0) -> {Options,RetType} = case (catch process_uparams(Options0,index)) of {A,B} -> @@ -573,7 +616,6 @@ urun2(Subject0,RE0,Options0) -> _ -> Ret end. - %% Might be called either with two-tuple (if regexp was already compiled) diff --git a/lib/stdlib/src/regexp.erl b/lib/stdlib/src/regexp.erl index 8f5994bbee..65f9ca247d 100644 --- a/lib/stdlib/src/regexp.erl +++ b/lib/stdlib/src/regexp.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. +%% Copyright Ericsson AB 1996-2011. 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 @@ -37,6 +37,9 @@ -import(string, [substr/2,substr/3]). -import(lists, [reverse/1]). +-type errordesc() :: term(). +-opaque regexp() :: term(). + %% -type matchres() = {match,Start,Length} | nomatch | {error,E}. %% -type subres() = {ok,RepString,RepCount} | {error,E}. %% -type splitres() = {ok,[SubString]} | {error,E}. @@ -287,6 +290,10 @@ re_apply_or(R1, nomatch) -> R1. %% Convert a sh style regexp into a full AWK one. The main difficulty is %% getting character sets right as the conventions are different. +-spec sh_to_awk(ShRegExp) -> AwkRegExp when + ShRegExp :: string(), + AwkRegExp :: string(). + sh_to_awk(Sh) -> "^(" ++ sh_to_awk_1(Sh). %Fix the beginning sh_to_awk_1([$*|Sh]) -> %This matches any string @@ -336,6 +343,12 @@ special_char(_C) -> false. %% parse(RegExp) -> {ok,RE} | {error,E}. %% Parse the regexp described in the string RegExp. +-spec parse(RegExp) -> ParseRes when + RegExp :: string(), + ParseRes :: {ok, RE} | {error, Error}, + RE :: regexp(), + Error :: errordesc(). + parse(S) -> case catch reg(S) of {R,[]} -> {ok,R}; @@ -345,6 +358,10 @@ parse(S) -> %% format_error(Error) -> String. +-spec format_error(ErrorDescriptor) -> Chars when + ErrorDescriptor :: errordesc(), + Chars :: io_lib:chars(). + format_error({illegal,What}) -> ["illegal character `",What,"'"]; format_error({unterminated,What}) -> ["unterminated `",What,"'"]; format_error({char_class,What}) -> @@ -353,6 +370,14 @@ format_error({char_class,What}) -> %% -type match(String, RegExp) -> matchres(). %% Find the longest match of RegExp in String. +-spec match(String, RegExp) -> MatchRes when + String :: string(), + RegExp :: string() | regexp(), + MatchRes :: {match, Start, Length} | nomatch | {error, Error}, + Start :: pos_integer(), + Length :: pos_integer(), + Error :: errordesc(). + match(S, RegExp) when is_list(RegExp) -> case parse(RegExp) of {ok,RE} -> match(S, RE); @@ -378,6 +403,14 @@ match(RE, S, St, Pos, L) -> %% -type first_match(String, RegExp) -> matchres(). %% Find the first match of RegExp in String. +-spec first_match(String, RegExp) -> MatchRes when + String :: string(), + RegExp :: string() | regexp(), + MatchRes :: {match, Start, Length} | nomatch | {error, Error}, + Start :: pos_integer(), + Length :: pos_integer(), + Error :: errordesc(). + first_match(S, RegExp) when is_list(RegExp) -> case parse(RegExp) of {ok,RE} -> first_match(S, RE); @@ -400,6 +433,15 @@ first_match(_RE, [], _St) -> nomatch. %% -type matches(String, RegExp) -> {match,[{Start,Length}]} | {error,E}. %% Return the all the non-overlapping matches of RegExp in String. +-spec matches(String, RegExp) -> MatchRes when + String :: string(), + RegExp :: string() | regexp(), + MatchRes :: {match, Matches} | {error, Error}, + Matches :: [{Start, Length}], + Start :: pos_integer(), + Length :: pos_integer(), + Error :: errordesc(). + matches(S, RegExp) when is_list(RegExp) -> case parse(RegExp) of {ok,RE} -> matches(S, RE); @@ -420,6 +462,15 @@ matches(S, RE, St) -> %% the string Replace in String. Accept pre-parsed regular %% expressions. +-spec sub(String, RegExp, New) -> SubRes when + String :: string(), + RegExp :: string() | regexp(), + New :: string(), + NewString :: string(), + SubRes :: {ok, NewString, RepCount} | {error, Error}, + RepCount :: 0 | 1, + Error :: errordesc(). + sub(String, RegExp, Rep) when is_list(RegExp) -> case parse(RegExp) of {ok,RE} -> sub(String, RE, Rep); @@ -449,6 +500,15 @@ sub_repl([], _M, Rest) -> Rest. %% Substitute every match of the regular expression RegExp with the %% string New in String. Accept pre-parsed regular expressions. +-spec gsub(String, RegExp, New) -> SubRes when + String :: string(), + RegExp :: string() | regexp(), + New :: string(), + NewString :: string(), + SubRes :: {ok, NewString, RepCount} | {error, Error}, + RepCount :: non_neg_integer(), + Error :: errordesc(). + gsub(String, RegExp, Rep) when is_list(RegExp) -> case parse(RegExp) of {ok,RE} -> gsub(String, RE, Rep); @@ -462,6 +522,13 @@ gsub(String, RE, Rep) -> %% Split a string into substrings where the RegExp describes the %% field seperator. The RegExp " " is specially treated. +-spec split(String, RegExp) -> SplitRes when + String :: string(), + RegExp :: string() | regexp(), + SplitRes :: {ok, FieldList} | {error, Error}, + FieldList :: [string()], + Error :: errordesc(). + split(String, " ") -> %This is really special {ok,RE} = parse("[ \t]+"), case split_apply(String, RE, true) of diff --git a/lib/stdlib/src/sets.erl b/lib/stdlib/src/sets.erl index bcddca2567..3fd6c81e5f 100644 --- a/lib/stdlib/src/sets.erl +++ b/lib/stdlib/src/sets.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2000-2009. All Rights Reserved. +%% Copyright Ericsson AB 2000-2011. 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 @@ -84,30 +84,38 @@ new() -> %% is_set(Set) -> boolean(). %% Return 'true' if Set is a set of elements, else 'false'. --spec is_set(term()) -> boolean(). +-spec is_set(Set) -> boolean() when + Set :: term(). is_set(#set{}) -> true; is_set(_) -> false. %% size(Set) -> int(). %% Return the number of elements in Set. --spec size(set()) -> non_neg_integer(). +-spec size(Set) -> non_neg_integer() when + Set :: set(). size(S) -> S#set.size. %% to_list(Set) -> [Elem]. %% Return the elements in Set as a list. --spec to_list(set()) -> [term()]. +-spec to_list(Set) -> List when + Set :: set(), + List :: [term()]. to_list(S) -> fold(fun (Elem, List) -> [Elem|List] end, [], S). %% from_list([Elem]) -> Set. %% Build a set from the elements in List. --spec from_list([term()]) -> set(). +-spec from_list(List) -> Set when + List :: [term()], + Set :: set(). from_list(L) -> lists:foldl(fun (E, S) -> add_element(E, S) end, new(), L). %% is_element(Element, Set) -> boolean(). %% Return 'true' if Element is an element of Set, else 'false'. --spec is_element(term(), set()) -> boolean(). +-spec is_element(Element, Set) -> boolean() when + Element :: term(), + Set :: set(). is_element(E, S) -> Slot = get_slot(S, E), Bkt = get_bucket(S, Slot), @@ -115,7 +123,10 @@ is_element(E, S) -> %% add_element(Element, Set) -> Set. %% Return Set with Element inserted in it. --spec add_element(term(), set()) -> set(). +-spec add_element(Element, Set1) -> Set2 when + Element :: term(), + Set1 :: set(), + Set2 :: set(). add_element(E, S0) -> Slot = get_slot(S0, E), {S1,Ic} = on_bucket(fun (B0) -> add_bkt_el(E, B0, B0) end, S0, Slot), @@ -129,7 +140,10 @@ add_bkt_el(E, [], Bkt) -> {[E|Bkt],1}. %% del_element(Element, Set) -> Set. %% Return Set but with Element removed. --spec del_element(term(), set()) -> set(). +-spec del_element(Element, Set1) -> Set2 when + Element :: term(), + Set1 :: set(), + Set2 :: set(). del_element(E, S0) -> Slot = get_slot(S0, E), {S1,Dc} = on_bucket(fun (B0) -> del_bkt_el(E, B0) end, S0, Slot), @@ -144,7 +158,10 @@ del_bkt_el(_, []) -> {[],0}. %% union(Set1, Set2) -> Set %% Return the union of Set1 and Set2. --spec union(set(), set()) -> set(). +-spec union(Set1, Set2) -> Set3 when + Set1 :: set(), + Set2 :: set(), + Set3 :: set(). union(S1, S2) when S1#set.size < S2#set.size -> fold(fun (E, S) -> add_element(E, S) end, S2, S1); union(S1, S2) -> @@ -152,7 +169,9 @@ union(S1, S2) -> %% union([Set]) -> Set %% Return the union of the list of sets. --spec union([set()]) -> set(). +-spec union(SetList) -> Set when + SetList :: [set()], + Set :: set(). union([S1,S2|Ss]) -> union1(union(S1, S2), Ss); union([S]) -> S; @@ -165,7 +184,10 @@ union1(S1, []) -> S1. %% intersection(Set1, Set2) -> Set. %% Return the intersection of Set1 and Set2. --spec intersection(set(), set()) -> set(). +-spec intersection(Set1, Set2) -> Set3 when + Set1 :: set(), + Set2 :: set(), + Set3 :: set(). intersection(S1, S2) when S1#set.size < S2#set.size -> filter(fun (E) -> is_element(E, S2) end, S1); intersection(S1, S2) -> @@ -173,7 +195,9 @@ intersection(S1, S2) -> %% intersection([Set]) -> Set. %% Return the intersection of the list of sets. --spec intersection([set(),...]) -> set(). +-spec intersection(SetList) -> Set when + SetList :: [set(),...], + Set :: set(). intersection([S1,S2|Ss]) -> intersection1(intersection(S1, S2), Ss); intersection([S]) -> S. @@ -185,7 +209,9 @@ intersection1(S1, []) -> S1. %% is_disjoint(Set1, Set2) -> boolean(). %% Check whether Set1 and Set2 are disjoint. --spec is_disjoint(set(), set()) -> boolean(). +-spec is_disjoint(Set1, Set2) -> boolean() when + Set1 :: set(), + Set2 :: set(). is_disjoint(S1, S2) when S1#set.size < S2#set.size -> fold(fun (_, false) -> false; (E, true) -> not is_element(E, S2) @@ -198,25 +224,39 @@ is_disjoint(S1, S2) -> %% subtract(Set1, Set2) -> Set. %% Return all and only the elements of Set1 which are not also in %% Set2. --spec subtract(set(), set()) -> set(). +-spec subtract(Set1, Set2) -> Set3 when + Set1 :: set(), + Set2 :: set(), + Set3 :: set(). subtract(S1, S2) -> filter(fun (E) -> not is_element(E, S2) end, S1). %% is_subset(Set1, Set2) -> boolean(). %% Return 'true' when every element of Set1 is also a member of %% Set2, else 'false'. --spec is_subset(set(), set()) -> boolean(). +-spec is_subset(Set1, Set2) -> boolean() when + Set1 :: set(), + Set2 :: set(). is_subset(S1, S2) -> fold(fun (E, Sub) -> Sub andalso is_element(E, S2) end, true, S1). %% fold(Fun, Accumulator, Set) -> Accumulator. %% Fold function Fun over all elements in Set and return Accumulator. --spec fold(fun((_,_) -> _), T, set()) -> T. +-spec fold(Function, Acc0, Set) -> Acc1 when + Function :: fun((E :: term(),AccIn) -> AccOut), + Set :: set(), + Acc0 :: T, + Acc1 :: T, + AccIn :: T, + AccOut :: T. fold(F, Acc, D) -> fold_set(F, Acc, D). %% filter(Fun, Set) -> Set. %% Filter Set with Fun. --spec filter(fun((_) -> boolean()), set()) -> set(). +-spec filter(Pred, Set1) -> Set2 when + Pred :: fun((E :: term()) -> boolean()), + Set1 :: set(), + Set2 :: set(). filter(F, D) -> filter_set(F, D). %% get_slot(Hashdb, Key) -> Slot. diff --git a/lib/stdlib/src/shell.erl b/lib/stdlib/src/shell.erl index ebb221c151..e3e23e09bc 100644 --- a/lib/stdlib/src/shell.erl +++ b/lib/stdlib/src/shell.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2010. All Rights Reserved. +%% Copyright Ericsson AB 1996-2011. 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 @@ -115,7 +115,9 @@ whereis_evaluator(Shell) -> %% Call this function to start a user restricted shell %% from a normal shell session. --spec start_restricted(module()) -> {'error', code:load_error_rsn()}. +-spec start_restricted(Module) -> {'error', Reason} when + Module :: module(), + Reason :: code:load_error_rsn(). start_restricted(RShMod) when is_atom(RShMod) -> case code:ensure_loaded(RShMod) of @@ -465,7 +467,7 @@ getc(N) -> {get({command,N}), get({result,N}), N}. get_cmd(Num, C) -> - case catch erl_eval:expr(Num, []) of + case catch erl_eval:expr(Num, erl_eval:new_bindings()) of {value,N,_} when N < 0 -> getc(C+N); {value,N,_} -> getc(N); _Other -> {undefined,undefined,undefined} @@ -1184,6 +1186,8 @@ expr(E, Bs, Lf, Ef) -> expr_list(Es, Bs, Lf, Ef) -> erl_eval:expr_list(Es, strip_bindings(Bs), Lf, Ef). +-spec strip_bindings(erl_eval:binding_struct()) -> erl_eval:binding_struct(). + strip_bindings(Bs) -> Bs -- [B || {{module,_},_}=B <- Bs]. @@ -1468,23 +1472,26 @@ set_env(App, Name, Val, Default) -> application_controller:set_env(App, Name, Val), Prev. --spec history(non_neg_integer()) -> non_neg_integer(). +-spec history(N) -> non_neg_integer() when + N :: non_neg_integer(). history(L) when is_integer(L), L >= 0 -> set_env(stdlib, shell_history_length, L, ?DEF_HISTORY). --spec results(non_neg_integer()) -> non_neg_integer(). +-spec results(N) -> non_neg_integer() when + N :: non_neg_integer(). results(L) when is_integer(L), L >= 0 -> set_env(stdlib, shell_saved_results, L, ?DEF_RESULTS). --spec catch_exception(boolean()) -> boolean(). +-spec catch_exception(Bool) -> Bool when + Bool :: boolean(). catch_exception(Bool) -> set_env(stdlib, shell_catch_exception, Bool, ?DEF_CATCH_EXCEPTION). --type prompt_func() :: 'default' | {module(),atom()}. --spec prompt_func(prompt_func()) -> prompt_func(). +-spec prompt_func(PromptFunc) -> PromptFunc when + PromptFunc :: 'default' | {module(),atom()}. prompt_func(String) -> set_env(stdlib, shell_prompt_func, String, ?DEF_PROMPT_FUNC). diff --git a/lib/stdlib/src/slave.erl b/lib/stdlib/src/slave.erl index 196b659938..de0179da59 100644 --- a/lib/stdlib/src/slave.erl +++ b/lib/stdlib/src/slave.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. +%% Copyright Ericsson AB 1996-2011. 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 @@ -54,6 +54,10 @@ pseudo([Master | ServerList]) -> pseudo(_) -> error_msg("No master node given to slave:pseudo/1~n",[]). +-spec pseudo(Master, ServerList) -> ok when + Master :: node(), + ServerList :: [atom()]. + pseudo(_, []) -> ok; pseudo(Master, [S|Tail]) -> start_pseudo(S, whereis(S), Master), @@ -68,6 +72,9 @@ start_pseudo(_,_,_) -> ok. %% It's already there %% This relay can be used to relay all messages directed to a process. +-spec relay(Pid) -> no_return() when + Pid :: pid(). + relay({badrpc,Reason}) -> error_msg(" ** exiting relay server ~w :~w **~n", [self(),Reason]), exit(Reason); @@ -120,25 +127,61 @@ relay1(Pid) -> %% {error, no_rsh} | %% {error, {already_running, Name@Host}} +-spec start(Host) -> {ok, Node} | {error, Reason} when + Host :: atom(), + Node :: node(), + Reason :: timeout | no_rsh | {already_running, Node}. + start(Host) -> L = atom_to_list(node()), Name = upto($@, L), - start(Host, Name). + start(Host, Name, [], no_link). + +-spec start(Host, Name) -> {ok, Node} | {error, Reason} when + Host :: atom(), + Name :: atom(), + Node :: node(), + Reason :: timeout | no_rsh | {already_running, Node}. start(Host, Name) -> start(Host, Name, []). +-spec start(Host, Name, Args) -> {ok, Node} | {error, Reason} when + Host :: atom(), + Name :: atom(), + Args :: string(), + Node :: node(), + Reason :: timeout | no_rsh | {already_running, Node}. + start(Host, Name, Args) -> start(Host, Name, Args, no_link). +-spec start_link(Host) -> {ok, Node} | {error, Reason} when + Host :: atom(), + Node :: node(), + Reason :: timeout | no_rsh | {already_running, Node}. + start_link(Host) -> L = atom_to_list(node()), Name = upto($@, L), - start_link(Host, Name). + start(Host, Name, [], self()). + +-spec start_link(Host, Name) -> {ok, Node} | {error, Reason} when + Host :: atom(), + Name :: atom(), + Node :: node(), + Reason :: timeout | no_rsh | {already_running, Node}. start_link(Host, Name) -> start_link(Host, Name, []). +-spec start_link(Host, Name, Args) -> {ok, Node} | {error, Reason} when + Host :: atom(), + Name :: atom(), + Args :: string(), + Node :: node(), + Reason :: timeout | no_rsh | {already_running, Node}. + start_link(Host, Name, Args) -> start(Host, Name, Args, self()). @@ -163,6 +206,9 @@ start(Host0, Name, Args, LinkTo, Prog) -> %% Stops a running node. +-spec stop(Node) -> ok when + Node :: node(). + stop(Node) -> % io:format("stop(~p)~n", [Node]), rpc:call(Node, erlang, halt, []), diff --git a/lib/stdlib/src/sofs.erl b/lib/stdlib/src/sofs.erl index a83f803330..34eb224647 100644 --- a/lib/stdlib/src/sofs.erl +++ b/lib/stdlib/src/sofs.erl @@ -1,19 +1,19 @@ %% %% %CopyrightBegin% -%% -%% Copyright Ericsson AB 2001-2009. All Rights Reserved. -%% +%% +%% Copyright Ericsson AB 2001-2011. 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 %% compliance with the License. You should have received a copy of the %% Erlang Public License along with this software. If not, it can be %% retrieved online at http://www.erlang.org/. -%% +%% %% Software distributed under the License is distributed on an "AS IS" %% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See %% the License for the specific language governing rights and limitations %% under the License. -%% +%% %% %CopyrightEnd% %% -module(sofs). @@ -40,11 +40,11 @@ substitution/2, projection/2, partition/1, partition/2, partition/3, multiple_relative_product/2, join/4]). --export([family_to_relation/1, family_specification/2, +-export([family_to_relation/1, family_specification/2, union_of_family/1, intersection_of_family/1, family_union/1, family_intersection/1, family_domain/1, family_range/1, family_field/1, - family_union/2, family_intersection/2, family_difference/2, + family_union/2, family_intersection/2, family_difference/2, partition_family/2, family_projection/2]). -export([family_to_digraph/1, family_to_digraph/2, @@ -64,9 +64,9 @@ -compile({inline, [{external_fun,1},{element_type,1}]}). --compile({inline, +-compile({inline, [{unify_types,2}, {match_types,2}, - {test_rel,3}, {symdiff,3}, + {test_rel,3}, {symdiff,3}, {subst,3}]}). -compile({inline, [{fam_binop,3}]}). @@ -80,13 +80,14 @@ -define(TAG, 'Set'). -define(ORDTAG, 'OrdSet'). --record(?TAG, {data = [], type = type}). --record(?ORDTAG, {orddata = {}, ordtype = type}). +-record(?TAG, {data = [] :: list(), type = type :: term()}). +-record(?ORDTAG, {orddata = {} :: tuple() | atom(), + ordtype = type :: term()}). -define(LIST(S), (S)#?TAG.data). -define(TYPE(S), (S)#?TAG.type). -%%-define(SET(L, T), -%% case is_type(T) of +%%-define(SET(L, T), +%% case is_type(T) of %% true -> #?TAG{data = L, type = T}; %% false -> erlang:error(badtype, [T]) %% end @@ -113,14 +114,40 @@ -define(IS_SET_OF(X), is_list(X)). -define(FAMILY(X, Y), ?BINREL(X, ?SET_OF(Y))). +-export_type([anyset/0, binary_relation/0, external_set/0, a_function/0, + family/0, relation/0, set_of_sets/0, set_fun/0, spec_fun/0, + type/0]). +-export_type([ordset/0, a_set/0]). + +-type(anyset() :: ordset() | a_set()). +-type(binary_relation() :: relation()). +-type(external_set() :: term()). +-type(a_function() :: relation()). +-type(family() :: a_function()). +-opaque(ordset() :: #?ORDTAG{}). +-type(relation() :: a_set()). +-opaque(a_set() :: #?TAG{}). +-type(set_of_sets() :: a_set()). +-type(set_fun() :: pos_integer() + | {external, fun((external_set()) -> external_set())} + | fun((anyset()) -> anyset())). +-type(spec_fun() :: {external, fun((external_set()) -> boolean())} + | fun((anyset()) -> boolean())). +-type(type() :: term()). + +-type(tuple_of(_T) :: tuple()). + %% %% Exported functions %% -%%% +%%% %%% Create sets -%%% +%%% +-spec(from_term(Term) -> AnySet when + AnySet :: anyset(), + Term :: term()). from_term(T) -> Type = case T of _ when is_list(T) -> [?ANYTYPE]; @@ -133,6 +160,10 @@ from_term(T) -> Set end. +-spec(from_term(Term, Type) -> AnySet when + AnySet :: anyset(), + Term :: term(), + Type :: type()). from_term(L, T) -> case is_type(T) of true -> @@ -146,14 +177,23 @@ from_term(L, T) -> erlang:error(badarg, [L, T]) end. +-spec(from_external(ExternalSet, Type) -> AnySet when + ExternalSet :: external_set(), + AnySet :: anyset(), + Type :: type()). from_external(L, ?SET_OF(Type)) -> ?SET(L, Type); from_external(T, Type) -> ?ORDSET(T, Type). +-spec(empty_set() -> Set when + Set :: a_set()). empty_set() -> ?SET([], ?ANYTYPE). +-spec(is_type(Term) -> Bool when + Bool :: boolean(), + Term :: term()). is_type(Atom) when ?IS_ATOM_TYPE(Atom), Atom =/= ?ANYTYPE -> true; is_type(?SET_OF(T)) -> @@ -163,19 +203,26 @@ is_type(T) when tuple_size(T) > 0 -> is_type(_T) -> false. +-spec(set(Terms) -> Set when + Set :: a_set(), + Terms :: [term()]). set(L) -> case catch usort(L) of {'EXIT', _} -> erlang:error(badarg, [L]); - SL -> + SL -> ?SET(SL, ?ATOM_TYPE) end. +-spec(set(Terms, Type) -> Set when + Set :: a_set(), + Terms :: [term()], + Type :: type()). set(L, ?SET_OF(Type) = T) when ?IS_ATOM_TYPE(Type), Type =/= ?ANYTYPE -> case catch usort(L) of {'EXIT', _} -> erlang:error(badarg, [L, T]); - SL -> + SL -> ?SET(SL, Type) end; set(L, ?SET_OF(_) = T) -> @@ -188,6 +235,12 @@ set(L, ?SET_OF(_) = T) -> set(L, T) -> erlang:error(badarg, [L, T]). +-spec(from_sets(ListOfSets) -> Set when + Set :: a_set(), + ListOfSets :: [anyset()]; + (TupleOfSets) -> Ordset when + Ordset :: ordset(), + TupleOfSets :: tuple_of(anyset())). from_sets(Ss) when is_list(Ss) -> case set_of_sets(Ss, [], ?ANYTYPE) of {error, Error} -> @@ -205,6 +258,9 @@ from_sets(Tuple) when is_tuple(Tuple) -> from_sets(T) -> erlang:error(badarg, [T]). +-spec(relation(Tuples) -> Relation when + Relation :: relation(), + Tuples :: [tuple()]). relation([]) -> ?SET([], ?BINREL(?ATOM_TYPE, ?ATOM_TYPE)); relation(Ts = [T | _]) when is_tuple(T) -> @@ -217,6 +273,11 @@ relation(Ts = [T | _]) when is_tuple(T) -> relation(E) -> erlang:error(badarg, [E]). +-spec(relation(Tuples, Type) -> Relation when + N :: integer(), + Type :: N | type(), + Relation :: relation(), + Tuples :: [tuple()]). relation(Ts, TS) -> case catch rel(Ts, TS) of {'EXIT', _} -> @@ -225,6 +286,9 @@ relation(Ts, TS) -> Set end. +-spec(a_function(Tuples) -> Function when + Function :: a_function(), + Tuples :: [tuple()]). a_function(Ts) -> case catch func(Ts, ?BINREL(?ATOM_TYPE, ?ATOM_TYPE)) of {'EXIT', _} -> @@ -235,6 +299,10 @@ a_function(Ts) -> Set end. +-spec(a_function(Tuples, Type) -> Function when + Function :: a_function(), + Tuples :: [tuple()], + Type :: type()). a_function(Ts, T) -> case catch a_func(Ts, T) of {'EXIT', _} -> @@ -245,6 +313,9 @@ a_function(Ts, T) -> Set end. +-spec(family(Tuples) -> Family when + Family :: family(), + Tuples :: [tuple()]). family(Ts) -> case catch fam2(Ts, ?FAMILY(?ATOM_TYPE, ?ATOM_TYPE)) of {'EXIT', _} -> @@ -255,6 +326,10 @@ family(Ts) -> Set end. +-spec(family(Tuples, Type) -> Family when + Family :: family(), + Tuples :: [tuple()], + Type :: type()). family(Ts, T) -> case catch fam(Ts, T) of {'EXIT', _} -> @@ -265,20 +340,30 @@ family(Ts, T) -> Set end. -%%% +%%% %%% Functions on sets. -%%% +%%% +-spec(to_external(AnySet) -> ExternalSet when + ExternalSet :: external_set(), + AnySet :: anyset()). to_external(S) when ?IS_SET(S) -> ?LIST(S); to_external(S) when ?IS_ORDSET(S) -> ?ORDDATA(S). +-spec(type(AnySet) -> Type when + AnySet :: anyset(), + Type :: type()). type(S) when ?IS_SET(S) -> ?SET_OF(?TYPE(S)); type(S) when ?IS_ORDSET(S) -> ?ORDTYPE(S). +-spec(to_sets(ASet) -> Sets when + ASet :: a_set() | ordset(), + Sets :: tuple_of(AnySet) | [AnySet], + AnySet :: anyset()). to_sets(S) when ?IS_SET(S) -> case ?TYPE(S) of ?SET_OF(Type) -> list_of_sets(?LIST(S), Type, []); @@ -289,6 +374,9 @@ to_sets(S) when ?IS_ORDSET(S), is_tuple(?ORDTYPE(S)) -> to_sets(S) when ?IS_ORDSET(S) -> erlang:error(badarg, [S]). +-spec(no_elements(ASet) -> NoElements when + ASet :: a_set() | ordset(), + NoElements :: non_neg_integer()). no_elements(S) when ?IS_SET(S) -> length(?LIST(S)); no_elements(S) when ?IS_ORDSET(S), is_tuple(?ORDTYPE(S)) -> @@ -296,6 +384,10 @@ no_elements(S) when ?IS_ORDSET(S), is_tuple(?ORDTYPE(S)) -> no_elements(S) when ?IS_ORDSET(S) -> erlang:error(badarg, [S]). +-spec(specification(Fun, Set1) -> Set2 when + Fun :: spec_fun(), + Set1 :: a_set(), + Set2 :: a_set()). specification(Fun, S) when ?IS_SET(S) -> Type = ?TYPE(S), R = case external_fun(Fun) of @@ -311,36 +403,62 @@ specification(Fun, S) when ?IS_SET(S) -> erlang:error(Bad, [Fun, S]) end. +-spec(union(Set1, Set2) -> Set3 when + Set1 :: a_set(), + Set2 :: a_set(), + Set3 :: a_set()). union(S1, S2) when ?IS_SET(S1), ?IS_SET(S2) -> case unify_types(?TYPE(S1), ?TYPE(S2)) of [] -> erlang:error(type_mismatch, [S1, S2]); Type -> ?SET(umerge(?LIST(S1), ?LIST(S2)), Type) end. +-spec(intersection(Set1, Set2) -> Set3 when + Set1 :: a_set(), + Set2 :: a_set(), + Set3 :: a_set()). intersection(S1, S2) when ?IS_SET(S1), ?IS_SET(S2) -> case unify_types(?TYPE(S1), ?TYPE(S2)) of [] -> erlang:error(type_mismatch, [S1, S2]); Type -> ?SET(intersection(?LIST(S1), ?LIST(S2), []), Type) end. +-spec(difference(Set1, Set2) -> Set3 when + Set1 :: a_set(), + Set2 :: a_set(), + Set3 :: a_set()). difference(S1, S2) when ?IS_SET(S1), ?IS_SET(S2) -> case unify_types(?TYPE(S1), ?TYPE(S2)) of [] -> erlang:error(type_mismatch, [S1, S2]); Type -> ?SET(difference(?LIST(S1), ?LIST(S2), []), Type) end. +-spec(symdiff(Set1, Set2) -> Set3 when + Set1 :: a_set(), + Set2 :: a_set(), + Set3 :: a_set()). symdiff(S1, S2) when ?IS_SET(S1), ?IS_SET(S2) -> case unify_types(?TYPE(S1), ?TYPE(S2)) of [] -> erlang:error(type_mismatch, [S1, S2]); Type -> ?SET(symdiff(?LIST(S1), ?LIST(S2), []), Type) end. +-spec(symmetric_partition(Set1, Set2) -> {Set3, Set4, Set5} when + Set1 :: a_set(), + Set2 :: a_set(), + Set3 :: a_set(), + Set4 :: a_set(), + Set5 :: a_set()). symmetric_partition(S1, S2) when ?IS_SET(S1), ?IS_SET(S2) -> case unify_types(?TYPE(S1), ?TYPE(S2)) of [] -> erlang:error(type_mismatch, [S1, S2]); Type -> sympart(?LIST(S1), ?LIST(S2), [], [], [], Type) end. +-spec(product(Set1, Set2) -> BinRel when + BinRel :: binary_relation(), + Set1 :: a_set(), + Set2 :: a_set()). product(S1, S2) when ?IS_SET(S1), ?IS_SET(S2) -> if ?TYPE(S1) =:= ?ANYTYPE -> S1; @@ -351,6 +469,9 @@ product(S1, S2) when ?IS_SET(S1), ?IS_SET(S2) -> ?SET(relprod(map(F, ?LIST(S1)), map(F, ?LIST(S2))), T) end. +-spec(product(TupleOfSets) -> Relation when + Relation :: relation(), + TupleOfSets :: tuple_of(a_set())). product({S1, S2}) -> product(S1, S2); product(T) when is_tuple(T) -> @@ -365,11 +486,15 @@ product(T) when is_tuple(T) -> case member([], L) of true -> empty_set(); - false -> + false -> ?SET(reverse(prod(L, [], [])), Type) end end. +-spec(constant_function(Set, AnySet) -> Function when + AnySet :: anyset(), + Function :: a_function(), + Set :: a_set()). constant_function(S, E) when ?IS_SET(S) -> case {?TYPE(S), is_sofs_set(E)} of {?ANYTYPE, true} -> S; @@ -381,6 +506,10 @@ constant_function(S, E) when ?IS_SET(S) -> constant_function(S, E) when ?IS_ORDSET(S) -> erlang:error(badarg, [S, E]). +-spec(is_equal(AnySet1, AnySet2) -> Bool when + AnySet1 :: anyset(), + AnySet2 :: anyset(), + Bool :: boolean()). is_equal(S1, S2) when ?IS_SET(S1), ?IS_SET(S2) -> case match_types(?TYPE(S1), ?TYPE(S2)) of true -> ?LIST(S1) == ?LIST(S2); @@ -396,12 +525,19 @@ is_equal(S1, S2) when ?IS_SET(S1), ?IS_ORDSET(S2) -> is_equal(S1, S2) when ?IS_ORDSET(S1), ?IS_SET(S2) -> erlang:error(type_mismatch, [S1, S2]). +-spec(is_subset(Set1, Set2) -> Bool when + Bool :: boolean(), + Set1 :: a_set(), + Set2 :: a_set()). is_subset(S1, S2) when ?IS_SET(S1), ?IS_SET(S2) -> case match_types(?TYPE(S1), ?TYPE(S2)) of true -> subset(?LIST(S1), ?LIST(S2)); false -> erlang:error(type_mismatch, [S1, S2]) end. +-spec(is_sofs_set(Term) -> Bool when + Bool :: boolean(), + Term :: term()). is_sofs_set(S) when ?IS_SET(S) -> true; is_sofs_set(S) when ?IS_ORDSET(S) -> @@ -409,16 +545,26 @@ is_sofs_set(S) when ?IS_ORDSET(S) -> is_sofs_set(_S) -> false. +-spec(is_set(AnySet) -> Bool when + AnySet :: anyset(), + Bool :: boolean()). is_set(S) when ?IS_SET(S) -> true; is_set(S) when ?IS_ORDSET(S) -> false. -is_empty_set(S) when ?IS_SET(S) -> +-spec(is_empty_set(AnySet) -> Bool when + AnySet :: anyset(), + Bool :: boolean()). +is_empty_set(S) when ?IS_SET(S) -> ?LIST(S) =:= []; is_empty_set(S) when ?IS_ORDSET(S) -> false. +-spec(is_disjoint(Set1, Set2) -> Bool when + Bool :: boolean(), + Set1 :: a_set(), + Set2 :: a_set()). is_disjoint(S1, S2) when ?IS_SET(S1), ?IS_SET(S2) -> case match_types(?TYPE(S1), ?TYPE(S2)) of true -> @@ -433,6 +579,9 @@ is_disjoint(S1, S2) when ?IS_SET(S1), ?IS_SET(S2) -> %%% Functions on set-of-sets. %%% +-spec(union(SetOfSets) -> Set when + Set :: a_set(), + SetOfSets :: set_of_sets()). union(Sets) when ?IS_SET(Sets) -> case ?TYPE(Sets) of ?SET_OF(Type) -> ?SET(lunion(?LIST(Sets)), Type); @@ -440,6 +589,9 @@ union(Sets) when ?IS_SET(Sets) -> _ -> erlang:error(badarg, [Sets]) end. +-spec(intersection(SetOfSets) -> Set when + Set :: a_set(), + SetOfSets :: set_of_sets()). intersection(Sets) when ?IS_SET(Sets) -> case ?LIST(Sets) of [] -> erlang:error(badarg, [Sets]); @@ -451,32 +603,41 @@ intersection(Sets) when ?IS_SET(Sets) -> end end. +-spec(canonical_relation(SetOfSets) -> BinRel when + BinRel :: binary_relation(), + SetOfSets :: set_of_sets()). canonical_relation(Sets) when ?IS_SET(Sets) -> ST = ?TYPE(Sets), case ST of ?SET_OF(?ANYTYPE) -> empty_set(); - ?SET_OF(Type) -> + ?SET_OF(Type) -> ?SET(can_rel(?LIST(Sets), []), ?BINREL(Type, ST)); ?ANYTYPE -> Sets; _ -> erlang:error(badarg, [Sets]) end. -%%% +%%% %%% Functions on binary relations only. -%%% +%%% rel2fam(R) -> relation_to_family(R). +-spec(relation_to_family(BinRel) -> Family when + Family :: family(), + BinRel :: binary_relation()). %% Inlined. relation_to_family(R) when ?IS_SET(R) -> case ?TYPE(R) of - ?BINREL(DT, RT) -> + ?BINREL(DT, RT) -> ?SET(rel2family(?LIST(R)), ?FAMILY(DT, RT)); ?ANYTYPE -> R; _Else -> erlang:error(badarg, [R]) end. +-spec(domain(BinRel) -> Set when + BinRel :: binary_relation(), + Set :: a_set()). domain(R) when ?IS_SET(R) -> case ?TYPE(R) of ?BINREL(DT, _) -> ?SET(dom(?LIST(R)), DT); @@ -484,6 +645,9 @@ domain(R) when ?IS_SET(R) -> _Else -> erlang:error(badarg, [R]) end. +-spec(range(BinRel) -> Set when + BinRel :: binary_relation(), + Set :: a_set()). range(R) when ?IS_SET(R) -> case ?TYPE(R) of ?BINREL(_, RT) -> ?SET(ran(?LIST(R), []), RT); @@ -491,35 +655,63 @@ range(R) when ?IS_SET(R) -> _ -> erlang:error(badarg, [R]) end. +-spec(field(BinRel) -> Set when + BinRel :: binary_relation(), + Set :: a_set()). %% In "Introduction to LOGIC", Suppes defines the field of a binary %% relation to be the union of the domain and the range (or %% counterdomain). field(R) -> union(domain(R), range(R)). +-spec(relative_product(ListOfBinRels) -> BinRel2 when + ListOfBinRels :: [BinRel, ...], + BinRel :: binary_relation(), + BinRel2 :: binary_relation()). +%% The following clause is kept for backward compatibility. +%% The list is due to Dialyzer's specs. relative_product(RT) when is_tuple(RT) -> - case relprod_n(RT, foo, false, false) of - {error, Reason} -> - erlang:error(Reason, [RT]); + relative_product(tuple_to_list(RT)); +relative_product(RL) when is_list(RL) -> + case relprod_n(RL, foo, false, false) of + {error, Reason} -> + erlang:error(Reason, [RL]); Reply -> Reply end. +-spec(relative_product(ListOfBinRels, BinRel1) -> BinRel2 when + ListOfBinRels :: [BinRel, ...], + BinRel :: binary_relation(), + BinRel1 :: binary_relation(), + BinRel2 :: binary_relation(); + (BinRel1, BinRel2) -> BinRel3 when + BinRel1 :: binary_relation(), + BinRel2 :: binary_relation(), + BinRel3 :: binary_relation()). relative_product(R1, R2) when ?IS_SET(R1), ?IS_SET(R2) -> relative_product1(converse(R1), R2); +%% The following clause is kept for backward compatibility. +%% The list is due to Dialyzer's specs. relative_product(RT, R) when is_tuple(RT), ?IS_SET(R) -> + relative_product(tuple_to_list(RT), R); +relative_product(RL, R) when is_list(RL), ?IS_SET(R) -> EmptyR = case ?TYPE(R) of ?BINREL(_, _) -> ?LIST(R) =:= []; ?ANYTYPE -> true; - _ -> erlang:error(badarg, [RT, R]) + _ -> erlang:error(badarg, [RL, R]) end, - case relprod_n(RT, R, EmptyR, true) of - {error, Reason} -> - erlang:error(Reason, [RT, R]); + case relprod_n(RL, R, EmptyR, true) of + {error, Reason} -> + erlang:error(Reason, [RL, R]); Reply -> Reply end. +-spec(relative_product1(BinRel1, BinRel2) -> BinRel3 when + BinRel1 :: binary_relation(), + BinRel2 :: binary_relation(), + BinRel3 :: binary_relation()). relative_product1(R1, R2) when ?IS_SET(R1), ?IS_SET(R2) -> {DTR1, RTR1} = case ?TYPE(R1) of ?BINREL(_, _) = R1T -> R1T; @@ -538,16 +730,23 @@ relative_product1(R1, R2) when ?IS_SET(R1), ?IS_SET(R2) -> false -> erlang:error(type_mismatch, [R1, R2]) end. +-spec(converse(BinRel1) -> BinRel2 when + BinRel1 :: binary_relation(), + BinRel2 :: binary_relation()). converse(R) when ?IS_SET(R) -> case ?TYPE(R) of ?BINREL(DT, RT) -> ?SET(converse(?LIST(R), []), ?BINREL(RT, DT)); ?ANYTYPE -> R; _ -> erlang:error(badarg, [R]) end. - + +-spec(image(BinRel, Set1) -> Set2 when + BinRel :: binary_relation(), + Set1 :: a_set(), + Set2 :: a_set()). image(R, S) when ?IS_SET(R), ?IS_SET(S) -> case ?TYPE(R) of - ?BINREL(DT, RT) -> + ?BINREL(DT, RT) -> case match_types(DT, ?TYPE(S)) of true -> ?SET(usort(restrict(?LIST(S), ?LIST(R))), RT); @@ -558,9 +757,13 @@ image(R, S) when ?IS_SET(R), ?IS_SET(S) -> _ -> erlang:error(badarg, [R, S]) end. +-spec(inverse_image(BinRel, Set1) -> Set2 when + BinRel :: binary_relation(), + Set1 :: a_set(), + Set2 :: a_set()). inverse_image(R, S) when ?IS_SET(R), ?IS_SET(S) -> case ?TYPE(R) of - ?BINREL(DT, RT) -> + ?BINREL(DT, RT) -> case match_types(RT, ?TYPE(S)) of true -> NL = restrict(?LIST(S), converse(?LIST(R), [])), @@ -572,17 +775,23 @@ inverse_image(R, S) when ?IS_SET(R), ?IS_SET(S) -> _ -> erlang:error(badarg, [R, S]) end. +-spec(strict_relation(BinRel1) -> BinRel2 when + BinRel1 :: binary_relation(), + BinRel2 :: binary_relation()). strict_relation(R) when ?IS_SET(R) -> case ?TYPE(R) of - Type = ?BINREL(_, _) -> + Type = ?BINREL(_, _) -> ?SET(strict(?LIST(R), []), Type); ?ANYTYPE -> R; _ -> erlang:error(badarg, [R]) end. - + +-spec(weak_relation(BinRel1) -> BinRel2 when + BinRel1 :: binary_relation(), + BinRel2 :: binary_relation()). weak_relation(R) when ?IS_SET(R) -> case ?TYPE(R) of - ?BINREL(DT, RT) -> + ?BINREL(DT, RT) -> case unify_types(DT, RT) of [] -> erlang:error(badarg, [R]); @@ -592,7 +801,12 @@ weak_relation(R) when ?IS_SET(R) -> ?ANYTYPE -> R; _ -> erlang:error(badarg, [R]) end. - + +-spec(extension(BinRel1, Set, AnySet) -> BinRel2 when + AnySet :: anyset(), + BinRel1 :: binary_relation(), + BinRel2 :: binary_relation(), + Set :: a_set()). extension(R, S, E) when ?IS_SET(R), ?IS_SET(S) -> case {?TYPE(R), ?TYPE(S), is_sofs_set(E)} of {T=?BINREL(DT, RT), ST, true} -> @@ -621,9 +835,12 @@ extension(R, S, E) when ?IS_SET(R), ?IS_SET(S) -> erlang:error(badarg, [R, S, E]) end. +-spec(is_a_function(BinRel) -> Bool when + Bool :: boolean(), + BinRel :: binary_relation()). is_a_function(R) when ?IS_SET(R) -> case ?TYPE(R) of - ?BINREL(_, _) -> + ?BINREL(_, _) -> case ?LIST(R) of [] -> true; [{V,_} | Es] -> is_a_func(Es, V) @@ -632,16 +849,28 @@ is_a_function(R) when ?IS_SET(R) -> _ -> erlang:error(badarg, [R]) end. +-spec(restriction(BinRel1, Set) -> BinRel2 when + BinRel1 :: binary_relation(), + BinRel2 :: binary_relation(), + Set :: a_set()). restriction(Relation, Set) -> restriction(1, Relation, Set). +-spec(drestriction(BinRel1, Set) -> BinRel2 when + BinRel1 :: binary_relation(), + BinRel2 :: binary_relation(), + Set :: a_set()). drestriction(Relation, Set) -> drestriction(1, Relation, Set). -%%% +%%% %%% Functions on functions only. -%%% +%%% +-spec(composite(Function1, Function2) -> Function3 when + Function1 :: a_function(), + Function2 :: a_function(), + Function3 :: a_function()). composite(Fn1, Fn2) when ?IS_SET(Fn1), ?IS_SET(Fn2) -> ?BINREL(DTF1, RTF1) = case ?TYPE(Fn1)of ?BINREL(_, _) = F1T -> F1T; @@ -656,7 +885,7 @@ composite(Fn1, Fn2) when ?IS_SET(Fn1), ?IS_SET(Fn2) -> case match_types(RTF1, DTF2) of true when DTF1 =:= ?ANYTYPE -> Fn1; true when DTF2 =:= ?ANYTYPE -> Fn2; - true -> + true -> case comp(?LIST(Fn1), ?LIST(Fn2)) of SL when is_list(SL) -> ?SET(sort(SL), ?BINREL(DTF1, RTF2)); @@ -666,9 +895,12 @@ composite(Fn1, Fn2) when ?IS_SET(Fn1), ?IS_SET(Fn2) -> false -> erlang:error(type_mismatch, [Fn1, Fn2]) end. +-spec(inverse(Function1) -> Function2 when + Function1 :: a_function(), + Function2 :: a_function()). inverse(Fn) when ?IS_SET(Fn) -> case ?TYPE(Fn) of - ?BINREL(DT, RT) -> + ?BINREL(DT, RT) -> case inverse1(?LIST(Fn)) of SL when is_list(SL) -> ?SET(SL, ?BINREL(RT, DT)); @@ -678,11 +910,16 @@ inverse(Fn) when ?IS_SET(Fn) -> ?ANYTYPE -> Fn; _ -> erlang:error(badarg, [Fn]) end. - -%%% + +%%% %%% Functions on relations (binary or other). -%%% +%%% +-spec(restriction(SetFun, Set1, Set2) -> Set3 when + SetFun :: set_fun(), + Set1 :: a_set(), + Set2 :: a_set(), + Set3 :: a_set()). %% Equivalent to range(restriction(inverse(substitution(Fun, S1)), S2)). restriction(I, R, S) when is_integer(I), ?IS_SET(R), ?IS_SET(S) -> RT = ?TYPE(R), @@ -747,6 +984,11 @@ restriction(SetFun, S1, S2) when ?IS_SET(S1), ?IS_SET(S2) -> end end. +-spec(drestriction(SetFun, Set1, Set2) -> Set3 when + SetFun :: set_fun(), + Set1 :: a_set(), + Set2 :: a_set(), + Set3 :: a_set()). drestriction(I, R, S) when is_integer(I), ?IS_SET(R), ?IS_SET(S) -> RT = ?TYPE(R), ST = ?TYPE(S), @@ -812,6 +1054,10 @@ drestriction(SetFun, S1, S2) when ?IS_SET(S1), ?IS_SET(S2) -> end end. +-spec(projection(SetFun, Set1) -> Set2 when + SetFun :: set_fun(), + Set1 :: a_set(), + Set2 :: a_set()). projection(I, Set) when is_integer(I), ?IS_SET(Set) -> Type = ?TYPE(Set), case check_for_sort(Type, I) of @@ -827,6 +1073,10 @@ projection(I, Set) when is_integer(I), ?IS_SET(Set) -> projection(Fun, Set) -> range(substitution(Fun, Set)). +-spec(substitution(SetFun, Set1) -> Set2 when + SetFun :: set_fun(), + Set1 :: a_set(), + Set2 :: a_set()). substitution(I, Set) when is_integer(I), ?IS_SET(Set) -> Type = ?TYPE(Set), case check_for_sort(Type, I) of @@ -867,11 +1117,18 @@ substitution(SetFun, Set) when ?IS_SET(Set) -> end end. +-spec(partition(SetOfSets) -> Partition when + SetOfSets :: set_of_sets(), + Partition :: a_set()). partition(Sets) -> F1 = relation_to_family(canonical_relation(Sets)), F2 = relation_to_family(converse(F1)), range(F2). +-spec(partition(SetFun, Set) -> Partition when + SetFun :: set_fun(), + Partition :: a_set(), + Set :: a_set()). partition(I, Set) when is_integer(I), ?IS_SET(Set) -> Type = ?TYPE(Set), case check_for_sort(Type, I) of @@ -887,6 +1144,12 @@ partition(I, Set) when is_integer(I), ?IS_SET(Set) -> partition(Fun, Set) -> range(partition_family(Fun, Set)). +-spec(partition(SetFun, Set1, Set2) -> {Set3, Set4} when + SetFun :: set_fun(), + Set1 :: a_set(), + Set2 :: a_set(), + Set3 :: a_set(), + Set4 :: a_set()). partition(I, R, S) when is_integer(I), ?IS_SET(R), ?IS_SET(S) -> RT = ?TYPE(R), ST = ?TYPE(S), @@ -954,21 +1217,32 @@ partition(SetFun, S1, S2) when ?IS_SET(S1), ?IS_SET(S2) -> end end. +-spec(multiple_relative_product(TupleOfBinRels, BinRel1) -> BinRel2 when + TupleOfBinRels :: tuple_of(BinRel), + BinRel :: binary_relation(), + BinRel1 :: binary_relation(), + BinRel2 :: binary_relation()). multiple_relative_product(T, R) when is_tuple(T), ?IS_SET(R) -> case test_rel(R, tuple_size(T), eq) of true when ?TYPE(R) =:= ?ANYTYPE -> empty_set(); - true -> + true -> MProd = mul_relprod(tuple_to_list(T), 1, R), - relative_product(list_to_tuple(MProd)); - false -> + relative_product(MProd); + false -> erlang:error(badarg, [T, R]) end. -join(R1, I1, R2, I2) +-spec(join(Relation1, I, Relation2, J) -> Relation3 when + Relation1 :: relation(), + Relation2 :: relation(), + Relation3 :: relation(), + I :: pos_integer(), + J :: pos_integer()). +join(R1, I1, R2, I2) when ?IS_SET(R1), ?IS_SET(R2), is_integer(I1), is_integer(I2) -> case test_rel(R1, I1, lte) and test_rel(R2, I2, lte) of - false -> + false -> erlang:error(badarg, [R1, I1, R2, I2]); true when ?TYPE(R1) =:= ?ANYTYPE -> R1; true when ?TYPE(R2) =:= ?ANYTYPE -> R2; @@ -980,8 +1254,8 @@ join(R1, I1, R2, I2) true -> fun({X,Y}) -> join_element(X, Y) end; false -> - fun({X,Y}) -> - list_to_tuple(join_element(X, Y, I2)) + fun({X,Y}) -> + list_to_tuple(join_element(X, Y, I2)) end end, ?SET(replace(T, F, []), F({?TYPE(R1), ?TYPE(R2)})) @@ -1001,9 +1275,15 @@ test_rel(R, I, C) -> %%% Family functions %%% +-spec(fam2rel(Family) -> BinRel when + Family :: family(), + BinRel :: binary_relation()). fam2rel(F) -> family_to_relation(F). +-spec(family_to_relation(Family) -> BinRel when + Family :: family(), + BinRel :: binary_relation()). %% Inlined. family_to_relation(F) when ?IS_SET(F) -> case ?TYPE(F) of @@ -1013,6 +1293,10 @@ family_to_relation(F) when ?IS_SET(F) -> _ -> erlang:error(badarg, [F]) end. +-spec(family_specification(Fun, Family1) -> Family2 when + Fun :: spec_fun(), + Family1 :: family(), + Family2 :: family()). family_specification(Fun, F) when ?IS_SET(F) -> case ?TYPE(F) of ?FAMILY(_DT, Type) = FType -> @@ -1032,6 +1316,9 @@ family_specification(Fun, F) when ?IS_SET(F) -> _ -> erlang:error(badarg, [Fun, F]) end. +-spec(union_of_family(Family) -> Set when + Family :: family(), + Set :: a_set()). union_of_family(F) when ?IS_SET(F) -> case ?TYPE(F) of ?FAMILY(_DT, Type) -> @@ -1040,6 +1327,9 @@ union_of_family(F) when ?IS_SET(F) -> _ -> erlang:error(badarg, [F]) end. +-spec(intersection_of_family(Family) -> Set when + Family :: family(), + Set :: a_set()). intersection_of_family(F) when ?IS_SET(F) -> case ?TYPE(F) of ?FAMILY(_DT, Type) -> @@ -1052,6 +1342,9 @@ intersection_of_family(F) when ?IS_SET(F) -> _ -> erlang:error(badarg, [F]) end. +-spec(family_union(Family1) -> Family2 when + Family1 :: family(), + Family2 :: family()). family_union(F) when ?IS_SET(F) -> case ?TYPE(F) of ?FAMILY(DT, ?SET_OF(Type)) -> @@ -1060,6 +1353,9 @@ family_union(F) when ?IS_SET(F) -> _ -> erlang:error(badarg, [F]) end. +-spec(family_intersection(Family1) -> Family2 when + Family1 :: family(), + Family2 :: family()). family_intersection(F) when ?IS_SET(F) -> case ?TYPE(F) of ?FAMILY(DT, ?SET_OF(Type)) -> @@ -1073,6 +1369,9 @@ family_intersection(F) when ?IS_SET(F) -> _ -> erlang:error(badarg, [F]) end. +-spec(family_domain(Family1) -> Family2 when + Family1 :: family(), + Family2 :: family()). family_domain(F) when ?IS_SET(F) -> case ?TYPE(F) of ?FAMILY(FDT, ?BINREL(DT, _)) -> @@ -1082,6 +1381,9 @@ family_domain(F) when ?IS_SET(F) -> _ -> erlang:error(badarg, [F]) end. +-spec(family_range(Family1) -> Family2 when + Family1 :: family(), + Family2 :: family()). family_range(F) when ?IS_SET(F) -> case ?TYPE(F) of ?FAMILY(DT, ?BINREL(_, RT)) -> @@ -1091,15 +1393,30 @@ family_range(F) when ?IS_SET(F) -> _ -> erlang:error(badarg, [F]) end. +-spec(family_field(Family1) -> Family2 when + Family1 :: family(), + Family2 :: family()). family_field(F) -> family_union(family_domain(F), family_range(F)). +-spec(family_union(Family1, Family2) -> Family3 when + Family1 :: family(), + Family2 :: family(), + Family3 :: family()). family_union(F1, F2) -> fam_binop(F1, F2, fun fam_union/3). +-spec(family_intersection(Family1, Family2) -> Family3 when + Family1 :: family(), + Family2 :: family(), + Family3 :: family()). family_intersection(F1, F2) -> fam_binop(F1, F2, fun fam_intersect/3). +-spec(family_difference(Family1, Family2) -> Family3 when + Family1 :: family(), + Family2 :: family(), + Family3 :: family()). family_difference(F1, F2) -> fam_binop(F1, F2, fun fam_difference/3). @@ -1108,13 +1425,17 @@ fam_binop(F1, F2, FF) when ?IS_SET(F1), ?IS_SET(F2) -> case unify_types(?TYPE(F1), ?TYPE(F2)) of [] -> erlang:error(type_mismatch, [F1, F2]); - ?ANYTYPE -> + ?ANYTYPE -> F1; - Type = ?FAMILY(_, _) -> + Type = ?FAMILY(_, _) -> ?SET(FF(?LIST(F1), ?LIST(F2), []), Type); _ -> erlang:error(badarg, [F1, F2]) end. +-spec(partition_family(SetFun, Set) -> Family when + Family :: family(), + SetFun :: set_fun(), + Set :: a_set()). partition_family(I, Set) when is_integer(I), ?IS_SET(Set) -> Type = ?TYPE(Set), case check_for_sort(Type, I) of @@ -1159,8 +1480,12 @@ partition_family(SetFun, Set) when ?IS_SET(Set) -> end end. +-spec(family_projection(SetFun, Family1) -> Family2 when + SetFun :: set_fun(), + Family1 :: family(), + Family2 :: family()). family_projection(SetFun, F) when ?IS_SET(F) -> - case ?TYPE(F) of + case ?TYPE(F) of ?FAMILY(_, _) when [] =:= ?LIST(F) -> empty_set(); ?FAMILY(DT, Type) -> @@ -1172,7 +1497,7 @@ family_projection(SetFun, F) when ?IS_SET(F) -> Bad -> erlang:error(Bad, [SetFun, F]) end; - _ -> + _ -> erlang:error(badarg, [SetFun, F]) end; ?ANYTYPE -> F; @@ -1183,6 +1508,9 @@ family_projection(SetFun, F) when ?IS_SET(F) -> %%% Digraph functions %%% +-spec(family_to_digraph(Family) -> Graph when + Graph :: digraph(), + Family :: family()). family_to_digraph(F) when ?IS_SET(F) -> case ?TYPE(F) of ?FAMILY(_, _) -> fam2digraph(F, digraph:new()); @@ -1190,6 +1518,10 @@ family_to_digraph(F) when ?IS_SET(F) -> _Else -> erlang:error(badarg, [F]) end. +-spec(family_to_digraph(Family, GraphType) -> Graph when + Graph :: digraph(), + Family :: family(), + GraphType :: [digraph:d_type()]). family_to_digraph(F, Type) when ?IS_SET(F) -> case ?TYPE(F) of ?FAMILY(_, _) -> ok; @@ -1208,12 +1540,19 @@ family_to_digraph(F, Type) when ?IS_SET(F) -> error:badarg -> erlang:error(badarg, [F, Type]) end. +-spec(digraph_to_family(Graph) -> Family when + Graph :: digraph(), + Family :: family()). digraph_to_family(G) -> case catch digraph_family(G) of {'EXIT', _} -> erlang:error(badarg, [G]); L -> ?SET(L, ?FAMILY(?ATOM_TYPE, ?ATOM_TYPE)) end. +-spec(digraph_to_family(Graph, Type) -> Family when + Graph :: digraph(), + Family :: family(), + Type :: type()). digraph_to_family(G, T) -> case {is_type(T), T} of {true, ?SET_OF(?FAMILY(_,_) = Type)} -> @@ -1284,7 +1623,7 @@ rel(Ts, [Type]) -> end; rel(Ts, Sz) -> rel(Ts, Sz, erlang:make_tuple(Sz, ?ATOM_TYPE)). - + atoms_only(Type, I) when ?IS_ATOM_TYPE(?REL_TYPE(I, Type)) -> atoms_only(Type, I+1); atoms_only(Type, I) when I > tuple_size(Type), ?IS_RELATION(Type) -> @@ -1312,7 +1651,7 @@ rel_type([], SL, Type) when ?IS_RELATION(Type) -> %% Inlined. a_func(Ts, T) -> case {T, is_type(T)} of - {[?BINREL(DT, RT) = Type], true} when ?IS_ATOM_TYPE(DT), + {[?BINREL(DT, RT) = Type], true} when ?IS_ATOM_TYPE(DT), ?IS_ATOM_TYPE(RT) -> func(Ts, Type); {[Type], true} -> @@ -1333,16 +1672,16 @@ func([], _X0, L, Type) -> %% Inlined. fam(Ts, T) -> case {T, is_type(T)} of - {[?FAMILY(DT, RT) = Type], true} when ?IS_ATOM_TYPE(DT), + {[?FAMILY(DT, RT) = Type], true} when ?IS_ATOM_TYPE(DT), ?IS_ATOM_TYPE(RT) -> fam2(Ts, Type); {[Type], true} -> func_type(Ts, [], Type, fun(?FAMILY(_,_)) -> true end) end. -fam2([], Type) -> +fam2([], Type) -> ?SET([], Type); -fam2(Ts, Type) -> +fam2(Ts, Type) -> fam2(sort(Ts), Ts, [], Type). fam2([{I,L} | T], I0, SL, Type) when I /= I0 -> @@ -1383,7 +1722,7 @@ setify(E, Type0) -> {Type, OrdSet} = make_element(E, Type0, Type0), ?ORDSET(OrdSet, Type). -is_no_lists(T) when is_tuple(T) -> +is_no_lists(T) when is_tuple(T) -> Sz = tuple_size(T), is_no_lists(T, Sz, Sz, []). @@ -1404,7 +1743,7 @@ create([], T, _T0, L) -> make_element(C, ?ANYTYPE, _T0) -> make_element(C); -make_element(C, Atom, ?ANYTYPE) when ?IS_ATOM_TYPE(Atom), +make_element(C, Atom, ?ANYTYPE) when ?IS_ATOM_TYPE(Atom), not is_list(C), not is_tuple(C) -> {Atom, C}; make_element(C, Atom, Atom) when ?IS_ATOM_TYPE(Atom) -> @@ -1585,12 +1924,12 @@ sympart([H1 | T1], [H2 | T2], L1, L12, L2, T) when H1 == H2 -> sympart([H1 | T1], [H2 | T2], L1, L12, L2, T) -> sympart2(T1, T2, L1, L12, [H2 | L2], T, H1); sympart(S1, [], L1, L12, L2, T) -> - {?SET(reverse(L1, S1), T), - ?SET(reverse(L12), T), + {?SET(reverse(L1, S1), T), + ?SET(reverse(L12), T), ?SET(reverse(L2), T)}; sympart(_, S2, L1, L12, L2, T) -> - {?SET(reverse(L1), T), - ?SET(reverse(L12), T), + {?SET(reverse(L1), T), + ?SET(reverse(L12), T), ?SET(reverse(L2, S2), T)}. sympart1([H1 | T1], T2, L1, L12, L2, T, H2) when H1 < H2 -> @@ -1600,8 +1939,8 @@ sympart1([H1 | T1], T2, L1, L12, L2, T, H2) when H1 == H2 -> sympart1([H1 | T1], T2, L1, L12, L2, T, H2) -> sympart2(T1, T2, L1, L12, [H2 | L2], T, H1); sympart1(_, T2, L1, L12, L2, T, H2) -> - {?SET(reverse(L1), T), - ?SET(reverse(L12), T), + {?SET(reverse(L1), T), + ?SET(reverse(L12), T), ?SET(reverse(L2, [H2 | T2]), T)}. sympart2(T1, [H2 | T2], L1, L12, L2, T, H1) when H1 > H2 -> @@ -1611,8 +1950,8 @@ sympart2(T1, [H2 | T2], L1, L12, L2, T, H1) when H1 == H2 -> sympart2(T1, [H2 | T2], L1, L12, L2, T, H1) -> sympart1(T1, T2, [H1 | L1], L12, L2, T, H2); sympart2(T1, _, L1, L12, L2, T, H1) -> - {?SET(reverse(L1, [H1 | T1]), T), - ?SET(reverse(L12), T), + {?SET(reverse(L1, [H1 | T1]), T), + ?SET(reverse(L12), T), ?SET(reverse(L2), T)}. prod([[E | Es] | Xs], T, L) -> @@ -1660,7 +1999,7 @@ lunion([[] | Ls]) -> lunion(Ls); lunion([S | Ss]) -> umerge(lunion(Ss, last(S), [S], [])); -lunion([]) -> +lunion([]) -> []. lunion([[E] = S | Ss], Last, SL, Ls) when E > Last -> % optimization @@ -1669,7 +2008,7 @@ lunion([S | Ss], Last, SL, Ls) when hd(S) > Last -> lunion(Ss, last(S), [S | SL], Ls); lunion([S | Ss], _Last, SL, Ls) -> lunion(Ss, last(S), [S], [append(reverse(SL)) | Ls]); -lunion([], _Last, SL, Ls) -> +lunion([], _Last, SL, Ls) -> [append(reverse(SL)) | Ls]. %% The empty list is always the first list, if present. @@ -1752,18 +2091,17 @@ relprod(B0, Bx0, By0, A0, L, Ax, [{Bx,By} | B], Ay) when Ay == Bx -> relprod(B0, Bx0, By0, A0, L, _Ax, _B, _Ay) -> relprod2(B0, Bx0, By0, A0, L). -relprod_n({}, _R, _EmptyG, _IsR) -> +relprod_n([], _R, _EmptyG, _IsR) -> {error, badarg}; -relprod_n(RT, R, EmptyR, IsR) -> - RL = tuple_to_list(RT), +relprod_n(RL, R, EmptyR, IsR) -> case domain_type(RL, ?ANYTYPE) of - Error = {error, _Reason} -> + Error = {error, _Reason} -> Error; DType -> Empty = any(fun is_empty_set/1, RL) or EmptyR, RType = range_type(RL, []), Type = ?BINREL(DType, RType), - Prod = + Prod = case Empty of true when DType =:= ?ANYTYPE; RType =:= ?ANYTYPE -> empty_set(); @@ -1771,7 +2109,7 @@ relprod_n(RT, R, EmptyR, IsR) -> ?SET([], Type); false -> TL = ?LIST((relprod_n(RL))), - Sz = tuple_size(RT), + Sz = length(RL), Fun = fun({X,A}) -> {X, flat(Sz, A, [])} end, ?SET(map(Fun, TL), Type) end, @@ -1799,12 +2137,12 @@ flat(N, {T,A}, L) -> domain_type([T | Ts], T0) when ?IS_SET(T) -> case ?TYPE(T) of - ?BINREL(DT, _RT) -> + ?BINREL(DT, _RT) -> case unify_types(DT, T0) of [] -> {error, type_mismatch}; T1 -> domain_type(Ts, T1) end; - ?ANYTYPE -> + ?ANYTYPE -> domain_type(Ts, T0); _ -> {error, badarg} end; @@ -1813,12 +2151,12 @@ domain_type([], T0) -> range_type([T | Ts], L) -> case ?TYPE(T) of - ?BINREL(_DT, RT) -> + ?BINREL(_DT, RT) -> range_type(Ts, [RT | L]); - ?ANYTYPE -> + ?ANYTYPE -> ?ANYTYPE end; -range_type([], L) -> +range_type([], L) -> list_to_tuple(reverse(L)). converse([{A,B} | X], L) -> @@ -1861,7 +2199,7 @@ weak1([E={X,_Y} | Es], Ys, L, X0) when X == X0 -> % when X < Y weak1(Es, Ys, L, X) -> weak(Es, Ys, [{X,X} | L]). -weak2([E={X,_Y} | Es], Ys, L, X0) when X == X0 -> % when X < _Y +weak2([E={X,_Y} | Es], Ys, L, X0) when X == X0 -> % when X < _Y weak2(Es, Ys, [E | L], X); weak2(Es, Ys, L, _X) -> weak(Es, Ys, L). @@ -1910,7 +2248,7 @@ restrict_n(I, [T | Ts], Key, Keys, L) -> end; restrict_n(_I, _Ts, _Key, _Keys, L) -> L. - + restrict_n(I, K, Ts, [Key | Keys], L, E) when K > Key -> restrict_n(I, K, Ts, Keys, L, E); restrict_n(I, K, Ts, [Key | Keys], L, E) when K == Key -> @@ -1933,7 +2271,7 @@ restrict([{K,E} | Ts], _Key, Keys, L) -> restrict(Ts, K, Keys, L, E); restrict(_Ts, _Key, _Keys, L) -> L. - + restrict(Ts, K, [Key | Keys], L, E) when K > Key -> restrict(Ts, K, Keys, L, E); restrict(Ts, K, [Key | Keys], L, E) when K == Key -> @@ -1956,7 +2294,7 @@ diff_restrict_n(I, _Ts, _Key, _Keys, L) when I =:= 1 -> reverse(L); diff_restrict_n(_I, _Ts, _Key, _Keys, L) -> sort(L). - + diff_restrict_n(I, K, Ts, [Key | Keys], L, T) when K > Key -> diff_restrict_n(I, K, Ts, Keys, L, T); diff_restrict_n(I, K, Ts, [Key | Keys], L, _T) when K == Key -> @@ -1981,7 +2319,7 @@ diff_restrict([{K,E} | Ts], _Key, Keys, L) -> diff_restrict(Ts, K, Keys, L, E); diff_restrict(_Ts, _Key, _Keys, L) -> L. - + diff_restrict(Ts, K, [Key | Keys], L, E) when K > Key -> diff_restrict(Ts, K, Keys, L, E); diff_restrict(Ts, K, [Key | Keys], L, _E) when K == Key -> @@ -2041,7 +2379,7 @@ external_fun({external, Function}) when is_atom(Function) -> false; external_fun({external, Fun}) -> Fun; -external_fun(_) -> +external_fun(_) -> false. %% Inlined. @@ -2121,7 +2459,7 @@ partition3_n(I, _Ts, _Key, _Keys, L1, L2) when I =:= 1 -> [reverse(L1) | reverse(L2)]; partition3_n(_I, _Ts, _Key, _Keys, L1, L2) -> [sort(L1) | sort(L2)]. - + partition3_n(I, K, Ts, [Key | Keys], L1, L2, T) when K > Key -> partition3_n(I, K, Ts, Keys, L1, L2, T); partition3_n(I, K, Ts, [Key | Keys], L1, L2, T) when K == Key -> @@ -2146,7 +2484,7 @@ partition3([{K,E} | Ts], _Key, Keys, L1, L2) -> partition3(Ts, K, Keys, L1, L2, E); partition3(_Ts, _Key, _Keys, L1, L2) -> [L1 | L2]. - + partition3(Ts, K, [Key | Keys], L1, L2, E) when K > Key -> partition3(Ts, K, Keys, L1, L2, E); partition3(Ts, K, [Key | Keys], L1, L2, E) when K == Key -> @@ -2192,7 +2530,7 @@ join_element(E1, E2, I2) -> join_element2([B | Bs], C, I2) when C =/= I2 -> [B | join_element2(Bs, C+1, I2)]; -join_element2([_ | Bs], _C, _I2) -> +join_element2([_ | Bs], _C, _I2) -> Bs. family2rel([{X,S} | F], L) -> @@ -2297,7 +2635,7 @@ check_function([{X,_} | XL], R) -> check_function(X, XL, R); check_function([], R) -> R. - + check_function(X0, [{X,_} | XL], R) when X0 /= X -> check_function(X, XL, R); check_function(X0, [{X,_} | _XL], _R) when X0 == X -> @@ -2371,14 +2709,14 @@ term2set(T, Type) -> ?ORDSET(T, Type). fam2digraph(F, G) -> - Fun = fun({From, ToL}) -> + Fun = fun({From, ToL}) -> digraph:add_vertex(G, From), Fun2 = fun(To) -> digraph:add_vertex(G, To), case digraph:add_edge(G, From, To) of - {error, {bad_edge, _}} -> + {error, {bad_edge, _}} -> throw({error, cyclic}); - _ -> + _ -> true end end, @@ -2397,7 +2735,7 @@ digraph_fam([V | Vs], V0, G, L) when V /= V0 -> digraph_fam([], _V0, _G, L) -> reverse(L). -%% -> bool() +%% -> boolean() check_fun(T, F, FunT) -> true = is_type(FunT), {NT, _MaxI} = number_tuples(T, 1), @@ -2424,7 +2762,7 @@ check_for_sort(T, _I) when T =:= ?ANYTYPE -> check_for_sort(T, I) when ?IS_RELATION(T), I =< ?REL_ARITY(T), I >= 1 -> I > 1; check_for_sort(_T, _I) -> - error. + error. inverse_substitution(L, Fun, Sort) -> %% One easily sees that the inverse of the tuples created by @@ -2477,11 +2815,11 @@ match_types(Type1, Type2) -> match_types1(Type1, Type2). match_types1(Atom, Atom) when ?IS_ATOM_TYPE(Atom) -> true; -match_types1(?ANYTYPE, _) -> +match_types1(?ANYTYPE, _) -> true; -match_types1(_, ?ANYTYPE) -> +match_types1(_, ?ANYTYPE) -> true; -match_types1(?SET_OF(Type1), ?SET_OF(Type2)) -> +match_types1(?SET_OF(Type1), ?SET_OF(Type2)) -> match_types1(Type1, Type2); match_types1(T1, T2) when tuple_size(T1) =:= tuple_size(T2) -> match_typesl(tuple_size(T1), T1, T2); diff --git a/lib/stdlib/src/stdlib.app.src b/lib/stdlib/src/stdlib.app.src index 3e52c48e42..9d15f01683 100644 --- a/lib/stdlib/src/stdlib.app.src +++ b/lib/stdlib/src/stdlib.app.src @@ -1,20 +1,20 @@ %% This is an -*- erlang -*- file. %% %% %CopyrightBegin% -%% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. -%% +%% +%% Copyright Ericsson AB 1996-2010. 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 %% compliance with the License. You should have received a copy of the %% Erlang Public License along with this software. If not, it can be %% retrieved online at http://www.erlang.org/. -%% +%% %% Software distributed under the License is distributed on an "AS IS" %% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See %% the License for the specific language governing rights and limitations %% under the License. -%% +%% %% %CopyrightEnd% %% {application, stdlib, @@ -23,6 +23,7 @@ {modules, [array, base64, beam_lib, + binary, c, calendar, dets, diff --git a/lib/stdlib/src/string.erl b/lib/stdlib/src/string.erl index 6636a03f06..30eac4f07d 100644 --- a/lib/stdlib/src/string.erl +++ b/lib/stdlib/src/string.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. +%% Copyright Ericsson AB 1996-2011. 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,23 +29,23 @@ %%--------------------------------------------------------------------------- --type direction() :: 'left' | 'right' | 'both'. - -%%--------------------------------------------------------------------------- - %% Robert's bit %% len(String) %% Return the length of a string. --spec len(string()) -> non_neg_integer(). +-spec len(String) -> Length when + String :: string(), + Length :: non_neg_integer(). len(S) -> length(S). %% equal(String1, String2) %% Test if 2 strings are equal. --spec equal(string(), string()) -> boolean(). +-spec equal(String1, String2) -> boolean() when + String1 :: string(), + String2 :: string(). equal(S, S) -> true; equal(_, _) -> false. @@ -53,7 +53,10 @@ equal(_, _) -> false. %% concat(String1, String2) %% Concatenate 2 strings. --spec concat(string(), string()) -> string(). +-spec concat(String1, String2) -> String3 when + String1 :: string(), + String2 :: string(), + String3 :: string(). concat(S1, S2) -> S1 ++ S2. @@ -61,7 +64,10 @@ concat(S1, S2) -> S1 ++ S2. %% rchr(String, Char) %% Return the first/last index of the character in a string. --spec chr(string(), char()) -> non_neg_integer(). +-spec chr(String, Character) -> Index when + String :: string(), + Character :: char(), + Index :: non_neg_integer(). chr(S, C) when is_integer(C) -> chr(S, C, 1). @@ -69,7 +75,10 @@ chr([C|_Cs], C, I) -> I; chr([_|Cs], C, I) -> chr(Cs, C, I+1); chr([], _C, _I) -> 0. --spec rchr(string(), char()) -> non_neg_integer(). +-spec rchr(String, Character) -> Index when + String :: string(), + Character :: char(), + Index :: non_neg_integer(). rchr(S, C) when is_integer(C) -> rchr(S, C, 1, 0). @@ -85,7 +94,10 @@ rchr([], _C, _I, L) -> L. %% Return the first/last index of the sub-string in a string. %% index/2 is kept for backwards compatibility. --spec str(string(), string()) -> non_neg_integer(). +-spec str(String, SubString) -> Index when + String :: string(), + SubString :: string(), + Index :: non_neg_integer(). str(S, Sub) when is_list(Sub) -> str(S, Sub, 1). @@ -97,7 +109,10 @@ str([C|S], [C|Sub], I) -> str([_|S], Sub, I) -> str(S, Sub, I+1); str([], _Sub, _I) -> 0. --spec rstr(string(), string()) -> non_neg_integer(). +-spec rstr(String, SubString) -> Index when + String :: string(), + SubString :: string(), + Index :: non_neg_integer(). rstr(S, Sub) when is_list(Sub) -> rstr(S, Sub, 1, 0). @@ -116,7 +131,10 @@ prefix(Pre, String) when is_list(Pre), is_list(String) -> false. %% span(String, Chars) -> Length. %% cspan(String, Chars) -> Length. --spec span(string(), string()) -> non_neg_integer(). +-spec span(String, Chars) -> Length when + String :: string(), + Chars :: string(), + Length :: non_neg_integer(). span(S, Cs) when is_list(Cs) -> span(S, Cs, 0). @@ -127,7 +145,10 @@ span([C|S], Cs, I) -> end; span([], _Cs, I) -> I. --spec cspan(string(), string()) -> non_neg_integer(). +-spec cspan(String, Chars) -> Length when + String :: string(), + Chars :: string(), + Length :: non_neg_integer(). cspan(S, Cs) when is_list(Cs) -> cspan(S, Cs, 0). @@ -142,14 +163,21 @@ cspan([], _Cs, I) -> I. %% substr(String, Start, Length) %% Extract a sub-string from String. --spec substr(string(), pos_integer()) -> string(). +-spec substr(String, Start) -> SubString when + String :: string(), + SubString :: string(), + Start :: pos_integer(). substr(String, 1) when is_list(String) -> String; substr(String, S) when is_integer(S), S > 1 -> substr2(String, S). --spec substr(string(), pos_integer(), non_neg_integer()) -> string(). +-spec substr(String, Start, Length) -> SubString when + String :: string(), + SubString :: string(), + Start :: pos_integer(), + Length :: non_neg_integer(). substr(String, S, L) when is_integer(S), S >= 1, is_integer(L), L >= 0 -> substr1(substr2(String, S), L). @@ -163,7 +191,10 @@ substr2([_|String], S) -> substr2(String, S-1). %% tokens(String, Seperators). %% Return a list of tokens seperated by characters in Seperators. --spec tokens(string(), string()) -> [[char(),...]]. +-spec tokens(String, SeparatorList) -> Tokens when + String :: string(), + SeparatorList :: string(), + Tokens :: [Token :: nonempty_string()]. tokens(S, Seps) -> tokens1(S, Seps, []). @@ -184,11 +215,18 @@ tokens2([C|S], Seps, Toks, Cs) -> tokens2([], _Seps, Toks, Cs) -> reverse([reverse(Cs)|Toks]). --spec chars(char(), non_neg_integer()) -> string(). +-spec chars(Character, Number) -> String when + Character :: char(), + Number :: non_neg_integer(), + String :: string(). chars(C, N) -> chars(C, N, []). --spec chars(char(), non_neg_integer(), string()) -> string(). +-spec chars(Character, Number, Tail) -> String when + Character :: char(), + Number :: non_neg_integer(), + Tail :: string(), + String :: string(). chars(C, N, Tail) when N > 0 -> chars(C, N-1, [C|Tail]); @@ -199,9 +237,12 @@ chars(C, 0, Tail) when is_integer(C) -> %%% COPIES %%% --spec copies(string(), non_neg_integer()) -> string(). +-spec copies(String, Number) -> Copies when + String :: string(), + Copies :: string(), + Number :: non_neg_integer(). -copies(CharList, Num) when is_list(CharList), Num >= 0 -> +copies(CharList, Num) when is_list(CharList), is_integer(Num), Num >= 0 -> copies(CharList, Num, []). copies(_CharList, 0, R) -> @@ -211,11 +252,16 @@ copies(CharList, Num, R) -> %%% WORDS %%% --spec words(string()) -> pos_integer(). +-spec words(String) -> Count when + String :: string(), + Count :: pos_integer(). words(String) -> words(String, $\s). --spec words(string(), char()) -> pos_integer(). +-spec words(String, Character) -> Count when + String :: string(), + Character :: char(), + Count :: pos_integer(). words(String, Char) when is_integer(Char) -> w_count(strip(String, both, Char), Char, 0). @@ -226,11 +272,18 @@ w_count([_H|T], Char, Num) -> w_count(T, Char, Num). %%% SUB_WORDS %%% --spec sub_word(string(), integer()) -> string(). +-spec sub_word(String, Number) -> Word when + String :: string(), + Word :: string(), + Number :: integer(). sub_word(String, Index) -> sub_word(String, Index, $\s). --spec sub_word(string(), integer(), char()) -> string(). +-spec sub_word(String, Number, Character) -> Word when + String :: string(), + Word :: string(), + Number :: integer(), + Character :: char(). sub_word(String, Index, Char) when is_integer(Index), is_integer(Char) -> case words(String, Char) of @@ -254,14 +307,21 @@ s_word([_|T],Stop,Char,Index,Res) when Index < Stop -> strip(String) -> strip(String, both). --spec strip(string(), direction()) -> string(). +-spec strip(String, Direction) -> Stripped when + String :: string(), + Stripped :: string(), + Direction :: left | right | both. strip(String, left) -> strip_left(String, $\s); strip(String, right) -> strip_right(String, $\s); strip(String, both) -> strip_right(strip_left(String, $\s), $\s). --spec strip(string(), direction(), char()) -> string(). +-spec strip(String, Direction, Character) -> Stripped when + String :: string(), + Stripped :: string(), + Direction :: left | right | both, + Character :: char(). strip(String, right, Char) -> strip_right(String, Char); strip(String, left, Char) -> strip_left(String, Char); @@ -285,11 +345,18 @@ strip_right([], Sc) when is_integer(Sc) -> %%% LEFT %%% --spec left(string(), non_neg_integer()) -> string(). +-spec left(String, Number) -> Left when + String :: string(), + Left :: string(), + Number :: non_neg_integer(). left(String, Len) when is_integer(Len) -> left(String, Len, $\s). --spec left(string(), non_neg_integer(), char()) -> string(). +-spec left(String, Number, Character) -> Left when + String :: string(), + Left :: string(), + Number :: non_neg_integer(), + Character :: char(). left(String, Len, Char) when is_integer(Char) -> Slen = length(String), @@ -303,11 +370,18 @@ l_pad(String, Num, Char) -> String ++ chars(Char, Num). %%% RIGHT %%% --spec right(string(), non_neg_integer()) -> string(). +-spec right(String, Number) -> Right when + String :: string(), + Right :: string(), + Number :: non_neg_integer(). right(String, Len) when is_integer(Len) -> right(String, Len, $\s). --spec right(string(), non_neg_integer(), char()) -> string(). +-spec right(String, Number, Character) -> Right when + String :: string(), + Right :: string(), + Number :: non_neg_integer(), + Character :: char(). right(String, Len, Char) when is_integer(Char) -> Slen = length(String), @@ -321,11 +395,18 @@ r_pad(String, Num, Char) -> chars(Char, Num, String). %%% CENTRE %%% --spec centre(string(), non_neg_integer()) -> string(). +-spec centre(String, Number) -> Centered when + String :: string(), + Centered :: string(), + Number :: non_neg_integer(). centre(String, Len) when is_integer(Len) -> centre(String, Len, $\s). --spec centre(string(), non_neg_integer(), char()) -> string(). +-spec centre(String, Number, Character) -> Centered when + String :: string(), + Centered :: string(), + Number :: non_neg_integer(), + Character :: char(). centre(String, 0, Char) when is_list(String), is_integer(Char) -> []; % Strange cases to centre string @@ -341,11 +422,18 @@ centre(String, Len, Char) when is_integer(Char) -> %%% SUB_STRING %%% --spec sub_string(string(), pos_integer()) -> string(). +-spec sub_string(String, Start) -> SubString when + String :: string(), + SubString :: string(), + Start :: pos_integer(). sub_string(String, Start) -> substr(String, Start). --spec sub_string(string(), pos_integer(), pos_integer()) -> string(). +-spec sub_string(String, Start, Stop) -> SubString when + String :: string(), + SubString :: string(), + Start :: pos_integer(), + Stop :: pos_integer(). sub_string(String, Start, Stop) -> substr(String, Start, Stop - Start + 1). @@ -370,23 +458,34 @@ to_upper_char(C) when is_integer(C), 16#F8 =< C, C =< 16#FE -> to_upper_char(C) -> C. --spec to_lower(string()) -> string() - ; (char()) -> char(). +-spec to_lower(String) -> Result when + String :: string(), + Result :: string() + ; (Char) -> CharResult when + Char :: char(), + CharResult :: char(). to_lower(S) when is_list(S) -> [to_lower_char(C) || C <- S]; to_lower(C) when is_integer(C) -> to_lower_char(C). --spec to_upper(string()) -> string() - ; (char()) -> char(). +-spec to_upper(String) -> Result when + String :: string(), + Result :: string() + ; (Char) -> CharResult when + Char :: char(), + CharResult :: char(). to_upper(S) when is_list(S) -> [to_upper_char(C) || C <- S]; to_upper(C) when is_integer(C) -> to_upper_char(C). --spec join([string()], string()) -> string(). +-spec join(StringList, Separator) -> String when + StringList :: [string()], + Separator :: string(), + String :: string(). join([], Sep) when is_list(Sep) -> []; diff --git a/lib/stdlib/src/supervisor.erl b/lib/stdlib/src/supervisor.erl index 22269a8d1b..dc31647eb5 100644 --- a/lib/stdlib/src/supervisor.erl +++ b/lib/stdlib/src/supervisor.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2010. All Rights Reserved. +%% Copyright Ericsson AB 1996-2011. 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 @@ -21,7 +21,7 @@ -behaviour(gen_server). %% External exports --export([start_link/2,start_link/3, +-export([start_link/2, start_link/3, start_child/2, restart_child/2, delete_child/2, terminate_child/2, which_children/1, count_children/1, @@ -33,28 +33,67 @@ -export([init/1, handle_call/3, handle_info/2, terminate/2, code_change/3]). -export([handle_cast/2]). +%%-------------------------------------------------------------------------- + +-export_type([child_spec/0, startchild_ret/0, strategy/0]). + +%%-------------------------------------------------------------------------- + +-type child() :: pid() | 'undefined'. +-type child_id() :: term(). +-type mfargs() :: {M :: module(), F :: atom(), A :: [term()] | undefined}. +-type modules() :: [module()] | 'dynamic'. +-type restart() :: 'permanent' | 'transient' | 'temporary'. +-type shutdown() :: 'brutal_kill' | timeout(). +-type worker() :: 'worker' | 'supervisor'. +-type sup_name() :: {'local', Name :: atom()} | {'global', Name :: atom()}. +-type sup_ref() :: (Name :: atom()) + | {Name :: atom(), Node :: node()} + | {'global', Name :: atom()} + | pid(). +-type child_spec() :: {Id :: child_id(), + StartFunc :: mfargs(), + Restart :: restart(), + Shutdown :: shutdown(), + Type :: worker(), + Modules :: modules()}. + +-type strategy() :: 'one_for_all' | 'one_for_one' + | 'rest_for_one' | 'simple_one_for_one'. + +%%-------------------------------------------------------------------------- + +-record(child, {% pid is undefined when child is not running + pid = undefined :: child(), + name, + mfargs :: mfargs(), + restart_type :: restart(), + shutdown :: shutdown(), + child_type :: worker(), + modules = [] :: modules()}). +-type child_rec() :: #child{}. + -define(DICT, dict). +-define(SETS, sets). +-define(SET, set). -record(state, {name, - strategy, - children = [], - dynamics = ?DICT:new(), - intensity, - period, + strategy :: strategy(), + children = [] :: [child_rec()], + dynamics :: ?DICT() | ?SET(), + intensity :: non_neg_integer(), + period :: pos_integer(), restarts = [], module, args}). - --record(child, {pid = undefined, % pid is undefined when child is not running - name, - mfa, - restart_type, - shutdown, - child_type, - modules = []}). +-type state() :: #state{}. -define(is_simple(State), State#state.strategy =:= simple_one_for_one). +%%-------------------------------------------------------------------------- + +-spec behaviour_info(atom()) -> 'undefined' | [{atom(), arity()}]. + behaviour_info(callbacks) -> [{init,1}]; behaviour_info(_Other) -> @@ -65,21 +104,54 @@ behaviour_info(_Other) -> %%% Servers/processes should/could also be built using gen_server.erl. %%% SupName = {local, atom()} | {global, atom()}. %%% --------------------------------------------------- + +-type startlink_err() :: {'already_started', pid()} | 'shutdown' | term(). +-type startlink_ret() :: {'ok', pid()} | 'ignore' | {'error', startlink_err()}. + +-spec start_link(Module, Args) -> startlink_ret() when + Module :: module(), + Args :: term(). start_link(Mod, Args) -> gen_server:start_link(supervisor, {self, Mod, Args}, []). +-spec start_link(SupName, Module, Args) -> startlink_ret() when + SupName :: sup_name(), + Module :: module(), + Args :: term(). start_link(SupName, Mod, Args) -> gen_server:start_link(SupName, supervisor, {SupName, Mod, Args}, []). %%% --------------------------------------------------- %%% Interface functions. %%% --------------------------------------------------- + +-type startchild_err() :: 'already_present' + | {'already_started', Child :: child()} | term(). +-type startchild_ret() :: {'ok', Child :: child()} + | {'ok', Child :: child(), Info :: term()} + | {'error', startchild_err()}. + +-spec start_child(SupRef, ChildSpec) -> startchild_ret() when + SupRef :: sup_ref(), + ChildSpec :: child_spec() | (List :: [term()]). start_child(Supervisor, ChildSpec) -> call(Supervisor, {start_child, ChildSpec}). +-spec restart_child(SupRef, Id) -> Result when + SupRef :: sup_ref(), + Id :: child_id(), + Result :: {'ok', Child :: child()} + | {'ok', Child :: child(), Info :: term()} + | {'error', Error}, + Error :: 'running' | 'not_found' | 'simple_one_for_one' | term(). restart_child(Supervisor, Name) -> call(Supervisor, {restart_child, Name}). +-spec delete_child(SupRef, Id) -> Result when + SupRef :: sup_ref(), + Id :: child_id(), + Result :: 'ok' | {'error', Error}, + Error :: 'running' | 'not_found' | 'simple_one_for_one'. delete_child(Supervisor, Name) -> call(Supervisor, {delete_child, Name}). @@ -89,18 +161,40 @@ delete_child(Supervisor, Name) -> %% Note that the child is *always* terminated in some %% way (maybe killed). %%----------------------------------------------------------------- + +-spec terminate_child(SupRef, Id) -> Result when + SupRef :: sup_ref(), + Id :: pid() | child_id(), + Result :: 'ok' | {'error', Error}, + Error :: 'not_found' | 'simple_one_for_one'. terminate_child(Supervisor, Name) -> call(Supervisor, {terminate_child, Name}). +-spec which_children(SupRef) -> [{Id,Child,Type,Modules}] when + SupRef :: sup_ref(), + Id :: child_id() | undefined, + Child :: child(), + Type :: worker(), + Modules :: modules(). which_children(Supervisor) -> call(Supervisor, which_children). +-spec count_children(SupRef) -> PropListOfCounts when + SupRef :: sup_ref(), + PropListOfCounts :: [Count], + Count :: {specs, ChildSpecCount :: non_neg_integer()} + | {active, ActiveProcessCount :: non_neg_integer()} + | {supervisors, ChildSupervisorCount :: non_neg_integer()} + |{workers, ChildWorkerCount :: non_neg_integer()}. count_children(Supervisor) -> call(Supervisor, count_children). call(Supervisor, Req) -> gen_server:call(Supervisor, Req, infinity). +-spec check_childspecs(ChildSpecs) -> Result when + ChildSpecs :: [child_spec()], + Result :: 'ok' | {'error', Error :: term()}. check_childspecs(ChildSpecs) when is_list(ChildSpecs) -> case check_startspec(ChildSpecs) of {ok, _} -> ok; @@ -113,6 +207,16 @@ check_childspecs(X) -> {error, {badarg, X}}. %%% Initialize the supervisor. %%% %%% --------------------------------------------------- + +-type init_sup_name() :: sup_name() | 'self'. + +-type stop_rsn() :: 'shutdown' | {'bad_return', {module(),'init', term()}} + | {'bad_start_spec', term()} | {'start_spec', term()} + | {'supervisor_data', term()}. + +-spec init({init_sup_name(), module(), [term()]}) -> + {'ok', state()} | 'ignore' | {'stop', stop_rsn()}. + init({SupName, Mod, Args}) -> process_flag(trap_exit, true), case Mod:init(Args) of @@ -130,7 +234,7 @@ init({SupName, Mod, Args}) -> Error -> {stop, {bad_return, {Mod, init, Error}}} end. - + init_children(State, StartSpec) -> SupName = State#state.name, case check_startspec(StartSpec) of @@ -158,12 +262,12 @@ init_dynamic(_State, StartSpec) -> %%----------------------------------------------------------------- %% Func: start_children/2 -%% Args: Children = [#child] in start order -%% SupName = {local, atom()} | {global, atom()} | {pid(),Mod} +%% Args: Children = [child_rec()] in start order +%% SupName = {local, atom()} | {global, atom()} | {pid(), Mod} %% Purpose: Start all children. The new list contains #child's %% with pids. %% Returns: {ok, NChildren} | {error, NChildren} -%% NChildren = [#child] in termination order (reversed +%% NChildren = [child_rec()] in termination order (reversed %% start order) %%----------------------------------------------------------------- start_children(Children, SupName) -> start_children(Children, [], SupName). @@ -182,8 +286,8 @@ start_children([], NChildren, _SupName) -> {ok, NChildren}. do_start_child(SupName, Child) -> - #child{mfa = {M, F, A}} = Child, - case catch apply(M, F, A) of + #child{mfargs = {M, F, Args}} = Child, + case catch apply(M, F, Args) of {ok, Pid} when is_pid(Pid) -> NChild = Child#child{pid = Pid}, report_progress(NChild, SupName), @@ -192,7 +296,7 @@ do_start_child(SupName, Child) -> NChild = Child#child{pid = Pid}, report_progress(NChild, SupName), {ok, Pid, Extra}; - ignore -> + ignore -> {ok, undefined}; {error, What} -> {error, What}; What -> {error, What} @@ -211,31 +315,50 @@ do_start_child_i(M, F, A) -> What -> {error, What} end. - %%% --------------------------------------------------- %%% %%% Callback functions. %%% %%% --------------------------------------------------- +-type call() :: 'which_children' | 'count_children' | {_, _}. % XXX: refine +-spec handle_call(call(), term(), state()) -> {'reply', term(), state()}. + handle_call({start_child, EArgs}, _From, State) when ?is_simple(State) -> - #child{mfa = {M, F, A}} = hd(State#state.children), + Child = hd(State#state.children), + #child{mfargs = {M, F, A}} = Child, Args = A ++ EArgs, case do_start_child_i(M, F, Args) of {ok, Pid} -> - NState = State#state{dynamics = - ?DICT:store(Pid, Args, State#state.dynamics)}, + NState = save_dynamic_child(Child#child.restart_type, Pid, Args, State), {reply, {ok, Pid}, NState}; {ok, Pid, Extra} -> - NState = State#state{dynamics = - ?DICT:store(Pid, Args, State#state.dynamics)}, + NState = save_dynamic_child(Child#child.restart_type, Pid, Args, State), {reply, {ok, Pid, Extra}, NState}; What -> {reply, What, State} end; -%%% The requests terminate_child, delete_child and restart_child are -%%% invalid for simple_one_for_one supervisors. +%% terminate_child for simple_one_for_one can only be done with pid +handle_call({terminate_child, Name}, _From, State) when not is_pid(Name), + ?is_simple(State) -> + {reply, {error, simple_one_for_one}, State}; + +handle_call({terminate_child, Name}, _From, State) -> + case get_child(Name, State, ?is_simple(State)) of + {value, Child} -> + case do_terminate(Child, State#state.name) of + #child{restart_type=RT} when RT=:=temporary; ?is_simple(State) -> + {reply, ok, state_del_child(Child, State)}; + NChild -> + {reply, ok, replace_child(NChild, State)} + end; + false -> + {reply, {error, not_found}, State} + end; + +%%% The requests delete_child and restart_child are invalid for +%%% simple_one_for_one supervisors. handle_call({_Req, _Data}, _From, State) when ?is_simple(State) -> {reply, {error, simple_one_for_one}, State}; @@ -278,37 +401,56 @@ handle_call({delete_child, Name}, _From, State) -> {reply, {error, not_found}, State} end; -handle_call({terminate_child, Name}, _From, State) -> - case get_child(Name, State) of - {value, Child} -> - NChild = do_terminate(Child, State#state.name), - {reply, ok, replace_child(NChild, State)}; - _ -> - {reply, {error, not_found}, State} - end; +handle_call(which_children, _From, #state{children = [#child{restart_type = temporary, + child_type = CT, + modules = Mods}]} = + State) when ?is_simple(State) -> + Reply = lists:map(fun(Pid) -> {undefined, Pid, CT, Mods} end, + ?SETS:to_list(dynamics_db(temporary, State#state.dynamics))), + {reply, Reply, State}; -handle_call(which_children, _From, State) when ?is_simple(State) -> - [#child{child_type = CT, modules = Mods}] = State#state.children, +handle_call(which_children, _From, #state{children = [#child{restart_type = RType, + child_type = CT, + modules = Mods}]} = + State) when ?is_simple(State) -> Reply = lists:map(fun({Pid, _}) -> {undefined, Pid, CT, Mods} end, - ?DICT:to_list(State#state.dynamics)), + ?DICT:to_list(dynamics_db(RType, State#state.dynamics))), {reply, Reply, State}; handle_call(which_children, _From, State) -> Resp = lists:map(fun(#child{pid = Pid, name = Name, child_type = ChildType, modules = Mods}) -> - {Name, Pid, ChildType, Mods} + {Name, Pid, ChildType, Mods} end, State#state.children), {reply, Resp, State}; -handle_call(count_children, _From, State) when ?is_simple(State) -> - [#child{child_type = CT}] = State#state.children, + +handle_call(count_children, _From, #state{children = [#child{restart_type = temporary, + child_type = CT}]} = State) + when ?is_simple(State) -> + {Active, Count} = + ?SETS:fold(fun(Pid, {Alive, Tot}) -> + if is_pid(Pid) -> {Alive+1, Tot +1}; + true -> {Alive, Tot + 1} end + end, {0, 0}, dynamics_db(temporary, State#state.dynamics)), + Reply = case CT of + supervisor -> [{specs, 1}, {active, Active}, + {supervisors, Count}, {workers, 0}]; + worker -> [{specs, 1}, {active, Active}, + {supervisors, 0}, {workers, Count}] + end, + {reply, Reply, State}; + +handle_call(count_children, _From, #state{children = [#child{restart_type = RType, + child_type = CT}]} = State) + when ?is_simple(State) -> {Active, Count} = ?DICT:fold(fun(Pid, _Val, {Alive, Tot}) -> if is_pid(Pid) -> {Alive+1, Tot +1}; true -> {Alive, Tot + 1} end - end, {0, 0}, State#state.dynamics), + end, {0, 0}, dynamics_db(RType, State#state.dynamics)), Reply = case CT of supervisor -> [{specs, 1}, {active, Active}, {supervisors, Count}, {workers, 0}]; @@ -318,7 +460,6 @@ handle_call(count_children, _From, State) when ?is_simple(State) -> {reply, Reply, State}; handle_call(count_children, _From, State) -> - %% Specs and children are together on the children list... {Specs, Active, Supers, Workers} = lists:foldl(fun(Child, Counts) -> @@ -347,15 +488,19 @@ count_child(#child{pid = Pid, child_type = supervisor}, %%% Hopefully cause a function-clause as there is no API function %%% that utilizes cast. +-spec handle_cast('null', state()) -> {'noreply', state()}. + handle_cast(null, State) -> error_logger:error_msg("ERROR: Supervisor received cast-message 'null'~n", []), - {noreply, State}. %% %% Take care of terminated children. %% +-spec handle_info(term(), state()) -> + {'noreply', state()} | {'stop', 'shutdown', state()}. + handle_info({'EXIT', Pid, Reason}, State) -> case restart_child(Pid, Reason, State) of {ok, State1} -> @@ -368,9 +513,12 @@ handle_info(Msg, State) -> error_logger:error_msg("Supervisor received unexpected message: ~p~n", [Msg]), {noreply, State}. + %% %% Terminate this server. %% +-spec terminate(term(), state()) -> 'ok'. + terminate(_Reason, State) -> terminate_children(State#state.children, State#state.name), ok. @@ -384,6 +532,9 @@ terminate(_Reason, State) -> %% NOTE: This requires that the init function of the call-back module %% does not have any side effects. %% +-spec code_change(term(), state(), term()) -> + {'ok', state()} | {'error', term()}. + code_change(_, State, _) -> case (State#state.module):init(State#state.args) of {ok, {SupFlags, StartSpec}} -> @@ -411,7 +562,7 @@ check_flags({Strategy, MaxIntensity, Period}) -> check_flags(What) -> {bad_flags, What}. -update_childspec(State, StartSpec) when ?is_simple(State) -> +update_childspec(State, StartSpec) when ?is_simple(State) -> case check_startspec(StartSpec) of {ok, [Child]} -> {ok, State#state{children = [Child]}}; @@ -437,7 +588,7 @@ update_childspec1([Child|OldC], Children, KeepOld) -> update_childspec1(OldC, Children, [Child|KeepOld]) end; update_childspec1([], Children, KeepOld) -> - % Return them in (keeped) reverse start order. + %% Return them in (kept) reverse start order. lists:reverse(Children ++ KeepOld). update_chsp(OldCh, Children) -> @@ -462,15 +613,11 @@ handle_start_child(Child, State) -> false -> case do_start_child(State#state.name, Child) of {ok, Pid} -> - Children = State#state.children, {{ok, Pid}, - State#state{children = - [Child#child{pid = Pid}|Children]}}; + save_child(Child#child{pid = Pid}, State)}; {ok, Pid, Extra} -> - Children = State#state.children, {{ok, Pid, Extra}, - State#state{children = - [Child#child{pid = Pid}|Children]}}; + save_child(Child#child{pid = Pid}, State)}; {error, What} -> {{error, {What, Child}}, State} end; @@ -482,27 +629,26 @@ handle_start_child(Child, State) -> %%% --------------------------------------------------- %%% Restart. A process has terminated. -%%% Returns: {ok, #state} | {shutdown, #state} +%%% Returns: {ok, state()} | {shutdown, state()} %%% --------------------------------------------------- -restart_child(Pid, Reason, State) when ?is_simple(State) -> - case ?DICT:find(Pid, State#state.dynamics) of +restart_child(Pid, Reason, #state{children = [Child]} = State) when ?is_simple(State) -> + RestartType = Child#child.restart_type, + case dynamic_child_args(Pid, dynamics_db(RestartType, State#state.dynamics)) of {ok, Args} -> - [Child] = State#state.children, - RestartType = Child#child.restart_type, - {M, F, _} = Child#child.mfa, - NChild = Child#child{pid = Pid, mfa = {M, F, Args}}, + {M, F, _} = Child#child.mfargs, + NChild = Child#child{pid = Pid, mfargs = {M, F, Args}}, do_restart(RestartType, Reason, NChild, State); error -> - {ok, State} + {ok, State} end; + restart_child(Pid, Reason, State) -> Children = State#state.children, - case lists:keysearch(Pid, #child.pid, Children) of - {value, Child} -> - RestartType = Child#child.restart_type, + case lists:keyfind(Pid, #child.pid, Children) of + #child{restart_type = RestartType} = Child -> do_restart(RestartType, Reason, Child, State); - _ -> + false -> {ok, State} end. @@ -534,8 +680,9 @@ restart(Child, State) -> end. restart(simple_one_for_one, Child, State) -> - #child{mfa = {M, F, A}} = Child, - Dynamics = ?DICT:erase(Child#child.pid, State#state.dynamics), + #child{mfargs = {M, F, A}} = Child, + Dynamics = ?DICT:erase(Child#child.pid, dynamics_db(Child#child.restart_type, + State#state.dynamics)), case do_start_child_i(M, F, A) of {ok, Pid} -> NState = State#state{dynamics = ?DICT:store(Pid, A, Dynamics)}, @@ -580,14 +727,21 @@ restart(one_for_all, Child, State) -> %%----------------------------------------------------------------- %% Func: terminate_children/2 -%% Args: Children = [#child] in termination order +%% Args: Children = [child_rec()] in termination order %% SupName = {local, atom()} | {global, atom()} | {pid(),Mod} -%% Returns: NChildren = [#child] in +%% Returns: NChildren = [child_rec()] in %% startup order (reversed termination order) %%----------------------------------------------------------------- terminate_children(Children, SupName) -> terminate_children(Children, SupName, []). +%% Temporary children should not be restarted and thus should +%% be skipped when building the list of terminated children, although +%% we do want them to be shut down as many functions from this module +%% use this function to just clear everything. +terminate_children([Child = #child{restart_type=temporary} | Children], SupName, Res) -> + do_terminate(Child, SupName), + terminate_children(Children, SupName, Res); terminate_children([Child | Children], SupName, Res) -> NChild = do_terminate(Child, SupName), terminate_children(Children, SupName, [NChild | Res]); @@ -595,14 +749,15 @@ terminate_children([], _SupName, Res) -> Res. do_terminate(Child, SupName) when Child#child.pid =/= undefined -> - case shutdown(Child#child.pid, - Child#child.shutdown) of - ok -> - Child#child{pid = undefined}; - {error, OtherReason} -> - report_error(shutdown_error, OtherReason, Child, SupName), - Child#child{pid = undefined} - end; + case shutdown(Child#child.pid, Child#child.shutdown) of + ok -> + ok; + {error, normal} when Child#child.restart_type =/= permanent -> + ok; + {error, OtherReason} -> + report_error(shutdown_error, OtherReason, Child, SupName) + end, + Child#child{pid = undefined}; do_terminate(Child, _SupName) -> Child. @@ -617,7 +772,6 @@ do_terminate(Child, _SupName) -> %% Returns: ok | {error, OtherReason} (this should be reported) %%----------------------------------------------------------------- shutdown(Pid, brutal_kill) -> - case monitor_child(Pid) of ok -> exit(Pid, kill), @@ -630,9 +784,7 @@ shutdown(Pid, brutal_kill) -> {error, Reason} -> {error, Reason} end; - shutdown(Pid, Time) -> - case monitor_child(Pid) of ok -> exit(Pid, shutdown), %% Try to shutdown gracefully @@ -684,15 +836,54 @@ monitor_child(Pid) -> %%----------------------------------------------------------------- %% Child/State manipulating functions. %%----------------------------------------------------------------- -state_del_child(#child{pid = Pid}, State) when ?is_simple(State) -> - NDynamics = ?DICT:erase(Pid, State#state.dynamics), + +%% Note we do not want to save the parameter list for temporary processes as +%% they will not be restarted, and hence we do not need this information. +%% Especially for dynamic children to simple_one_for_one supervisors +%% it could become very costly as it is not uncommon to spawn +%% very many such processes. +save_child(#child{restart_type = temporary, + mfargs = {M, F, _}} = Child, #state{children = Children} = State) -> + State#state{children = [Child#child{mfargs = {M, F, undefined}} |Children]}; +save_child(Child, #state{children = Children} = State) -> + State#state{children = [Child |Children]}. + +save_dynamic_child(temporary, Pid, _, #state{dynamics = Dynamics} = State) -> + State#state{dynamics = ?SETS:add_element(Pid, dynamics_db(temporary, Dynamics))}; +save_dynamic_child(RestartType, Pid, Args, #state{dynamics = Dynamics} = State) -> + State#state{dynamics = ?DICT:store(Pid, Args, dynamics_db(RestartType, Dynamics))}. + +dynamics_db(temporary, undefined) -> + ?SETS:new(); +dynamics_db(_, undefined) -> + ?DICT:new(); +dynamics_db(_,Dynamics) -> + Dynamics. + +dynamic_child_args(Pid, Dynamics) -> + case ?SETS:is_set(Dynamics) of + true -> + {ok, undefined}; + false -> + ?DICT:find(Pid, Dynamics) + end. + +state_del_child(#child{pid = Pid, restart_type = temporary}, State) when ?is_simple(State) -> + NDynamics = ?SETS:del_element(Pid, dynamics_db(temporary, State#state.dynamics)), + State#state{dynamics = NDynamics}; +state_del_child(#child{pid = Pid, restart_type = RType}, State) when ?is_simple(State) -> + NDynamics = ?DICT:erase(Pid, dynamics_db(RType, State#state.dynamics)), State#state{dynamics = NDynamics}; state_del_child(Child, State) -> NChildren = del_child(Child#child.name, State#state.children), State#state{children = NChildren}. +del_child(Name, [Ch|Chs]) when Ch#child.name =:= Name, Ch#child.restart_type =:= temporary -> + Chs; del_child(Name, [Ch|Chs]) when Ch#child.name =:= Name -> [Ch#child{pid = undefined} | Chs]; +del_child(Pid, [Ch|Chs]) when Ch#child.pid =:= Pid, Ch#child.restart_type =:= temporary -> + Chs; del_child(Pid, [Ch|Chs]) when Ch#child.pid =:= Pid -> [Ch#child{pid = undefined} | Chs]; del_child(Name, [Ch|Chs]) -> @@ -715,7 +906,31 @@ split_child(_, [], After) -> {lists:reverse(After), []}. get_child(Name, State) -> + get_child(Name, State, false). +get_child(Pid, State, AllowPid) when AllowPid, is_pid(Pid) -> + get_dynamic_child(Pid, State); +get_child(Name, State, _) -> lists:keysearch(Name, #child.name, State#state.children). + +get_dynamic_child(Pid, #state{children=[Child], dynamics=Dynamics}) -> + case is_dynamic_pid(Pid, dynamics_db(Child#child.restart_type, Dynamics)) of + true -> + {value, Child#child{pid=Pid}}; + false -> + case erlang:is_process_alive(Pid) of + true -> false; + false -> {value, Child} + end + end. + +is_dynamic_pid(Pid, Dynamics) -> + case ?SETS:is_set(Dynamics) of + true -> + ?SETS:is_element(Pid, Dynamics); + false -> + ?DICT:is_key(Pid, Dynamics) + end. + replace_child(Child, State) -> Chs = do_replace_child(Child, State#state.children), State#state{children = Chs}. @@ -738,9 +953,9 @@ remove_child(Child, State) -> %% MaxIntensity = integer() %% Period = integer() %% Mod :== atom() -%% Arsg :== term() +%% Args :== term() %% Purpose: Check that Type is of correct type (!) -%% Returns: {ok, #state} | Error +%% Returns: {ok, state()} | Error %%----------------------------------------------------------------- init_state(SupName, Type, Mod, Args) -> case catch init_state1(SupName, Type, Mod, Args) of @@ -755,11 +970,11 @@ init_state1(SupName, {Strategy, MaxIntensity, Period}, Mod, Args) -> validIntensity(MaxIntensity), validPeriod(Period), {ok, #state{name = supname(SupName,Mod), - strategy = Strategy, - intensity = MaxIntensity, - period = Period, - module = Mod, - args = Args}}; + strategy = Strategy, + intensity = MaxIntensity, + period = Period, + module = Mod, + args = Args}}; init_state1(_SupName, Type, _, _) -> {invalid_type, Type}. @@ -771,26 +986,26 @@ validStrategy(What) -> throw({invalid_strategy, What}). validIntensity(Max) when is_integer(Max), Max >= 0 -> true; -validIntensity(What) -> throw({invalid_intensity, What}). +validIntensity(What) -> throw({invalid_intensity, What}). validPeriod(Period) when is_integer(Period), Period > 0 -> true; validPeriod(What) -> throw({invalid_period, What}). -supname(self,Mod) -> {self(),Mod}; -supname(N,_) -> N. +supname(self, Mod) -> {self(), Mod}; +supname(N, _) -> N. %%% ------------------------------------------------------ %%% Check that the children start specification is valid. %%% Shall be a six (6) tuple %%% {Name, Func, RestartType, Shutdown, ChildType, Modules} %%% where Name is an atom -%%% Func is {Mod, Fun, Args} == {atom, atom, list} +%%% Func is {Mod, Fun, Args} == {atom(), atom(), list()} %%% RestartType is permanent | temporary | transient %%% Shutdown = integer() | infinity | brutal_kill %%% ChildType = supervisor | worker %%% Modules = [atom()] | dynamic -%%% Returns: {ok, [#child]} | Error +%%% Returns: {ok, [child_rec()]} | Error %%% ------------------------------------------------------ check_startspec(Children) -> check_startspec(Children, []). @@ -818,14 +1033,14 @@ check_childspec(Name, Func, RestartType, Shutdown, ChildType, Mods) -> validChildType(ChildType), validShutdown(Shutdown, ChildType), validMods(Mods), - {ok, #child{name = Name, mfa = Func, restart_type = RestartType, + {ok, #child{name = Name, mfargs = Func, restart_type = RestartType, shutdown = Shutdown, child_type = ChildType, modules = Mods}}. validChildType(supervisor) -> true; validChildType(worker) -> true; validChildType(What) -> throw({invalid_child_type, What}). -validName(_Name) -> true. +validName(_Name) -> true. validFunc({M, F, A}) when is_atom(M), is_atom(F), @@ -923,7 +1138,7 @@ report_error(Error, Reason, Child, SupName) -> extract_child(Child) -> [{pid, Child#child.pid}, {name, Child#child.name}, - {mfa, Child#child.mfa}, + {mfargs, Child#child.mfargs}, {restart_type, Child#child.restart_type}, {shutdown, Child#child.shutdown}, {child_type, Child#child.child_type}]. diff --git a/lib/stdlib/src/supervisor_bridge.erl b/lib/stdlib/src/supervisor_bridge.erl index 3d2bd2c9a5..555cb5a66f 100644 --- a/lib/stdlib/src/supervisor_bridge.erl +++ b/lib/stdlib/src/supervisor_bridge.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. +%% Copyright Ericsson AB 1996-2011. 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 @@ -49,9 +49,25 @@ behaviour_info(_Other) -> %%%----------------------------------------------------------------- -record(state, {mod, pid, child_state, name}). +-spec start_link(Module, Args) -> Result when + Module :: module(), + Args :: term(), + Result :: {ok, Pid} | ignore | {error, Error}, + Error :: {already_started, Pid} | term(), + Pid :: pid(). + start_link(Mod, StartArgs) -> gen_server:start_link(supervisor_bridge, [Mod, StartArgs, self], []). +-spec start_link(SupBridgeName, Module, Args) -> Result when + SupBridgeName :: {local, Name} | {global, Name}, + Name :: atom(), + Module :: module(), + Args :: term(), + Result :: {ok, Pid} | ignore | {error, Error}, + Error :: {already_started, Pid} | term(), + Pid :: pid(). + start_link(Name, Mod, StartArgs) -> gen_server:start_link(Name, supervisor_bridge, [Mod, StartArgs, Name], []). diff --git a/lib/stdlib/src/sys.erl b/lib/stdlib/src/sys.erl index 12209c16d7..f34201604c 100644 --- a/lib/stdlib/src/sys.erl +++ b/lib/stdlib/src/sys.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. +%% Copyright Ericsson AB 1996-2011. 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,22 +33,74 @@ %%----------------------------------------------------------------- -type name() :: pid() | atom() | {'global', atom()}. --type system_event() :: {'in', _Msg} | {'in', _Msg, _From} | {'out', _Msg, _To}. +-type system_event() :: {'in', Msg :: _} + | {'in', Msg :: _, From :: _} + | {'out', Msg :: _, To :: _} + | term(). +-opaque dbg_opt() :: list(). +-type dbg_fun() :: fun((FuncState :: _, + Event :: system_event(), + ProcState :: _) -> 'done' | (NewFuncState :: _)). %%----------------------------------------------------------------- %% System messages %%----------------------------------------------------------------- +-spec suspend(Name) -> Void when + Name :: name(), + Void :: term(). suspend(Name) -> send_system_msg(Name, suspend). +-spec suspend(Name, Timeout) -> Void when + Name :: name(), + Timeout :: timeout(), + Void :: term(). suspend(Name, Timeout) -> send_system_msg(Name, suspend, Timeout). +-spec resume(Name) -> Void when + Name :: name(), + Void :: term(). resume(Name) -> send_system_msg(Name, resume). +-spec resume(Name, Timeout) -> Void when + Name :: name(), + Timeout :: timeout(), + Void :: term(). resume(Name, Timeout) -> send_system_msg(Name, resume, Timeout). +-spec get_status(Name) -> Status when + Name :: name(), + Status :: {status, Pid :: pid(), {module, Module :: module()}, [SItem]}, + SItem :: (PDict :: [{Key :: term(), Value :: term()}]) + | (SysState :: 'running' | 'suspended') + | (Parent :: pid()) + | (Dbg :: dbg_opt()) + | (Misc :: term()). get_status(Name) -> send_system_msg(Name, get_status). +-spec get_status(Name, Timeout) -> Status when + Name :: name(), + Timeout :: timeout(), + Status :: {status, Pid :: pid(), {module, Module :: module()}, [SItem]}, + SItem :: (PDict :: [{Key :: term(), Value :: term()}]) + | (SysState :: 'running' | 'suspended') + | (Parent :: pid()) + | (Dbg :: dbg_opt()) + | (Misc :: term()). get_status(Name, Timeout) -> send_system_msg(Name, get_status, Timeout). +-spec change_code(Name, Module, OldVsn, Extra) -> 'ok' | {error, Reason} when + Name :: name(), + Module :: module(), + OldVsn :: 'undefined' | term(), + Extra :: term(), + Reason :: term(). change_code(Name, Mod, Vsn, Extra) -> send_system_msg(Name, {change_code, Mod, Vsn, Extra}). +-spec change_code(Name, Module, OldVsn, Extra, Timeout) -> + 'ok' | {error, Reason} when + Name :: name(), + Module :: module(), + OldVsn :: 'undefined' | term(), + Extra :: term(), + Timeout :: timeout(), + Reason :: term(). change_code(Name, Mod, Vsn, Extra, Timeout) -> send_system_msg(Name, {change_code, Mod, Vsn, Extra}, Timeout). @@ -56,52 +108,116 @@ change_code(Name, Mod, Vsn, Extra, Timeout) -> %% Debug commands %%----------------------------------------------------------------- --type log_flag() :: 'true' | {'true',pos_integer()} | 'false' | 'get' | 'print'. - --spec log(name(), log_flag()) -> 'ok' | {'ok', [system_event()]}. +-spec log(Name, Flag) -> 'ok' | {'ok', [system_event()]} when + Name :: name(), + Flag :: 'true' | + {'true', N :: pos_integer()} + | 'false' | 'get' | 'print'. log(Name, Flag) -> send_system_msg(Name, {debug, {log, Flag}}). --spec log(name(), log_flag(), timeout()) -> 'ok' | {'ok', [system_event()]}. +-spec log(Name, Flag, Timeout) -> 'ok' | {'ok', [system_event()]} when + Name :: name(), + Flag :: 'true' | + {'true', N :: pos_integer()} + | 'false' | 'get' | 'print', + Timeout :: timeout(). log(Name, Flag, Timeout) -> send_system_msg(Name, {debug, {log, Flag}}, Timeout). --spec trace(name(), boolean()) -> 'ok'. +-spec trace(Name, Flag) -> 'ok' when + Name :: name(), + Flag :: boolean(). trace(Name, Flag) -> send_system_msg(Name, {debug, {trace, Flag}}). --spec trace(name(), boolean(), timeout()) -> 'ok'. +-spec trace(Name, Flag, Timeout) -> 'ok' when + Name :: name(), + Flag :: boolean(), + Timeout :: timeout(). trace(Name, Flag, Timeout) -> send_system_msg(Name, {debug, {trace, Flag}}, Timeout). --type l2f_fname() :: string() | 'false'. - --spec log_to_file(name(), l2f_fname()) -> 'ok' | {'error','open_file'}. +-spec log_to_file(Name, Flag) -> 'ok' | {'error','open_file'} when + Name :: name(), + Flag :: (FileName :: string()) | 'false'. log_to_file(Name, FileName) -> send_system_msg(Name, {debug, {log_to_file, FileName}}). --spec log_to_file(name(), l2f_fname(), timeout()) -> 'ok' | {'error','open_file'}. +-spec log_to_file(Name, Flag, Timeout) -> 'ok' | {'error','open_file'} when + Name :: name(), + Flag :: (FileName :: string()) | 'false', + Timeout :: timeout(). log_to_file(Name, FileName, Timeout) -> send_system_msg(Name, {debug, {log_to_file, FileName}}, Timeout). +-spec statistics(Name, Flag) -> 'ok' | {'ok', Statistics} when + Name :: name(), + Flag :: 'true' | 'false' | 'get', + Statistics :: [StatisticsTuple] | no_statistics, + StatisticsTuple :: {'start_time', DateTime1} + | {'current_time', DateTime2} + | {'reductions', non_neg_integer()} + | {'messages_in', non_neg_integer()} + | {'messages_out', non_neg_integer()}, + DateTime1 :: file:date_time(), + DateTime2 :: file:date_time(). statistics(Name, Flag) -> send_system_msg(Name, {debug, {statistics, Flag}}). + +-spec statistics(Name, Flag, Timeout) -> 'ok' | {'ok', Statistics} when + Name :: name(), + Flag :: 'true' | 'false' | 'get', + Statistics :: [StatisticsTuple] | no_statistics, + StatisticsTuple :: {'start_time', DateTime1} + | {'current_time', DateTime2} + | {'reductions', non_neg_integer()} + | {'messages_in', non_neg_integer()} + | {'messages_out', non_neg_integer()}, + DateTime1 :: file:date_time(), + DateTime2 :: file:date_time(), + Timeout :: timeout(). statistics(Name, Flag, Timeout) -> send_system_msg(Name, {debug, {statistics, Flag}}, Timeout). --spec no_debug(name()) -> 'ok'. +-spec no_debug(Name) -> 'ok' when + Name :: name(). no_debug(Name) -> send_system_msg(Name, {debug, no_debug}). --spec no_debug(name(), timeout()) -> 'ok'. +-spec no_debug(Name, Timeout) -> 'ok' when + Name :: name(), + Timeout :: timeout(). no_debug(Name, Timeout) -> send_system_msg(Name, {debug, no_debug}, Timeout). +-spec install(Name, FuncSpec) -> Void when + Name :: name(), + FuncSpec :: {Func, FuncState}, + Func :: dbg_fun(), + FuncState :: term(), + Void :: term(). install(Name, {Func, FuncState}) -> send_system_msg(Name, {debug, {install, {Func, FuncState}}}). +-spec install(Name, FuncSpec, Timeout) -> Void when + Name :: name(), + FuncSpec :: {Func, FuncState}, + Func :: dbg_fun(), + FuncState :: term(), + Timeout :: timeout(), + Void :: term(). install(Name, {Func, FuncState}, Timeout) -> send_system_msg(Name, {debug, {install, {Func, FuncState}}}, Timeout). +-spec remove(Name, Func) -> Void when + Name :: name(), + Func :: dbg_fun(), + Void :: term(). remove(Name, Func) -> send_system_msg(Name, {debug, {remove, Func}}). +-spec remove(Name, Func, Timeout) -> Void when + Name :: name(), + Func :: dbg_fun(), + Timeout :: timeout(), + Void :: term(). remove(Name, Func, Timeout) -> send_system_msg(Name, {debug, {remove, Func}}, Timeout). @@ -150,6 +266,14 @@ mfa(Name, Req, Timeout) -> %% The Module must export system_continue/3, system_terminate/4 %% and format_status/2 for status information. %%----------------------------------------------------------------- +-spec handle_system_msg(Msg, From, Parent, Module, Debug, Misc) -> Void when + Msg :: term(), + From :: {pid(), Tag :: _}, + Parent :: pid(), + Module :: module(), + Debug :: [dbg_opt()], + Misc :: term(), + Void :: term(). handle_system_msg(Msg, From, Parent, Module, Debug, Misc) -> handle_system_msg(running, Msg, From, Parent, Module, Debug, Misc, false). @@ -176,6 +300,11 @@ handle_system_msg(SysState, Msg, From, Parent, Mod, Debug, Misc, Hib) -> %% Func is a formatting function, called as Func(Device, Event). %% Returns: [debug_opts()] %%----------------------------------------------------------------- +-spec handle_debug(Debug, FormFunc, Extra, Event) -> [dbg_opt()] when + Debug :: [dbg_opt()], + FormFunc :: dbg_fun(), + Extra :: term(), + Event :: system_event(). handle_debug([{trace, true} | T], FormFunc, State, Event) -> print_event({Event, State, FormFunc}), [{trace, true} | handle_debug(T, FormFunc, State, Event)]; @@ -341,24 +470,36 @@ trim(N, LogData) -> %% Debug structure manipulating functions %%----------------------------------------------------------------- install_debug(Item, Data, Debug) -> - case get_debug(Item, Debug, undefined) of + case get_debug2(Item, Debug, undefined) of undefined -> [{Item, Data} | Debug]; _ -> Debug end. remove_debug(Item, Debug) -> lists:keydelete(Item, 1, Debug). + +-spec get_debug(Item, Debug, Default) -> term() when + Item :: 'log' | 'statistics', + Debug :: [dbg_opt()], + Default :: term(). get_debug(Item, Debug, Default) -> + get_debug2(Item, Debug, Default). + +%% Workaround: accepts more Item types than get_debug/3. +get_debug2(Item, Debug, Default) -> case lists:keysearch(Item, 1, Debug) of {value, {Item, Data}} -> Data; _ -> Default end. +-spec print_log(Debug) -> Void when + Debug :: [dbg_opt()], + Void :: term(). print_log(Debug) -> {_N, Logs} = get_debug(log, Debug, {0, []}), lists:foreach(fun print_event/1, lists:reverse(Logs)). close_log_file(Debug) -> - case get_debug(log_to_file, Debug, []) of + case get_debug2(log_to_file, Debug, []) of [] -> Debug; Fd -> @@ -375,6 +516,15 @@ close_log_file(Debug) -> %% system messages. %% Returns: [debug_opts()] %%----------------------------------------------------------------- + +-spec debug_options(Options) -> [dbg_opt()] when + Options :: [Opt], + Opt :: 'trace' | 'log' | 'statistics' | {'log_to_file', FileName} + | {'install', FuncSpec}, + FileName :: file:name(), + FuncSpec :: {Func, FuncState}, + Func :: dbg_fun(), + FuncState :: term(). debug_options(Options) -> debug_options(Options, []). debug_options([trace | T], Debug) -> diff --git a/lib/stdlib/src/timer.erl b/lib/stdlib/src/timer.erl index 36fdb48c75..689e42051f 100644 --- a/lib/stdlib/src/timer.erl +++ b/lib/stdlib/src/timer.erl @@ -1,19 +1,19 @@ %% %% %CopyrightBegin% -%% -%% Copyright Ericsson AB 1996-2009. All Rights Reserved. -%% +%% +%% Copyright Ericsson AB 1996-2011. 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 %% compliance with the License. You should have received a copy of the %% Erlang Public License along with this software. If not, it can be %% retrieved online at http://www.erlang.org/. -%% +%% %% Software distributed under the License is distributed on an "AS IS" %% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See %% the License for the specific language governing rights and limitations %% under the License. -%% +%% %% %CopyrightEnd% %% -module(timer). @@ -22,7 +22,7 @@ send_after/3, send_after/2, exit_after/3, exit_after/2, kill_after/2, kill_after/1, apply_interval/4, send_interval/3, send_interval/2, - cancel/1, sleep/1, tc/3, now_diff/2, + cancel/1, sleep/1, tc/1, tc/2, tc/3, now_diff/2, seconds/1, minutes/1, hours/1, hms/3]). -export([start_link/0, start/0, @@ -33,6 +33,9 @@ %% internal exports for test purposes only -export([get_status/0]). +%% types which can be used by other modules +-export_type([tref/0]). + %% Max -define(MAX_TIMEOUT, 16#0800000). -define(TIMER_TAB, timer_tab). @@ -41,94 +44,191 @@ %% %% Time is in milliseconds. %% --opaque tref() :: any(). +-opaque tref() :: {integer(), reference()}. -type time() :: non_neg_integer(). --type timestamp() :: {non_neg_integer(), non_neg_integer(), non_neg_integer()}. %% %% Interface functions %% --spec apply_after(time(), atom(), atom(), [_]) -> {'ok', tref()} | {'error', _}. +-spec apply_after(Time, Module, Function, Arguments) -> + {'ok', TRef} | {'error', Reason} when + Time :: time(), + Module :: module(), + Function :: atom(), + Arguments :: [term()], + TRef :: tref(), + Reason :: term(). + apply_after(Time, M, F, A) -> req(apply_after, {Time, {M, F, A}}). --spec send_after(time(), pid() | atom(), term()) -> {'ok', tref()} | {'error', _}. +-spec send_after(Time, Pid, Message) -> {'ok', TRef} | {'error', Reason} when + Time :: time(), + Pid :: pid() | (RegName :: atom()), + Message :: term(), + TRef :: tref(), + Reason :: term(). send_after(Time, Pid, Message) -> req(apply_after, {Time, {?MODULE, send, [Pid, Message]}}). --spec send_after(time(), _) -> {'ok', tref()} | {'error', _}. +-spec send_after(Time, Message) -> {'ok', TRef} | {'error', Reason} when + Time :: time(), + Message :: term(), + TRef :: tref(), + Reason :: term(). send_after(Time, Message) -> send_after(Time, self(), Message). --spec exit_after(time(), pid() | atom(), _) -> {'ok', tref()} | {'error', _}. +-spec exit_after(Time, Pid, Reason1) -> {'ok', TRef} | {'error', Reason2} when + Time :: time(), + Pid :: pid() | (RegName :: atom()), + TRef :: tref(), + Reason1 :: term(), + Reason2 :: term(). exit_after(Time, Pid, Reason) -> req(apply_after, {Time, {erlang, exit, [Pid, Reason]}}). --spec exit_after(time(), term()) -> {'ok', tref()} | {'error', _}. +-spec exit_after(Time, Reason1) -> {'ok', TRef} | {'error', Reason2} when + Time :: time(), + TRef :: tref(), + Reason1 :: term(), + Reason2 :: term(). exit_after(Time, Reason) -> exit_after(Time, self(), Reason). --spec kill_after(time(), pid() | atom()) -> {'ok', tref()} | {'error', _}. +-spec kill_after(Time, Pid) -> {'ok', TRef} | {'error', Reason2} when + Time :: time(), + Pid :: pid() | (RegName :: atom()), + TRef :: tref(), + Reason2 :: term(). kill_after(Time, Pid) -> exit_after(Time, Pid, kill). --spec kill_after(time()) -> {'ok', tref()} | {'error', _}. +-spec kill_after(Time) -> {'ok', TRef} | {'error', Reason2} when + Time :: time(), + TRef :: tref(), + Reason2 :: term(). kill_after(Time) -> exit_after(Time, self(), kill). --spec apply_interval(time(), atom(), atom(), [_]) -> {'ok', tref()} | {'error', _}. +-spec apply_interval(Time, Module, Function, Arguments) -> + {'ok', TRef} | {'error', Reason} when + Time :: time(), + Module :: module(), + Function :: atom(), + Arguments :: [term()], + TRef :: tref(), + Reason :: term(). apply_interval(Time, M, F, A) -> req(apply_interval, {Time, self(), {M, F, A}}). --spec send_interval(time(), pid() | atom(), term()) -> {'ok', tref()} | {'error', _}. +-spec send_interval(Time, Pid, Message) -> + {'ok', TRef} | {'error', Reason} when + Time :: time(), + Pid :: pid() | (RegName :: atom()), + Message :: term(), + TRef :: tref(), + Reason :: term(). send_interval(Time, Pid, Message) -> req(apply_interval, {Time, Pid, {?MODULE, send, [Pid, Message]}}). --spec send_interval(time(), term()) -> {'ok', tref()} | {'error', _}. +-spec send_interval(Time, Message) -> {'ok', TRef} | {'error', Reason} when + Time :: time(), + Message :: term(), + TRef :: tref(), + Reason :: term(). send_interval(Time, Message) -> send_interval(Time, self(), Message). --spec cancel(tref()) -> {'ok', 'cancel'} | {'error', _}. +-spec cancel(TRef) -> {'ok', 'cancel'} | {'error', Reason} when + TRef :: tref(), + Reason :: term(). cancel(BRef) -> req(cancel, BRef). --spec sleep(timeout()) -> 'ok'. +-spec sleep(Time) -> 'ok' when + Time :: timeout(). sleep(T) -> receive after T -> ok end. %% +%% Measure the execution time (in microseconds) for Fun(). +%% +-spec tc(Fun) -> {Time, Value} when + Fun :: function(), + Time :: integer(), + Value :: term(). +tc(F) -> + Before = os:timestamp(), + Val = F(), + After = os:timestamp(), + {now_diff(After, Before), Val}. + +%% +%% Measure the execution time (in microseconds) for Fun(Args). +%% +-spec tc(Fun, Arguments) -> {Time, Value} when + Fun :: function(), + Arguments :: [term()], + Time :: integer(), + Value :: term(). +tc(F, A) -> + Before = os:timestamp(), + Val = apply(F, A), + After = os:timestamp(), + {now_diff(After, Before), Val}. + +%% %% Measure the execution time (in microseconds) for an MFA. %% --spec tc(atom(), atom(), [_]) -> {time(), term()}. +-spec tc(Module, Function, Arguments) -> {Time, Value} when + Module :: module(), + Function :: atom(), + Arguments :: [term()], + Time :: integer(), + Value :: term(). tc(M, F, A) -> - Before = erlang:now(), - Val = (catch apply(M, F, A)), - After = erlang:now(), + Before = os:timestamp(), + Val = apply(M, F, A), + After = os:timestamp(), {now_diff(After, Before), Val}. %% %% Calculate the time difference (in microseconds) of two %% erlang:now() timestamps, T2-T1. %% --spec now_diff(timestamp(), timestamp()) -> integer(). +-spec now_diff(T2, T1) -> Tdiff when + T1 :: erlang:timestamp(), + T2 :: erlang:timestamp(), + Tdiff :: integer(). now_diff({A2, B2, C2}, {A1, B1, C1}) -> ((A2-A1)*1000000 + B2-B1)*1000000 + C2-C1. %% %% Convert seconds, minutes etc. to milliseconds. %% --spec seconds(non_neg_integer()) -> non_neg_integer(). +-spec seconds(Seconds) -> MilliSeconds when + Seconds :: non_neg_integer(), + MilliSeconds :: non_neg_integer(). seconds(Seconds) -> 1000*Seconds. --spec minutes(non_neg_integer()) -> non_neg_integer(). +-spec minutes(Minutes) -> MilliSeconds when + Minutes :: non_neg_integer(), + MilliSeconds :: non_neg_integer(). minutes(Minutes) -> 1000*60*Minutes. --spec hours(non_neg_integer()) -> non_neg_integer(). +-spec hours(Hours) -> MilliSeconds when + Hours :: non_neg_integer(), + MilliSeconds :: non_neg_integer(). hours(Hours) -> 1000*60*60*Hours. --spec hms(non_neg_integer(), non_neg_integer(), non_neg_integer()) -> non_neg_integer(). +-spec hms(Hours, Minutes, Seconds) -> MilliSeconds when + Hours :: non_neg_integer(), + Minutes :: non_neg_integer(), + Seconds :: non_neg_integer(), + MilliSeconds :: non_neg_integer(). hms(H, M, S) -> hours(H) + minutes(M) + seconds(S). @@ -141,7 +241,7 @@ hms(H, M, S) -> start() -> ensure_started(). --spec start_link() -> {'ok', pid()} | {'error', _}. +-spec start_link() -> {'ok', pid()} | {'error', term()}. start_link() -> gen_server:start_link({local, timer_server}, ?MODULE, [], []). @@ -152,6 +252,7 @@ init([]) -> ?INTERVAL_TAB = ets:new(?INTERVAL_TAB, [named_table,protected]), {ok, [], infinity}. +-spec ensure_started() -> 'ok'. ensure_started() -> case whereis(timer_server) of undefined -> @@ -175,6 +276,10 @@ req(Req, Arg) -> %% %% Time and Timeout is in milliseconds. Started is in microseconds. %% +-type timers() :: term(). % XXX: refine? + +-spec handle_call(term(), term(), timers()) -> + {'reply', term(), timers(), timeout()} | {'noreply', timers(), timeout()}. handle_call({apply_after, {Time, Op}, Started}, _From, _Ts) when is_integer(Time), Time >= 0 -> BRef = {Started + 1000*Time, make_ref()}, @@ -194,7 +299,7 @@ handle_call({apply_interval, {Time, To, MFA}, Started}, _From, _Ts) Interval = Time*1000, BRef2 = {Started + Interval, Ref}, Timer = {BRef2, {repeat, Interval, Pid}, MFA}, - ets:insert(?INTERVAL_TAB,{BRef1,BRef2,Pid}), + ets:insert(?INTERVAL_TAB, {BRef1,BRef2,Pid}), ets:insert(?TIMER_TAB, Timer), Timeout = timer_timeout(SysTime), {reply, {ok, BRef1}, [], Timeout}; @@ -202,7 +307,7 @@ handle_call({apply_interval, {Time, To, MFA}, Started}, _From, _Ts) {reply, {error, badarg}, [], next_timeout()} end; handle_call({cancel, BRef = {_Time, Ref}, _}, _From, Ts) - when is_reference(Ref) -> + when is_reference(Ref) -> delete_ref(BRef), {reply, {ok, cancel}, Ts, next_timeout()}; handle_call({cancel, _BRef, _}, _From, Ts) -> @@ -214,6 +319,7 @@ handle_call({apply_interval, _, _}, _From, Ts) -> handle_call(_Else, _From, Ts) -> % Catch anything else {noreply, Ts, next_timeout()}. +-spec handle_info(term(), timers()) -> {'noreply', timers(), timeout()}. handle_info(timeout, Ts) -> % Handle timeouts Timeout = timer_timeout(system_time()), {noreply, Ts, Timeout}; @@ -223,19 +329,21 @@ handle_info({'EXIT', Pid, _Reason}, Ts) -> % Oops, someone died handle_info(_OtherMsg, Ts) -> % Other Msg's {noreply, Ts, next_timeout()}. +-spec handle_cast(term(), timers()) -> {'noreply', timers(), timeout()}. handle_cast(_Req, Ts) -> % Not predicted but handled {noreply, Ts, next_timeout()}. --spec terminate(_, _) -> 'ok'. +-spec terminate(term(), _State) -> 'ok'. terminate(_Reason, _State) -> ok. +-spec code_change(term(), State, term()) -> {'ok', State}. code_change(_OldVsn, State, _Extra) -> %% According to the man for gen server no timer can be set here. {ok, State}. %% -%% timer_timeout(Timers, SysTime) +%% timer_timeout(SysTime) %% %% Apply and remove already timed-out timers. A timer is a tuple %% {Time, BRef, Op, MFA}, where Time is in microseconds. @@ -279,12 +387,13 @@ delete_ref(BRef = {interval, _}) -> ok end; delete_ref(BRef) -> - ets:delete(?TIMER_TAB,BRef). + ets:delete(?TIMER_TAB, BRef). %% %% pid_delete %% +-spec pid_delete(pid()) -> 'ok'. pid_delete(Pid) -> IntervalTimerList = ets:select(?INTERVAL_TAB, @@ -292,13 +401,14 @@ pid_delete(Pid) -> [{'==','$1',Pid}], ['$_']}]), lists:foreach(fun({IntKey, TimerKey, _ }) -> - ets:delete(?INTERVAL_TAB,IntKey), - ets:delete(?TIMER_TAB,TimerKey) + ets:delete(?INTERVAL_TAB, IntKey), + ets:delete(?TIMER_TAB, TimerKey) end, IntervalTimerList). %% Calculate time to the next timeout. Returned timeout must fit in a %% small int. +-spec next_timeout() -> timeout(). next_timeout() -> case ets:first(?TIMER_TAB) of '$end_of_table' -> @@ -358,7 +468,7 @@ get_pid(_) -> get_status() -> Info1 = ets:info(?TIMER_TAB), - {value,{size,TotalNumTimers}} = lists:keysearch(size, 1, Info1), + {size,TotalNumTimers} = lists:keyfind(size, 1, Info1), Info2 = ets:info(?INTERVAL_TAB), - {value,{size,NumIntervalTimers}} = lists:keysearch(size, 1, Info2), + {size,NumIntervalTimers} = lists:keyfind(size, 1, Info2), {{?TIMER_TAB,TotalNumTimers},{?INTERVAL_TAB,NumIntervalTimers}}. diff --git a/lib/stdlib/src/unicode.erl b/lib/stdlib/src/unicode.erl index 09b1deff9c..a5d9965ca2 100644 --- a/lib/stdlib/src/unicode.erl +++ b/lib/stdlib/src/unicode.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2008-2009. All Rights Reserved. +%% Copyright Ericsson AB 2008-2011. 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 @@ -25,8 +25,39 @@ %% 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,bom_to_encoding/1, encoding_to_bom/1]). - +-export([characters_to_list/1, characters_to_list_int/2, + characters_to_binary/1, characters_to_binary_int/2, + characters_to_binary/3, + bom_to_encoding/1, encoding_to_bom/1]). + +-export_type([chardata/0, charlist/0, encoding/0, external_chardata/0, + external_charlist/0, latin1_chardata/0, + latin1_charlist/0, unicode_binary/0, unicode_char/0]). + +-type encoding() :: 'latin1' | 'unicode' | 'utf8' + | 'utf16' | {'utf16', endian()} + | 'utf32' | {'utf32', endian()}. +-type endian() :: 'big' | 'little'. +-type unicode_binary() :: binary(). +-type unicode_char() :: non_neg_integer(). +-type charlist() :: [unicode_char() | unicode_binary() | charlist()]. +-type chardata() :: charlist() | unicode_binary(). +-type external_unicode_binary() :: binary(). +-type external_chardata() :: external_charlist() | external_unicode_binary(). +-type external_charlist() :: [unicode_char() | external_unicode_binary() + | external_charlist()]. +-type latin1_binary() :: binary(). +-type latin1_char() :: byte(). +-type latin1_chardata() :: latin1_charlist() | latin1_binary(). +-type latin1_charlist() :: [latin1_char() | latin1_binary() + | latin1_charlist()]. + +-spec characters_to_list(Data) -> Result when + Data :: latin1_chardata() | chardata() | external_chardata(), + Result :: list() + | {error, list(), RestData} + | {incomplete, list(), binary()}, + RestData :: latin1_chardata() | chardata() | external_chardata(). characters_to_list(ML) -> unicode:characters_to_list(ML,unicode). @@ -60,6 +91,13 @@ do_characters_to_list(ML, Encoding) -> end. +-spec characters_to_binary(Data) -> Result when + Data :: latin1_chardata() | chardata() | external_chardata(), + Result :: binary() + | {error, binary(), RestData} + | {incomplete, binary(), binary()}, + RestData :: latin1_chardata() | chardata() | external_chardata(). + characters_to_binary(ML) -> try unicode:characters_to_binary(ML,unicode) @@ -95,6 +133,15 @@ characters_to_binary_int(ML,InEncoding) -> erlang:raise(error,TheError,[{Mod,characters_to_binary,L}|Rest]) end. +-spec characters_to_binary(Data, InEncoding, OutEncoding) -> Result when + Data :: latin1_chardata() | chardata() | external_chardata(), + InEncoding :: encoding(), + OutEncoding :: encoding(), + Result :: binary() + | {error, binary(), RestData} + | {incomplete, binary(), binary()}, + RestData :: latin1_chardata() | chardata() | external_chardata(). + characters_to_binary(ML, latin1, latin1) when is_binary(ML) -> ML; characters_to_binary(ML, latin1, Uni) when is_binary(ML) and ((Uni =:= utf8) or (Uni =:= unicode)) -> @@ -206,6 +253,13 @@ characters_to_binary_int(ML, InEncoding, OutEncoding) -> Res end. +-spec bom_to_encoding(Bin) -> {Encoding, Length} when + Bin :: binary(), + Encoding :: 'latin1' | 'utf8' + | {'utf16', endian()} + | {'utf32', endian()}, + Length :: non_neg_integer(). + bom_to_encoding(<<239,187,191,_/binary>>) -> {utf8,3}; bom_to_encoding(<<0,0,254,255,_/binary>>) -> @@ -219,6 +273,10 @@ bom_to_encoding(<<255,254,_/binary>>) -> bom_to_encoding(Bin) when is_binary(Bin) -> {latin1,0}. +-spec encoding_to_bom(InEncoding) -> Bin when + Bin :: binary(), + InEncoding :: encoding(). + encoding_to_bom(unicode) -> <<239,187,191>>; encoding_to_bom(utf8) -> diff --git a/lib/stdlib/src/win32reg.erl b/lib/stdlib/src/win32reg.erl index ee0d17bc94..598e77ffdc 100644 --- a/lib/stdlib/src/win32reg.erl +++ b/lib/stdlib/src/win32reg.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1997-2009. All Rights Reserved. +%% Copyright Ericsson AB 1997-2011. 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 @@ -52,14 +52,17 @@ -define(reg_dword, 4). %% Basic types internal to this file. --type open_mode() :: 'read' | 'write'. --type reg_handle() :: {'win32reg',port()}. +-opaque reg_handle() :: {'win32reg',port()}. -type name() :: string() | 'default'. -type value() :: string() | integer() | binary(). %%% Exported functions. --spec open([open_mode()]) -> {'ok', reg_handle()} | {'error', 'enotsup'}. +-spec open(OpenModeList) -> ReturnValue when + OpenModeList :: [OpenMode], + OpenMode :: 'read' | 'write', + ReturnValue :: {'ok', RegHandle} | {'error', ErrorId :: 'enotsup'}, + RegHandle :: reg_handle(). open(Modes) -> case os:type() of @@ -75,14 +78,17 @@ open(Modes) -> {error, enotsup} end. --spec close(reg_handle()) -> 'ok'. +-spec close(RegHandle) -> 'ok' when + RegHandle :: reg_handle(). close({win32reg, Reg}) when is_port(Reg) -> unlink(Reg), exit(Reg, die), ok. --spec current_key(reg_handle()) -> {'ok', string()}. +-spec current_key(RegHandle) -> ReturnValue when + RegHandle :: reg_handle(), + ReturnValue :: {'ok', string()}. current_key({win32reg, Reg}) when is_port(Reg) -> Cmd = [?cmd_get_current], @@ -94,12 +100,18 @@ current_key({win32reg, Reg}) when is_port(Reg) -> _ -> Root ++ [$\\|Name] end}. --spec change_key(reg_handle(), string()) -> 'ok' | {'error', atom()}. +-spec change_key(RegHandle, Key) -> ReturnValue when + RegHandle :: reg_handle(), + Key :: string(), + ReturnValue :: 'ok' | {'error', ErrorId :: atom()}. change_key({win32reg, Reg}, Key) when is_port(Reg) -> change_key(Reg, ?cmd_open_key, Key). --spec change_key_create(reg_handle(), string()) -> 'ok' | {'error', atom()}. +-spec change_key_create(RegHandle, Key) -> ReturnValue when + RegHandle :: reg_handle(), + Key :: string(), + ReturnValue :: 'ok' | {'error', ErrorId :: atom()}. change_key_create({win32reg, Reg}, Key) when is_port(Reg) -> change_key(Reg, ?cmd_create_key, Key). @@ -113,21 +125,30 @@ change_key(Reg, Cmd, Key) -> {error, Reason} end. --spec sub_keys(reg_handle()) -> {'ok', [string()]} | {'error', atom()}. +-spec sub_keys(RegHandle) -> ReturnValue when + RegHandle :: reg_handle(), + ReturnValue :: {'ok', [SubKey]} | {'error', ErrorId :: atom()}, + SubKey :: string(). sub_keys({win32reg, Reg}) when is_port(Reg) -> Cmd = [?cmd_get_all_subkeys], Reg ! {self(), {command, Cmd}}, collect_keys(Reg, []). --spec delete_key(reg_handle()) -> 'ok' | {'error', atom()}. +-spec delete_key(RegHandle) -> ReturnValue when + RegHandle :: reg_handle(), + ReturnValue :: 'ok' | {'error', ErrorId :: atom()}. delete_key({win32reg, Reg}) when is_port(Reg) -> Cmd = [?cmd_delete_key], Reg ! {self(), {command, Cmd}}, get_result(Reg). --spec set_value(reg_handle(), name(), value()) -> 'ok' | {'error', atom()}. +-spec set_value(RegHandle, Name, Value) -> ReturnValue when + RegHandle :: reg_handle(), + Name :: name(), + Value :: value(), + ReturnValue :: 'ok' | {'error', ErrorId :: atom()}. set_value({win32reg, Reg}, Name0, Value) when is_port(Reg) -> Name = @@ -140,7 +161,10 @@ set_value({win32reg, Reg}, Name0, Value) when is_port(Reg) -> Reg ! {self(), {command, Cmd}}, get_result(Reg). --spec value(reg_handle(), name()) -> {'ok', value()} | {'error', atom()}. +-spec value(RegHandle, Name) -> ReturnValue when + RegHandle :: reg_handle(), + Name :: name(), + ReturnValue :: {'ok', Value :: value()} | {'error', ErrorId :: atom()}. value({win32reg, Reg}, Name) when is_port(Reg) -> Cmd = [?cmd_get_value, Name, 0], @@ -152,14 +176,20 @@ value({win32reg, Reg}, Name) when is_port(Reg) -> {error, Reason} end. --spec values(reg_handle()) -> {'ok', [{name(), value()}]} | {'error', atom()}. +-spec values(RegHandle) -> ReturnValue when + RegHandle :: reg_handle(), + ReturnValue :: {'ok', [ValuePair]} | {'error', ErrorId :: atom()}, + ValuePair :: {Name :: name(), Value :: value()}. values({win32reg, Reg}) when is_port(Reg) -> Cmd = [?cmd_get_all_values], Reg ! {self(), {command, Cmd}}, collect_values(Reg, []). --spec delete_value(reg_handle(), name()) -> 'ok' | {'error', atom()}. +-spec delete_value(RegHandle, Name) -> ReturnValue when + RegHandle :: reg_handle(), + Name :: name(), + ReturnValue :: 'ok' | {'error', ErrorId :: atom()}. delete_value({win32reg, Reg}, Name0) when is_port(Reg) -> Name = @@ -171,7 +201,9 @@ delete_value({win32reg, Reg}, Name0) when is_port(Reg) -> Reg ! {self(), {command, Cmd}}, get_result(Reg). --spec expand(string()) -> string(). +-spec expand(String) -> ExpandedString when + String :: string(), + ExpandedString :: string(). expand(Value) -> expand(Value, [], []). @@ -195,7 +227,9 @@ expand([C|Rest], Env, Result) -> expand([], [], Result) -> lists:reverse(Result). --spec format_error(atom()) -> string(). +-spec format_error(ErrorId) -> ErrorString when + ErrorId :: atom(), + ErrorString :: string(). format_error(ErrorId) -> erl_posix_msg:message(ErrorId). @@ -203,7 +237,7 @@ format_error(ErrorId) -> %%% Implementation. -spec collect_values(port(), [{name(), value()}]) -> - {'ok', [{name(), value()}]} | {'error', atom()}. + {'ok', [{name(), value()}]} | {'error', ErrorId :: atom()}. collect_values(P, Result) -> case get_result(P) of @@ -215,7 +249,7 @@ collect_values(P, Result) -> {error, Reason} end. --spec collect_keys(port(), string()) -> {'ok', [string()]} | {'error', atom()}. +-spec collect_keys(port(), string()) -> {'ok', [string()]} | {'error', ErrorId :: atom()}. collect_keys(P, Result) -> case get_result(P) of diff --git a/lib/stdlib/src/zip.erl b/lib/stdlib/src/zip.erl index f44d97c227..c82c8159b6 100644 --- a/lib/stdlib/src/zip.erl +++ b/lib/stdlib/src/zip.erl @@ -1,26 +1,26 @@ %% %% %CopyrightBegin% -%% -%% Copyright Ericsson AB 2006-2009. All Rights Reserved. -%% +%% +%% Copyright Ericsson AB 2006-2011. 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 %% compliance with the License. You should have received a copy of the %% Erlang Public License along with this software. If not, it can be %% retrieved online at http://www.erlang.org/. -%% +%% %% Software distributed under the License is distributed on an "AS IS" %% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See %% the License for the specific language governing rights and limitations %% under the License. -%% +%% %% %CopyrightEnd% %% -module(zip). %% Basic api -export([unzip/1, unzip/2, extract/1, extract/2, - zip/2, zip/3, create/2, create/3, + zip/2, zip/3, create/2, create/3, foldl/3, list_dir/1, list_dir/2, table/1, table/2, t/1, tt/1]). @@ -38,7 +38,7 @@ zip_t/1, zip_tt/1, zip_list_dir/1, zip_list_dir/2, zip_close/1]). - + %% just for debugging zip server, not documented, not tested, not to be used -export([zip_get_state/1]). @@ -82,7 +82,7 @@ -record(openzip_opts, { output, % output object (fun) open_opts, % file:open options - cwd % directory to relate paths to + cwd % directory to relate paths to }). % openzip record, state for an open zip-file @@ -93,10 +93,10 @@ input, % archive io object (fun) output, % output io object (fun) zlib, % handle to open zlib - cwd % directory to relate paths to + cwd % directory to relate paths to }). -% Things that I would like to add to the public record #zip_file, +% Things that I would like to add to the public record #zip_file, % but can't as it would make things fail at upgrade. % Instead we use {#zip_file,#zip_file_extra} internally. -record(zip_file_extra, { @@ -203,6 +203,9 @@ zip_comment_length}). +-type zip_file() :: #zip_file{}. +-type zip_comment() :: #zip_comment{}. + %% Open a zip archive with options %% @@ -220,7 +223,7 @@ openzip_open(F, Options) -> do_openzip_open(F, Options) -> Opts = get_openzip_options(Options), #openzip_opts{output = Output, open_opts = OpO, cwd = CWD} = Opts, - Input = get_zip_input(F), + Input = get_input(F), In0 = Input({open, F, OpO -- [write]}, []), {[#zip_comment{comment = C} | Files], In1} = get_central_dir(In0, fun raw_file_info_etc/5, Input), @@ -278,7 +281,7 @@ file_name_search(Name,Files) -> [ZFile|_] -> ZFile; [] -> false end. - + %% %% add a file to an open archive %% openzip_add(File, OpenZip) -> %% case ?CATCH do_openzip_add(File, OpenZip) of @@ -323,8 +326,33 @@ openzip_close(_) -> %% Accepted options: %% verbose, cooked, file_list, keep_old_files, file_filter, memory +-spec(unzip(Archive) -> RetValue when + Archive :: file:name() | binary(), + RetValue :: {ok, FileList} + | {ok, FileBinList} + | {error, Reason :: term()} + | {error, {Name :: file:name(), Reason :: term()}}, + FileList :: [file:name()], + FileBinList :: [{file:name(),binary()}]). + unzip(F) -> unzip(F, []). +-spec(unzip(Archive, Options) -> RetValue when + Archive :: file:name() | binary(), + Options :: [Option], + Option :: {file_list, FileList} + | keep_old_files | verbose | memory | + {file_filter, FileFilter} | {cwd, CWD}, + FileList :: [file:name()], + FileBinList :: [{file:name(),binary()}], + FileFilter :: fun((ZipFile) -> boolean()), + CWD :: string(), + ZipFile :: zip_file(), + RetValue :: {ok, FileList} + | {ok, FileBinList} + | {error, Reason :: term()} + | {error, {Name :: file:name(), Reason :: term()}}). + unzip(F, Options) -> case ?CATCH do_unzip(F, Options) of {ok, R} -> {ok, R}; @@ -344,13 +372,69 @@ do_unzip(F, Options) -> Input(close, In1), {ok, Files}. +%% Iterate over all files in a zip archive +-spec(foldl(Fun, Acc0, Archive) -> {ok, Acc1} | {error, Reason} when + Fun :: fun((FileInArchive, GetInfo, GetBin, AccIn) -> AccOut), + FileInArchive :: file:name(), + GetInfo :: fun(() -> file:file_info()), + GetBin :: fun(() -> binary()), + Acc0 :: term(), + Acc1 :: term(), + AccIn :: term(), + AccOut :: term(), + Archive :: file:name() | {file:name(), binary()}, + Reason :: term()). + +foldl(Fun, Acc0, Archive) when is_function(Fun, 4) -> + ZipFun = + fun({Name, GetInfo, GetBin}, A) -> + A2 = Fun(Name, GetInfo, GetBin, A), + {true, false, A2} + end, + case prim_zip:open(ZipFun, Acc0, Archive) of + {ok, PrimZip, Acc1} -> + ok = prim_zip:close(PrimZip), + {ok, Acc1}; + {error, bad_eocd} -> + {error, "Not an archive file"}; + {error, Reason} -> + {error, Reason} + end; +foldl(_,_, _) -> + {error, einval}. + %% Create zip archive name F from Files or binaries %% %% Accepted options: %% verbose, cooked, memory, comment +-spec(zip(Name, FileList) -> RetValue when + Name :: file:name(), + FileList :: [FileSpec], + FileSpec :: file:name() | {file:name(), binary()} + | {file:name(), binary(), file:file_info()}, + RetValue :: {ok, FileName :: file:name()} + | {ok, {FileName :: file:name(), binary()}} + | {error, Reason :: term()}). + zip(F, Files) -> zip(F, Files, []). +-spec(zip(Name, FileList, Options) -> RetValue when + Name :: file:name(), + FileList :: [FileSpec], + FileSpec :: file:name() | {file:name(), binary()} + | {file:name(), binary(), file:file_info()}, + Options :: [Option], + Option :: memory | cooked | verbose | {comment, Comment} + | {cwd, CWD} | {compress, What} | {uncompress, What}, + What :: all | [Extension] | {add, [Extension]} | {del, [Extension]}, + Extension :: string(), + Comment :: string(), + CWD :: string(), + RetValue :: {ok, FileName :: file:name()} + | {ok, {FileName :: file:name(), binary()}} + | {error, Reason :: term()}). + zip(F, Files, Options) -> case ?CATCH do_zip(F, Files, Options) of {ok, R} -> {ok, R}; @@ -373,8 +457,20 @@ do_zip(F, Files, Options) -> %% Accepted options: %% cooked, file_filter, file_output (latter 2 undocumented) +-spec(list_dir(Archive) -> RetValue when + Archive :: file:name() | binary(), + RetValue :: {ok, CommentAndFiles} | {error, Reason :: term()}, + CommentAndFiles :: [zip_comment() | zip_file()]). + list_dir(F) -> list_dir(F, []). +-spec(list_dir(Archive, Options) -> RetValue when + Archive :: file:name() | binary(), + RetValue :: {ok, CommentAndFiles} | {error, Reason :: term()}, + CommentAndFiles :: [zip_comment() | zip_file()], + Options :: [Option], + Option :: cooked). + list_dir(F, Options) -> case ?CATCH do_list_dir(F, Options) of {ok, R} -> {ok, R}; @@ -383,7 +479,7 @@ list_dir(F, Options) -> do_list_dir(F, Options) -> Opts = get_list_dir_options(F, Options), - #list_dir_opts{input = Input, open_opts = OpO, + #list_dir_opts{input = Input, open_opts = OpO, raw_iterator = RawIterator} = Opts, In0 = Input({open, F, OpO}, []), {Info, In1} = get_central_dir(In0, RawIterator, Input), @@ -392,6 +488,10 @@ do_list_dir(F, Options) -> %% Print zip directory in short form +-spec(t(Archive) -> ok when + Archive :: file:name() | binary() | ZipHandle, + ZipHandle :: pid()). + t(F) when is_pid(F) -> zip_t(F); t(F) when is_record(F, openzip) -> openzip_t(F); t(F) -> t(F, fun raw_short_print_info_etc/5). @@ -412,12 +512,16 @@ do_t(F, RawPrint) -> %% Print zip directory in long form (like ls -l) +-spec(tt(Archive) -> ok when + Archive :: file:name() | binary() | ZipHandle, + ZipHandle :: pid()). + tt(F) when is_pid(F) -> zip_tt(F); tt(F) when is_record(F, openzip) -> openzip_tt(F); tt(F) -> t(F, fun raw_long_print_info_etc/5). -%% option utils +%% option utils get_unzip_opt([], Opts) -> Opts; get_unzip_opt([verbose | Rest], Opts) -> @@ -470,7 +574,7 @@ get_zip_opt([{cwd, CWD} | Rest], Opts) -> get_zip_opt([{comment, C} | Rest], Opts) -> get_zip_opt(Rest, Opts#zip_opts{comment = C}); get_zip_opt([{compress, Which} = O| Rest], Opts) -> - Which2 = + Which2 = case Which of all -> all; @@ -485,7 +589,7 @@ get_zip_opt([{compress, Which} = O| Rest], Opts) -> end, get_zip_opt(Rest, Opts#zip_opts{compress = Which2}); get_zip_opt([{uncompress, Which} = O| Rest], Opts) -> - Which2 = + Which2 = case Which of all -> all; @@ -560,16 +664,24 @@ get_openzip_options(Options) -> get_input(F) when is_binary(F) -> fun binary_io/2; get_input(F) when is_list(F) -> - fun file_io/2. + fun file_io/2; +get_input(_) -> + throw(einval). get_zip_input({F, B}) when is_binary(B), is_list(F) -> fun binary_io/2; +get_zip_input({F, B, #file_info{}}) when is_binary(B), is_list(F) -> + fun binary_io/2; +get_zip_input({F, #file_info{}, B}) when is_binary(B), is_list(F) -> + fun binary_io/2; get_zip_input(F) when is_list(F) -> fun file_io/2; get_zip_input({files, []}) -> fun binary_io/2; get_zip_input({files, [File | _]}) -> - get_zip_input(File). + get_zip_input(File); +get_zip_input(_) -> + throw(einval). get_list_dir_options(F, Options) -> Opts = #list_dir_opts{raw_iterator = fun raw_file_info_public/5, @@ -578,11 +690,78 @@ get_list_dir_options(F, Options) -> get_list_dir_opt(Options, Opts). %% aliases for erl_tar compatibility +-spec(table(Archive) -> RetValue when + Archive :: file:name() | binary(), + RetValue :: {ok, CommentAndFiles} | {error, Reason :: term()}, + CommentAndFiles :: [zip_comment() | zip_file()]). + table(F) -> list_dir(F). + +-spec(table(Archive, Options) -> RetValue when + Archive :: file:name() | binary(), + RetValue :: {ok, CommentAndFiles} | {error, Reason :: term()}, + CommentAndFiles :: [zip_comment() | zip_file()], + + Options :: [Option], + Option :: cooked). + table(F, O) -> list_dir(F, O). + +-spec(create(Name, FileList) -> RetValue when + Name :: file:name(), + FileList :: [FileSpec], + FileSpec :: file:name() | {file:name(), binary()} + | {file:name(), binary(), file:file_info()}, + RetValue :: {ok, FileName :: file:name()} + | {ok, {FileName :: file:name(), binary()}} + | {error, Reason :: term()}). + create(F, Fs) -> zip(F, Fs). + +-spec(create(Name, FileList, Options) -> RetValue when + Name :: file:name(), + FileList :: [FileSpec], + FileSpec :: file:name() | {file:name(), binary()} + | {file:name(), binary(), file:file_info()}, + Options :: [Option], + Option :: memory | cooked | verbose | {comment, Comment} + | {cwd, CWD} | {compress, What} | {uncompress, What}, + What :: all | [Extension] | {add, [Extension]} | {del, [Extension]}, + Extension :: string(), + Comment :: string(), + CWD :: string(), + RetValue :: {ok, FileName :: file:name()} + | {ok, {FileName :: file:name(), binary()}} + | {error, Reason :: term()}). create(F, Fs, O) -> zip(F, Fs, O). + +-spec(extract(Archive) -> RetValue when + Archive :: file:name() | binary(), + RetValue :: {ok, FileList} + | {ok, FileBinList} + | {error, Reason :: term()} + | {error, {Name :: file:name(), Reason :: term()}}, + FileList :: [file:name()], + FileBinList :: [{file:name(),binary()}]). + extract(F) -> unzip(F). + +-spec(extract(Archive, Options) -> RetValue when + Archive :: file:name() | binary(), + Options :: [Option], + Option :: {file_list, FileList} + | keep_old_files | verbose | memory | + {file_filter, FileFilter} | {cwd, CWD}, + FileList :: [file:name()], + FileBinList :: [{file:name(),binary()}], + FileFilter :: fun((ZipFile) -> boolean()), + CWD :: string(), + ZipFile :: zip_file(), + RetValue :: {ok, FileList} + | {ok, FileBinList} + | {error, Reason :: term()} + | {error, {Name :: file:name(), Reason :: term()}}). + extract(F, O) -> unzip(F, O). @@ -620,6 +799,8 @@ put_eocd(N, Pos, Sz, Comment, Output, Out0) -> get_filename({Name, _}, Type) -> get_filename(Name, Type); +get_filename({Name, _, _}, Type) -> + get_filename(Name, Type); get_filename(Name, regular) -> Name; get_filename(Name, directory) -> @@ -895,7 +1076,7 @@ local_file_header_to_bin( CompSize:32/little, UncompSize:32/little, FileNameLength:16/little, - ExtraFieldLength:16/little>>. + ExtraFieldLength:16/little>>. eocd_to_bin(#eocd{disk_num = DiskNum, start_disk_num = StartDiskNum, @@ -912,7 +1093,7 @@ eocd_to_bin(#eocd{disk_num = DiskNum, Offset:32/little, ZipCommentLength:16/little>>. -%% put together a local file header +%% put together a local file header local_file_header_from_info_method_name(#file_info{mtime = MTime}, UncompSize, CompMethod, Name) -> @@ -939,7 +1120,7 @@ server_loop(OpenZip) -> server_loop(NewOpenZip); Error -> From ! {self(), Error} - end; + end; {From, close} -> From ! {self(), openzip_close(OpenZip)}; {From, get} -> @@ -961,21 +1142,52 @@ server_loop(OpenZip) -> {error, bad_msg} end. +-spec(zip_open(Archive) -> {ok, ZipHandle} | {error, Reason} when + Archive :: file:name() | binary(), + ZipHandle :: pid(), + Reason :: term()). + zip_open(Archive) -> zip_open(Archive, []). +-spec(zip_open(Archive, Options) -> {ok, ZipHandle} | {error, Reason} when + Archive :: file:name() | binary(), + ZipHandle :: pid(), + Options :: [Option], + Option :: cooked | memory | {cwd, CWD :: string()}, + Reason :: term()). + zip_open(Archive, Options) -> Pid = spawn(fun() -> server_loop(not_open) end), request(self(), Pid, {open, Archive, Options}). +-spec(zip_get(ZipHandle) -> {ok, [Result]} | {error, Reason} when + ZipHandle :: pid(), + Result :: file:name() | {file:name(), binary()}, + Reason :: term()). + zip_get(Pid) when is_pid(Pid) -> request(self(), Pid, get). +-spec(zip_close(ZipHandle) -> ok | {error, einval} when + ZipHandle :: pid()). + zip_close(Pid) when is_pid(Pid) -> request(self(), Pid, close). +-spec(zip_get(FileName, ZipHandle) -> {ok, Result} | {error, Reason} when + FileName :: file:name(), + ZipHandle :: pid(), + Result :: file:name() | {file:name(), binary()}, + Reason :: term()). + zip_get(FileName, Pid) when is_pid(Pid) -> request(self(), Pid, {get, FileName}). +-spec(zip_list_dir(ZipHandle) -> {ok, Result} | {error, Reason} when + Result :: [zip_comment() | zip_file()], + ZipHandle :: pid(), + Reason :: term()). + zip_list_dir(Pid) when is_pid(Pid) -> request(self(), Pid, list_dir). @@ -1024,7 +1236,7 @@ lists_foreach(F, [Hd|Tl]) -> F(Hd), lists_foreach(F, Tl). -%% option utils +%% option utils get_openzip_opt([], Opts) -> Opts; get_openzip_opt([cooked | Rest], #openzip_opts{open_opts = OO} = Opts) -> @@ -1121,7 +1333,7 @@ raw_file_info_public(CD, FileName, FileComment, BExtraField, Acc0) -> Other -> Other end, [H2|T]. - + %% make a file_info from a central directory header cd_file_header_to_file_info(FileName, @@ -1213,8 +1425,8 @@ get_z_file(In0, Z, Input, Output, OpO, FB, CWD, {ZipFile,Extra}) -> {dir, In3}; _ -> %% FileInfo = local_file_header_to_file_info(LH) - %%{Out, In4, CRC, UncompSize} = - {Out, In4, CRC, _UncompSize} = + %%{Out, In4, CRC, UncompSize} = + {Out, In4, CRC, _UncompSize} = get_z_data(CompMethod, In3, FileName1, CompSize, Input, Output, OpO, Z), In5 = skip_z_data_descriptor(GPFlag, Input, In4), @@ -1280,7 +1492,7 @@ get_z_data_loop(CompSize, UncompSize, In0, Out0, Input, Output, Z) -> Out1 = Output({write, Uncompressed}, Out0), get_z_data_loop(CompSize-N, UncompSize + iolist_size(Uncompressed), In1, Out1, Input, Output, Z) - end. + end. %% skip data descriptor if any @@ -1298,7 +1510,7 @@ dos_date_time_to_datetime(DosDate, DosTime) -> <<Hour:5, Min:6, Sec:5>> = <<DosTime:16>>, <<YearFrom1980:7, Month:4, Day:5>> = <<DosDate:16>>, {{YearFrom1980+1980, Month, Day}, - {Hour, Min, Sec}}. + {Hour, Min, Sec}}. dos_date_time_from_datetime({{Year, Month, Day}, {Hour, Min, Sec}}) -> YearFrom1980 = Year-1980, @@ -1319,7 +1531,6 @@ unix_extra_field_and_var_from_bin(<<TSize:16/little, Var}; unix_extra_field_and_var_from_bin(_) -> throw(bad_unix_extra_field). - %% A pwrite-like function for iolists (used by memory-option) @@ -1478,6 +1689,8 @@ local_file_header_from_bin(_) -> %% io functions binary_io({file_info, {_Filename, _B, #file_info{} = FI}}, _A) -> FI; +binary_io({file_info, {_Filename, #file_info{} = FI, _B}}, _A) -> + FI; binary_io({file_info, {_Filename, B}}, A) -> binary_io({file_info, B}, A); binary_io({file_info, B}, _) -> @@ -1493,9 +1706,11 @@ binary_io({file_info, B}, _) -> links = 1, major_device = 0, minor_device = 0, inode = 0, uid = 0, gid = 0}; -binary_io({open, {_Filename, B, _FI}, _Opts}, _) -> +binary_io({open, {_Filename, B, _FI}, _Opts}, _) when is_binary(B) -> + {0, B}; +binary_io({open, {_Filename, _FI, B}, _Opts}, _) when is_binary(B) -> {0, B}; -binary_io({open, {_Filename, B}, _Opts}, _) -> +binary_io({open, {_Filename, B}, _Opts}, _) when is_binary(B) -> {0, B}; binary_io({open, B, _Opts}, _) when is_binary(B) -> {0, B}; |