~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/stdlib/src/array.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-08-05 20:54:29 UTC
  • mfrom: (6.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090805205429-pm4pnwew8axraosl
Tags: 1:13.b.1-dfsg-5
* Fixed parentheses in Emacs mode (closes: #536891).
* Removed unnecessary conflicts with erlang-manpages package.
* Added workaround for #475459: disabled threads on sparc architecture.
  This breaks wxErlang, so it's only a temporary solution.

Show diffs side-by-side

added added

removed removed

Lines of Context:
886
886
-spec from_list(list(), term()) -> array().
887
887
 
888
888
from_list([], Default) ->
889
 
    new(0, {default,Default});
 
889
    new({default,Default});
890
890
from_list(List, Default) when is_list(List) ->
891
891
    {E, N, M} = from_list_1(?LEAFSIZE, List, Default, 0, [], []),
892
892
    #array{size = N, max = M, default = Default, elements = E};
960
960
    N3 = ?NODESIZE*N2,
961
961
    N4 = ?NODESIZE*N3,
962
962
    [?_assert(array:size(from_list([])) =:= 0),
 
963
     ?_assert(array:is_fix(from_list([])) =:= false),
963
964
     ?_assert(array:size(from_list([undefined])) =:= 1),
 
965
     ?_assert(array:is_fix(from_list([undefined])) =:= false),
964
966
     ?_assert(array:size(from_list(lists:seq(1,N1))) =:= N1),
965
967
     ?_assert(to_list(from_list(lists:seq(1,N0))) =:= lists:seq(1,N0)),
966
968
     ?_assert(to_list(from_list(lists:seq(1,N0+1))) =:= lists:seq(1,N0+1)),
1173
1175
-spec from_orddict(indx_pairs(), term()) -> array().
1174
1176
 
1175
1177
from_orddict([], Default) ->
1176
 
    new(0, {default,Default});
 
1178
    new({default,Default});
1177
1179
from_orddict(List, Default) when is_list(List) ->
1178
1180
    {E, N, M} = from_orddict_1(?LEAFSIZE, List, 0, Default, 0, [], []),
1179
1181
    #array{size = N, max = M, default = Default, elements = E};
1221
1223
    N3 = ?NODESIZE*N2,
1222
1224
    N4 = ?NODESIZE*N3,
1223
1225
    [?_assert(array:size(from_orddict([])) =:= 0),
 
1226
     ?_assert(array:is_fix(from_orddict([])) =:= false),
1224
1227
     ?_assert(array:size(from_orddict([{0,undefined}])) =:= 1),
 
1228
     ?_assert(array:is_fix(from_orddict([{0,undefined}])) =:= false),
1225
1229
     ?_assert(array:size(from_orddict([{N0-1,undefined}])) =:= N0),
1226
1230
     ?_assert(array:size(from_orddict([{N,0}||N<-lists:seq(0,N1-1)]))
1227
1231
              =:= N1),