Skip to content

Commit

Permalink
Merge branch 'lukas/stdlib/doctests'
Browse files Browse the repository at this point in the history
* lukas/stdlib/doctests:
  stdlib: Add doctests for binary module
  erts: Fix binary:referenced_bytes_size for heap binaries
  stdlib: Add doctests to maps
  stdlib: Use doctests for lists
  stdlib: Rewrite map assoc to map exact for match expression
  stdlib: Add basic support for running doctests
  • Loading branch information
garazdawi committed Jan 30, 2025
2 parents 7da0086 + edc69ed commit d628424
Show file tree
Hide file tree
Showing 12 changed files with 363 additions and 94 deletions.
2 changes: 2 additions & 0 deletions erts/emulator/beam/erl_bif_binary.c
Original file line number Diff line number Diff line change
Expand Up @@ -2524,6 +2524,8 @@ BIF_RETTYPE binary_referenced_byte_size_1(BIF_ALIST_1)

if (br != NULL) {
size = (br->val)->orig_size;
} else {
size = BYTE_SIZE(size);
}

BIF_RET(erts_make_integer(size, BIF_P));
Expand Down
1 change: 1 addition & 0 deletions lib/stdlib/src/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -122,6 +122,7 @@ MODULES= \
shell_default \
shell_docs \
shell_docs_markdown \
shell_docs_test \
slave \
sofs \
string \
Expand Down
92 changes: 46 additions & 46 deletions lib/stdlib/src/binary.erl
Original file line number Diff line number Diff line change
Expand Up @@ -99,7 +99,7 @@ Converts `Subject` to a list of `t:byte/0`s, each representing the value of one
_Example:_
```erlang
1> binary:bin_to_list(<<"erlang">>).
> binary:bin_to_list(<<"erlang">>).
"erlang"
%% or [101,114,108,97,110,103] in list notation.
```
Expand Down Expand Up @@ -142,7 +142,7 @@ converted.
_Example:_
```erlang
1> binary:bin_to_list(<<"erlang">>, {1,3}).
> binary:bin_to_list(<<"erlang">>, {1,3}).
"rla"
%% or [114,108,97] in list notation.
```
Expand Down Expand Up @@ -259,11 +259,11 @@ positive integer in `Subject` to an Erlang `t:integer/0`.
_Example:_

```erlang
1> binary:decode_unsigned(<<169,138,199>>).
> binary:decode_unsigned(<<169,138,199>>).
11111111
2> binary:decode_unsigned(<<169,138,199>>, big).
> binary:decode_unsigned(<<169,138,199>>, big).
11111111
3> binary:decode_unsigned(<<169,138,199>>, little).
> binary:decode_unsigned(<<169,138,199>>, little).
13077161
```
""".
Expand Down Expand Up @@ -291,11 +291,11 @@ digit representation, either big endian or little endian.
_Example:_

```erlang
1> binary:encode_unsigned(11111111).
> binary:encode_unsigned(11111111).
<<169,138,199>>
2> binary:encode_unsigned(11111111, big).
> binary:encode_unsigned(11111111, big).
<<169,138,199>>
2> binary:encode_unsigned(11111111, little).
> binary:encode_unsigned(11111111, little).
<<199,138,169>>
```
""".
Expand Down Expand Up @@ -344,9 +344,9 @@ Returns the length of the longest common prefix of the binaries in list
_Example:_

```erlang
1> binary:longest_common_prefix([<<"erlang">>, <<"ergonomy">>]).
> binary:longest_common_prefix([<<"erlang">>, <<"ergonomy">>]).
2
2> binary:longest_common_prefix([<<"erlang">>, <<"perl">>]).
> binary:longest_common_prefix([<<"erlang">>, <<"perl">>]).
0
```

Expand All @@ -367,9 +367,9 @@ Returns the length of the longest common suffix of the binaries in list
_Example:_

```erlang
1> binary:longest_common_suffix([<<"erlang">>, <<"fang">>]).
> binary:longest_common_suffix([<<"erlang">>, <<"fang">>]).
3
2> binary:longest_common_suffix([<<"erlang">>, <<"perl">>]).
> binary:longest_common_suffix([<<"erlang">>, <<"perl">>]).
0
```

Expand Down Expand Up @@ -404,7 +404,7 @@ the lowest position in `Subject`.
_Example:_

```erlang
1> binary:match(<<"abcde">>, [<<"bcde">>, <<"cd">>],[]).
> binary:match(<<"abcde">>, [<<"bcde">>, <<"cd">>],[]).
{1,4}
```

Expand Down Expand Up @@ -457,7 +457,7 @@ The first and longest match is preferred to a shorter, which is illustrated by
the following example:

