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

« back to all changes in this revision

Viewing changes to lib/cosTime/test/time_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
%%
 
3
%% %CopyrightBegin%
 
4
%% 
 
5
%% Copyright Ericsson AB 2000-2011. All Rights Reserved.
 
6
%% 
 
7
%% The contents of this file are subject to the Erlang Public License,
 
8
%% Version 1.1, (the "License"); you may not use this file except in
 
9
%% compliance with the License. You should have received a copy of the
 
10
%% Erlang Public License along with this software. If not, it can be
 
11
%% retrieved online at http://www.erlang.org/.
 
12
%% 
 
13
%% Software distributed under the License is distributed on an "AS IS"
 
14
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
15
%% the License for the specific language governing rights and limitations
 
16
%% under the License.
 
17
%% 
 
18
%% %CopyrightEnd%
 
19
%%
 
20
%%
 
21
%%----------------------------------------------------------------------
 
22
%% File    : time_SUITE.erl
 
23
%% Purpose : 
 
24
%%----------------------------------------------------------------------
 
25
 
 
26
-module(time_SUITE).
 
27
 
 
28
 
 
29
%%--------------- INCLUDES -----------------------------------
 
30
-include_lib("cosTime/src/cosTimeApp.hrl").
 
31
 
 
32
-include_lib("test_server/include/test_server.hrl").
 
33
 
 
34
%%--------------- DEFINES ------------------------------------
 
35
-define(default_timeout, ?t:minutes(20)).
 
36
-define(match(ExpectedRes, Expr),
 
37
        fun() ->
 
38
               AcTuAlReS = (catch (Expr)),
 
39
               case AcTuAlReS of
 
40
                   ExpectedRes ->
 
41
                       io:format("------ CORRECT RESULT ------~n~p~n",
 
42
                                 [AcTuAlReS]),
 
43
                       AcTuAlReS;
 
44
                   _ ->
 
45
                       io:format("###### ERROR ERROR ######~n~p~n",
 
46
                                 [AcTuAlReS]),
 
47
                       exit(AcTuAlReS)
 
48
               end
 
49
       end()).
 
50
 
 
51
-define(match_inverse(NotExpectedRes, Expr),
 
52
        fun() ->
 
53
                AcTuAlReS = (catch (Expr)),
 
54
               case AcTuAlReS of
 
55
                   NotExpectedRes ->
 
56
                       io:format("###### ERROR ERROR ######~n ~p~n",
 
57
                                 [AcTuAlReS]),
 
58
                       exit(AcTuAlReS);
 
59
                   _ ->
 
60
                       io:format("------ CORRECT RESULT ------~n~p~n",
 
61
                                 [AcTuAlReS]),
 
62
                       AcTuAlReS
 
63
               end
 
64
       end()).
 
65
 
 
66
 
 
67
%%-----------------------------------------------------------------
 
68
%% External exports
 
69
%%-----------------------------------------------------------------
 
70
-export([all/0, suite/0,groups/0,init_per_group/2,end_per_group/2, cases/0, 
 
71
         init_per_suite/1, end_per_suite/1, time_api/1, timerevent_api/1,
 
72
         init_per_testcase/2, end_per_testcase/2,
 
73
         app_test/1]).
 
74
 
 
75
%%-----------------------------------------------------------------
 
76
%% Func: all/1
 
77
%% Args: 
 
78
%% Returns: 
 
79
%%-----------------------------------------------------------------
 
80
suite() -> [{ct_hooks,[ts_install_cth]}].
 
81
 
 
82
all() -> 
 
83
    cases().
 
84
 
 
85
groups() -> 
 
86
    [].
 
87
 
 
88
init_per_group(_GroupName, Config) ->
 
89
    Config.
 
90
 
 
91
end_per_group(_GroupName, Config) ->
 
92
    Config.
 
93
 
 
94
 
 
95
cases() -> 
 
96
    [time_api, timerevent_api, app_test].
 
