~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/stdlib/test/edlin_expand_SUITE.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 2010-2011. All Rights Reserved.
 
5
%%
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%%
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%%
 
17
%% %CopyrightEnd%
 
18
%%
 
19
-module(edlin_expand_SUITE).
 
20
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 
21
         init_per_group/2,end_per_group/2]).
 
22
 
 
23
-export([normal/1, quoted_fun/1, quoted_module/1, quoted_both/1]).
 
24
 
 
25
-export([init_per_testcase/2, end_per_testcase/2]).
 
26
 
 
27
-include_lib("test_server/include/test_server.hrl").
 
28
 
 
29
% Default timetrap timeout (set in init_per_testcase).
 
30
-define(default_timeout, ?t:minutes(1)).
 
31
 
 
32
init_per_testcase(_Case, Config) ->
 
33
    ?line Dog = ?t:timetrap(?default_timeout),
 
34
    [{watchdog, Dog} | Config].
 
35
end_per_testcase(_Case, Config) ->
 
36
    Dog = ?config(watchdog, Config),
 
37
    test_server:timetrap_cancel(Dog),
 
38
    ok.
 
39
 
 
40
suite() -> [{ct_hooks,[ts_install_cth]}].
 
41
 
 
42
all() -> 
 
43
    [normal, quoted_fun, quoted_module, quoted_both].
 
44
 
 
45
groups() -> 
 
46
    [].
 
47
 
 
48
init_per_suite(Config) ->
 
49
    true = code:delete(expand_test),
 
50
    true = code:delete(expand_test1),
 
51
    true = code:delete('ExpandTestCaps'),
 
52
    true = code:delete('ExpandTestCaps1'),
 
53
    Config.
 
54
 
 
55
end_per_suite(_Config) ->
 
56
    ok.
 
57
 
 
58
init_per_group(_GroupName, Config) ->
 
59
    Config.
 
60
 
 
61
end_per_group(_GroupName, Config) ->
 
62
    Config.
 
63
 
 
64
 
 
65
normal(doc) ->
 
66
    [""];
 
67
normal(suite) ->
 
68
    [];
 
69
normal(Config) when is_list(Config) ->
 
70
    ?line {module,expand_test} = c:l(expand_test),
 
71
    % These tests might fail if another module with the prefix "expand_" happens
 
72
    % to also be loaded.
 
73
    ?line {yes, "test:", []} = edlin_expand:expand(lists:reverse("expand_")),
 
74
    ?line {no, [], []} = edlin_expand:expand(lists:reverse("expandXX_")),
 
75
    ?line {no,[],
 
76
           [{"a_fun_name",1},
 
77
            {"a_less_fun_name",1},
 
78
            {"b_comes_after_a",1},
 
79
            {"module_info",0},
 
80
            {"module_info",1}]} = edlin_expand:expand(lists:reverse("expand_test:")),
 
81
    ?line {yes,[],[{"a_fun_name",1},
 
82
                   {"a_less_fun_name",1}]} = edlin_expand:expand(
 
83
                                               lists:reverse("expand_test:a_")),
 
84
    ok.
 
85
 
 
86
quoted_fun(doc) ->
 
87
    ["Normal module name, some function names using quoted atoms"];
 
88
quoted_fun(suite) ->
 
89
    [];
 
90
quoted_fun(Config) when is_list(Config) ->
 
91
    ?line {module,expand_test} = c:l(expand_test),
 
92
    ?line {module,expand_test1} = c:l(expand_test1),
 
93
    %% should be no colon after test this time
 
94
    ?line {yes, "test", []} = edlin_expand:expand(lists:reverse("expand_")),
 
95
    ?line {no, [], []} = edlin_expand:expand(lists:reverse("expandXX_")),
 
96
    ?line {no,[],[{"'#weird-fun-name'",0},
 
97
                  {"'Quoted_fun_name'",0},
 
98
                  {"'Quoted_fun_too'",0},
 
99
                  {"a_fun_name",1},
 
100
                  {"a_less_fun_name",1},
 
101
                  {"b_comes_after_a",1},
 
102
                  {"module_info",0},
 
103
                  {"module_info",1}]} = edlin_expand:expand(
 
104
                                          lists:reverse("expand_test1:")),
 
105
    ?line {yes,"_",[]} = edlin_expand:expand(
 
106
                           lists:reverse("expand_test1:a")),
 
