~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/snmp/test/snmp_agent_test.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%% 
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 2003-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2003-2010. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%% 
19
19
 
32
32
-include("snmp_test_lib.hrl").
33
33
-define(SNMP_USE_V3, true).
34
34
-include_lib("snmp/include/snmp_types.hrl").
 
35
-include_lib("snmp/src/agent/snmpa_atl.hrl").
 
36
 
35
37
%% -include_lib("snmp/include/SNMP-COMMUNITY-MIB.hrl").
36
38
%% -include_lib("snmp/include/SNMP-VIEW-BASED-ACM-MIB.hrl").
37
39
%% -include_lib("snmp/include/SNMP-USER-BASED-SM-MIB.hrl").
84
86
 
85
87
 
86
88
all(suite) -> 
87
 
    {req,
88
 
     [
89
 
      mnesia, 
90
 
      distribution,
91
 
      {local_slave_nodes, 2}, 
92
 
      {time, 360}
93
 
     ],
94
 
     [{conf, init_all, cases(), finish_all}]}.
95
 
 
96
 
 
 
89
    Reqs = [mnesia, distribution, {local_slave_nodes, 2}, {time, 360}], 
 
90
    Conf1 = [{conf, init_all, cases(), finish_all}], 
 
91
    Conf2 = [tickets2], 
 
92
    {req, Reqs, Conf1 ++ Conf2}.
 
93
 
 
94
 
 
95
init_per_testcase(otp8395 = Case, Config) when is_list(Config) ->
 
96
    ?DBG("init_per_testcase -> entry with"
 
97
         "~n   Case:   ~p"
 
98
         "~n   Config: ~p", [Case, Config]),
 
99
    Config2 = init_per_testcase2(Case, init_suite(Config)), 
 
100
    otp8395({init, Config2});
