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

« back to all changes in this revision

Viewing changes to lib/os_mon/test/os_sup_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 2006-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(os_sup_SUITE).
 
20
-include_lib("test_server/include/test_server.hrl").
 
21
 
 
22
%% Test server specific exports
 
23
-export([all/0, suite/0,groups/0,init_per_group/2,end_per_group/2]).
 
24
-export([init_per_suite/1, end_per_suite/1]).
 
25
-export([init_per_testcase/2, end_per_testcase/2]).
 
26
 
 
27
%% Test cases
 
28
-export([message/1]).
 
29
-export([config/1, port/1]).
 
30
 
 
31
%% Default timetrap timeout (set in init_per_testcase)
 
32
-define(default_timeout, ?t:minutes(1)).
 
33
 
 
34
-define(TAG, test_tag).
 
35
-define(MFA, {?MODULE, test_mfa, [?TAG]}).
 
36
 
 
37
-export([test_mfa/2]).
 
38
 
 
39
init_per_suite(Config) when is_list(Config) ->
 
40
    spawn(fun() -> message_receptor() end),
 
41
    ?line application:load(os_mon),
 
42
    ?line ok = application:set_env(os_mon, start_os_sup, true),
 
43
    ?line ok = application:set_env(os_mon, os_sup_mfa, ?MFA),
 
44
    ?line ok = application:set_env(os_mon, os_sup_enable, false),
 
45
    ?line ok = application:start(os_mon),
 
46
    Config.
 
47
 
 
48
end_per_suite(Config) when is_list(Config) ->
 
49
    ?line application:stop(os_mon),
 
50
    ?line ok = application:set_env(os_mon, start_os_sup, false),
 
51
    MFA = {os_sup, error_report, [std_error]},
 
52
    ?line ok = application:set_env(os_mon, os_sup_mfa, MFA),
 
53
    ?line ok = application:set_env(os_mon, os_sup_enable, true),
 
54
    ?line exit(whereis(message_receptor), done),
 
55
    Config.
 
56
 
 
57
init_per_testcase(_Case, Config) ->
 
58
    Dog = ?t:timetrap(?default_timeout),
 
59
    [{watchdog,Dog} | Config].
 
60
 
 
61
end_per_testcase(_Case, Config) ->
 
62
    Dog = ?config(watchdog, Config),
 
63
    ?t:timetrap_cancel(Dog),
 
64
    ok.
 
65
 
 
66
suite() -> [{ct_hooks,[ts_install_cth]}].
 
67
 
 
68
all() -> 
 
69
    case test_server:os_type() of
 
70
        {unix, sunos} -> [message, config, port];
 
71
        {win32, _OSname} -> [message];
 
72
        OS ->
 
73
            Str = io_lib:format("os_sup not available for ~p",
 
74
                                [OS]),
 
75
            {skip, lists:flatten(Str)}
 
76
    end.
 
77
 
 
78
groups() -> 
 
79
    [].
 
80
 
 
81
init_per_group(_GroupName, Config) ->
 
82
    Config.
 
83
 
 
84
end_per_group(_GroupName, Config) ->
 
85
    Config.
 
86
 
 
87
 
 
88
message(suite) ->
 
89
    [];
 
90
message(doc) ->
 
91
    ["Test OS message handling"];
 
92
message(Config) when is_list(Config) ->
 
93
 
 
94
    %% Fake an OS message
 
95
    Data = "10H11386278426HSystem4HTest5HError5HTesto",
 
96
    ?line os_sup_server ! {faked_port, {data, Data}},
 
97
 
 
98
    %% Check with message_receptor that it has been received
 
99
    ?t:sleep(?t:seconds(1)),
 
100
    Msg =
 
101
        case ?t:os_type() of
 
102
            {unix, sunos} ->
 
103
                {?TAG, Data};
 
104
            {win32, _} ->
 
105
                {?TAG,{{1138,627842,0},"System","Test","Error","Testo"}}
 
106
        end,
 
107
    ?line message_receptor ! {check, self(), Msg},
 
108
    receive
 
109
        {result, true} ->
 
110
            ok;
 
111
        {result, Rec} ->
 
112
            ?t:fail({no_message, Rec})
 
113
    end,
 
114
 
 
115
    ok.
 
116
 
 
117
config(suite) ->
 
118
    [];
 
119
config(doc) ->
 
120
    ["Test configuration"];
 
121
config(Config) when is_list(Config) ->
 
122
 
 
123
    %% os_sup_enable==true and os_sup_own/os_sup_syslogconf cannot
 
124
    %% be tested as test_server is not running is root
 
125
 
 
126
    %% os_sup_mfa is already tested, sort of (in init_per_suite)
 
127
 
 
128
    %% os_sup_errortag should be tested, however
 
129
 
 
130
    ok.
 
131
 
 
132
port(suite) ->
 
133
    [];
 
134
port(doc) ->
 
135
    ["Test that os_sup handles a terminating port program"];
 
136
port(Config) when is_list(Config) ->
 
137
    ?line Str = os:cmd("ps -e | grep '[f]errule'"),
 
138
    case io_lib:fread("~s", Str) of
 
139
         {ok, [Pid], _Rest} ->
 
140
 
 
141
            %% Monitor os_sup_server
 
142
            ?line MonRef = erlang:monitor(process, os_sup_server),
 
143
 
 
144
            %% Kill the port program
 
145
            case os:cmd("kill -9 " ++ Pid) of
 
146
                [] ->
 
147
 
 
148
                    %% os_sup_server should now terminate
 
149
                    receive
 
150
                        {'DOWN', MonRef, _, _, {port_died, _Reason}} ->
 
151
                            ok;
 
152
                        {'DOWN', MonRef, _, _, Reason} ->
 
153
                            ?line ?t:fail({unexpected_exit_reason, Reason})
 
154
                    after
 
155
                        3000 ->
 
156
                            ?line ?t:fail(still_alive)
 
157
                    end,
 
158
 
 
159
                    %% Give os_mon_sup time to restart os_sup
 
160
                    ?t:sleep(?t:seconds(3)),
 
161
                    ?line true = is_pid(whereis(os_sup_server)),
 
162
 
 
163
                    ok;
 
164
 
 
165
                Line ->
 
166
                    erlang:demonitor(MonRef),
 
167
                    {skip, {not_killed, Line}}
 
168
            end;
 
169
        _ ->
 
170
            {skip, {os_pid_not_found}}
 
171
    end.
 
172
 
 
173
%%----------------------------------------------------------------------
 
174
%% Auxiliary
 
175
%%----------------------------------------------------------------------
 
176
 
 
177
test_mfa(Message, Tag) ->
 
178
    message_receptor ! {Tag, Message}.
 
179
 
 
180
message_receptor() ->
 
181
    register(message_receptor, self()),
 
182
    message_receptor([]).
 
183
 
 
184
message_receptor(Received) ->
 
185
    receive
 
186
        %% Check if a certain message has been received
 
187
        {check, From, Msg} ->
 
188
            case lists:member(Msg, Received) of
 
189
                true ->
 
190
                    From ! {result, true},
 
191
                    message_receptor(lists:delete(Msg, Received));
 
192
                false ->
 
193
                    From ! {result, Received},
 
194
                    message_receptor(Received)
 
195
            end;
 
196
 
 
197
        %% Save all other messages
 
198
        Msg ->
 
199
            message_receptor([Msg|Received])
 
200
    end.