diff options
Diffstat (limited to 'lib/stdlib/doc')
-rw-r--r-- | lib/stdlib/doc/src/beam_lib.xml | 1 | ||||
-rw-r--r-- | lib/stdlib/doc/src/dets.xml | 4 | ||||
-rw-r--r-- | lib/stdlib/doc/src/ets.xml | 141 | ||||
-rw-r--r-- | lib/stdlib/doc/src/filename.xml | 2 | ||||
-rw-r--r-- | lib/stdlib/doc/src/io_protocol.xml | 2 | ||||
-rw-r--r-- | lib/stdlib/doc/src/lists.xml | 2 | ||||
-rw-r--r-- | lib/stdlib/doc/src/sofs.xml | 2 | ||||
-rw-r--r-- | lib/stdlib/doc/src/timer.xml | 25 |
8 files changed, 152 insertions, 27 deletions
diff --git a/lib/stdlib/doc/src/beam_lib.xml b/lib/stdlib/doc/src/beam_lib.xml index 27308e02f3..adc411e272 100644 --- a/lib/stdlib/doc/src/beam_lib.xml +++ b/lib/stdlib/doc/src/beam_lib.xml @@ -341,6 +341,7 @@ chunkref() = chunkname() | chunkid()</code> <v>Beam1 = Beam2 = beam()</v> <v>Reason = {modules_different, Module1, Module2}</v> <v> | {chunks_different, ChunkId}</v> + <v> | different_chunks</v> <v> | Reason1 -- see info/1</v> <v> Module1 = Module2 = atom()</v> <v> ChunkId = chunkid()</v> diff --git a/lib/stdlib/doc/src/dets.xml b/lib/stdlib/doc/src/dets.xml index 8d1398d3b7..ad100d2cf5 100644 --- a/lib/stdlib/doc/src/dets.xml +++ b/lib/stdlib/doc/src/dets.xml @@ -109,7 +109,7 @@ bool() = true | false file() = string() int() = integer() >= 0 keypos() = integer() >= 1 -name() = atom() | ref() +name() = atom() | reference() no_slots() = integer() >= 0 | default object() = tuple() object_cont() = tuple() @@ -759,7 +759,7 @@ ok <fsummary>Open an existing Dets table.</fsummary> <type> <v>FileName = file()</v> - <v>Reference = ref()</v> + <v>Reference = reference()</v> </type> <desc> <p>Opens an existing table. If the table has not been properly diff --git a/lib/stdlib/doc/src/ets.xml b/lib/stdlib/doc/src/ets.xml index ee1befc882..dd4a289c61 100644 --- a/lib/stdlib/doc/src/ets.xml +++ b/lib/stdlib/doc/src/ets.xml @@ -1039,15 +1039,22 @@ ets:select(Table,MatchSpec),</code> the owner terminates.</p> </item> <item> + <marker id="new_2_write_concurrency"></marker> <p><c>{write_concurrency,bool()}</c> - Performance tuning. Default is <c>false</c>, which means that the table - is optimized towards concurrent read access. An operation that + Performance tuning. Default is <c>false</c>. An operation that mutates (writes to) the table will obtain exclusive access, blocking any concurrent access of the same table until finished. If set to <c>true</c>, the table is optimized towards concurrent write access. Different objects of the same table can be mutated (and read) by concurrent processes. This is achieved to some degree at the expense of single access and concurrent reader performance. + The <c>write_concurrency</c> option can be combined with the + <seealso marker="#new_2_read_concurrency">read_concurrency</seealso> + option. You typically want to combine these when large concurrent + read bursts and large concurrent write bursts are common (see the + documentation of the + <seealso marker="#new_2_read_concurrency">read_concurrency</seealso> + option for more information). Note that this option does not change any guarantees about <seealso marker="#concurrency">atomicy and isolation</seealso>. Functions that makes such promises over several objects (like @@ -1055,6 +1062,29 @@ ets:select(Table,MatchSpec),</code> <p>Table type <c>ordered_set</c> is not affected by this option in current implementation.</p> </item> + <item> + <marker id="new_2_read_concurrency"></marker> + <p><c>{read_concurrency,bool()}</c> + Performance tuning. Default is <c>false</c>. When set to + <c>true</c>, the table is optimized for concurrent read + operations. When this option is enabled on a runtime system with + SMP support, read operations become much cheaper; especially on + systems with multiple physical processors. However, switching + between read and write operations becomes more expensive. You + typically want to enable this option when concurrent read + operations are much more frequent than write operations, or when + concurrent reads and writes comes in large read and write + bursts (i.e., lots of reads not interrupted by writes, and lots + of writes not interrupted by reads). You typically do + <em>not</em> want to enable this option when the common access + pattern is a few read operations interleaved with a few write + operations repeatedly. In this case you will get a performance + degradation by enabling this option. The <c>read_concurrency</c> + option can be combined with the + <seealso marker="#new_2_write_concurrency">write_concurrency</seealso> + option. You typically want to combine these when large concurrent + read bursts and large concurrent write bursts are common.</p> + </item> </list> </desc> </func> @@ -1355,6 +1385,28 @@ is_integer(X), is_integer(Y), X + Y < 4711]]></code> </desc> </func> <func> + <name>select_count(Tab, MatchSpec) -> NumMatched</name> + <fsummary>Match the objects in an ETS table against a match_spec and returns the number of objects for which the match_spec returned 'true'</fsummary> + <type> + <v>Tab = tid() | atom()</v> + <v>Object = tuple()</v> + <v>MatchSpec = match_spec()</v> + <v>NumMatched = integer()</v> + </type> + <desc> + <p>Matches the objects in the table <c>Tab</c> using a + <seealso marker="#match_spec">match_spec</seealso>. If the + match_spec returns <c>true</c> for an object, that object + considered a match and is counted. For any other result from + the match_spec the object is not considered a match and is + therefore not counted.</p> + <p>The function could be described as a <c>match_delete/2</c> + that does not actually delete any elements, but only counts + them.</p> + <p>The function returns the number of objects matched.</p> + </desc> + </func> + <func> <name>select_delete(Tab, MatchSpec) -> NumDeleted</name> <fsummary>Match the objects in an ETS table against a match_spec and deletes objects where the match_spec returns 'true'</fsummary> <type> @@ -1381,25 +1433,82 @@ is_integer(X), is_integer(Y), X + Y < 4711]]></code> </desc> </func> <func> - <name>select_count(Tab, MatchSpec) -> NumMatched</name> - <fsummary>Match the objects in an ETS table against a match_spec and returns the number of objects for which the match_spec returned 'true'</fsummary> + <name>select_reverse(Tab, MatchSpec) -> [Match]</name> + <fsummary>Match the objects in an ETS table against a match_spec.</fsummary> <type> <v>Tab = tid() | atom()</v> - <v>Object = tuple()</v> + <v>Match = term()</v> <v>MatchSpec = match_spec()</v> - <v>NumMatched = integer()</v> </type> <desc> - <p>Matches the objects in the table <c>Tab</c> using a - <seealso marker="#match_spec">match_spec</seealso>. If the - match_spec returns <c>true</c> for an object, that object - considered a match and is counted. For any other result from - the match_spec the object is not considered a match and is - therefore not counted.</p> - <p>The function could be described as a <c>match_delete/2</c> - that does not actually delete any elements, but only counts - them.</p> - <p>The function returns the number of objects matched.</p> + + <p>Works like <c>select/2</c>, but returns the list in reverse + order for the <c>ordered_set</c> table type. For all other table + types, the return value is identical to that of <c>select/2</c>.</p> + + </desc> + </func> + <func> + <name>select_reverse(Tab, MatchSpec, Limit) -> {[Match],Continuation} | '$end_of_table'</name> + <fsummary>Match the objects in an ETS table against a match_spec and returns part of the answers.</fsummary> + <type> + <v>Tab = tid() | atom()</v> + <v>Match = term()</v> + <v>MatchSpec = match_spec()</v> + <v>Continuation = term()</v> + </type> + <desc> + + <p>Works like <c>select/3</c>, but for the <c>ordered_set</c> + table type, traversing is done starting at the last object in + Erlang term order and moves towards the first. For all other + table types, the return value is identical to that of + <c>select/3</c>.</p> + + <p>Note that this is <em>not</em> equivalent to + reversing the result list of a <c>select/3</c> call, as the result list + is not only reversed, but also contains the last <c>Limit</c> + matching objects in the table, not the first.</p> + + </desc> + </func> + <func> + <name>select_reverse(Continuation) -> {[Match],Continuation} | '$end_of_table'</name> + <fsummary>Continue matching objects in an ETS table.</fsummary> + <type> + <v>Match = term()</v> + <v>Continuation = term()</v> + </type> + <desc> + + <p>Continues a match started with + <c>ets:select_reverse/3</c>. If the table is an + <c>ordered_set</c>, the traversal of the table will continue + towards objects with keys earlier in the Erlang term order. The + returned list will also contain objects with keys in reverse + order.</p> + + <p>For all other table types, the behaviour is exatly that of <c>select/1</c>.</p> + <p>Example:</p> + <code> +1> T = ets:new(x,[ordered_set]). +2> [ ets:insert(T,{N}) || N <- lists:seq(1,10) ]. +... +3> {R0,C0} = ets:select_reverse(T,[{'_',[],['$_']}],4). +... +4> R0. +[{10},{9},{8},{7}] +5> {R1,C1} = ets:select_reverse(C0). +... +6> R1. +[{6},{5},{4},{3}] +7> {R2,C2} = ets:select_reverse(C1). +... +8> R2. +[{2},{1}] +9> '$end_of_table' = ets:select_reverse(C2). +... + </code> </desc> </func> <func> diff --git a/lib/stdlib/doc/src/filename.xml b/lib/stdlib/doc/src/filename.xml index 0cf82fa48b..fe6c6f898e 100644 --- a/lib/stdlib/doc/src/filename.xml +++ b/lib/stdlib/doc/src/filename.xml @@ -49,7 +49,7 @@ <title>DATA TYPES</title> <code type="none"> name() = string() | atom() | DeepList - DeepList = [char() | atom() | DeepList]</code> +DeepList = [char() | atom() | DeepList]</code> </section> <funcs> <func> diff --git a/lib/stdlib/doc/src/io_protocol.xml b/lib/stdlib/doc/src/io_protocol.xml index b52e862a5c..a97d996d98 100644 --- a/lib/stdlib/doc/src/io_protocol.xml +++ b/lib/stdlib/doc/src/io_protocol.xml @@ -79,7 +79,7 @@ sends the reply to.</item> io_reply. The io-module in the Erlang standard library simply uses the pid() of the io_server as the ReplyAs datum, but a more complicated client could have several outstanding io-requests to the same server and -would then use i.e. a ref() or something else to differentiate among +would then use i.e. a reference() or something else to differentiate among the incoming io_reply's. The ReplyAs element should be considered opaque by the io_server. Note that the pid() of the server is not explicitly present in the io_reply. The reply can be sent from any diff --git a/lib/stdlib/doc/src/lists.xml b/lib/stdlib/doc/src/lists.xml index a273a2301f..b3ad7aaf46 100644 --- a/lib/stdlib/doc/src/lists.xml +++ b/lib/stdlib/doc/src/lists.xml @@ -48,7 +48,7 @@ <item><p>if x <c>F</c> y and y <c>F</c> x then x = y (<c>F</c> is antisymmetric);</p> </item> - <item><p>if x <c>F</c> y and and y <c>F</c> z then x <c>F</c> z + <item><p>if x <c>F</c> y and y <c>F</c> z then x <c>F</c> z (<c>F</c> is transitive);</p> </item> <item><p>x <c>F</c> y or y <c>F</c> x (<c>F</c> is total).</p> diff --git a/lib/stdlib/doc/src/sofs.xml b/lib/stdlib/doc/src/sofs.xml index 8c8ae51262..729df1e678 100644 --- a/lib/stdlib/doc/src/sofs.xml +++ b/lib/stdlib/doc/src/sofs.xml @@ -210,7 +210,7 @@ X[i] to Y[i] and S a subset of X[1] × ... × X[n]. The <marker id="multiple_relative_product"></marker><em>multiple - relative product</em> of TR and and S is defined to be the + relative product</em> of TR and S is defined to be the set {z : z = ((x[1], ..., x[n]), (y[1],...,y[n])) for some (x[1], ..., x[n]) in S and for some (x[i], y[i]) in R[i], diff --git a/lib/stdlib/doc/src/timer.xml b/lib/stdlib/doc/src/timer.xml index 0b6807dd6c..1b34e71490 100644 --- a/lib/stdlib/doc/src/timer.xml +++ b/lib/stdlib/doc/src/timer.xml @@ -202,18 +202,33 @@ </func> <func> <name>tc(Module, Function, Arguments) -> {Time, Value}</name> - <fsummary>Measure the real time it takes to evaluate <c>apply(Module, Function, Arguments)</c></fsummary> + <name>tc(Fun, Arguments) -> {Time, Value}</name> + <fsummary>Measure the real time it takes to evaluate <c>apply(Module, + Function, Arguments)</c> or <c>apply(Fun, Arguments)</c></fsummary> <type> <v>Module = Function = atom()</v> + <v>Fun = fun()</v> <v>Arguments = [term()]</v> <v>Time = integer() in microseconds</v> <v>Value = term()</v> </type> <desc> - <p>Evaluates <c>apply(Module, Function, Arguments)</c> and measures - the elapsed real time. Returns <c>{Time, Value}</c>, where - <c>Time</c> is the elapsed real time in <em>microseconds</em>, - and <c>Value</c> is what is returned from the apply.</p> + <p></p> + <taglist> + <tag><c>tc/3</c></tag> + <item> + <p>Evaluates <c>apply(Module, Function, Arguments)</c> and measures + the elapsed real time as reported by <c>now/0</c>. + Returns <c>{Time, Value}</c>, where + <c>Time</c> is the elapsed real time in <em>microseconds</em>, + and <c>Value</c> is what is returned from the apply.</p> + </item> + <tag><c>tc/2</c></tag> + <item> + <p>Evaluates <c>apply(Fun, Arguments)</c>. Otherwise works + like <c>tc/3</c>.</p> + </item> + </taglist> </desc> </func> <func> |