97
 
 
98
 
 
99
        
 
100
%%-----------------------------------------------------------------
 
101
%% Init and cleanup functions.
 
102
%%-----------------------------------------------------------------
 
103
 
 
104
init_per_testcase(_Case, Config) ->
 
105
    Path = code:which(?MODULE),
 
106
    code:add_pathz(filename:join(filename:dirname(Path), "idl_output")),
 
107
    ?line Dog=test_server:timetrap(?default_timeout),
 
108
    [{watchdog, Dog}|Config].
 
109
 
 
110
 
 
111
end_per_testcase(_Case, Config) ->
 
112
    Path = code:which(?MODULE),
 
113
    code:del_path(filename:join(filename:dirname(Path), "idl_output")),
 
114
    Dog = ?config(watchdog, Config),
 
115
    test_server:timetrap_cancel(Dog),
 
116
    ok.
 
117
 
 
118
init_per_suite(Config) ->
 
119
    Path = code:which(?MODULE),
 
120
    code:add_pathz(filename:join(filename:dirname(Path), "idl_output")),
 
121
    mnesia:delete_schema([node()]),
 
122
    mnesia:create_schema([node()]),
 
123
    orber:install([node()]),
 
124
    application:start(mnesia),
 
125
    application:start(orber),
 
126
    cosNotificationApp:install_event(),
 
127
    cosNotificationApp:install(),
 
128
    cosTime:install_time(),
 
129
    cosTime:install_timerevent(),
 
130
    if
 
131
        is_list(Config) ->
 
132
            Config;
 
133
        true ->
 
134
            exit("Config not a list")
 
135
    end.
 
136
 
 
137
end_per_suite(Config) ->
 
138
    Path = code:which(?MODULE),
 
139
    code:del_path(filename:join(filename:dirname(Path), "idl_output")),
 
140
    cosTime:uninstall_time(),
 
141
    cosTime:uninstall_timerevent(),
 
142
    cosNotificationApp:uninstall(),
 
143
    cosNotificationApp:uninstall_event(),
 
144
    application:stop(orber),
 
145
    application:stop(mnesia),
 
146
    mnesia:delete_schema([node()]),
 
147
    Config.
 
148
 
 
149
%%-----------------------------------------------------------------
 
150
%%  Tests app file
 
151
%%-----------------------------------------------------------------
 
152
app_test(doc) -> [];
 
153
app_test(suite) -> [];
 
154
app_test(_Config) ->
 
155
    ok=test_server:app_test(cosTime),
 
156
    ok.
 
157
 
 
158
%%-----------------------------------------------------------------
 
159
%%  CosTime API tests 
 
160
%%-----------------------------------------------------------------
 
161
time_api(doc) -> ["CosTime API tests.", ""];
 
162
time_api(suite) -> [];
 
163
time_api(_Config) ->
 
164
    ?line ?match(ok, application:start(cosTime)),
 
165
    TS=cosTime:start_time_service(0, 500),
 
166
    Time=calendar:datetime_to_gregorian_seconds({{1582,1,1},{0,0,0}}),
 
167
    Inaccuracy = 1000,
 
168
    Tdf =1,
 
169
    Utc = #'TimeBase_UtcT'{time=Time, inacclo = ?low_TimeT(Inaccuracy), 
 
170
                           inacchi = ?high_TimeT(Inaccuracy), tdf = Tdf},
 
171
    ?line UTO1='CosTime_TimeService':new_universal_time(TS, Time, Inaccuracy, Tdf),
 
172
    ?line UTO2='CosTime_TimeService':uto_from_utc(TS, Utc),
 
173
    ?line ?match(Time, 'CosTime_UTO':'_get_time'(UTO1)),
 
174
    ?line ?match(Inaccuracy, 'CosTime_UTO':'_get_inaccuracy'(UTO1)),
 
175
    ?line ?match(Tdf, 'CosTime_UTO':'_get_tdf'(UTO1)),
 
