1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 2010-2018. All Rights Reserved.
5%%
6%% Licensed under the Apache License, Version 2.0 (the "License");
7%% you may not use this file except in compliance with the License.
8%% You may obtain a copy of the License at
9%%
10%%     http://www.apache.org/licenses/LICENSE-2.0
11%%
12%% Unless required by applicable law or agreed to in writing, software
13%% distributed under the License is distributed on an "AS IS" BASIS,
14%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15%% See the License for the specific language governing permissions and
16%% limitations under the License.
17%%
18%% %CopyrightEnd%
19%%
20
21%%% TS Installed SCB
22%%%
23%%% This module does what the make parts of the ts:run/x command did,
24%%% but not the Makefile.first parts! So they have to be done by ts or
25%%% manually!!
26
27-module(ts_install_cth).
28
29%% Suite Callbacks
30-export([id/1]).
31-export([init/2]).
32
33-export([pre_init_per_suite/3]).
34-export([post_init_per_suite/4]).
35-export([pre_end_per_suite/3]).
36-export([post_end_per_suite/4]).
37
38-export([pre_init_per_group/3]).
39-export([post_init_per_group/4]).
40-export([pre_end_per_group/3]).
41-export([post_end_per_group/4]).
42
43-export([pre_init_per_testcase/3]).
44-export([post_init_per_testcase/4]).
45-export([pre_end_per_testcase/3]).
46-export([post_end_per_testcase/4]).
47
48-export([on_tc_fail/3]).
49-export([on_tc_skip/3]).
50
51-export([terminate/1]).
52
53-include_lib("kernel/include/file.hrl").
54
55-type config() :: proplists:proplist().
56-type reason() :: term().
57-type skip_or_fail() :: {skip, reason()} |
58                        {auto_skip, reason()} |
59                        {fail, reason()}.
60
61-record(state, { ts_conf_dir, target_system, install_opts, nodenames, nodes }).
62
63%% The id of this SCB
64-spec id(Opts :: term()) ->
65    Id :: term().
66id(_Opts) ->
67    ?MODULE.
68
69%% Always called before any other callback function.
70-spec init(Id :: term(), Opts :: proplists:proplist()) ->
71    {ok, State :: #state{}}.
72init(_Id, Opts) ->
73    Nodenames = proplists:get_value(nodenames, Opts, 0),
74    Nodes = proplists:get_value(nodes, Opts, 0),
75    TSConfDir = proplists:get_value(ts_conf_dir, Opts),
76    TargetSystem = proplists:get_value(target_system, Opts, install_local),
77    InstallOpts = proplists:get_value(install_opts, Opts, []),
78    {ok, #state{ nodenames = Nodenames,
79		 nodes = Nodes,
80		 ts_conf_dir = TSConfDir,
81		 target_system = TargetSystem,
82		 install_opts = InstallOpts } }.
83
84%% Called before init_per_suite is called.
85-spec pre_init_per_suite(Suite :: atom(),
86			 Config :: config(),
87			 State :: #state{}) ->
88	{config() | skip_or_fail(), NewState :: #state{}}.
89pre_init_per_suite(Suite,Config,#state{ ts_conf_dir = undefined} = State) ->
90    DataDir = proplists:get_value(data_dir, Config),
91    ParentDir = filename:join(
92		  lists:reverse(
93		    tl(lists:reverse(filename:split(DataDir))))),
94    TSConfDir = filename:join([ParentDir, "..","test_server"]),
95    pre_init_per_suite(Suite, Config, State#state{ ts_conf_dir = TSConfDir });
96pre_init_per_suite(_Suite,Config,State) ->
97    DataDir = proplists:get_value(data_dir, Config),
98    try
99	{ok,Variables} =
100	    file:consult(filename:join(State#state.ts_conf_dir,"variables")),
101	case proplists:get_value(cross,Variables) of
102	    "yes" ->
103		ct:log("Not making data dir as tests have been cross compiled");
104	    _ ->
105		ts_lib:make_non_erlang(DataDir, Variables)
106	end,
107
108	{add_node_name(Config, State), State}
109    catch error:{badmatch,{error,enoent}} ->
110	{add_node_name(Config, State), State};
111	  Error:Reason:Stack ->
112	    ct:pal("~p failed! ~p:{~p,~p}",[?MODULE,Error,Reason,Stack]),
113	    {{fail,{?MODULE,{Error,Reason, Stack}}},State}
114    end.
115
116%% Called after init_per_suite.
117-spec post_init_per_suite(Suite :: atom(),
118			  Config :: config(),
119			  Return :: config() | skip_or_fail(),
120			  State :: #state{}) ->
121	{config() | skip_or_fail(), NewState :: #state{}}.
122post_init_per_suite(_Suite,_Config,Return,State) ->
123    test_server_ctrl:kill_slavenodes(),
124    {Return, State}.
125
126%% Called before end_per_suite.
127-spec pre_end_per_suite(Suite :: atom(),
128			Config :: config() | skip_or_fail(),
129			State :: #state{}) ->
130	{ok | skip_or_fail(), NewState :: #state{}}.
131pre_end_per_suite(_Suite,Config,State) ->
132    {Config, State}.
133
134%% Called after end_per_suite.
135-spec post_end_per_suite(Suite :: atom(),
136			 Config :: config(),
137			 Return :: term(),
138			 State :: #state{}) ->
139	{ok | skip_or_fail(), NewState :: #state{}}.
140post_end_per_suite(_Suite,_Config,Return,State) ->
141    {Return, State}.
142
143%% Called before each init_per_group.
144-spec pre_init_per_group(Group :: atom(),
145			 Config :: config(),
146			 State :: #state{}) ->
147	{config() | skip_or_fail(), NewState :: #state{}}.
148pre_init_per_group(_Group,Config,State) ->
149    {add_node_name(Config, State), State}.
150
151%% Called after each init_per_group.
152-spec post_init_per_group(Group :: atom(),
153			  Config :: config(),
154			  Return :: config() | skip_or_fail(),
155			  State :: #state{}) ->
156	{config() | skip_or_fail(), NewState :: #state{}}.
157post_init_per_group(_Group,_Config,Return,State) ->
158    {Return, State}.
159
160%% Called after each end_per_group.
161-spec pre_end_per_group(Group :: atom(),
162			Config :: config() | skip_or_fail(),
163			State :: #state{}) ->
164	{ok | skip_or_fail(), NewState :: #state{}}.
165pre_end_per_group(_Group,Config,State) ->
166    {Config, State}.
167
168%% Called after each end_per_group.
169-spec post_end_per_group(Group :: atom(),
170			 Config :: config(),
171			 Return :: term(),
172			 State :: #state{}) ->
173	{ok | skip_or_fail(), NewState :: #state{}}.
174post_end_per_group(_Group,_Config,Return,State) ->
175    {Return, State}.
176
177%% Called before each test case.
178-spec pre_init_per_testcase(TC :: atom(),
179			    Config :: config(),
180			    State :: #state{}) ->
181	{config() | skip_or_fail(), NewState :: #state{}}.
182pre_init_per_testcase(_TC,Config,State) ->
183    {add_node_name(Config, State), State}.
184
185-spec post_init_per_testcase(TC :: atom(),
186			    Config :: config(),
187			    Return :: term(),
188			    State :: #state{}) ->
189	{ok | skip_or_fail(), NewState :: #state{}}.
190post_init_per_testcase(_TC,_Config,Return,State) ->
191    {Return, State}.
192
193%% Called after each test case.
194-spec pre_end_per_testcase(TC :: atom(),
195			   Config :: config(),
196			   State :: #state{}) ->
197	{config() | skip_or_fail(), NewState :: #state{}}.
198pre_end_per_testcase(_TC,Config,State) ->
199    {Config, State}.
200
201-spec post_end_per_testcase(TC :: atom(),
202			    Config :: config(),
203			    Return :: term(),
204			    State :: #state{}) ->
205	{ok | skip_or_fail(), NewState :: #state{}}.
206post_end_per_testcase(_TC,_Config,Return,State) ->
207    {Return, State}.
208
209%% Called after a test case failed.
210-spec on_tc_fail(TC :: init_per_suite | end_per_suite |
211		       init_per_group | end_per_group | atom(),
212		 Reason :: term(), State :: #state{}) ->
213	NewState :: #state{}.
214on_tc_fail(_TC, _Reason, State) ->
215    State.
216
217%% Called when a test case is skipped.
218-spec on_tc_skip(TC :: end_per_suite | init_per_group | end_per_group | atom(),
219		 {tc_auto_skip, {failed, {Mod :: atom(), Function :: atom(),
220					  Reason :: term()}}} |
221		 {tc_user_skip, {skipped, Reason :: term()}},
222		 State :: #state{}) ->
223	NewState :: #state{}.
224on_tc_skip(_TC, _Reason, State) ->
225    State.
226
227%% Called when the scope of the SCB is done.
228-spec terminate(State :: #state{}) ->
229	term().
230terminate(_State) ->
231    ok.
232
233%%% ============================================================================
234%%% Local functions
235%%% ============================================================================
236
237%% Add a nodename to config if it does not exist
238add_node_name(Config, State) ->
239    case proplists:get_value(nodenames, Config) of
240	undefined ->
241	    lists:keystore(
242	       nodenames, 1, Config,
243	       {nodenames,generate_nodenames(State#state.nodenames)});
244	_Else ->
245	    Config
246    end.
247
248
249%% Copied from test_server_ctrl.erl
250generate_nodenames(Num) ->
251    {ok,Name} = inet:gethostname(),
252    generate_nodenames2(Num, [Name], []).
253
254generate_nodenames2(0, _Hosts, Acc) ->
255    Acc;
256generate_nodenames2(N, Hosts, Acc) ->
257    Host=lists:nth((N rem (length(Hosts)))+1, Hosts),
258    Name=list_to_atom(temp_nodename("nod",N) ++ "@" ++ Host),
259    generate_nodenames2(N-1, Hosts, [Name|Acc]).
260
261%% We cannot use erlang:unique_integer([positive])
262%% here since this code in run on older test releases as well.
263temp_nodename(Base,I) ->
264    {A,B,C} = os:timestamp(),
265    Nstr = integer_to_list(I),
266    Astr = integer_to_list(A),
267    Bstr = integer_to_list(B),
268    Cstr = integer_to_list(C),
269    Base++Nstr++Astr++Bstr++Cstr.
270