aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test/edlin_expand_SUITE.erl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test/edlin_expand_SUITE.erl')
-rw-r--r--lib/stdlib/test/edlin_expand_SUITE.erl144
1 files changed, 114 insertions, 30 deletions
diff --git a/lib/stdlib/test/edlin_expand_SUITE.erl b/lib/stdlib/test/edlin_expand_SUITE.erl
index 6fdc4c35df..5c2b1965ba 100644
--- a/lib/stdlib/test/edlin_expand_SUITE.erl
+++ b/lib/stdlib/test/edlin_expand_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2010-2012. All Rights Reserved.
+%% Copyright Ericsson AB 2010-2017. 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.
@@ -19,29 +19,26 @@
%%
-module(edlin_expand_SUITE).
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_testcase/2, end_per_testcase/2,
init_per_group/2,end_per_group/2]).
+-export([normal/1, quoted_fun/1, quoted_module/1, quoted_both/1, erl_1152/1,
+ erl_352/1, unicode/1]).
--export([normal/1, quoted_fun/1, quoted_module/1, quoted_both/1]).
-
--export([init_per_testcase/2, end_per_testcase/2]).
-
--include_lib("test_server/include/test_server.hrl").
-
-%% Default timetrap timeout (set in init_per_testcase).
--define(default_timeout, ?t:minutes(1)).
+-include_lib("common_test/include/ct.hrl").
init_per_testcase(_Case, Config) ->
- Dog = ?t:timetrap(?default_timeout),
- [{watchdog, Dog} | Config].
-end_per_testcase(_Case, Config) ->
- Dog = ?config(watchdog, Config),
- test_server:timetrap_cancel(Dog),
+ Config.
+
+end_per_testcase(_Case, _Config) ->
ok.
-suite() -> [{ct_hooks,[ts_install_cth]}].
+suite() ->
+ [{ct_hooks,[ts_install_cth]},
+ {timetrap,{minutes,1}}].
all() ->
- [normal, quoted_fun, quoted_module, quoted_both].
+ [normal, quoted_fun, quoted_module, quoted_both, erl_1152, erl_352,
+ unicode].
groups() ->
[].
@@ -63,10 +60,6 @@ end_per_group(_GroupName, Config) ->
Config.
-normal(doc) ->
- [""];
-normal(suite) ->
- [];
normal(Config) when is_list(Config) ->
{module,expand_test} = c:l(expand_test),
%% These tests might fail if another module with the prefix
@@ -85,10 +78,7 @@ normal(Config) when is_list(Config) ->
{yes,"arity_entirely()",[]} = do_expand("expand_test:expand0"),
ok.
-quoted_fun(doc) ->
- ["Normal module name, some function names using quoted atoms"];
-quoted_fun(suite) ->
- [];
+%% Normal module name, some function names using quoted atoms.
quoted_fun(Config) when is_list(Config) ->
{module,expand_test} = c:l(expand_test),
{module,expand_test1} = c:l(expand_test1),
@@ -121,10 +111,6 @@ quoted_fun(Config) when is_list(Config) ->
{yes,"(",[]} = do_expand("expand_test:module_info"),
ok.
-quoted_module(doc) ->
- [""];
-quoted_module(suite) ->
- [];
quoted_module(Config) when is_list(Config) ->
{module,'ExpandTestCaps'} = c:l('ExpandTestCaps'),
{yes, "Caps':", []} = do_expand("'ExpandTest"),
@@ -138,8 +124,6 @@ quoted_module(Config) when is_list(Config) ->
{"a_less_fun_name",1}]} = do_expand("'ExpandTestCaps':a_"),
ok.
-quoted_both(suite) ->
- [];
quoted_both(Config) when is_list(Config) ->
{module,'ExpandTestCaps'} = c:l('ExpandTestCaps'),
{module,'ExpandTestCaps1'} = c:l('ExpandTestCaps1'),
@@ -167,5 +151,105 @@ quoted_both(Config) when is_list(Config) ->
{yes,"weird-fun-name'()",[]} = do_expand("'ExpandTestCaps1':'#"),
ok.
+%% Note: pull request #1152.
+erl_1152(Config) when is_list(Config) ->
+ "\n"++"foo"++" "++[1089]++_ = do_format(["foo",[1089]]),
+ ok.
+
+erl_352(Config) when is_list(Config) ->
+ erl_352_test(3, 3),
+
+ erl_352_test(3, 75),
+ erl_352_test(3, 76, [trailing]),
+ erl_352_test(4, 74),
+ erl_352_test(4, 75, [leading]),
+ erl_352_test(4, 76, [leading, trailing]),
+
+ erl_352_test(75, 3),
+ erl_352_test(76, 3, [leading]),
+ erl_352_test(74, 4),
+ erl_352_test(75, 4, [leading]),
+ erl_352_test(76, 4, [leading]),
+
+ erl_352_test(74, 74, [leading]),
+ erl_352_test(74, 75, [leading]),
+ erl_352_test(74, 76, [leading, trailing]).
+
+erl_352_test(PrefixLen, SuffixLen) ->
+ erl_352_test(PrefixLen, SuffixLen, []).
+
+erl_352_test(PrefixLen, SuffixLen, Dots) ->
+ io:format("\nPrefixLen = ~w, SuffixLen = ~w\n", [PrefixLen, SuffixLen]),
+
+ PrefixM = lists:duplicate(PrefixLen, $p),
+ SuffixM = lists:duplicate(SuffixLen, $s),
+ LM = [PrefixM ++ S ++ SuffixM || S <- ["1", "2"]],
+ StrM = do_format(LM),
+ check_leading(StrM, "", PrefixM, SuffixM, Dots),
+
+ PrefixF = lists:duplicate(PrefixLen, $p),
+ SuffixF = lists:duplicate(SuffixLen-2, $s),
+ LF = [{PrefixF ++ S ++ SuffixF, 1} || S <- ["1", "2"]],
+ StrF = do_format(LF),
+ true = check_leading(StrF, "/1", PrefixF, SuffixF, Dots),
+
+ ok.
+
+check_leading(FormStr, ArityStr, Prefix, Suffix, Dots) ->
+ List = string:tokens(FormStr, "\n "),
+ io:format("~p\n", [List]),
+ true = lists:all(fun(L) -> length(L) < 80 end, List),
+ case lists:member(leading, Dots) of
+ true ->
+ true = lists:all(fun(L) ->
+ {"...", Rest} = lists:split(3, L),
+ check_trailing(Rest, ArityStr,
+ Suffix, Dots)
+ end, List);
+ false ->
+ true = lists:all(fun(L) ->
+ {Prefix, Rest} =
+ lists:split(length(Prefix), L),
+ check_trailing(Rest, ArityStr,
+ Suffix, Dots)
+ end, List)
+ end.
+
+check_trailing([I|Str], ArityStr, Suffix, Dots) ->
+ true = lists:member(I, [$1, $2]),
+ case lists:member(trailing, Dots) of
+ true ->
+ {Rest, "..." ++ ArityStr} =
+ lists:split(length(Str) - (3 + length(ArityStr)), Str),
+ true = lists:prefix(Rest, Suffix);
+ false ->
+ {Rest, ArityStr} =
+ lists:split(length(Str) - length(ArityStr), Str),
+ Rest =:= Suffix
+ end.
+
+unicode(Config) when is_list(Config) ->
+ {module,unicode_expand} = c:l('unicode_expand'),
+ {no,[],[{"'кlирилли́ческий атом'",0},
+ {"'кlирилли́ческий атом'",1},
+ {"'кlирилли́ческий атомB'",1},
+ {"module_info",0},
+ {"module_info",1}]} = do_expand("unicode_expand:"),
+ {yes,"рилли́ческий атом", []} = do_expand("unicode_expand:'кlи"),
+ {yes,"еский атом", []} = do_expand("unicode_expand:'кlирилли́ч"),
+ {yes,"(",[]} = do_expand("unicode_expand:'кlирилли́ческий атомB'"),
+ "\n'кlирилли́ческий атом'/0 'кlирилли́ческий атом'/1 "
+ "'кlирилли́ческий атомB'/1 \nmodule_info/0 "
+ "module_info/1 \n" =
+ do_format([{"'кlирилли́ческий атом'",0},
+ {"'кlирилли́ческий атом'",1},
+ {"'кlирилли́ческий атомB'",1},
+ {"module_info",0},
+ {"module_info",1}]),
+ ok.
+
do_expand(String) ->
edlin_expand:expand(lists:reverse(String)).
+
+do_format(StringList) ->
+ lists:flatten(edlin_expand:format_matches(StringList)).