176
    ?line ?match(Utc, 'CosTime_UTO':'_get_utc_time'(UTO1)),
 
177
 
 
178
    ?line ?match(Time, 'CosTime_UTO':'_get_time'(UTO2)),
 
179
    ?line ?match(Inaccuracy, 'CosTime_UTO':'_get_inaccuracy'(UTO2)),
 
180
    ?line ?match(Tdf, 'CosTime_UTO':'_get_tdf'(UTO2)),
 
181
    ?line ?match(Utc, 'CosTime_UTO':'_get_utc_time'(UTO2)),
 
182
 
 
183
    TIO1='CosTime_TimeService':new_interval(TS, 2, 5),
 
184
    _TIO2='CosTime_TimeService':new_interval(TS, 3, 6),
 
185
    TIO3='CosTime_TimeService':new_interval(TS, 1, 3),
 
186
    TIO4='CosTime_TimeService':new_interval(TS, 3, 4),
 
187
    TIO5='CosTime_TimeService':new_interval(TS, 7, 8),
 
188
    TIO6='CosTime_TimeService':new_interval(TS, 2, 6),
 
189
    TIO7='CosTime_TimeService':new_interval(TS, 3, 7),
 
190
 
 
191
    ?line {_,TIO8} = ?match({'OTContained', _}, 'CosTime_TIO':overlaps(TIO1, TIO6)),
 
192
    ?line {_,TIO9} = ?match({'OTContainer', _}, 'CosTime_TIO':overlaps(TIO1, TIO1)),
 
193
    ?line {_,TIO10} = ?match({'OTContainer', _}, 'CosTime_TIO':overlaps(TIO1, TIO4)),
 
194
    ?line {_,TIO11} = ?match({'OTOverlap', _}, 'CosTime_TIO':overlaps(TIO1, TIO3)),
 
195
    ?line {_,TIO12} = ?match({'OTOverlap', _}, 'CosTime_TIO':overlaps(TIO1, TIO7)),
 
196
    ?line {_,TIO13} = ?match({'OTNoOverlap', _}, 'CosTime_TIO':overlaps(TIO1, TIO5)),
 
197
    
 
198
    ?line ?match({'TimeBase_IntervalT',2,5},'CosTime_TIO':'_get_time_interval'(TIO8)),
 
199
    ?line ?match({'TimeBase_IntervalT',2,5},'CosTime_TIO':'_get_time_interval'(TIO9)),
 
200
    ?line ?match({'TimeBase_IntervalT',3,4},'CosTime_TIO':'_get_time_interval'(TIO10)),
 
201
    ?line ?match({'TimeBase_IntervalT',2,3},'CosTime_TIO':'_get_time_interval'(TIO11)),
 
202
    ?line ?match({'TimeBase_IntervalT',3,5},'CosTime_TIO':'_get_time_interval'(TIO12)),
 
203
    ?line ?match({'TimeBase_IntervalT',5,7},'CosTime_TIO':'_get_time_interval'(TIO13)),
 
204
    
 
205
    ?line UTO3='CosTime_TimeService':new_universal_time(TS, 4, 2, 0), %% 2-6
 
206
    ?line UTO4='CosTime_TimeService':new_universal_time(TS, 2, 1, 0), %% 1-3
 
207
    ?line UTO5='CosTime_TimeService':new_universal_time(TS, 3, 0, 0), %% 3-3
 
208
    ?line UTO6='CosTime_TimeService':new_universal_time(TS, 9, 1, 0), %% 8-10
 
209
    ?line UTO7='CosTime_TimeService':new_universal_time(TS, 4, 3, 0), %% 1-7
 
210
    ?line UTO8='CosTime_TimeService':new_universal_time(TS, 5, 2, 0), %% 3-7
 
211
 
 
212
    ?line {_,TIO14} = ?match({'OTContained', _}, 'CosTime_TIO':spans(TIO1, UTO7)),
 
