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

« back to all changes in this revision

Viewing changes to lib/debugger/test/int_eval_SUITE_data/my_int_eval_module.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 1999-2010. 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
 
 
20
%%
 
21
-module(my_int_eval_module).
 
22
-stupid_attribute({a,b}).
 
23
 
 
24
-export([ets_new/0,ets_delete/1,spawn_test/0,apply_test/1,external_call_test/1]).
 
25
-export([check_exports/1,check_module_info/2]).
 
26
-export([give_me_a_fun_0/0,give_me_a_fun_0/1,give_me_a_fun_1/2,
 
27
         give_me_a_bad_fun/0, do_apply/1, do_apply/2]).
 
28
-export([please_call_exit/1,i_will_do_the_exit/1]).
 
29
-export([more_catch/1,more_nocatch/1,exit_me/0]).
 
30
-export([f/1, f_try/1, f_catch/1]).
 
31
-export([otp_5837/1, otp_8310/0]).
 
32
 
 
33
%% Internal exports.
 
34
-export([echo/2,my_subtract/2,catch_a_ball/0,throw_a_ball/0]).
 
35
-export([i_am_exported/1]).
 
36
 
 
37
-import(lists, [member/2]).
 
38
 
 
39
-define(line,put(test_server_loc,{?MODULE,?LINE}),).
 
40
-define(t,test_server).
 
41
-define(m,test_server:match).
 
42
-define(config,test_server:lookup_config).
 
43
 
 
44
ets_new() ->
 
45
    Id = ets:new(my_int_eval_table, [private]),
 
46
    Id.
 
47
 
 
48
ets_delete(Tab) ->
 
49
    ets:delete(Tab).
 
50
 
 
51
%% Spawning.
 
52
 
 
53
spawn_test() ->
 
54
    Term = {a,tuple},
 
55
    Pid = spawn_link(?MODULE, echo, [self(),Term]),
 
56
    receive
 
57
        {result,Pid,Term} -> ok;
 
58
        Other -> {bad_response,Other}
 
59
    after 5000 ->
 
60
            timeout
 
61
    end.
 
62
 
 
63
echo(Parent, Term) ->
 
64
    Parent ! {result,self(),Term}.
 
65
 
 
66
%% Applying.
 
67
 
 
68
apply_test(Fun) ->
 
69
    42 = Fun(number(2), number(40)),
 
70
    12 = apply(Fun, [number(7),number(5)]),
 
71
 
 
72
    Mod = module(),
 
73
    Func = func(),
 
74
    [a] = Mod:my_subtract(same([a,b,c]), same([b,c])),
 
75
    [a,b] = Mod:Func(same([a,b,c]), same([c])),
 
76
    [a,b,d] = ?MODULE:Func(same([a,b,c,d]), same([c])),
 
77
    [d,e] = apply(Mod, Func, [same([d,e,f]), same([f])]),
 
78
    [3] = apply(?MODULE, Func, [same([3,4]),same([4])]),
 
79
 
 
80
    %% This is obsolete, but it should work anyway.
 
81
    HomeMadeFun = {?MODULE,my_subtract},
 
82
    [a] = HomeMadeFun(same([a,x,c]), same([x,c])),
 
83
    [x] = apply(HomeMadeFun, [[x,y],[y,z]]),
 
84
 
 
85
    ok.
 
86
 
 
87
number(X) -> {number,X}.
 
88
module() -> ?MODULE.
 
89
func() -> my_subtract.
 
90
same(X) -> X.
 
91
 
 
92
my_subtract(X, Y) -> X -- Y.
 
93
 
 
94
%% Catch and throw.
 
95
 
 
96
catch_a_ball() ->
 
97
    {a,ball} = (catch throw_a_ball()),
 
98
    ok.
 
99
 
 
100
throw_a_ball() ->
 
101
    throw({a,ball}),
 
102
    not_ok.
 
103
 
 
104
exit_me() ->
 
105
    exit({int,exit}).
 
106
 
 
107
more_catch(Fun) ->
 
108
    case catch lists:filter(Fun, [a]) of
 
109
        {'EXIT', {_, exit}} ->
 
110
            ok;
 
111
        Else -> Else
 
112
    end.
 
113
 
 
114
more_nocatch(Fun) ->
 
115
    lists:filter(Fun, [a]).
 
116
 
 
117
%% External calls.
 
118
 
 
119
external_call_test(Data) ->
 
120
    {'EXIT',{undef,[{?MODULE,not_exported,[42,Data]}|_]}} =
 
121
        (catch ?MODULE:not_exported(42, Data)),
 
122
    {yes,Data} = i_am_exported(Data),
 
123
    {yes,Data} = ?MODULE:i_am_exported(Data),
 
124
 
 
125
    %% Excercise the function cache in the interpreter.
 
126
 
 
127
    {ok,Data,[a,b]} = not_exported(Data, [a,b]),
 
