~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

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

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
3
%% 
4
 
%% Copyright Ericsson AB 2007-2009. All Rights Reserved.
 
4
%% Copyright Ericsson AB 2007-2011. All Rights Reserved.
5
5
%% 
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
163
163
 
164
164
-type array_indx() :: non_neg_integer().
165
165
 
166
 
-type array_opt()  :: 'fixed' | non_neg_integer()
167
 
                    | {'default', term()} | {'fixed', boolean()}
168
 
                    | {'size', non_neg_integer()}.
 
166
-type array_opt()  :: {'fixed', boolean()} | 'fixed'
 
167
                    | {'default', Value :: term()}
 
168
                    | {'size', N :: non_neg_integer()}
 
169
                    | (N :: non_neg_integer()).
169
170
-type array_opts() :: array_opt() | [array_opt()].
170
171
 
171
 
-type indx_pair()  :: {array_indx(), term()}.
 
172
-type indx_pair()  :: {Index :: array_indx(), Value :: term()}.
172
173
-type indx_pairs() :: [indx_pair()].
173
174
 
174
175
%%--------------------------------------------------------------------------
175
176
 
176
 
%% @spec () -> array()
177
177
%% @doc Create a new, extendible array with initial size zero.
178
178
%% @equiv new([])
179
179
%%
185
185
new() ->
186
186
    new([]).
187
187
 
188
 
%% @spec (Options::term()) -> array()
189
188
%% @doc Create a new array according to the given options. By default,
190
189
%% the array is extendible and has initial size zero. Array indices
191
190
%% start at 0.
224
223
%% @see from_list/2
225
224
%% @see fix/1
226
225
 
227
 
-spec new(array_opts()) -> array().
 
226
-spec new(Options :: array_opts()) -> array().
228
227
 
229
228
new(Options) ->
230
229
    new_0(Options, 0, false).
231
230
 
232
 
%% @spec (Size::integer(), Options::term()) -> array()
233
231
%% @doc Create a new array according to the given size and options. If
234
232
%% `Size' is not a nonnegative integer, the call fails with reason
235
233
%% `badarg'. By default, the array has fixed size. Note that any size
245
243
%%
246
244
%% @see new/1
247
245
 
248
 
-spec new(non_neg_integer(), array_opts()) -> array().
 
246
-spec new(Size :: non_neg_integer(), Options :: array_opts()) -> array().
249
247
 
250
248
new(Size, Options) when is_integer(Size), Size >= 0 ->
251
249
    new_0(Options, Size, true);
293
291
    M.
294
292
 
295
293
 
296
 
%% @spec (X::term()) -> boolean()
297
294
%% @doc Returns `true' if `X' appears to be an array, otherwise `false'.
298
295
%% Note that the check is only shallow; there is no guarantee that `X'
299
296
%% is a well-formed array representation even if this function returns
300
297
%% `true'.
301
298
 
302
 
-spec is_array(term()) -> boolean().
 
299
-spec is_array(X :: term()) -> boolean().
303
300
 