213
    ?line {_,TIO15} = ?match({'OTContainer', _}, 'CosTime_TIO':spans(TIO1, UTO5)),
 
214
    ?line {_,TIO16} = ?match({'OTOverlap', _}, 'CosTime_TIO':spans(TIO1, UTO4)),
 
215
    ?line {_,TIO17} = ?match({'OTOverlap', _}, 'CosTime_TIO':spans(TIO1, UTO8)),
 
216
    ?line {_,TIO18} = ?match({'OTNoOverlap', _}, 'CosTime_TIO':spans(TIO1, UTO6)),
 
217
    ?line {_,TIO19} = ?match({'OTContained', _}, 'CosTime_TIO':spans(TIO1, UTO3)),
 
218
 
 
219
    ?line ?match({'TimeBase_IntervalT',2,5},'CosTime_TIO':'_get_time_interval'(TIO14)),
 
220
    ?line ?match({'TimeBase_IntervalT',3,3},'CosTime_TIO':'_get_time_interval'(TIO15)),
 
221
    ?line ?match({'TimeBase_IntervalT',2,3},'CosTime_TIO':'_get_time_interval'(TIO16)),
 
222
    ?line ?match({'TimeBase_IntervalT',3,5},'CosTime_TIO':'_get_time_interval'(TIO17)),
 
223
    ?line ?match({'TimeBase_IntervalT',5,8},'CosTime_TIO':'_get_time_interval'(TIO18)),
 
224
    ?line ?match({'TimeBase_IntervalT',2,5},'CosTime_TIO':'_get_time_interval'(TIO19)),
 
225
 
 
226
 
 
227
    cosTime:stop_time_service(TS),
 
228
    application:stop(cosTime),
 
229
    ok.
 
230
 
 
231
 
 
232
%%-----------------------------------------------------------------
 
233
%%  CosTimerEvent API tests 
 
234
%%-----------------------------------------------------------------
 
235
timerevent_api(doc) -> ["CosTimerEvent API tests.", ""];
 
236
timerevent_api(suite) -> [];
 
237
timerevent_api(_Config) ->
 
238
    %% Init cosTime apps.
 
239
    ?line ?match(ok, application:start(cosTime)),
 
240
    ?line TS=cosTime:start_time_service(0, 500),
 
241
    ?line TES=cosTime:start_timerevent_service(TS),
 
242
 
 
243
    %%----- Initialize the cosNotification application. -----
 
244
    ?line cosNotificationApp:start(),
 
245
    ?line Fac = (catch cosNotificationApp:start_factory([])),
 
246
    ?line {Ch, _Id1} = (catch 'CosNotifyChannelAdmin_EventChannelFactory':create_channel(Fac, [], [])),
 
247
    %% Create the Admin objects
 
248
    ?line {AdminSupplier, _ASID}= ?match({{_,key,_,_,_,_},_},
 
249
             'CosNotifyChannelAdmin_EventChannel':new_for_suppliers(Ch,'OR_OP')),
 
250
    ?line {AdminConsumer, _ACID}= ?match({{_,key,_,_,_,_},_},
 
251
             'CosNotifyChannelAdmin_EventChannel':new_for_consumers(Ch,'OR_OP')),
 
252
 
 
253
    %% Create a push consumer TimerEventService will push events to.
 
254
    ?line {ProxyPushConsumer,_ID10}= ?match({{_,key,_,_,_,_},_},
 
255
          'CosNotifyChannelAdmin_SupplierAdmin':obtain_notification_push_consumer(AdminSupplier, 'ANY_EVENT')),
 
256
 
 
257
    %% Create a pull suppliers so we can check we actually got the event.
 
258
    ?line {ProxyPullSupplier,_ID1} = ?match({{_,key,_,_,_,_},_},
 
259
          'CosNotifyChannelAdmin_ConsumerAdmin':obtain_notification_pull_supplier(AdminConsumer, 'ANY_EVENT')),
 