97
101
init_per_testcase(otp_7157_test = _Case, Config) when is_list(Config) ->
98
102
    ?DBG("init_per_testcase -> entry with"
99
103
         "~n   Case:   ~p"
119
123
    Dog = ?WD_START(?MINS(6)),
120
124
    [{watchdog, Dog}|Config].
121
125
 
 
126
fin_per_testcase(otp8395, Config) when is_list(Config) ->
 
127
    otp8395({fin, Config});
122
128
fin_per_testcase(_Case, Config) when is_list(Config) ->
123
129
    ?DBG("fin_per_testcase -> entry with"
124
130
         "~n   Case:   ~p"
127
133
    ?WD_STOP(Dog),
128
134
    Config.
129
135
 
 
136
 
 
137
init_suite(Config) ->
 
138
    ?DBG("init_suite -> entry with"
 
139
         "~n   Config: ~p", [Config]),
 
140
 
 
141
    %% Suite root dir for test suite
 
142
    PrivDir = ?config(priv_dir, Config),
 
143
 
 
144
    %% Create top-directory for this sub-suite
 
145
    SuiteTopDir = filename:join([PrivDir, ?MODULE]),
 
146
    case file:make_dir(SuiteTopDir) of
 
147
        ok ->
 
148
            ok;
 
149
        {error, eexist} ->
 
150
            %% This can happen since this is not really a 
 
151
            %% suite-init function.
 
152
            ok;
 
153
        {error, Reason} ->
 
154
            ?FAIL({failed_creating_suite_top_dir, SuiteTopDir, Reason})
 
155
    end,
 
156
    
 
157
 
 
158
    %% --
 
159
    %% Fix config (data-dir is not correct):
 
160
    %% 
 
161
 
 
162
    Config1 = fix_data_dir(Config), 
 
163
    %% Config1 = Config, 
 
164
 
 
165
    %% Mib-dirs
 
166
    MibDir    = ?config(data_dir, Config1),
 
167
    StdMibDir = filename:join([code:priv_dir(snmp), "mibs"]),
 
168
 
 
169
    Config2 = [{suite_top_dir, SuiteTopDir}, 
 
170
               {mib_dir,       MibDir}, 
 
171
               {std_mib_dir,   StdMibDir} | Config1],
 
172
 
 
173
    ?DBG("init_suite -> done when"
 
174
         "~n   Config2: ~p", [Config2]),
 
175
    Config2.
 
176
 
 
177
%% end_per_suite(Config) ->
 
178
end_suite(Config) ->
 
179
    Config.
 
180
 
 
181
fix_data_dir(Config) ->
 
182
    DataDir0     = ?config(data_dir, Config),
 
183
    DataDir1     = filename:split(filename:absname(DataDir0)),
 
184
    [_|DataDir2] = lists:reverse(DataDir1),
 
185
    DataDir      = filename:join(lists:reverse(DataDir2) ++ [?snmp_test_data]),
 
186
    Config1      = lists:keydelete(data_dir, 1, Config),
 
187
    [{data_dir, DataDir} | Config1].
 
188
 
 
189
 
 
190
init_per_testcase2(Case, Config) ->
 
191
    SuiteToDir = ?config(suite_top_dir, Config),
 
192
    
 
193
    %% Create top-directory for this test-case
 
194
    CaseTopDir = filename:join([SuiteToDir, Case]),
 
195
    ok = file:make_dir(CaseTopDir),
 
196
 
 
197
    %% Create agent top-dir(s)
 
198
    AgentTopDir = filename:join([CaseTopDir, agent]),
 
199
    ok = file:make_dir(AgentTopDir),
 
200
    AgentConfDir = filename:join([AgentTopDir, config]),
 
201
    ok = file:make_dir(AgentConfDir),
 
202
    AgentDbDir = filename:join([AgentTopDir, db]),
 
203
    ok = file:make_dir(AgentDbDir),
 
204
    AgentLogDir = filename:join([AgentTopDir, log]),
 
205
    ok = file:make_dir(AgentLogDir),
 
206
 
 
207
    %% Create sub-agent top-dir(s)
 
208
    SubAgentTopDir = filename:join([CaseTopDir, sub_agent]),
 
209
    ok = file:make_dir(SubAgentTopDir),
 
210
 
 
211
    %% Create manager top-dir(s)
 
212
    ManagerTopDir = filename:join([CaseTopDir, manager]),
 
213
    ok = file:make_dir(ManagerTopDir),
 
214
 
 
215
    [{case_top_dir,      CaseTopDir}, 
 
216
     {agent_top_dir,     AgentTopDir}, 
 
217
     {agent_conf_dir,    AgentConfDir}, 
 
218
     {agent_db_dir,      AgentDbDir}, 
 
219
     {agent_log_dir,     AgentLogDir}, 
 
220
     {sub_agent_top_dir, SubAgentTopDir}, 
 
221
     {manager_top_dir,   ManagerTopDir} | Config].
 
222
 
 
223
fin_per_testcase2(_Case, Config) ->
 
224
    Config.
 
225
 
 
226
 
130
227
cases() ->
131
228
    case ?OSTYPE() of
132
229
        vxworks ->
138
235
             test_v1_v2, 
139
236
             test_multi_threaded, 
140
237
             mib_storage, 
141
 
             tickets
 
238
             tickets1
142
239
            ];
143
240
        _Else ->
144
241
            [
149
246
             test_v3, 
150
247
             test_multi_threaded, 
151
248
             mib_storage, 
152
 
             tickets
 
249
             tickets1
153
250
            ]
154
251
    end.
155
252
 
5071
5168
 
5072
5169
%% These are (ticket) test cases where the initiation has to be done
5073
5170
%% individually.
5074
 
tickets(suite) ->
 
5171
tickets1(suite) ->
5075
5172
    [
5076
5173
     otp_4394, 
5077
5174
     otp_7157
5078
5175
    ].
5079
5176
 
 
5177
 
 
5178
tickets2(suite) ->
 
5179
    [
 
5180
     otp8395
 
5181
    ].
 
5182
 
 
5183
 
 
5184
 
5080
5185
%%-----------------------------------------------------------------
5081
5186
%% Ticket: OTP-1128
5082
5187
%% Slogan: Bug in handling of createAndWait set-requests.
5624
5729
 
5625
5730
 
5626
5731
otp_7157(suite) -> 
5627
 
    {req, [], {conf, 
5628
 
               init_otp_7157, 
5629
 
               [otp_7157_test], 
5630
 
               finish_otp_7157}}.
 
5732
    Reqs = [], 
 
5733
    Conf = [{conf, init_otp_7157, [otp_7157_test], finish_otp_7157}], 
 
5734
    {req, Reqs, Conf}.
5631
5735
 
5632
5736
init_otp_7157(Config) when is_list(Config) ->
5633
5737
    %% <CONDITIONAL-SKIP>
5691
5795
 
5692
5796
 
5693
5797
%%-----------------------------------------------------------------
 
5798
%% Extra test cases
 
5799
%% These cases are started in the new way
 
5800
%%-----------------------------------------------------------------
 
5801
 
 
5802
otp8395({init, Config}) when is_list(Config) ->
 
5803
    ?DBG("otp8395(init) -> entry with"
 
5804
         "~n   Config: ~p", [Config]),
 
5805
    
 
5806
    %% -- 
 
5807
    %% Start nodes
 
5808
    %% 
 
5809
 
 
5810
    {ok, AgentNode}    = start_node(agent),
 
5811
    %% {ok, SubAgentNode} = start_node(sub_agent),
 
5812
    {ok, ManagerNode}  = start_node(manager),
 
5813
    
 
5814
    %% -- 
 
5815
    %% Mnesia init
 
5816
    %% 
 
5817
 
 
5818
    AgentDbDir = ?config(agent_db_dir, Config),
 
5819
    AgentMnesiaDir = filename:join([AgentDbDir, "mnesia"]),
 
5820
    mnesia_init(AgentNode, AgentMnesiaDir),
 
5821
    
 
5822
%%     SubAgentDir = ?config(sub_agent_dir, Config),
 
5823
%%     SubAgentMnesiaDir = filename:join([SubAgentDir, "mnesia"]),
 
5824
%%     mnesia_init(SubAgentNode, SubAgentMnesiaDir),
 
5825
 
 
5826
    %% ok = mnesia_create_schema(AgentNode, [AgentNode, SubAgentNode]), 
 
5827
    %% ok = mnesia:create_schema([AgentNode, SubAgentNode]),
 
5828
    mnesia_create_schema(AgentNode, [AgentNode]),
 
5829
 
 
5830
    mnesia_start(AgentNode),
 
5831
    %% mnesia_start(SubAgentNode),
 
5832
 
 
5833
    %% --
 
5834
    %% Host & IP
 
5835
    %% 
 
5836
 
 
5837
    AgentHost    = ?HOSTNAME(AgentNode),
 
5838
    %% SubAgentHost = ?HPSTNAME(SubAgentNode), 
 
5839
    ManagerHost  = ?HOSTNAME(ManagerNode),
 
5840
 
 
5841
    Host              = snmp_test_lib:hostname(), 
 
5842
    Ip                = ?LOCALHOST(),
 
5843
    {ok, AgentIP0}    = snmp_misc:ip(AgentHost),
 
5844
    AgentIP           = tuple_to_list(AgentIP0), 
 
5845
    %% {ok, SubAgentIP0} = snmp_misc:ip(SubAgentHost),
 
5846
    %% SubAgentIP        = tuple_to_list(SubAgentIP0), 
 
5847
    {ok, ManagerIP0}  = snmp_misc:ip(ManagerHost),
 
5848
    ManagerIP         = tuple_to_list(ManagerIP0),
 
5849
    
 
5850
 
 
5851
    %% --
 
5852
    %% Write agent config
 
5853
    %% 
 
5854
    
 
5855
    Vsns           = [v1], 
 
5856
    AgentConfDir   = ?config(agent_conf_dir, Config),
 
5857
    ManagerConfDir = ?config(manager_top_dir, Config),
 
5858
    snmp_agent_test_lib:config(Vsns, 
 
5859
                               ManagerConfDir, AgentConfDir, 
 
5860
                               ManagerIP, AgentIP),
 
5861
 
 
5862
 
 
5863
    %% --
 
5864
    %% Start the agent
 
5865
    %% 
 
5866
 
 
5867
    Config2 = start_agent([{host,          Host}, 
 
5868
                           {ip,            Ip}, 
 
5869
                           {agent_node,    AgentNode}, 
 
5870
                           {agent_host,    AgentHost}, 
 
5871
                           {agent_ip,      AgentIP}, 
 
5872
                           %% {sub_agent_node, SubAgentNode}, 
 
5873
                           %% {sub_agent_host, SubAgentHost}, 
 
5874
                           %% {sub_agent_ip,   SubAgentIP}, 
 
5875
                           {manager_node,  ManagerNode},
 
5876
                           {manager_host,  ManagerHost}, 
 
5877
                           {manager_ip,    ManagerIP}|Config]),
 
5878
    
 
5879
    %% -- 
 
5880
    %% Create watchdog 
 
5881
    %% 
 
5882
 
 
5883
    Dog = ?WD_START(?MINS(1)),
 
5884
 
 
5885
    [{watchdog, Dog} | Config2];
 
5886
 
 
5887
otp8395({fin, Config}) when is_list(Config) ->
 
5888
    ?DBG("otp8395(fin) -> entry with"
 
5889
         "~n   Config: ~p", [Config]),
 
5890
    
 
5891
    AgentNode   = ?config(agent_node, Config),
 
5892
    ManagerNode = ?config(manager_node, Config),
 
5893
 
 
5894
    %% -
 
5895
    %% Stop agent (this is the nice way to do it, 
 
5896
    %% so logs and files can be closed in the proper way).
 
5897
    %% 
 
5898
    
 
5899
    AgentSup = ?config(agent_sup, Config),
 
5900
    ?DBG("otp8395(fin) -> stop (stand-alone) agent: ~p", [AgentSup]),
 
5901
    stop_stdalone_agent(AgentSup), 
 
5902
    
 
5903
    %% - 
 
5904
    %% Stop mnesia
 
5905
    %% 
 
5906
    ?DBG("otp8395(fin) -> stop mnesia", []),
 
5907
    mnesia_stop(AgentNode),
 
5908
 
 
5909
 
 
5910
    %% - 
 
5911
    %% Stop the agent node
 
5912
    %% 
 
5913
 
 
5914
    ?DBG("otp8395(fin) -> stop agent node", []),
 
5915
    stop_node(AgentNode),
 
5916
 
 
5917
 
 
5918
%%     SubAgentNode = ?config(sub_agent_node, Config),
 
5919
%%     stop_node(SubAgentNode),
 
5920
 
 
5921
 
 
5922
    %% - 
 
5923
    %% Stop the manager node
 
5924
    %% 
 
5925
 
 
5926
    ?DBG("otp8395(fin) -> stop manager node", []),
 
5927
    stop_node(ManagerNode),
 
5928
 
 
5929
    Dog = ?config(watchdog, Config),
 
5930
    ?WD_STOP(Dog),
 
5931
    lists:keydelete(watchdog, 1, Config);
 
5932
 
 
5933
otp8395(doc) ->
 
5934
    "OTP-8395 - ATL with sequence numbering. ";
 
5935
 
 
5936
otp8395(Config) when is_list(Config) ->
 
5937
    ?DBG("otp8395 -> entry with"
 
5938
         "~n   Config: ~p", [Config]),
 
5939
    
 
5940
    ?SLEEP(1000),
 
5941
 
 
5942
    %% This is just to dirty trick for the ***old*** test-code
 
5943
    put(mgr_node, ?config(manager_node, Config)), 
 
5944
    put(mgr_dir,  ?config(manager_top_dir, Config)),
 
5945
    put(mib_dir,  ?config(mib_dir, Config)),
 
5946
    put(vsn, v1), 
 
5947
    put(master_host, ?config(agent_host, Config)),
 
5948
    try_test(simple_standard_test),
 
5949
 
 
5950
    ?SLEEP(1000),
 
5951
    AgentNode   = ?config(agent_node, Config),
 
5952
    AgentLogDir = ?config(agent_log_dir, Config),
 
5953
    OutFile     = filename:join([AgentLogDir, "otp8395.txt"]),
 
5954
    {ok, LogInfo} = rpc:call(AgentNode, snmpa, log_info, []),
 
5955
    ?DBG("otp8395 -> LogInfo: ~p", [LogInfo]), 
 
5956
 
 
5957
%%     SyncRes = rpc:call(AgentNode, snmp, log_sync, [?audit_trail_log_name]),
 
5958
%%     ?DBG("otp8395 -> SyncRes: ~p", [SyncRes]), 
 
5959
 
 
5960
    ok = agent_log_validation(AgentNode),
 
5961
    LTTRes = 
 
5962
        rpc:call(AgentNode, snmpa, log_to_txt, [AgentLogDir, [], OutFile]), 
 
5963
    ?DBG("otp8395 -> LTTRes: ~p", [LTTRes]), 
 
5964
 
 
5965
    ?SLEEP(1000),
 
5966
    ?DBG("otp8395 -> done", []),
 
5967
    ok.
 
5968
                    
 
5969
 
 
5970
agent_log_validation(Node) ->
 
5971
    rpc:call(Node, ?MODULE, agent_log_validation, []).
 
5972
 
 
5973
agent_log_validation() ->
 
5974
    put(sname, otp8308),
 
5975
    put(verbosity, trace),
 
5976
    snmp_log:validate(?audit_trail_log_name, true).
 
5977
 
 
5978
mnesia_init(Node, Dir) ->
 
5979
    rpc:call(Node, ?MODULE, mnesia_init, [Dir]).
 
5980
 
 
5981
mnesia_init(Dir) ->
 
5982
    ok = application:load(mnesia),
 
5983
    application_controller:set_env(mnesia, dir, Dir).
 
5984
 
 
5985
mnesia_create_schema(Node, Nodes) ->
 
5986
    rpc:call(Node, mnesia, create_schema, [Nodes]).
 
5987
    
 
5988
mnesia_start(Node) ->
 
5989
    rpc:call(Node, application, start, [mnesia]).
 
5990
 
 
5991
mnesia_start() ->
 
5992
    application:start(mnesia).
 
5993
 
 
5994
mnesia_stop(Node) ->
 
5995
    rpc:call(Node, application, stop, [mnesia]).
 
5996
 
 
5997
mnesia_stop() ->
 
5998
    application:start(mnesia).
 
5999
 
 
6000
    
 
6001
start_agent(Config) ->
 
6002
    start_agent(Config, []).
 
6003
 
 
6004
start_agent(Config, Opts) ->
 
6005
 
 
6006
    %% Directories
 
6007
    ConfDir = ?config(agent_conf_dir, Config),
 
6008
    DbDir   = ?config(agent_db_dir,   Config),
 
6009
    LogDir  = ?config(agent_log_dir,  Config),
 
6010
 
 
6011
    Vsns = [v1], 
 
6012
 
 
6013
    AgentConfig = process_agent_options(ConfDir, DbDir, LogDir, Vsns, Opts),
 
6014
    
 
6015
    %% Nodes
 
6016
    AgentNode = ?config(agent_node, Config),
 
6017
    %% ManagerNode = ?config(manager_node, Config),
 
6018
    
 
6019
    process_flag(trap_exit,true),
 
6020
 
 
6021
    AgentTopSup = start_stdalone_agent(AgentNode, AgentConfig),
 
6022
 
 
6023
    [{agent_sup, AgentTopSup} | Config].
 
6024
    
 
6025
 
 
6026
process_agent_options(ConfDir, DbDir, LogDir, Vsns, Opts) ->
 
6027
    Defaults = 
 
6028
        [{agent_type,      master},
 
6029
         {agent_verbosity, trace},
 
6030
         {priority,        normal},
 
6031
         {versions,        Vsns},
 
6032
         {db_dir,          DbDir},
 
6033
         {mib_storage,     ets},
 
6034
         {local_db, [{repair,    true},
 
6035
                     {auto_save, 5000},
 
6036
                     {verbosity, log}]},
 
6037
         {error_report_module, snmpa_error_logger},
 
6038
         {config, [{dir,        ConfDir},
 
6039
                   {force_load, true},
 
6040
                   {verbosity,  trace}]},
 
6041
         {multi_threaded, true},
 
6042
         {mib_server, [{mibentry_override,  false},
 
6043
                       {trapentry_override, false},
 
6044
                       {verbosity,          info}]},
 
6045
         {target_cache,   [{verbosity,info}]},
 
6046
         {symbolic_store, [{verbosity,log}]},
 
6047
         {note_store, [{timeout,30000}, {verbosity,log}]},
 
6048
         {net_if, [{module,    snmpa_net_if},
 
6049
                   {verbosity, trace},
 
6050
                   {options,   [{bind_to,   false},
 
6051
                                {no_reuse,  false},
 
6052
                                {req_limit, infinity}]}]},
 
6053
         {audit_trail_log, [{type,   read_write},
 
6054
                            {dir,    LogDir},
 
6055
                            {size,   {10240,20}},
 
6056
                            {repair, true},
 
6057
                            {seqno,  true}]}],
 
6058
    
 
6059
    process_options(Defaults, Opts).
 
6060
 
 
6061
process_options(Defaults, _Opts) ->
 
6062
    %% process_options(Defaults, Opts, []).
 
6063
    Defaults.
 
6064
 
 
6065
%% process_options([], _Opts, Acc) ->
 
6066
%%     lists:reverse(Acc);
 
6067
%% process_options([{Key, DefaultValue}|Defaults], Opts, Acc) ->
 
6068
%%     case lists:keysearch(Key, 1, Opts) of
 
6069
%%      {value, {Key, Value}} when is_list->
 
6070
            
 
6071
 
 
6072
snmp_app_env_init(Node, Entity, Conf) ->
 
6073
    rpc:call(Node, snmp_app_env_init, [Entity, Conf]).
 
6074
 
 
6075
snmp_app_env_init(Entity, Conf) ->
 
6076
    application:unload(snmp),
 
6077
    application:load(snmp),
 
6078
    application:set_env(snmp, Entity, Conf).
 
6079
 
 
6080
start_stdalone_agent(Node, Config)  ->
 
6081
    rpc:call(Node, ?MODULE, start_stdalone_agent, [Config]).
 
6082
 
 
6083
start_stdalone_agent(Config)  ->
 
6084
    case snmpa_supervisor:start_link(normal, Config) of
 
6085
        {ok, AgentTopSup} ->
 
6086
            unlink(AgentTopSup),
 
6087
            AgentTopSup;
 
6088
        {error, {already_started, AgentTopSup}} ->
 
6089
            AgentTopSup
 
6090
    end.
 
6091
 
 
6092
stop_stdalone_agent(Pid) when (node(Pid) =/= node()) ->
 
6093
    MRef = erlang:monitor(process, Pid),
 
6094
    rpc:call(node(Pid), ?MODULE, stop_stdalone_agent, [Pid]),
 
6095
    receive
 
6096
        {'DOWN', MRef, process, Pid, Info} ->
 
6097
            ?DBG("received expected DOWN message "
 
6098
                 "regarding snmp agent supervisor: "
 
6099
                 "~n   Info: ~p", [Info]),
 
6100
            ok
 
6101
    after 5000 ->
 
6102
            ?DBG("no DOWN message "
 
6103
                 "regarding snmp agent supervisor within time", []),
 
6104
            ok
 
6105
    end;
 
6106
stop_stdalone_agent(Pid) ->
 
6107
    ?DBG("attempting to terminate agent top-supervisor: ~p", [Pid]),
 
6108
    nkill(Pid, kill).
 
6109
 
 
6110
 
 
6111
nkill(Pid, Reason) ->
 
6112
    nkill(Pid, Reason, 10).
 
6113
 
 
6114
nkill(Pid, Reason, N) when N > 0 ->
 
6115
    case (catch erlang:process_info(Pid)) of
 
6116
        Info when is_list(Info) ->
 
6117
            ?DBG("Info for process to kill: "
 
6118
                 "~n   Info: ~p", [Info]),
 
6119
            exit(Pid, Reason),
 
6120
            ?SLEEP(1000),
 
6121
            nkill(Pid, Reason, N-1);
 
6122
        _ ->
 
6123
            ?DBG("No process info => already dead?", []),
 
6124
            ok
 
6125
    end.
 
6126
 
 
6127
    
 
6128
%%-----------------------------------------------------------------
5694
6129
%% Slogan: info test
5695
6130
%%-----------------------------------------------------------------
5696
6131