Skip to content

Commit ceacc7e

Browse files
committed
Test doc examples
1 parent 694bcf8 commit ceacc7e

File tree

3 files changed

+104
-76
lines changed

3 files changed

+104
-76
lines changed

lib/stdlib/src/rand.erl

Lines changed: 86 additions & 69 deletions
Original file line numberDiff line numberDiff line change
@@ -128,76 +128,93 @@ to operate on the state in the process dictionary.
128128

129129
#### _Examples_
130130

131-
Generate two uniformly distibuted floating point numbers.
132-
133-
By not calling a [seed](`seed/1`) function, this uses the genarator state
134-
(and [algorithm](#algorithms)) in the process dictinary.
135-
If there is no state there, [`seed(default)`](`seed/1`)
136-
is implicitly called first:
137-
138-
```erlang
139-
R0 = rand:uniform(),
140-
R1 = rand:uniform(),
141-
```
142-
143-
Generate a uniformly distributed integer in the range 1..4711:
144-
145-
```erlang
146-
K0 = rand:uniform(4711),
147-
```
148-
149-
Generate a binary with 16 bytes, uniformly distributed:
150-
151-
```erlang
152-
B0 = rand:bytes(16),
153-
```
154-
155-
Select and initialize a specified algorithm, with an automatic default seed,
156-
then generate a floating point number:
157-
158-
```erlang
159-
_ = rand:seed(exro928ss),
160-
R2 = rand:uniform(),
161-
```
162-
163-
Select and initialize a specified algorithm with a specified seed,
164-
then generate a floating point number:
165-
166-
```erlang
167-
_ = rand:seed(exro928ss, 123456789),
168-
R3 = rand:uniform(),
169-
```
170-
171-
Select and initialize a specified algorithm, with an automatic default seed,
172-
using the functional API with explicit generator state,
173-
then generate a floating point number.
174-
175-
```erlang
176-
S0 = rand:seed_s(exsss),
177-
{R4, S1} = rand:uniform_s(S0),
178-
```
179-
180-
Generate a standard normal distribution number using the built-in
181-
fast Ziggurat Method:
182-
183-
```erlang
184-
{SND1, S2} = rand:normal_s(S1),
185-
```
186-
187-
Generate a normal distribution number with with mean -3 and variance 0.5:
188-
189-
```erlang
190-
{ND0, S3} = rand:normal_s(-3, 0.5, S2),
191-
```
192-
193-
Generate a textbook basic form Box-Muller standard normal distribution number,
194-
which has the same distribution as the built-in Ziggurat mathod above,
195-
but is much slower:
196-
197131
```erlang
198-
R5 = rand:uniform_real(),
199-
R6 = rand:uniform(),
200-
SND0 = math:sqrt(-2 * math:log(R5)) * math:cos(math:pi() * R6)
132+
%% Generate two uniformly distibuted floating point numbers.
133+
%%
134+
%% By not calling a [seed](`seed/1`) function, this uses
135+
%% the genarator state and algorithm in the process dictinary.
136+
%% If there is no state there, [`seed(default)`](`seed/1`)
137+
%% is implicitly called first:
138+
%%
139+
1> R0 = rand:uniform(),
140+
is_float(R0) andalso 0.0 =< R0 andalso R0 < 1.0.
141+
true
142+
2> R1 = rand:uniform(),
143+
is_float(R1) andalso 0.0 =< R1 andalso R1 < 1.0.
144+
true
145+
146+
%% Generate a uniformly distributed integer in the range 1..4711:
147+
%%
148+
3> K0 = rand:uniform(4711),
149+
is_integer(K0) andalso 1 =< K0 andalso K0 =< 4711.
150+
true
151+
152+
%% Generate a binary with 16 bytes, uniformly distributed:
153+
%%
154+
4> B0 = rand:bytes(16),
155+
byte_size(B0) == 16.
156+
true
157+
158+
%% Select and initialize a specified algorithm,
159+
%% with an automatic default seed, then generate
160+
%% a floating point number:
161+
%%
162+
5> _ = rand:seed(exro928ss).
163+
6> R2 = rand:uniform(),
164+
is_float(R2) andalso 0.0 =< R2 andalso R2 < 1.0.
165+
true
166+
167+
%% Select and initialize a specified algorithm
168+
%% with a specified seed, then generate
169+
%% a floating point number:
170+
%%
171+
7> _ = rand:seed(exro928ss, 123456789).
172+
8> R3 = rand:uniform(),
173+
is_float(R3) andalso 0.0 =< R3 andalso R3 < 1.0.
174+
true
175+
176+
%% Select and initialize a specified algorithm,
177+
%% with an automatic default seed, using the functional API
178+
%% with explicit generator state, then generate
179+
%% two floating point numbers.
180+
%%
181+
9> S0 = rand:seed_s(exsss).
182+
10> {R4, S1} = rand:uniform_s(S0),
183+
is_float(R4) andalso 0.0 =< R4 andalso R4 < 1.0.
184+
true
185+
11> {R5, S2} = rand:uniform_s(S1),
186+
is_float(R5) andalso 0.0 =< R5 andalso R5 < 1.0.
187+
true
188+
%% Repeat the first after seed
189+
12> {R4, _} = rand:uniform_s(S0).
190+
191+
%% Generate a standard normal distribution number
192+
%% using the built-in fast Ziggurat Method:
193+
%%
194+
13> {SND0, S3} = rand:normal_s(S2),
195+
is_float(SND0).
196+
true
197+
198+
%% Generate a normal distribution number
199+
%% with with mean -3 and variance 0.5:
200+
%%
201+
14> {ND0, S4} = rand:normal_s(-3, 0.5, S3),
202+
is_float(ND0).
203+
true
204+
205+
%% Generate a textbook basic form Box-Muller
206+
%% standard normal distribution number, which has the same
207+
%% distribution as the built-in Ziggurat method above,
208+
%% but is much slower:
209+
%%
210+
15> R6 = rand:uniform_real(),
211+
is_float(R6) andalso 0.0 < R6 andalso R6 < 1.0.
212+
true
213+
16> R7 = rand:uniform(),
214+
is_float(R7) andalso 0.0 =< R7 andalso R7 < 1.0.
215+
true
216+
%% R6 cannot be equal to 0.0 so math:log/1 will never fail
217+
17> SND1 = math:sqrt(-2 * math:log(R6)) * math:cos(math:pi() * R7).
201218
```
202219

203220
[](){: #algorithms } Algorithms

lib/stdlib/src/shell_docs_test.erl

Lines changed: 11 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -169,12 +169,15 @@ should not be tested
169169
""".
170170
-spec module(#docs_v1{}, erl_eval:binding_struct()) -> _.
171171
module(#docs_v1{ docs = Docs, module_doc = MD }, Bindings) ->
172-
MDRes = [parse_and_run(module_doc, MD, Bindings)],
173-
Res0 = [parse_and_run(KFA, EntryDocs, Bindings) ||
174-
{KFA, _Anno, _Sig, EntryDocs, _Meta} <- Docs,
175-
is_map(EntryDocs)] ++ MDRes,
176-
Res = lists:append(Res0),
177-
Errors = [{{F,A},E} || {{function,F,A},[{error,E}]} <- Res],
172+
MDRes = lists:append([parse_and_run(module_doc, MD, Bindings)]),
173+
Res =
174+
lists:append(
175+
[parse_and_run(KFA, EntryDocs, Bindings) ||
176+
{KFA, _Anno, _Sig, EntryDocs, _Meta} <- Docs,
177+
is_map(EntryDocs)]),
178+
Errors =
179+
[{{F,A},E} || {{function,F,A},[{error,E}]} <- Res]
180+
++ [{module_doc,E} || {module_doc,[{error,E}]} <- MDRes],
178181
_ = [print_error(E) || E <- Errors],
179182
case length(Errors) of
180183
0 ->
@@ -193,6 +196,8 @@ module(#docs_v1{ docs = Docs, module_doc = MD }, Bindings) ->
193196
error({N,errors})
194197
end.
195198

199+
print_error({module_doc,{Message,Context}}) ->
200+
io:format("Module Doc: ~ts~n~ts~n", [Context,Message]);
196201
print_error({{Name,Arity},{Message,Context}}) ->
197202
io:format("~p/~p: ~ts~n~ts~n", [Name,Arity,Context,Message]).
198203

lib/stdlib/test/rand_SUITE.erl

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -46,7 +46,8 @@ all() ->
4646
uniform_real_conv,
4747
plugin, measure,
4848
{group, reference_jump},
49-
short_jump
49+
short_jump,
50+
doctests
5051
].
5152

5253
groups() ->
@@ -2051,6 +2052,11 @@ check(N, Range, StateA, StateB) ->
20512052
ct:fail({Wrong,neq,V,for,N})
20522053
end.
20532054

2055+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2056+
2057+
doctests(Config) when is_list(Config) ->
2058+
shell_docs:test(rand, []).
2059+
20542060
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
20552061
%%% Data
20562062
reference_val(exs64) ->

0 commit comments

Comments
 (0)