```erlang
1> binary:matches(<<"abcde">>,
> binary:matches(<<"abcde">>,
[<<"bcde">>,<<"bc">>,<<"de">>],[]).
[{1,4}]
```
Expand Down Expand Up @@ -504,8 +504,8 @@ Extracts the part of binary `Subject` described by `PosLen`.
A negative length can be used to extract bytes at the end of a binary:

```erlang
1> Bin = <<1,2,3,4,5,6,7,8,9,10>>.
2> binary:part(Bin, {byte_size(Bin), -5}).
> Bin = <<1,2,3,4,5,6,7,8,9,10>>.
> binary:part(Bin, {byte_size(Bin), -5}).
<<6,7,8,9,10>>
```

Expand Down Expand Up @@ -533,7 +533,7 @@ Get the size of the underlying binary referenced by `Binary`.
If a binary references a larger binary (often described as being a subbinary),
it can be useful to get the size of the referenced binary. This function can be
used in a program to trigger the use of `copy/1`. By copying
a binary, one can dereference the original, possibly large, binary that a
a binary, one can dereference the original, possibly large, binary that a
smaller binary is a reference to.

_Example:_
Expand Down Expand Up @@ -564,18 +564,18 @@ for memory use.
Example of binary sharing:

```erlang
1> A = binary:copy(<<1>>, 100).
<<1,1,1,1,1 ...
2> byte_size(A).
100
3> binary:referenced_byte_size(A).
100
4> <<B:10/binary, C:90/binary>> = A.
<<1,1,1,1,1 ...
5> {byte_size(B), binary:referenced_byte_size(B)}.
> A = binary:copy(<<1>>, 1000).
<<1,1,1,1,1,_/binary>>
> byte_size(A).
1000
> binary:referenced_byte_size(A).
1000
> <<B:10/binary, C/binary>> = A.
_
> {byte_size(B), binary:referenced_byte_size(B)}.
{10,10}
6> {byte_size(C), binary:referenced_byte_size(C)}.
{90,100}
> {byte_size(C), binary:referenced_byte_size(C)}.
{990,1000}
```

In the above example, the small binary `B` was copied while the larger binary
Expand Down Expand Up @@ -618,9 +618,9 @@ The parts of `Pattern` found in `Subject` are not included in the result.
_Example:_

```erlang
1> binary:split(<<1,255,4,0,0,0,2,3>>, [<<0,0,0>>,<<2>>],[]).
> binary:split(<<1,255,4,0,0,0,2,3>>, [<<0,0,0>>,<<2>>],[]).
[<<1,255,4>>, <<2,3>>]
2> binary:split(<<0,1,0,0,4,255,255,9>>, [<<0,0>>, <<255,255>>],[global]).
> binary:split(<<0,1,0,0,4,255,255,9>>, [<<0,0>>, <<255,255>>],[global]).
[<<0,1>>,<<4>>,<<9>>]
```

Expand All @@ -644,9 +644,9 @@ Example of the difference between a scope and taking the binary apart before
splitting:

```erlang
1> binary:split(<<"banana">>, [<<"a">>],[{scope,{2,3}}]).
> binary:split(<<"banana">>, [<<"a">>],[{scope,{2,3}}]).
[<<"ban">>,<<"na">>]
2> binary:split(binary:part(<<"banana">>,{2,3}), [<<"a">>],[]).
> binary:split(binary:part(<<"banana">>,{2,3}), [<<"a">>],[]).
[<<"n">>,<<"n">>]
```

Expand Down Expand Up @@ -714,28 +714,28 @@ For a description of `Pattern`, see `compile_pattern/1`.
_Examples:_

