aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r--lib/stdlib/test/erl_lint_SUITE.erl156
-rw-r--r--lib/stdlib/test/erl_pp_SUITE.erl23
-rw-r--r--lib/stdlib/test/lists_SUITE.erl16
-rw-r--r--lib/stdlib/test/maps_SUITE.erl56
4 files changed, 174 insertions, 77 deletions
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl
index 6fea198af3..b0214e5238 100644
--- a/lib/stdlib/test/erl_lint_SUITE.erl
+++ b/lib/stdlib/test/erl_lint_SUITE.erl
@@ -33,47 +33,38 @@
-define(privdir, proplists:get_value(priv_dir, Conf)).
-endif.
--export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
- init_per_group/2,end_per_group/2,
- init_per_testcase/2, end_per_testcase/2]).
-
--export([
- unused_vars_warn_basic/1,
- unused_vars_warn_lc/1,
- unused_vars_warn_rec/1,
- unused_vars_warn_fun/1,
- unused_vars_OTP_4858/1,
- unused_unsafe_vars_warn/1,
- export_vars_warn/1,
- shadow_vars/1,
- unused_import/1,
- unused_function/1,
- unsafe_vars/1,unsafe_vars2/1,
- unsafe_vars_try/1,
- unsized_binary_in_bin_gen_pattern/1,
- guard/1, otp_4886/1, otp_4988/1, otp_5091/1, otp_5276/1, otp_5338/1,
- otp_5362/1, otp_5371/1, otp_7227/1, otp_5494/1, otp_5644/1, otp_5878/1,
- otp_5917/1, otp_6585/1, otp_6885/1, otp_10436/1, otp_11254/1,
- otp_11772/1, otp_11771/1, otp_11872/1,
- export_all/1,
- bif_clash/1,
- behaviour_basic/1, behaviour_multiple/1, otp_11861/1,
- otp_7550/1,
- otp_8051/1,
- format_warn/1,
- on_load_successful/1, on_load_failing/1,
- too_many_arguments/1,
- basic_errors/1,bin_syntax_errors/1,
- predef/1,
- maps/1,maps_type/1,otp_11851/1,otp_11879/1,otp_13230/1,
- record_errors/1
- ]).
-
-init_per_testcase(_Case, Config) ->
- Config.
-
-end_per_testcase(_Case, _Config) ->
- ok.
+-export([all/0, suite/0, groups/0]).
+
+-export([unused_vars_warn_basic/1,
+ unused_vars_warn_lc/1,
+ unused_vars_warn_rec/1,
+ unused_vars_warn_fun/1,
+ unused_vars_OTP_4858/1,
+ unused_unsafe_vars_warn/1,
+ export_vars_warn/1,
+ shadow_vars/1,
+ unused_import/1,
+ unused_function/1,
+ unsafe_vars/1,unsafe_vars2/1,
+ unsafe_vars_try/1,
+ unsized_binary_in_bin_gen_pattern/1,
+ guard/1, otp_4886/1, otp_4988/1, otp_5091/1, otp_5276/1, otp_5338/1,
+ otp_5362/1, otp_5371/1, otp_7227/1, otp_5494/1, otp_5644/1, otp_5878/1,
+ otp_5917/1, otp_6585/1, otp_6885/1, otp_10436/1, otp_11254/1,
+ otp_11772/1, otp_11771/1, otp_11872/1,
+ export_all/1,
+ bif_clash/1,
+ behaviour_basic/1, behaviour_multiple/1, otp_11861/1,
+ otp_7550/1,
+ otp_8051/1,
+ format_warn/1,
+ on_load_successful/1, on_load_failing/1,
+ too_many_arguments/1,
+ basic_errors/1,bin_syntax_errors/1,
+ predef/1,
+ maps/1,maps_type/1,maps_parallel_match/1,
+ otp_11851/1,otp_11879/1,otp_13230/1,
+ record_errors/1]).
suite() ->
[{ct_hooks,[ts_install_cth]},
@@ -91,7 +82,8 @@ all() ->
bif_clash, behaviour_basic, behaviour_multiple, otp_11861,
otp_7550, otp_8051, format_warn, {group, on_load},
too_many_arguments, basic_errors, bin_syntax_errors, predef,
- maps, maps_type, otp_11851, otp_11879, otp_13230,
+ maps, maps_type, maps_parallel_match,
+ otp_11851, otp_11879, otp_13230,
record_errors].
groups() ->
@@ -101,19 +93,6 @@ groups() ->
unused_vars_OTP_4858, unused_unsafe_vars_warn]},
{on_load, [], [on_load_successful, on_load_failing]}].
-init_per_suite(Config) ->
- Config.
-
-end_per_suite(_Config) ->
- ok.
-
-init_per_group(_GroupName, Config) ->
- Config.
-
-end_per_group(_GroupName, Config) ->
- Config.
-
-
%% Warnings for unused variables in some simple cases.
unused_vars_warn_basic(Config) when is_list(Config) ->
@@ -3583,8 +3562,6 @@ predef(Config) when is_list(Config) ->
ok.
maps(Config) ->
- %% TODO: test key patterns, not done because map patterns are going to be
- %% changed a lot.
Ts = [{illegal_map_construction,
<<"t() ->
#{ a := b,
@@ -3626,6 +3603,26 @@ maps(Config) ->
{errors,[{1,erl_lint,illegal_map_construction},
{1,erl_lint,{unbound_var,'X'}}],
[]}},
+ {legal_map_pattern,
+ <<"
+ -record(mapkey, {a=1,b=2}).
+ t(M,K1) ->
+ #{ a := 1,
+ $a := 1, $z := 99,
+ #{a=>val} := 2,
+ K1 := 1337,
+ #mapkey{a = 10} := wat,
+ #{{a,val}=>val} := 2,
+ #{ \"hi\" => wazzup, hi => ho } := yep,
+ ok := 1.0,
+ [3+3] := nope,
+ 1.0 := yep,
+ {3.0+3} := nope,
+ {yep} := yep
+ } = M.
+ ">>,
+ [],
+ []},
{legal_map_construction,
<<"t(V) -> #{ a => 1,
#{a=>V} => 2,
@@ -3692,6 +3689,51 @@ maps_type(Config) when is_list(Config) ->
[] = run(Config, Ts),
ok.
+maps_parallel_match(Config) when is_list(Config) ->
+ Ts = [{parallel_map_patterns_unbound1,
+ <<"
+ t(#{} = M) ->
+ #{K := V} = #{k := K} = M,
+ V.
+ ">>,
+ [],
+ {errors,[{3,erl_lint,{unbound_var,'K'}}],[]}},
+ {parallel_map_patterns_unbound2,
+ <<"
+ t(#{} = M) ->
+ #{K1 := V1} =
+ #{K2 := V2} =
+ #{k1 := K1,k2 := K2} = M,
+ [V1,V2].
+ ">>,
+ [],
+ {errors,[{3,erl_lint,{unbound_var,'K1'}},
+ {3,erl_lint,{unbound_var,'K1'}},
+ {4,erl_lint,{unbound_var,'K2'}},
+ {4,erl_lint,{unbound_var,'K2'}}],[]}},
+ {parallel_map_patterns_bound,
+ <<"
+ t(#{} = M,K1,K2) ->
+ #{K1 := V1} =
+ #{K2 := V2} =
+ #{k1 := K1,k2 := K2} = M,
+ [V1,V2].
+ ">>,
+ [],
+ []},
+ {parallel_map_patterns_literal,
+ <<"
+ t(#{} = M) ->
+ #{k1 := V1} =
+ #{k2 := V2} =
+ #{k1 := V1,k2 := V2} = M,
+ [V1,V2].
+ ">>,
+ [],
+ []}],
+ [] = run(Config, Ts),
+ ok.
+
%% OTP-11851: More atoms can be used as type names + bug fixes.
otp_11851(Config) when is_list(Config) ->
Ts = [
diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl
index 6dc285e448..a48ba7b5b7 100644
--- a/lib/stdlib/test/erl_pp_SUITE.erl
+++ b/lib/stdlib/test/erl_pp_SUITE.erl
@@ -50,7 +50,7 @@
otp_6321/1, otp_6911/1, otp_6914/1, otp_8150/1, otp_8238/1,
otp_8473/1, otp_8522/1, otp_8567/1, otp_8664/1, otp_9147/1,
- otp_10302/1, otp_10820/1, otp_11100/1, otp_11861/1]).
+ otp_10302/1, otp_10820/1, otp_11100/1, otp_11861/1, pr_1014/1]).
%% Internal export.
-export([ehook/6]).
@@ -79,7 +79,7 @@ groups() ->
{tickets, [],
[otp_6321, otp_6911, otp_6914, otp_8150, otp_8238,
otp_8473, otp_8522, otp_8567, otp_8664, otp_9147,
- otp_10302, otp_10820, otp_11100, otp_11861]}].
+ otp_10302, otp_10820, otp_11100, otp_11861, pr_1014]}].
init_per_suite(Config) ->
Config.
@@ -902,6 +902,7 @@ maps_syntax(Config) when is_list(Config) ->
"-compile(export_all).\n"
"-type t1() :: map().\n"
"-type t2() :: #{ atom() => integer(), atom() => float() }.\n"
+ "-type t3() :: #{ atom() := integer(), atom() := float() }.\n"
"-type u() :: #{a => (I :: integer()) | (A :: atom()),\n"
" (X :: atom()) | (Y :: atom()) =>\n"
" (I :: integer()) | (A :: atom())}.\n"
@@ -1106,6 +1107,24 @@ otp_11861(Config) when is_list(Config) ->
pf(Form) ->
lists:flatten(erl_pp:form(Form, none)).
+pr_1014(Config) ->
+ ok = pp_forms(<<"-type t() :: #{_ => _}. ">>),
+ ok = pp_forms(<<"-type t() :: #{any() => _}. ">>),
+ ok = pp_forms(<<"-type t() :: #{_ => any()}. ">>),
+ ok = pp_forms(<<"-type t() :: #{any() => any()}. ">>),
+ ok = pp_forms(<<"-type t() :: #{...}. ">>),
+ ok = pp_forms(<<"-type t() :: #{atom() := integer(), ...}. ">>),
+
+ FileName = filename('pr_1014.erl', Config),
+ C = <<"-module pr_1014.\n"
+ "-compile export_all.\n"
+ "-type m() :: #{..., a := integer()}.\n">>,
+ ok = file:write_file(FileName, C),
+ {error,[{_,[{3,erl_parse,["syntax error before: ","','"]}]}],_} =
+ compile:file(FileName, [return]),
+
+ ok.
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
compile(Config, Tests) ->
diff --git a/lib/stdlib/test/lists_SUITE.erl b/lib/stdlib/test/lists_SUITE.erl
index 6f2a510f65..531e97e8d6 100644
--- a/lib/stdlib/test/lists_SUITE.erl
+++ b/lib/stdlib/test/lists_SUITE.erl
@@ -55,6 +55,7 @@
ufunsort_error/1,
zip_unzip/1, zip_unzip3/1, zipwith/1, zipwith3/1,
filter_partition/1,
+ join/1,
otp_5939/1, otp_6023/1, otp_6606/1, otp_7230/1,
suffix/1, subtract/1, droplast/1, hof/1]).
@@ -119,7 +120,7 @@ groups() ->
{tickets, [parallel], [otp_5939, otp_6023, otp_6606, otp_7230]},
{zip, [parallel], [zip_unzip, zip_unzip3, zipwith, zipwith3]},
{misc, [parallel], [reverse, member, dropwhile, takewhile,
- filter_partition, suffix, subtract,
+ filter_partition, suffix, subtract, join,
hof]}
].
@@ -2413,6 +2414,19 @@ zipwith3(Config) when is_list(Config) ->
ok.
+%% Test lists:join/2
+join(Config) when is_list(Config) ->
+ A = [a,b,c],
+ Sep = x,
+ [a,x,b,x,c] = lists:join(Sep, A),
+
+ B = [b],
+ [b] = lists:join(Sep, B),
+
+ C = [],
+ [] = lists:join(Sep, C),
+ ok.
+
%% Test lists:filter/2, lists:partition/2.
filter_partition(Config) when is_list(Config) ->
F = fun(I) -> I rem 2 =:= 0 end,
diff --git a/lib/stdlib/test/maps_SUITE.erl b/lib/stdlib/test/maps_SUITE.erl
index 8b3a8d7ae2..42e669a799 100644
--- a/lib/stdlib/test/maps_SUITE.erl
+++ b/lib/stdlib/test/maps_SUITE.erl
@@ -25,15 +25,10 @@
-include_lib("common_test/include/ct.hrl").
-%% Test server specific exports
--export([all/0]).
--export([suite/0]).
--export([init_per_suite/1]).
--export([end_per_suite/1]).
--export([init_per_testcase/2]).
--export([end_per_testcase/2]).
-
--export([t_get_3/1, t_filter_2/1,
+-export([all/0, suite/0]).
+
+-export([t_update_with_3/1, t_update_with_4/1,
+ t_get_3/1, t_filter_2/1,
t_fold_3/1,t_map_2/1,t_size_1/1,
t_with_2/1,t_without_2/1]).
@@ -41,29 +36,56 @@
%%-define(badarg(F,Args), {'EXIT', {badarg, [{maps,F,Args,_}|_]}}).
%% silly broken hipe
-define(badmap(V,F,_Args), {'EXIT', {{badmap,V}, [{maps,F,_,_}|_]}}).
+-define(badkey(K,F,_Args), {'EXIT', {{badkey,K}, [{maps,F,_,_}|_]}}).
-define(badarg(F,_Args), {'EXIT', {badarg, [{maps,F,_,_}|_]}}).
suite() ->
- [{ct_hooks, [ts_install_cth]},
+ [{ct_hooks,[ts_install_cth]},
{timetrap,{minutes,1}}].
all() ->
- [t_get_3,t_filter_2,
+ [t_update_with_3,t_update_with_4,
+ t_get_3,t_filter_2,
t_fold_3,t_map_2,t_size_1,
t_with_2,t_without_2].
-init_per_suite(Config) ->
- Config.
+t_update_with_3(Config) when is_list(Config) ->
+ V1 = value1,
+ V2 = <<"value2">>,
+ V3 = "value3",
+ Map = #{ key1 => V1, key2 => V2, "key3" => V3 },
+ Fun = fun(V) -> [V,V,{V,V}] end,
+
+ #{ key1 := [V1,V1,{V1,V1}] } = maps:update_with(key1,Fun,Map),
+ #{ key2 := [V2,V2,{V2,V2}] } = maps:update_with(key2,Fun,Map),
+ #{ "key3" := [V3,V3,{V3,V3}] } = maps:update_with("key3",Fun,Map),
-end_per_suite(_Config) ->
+ %% error case
+ ?badmap(b,update_with,[[a,b],a,b]) = (catch maps:update_with([a,b],id(a),b)),
+ ?badarg(update_with,[[a,b],a,#{}]) = (catch maps:update_with([a,b],id(a),#{})),
+ ?badkey([a,b],update_with,[[a,b],Fun,#{}]) = (catch maps:update_with([a,b],Fun,#{})),
ok.
-init_per_testcase(_Case, Config) ->
- Config.
+t_update_with_4(Config) when is_list(Config) ->
+ V1 = value1,
+ V2 = <<"value2">>,
+ V3 = "value3",
+ Map = #{ key1 => V1, key2 => V2, "key3" => V3 },
+ Fun = fun(V) -> [V,V,{V,V}] end,
+ Init = 3,
+
+ #{ key1 := [V1,V1,{V1,V1}] } = maps:update_with(key1,Fun,Init,Map),
+ #{ key2 := [V2,V2,{V2,V2}] } = maps:update_with(key2,Fun,Init,Map),
+ #{ "key3" := [V3,V3,{V3,V3}] } = maps:update_with("key3",Fun,Init,Map),
-end_per_testcase(_Case, _Config) ->
+ #{ key3 := Init } = maps:update_with(key3,Fun,Init,Map),
+
+ %% error case
+ ?badmap(b,update_with,[[a,b],a,b]) = (catch maps:update_with([a,b],id(a),b)),
+ ?badarg(update_with,[[a,b],a,#{}]) = (catch maps:update_with([a,b],id(a),#{})),
ok.
+
t_get_3(Config) when is_list(Config) ->
Map = #{ key1 => value1, key2 => value2 },
DefaultValue = "Default value",