304
301
is_array(#array{size = Size, max = Max})
305
302
  when is_integer(Size), is_integer(Max) ->
308
305
    false.
309
306
 
310
307
 
311
 
%% @spec (array()) -> integer()
312
308
%% @doc Get the number of entries in the array. Entries are numbered
313
309
%% from 0 to `size(Array)-1'; hence, this is also the index of the first
314
310
%% entry that is guaranteed to not have been previously set.
315
311
%% @see set/3
316
312
%% @see sparse_size/1
317
313
 
318
 
-spec size(array()) -> non_neg_integer().
 
314
-spec size(Array :: array()) -> non_neg_integer().
319
315
 
320
316
size(#array{size = N}) -> N;
321
317
size(_) -> erlang:error(badarg).
322
318
 
323
319
 
324
 
%% @spec (array()) -> term()
325
320
%% @doc Get the value used for uninitialized entries.
326
321
%%
327
322
%% @see new/2
328
323
 
329
 
-spec default(array()) -> term().
 
324
-spec default(Array :: array()) -> term().
330
325
 
331
326
default(#array{default = D}) -> D;
332
327
default(_) -> erlang:error(badarg).
405
400
-endif.
406
401
 
407
402
 
408
 
%% @spec (array()) -> array()
409
403
%% @doc Fix the size of the array. This prevents it from growing
410
404
%% automatically upon insertion; see also {@link set/3}.
411
405
%% @see relax/1
412
406
 
413
 
-spec fix(array()) -> array().
 
407
-spec fix(Array :: array()) -> array().
414
408
 
415
409
fix(#array{}=A) ->
416
410
    A#array{max = 0}.
417
411
 
418
412
 
419
 
%% @spec (array()) -> boolean()
420
413
%% @doc Check if the array has fixed size. 
421
414
%% Returns `true' if the array is fixed, otherwise `false'.
422
415
%% @see fix/1
423
416
 
424
 
-spec is_fix(array()) -> boolean().
 
417
-spec is_fix(Array :: array()) -> boolean().
425
418
 
426
419
is_fix(#array{max = 0}) -> true;
427
420
is_fix(#array{}) -> false.
455
448
-endif.
456
449
 
457
450
 
458
 
%% @spec (array()) -> array()
459
451
%% @doc Make the array resizable. (Reverses the effects of {@link
460
452
%% fix/1}.)
461
453
%% @see fix/1
462
454
 
463
 
-spec relax(array()) -> array().
 
455
-spec relax(Array :: array()) -> array().
464
456
 
465
457
relax(#array{size = N}=A) ->
466
458
    A#array{max = find_max(N-1, ?LEAFSIZE)}.
481
473
-endif.
482
474
 
483
475
 
484
 
%% @spec (integer(), array()) -> array()
485
476
%% @doc Change the size of the array. If `Size' is not a nonnegative
486
477
%% integer, the call fails with reason `badarg'. If the given array has
487
478
%% fixed size, the resulting array will also have fixed size.
488
479
 
489
 
-spec resize(non_neg_integer(), array()) -> array().
 
480
-spec resize(Size :: non_neg_integer(), Array :: array()) -> array().
490
481
 
491
482
resize(Size, #array{size = N, max = M, elements = E}=A)
492
483
  when is_integer(Size), Size >= 0 ->
510
501
    erlang:error(badarg).
511
502
 
512
503
 
513
 
%% @spec (array()) -> array()
514
 
 
515
504
%% @doc Change the size of the array to that reported by {@link
516
505
%% sparse_size/1}. If the given array has fixed size, the resulting
517
506
%% array will also have fixed size.
519
508
%% @see resize/2
520
509
%% @see sparse_size/1
521
510
 
522
 
-spec resize(array()) -> array().
 
511
-spec resize(Array :: array()) -> array().
523
512
 
524
513
resize(Array) ->
525
514
    resize(sparse_size(Array), Array).
559
548
-endif.
560
549
 
561
550
 
562
 
%% @spec (integer(), term(), array()) -> array()
563
551
%% @doc Set entry `I' of the array to `Value'. If `I' is not a
564
552
%% nonnegative integer, or if the array has fixed size and `I' is larger
565
553
%% than the maximum index, the call fails with reason `badarg'.
570
558
%% @see get/2
571
559
%% @see reset/2
572
560
 
573
 
-spec set(array_indx(), term(), array()) -> array().
 
561
-spec set(I :: array_indx(), Value :: term(), Array :: array()) -> array().
574
562
 
575
563
set(I, Value, #array{size = N, max = M, default = D, elements = E}=A)
576
564
  when is_integer(I), I >= 0 ->
624
612
    setelement(I+1, ?NEW_LEAF(D), X).
625
613
 
626
614
 
627
 
%% @spec (integer(), array()) -> term()
628
615
%% @doc Get the value of entry `I'. If `I' is not a nonnegative
629
616
%% integer, or if the array has fixed size and `I' is larger than the
630
617
%% maximum index, the call fails with reason `badarg'.
634
621
 
635
622
%% @see set/3
636
623
 
637
 
-spec get(array_indx(), array()) -> term().
 
624
-spec get(I :: array_indx(), Array :: array()) -> term().
638
625
 
639
626
get(I, #array{size = N, max = M, elements = E, default = D})
640
627
  when is_integer(I), I >= 0 ->
660
647
    element(I+1, E).
661
648
 
662
649
 
663
 
%% @spec (integer(), array()) -> array()
664
650
%% @doc Reset entry `I' to the default value for the array. 
665
651
%% If the value of entry `I' is the default value the array will be
666
652
%% returned unchanged. Reset will never change size of the array. 
675
661
 
676
662
%% TODO: a reset_range function
677
663
 
678
 
-spec reset(array_indx(), array()) -> array().
 
664
-spec reset(I :: array_indx(), Array :: array()) -> array().
679
665
 
680
666
reset(I, #array{size = N, max = M, default = D, elements = E}=A) 
681
667
    when is_integer(I), I >= 0 ->
756
742
-endif.
757
743
 
758
744
 
759
 
%% @spec (array()) -> list()
760
745
%% @doc Converts the array to a list.
761
746
%%
762
747
%% @see from_list/2
763
748
%% @see sparse_to_list/1
764
749
 
765
 
-spec to_list(array()) -> list().
 
750
-spec to_list(Array :: array()) -> list().
766
751
 
767
752
to_list(#array{size = 0}) ->
768
753
    [];
831
816
-endif.
832
817
 
833
818
 
834
 
%% @spec (array()) -> list()
835
819
%% @doc Converts the array to a list, skipping default-valued entries.
836
820
%%
837
821
%% @see to_list/1
838
822
 
839
 
-spec sparse_to_list(array()) -> list().
 
823
-spec sparse_to_list(Array :: array()) -> list().
840
824
 
841
825
sparse_to_list(#array{size = 0}) ->
842
826
    [];
901
885
-endif.
902
886
 
903
887
 
904
 
%% @spec (list()) -> array()
905
888
%% @equiv from_list(List, undefined)
906
889
 
907
 
-spec from_list(list()) -> array().
 
890
-spec from_list(List :: list()) -> array().
908
891
 
909
892
from_list(List) ->
910
893
    from_list(List, undefined).
911
894
 
912
 
%% @spec (list(), term()) -> array()
913
895
%% @doc Convert a list to an extendible array. `Default' is used as the value
914
896
%% for uninitialized entries of the array. If `List' is not a proper list,
915
897
%% the call fails with reason `badarg'.
917
899
%% @see new/2
918
900
%% @see to_list/1
919
901
 
920
 
-spec from_list(list(), term()) -> array().
 
902
-spec from_list(List :: list(), Default :: term()) -> array().
921
903
 
922
904
from_list([], Default) ->
923
905
    new({default,Default});
1011
993
-endif.
1012
994
 
1013
995
 
1014
 
%% @spec (array()) -> [{Index::integer(), Value::term()}]
1015
996
%% @doc Convert the array to an ordered list of pairs `{Index, Value}'.
1016
997
%%
1017
998
%% @see from_orddict/2
1018
999
%% @see sparse_to_orddict/1
1019
1000
 
1020
 
-spec to_orddict(array()) -> indx_pairs().
 
1001
-spec to_orddict(Array :: array()) -> indx_pairs().
1021
1002
 
1022
1003
to_orddict(#array{size = 0}) ->
1023
1004
    [];
1104
1085
-endif.
1105
1086
 
1106
1087
 
1107
 
%% @spec (array()) -> [{Index::integer(), Value::term()}]
1108
1088
%% @doc Convert the array to an ordered list of pairs `{Index, Value}',
1109
1089
%% skipping default-valued entries.
1110
1090
%% 
1111
1091
%% @see to_orddict/1
1112
1092
 
1113
 
-spec sparse_to_orddict(array()) -> indx_pairs().
 
1093
-spec sparse_to_orddict(Array :: array()) -> indx_pairs().
1114
1094
 
1115
1095
sparse_to_orddict(#array{size = 0}) ->
1116
1096
    [];
1188
1168
-endif.
1189
1169
 
1190
1170
 
1191
 
%% @spec (list()) -> array()
1192
1171
%% @equiv from_orddict(Orddict, undefined)
1193
1172
 
1194
 
-spec from_orddict(indx_pairs()) -> array().
 
1173
-spec from_orddict(Orddict :: indx_pairs()) -> array().
1195
1174
 
1196
1175
from_orddict(Orddict) ->
1197
1176
    from_orddict(Orddict, undefined).
1198
1177
 
1199
 
%% @spec (list(), term()) -> array() 
1200
1178
%% @doc Convert an ordered list of pairs `{Index, Value}' to a
1201
1179
%% corresponding extendible array. `Default' is used as the value for
1202
1180
%% uninitialized entries of the array. If `List' is not a proper,
1206
1184
%% @see new/2
1207
1185
%% @see to_orddict/1
1208
1186
 
1209
 
-spec from_orddict(indx_pairs(), term()) -> array().
 
1187
-spec from_orddict(Orddict :: indx_pairs(), Default :: term()) -> array().
1210
1188
 
1211
1189
from_orddict([], Default) ->
1212
1190
    new({default,Default});
1392
1370
-endif.
1393
1371
 
1394
1372
 
1395
 
%% @spec (Function, array()) -> array()
1396
1373
%%    Function = (Index::integer(), Value::term()) -> term()
1397
1374
%% @doc Map the given function onto each element of the array. The
1398
1375
%% elements are visited in order from the lowest index to the highest.
1402
1379
%% @see foldr/3
1403
1380
%% @see sparse_map/2
1404
1381
 
1405
 
-spec map(fun((array_indx(), _) -> _), array()) -> array().
 
1382
-spec map(Function, Array :: array()) -> array() when
 
1383
      Function :: fun((Index :: array_indx(), Value :: _) -> _).
1406
1384
 
1407
1385
map(Function, Array=#array{size = N, elements = E, default = D})
1408
1386
  when is_function(Function, 2) ->
1485
1463
-endif.
1486
1464
 
1487
1465
 
1488
 
%% @spec (Function, array()) -> array()
1489
1466
%%    Function = (Index::integer(), Value::term()) -> term()
1490
1467
%% @doc Map the given function onto each element of the array, skipping
1491
1468
%% default-valued entries. The elements are visited in order from the
1494
1471
%%
1495
1472
%% @see map/2
1496
1473
 
1497
 
-spec sparse_map(fun((array_indx(), _) -> _), array()) -> array().
 
1474
-spec sparse_map(Function, Array :: array()) -> array() when
 
1475
      Function :: fun((Index :: array_indx(), Value :: _) -> _).
1498
1476
 
1499
1477
sparse_map(Function, Array=#array{size = N, elements = E, default = D})
1500
1478
  when is_function(Function, 2) ->
1580
1558
-endif.
1581
1559
 
1582
1560
 
1583
 
%% @spec (Function, InitialAcc::term(), array()) -> term()
1584
 
%%    Function = (Index::integer(), Value::term(), Acc::term()) ->
1585
 
%%               term()
1586
1561
%% @doc Fold the elements of the array using the given function and
1587
1562
%% initial accumulator value. The elements are visited in order from the
1588
1563
%% lowest index to the highest. If `Function' is not a function, the
1592
1567
%% @see map/2
1593
1568
%% @see sparse_foldl/3
1594
1569
 
1595
 
-spec foldl(fun((array_indx(), _, A) -> B), A, array()) -> B.
 
1570
-spec foldl(Function, InitialAcc :: A, Array :: array()) -> B when
 
1571
      Function :: fun((Index :: array_indx(), Value :: _, Acc :: A) -> B).
1596
1572
 
1597
1573
foldl(Function, A, #array{size = N, elements = E, default = D})
1598
1574
  when is_function(Function, 3) ->
1656
1632
-endif.
1657
1633
 
1658
1634
 
1659
 
%% @spec (Function, InitialAcc::term(), array()) -> term()
1660
 
%%    Function = (Index::integer(), Value::term(), Acc::term()) ->
1661
 
%%               term()
1662
1635
%% @doc Fold the elements of the array using the given function and
1663
1636
%% initial accumulator value, skipping default-valued entries. The
1664
1637
%% elements are visited in order from the lowest index to the highest.
1667
1640
%% @see foldl/3
1668
1641
%% @see sparse_foldr/3
1669
1642
 
1670
 
-spec sparse_foldl(fun((array_indx(), _, A) -> B), A, array()) -> B.
 
1643
-spec sparse_foldl(Function, InitialAcc :: A, Array :: array()) -> B when
 
1644
      Function :: fun((Index :: array_indx(), Value :: _, Acc :: A) -> B).
1671
1645
 
1672
1646
sparse_foldl(Function, A, #array{size = N, elements = E, default = D})
1673
1647
  when is_function(Function, 3) ->
1735
1709
-endif.
1736
1710
 
1737
1711
 
1738
 
%% @spec (Function, InitialAcc::term(), array()) -> term()
1739
 
%%    Function = (Index::integer(), Value::term(), Acc::term()) ->
1740
 
%%               term()
1741
1712
%% @doc Fold the elements of the array right-to-left using the given
1742
1713
%% function and initial accumulator value. The elements are visited in
1743
1714
%% order from the highest index to the lowest. If `Function' is not a
1746
1717
%% @see foldl/3
1747
1718
%% @see map/2
1748
1719
 
1749
 
-spec foldr(fun((array_indx(), _, A) -> B), A, array()) -> B.
 
1720
-spec foldr(Function, InitialAcc :: A, Array :: array()) -> B when
 
1721
      Function :: fun((Index :: array_indx(), Value :: _, Acc :: A) -> B).
1750
1722
 
1751
1723
foldr(Function, A, #array{size = N, elements = E, default = D})
1752
1724
  when is_function(Function, 3) ->
1815
1787
-endif.
1816
1788
 
1817
1789
 
1818
 
%% @spec (Function, InitialAcc::term(), array()) -> term()
1819
 
%%    Function = (Index::integer(), Value::term(), Acc::term()) ->
1820
 
%%               term()
1821
1790
%% @doc Fold the elements of the array right-to-left using the given
1822
1791
%% function and initial accumulator value, skipping default-valued
1823
1792
%% entries. The elements are visited in order from the highest index to
1827
1796
%% @see foldr/3
1828
1797
%% @see sparse_foldl/3
1829
1798
 
1830
 
-spec sparse_foldr(fun((array_indx(), _, A) -> B), A, array()) -> B.
 
1799
-spec sparse_foldr(Function, InitialAcc :: A, Array :: array()) -> B when
 
1800
      Function :: fun((Index :: array_indx(), Value :: _, Acc :: A) -> B).
1831
1801
 
1832
1802
sparse_foldr(Function, A, #array{size = N, elements = E, default = D})
1833
1803
  when is_function(Function, 3) ->
1870
1840
    end.
1871
1841
 
1872
1842
 
1873
 
%% @spec (array()) -> integer()
1874
1843
%% @doc Get the number of entries in the array up until the last
1875
1844
%% non-default valued entry. In other words, returns `I+1' if `I' is the
1876
1845
%% last non-default valued entry in the array, or zero if no such entry
1878
1847
%% @see size/1
1879
1848
%% @see resize/1
1880
1849
 
1881
 
-spec sparse_size(array()) -> non_neg_integer().
 
1850
-spec sparse_size(Array :: array()) -> non_neg_integer().
1882
1851
 
1883
1852
sparse_size(A) ->
1884
1853
    F = fun (I, _V, _A) -> throw({value, I}) end,