From 229d0d8ca88bc344bed89e46541b325c1d267996 Mon Sep 17 00:00:00 2001 From: Hans Bolinder Date: Fri, 6 May 2011 15:58:09 +0200 Subject: r Use Erlang specs and types for documentation --- lib/stdlib/doc/src/qlc.xml | 646 ++++++++++++++++++++------------------------- 1 file changed, 287 insertions(+), 359 deletions(-) (limited to 'lib/stdlib/doc/src/qlc.xml') diff --git a/lib/stdlib/doc/src/qlc.xml b/lib/stdlib/doc/src/qlc.xml index da24ee9914..6a45ade447 100644 --- a/lib/stdlib/doc/src/qlc.xml +++ b/lib/stdlib/doc/src/qlc.xml @@ -4,7 +4,7 @@
- 20042009 + 20042011 Ericsson AB. All Rights Reserved. @@ -45,7 +45,9 @@ tables. Typical QLC tables are ETS, Dets, and Mnesia tables. There is also support for user defined tables, see the Implementing a QLC - table section. A query is stated using + table section. + A query is stated using Query List Comprehensions (QLCs). The answers to a query are determined by data in QLC tables that fulfill the constraints expressed by the QLCs of the query. QLCs are similar @@ -55,10 +57,11 @@ fact, in the absence of optimizations and options such as cache and unique (see below), every QLC free of QLC tables evaluates to the same list of answers as the - identical ordinary list comprehension.

+ identical ordinary list comprehension.

While ordinary list comprehensions evaluate to lists, calling - qlc:q/1,2 returns a Query + qlc:q/1,2 returns a Query Handle. To obtain all the answers to a query, qlc:eval/1,2 should be called with the query handle as first argument. Query handles are essentially @@ -69,7 +72,8 @@ Code replacement is described in the Erlang Reference Manual. The list of answers can also be traversed in - chunks by use of a Query Cursor. Query cursors are + chunks by use of a Query Cursor. Query cursors are created by calling qlc:cursor/1,2 with a query handle as first argument. Query cursors are essentially Erlang processes. @@ -226,75 +230,6 @@ -

Common data types - - -

QueryCursor = {qlc_cursor, term()}

-
-

QueryHandle = {qlc_handle, term()}

-
-

QueryHandleOrList = QueryHandle | list()

-
-

Answers = [Answer]

-
-

Answer = term()

-
-

AbstractExpression =  - parse trees - for Erlang expressions, see the abstract format - documentation in the ERTS User's Guide -

-
-

MatchExpression =  - - match specifications, see the match specification - documentation in the ERTS User's Guide and ms_transform(3) -

-
-

SpawnOptions = default | spawn_options()

-
-

SortOptions = [SortOption] | SortOption

-
-

SortOption = {compressed, bool()} - | {no_files, NoFiles} - | {order, Order} - | {size, Size} - | {tmpdir, TempDirectory} - | {unique, bool()}  - - see file_sorter(3) -

-
-

Order = ascending | descending | OrderFun

-
-

OrderFun = fun(term(), term()) -> bool()

-
-

TempDirectory = "" | filename()

-
-

Size = int() > 0

-
-

NoFiles = int() > 1

-
-

KeyPos = int() > 0 | [int() > 0]

-
-

MaxListSize = int() >= 0

-
-

bool() = true | false

-
-

Cache = ets | list | no

-
-

TmpFileUsage = allowed | not_allowed | info_msg - | warning_msg | error_msg

-
-

filename() =  - see filename(3) -

-
-

spawn_options() =  - see erlang(3) -

-
- -
- -
-
Getting started