```erlang
1> binary:replace(<<"abcde">>, [<<"b">>, <<"d">>], <<"X">>, []).
> binary:replace(<<"abcde">>, [<<"b">>, <<"d">>], <<"X">>, []).
<<"aXcde">>

2> binary:replace(<<"abcde">>, [<<"b">>, <<"d">>], <<"X">>, [global]).
> binary:replace(<<"abcde">>, [<<"b">>, <<"d">>], <<"X">>, [global]).
<<"aXcXe">>

3> binary:replace(<<"abcde">>, <<"b">>, <<"[]">>, [{insert_replaced, 1}]).
> binary:replace(<<"abcde">>, <<"b">>, <<"[]">>, [{insert_replaced, 1}]).
<<"a[b]cde">>

4> binary:replace(<<"abcde">>, [<<"b">>, <<"d">>], <<"[]">>, [global, {insert_replaced, 1}]).
> binary:replace(<<"abcde">>, [<<"b">>, <<"d">>], <<"[]">>, [global, {insert_replaced, 1}]).
<<"a[b]c[d]e">>

5> binary:replace(<<"abcde">>, [<<"b">>, <<"d">>], <<"[]">>, [global, {insert_replaced, [1, 1]}]).
> binary:replace(<<"abcde">>, [<<"b">>, <<"d">>], <<"[]">>, [global, {insert_replaced, [1, 1]}]).
<<"a[bb]c[dd]e">>

6> binary:replace(<<"abcde">>, [<<"b">>, <<"d">>], <<"[-]">>, [global, {insert_replaced, [1, 2]}]).
> binary:replace(<<"abcde">>, [<<"b">>, <<"d">>], <<"[-]">>, [global, {insert_replaced, [1, 2]}]).
<<"a[b-b]c[d-d]e">>

7> binary:replace(<<"abcde">>, [<<"b">>, <<"d">>], fun(M) -> <<$[, M/binary, $]>> end, []).
> binary:replace(<<"abcde">>, [<<"b">>, <<"d">>], fun(M) -> <<$[, M/binary, $]>> end, []).
<<"a[b]cde">>

8> binary:replace(<<"abcde">>, [<<"b">>, <<"d">>], fun(M) -> <<$[, M/binary, $]>> end, [global]).
> binary:replace(<<"abcde">>, [<<"b">>, <<"d">>], fun(M) -> <<$[, M/binary, $]>> end, [global]).
<<"a[b]c[d]e">>
```
""".
Expand Down Expand Up @@ -839,13 +839,13 @@ The default case is `uppercase`.
_Example:_

```erlang
1> binary:encode_hex(<<"f">>).
> binary:encode_hex(<<"f">>).
<<"66">>
2> binary:encode_hex(<<"/">>).
> binary:encode_hex(<<"/">>).
<<"2F">>
3> binary:encode_hex(<<"/">>, lowercase).
> binary:encode_hex(<<"/">>, lowercase).
<<"2f">>
4> binary:encode_hex(<<"/">>, uppercase).
> binary:encode_hex(<<"/">>, uppercase).
<<"2F">>
```
""".
Expand Down Expand Up @@ -918,7 +918,7 @@ Decodes a hex encoded binary into a binary.
_Example_

```erlang
1> binary:decode_hex(<<"66">>).
> binary:decode_hex(<<"66">>).
<<"f">>
```
""".
Expand Down Expand Up @@ -967,7 +967,7 @@ Equivalent to `iolist_to_binary(lists:join(Separator, Binaries))`, but faster.
_Example:_

```erlang
1> binary:join([<<"a">>, <<"b">>, <<"c">>], <<", ">>).
> binary:join([<<"a">>, <<"b">>, <<"c">>], <<", ">>).
<<"a, b, c">>
```
""".
Expand Down
18 changes: 8 additions & 10 deletions lib/stdlib/src/lists.erl
Original file line number Diff line number Diff line change
Expand Up @@ -240,7 +240,7 @@ _Example:_
```erlang
> lists:subtract("123212", "212").
"312".
"312"
```
`lists:subtract(A, B)` is equivalent to `A -- B`.
Expand Down Expand Up @@ -1546,8 +1546,7 @@ _Examples:_
```erlang
> Fun = fun(Atom) -> atom_to_list(Atom) end.
#Fun<erl_eval.6.10732646>
2> lists:keymap(Fun, 2, [{name,jane,22},{name,lizzie,20},{name,lydia,15}]).
> lists:keymap(Fun, 2, [{name,jane,22},{name,lizzie,20},{name,lydia,15}]).
[{name,"jane",22},{name,"lizzie",20},{name,"lydia",15}]
```
""".
Expand Down Expand Up @@ -2163,12 +2162,11 @@ Like `foldl/3`, but the list is traversed from right to left.
_Example:_
```erlang
> P = fun(A, AccIn) -> io:format("~p ", [A]), AccIn end.
#Fun<erl_eval.12.2225172>
> lists:foldl(P, void, [1,2,3]).
1 2 3 void
> lists:foldr(P, void, [1,2,3]).
3 2 1 void
> P = fun(A, AccIn) -> [A|AccIn] end.
> lists:foldl(P, [], [1,2,3]).
[3,2,1]
> lists:foldr(P, [], [1,2,3]).
[1,2,3]
```
[`foldl/3`](`foldl/3`) is tail recursive and is usually preferred to
Expand Down Expand Up @@ -2326,7 +2324,7 @@ Summing the elements in a list and double them at the same time:
```erlang
> lists:mapfoldl(fun(X, Sum) -> {2*X, X+Sum} end,
0, [1,2,3,4,5]).
0, [1,2,3,4,5]).
{[2,4,6,8,10],15}
```
""".
Expand Down
Loading

0 comments on commit d628424

Please sign in to comment.