260
 
 
261
    AnyEvent = any:create(orber_tc:long(), 100),
 
262
    ?line UTO=?match({_,pseudo,_,_,_,_}, 'CosTime_TimeService':new_universal_time(TS, 10*10000000,1,1)),
 
263
    ?line EH=?match({_,key,_,_,_,_}, 'CosTimerEvent_TimerEventService':register(TES, ProxyPushConsumer, AnyEvent)), 
 
264
 
 
265
    ?line ?match('ESTimeCleared','CosTimerEvent_TimerEventHandler':'_get_status'(EH)),
 
266
    ?line ?match({false,_},'CosTimerEvent_TimerEventHandler':time_set(EH)),
 
267
    ?line ?match(ok,'CosTimerEvent_TimerEventHandler':set_timer(EH, 'TTRelative', UTO)),
 
268
    ?line ?match({true,_},'CosTimerEvent_TimerEventHandler':time_set(EH)),
 
269
    ?line ?match('ESTimeSet','CosTimerEvent_TimerEventHandler':'_get_status'(EH)),
 
270
    
 
271
    ?line ?match({{any,tk_null,null}, false}, 
 
272
           'CosNotifyChannelAdmin_ProxyPullSupplier':try_pull(ProxyPullSupplier)),
 
273
 
 
274
    ?line ?match(AnyEvent, 'CosNotifyChannelAdmin_ProxyPullSupplier':pull(ProxyPullSupplier)),
 
275
    ?line ?match('ESTriggered','CosTimerEvent_TimerEventHandler':'_get_status'(EH)),
 
276
 
 
277
    %% It's allowed to send an UTO with time eq. to 0 if the server is TTRelative.
 
278
    %% When TTAbsolute BAD_PARAM is raised.
 
279
    ?line UTO2=?match({_,pseudo,_,_,_,_}, 'CosTime_TimeService':new_universal_time(TS, 0,1,1)),
 
280
    ?line ?match({'EXCEPTION',_},'CosTimerEvent_TimerEventHandler':set_timer(EH, 'TTAbsolute', UTO2)),
 
281
    ?line ?match(ok,'CosTimerEvent_TimerEventHandler':set_timer(EH, 'TTRelative', UTO2)),
 
282
    ?line ?match(AnyEvent, 'CosNotifyChannelAdmin_ProxyPullSupplier':pull(ProxyPullSupplier)),
 
283
 
 
284
    %% TTPeriodic is defined to be relative, i.e., we can use the tactic as above.
 
285
    ?line ?match(ok,'CosTimerEvent_TimerEventHandler':set_timer(EH, 'TTPeriodic', UTO2)),
 
286
 
 
287
    %% Sleep for UTO*2+4 secs. At this point the Timer should have delivered 2 events.
 
288
    timer:sleep(24000),
 
289
    %% Cancel the timer so no more events will be delivered.
 
290
    ?line ?match(true,'CosTimerEvent_TimerEventHandler':cancel_timer(EH)),
 
291
 
 
292
    ?line ?match({AnyEvent, true}, 'CosNotifyChannelAdmin_ProxyPullSupplier':try_pull(ProxyPullSupplier)),
 
293
    ?line ?match({AnyEvent, true}, 'CosNotifyChannelAdmin_ProxyPullSupplier':try_pull(ProxyPullSupplier)),
 
294
    ?line ?match({{any,tk_null,null}, false}, 
 
295
           'CosNotifyChannelAdmin_ProxyPullSupplier':try_pull(ProxyPullSupplier)),
 
296
 
 
297
 
 
298
 
 
299
    %% Clean up.
 
300
    cosNotificationApp:stop(),
 
301
    cosTime:stop_timerevent_service(TES),
 
302
    cosTime:stop_time_service(TS),
 
303
    application:stop(cosTime),
 
304
    ok.
 
305
 
 
306