128
    {yes,Data} = i_am_exported(Data),
 
129
    {ok,Data,[a,b]} = not_exported(Data, [a,b]),
 
130
    {'EXIT',{undef,[{?MODULE,not_exported,[7,Data]}|_]}} =
 
131
        (catch ?MODULE:not_exported(7, Data)),
 
132
    {yes,Data} = ?MODULE:i_am_exported(Data),
 
133
    ok.
 
134
 
 
135
not_exported(N, D) ->
 
136
    {ok,N,D}.
 
137
 
 
138
i_am_exported(D) ->
 
139
    {yes,D}.
 
140
 
 
141
%% The module_info/0,1 functions and list comprehensions (funs).
 
142
 
 
143
check_exports(Exp) ->
 
144
    %% Check the structure of the export list and that there are more
 
145
    %% than 4 elements.
 
146
 
 
147
    Exp = [{F,A} || {F,A} <- Exp, erlang:is_atom(F), erlang:is_integer(A)],
 
148
    case length(Exp) of
 
149
        Len when Len > 4 -> ok
 
150
    end.
 
151
 
 
152
check_module_info(ModInfo, Exports) ->
 
153
    ModInfo = module_info(),
 
154
    Exports = module_info(exports),
 
155
    ok.
 
156
 
 
157
%% Testcase apply_interpreted_fun/1.
 
158
 
 
159
give_me_a_fun_0() ->
 
160
    fun() -> perfectly_alright end.
 
161
 
 
162
give_me_a_fun_0(Term) ->
 
163
    fun() -> {ok,Term} end.
 
164
 
 
165
give_me_a_fun_1(Min, Max) ->
 
166
    Seq = lists:seq(Min, Max),
 
167
    fun (L) when list(L) ->
 
168
            [Info || {Key,Info} <- L, lists:member(Key, Seq)];
 
169
        (T) when tuple(T) ->
 
170
            L = tuple_to_list(T),
 
171
            F = fun({Key,Info}) ->
 
172
                        case lists:member(Key, Seq) of
 
173
                            true -> Info;
 
174
                            false -> false
 
175
                        end
 
176
                end,
 
177
            list_to_tuple(lists:map(F, L))
 
178
    end.
 
179
 
 
180
give_me_a_bad_fun() ->
 
181
    fun(Arg) -> erlang:error(Arg) end.
 
182
 
 
183
do_apply(Fun) ->
 
184
    Fun().
 
185
do_apply(Fun, Arg) ->
 
186
    Fun(Arg).
 
187
 
 
188
 
 
189
please_call_exit(Reason) ->
 
190
    put(asked_to_call_exit, Reason),
 
191
    put(will_call_my_good_friend, ''),
 
192
    Res = int_eval_SUITE:applier(?MODULE, i_will_do_the_exit, [Reason]),
 
193
 
 
194
    %% We don't want a tail-recursive call above.
 
195
    io:format("Returned from exit/1 -- how strange\n").
 
196
 
 
197
i_will_do_the_exit(Reason) ->
 
198
    exit(Reason).
 
199
 
 
200
f(Arg) ->
 
201
    g(Arg).
 
202
 
 
203
f_try(Arg) ->
 
204
    try g(Arg)
 
205
    catch
 
206
        Class:Reason ->
 
207
            {Class, Reason}
 
208
    end.
 
209
 
 
210
f_catch(Arg) ->
 
211
    catch g(Arg).
 
212
 
 
213
g({error, Reason}) ->
 
214
    erlang:error(Reason);
 
215
g({exit, Reason}) ->
 
216
    erlang:exit(Reason);
 
217
g({throw, Reason}) ->
 
218
    erlang:throw(Reason);
 
219
g(Value) ->
 
220
    Value.
 
221
 
 
222
otp_5837(N) ->
 
223
    n(N).
 
224
 
 
225
n(N) ->
 
226
    lists:map(fun(X) when N==X ->
 
227
                      yes;
 
228
                 (_) ->
 
229
                      no
 
230
              end,
 
231
              [1,2,3,4]).
 
232
 
 
233
otp_8310() ->
 
234
    a = if (false orelse a) =:= a -> a; true -> b end,
 
235
    F1 = fun() -> a end,
 
236
    {'EXIT',{{bad_filter,a},_}} =
 
237
        (catch {a, [X || X <- [1,2,3], _ = F1()]}),
 
238
    F2 = fun() -> << 3:8 >> end,
 
239
    {'EXIT',{{bad_filter,<<3>>},_}} =
 
240
        (catch {a, << << X >> || << X >> <= << 7:8 >>,_ = F2() >>}),
 
241
    {'EXIT',{{bad_generator,a},_}} =
 
242
        (catch {a, [X || X <- a]}),
 
243
    {'EXIT',{{bad_generator,b},_}} =
 
244
        (catch {a, << <<X>>  || << X >> <= b >>}),
 
245
    ok.