As already mentioned @@ -679,34 +614,105 @@ ets:match_spec_run(ets:lookup(86033, {2,2}),

+ + + +

Parse trees for Erlang expression, see the abstract format + documentation in the ERTS User's Guide.

+
+ + + + + + + + + + + +

Match specification, see the match specification + documentation in the ERTS User's Guide and ms_transform(3).

+
+ + +

Actually an integer > 1.

+
+ + + + + + + + + + + + + + +

A query cursor.

+
+
+ + +

A query handle.

+
+
+ + + + + +

A literal + query + list comprehension.

+
+ + + + + + + + +

See file_sorter(3).

+
+ + + + + +

+
+
+ - append(QHL) -> QH + Return a query handle. - - QHL = [QueryHandleOrList] - QH = QueryHandle -

Returns a query handle. When evaluating the query handle - QH all answers to the first query handle in - QHL is returned followed by all answers to the rest - of the query handles in QHL.

+ QH all answers to the first query handle in + QHL are returned followed by all answers + to the rest of the query handles in QHL.

- append(QH1, QH2) -> QH3 + Return a query handle. - - QH1 = QH2 = QueryHandleOrList - QH3 = QueryHandle -

Returns a query handle. When evaluating the query handle - QH3 all answers to QH1 are returned followed - by all answers to QH2.

+ QH3 all answers to + QH1 are returned followed by all answers + to QH2.

append(QH1, QH2) is equivalent to append([QH1, QH2]).

@@ -714,17 +720,9 @@ ets:match_spec_run(ets:lookup(86033, {2,2}),
- cursor(QueryHandleOrList [, Options]) -> QueryCursor + + Create a query cursor. - - Options = [Option] | Option - Option = {cache_all, Cache} | cache_all - | {max_list_size, MaxListSize} - | {spawn_options, SpawnOptions} - | {tmpdir_usage, TmpFileUsage} - | {tmpdir, TempDirectory} - | {unique_all, bool()} | unique_all -

Creates a query cursor and makes the calling process the owner of the cursor. The @@ -746,11 +744,13 @@ ets:match_spec_run(ets:lookup(86033, {2,2}), [{b,1},{b,2}] 4> qlc:delete_cursor(QC). ok +

cursor(QH) is equivalent to + cursor(QH, []).

- delete_cursor(QueryCursor) -> ok + Delete a query cursor.

Deletes a query cursor. Only the owner of the cursor can @@ -759,19 +759,11 @@ ok - eval(QueryHandleOrList [, Options]) -> Answers | Error - e(QueryHandleOrList [, Options]) -> Answers + + + + Return all answers to a query. - - Options = [Option] | Option - Option = {cache_all, Cache} | cache_all - | {max_list_size, MaxListSize} - | {tmpdir_usage, TmpFileUsage} - | {tmpdir, TempDirectory} - | {unique_all, bool()} | unique_all - Error = {error, module(), Reason} - Reason = - as returned by file_sorter(3) - -

Evaluates a query handle in the calling process and collects all answers in a list.

@@ -780,47 +772,39 @@ ok 1> QH = qlc:q([{X,Y} || X <- [a,b], Y <- [1,2]]), qlc:eval(QH). [{a,1},{a,2},{b,1},{b,2}] +

eval(QH) is equivalent to + eval(QH, []).

- fold(Function, Acc0, QueryHandleOrList [, Options]) -> - Acc1 | Error + + Fold a function over the answers to a query. - - Function = fun(Answer, AccIn) -> AccOut - Acc0 = Acc1 = AccIn = AccOut = term() - Options = [Option] | Option - Option = {cache_all, Cache} | cache_all - | {max_list_size, MaxListSize} - | {tmpdir_usage, TmpFileUsage} - | {tmpdir, TempDirectory} - | {unique_all, bool()} | unique_all - Error = {error, module(), Reason} - Reason = - as returned by file_sorter(3) - - -

Calls Function on successive answers to the query - handle together with an extra argument AccIn. The - query handle and the function are evaluated in the calling - process. Function must return a new accumulator which - is passed to the next call. Acc0 is returned if there - are no answers to the query handle.

+

Calls Function on successive answers to + the query handle together with an extra argument + AccIn. The query handle and the function + are evaluated in the calling process. + Function must return a new accumulator + which is passed to the next call. + Acc0 is returned if there are no answers + to the query handle.

 1> QH = [1,2,3,4,5,6],
 qlc:fold(fun(X, Sum) -> X + Sum end, 0, QH).
 21
+

fold(Function, Acc0, + QH) is equivalent to + fold(Function, Acc0, + QH, []).

- format_error(Error) -> Chars + Return an English description of a an error tuple. - - Error = {error, module(), term()} - Chars = [char() | Chars] -

Returns a descriptive string in English of an error tuple returned by some of the functions of the qlc module @@ -830,25 +814,9 @@ ok - info(QueryHandleOrList [, Options]) -> Info + + Return code describing a query handle. - - Options = [Option] | Option - Option = EvalOption | ReturnOption - EvalOption = {cache_all, Cache} | cache_all - | {max_list_size, MaxListSize} - | {tmpdir_usage, TmpFileUsage} - | {tmpdir, TempDirectory} - | {unique_all, bool()} | unique_all - ReturnOption = {depth, Depth} - | {flat, bool()} - | {format, Format} - | {n_elements, NElements} - Depth = infinity | int() >= 0 - Format = abstract_code | string - NElements = infinity | int() > 0 - Info = AbstractExpression | string() -

Returns information about a query handle. The information describes the simplifications @@ -879,18 +847,18 @@ ok io:format("~s~n", [qlc:info(QH, unique_all)]). begin V1 = - qlc:q([ + qlc:q([ SQV || SQV <- [x,y] ], [{unique,true}]), V2 = - qlc:q([ + qlc:q([ SQV || SQV <- [a,b] ], [{unique,true}]), - qlc:q([ + qlc:q([ {X,Y} || X <- V1, Y <- V2 @@ -913,19 +881,19 @@ end io:format("~s~n", [qlc:info(Q)]). begin V1 = - qlc:q([ + qlc:q([ P0 || P0 = {W,Y} <- ets:table(17) ]), V2 = - qlc:q([ + qlc:q([ [G1|G2] || G2 <- V1, G1 <- ets:table(16), element(2, G1) =:= element(1, G2) ], [{join,lookup}]), - qlc:q([ + qlc:q([ {X,Z,W} || [{X,Z}|{W,Y}] <- V2 ]) @@ -936,44 +904,43 @@ end method chosen. A convention is used for lookup join: the first generator (G2) is the one traversed, the second one (G1) is the table where constants are looked up.

+ +

info(QH) is equivalent to + info(QH, []).

- keysort(KeyPos, QH1 [, SortOptions]) -> QH2 + + Return a query handle. - - QH1 = QueryHandleOrList - QH2 = QueryHandle -

Returns a query handle. When evaluating the query handle - QH2 the answers to the query handle QH1 are - sorted by QH2 the answers to the query handle + QH1 are sorted by file_sorter:keysort/4 according to the options.

-

The sorter will use temporary files only if QH1 does - not evaluate to a list and the size of the binary - representation of the answers exceeds Size bytes, - where Size is the value of the size option.

+

The sorter will use temporary files only if + QH1 does not evaluate to a list and the + size of the binary representation of the answers exceeds + Size bytes, where Size is the value of the + size option.

+ +

keysort(KeyPos, QH1) + is equivalent to + keysort(KeyPos, QH1, []).

- next_answers(QueryCursor [, NumberOfAnswers]) -> - Answers | Error + + Return some or all answers to a query. - - NumberOfAnswers = all_remaining | int() > 0 - Error = {error, module(), Reason} - Reason = - as returned by file_sorter(3) - -

Returns some or all of the remaining answers to a query - cursor. Only the owner of Cursor can retrieve - answers.

- + cursor. Only the owner of QueryCursor can + retrieve answers.

The optional argument NumberOfAnswersdetermines the maximum number of answers returned. The default value is 10. If less than the requested number of answers is @@ -983,21 +950,9 @@ end - q(QueryListComprehension [, Options]) -> QueryHandle + + Return a handle for a query list comprehension. - - QueryListComprehension =  - - literal query listcomprehension - - Options = [Option] | Option - Option = {max_lookup, MaxLookup} - | {cache, Cache} | cache - | {join, Join} - | {lookup, Lookup} - | {unique, bool()} | unique - MaxLookup = int() >= 0 | infinity - Join = any | lookup | merge | nested_loop - Lookup = bool() | any -

Returns a query handle for a query list comprehension. The query list comprehension must be the @@ -1024,7 +979,7 @@ end

 ...
-A = [X || {X} <- [{1},{2}]], 
+A = [X || {X} <- [{1},{2}]],
 QH = qlc:q(A),
 ...
@@ -1034,6 +989,9 @@ QH = qlc:q(A), list comprehension"); the shell process stops with a badarg reason.

+

q(QLC) is equivalent to + q(QLC, []).

+

The {cache, ets} option can be used to cache the answers to a query list comprehension. The answers are stored in one ETS table for each cached query list @@ -1092,26 +1050,26 @@ QH = qlc:q(A), io:format("~s~n", [qlc:info(Q)]). begin V1 = - qlc:q([ + qlc:q([ P0 || P0 = {X,Z} <- qlc:keysort(1, [{a,1},{b,4},{c,6}], []) ]), V2 = - qlc:q([ + qlc:q([ P0 || P0 = {W,Y} <- qlc:keysort(2, [{2,a},{3,b},{4,c}], []) ]), V3 = - qlc:q([ + qlc:q([ [G1|G2] || G1 <- V1, G2 <- V2, element(1, G1) == element(2, G2) ], [{join,merge},{cache,list}]), - qlc:q([ + qlc:q([ {A,X,Z,W} || A <- [a,b,c], [{X,Z}|{W,Y}] <- V3, @@ -1170,7 +1128,7 @@ ets:match_spec_run( elements of the key {X, Y} are compared separately.

The {lookup, true} option can be used to ensure - that the qlc module will look up constants in some + that the qlc module will look up constants in some QLC table. If there are more than one QLC table among the generators' list expressions, constants have to be looked up in at least one @@ -1190,7 +1148,7 @@ ets:match_spec_run( {join, nested_loop} invokes the method of matching every pair of objects from two handles. The last method is mostly very slow. The evaluation of the query - fails if the qlc module cannot carry out the chosen + fails if the qlc module cannot carry out the chosen join method. The default value is any which means that some fast join method will be used if possible.

@@ -1198,47 +1156,33 @@ ets:match_spec_run(
- sort(QH1 [, SortOptions]) -> QH2 + + Return a query handle. - - QH1 = QueryHandleOrList - QH2 = QueryHandle -

Returns a query handle. When evaluating the query handle - QH2 the answers to the query handle QH1 are - sorted by QH2 the answers to the query handle + QH1 are sorted by file_sorter:sort/3 according to the options.

-

The sorter will use temporary files only if QH1 does - not evaluate to a list and the size of the binary - representation of the answers exceeds Size bytes, - where Size is the value of the size option.

+

The sorter will use temporary files only if + QH1 does not evaluate to a list and the + size of the binary representation of the answers exceeds + Size bytes, where Size is the value of the + size option.

+ +

sort(QH1) is equivalent to + sort(QH1, []).

+
- string_to_handle(QueryString [, Options [, Bindings]]) -> - QueryHandle | Error + + + Return a handle for a query list comprehension. - - QueryString = string() - Options = [Option] | Option - Option = {max_lookup, MaxLookup} - | {cache, Cache} | cache - | {join, Join} - | {lookup, Lookup} - | {unique, bool()} | unique - MaxLookup = int() >= 0 | infinity - Join = any | lookup | merge | nested_loop - Lookup = bool() | any - Bindings = - as returned by - erl_eval:bindings/1 - - Error = {error, module(), Reason} - Reason =  - ErrorInfo as returned by - erl_scan:string/1 or erl_parse:parse_exprs/1 - -

A string version of qlc:q/1,2. When the query handle is evaluated the fun created by the parse transform is @@ -1253,57 +1197,24 @@ ets:match_spec_run( qlc:eval(QH). [2,3,4] +

string_to_handle(QueryString) + is equivalent to + string_to_handle(QueryString, []).

+ +

string_to_handle(QueryString, + Options) + is equivalent to + string_to_handle(QueryString, + Options, erl_eval:new_bindings()).

+

This function is probably useful mostly when called from outside of Erlang, for instance from a driver written in C.

- table(TraverseFun, Options) -> QueryHandle + Return a query handle for a table. - - TraverseFun = TraverseFun0 | TraverseFun1 - TraverseFun0 = fun() -> TraverseResult - TraverseFun1 = fun(MatchExpression) -> 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, MatchExpression} - | {lookup, Position, Keys} - | {lookup, Position, Keys, NElements, DepthFun} - NElements = infinity | int() > 0 - DepthFun = fun(term()) -> term() - FormatedTable = {Mod, Fun, Args} - | AbstractExpression - | character_list() - 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() -> void() - PreFun = undefined | fun([PreArg]) -> void() - PreArg = {parent_value, ParentFunValue} | {stop_fun, StopFun} - ParentFunValue = undefined | term() - StopFun = undefined | fun() -> void() - KeyComparison = '=:=' | '==' - Position = int() > 0 - Keys = [term()] - Mod = Fun = atom() - Args = [term()] -

Returns a query handle for a QLC table. In Erlang/OTP there is support for ETS, Dets and @@ -1315,77 +1226,90 @@ ets:match_spec_run( as well as properties of the table are handled by callback functions provided as options to qlc:table/2.

-

The callback function TraverseFun is used for - traversing the table. It is to return a list of objects - terminated by either [] or a nullary fun to be used - for traversing the not yet traversed objects of the table. - Any other return value is immediately returned as value of - the query evaluation. Unary TraverseFuns are to - accept a match specification as argument. The match - specification is created by the parse transform by analyzing - the pattern of the generator calling qlc:table/2 and - filters using variables introduced in the pattern. If the - parse transform cannot find a match specification equivalent - to the pattern and filters, TraverseFun will be - called with a match specification returning every object. - Modules that can utilize match specifications for optimized +

The callback function TraverseFun is + used for traversing the table. It is to return a list of + objects terminated by either [] or a nullary fun to + be used for traversing the not yet traversed objects of the + table. Any other return value is immediately returned as + value of the query evaluation. Unary + TraverseFuns are to accept a match + specification as argument. The match specification is + created by the parse transform by analyzing the pattern of + the generator calling qlc:table/2 and filters using + variables introduced in the pattern. If the parse transform + cannot find a match specification equivalent to the pattern + and filters, TraverseFun will be called + with a match specification returning every object. Modules + that can utilize match specifications for optimized traversal of tables should call qlc:table/2 with a - unary TraverseFun while other modules can provide a - nullary TraverseFun. ets:table/2 is an example - of the former; gb_table:table/1 in the Implementing a QLC - table section is an example of the latter.

- -

PreFun is a unary callback function that is called - once before the table is read for the first time. If the - call fails, the query evaluation fails. Similarly, the - nullary callback function PostFun is called once - after the table was last read. The return value, which is - caught, is ignored. If PreFun has been called for a - table, PostFun is guaranteed to be called for that - table, even if the evaluation of the query fails for some - reason. The order in which pre (post) functions for + unary + TraverseFun while other modules can + provide a nullary + TraverseFun. ets:table/2 is an + example of the former; gb_table:table/1 in the + Implementing a + QLC table section is an example of the latter.

+ +

PreFun is a unary callback function + that is called once before the table is read for the first + time. If the call fails, the query evaluation fails. + Similarly, the nullary callback function + PostFun is called once after the table + was last read. The return value, which is caught, is + ignored. If PreFun has been called for a + table, + PostFun is guaranteed to be called for + that table, even if the evaluation of the query fails for + some reason. The order in which pre (post) functions for different tables are evaluated is not specified. Other table - access than reading, such as calling InfoFun, is - assumed to be OK at any time. The argument PreArgs is - a list of tagged values. Currently there are two tags, + access than reading, such as calling + InfoFun, is assumed to be OK at any + time. The argument PreArgs is a list of + tagged values. Currently there are two tags, parent_value and stop_fun, used by Mnesia for managing transactions. The value of parent_value is - the value returned by ParentFun, or undefined - if there is no ParentFun. ParentFun is called - once just before the call of PreFun in the context of - the process calling eval, fold, or + the value returned by ParentFun, or + undefined if there is no ParentFun. + ParentFun is called once just before the + call of + PreFun in the context of the process + calling + eval, fold, or cursor. The value of stop_fun is a nullary fun that deletes the cursor if called from the parent, or undefined if there is no cursor.

The binary callback - function LookupFun is used for looking up objects in - the table. The first argument Position is the key - position or an indexed position and the second argument - Keys is a sorted list of unique values. The return - value is to be a list of all objects (tuples) such that the - element at Position is a member of Keys. Any - other return value is immediately returned as value of the - query evaluation. LookupFun is called instead of + function LookupFun is used for looking + up objects in the table. The first argument + Position is the key position or an + indexed position and the second argument + Keys is a sorted list of unique values. + The return value is to be a list of all objects (tuples) + such that the element at Position is a member of + Keys. Any other return value is + immediately returned as value of the query evaluation. + LookupFun is called instead of traversing the table if the parse transform at compile time can find out that the filters match and compare the element - at Position in such a way that only Keys need - to be looked up in order to find all potential answers. The - key position is obtained by calling InfoFun(keypos) - and the indexed positions by calling - InfoFun(indices). If the key position can be used for - lookup it is always chosen, otherwise the indexed position - requiring the least number of lookups is chosen. If there is - a tie between two indexed positions the one occurring first - in the list returned by InfoFun is chosen. Positions - requiring more than max_lookup lookups are - ignored.

- -

The unary callback function InfoFun is to return - information about the table. undefined should be - returned if the value of some tag is unknown:

+ at Position in such a way that only + Keys need to be looked up in order to + find all potential answers. The key position is obtained by + calling + InfoFun(keypos) and the indexed + positions by calling + InfoFun(indices). If the key position + can be used for lookup it is always chosen, otherwise the + indexed position requiring the least number of lookups is + chosen. If there is a tie between two indexed positions the + one occurring first in the list returned by + InfoFun is chosen. Positions requiring + more than max_lookup + lookups are ignored.

+ +

The unary callback function InfoFun is + to return information about the table. undefined + should be returned if the value of some tag is unknown:

indices. Returns a list of indexed @@ -1406,20 +1330,22 @@ ets:match_spec_run( -

The unary callback function FormatFun is used by - qlc:info/1,2 for - displaying the call that created the table's query handle. - The default value, undefined, means that +

The unary callback function FormatFun + is used by qlc:info/1,2 + for displaying the call that created the table's query + handle. The default value, undefined, means that info/1,2 displays a call to '$MOD':'$FUN'/0. - It is up to FormatFun to present the selected objects - of the table in a suitable way. However, if a character list - is chosen for presentation it must be an Erlang expression - that can be scanned and parsed (a trailing dot will be added - by qlc:info though). FormatFun is called with - an argument that describes the selected objects based on - optimizations done as a result of analyzing the filters of - the QLC where the call to qlc:table/2 occurs. The - possible values of the argument are:

+ It is up to FormatFun to present the + selected objects of the table in a suitable way. However, if + a character list is chosen for presentation it must be an + Erlang expression that can be scanned and parsed (a trailing + dot will be added by qlc:info though). + FormatFun is called with an argument + that describes the selected objects based on optimizations + done as a result of analyzing the filters of the QLC where + the call to + qlc:table/2 occurs. The possible values of the + argument are:

{lookup, Position, Keys, NElements, DepthFun}. @@ -1443,10 +1369,12 @@ ets:match_spec_run( can be used for limiting the size of terms; calling DepthFun(Term) substitutes '...' for parts of Term below the depth specified by the info/1,2 - option depth. If calling FormatFun with an - argument including NElements and DepthFun - fails, FormatFun is called once again with an - argument excluding NElements and DepthFun + option depth. If calling + FormatFun with an argument including + NElements and DepthFun fails, + FormatFun is called once again with an + argument excluding + NElements and DepthFun ({lookup, Position, Keys} or all).

@@ -1458,7 +1386,7 @@ ets:match_spec_run(

See ets(3), dets(3) and - mnesia(3) + mnesia(3) for the various options recognized by table/1,2 in respective module.

@@ -1472,12 +1400,12 @@ ets:match_spec_run( Erlang Reference Manual, erl_eval(3), - erlang(3), + erlang(3), ets(3), - file(3), - error_logger(3), + file(3), + error_logger(3), file_sorter(3), - mnesia(3), + mnesia(3), Programming Examples, shell(3)

-- cgit v1.2.3