107
    ?line {yes,[],[{"a_fun_name",1},
 
108
                   {"a_less_fun_name",1}]} = edlin_expand:expand(
 
109
                                               lists:reverse("expand_test1:a_")),
 
110
    ?line {yes,[],
 
111
           [{"'#weird-fun-name'",0},
 
112
            {"'Quoted_fun_name'",0},
 
113
            {"'Quoted_fun_too'",0}]} = edlin_expand:expand(
 
114
                                         lists:reverse("expand_test1:'")),
 
115
    ?line {yes,"uoted_fun_",[]} = edlin_expand:expand(
 
116
                                    lists:reverse("expand_test1:'Q")),
 
117
    ?line {yes,[],
 
118
           [{"'Quoted_fun_name'",0},
 
119
            {"'Quoted_fun_too'",0}]} = edlin_expand:expand(
 
120
                                         lists:reverse("expand_test1:'Quoted_fun_")),
 
121
    ?line {yes,"weird-fun-name'(",[]} = edlin_expand:expand(
 
122
                                          lists:reverse("expand_test1:'#")),
 
123
    ok.
 
124
 
 
125
quoted_module(doc) ->
 
126
    [""];
 
127
quoted_module(suite) ->
 
128
    [];
 
129
quoted_module(Config) when is_list(Config) ->
 
130
    ?line {module,'ExpandTestCaps'} = c:l('ExpandTestCaps'),
 
131
    ?line {yes, "Caps':", []} = edlin_expand:expand(lists:reverse("'ExpandTest")),
 
132
    ?line {no,[],
 
133
           [{"a_fun_name",1},
 
134
            {"a_less_fun_name",1},
 
135
            {"b_comes_after_a",1},
 
136
            {"module_info",0},
 
137
            {"module_info",1}]} = edlin_expand:expand(lists:reverse("'ExpandTestCaps':")),
 
138
    ?line {yes,[],[{"a_fun_name",1},
 
139
                   {"a_less_fun_name",1}]} = edlin_expand:expand(
 
140
                                               lists:reverse("'ExpandTestCaps':a_")),
 
141
    ok.
 
142
 
 
143
quoted_both(suite) ->
 
144
    [];
 
145
quoted_both(Config) when is_list(Config) ->
 
146
    ?line {module,'ExpandTestCaps'} = c:l('ExpandTestCaps'),
 
147
    ?line {module,'ExpandTestCaps1'} = c:l('ExpandTestCaps1'),
 
148
    %% should be no colon (or quote) after test this time
 
149
    ?line {yes, "Caps", []} = edlin_expand:expand(lists:reverse("'ExpandTest")),
 
150
    ?line {no,[],[{"'#weird-fun-name'",0},
 
151
                  {"'Quoted_fun_name'",0},
 
152
                  {"'Quoted_fun_too'",0},
 
153
                  {"a_fun_name",1},
 
154
                  {"a_less_fun_name",1},
 
155
                  {"b_comes_after_a",1},
 
156
                  {"module_info",0},
 
157
                  {"module_info",1}]} = edlin_expand:expand(
 
158
                                          lists:reverse("'ExpandTestCaps1':")),
 
159
    ?line {yes,"_",[]} = edlin_expand:expand(
 
160
                           lists:reverse("'ExpandTestCaps1':a")),
 
161
    ?line {yes,[],[{"a_fun_name",1},
 
162
                   {"a_less_fun_name",1}]} = edlin_expand:expand(
 
163
                                               lists:reverse("'ExpandTestCaps1':a_")),
 
164
    ?line {yes,[],
 
165
           [{"'#weird-fun-name'",0},
 
166
            {"'Quoted_fun_name'",0},
 
167
            {"'Quoted_fun_too'",0}]} = edlin_expand:expand(
 
168
                                         lists:reverse("'ExpandTestCaps1':'")),
 
169
    ?line {yes,"uoted_fun_",[]} = edlin_expand:expand(
 
170
                                    lists:reverse("'ExpandTestCaps1':'Q")),
 
171
    ?line {yes,[],
 
172
           [{"'Quoted_fun_name'",0},
 
173
            {"'Quoted_fun_too'",0}]} = edlin_expand:expand(
 
174
                                         lists:reverse("'ExpandTestCaps1':'Quoted_fun_")),
 
175
    ?line {yes,"weird-fun-name'(",[]} = edlin_expand:expand(
 
176
                                          lists:reverse("'ExpandTestCaps1':'#")),
 
177
    ok.