Key-value dictionary as ordered list.
This module provides a Key
-Value
dictionary.
An orddict
is a representation of a dictionary, where a
list of pairs is used to store the keys and values. The list is
ordered after the keys in the Erlang term order.
This module provides the same interface as the
dict(3)
module
but with a defined representation. One difference is
that while dict
considers two keys as different if they
do not match (=:=
), this module considers two keys as
different if and only if they do not compare equal (==
).
Types
orddict(Key, Value) = [{Key, Value}]
Dictionary as returned by
new/0
.
orddict() = orddict(term(), term())
Functions
append(Key, Value, Orddict1) -> Orddict2
Orddict1 = Orddict2 = orddict(Key, Value)
Appends a new
to the current list
of values associated with
. An exception is
generated if the initial value associated with
is not a list of values.
See also section Notes.
append_list(Key, ValList, Orddict1) -> Orddict2
ValList = [Value]
Orddict1 = Orddict2 = orddict(Key, Value)
Appends a list of values
to
the current list of values associated with
.
An exception is generated if the initial value associated with
is not a list of values.
See also section Notes.
erase(Key, Orddict1) -> Orddict2
Orddict1 = Orddict2 = orddict(Key, Value)
Erases all items with a specified key from a dictionary.
fetch(Key, Orddict) -> Value
Orddict = orddict(Key, Value)
Returns the value associated with
in dictionary
. This function assumes that
the
is present in the dictionary. An exception
is generated if
is not in the dictionary.
See also section Notes.
fetch_keys(Orddict) -> Keys
Orddict = orddict(Key, Value :: term())
Keys = [Key]
Returns a list of all keys in a dictionary.
take(Key, Orddict) -> {Value, Orddict1} | error
Orddict = Orddict1 = orddict(Key, Value)
Key = Value = term()
This function returns value from dictionary and new dictionary without this value.
Returns error
if the key is not present in the dictionary.
filter(Pred, Orddict1) -> Orddict2
Pred = fun((Key, Value) -> boolean())
Orddict1 = Orddict2 = orddict(Key, Value)
is a dictionary of all keys and values
in
for which
is
true
.
find(Key, Orddict) -> {ok, Value} | error
Orddict = orddict(Key, Value)
Searches for a key in a dictionary. Returns
{ok,
, where
is
the value associated with
, or error
if
the key is not present in the dictionary.
See also section Notes.
fold(Fun, Acc0, Orddict) -> Acc1
Fun = fun((Key, Value, AccIn) -> AccOut)
Orddict = orddict(Key, Value)
Acc0 = Acc1 = AccIn = AccOut = Acc
Calls
on successive keys and values of
together with an extra argument Acc
(short for accumulator).
must return a new
accumulator that is passed to the next call.
is returned if the list is empty.
from_list(List) -> Orddict
List = [{Key, Value}]
Orddict = orddict(Key, Value)
Converts the
-
list
to a dictionary.
is_empty(Orddict) -> boolean()
Orddict = orddict()
Returns true
if
has no elements,
otherwise false
.
is_key(Key, Orddict) -> boolean()
Orddict = orddict(Key, Value :: term())
Tests if
is contained in
dictionary
.
map(Fun, Orddict1) -> Orddict2
Calls
on successive keys and values of
tvo return a new value for each key.
merge(Fun, Orddict1, Orddict2) -> Orddict3
Fun = fun((Key, Value1, Value2) -> Value)
Orddict1 = orddict(Key, Value1)
Orddict2 = orddict(Key, Value2)
Orddict3 = orddict(Key, Value)
Merges two dictionaries,
and
, to create a new dictionary. All the
-
pairs from both
dictionaries are included in the new dictionary. If a key occurs in
both dictionaries,
is called with the key and
both values to return a new value.
merge/3
can be defined as follows, but is faster:
merge(Fun, D1, D2) -> fold(fun (K, V1, D) -> update(K, fun (V2) -> Fun(K, V1, V2) end, V1, D) end, D2, D1).
new() -> orddict()
Creates a new dictionary.
store(Key, Value, Orddict1) -> Orddict2
Orddict1 = Orddict2 = orddict(Key, Value)
Stores a
-
pair in a
dictionary. If the
already exists in
,
the associated value is replaced by
.
to_list(Orddict) -> List
Orddict = orddict(Key, Value)
List = [{Key, Value}]
Converts a dictionary to a list representation.
update(Key, Fun, Orddict1) -> Orddict2
Fun = fun((Value1 :: Value) -> Value2 :: Value)
Orddict1 = Orddict2 = orddict(Key, Value)
Updates a value in a dictionary by calling
on the value to get a new value. An exception is generated if
is not present in the dictionary.
update(Key, Fun, Initial, Orddict1) -> Orddict2
Initial = Value
Fun = fun((Value1 :: Value) -> Value2 :: Value)
Orddict1 = Orddict2 = orddict(Key, Value)
Updates a value in a dictionary by calling
on the value to get a new value. If
is not
present in the dictionary,
is stored as
the first value. For example, append/3
can be defined
as follows:
append(Key, Val, D) -> update(Key, fun (Old) -> Old ++ [Val] end, [Val], D).
update_counter(Key, Increment, Orddict1) -> Orddict2
Orddict1 = Orddict2 = orddict(Key, Value)
Increment = number()
Adds
to the value associated with
and store this value. If
is not present in
the dictionary,
is stored as
the first value.
This can be defined as follows, but is faster:
update_counter(Key, Incr, D) -> update(Key, fun (Old) -> Old + Incr end, Incr, D).
Notes
Functions append/3
and append_list/3
are included
so that keyed values can be stored in a list accumulator, for
example:
> D0 = orddict:new(), D1 = orddict:store(files, [], D0), D2 = orddict:append(files, f1, D1), D3 = orddict:append(files, f2, D2), D4 = orddict:append(files, f3, D3), orddict:fetch(files, D4). [f1,f2,f3]
This saves the trouble of first fetching a keyed value, appending a new value to the list of stored values, and storing the result.
Function fetch/2
is to be used if the key is known to
be in the dictionary, otherwise function find/2
.