Module proplists
An implementation of the Erlang/OTP proplists interface.
Description
This module implements a strict subset of the Erlang/OTP proplists interface.
Data Types
property()
property() = atom() | {term(), term()}
Function Index
compact/1 | Minimizes the representation of all entries in the list. |
delete/2 | Deletes all entries associated with Key from List . |
from_map/1 | Converts the map Map to a property list. |
get_all_values/2 | Similar to get_value/2 , but returns the list of values for _all_ entries
{Key, Value} in List . |
get_bool/2 | Returns the value of a boolean key/value option. |
get_value/2 | Get a value from a property list. |
get_value/3 | Get a value from a property list. |
is_defined/2 | Returns true if List contains at least one entry associated with Key , otherwise
false . |
lookup/2 | Returns the first entry associated with Key in List , if one exists,
otherwise returns none . |
lookup_all/2 | Returns the list of all entries associated with Key in List . |
property/1 | Creates a normal form (minimal) representation of a property. |
property/2 | Creates a normal form (minimal) representation of a simple key/value property. |
to_map/1 | Converts the property list List to a map. |
unfold/1 | Unfolds all occurrences of atoms in ListIn to tuples {Atom, true} . |
Function Details
compact/1
compact(ListIn) -> ListOut
ListIn = [property()]
ListOut = [property()]
ListIn
: the list will be compacted, such as [{key, true}]
returns: the compacted list, such as [key]
Minimizes the representation of all entries in the list. This is equivalent to
[property(P) || P <- ListIn]
.
See also property/1
, unfold/1
.
delete/2
delete(Key, List) -> List
Key = term()
List = [term()]
Key
: the item key that will be deletedList
: the property list from which items will be deleted
returns: A list without items having key Key
Deletes all entries associated with Key
from List
.
from_map/1
from_map(Map) -> List
Map = #{Key => Value}
List = [{Key, Value}]
Key = term()
Value = term()
Map
: the map that will be converted, such as #{key => true}
returns: the map converted to list, such as [{key, true}]
Converts the map Map
to a property list.
get_all_values/2
get_all_values(Key, List) -> [term()]
Key = term()
List = [term()]
Key
: the key with which to find the valuesList
: the property list from which to get the value
returns: a list of values for all entries having Key
as key
Similar to get_value/2
, but returns the list of values for all entries
{Key, Value}
in List
. If no such entry exists, the result is the empty list.
get_bool/2
get_bool(Key, List) -> boolean()
Key = term()
List = [term()]
Key
: the key that will be searchedList
: the list where key is searched
returns: true
when exists an option with given key that is true
, otherwise false
Returns the value of a boolean key/value option. If
lookup(Key, List)
would yield {Key, true}
, this function
returns true
, otherwise false
.
See also get_value/2
, lookup/2
.
get_value/2
get_value(Key::term(), List::[property()]) -> term() | true | undefined
Equivalent to get_value(Key, List, undefined)
.
Get a value from a property list.
get_value/3
get_value(Key::term(), List::[property()], Default::term()) -> term()
Key
: the key with which to find the valueList
: the property list from which to get the valueDefault
: the default value to return, if Key is not in the property list.
returns: the value in the property list under the key, or Default, if Key is not in List.
Get a value from a property list.
Returns the value under the specified key, or the specified Default, if the Key is not in the supplied List. If the Key corresponds to an entry in the property list that is just a single atom, this function returns the atom true.
is_defined/2
is_defined(Key, List) -> boolean()
Key = term()
List = [term()]
Key
: the key that will be searchedList
: the list where key is searched
returns: true
if Key
is defined, otherwise false
Returns true
if List
contains at least one entry associated with Key
, otherwise
false
.
lookup/2
lookup(Key, List) -> none | tuple()
Key = term()
List = [term()]
Key
: the key with which to find the entryList
: the property list from which to get the entry
returns: Either the found entry (always as a tuple) or none
Returns the first entry associated with Key
in List
, if one exists,
otherwise returns none
. For an atom A
in the list, the tuple {A, true}
is
the entry associated with A
.
See also get_bool/2
, get_value/2
, lookup_all/2
.
lookup_all/2
lookup_all(Key, List) -> [tuple()]
Key = term()
List = [term()]
Key
: the key with which to find the entriesList
: the property list from which to get the entries
returns: all entries having Key
as key
Returns the list of all entries associated with Key
in List
. If no such
entry exists, the result is the empty list.
See also lookup/2
.
property/1
property(PropertyIn) -> PropertyOut
PropertyIn = property()
PropertyOut = property()
PropertyIn
: a property
returns: the same property in normal form
Creates a normal form (minimal) representation of a property. If PropertyIn
is
{Key, true}
, where Key
is an atom, Key
is returned, otherwise the whole
term PropertyIn
is returned.
See also property/2
.
property/2
property(Key, Value) -> Property
Key = term()
Value = term()
Property = atom() | {term(), term()}
Key
: the property keyValue
: the property value
returns: Creates a property in normal form
Creates a normal form (minimal) representation of a simple key/value property.
Returns Key
if Value
is true
and Key
is an atom, otherwise a tuple
{Key, Value}
is returned.
See also property/1
.
to_map/1
to_map(List) -> Map
List = [Shorthand | {Key, Value} | term()]
Map = #{Shorthand => true, Key => Value}
Shorthand = atom()
Key = term()
Value = term()
List
: the list will be converted to a map, such as [key, {one, 1}]
returns: the list converted as a map, such as #{key => true, one => 1}
Converts the property list List
to a map
Shorthand atom values in List
will be expanded to an association of the form
Atom => true
. Tuples of the form {Key, Value}
in List
will be converted to
an association of the form Key => Value
. Anything else will be silently
ignored.
If the same key appears in List
multiple times, the value of the one appearing
nearest to the head of List
will be in the result map, that is the value that
would be returned by a call to get_value(Key, List)
.
unfold/1
unfold(ListIn) -> ListOut
ListIn = [term()]
ListOut = [term()]
ListIn
: the list that will be unfolded, such as [key]
returns: the unfolded list, such as {key, true}
Unfolds all occurrences of atoms in ListIn
to tuples {Atom, true}
.