diff --git a/erts/emulator/beam/erl_bif_binary.c b/erts/emulator/beam/erl_bif_binary.c index 2b7e007822e..5abf5bf0f18 100644 --- a/erts/emulator/beam/erl_bif_binary.c +++ b/erts/emulator/beam/erl_bif_binary.c @@ -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)); diff --git a/lib/stdlib/src/Makefile b/lib/stdlib/src/Makefile index a6bb6bfd8c2..cc45ee6d068 100644 --- a/lib/stdlib/src/Makefile +++ b/lib/stdlib/src/Makefile @@ -122,6 +122,7 @@ MODULES= \ shell_default \ shell_docs \ shell_docs_markdown \ + shell_docs_test \ slave \ sofs \ string \ diff --git a/lib/stdlib/src/binary.erl b/lib/stdlib/src/binary.erl index f7acbee55d1..17b10dd640e 100644 --- a/lib/stdlib/src/binary.erl +++ b/lib/stdlib/src/binary.erl @@ -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. ``` @@ -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. ``` @@ -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 ``` """. @@ -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>> ``` """. @@ -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 ``` @@ -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 ``` @@ -404,7 +404,7 @@ the lowest position in `Subject`. _Example:_ ```erlang -1> binary:match(<<"abcde">>, [<<"bcde">>, <<"cd">>],[]). +> binary:match(<<"abcde">>, [<<"bcde">>, <<"cd">>],[]). {1,4} ``` @@ -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}] ``` @@ -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>> ``` @@ -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:_ @@ -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> <> = 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 +> <> = 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 @@ -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>>] ``` @@ -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">>] ``` @@ -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">> ``` """. @@ -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">> ``` """. @@ -918,7 +918,7 @@ Decodes a hex encoded binary into a binary. _Example_ ```erlang -1> binary:decode_hex(<<"66">>). +> binary:decode_hex(<<"66">>). <<"f">> ``` """. @@ -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">> ``` """. diff --git a/lib/stdlib/src/lists.erl b/lib/stdlib/src/lists.erl index 8fa4bc19660..0a747ff0655 100644 --- a/lib/stdlib/src/lists.erl +++ b/lib/stdlib/src/lists.erl @@ -240,7 +240,7 @@ _Example:_ ```erlang > lists:subtract("123212", "212"). -"312". +"312" ``` `lists:subtract(A, B)` is equivalent to `A -- B`. @@ -1546,8 +1546,7 @@ _Examples:_ ```erlang > Fun = fun(Atom) -> atom_to_list(Atom) end. -#Fun -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}] ``` """. @@ -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 -> 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 @@ -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} ``` """. diff --git a/lib/stdlib/src/maps.erl b/lib/stdlib/src/maps.erl index e577f603085..a70bdd633cb 100644 --- a/lib/stdlib/src/maps.erl +++ b/lib/stdlib/src/maps.erl @@ -105,7 +105,7 @@ _Example:_ ```erlang > Key = 1337, Map = #{42 => value_two,1337 => "value one","a" => 1}, - maps:get(Key,Map). + maps:get(Key, Map). "value one" ``` """. @@ -794,14 +794,14 @@ valid iterator, or with `badarg` if `Fun` is not a function of arity 2. _Example:_ ```erlang -> Fun = fun(K,V) -> io:format("~p:~p~n",[K,V]) end. -#Fun +> Fun = fun(K,V) -> io:format("% ~p:~p~n",[K,V]) end. + > Map = #{"x" => 10, "y" => 20, "z" => 30}. #{"x" => 10,"y" => 20,"z" => 30} > maps:foreach(Fun,Map). -"x":10 -"y":20 -"z":30 +% "x":10 +% "y":20 +% "z":30 ok ``` """. @@ -942,22 +942,22 @@ size(Map) -> -doc """ Returns a map iterator `Iterator` that can be used by [`maps:next/1`](`next/1`) -to traverse the key-value associations in a map. When iterating over a map, the -memory usage is guaranteed to be bounded no matter the size of the map. +to traverse the key-value associations in a map. The order of iteration is +undefined. When iterating over a map, the memory usage is guaranteed to be +bounded no matter the size of the map. The call fails with a `{badmap,Map}` exception if `Map` is not a map. _Example:_ ```erlang -> M = #{ a => 1, b => 2 }. -#{a => 1,b => 2} -> I = maps:iterator(M), ok. -ok +> M = #{ "foo" => 1, "bar" => 2 }. +#{"foo" => 1,"bar" => 2} +> I = maps:iterator(M). > {K1, V1, I2} = maps:next(I), {K1, V1}. -{a,1} +{"bar",2} > {K2, V2, I3} = maps:next(I2),{K2, V2}. -{b,2} +{"foo",1} > maps:next(I3). none ``` @@ -983,8 +983,7 @@ _Example (when _`Order`_ is _`ordered`_):_ ```erlang > M = #{ a => 1, b => 2 }. #{a => 1,b => 2} -> OrdI = maps:iterator(M, ordered), ok. -ok +> OrdI = maps:iterator(M, ordered). > {K1, V1, OrdI2} = maps:next(OrdI), {K1, V1}. {a,1} > {K2, V2, OrdI3} = maps:next(OrdI2),{K2, V2}. @@ -998,8 +997,7 @@ _Example (when _`Order`_ is _`reversed`_):_ ```erlang > M = #{ a => 1, b => 2 }. #{a => 1,b => 2} -> RevI = maps:iterator(M, reversed), ok. -ok +> RevI = maps:iterator(M, reversed). > {K2, V2, RevI2} = maps:next(RevI), {K2, V2}. {b,2} > {K1, V1, RevI3} = maps:next(RevI2),{K1, V1}. @@ -1013,12 +1011,10 @@ _Example (when _`Order`_ is an arithmetic sorting function):_ ```erlang > M = #{ -1 => a, -1.0 => b, 0 => c, 0.0 => d }. #{-1 => a,0 => c,-1.0 => b,0.0 => d} -> ArithOrdI = maps:iterator(M, fun(A, B) -> A =< B end), ok. -ok +> ArithOrdI = maps:iterator(M, fun(A, B) -> A =< B end). > maps:to_list(ArithOrdI). [{-1,a},{-1.0,b},{0,c},{0.0,d}] -> ArithRevI = maps:iterator(M, fun(A, B) -> B < A end), ok. -ok +> ArithRevI = maps:iterator(M, fun(A, B) -> B < A end). > maps:to_list(ArithRevI). [{0.0,d},{0,c},{-1.0,b},{-1,a}] ``` @@ -1056,8 +1052,7 @@ _Example:_ ```erlang > Map = #{a => 1, b => 2, c => 3}. #{a => 1,b => 2,c => 3} -> I = maps:iterator(Map), ok. -ok +> I = maps:iterator(Map, ordered). > {K1, V1, I1} = maps:next(I), {K1, V1}. {a,1} > {K2, V2, I2} = maps:next(I1), {K2, V2}. @@ -1159,7 +1154,7 @@ _Examples:_ ```erlang > EvenOdd = fun(X) -> case X rem 2 of 0 -> even; 1 -> odd end end, -maps:groups_from_list(EvenOdd, [1, 2, 3]). + maps:groups_from_list(EvenOdd, [1, 2, 3]). #{even => [2], odd => [1, 3]} > maps:groups_from_list(fun erlang:length/1, ["ant", "buffalo", "cat", "dingo"]). #{3 => ["ant", "cat"], 5 => ["dingo"], 7 => ["buffalo"]} @@ -1209,8 +1204,8 @@ _Examples:_ ```erlang > EvenOdd = fun(X) -> case X rem 2 of 0 -> even; 1 -> odd end end, -> Square = fun(X) -> X * X end, -> maps:groups_from_list(EvenOdd, Square, [1, 2, 3]). + Square = fun(X) -> X * X end, + maps:groups_from_list(EvenOdd, Square, [1, 2, 3]). #{even => [4], odd => [1, 9]} > maps:groups_from_list( fun erlang:length/1, diff --git a/lib/stdlib/src/shell_docs.erl b/lib/stdlib/src/shell_docs.erl index 3a462054790..2f1ce9083e4 100644 --- a/lib/stdlib/src/shell_docs.erl +++ b/lib/stdlib/src/shell_docs.erl @@ -66,6 +66,8 @@ be rendered as is. -export([render_type/2, render_type/3, render_type/4, render_type/5]). -export([render_callback/2, render_callback/3, render_callback/4, render_callback/5]). +-export([test/2]). + %% Used by chunks.escript in erl_docgen -export([validate/1, normalize/1, supported_tags/0]). @@ -456,6 +458,19 @@ get_doc(Module, Function, Arity) -> Map = fun ({F,A,S,Dc,M}) -> {F,A,S,get_local_doc(F, Dc, D),M} end, filtermap_mfa({function, Function, Arity}, Map, Docs). +-doc false. +-spec test(module(), [{{function | type | callback, atom(), non_neg_integer()} + | module_doc, erl_eval:binding_struct()}]) -> ok. +test(Module, Bindings) -> + case code:get_doc(Module) of + {ok, #docs_v1{ format = ~"text/markdown" } = Docs} -> + shell_docs_test:module(Docs, Bindings); + {ok, _} -> + {error, unsupported_format}; + Else -> + Else + end. + -doc(#{equiv => render(Module, Docs, #{})}). -doc(#{since => <<"OTP 23.0">>}). -spec render(Module, Docs) -> unicode:chardata() when diff --git a/lib/stdlib/src/shell_docs_test.erl b/lib/stdlib/src/shell_docs_test.erl new file mode 100644 index 00000000000..9bbbcca764e --- /dev/null +++ b/lib/stdlib/src/shell_docs_test.erl @@ -0,0 +1,237 @@ +%% +%% %CopyrightBegin% +%% +%% Copyright Ericsson AB 1996-2024. All Rights Reserved. +%% +%% Licensed under the Apache License, Version 2.0 (the "License"); +%% you may not use this file except in compliance with the License. +%% You may obtain a copy of the License at +%% +%% http://www.apache.org/licenses/LICENSE-2.0 +%% +%% Unless required by applicable law or agreed to in writing, software +%% distributed under the License is distributed on an "AS IS" BASIS, +%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. +%% See the License for the specific language governing permissions and +%% limitations under the License. +%% +%% %CopyrightEnd% +%% +-module(shell_docs_test). +-moduledoc false. + +-include_lib("kernel/include/eep48.hrl"). + +-export([module/2]). + +-doc """ +Here are some examples of what should work: + +## Basic example: + +``` +> 1+2. +3 +``` + +## Basic example using erlang code: + +```erlang +> 1+2. +3 +``` + +## Multi-line prompt example: + +```erlang +> 1 + + + 2 + . +3 +``` + +## Multi-line with comma example: + +```erlang +> A = 1, + A + 2. +3 +``` + +## Multi-match example: + +```erlang +> [1, 2]. +[ + 1 + , + 2 + ] +``` + +## Multiple prompts: + +``` +> 1 + 2. +3 +> 3 + 4. +7 +``` + +## Ignore result: + +``` +> 1 + 2. +``` + +## Defining variables: + +``` +> A = 1+2. +> A + 3. +6 +``` + +## Comments: + +``` +> [1, +% A comment in between prompts + 2]. +[1, +% A comment in a match + 2] +> [1, + % Indented comment in between prompts + 2]. +[1, + % Indented comment in a match + 2] +``` + +## Prebound variables: + +``` +> Prebound. +hello +``` + +## Matching of maps: + +``` +> #{ a => b }. +#{ a => b } +``` + +""". +-spec module(#docs_v1{}, erl_eval:binding_struct()) -> _. +module(#docs_v1{ docs = Docs, module_doc = MD }, Bindings) -> + MDRes = parse_and_run(module_doc, MD, Bindings), + case lists:flatten( + [parse_and_run(KFA, EntryDocs, Bindings) + || {KFA, _Anno, _Sig, EntryDocs, _Meta} <- Docs, is_map(EntryDocs)] ++ MDRes) of + [] -> + ok; + Else -> + Else + end. + +parse_and_run(_, hidden, _) -> []; +parse_and_run(_, none, _) -> []; +parse_and_run(KFA, #{} = Ds, Bindings) -> + [parse_and_run(KFA, D, Bindings) || _ := D <- Ds]; +parse_and_run(KFA, Docs, Bindings) -> + InitialBindings = proplists:get_value(KFA, Bindings, erl_eval:new_bindings()), + io:format("Testing: ~p~n",[KFA]), + case test(inspect(shell_docs_markdown:parse_md(Docs)), InitialBindings) of + [] -> []; + Else -> + {KFA, lists:flatten(Else)} + end. + +test({pre,[],[{code,Attrs,[<<">",_/binary>> = Code]}]}, Bindings) -> + case proplists:get_value(class, Attrs, ~"language-erlang") of + ~"language-erlang" -> + run_test(Code, Bindings); + _ -> + test(Code, Bindings) + end; +test({_Tag,_Attr, Content}, Bindings) -> + test(Content, Bindings); +test([H | T], Bindings) -> + [test(H, Bindings) | test(T, Bindings)]; +test(Text, _Bindings) when is_binary(Text); Text =:= [] -> + []. + +run_test(Code, InitialBindings) -> + Lines = string:split(Code, "\n", all), + Tests = inspect(parse_tests(Lines, [])), + lists:foldl(fun(Test, Bindings) -> + run_tests(Test, Bindings) + end, InitialBindings, Tests). + +parse_tests([], []) -> + []; +parse_tests([], Cmd) -> + [{test, lists:join($\n, lists:reverse(Cmd)), "_"}]; +parse_tests([<<>>|T], Cmd) -> + parse_tests(T, Cmd); +parse_tests([<<"%", _Skip/binary>> | T], Cmd) -> + parse_tests(T, Cmd); +parse_tests([<<"> ", NewCmd/binary>> | T], []) -> + parse_tests(T, [NewCmd]); +parse_tests([<<"> ", NewCmd/binary>> | T], Cmd) -> + [{test, lists:join($\n, lists:reverse(Cmd)), "_"} | parse_tests(T, [NewCmd])]; +parse_tests([<<" ", More/binary>> | T], Acc) -> + parse_tests(T, [More | Acc]); +parse_tests([NewMatch | T], Cmd) -> + {Match, Rest} = parse_match(T, [NewMatch]), + [{test, lists:join($\n, lists:reverse(Cmd)), + lists:join($\n, lists:reverse(Match))} | parse_tests(Rest, [])]. + +parse_match([<<"%", _Skip/binary>> | T], Acc) -> + parse_match(T, Acc); +parse_match([<<" ", More/binary>> | T], Acc) -> + parse_match(T, [More | Acc]); +parse_match(Rest, Acc) -> + {Acc, Rest}. + +run_tests({test, Test, Match}, Bindings) -> + maybe + Cmd = [unicode:characters_to_list(Match), " = begin ", + string:trim(string:trim(unicode:characters_to_list(Test)), trailing, "."), " end."], + {ok, T, _} ?= erl_scan:string(lists:flatten(Cmd)), + {ok, Ast0} ?= inspect(erl_parse:parse_exprs(T)), + Ast = rewrite(Ast0), + try + {value, _Res, NewBindings} = inspect(erl_eval:exprs(Ast, Bindings)), + NewBindings + catch E:R:ST -> + io:format("~p~n", [Ast]), + erlang:raise(E,R,ST) + end + else + Else -> throw({iolist_to_binary(Test), iolist_to_binary(Match), Else}) + end. + +rewrite([{match, Ann, LHS, RHS} | Rest]) -> + [{match, Ann, rewrite_map_match(LHS), RHS} | Rest]. + +rewrite_map_match(AST) -> + erl_syntax:revert( + erl_syntax_lib:map(fun(Tree) -> + case erl_syntax:type(Tree) of + map_field_assoc -> + Name = erl_syntax:map_field_assoc_name(Tree), + Value = erl_syntax:map_field_assoc_value(Tree), + erl_syntax:map_field_exact(Name, Value); + _Else -> + Tree + end + end, AST)). + +inspect(Term) -> +%% Uncomment for debugging +% io:format("~tp~n",[Term]), + Term. diff --git a/lib/stdlib/src/stdlib.app.src b/lib/stdlib/src/stdlib.app.src index b299de46e1c..22c13252870 100644 --- a/lib/stdlib/src/stdlib.app.src +++ b/lib/stdlib/src/stdlib.app.src @@ -101,7 +101,8 @@ shell, shell_default, shell_docs, - shell_docs_markdown, + shell_docs_markdown, + shell_docs_test, slave, sofs, string, @@ -119,5 +120,5 @@ {applications, [kernel]}, {env, []}, {runtime_dependencies, ["sasl-3.0","kernel-10.0","erts-15.0","crypto-4.5", - "compiler-5.0"]} + "compiler-5.0", "syntax_tools-3.2.1"]} ]}. diff --git a/lib/stdlib/test/binary_module_SUITE.erl b/lib/stdlib/test/binary_module_SUITE.erl index 3d9efd919e5..82862e97a9f 100644 --- a/lib/stdlib/test/binary_module_SUITE.erl +++ b/lib/stdlib/test/binary_module_SUITE.erl @@ -23,7 +23,7 @@ interesting/1,scope_return/1,random_ref_comp/1,random_ref_sr_comp/1, random_ref_fla_comp/1,parts/1, bin_to_list/1, list_to_bin/1, copy/1, referenced/1,guard/1,encode_decode/1,badargs/1,longest_common_trap/1, - check_no_invalid_read_bug/1,error_info/1, hex_encoding/1, join/1]). + check_no_invalid_read_bug/1,error_info/1, hex_encoding/1, join/1, doctests/1]). -export([random_number/1, make_unaligned/1]). @@ -38,7 +38,7 @@ all() -> random_ref_comp, parts, bin_to_list, list_to_bin, copy, referenced, guard, encode_decode, badargs, longest_common_trap, check_no_invalid_read_bug, - error_info, hex_encoding, join]. + error_info, hex_encoding, join, doctests]. -define(MASK_ERROR(EXPR),mask_error((catch (EXPR)))). @@ -1599,6 +1599,9 @@ join(Config) when is_list(Config) -> ~"a" = binary:join([~"a"], ~", "), ~"" = binary:join([], ~", "). +doctests(_Config) -> + shell_docs:test(binary, []). + %%% %%% Utilities. %%% diff --git a/lib/stdlib/test/lists_SUITE.erl b/lib/stdlib/test/lists_SUITE.erl index 7a73e1bc820..fc7acf6923e 100644 --- a/lib/stdlib/test/lists_SUITE.erl +++ b/lib/stdlib/test/lists_SUITE.erl @@ -57,7 +57,8 @@ join/1, otp_5939/1, otp_6023/1, otp_6606/1, otp_7230/1, suffix/1, subtract/1, droplast/1, search/1, hof/1, - enumerate/1, error_info/1]). + enumerate/1, error_info/1, + doctests/1]). %% Sort randomized lists until stopped. %% @@ -116,9 +117,9 @@ groups() -> {uniq, [parallel], [uniq_1, uniq_2]}, {misc, [parallel], [reverse, member, dropwhile, takewhile, filter_partition, suffix, subtract, join, - hof, droplast, search, enumerate, error_info]} + hof, droplast, search, enumerate, error_info, + doctests]} ]. - init_per_suite(Config) -> Config. @@ -2452,3 +2453,6 @@ uniq_2(_Config) -> [{42, 1}, {42.0, 99}, {a, 99}, {a, 1}, {42, 100}]), [1] = lists:uniq(fun(_) -> whatever end, lists:seq(1, 10)), ok. + +doctests(_Config) -> + shell_docs:test(lists, []). \ No newline at end of file diff --git a/lib/stdlib/test/maps_SUITE.erl b/lib/stdlib/test/maps_SUITE.erl index 0f203988038..86e1d47548b 100644 --- a/lib/stdlib/test/maps_SUITE.erl +++ b/lib/stdlib/test/maps_SUITE.erl @@ -36,7 +36,7 @@ t_with_2/1,t_without_2/1, t_intersect/1, t_intersect_with/1, t_merge_with/1, t_from_keys/1, - error_info/1, + error_info/1, doctests/1, t_from_list_kill_process/1, t_from_keys_kill_process/1, t_values_kill_process/1, @@ -65,7 +65,7 @@ all() -> t_with_2,t_without_2, t_intersect, t_intersect_with, t_merge_with, t_from_keys, - error_info, + error_info, doctests, t_from_list_kill_process, t_from_keys_kill_process, t_values_kill_process, @@ -1064,4 +1064,7 @@ error_info(_Config) -> ], error_info_lib:test_error_info(maps, L). +doctests(_Config) -> + shell_docs:test(maps, []). + id(I) -> I. diff --git a/lib/stdlib/test/shell_docs_SUITE.erl b/lib/stdlib/test/shell_docs_SUITE.erl index 2a92b5275cd..448069617b3 100644 --- a/lib/stdlib/test/shell_docs_SUITE.erl +++ b/lib/stdlib/test/shell_docs_SUITE.erl @@ -25,7 +25,7 @@ init_per_group/2, end_per_group/2, init_per_testcase/2, end_per_testcase/2]). -export([render/1, links/1, normalize/1, render_prop/1,render_non_native/1, ansi/1, columns/1]). --export([render_function/1, render_type/1, render_callback/1]). +-export([render_function/1, render_type/1, render_callback/1, doctests/1]). -export([render_all/1, update_render/0, update_render/1]). @@ -41,7 +41,8 @@ all() -> [ {group, render}, {group, prop}, {group, render_smoke}, - ansi, columns + ansi, columns, + doctests ]. @@ -577,6 +578,15 @@ columns(_Config) -> ok. +doctests(_Config) -> + shell_docs:test( + shell_docs_test, + [ + {{function, module, 2}, erl_eval:add_binding('Prebound', hello, + erl_eval:new_bindings())} + ]), + ok. + %% %% Parallel map function. %%