~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/common_test/doc/src/dependencies_chapter.xml

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (1.1.13 upstream)
  • mto: (3.3.1 squeeze)
  • mto: This revision was merged to the branch mainline in revision 17.
  • Revision ID: james.westby@ubuntu.com-20090215164252-dxpjjuq108nz4noa
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
<?xml version="1.0" encoding="latin1" ?>
 
2
<!DOCTYPE chapter SYSTEM "chapter.dtd">
 
3
 
 
4
<chapter>
 
5
  <header>
 
6
    <copyright>
 
7
      <year>2006</year>
 
8
      <year>2008</year>
 
9
      <holder>Ericsson AB, All Rights Reserved</holder>
 
10
    </copyright>
 
11
    <legalnotice>
 
12
  The contents of this file are subject to the Erlang Public License,
 
13
  Version 1.1, (the "License"); you may not use this file except in
 
14
  compliance with the License. You should have received a copy of the
 
15
  Erlang Public License along with this software. If not, it can be
 
16
  retrieved online at http://www.erlang.org/.
 
17
 
 
18
  Software distributed under the License is distributed on an "AS IS"
 
19
  basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
20
  the License for the specific language governing rights and limitations
 
21
  under the License.
 
22
 
 
23
  The Initial Developer of the Original Code is Ericsson AB.
 
24
    </legalnotice>
 
25
 
 
26
    <title>Dependencies between Test Cases and Suites</title>
 
27
    <prepared>Peter Andersson</prepared>
 
28
    <docno></docno>
 
29
    <date></date>
 
30
    <rev></rev>
 
31
  </header>
 
32
 
 
33
  <section>
 
34
    <title>General</title>
 
35
    <p>When creating test suites, it is strongly recommended to not
 
36
      create dependencies between test cases, i.e. letting test cases
 
37
      depend on the result of previous test cases. There are various
 
38
      reasons for this, for example:</p>
 
39
 
 
40
    <list>
 
41
      <item>It makes it impossible to run test cases individually.</item>
 
42
      <item>It makes it impossible to run test cases in different order.</item>
 
43
      <item>It makes debugging very difficult (since a fault could be
 
44
        the result of a problem in a different test case than the one failing).</item>
 
45
      <item>There exists no good and explicit ways to declare dependencies, so 
 
46
        it may be very difficult to see and understand these in test suite 
 
47
        code and in test logs.</item>
 
48
      <item>Extending, restructuring and maintaining test suites with 
 
49
        test case dependencies is difficult.</item>      
 
50
    </list>
 
51
    
 
52
    <p>There are often sufficient means to work around the need for test 
 
53
      case dependencies. Generally, the problem is related to the state of 
 
54
      the system under test (SUT). The action of one test case may alter the state 
 
55
      of the system and for some other test case to run properly, the new state 
 
56
      must be known.</p>
 
57
 
 
58
    <p>Instead of passing data between test cases, it is recommended
 
59
      that the test cases read the state from the SUT and perform assertions
 
60
      (i.e. let the test case run if the state is as expected, otherwise reset or fail)
 
61
      and/or use the state to set variables necessary for the test case to execute
 
62
      properly. Common actions can often be implemented as library functions for
 
63
      test cases to call to set the SUT in a required state. (Such common actions
 
64
      may of course also be separately tested if necessary, to ensure they are 
 
65
      working as expected). It is sometimes also possible, but not always desirable, 
 
66
      to group tests together in one test case, i.e. let a test case perform a 
 
67
      "scenario" test (a test that consists of subtests).</p>
 
68
 
 
69
    <p>Consider for example a server application under test. The following 
 
70
      functionality is to be tested:</p>
 
71
    
 
72
    <list>
 
73
      <item>Starting the server.</item>
 
74
      <item>Configuring the server.</item>
 
75
      <item>Connecting a client to the server.</item>
 
76
      <item>Disconnecting a client from the server.</item>
 
77
      <item>Stopping the server.</item>
 
78
    </list>
 
79
 
 
80
    <p>There are obvious dependencies between the listed functions. We can't configure 
 
81
      the server if it hasn't first been started, we can't connect a client until 
 
82
      the server has been properly configured, etc. If we want to have one test 
 
83
      case for each of the functions, we might be tempted to try to always run the
 
84
      test cases in the stated order and carry possible data (identities, handles,
 
85
      etc) between the cases and therefore introduce dependencies between them. 
 
86
      To avoid this we could consider starting and stopping the server for every test.
 
87
      We would implement the start and stop action as common functions that may be 
 
88
      called from init_per_testcase and end_per_testcase. (We would of course test 
 
89
      the start and stop functionality separately). The configuration could perhaps also
 
90
      be implemented as a common function, maybe grouped with the start function.
 
91
      Finally the testing of connecting and disconnecting a client may be grouped into
 
92
      one test case. The resulting suite would look something like this:</p>
 
93
 
 
94
 
 
95
    <pre>      
 
96
      -module(my_server_SUITE).
 
97
      -compile(export_all).
 
98
      -include_lib("ct.hrl").
 
99
 
 
100
      %%% init and end functions...
 
101
 
 
102
      suite() -> [{require,my_server_cfg}].
 
103
 
 
104
      init_per_testcase(start_and_stop, Config) ->
 
105
          Config;
 
106
 
 
107
      init_per_testcase(config, Config) ->
 
108
          [{server_pid,start_server()} | Config];
 
109
 
 
110
      init_per_testcase(_, Config) ->
 
111
          ServerPid = start_server(),
 
112
          configure_server(),
 
113
          [{server_pid,ServerPid} | Config].
 
114
 
 
115
      end_per_testcase(start_and_stop, _) ->
 
116
          ok;
 
117
 
 
118
      end_per_testcase(_, _) ->
 
119
          ServerPid = ?config(server_pid),
 
120
          stop_server(ServerPid).
 
121
 
 
122
      %%% test cases...
 
123
 
 
124
      all() -> [start_and_stop, config, connect_and_disconnect].
 
125
 
 
126
      %% test that starting and stopping works
 
127
      start_and_stop(_) ->
 
128
          ServerPid = start_server(),
 
129
          stop_server(ServerPid).
 
130
 
 
131
      %% configuration test
 
132
      config(Config) ->
 
133
          ServerPid = ?config(server_pid, Config),
 
134
          configure_server(ServerPid).
 
135
 
 
136
      %% test connecting and disconnecting client
 
137
      connect_and_disconnect(Config) ->
 
138
          ServerPid = ?config(server_pid, Config),
 
139
          {ok,SessionId} = my_server:connect(ServerPid),
 
140
          ok = my_server:disconnect(ServerPid, SessionId).
 
141
 
 
142
      %%% common functions...
 
143
 
 
144
      start_server() ->
 
145
          {ok,ServerPid} = my_server:start(),
 
146
          ServerPid.
 
147
 
 
148
      stop_server(ServerPid) ->
 
149
          ok = my_server:stop(),
 
150
          ok.
 
151
 
 
152
      configure_server(ServerPid) ->
 
153
          ServerCfgData = ct:get_config(my_server_cfg),
 
154
          ok = my_server:configure(ServerPid, ServerCfgData),
 
155
          ok.
 
156
      </pre>
 
157
    </section>
 
158
 
 
159
    <section>
 
160
    <marker id="save_config"></marker>
 
161
      <title>Saving configuration data</title>
 
162
 
 
163
      <p>There might be situations where it is impossible, or infeasible at least, to
 
164
        implement independent test cases. Maybe it is simply not possible to read the 
 
165
        SUT state. Maybe resetting the SUT is impossible and it takes much too long
 
166
        to restart the system. In situations where test case dependency is necessary,
 
167
        CT offers a structured way to carry data from one test case to the next. The
 
168
        same mechanism may also be used to carry data from one test suite to the next.</p>
 
169
 
 
170
      <p>The mechanism for passing data is called <c>save_config</c>. The idea is that
 
171
        one test case (or suite) may save the current value of Config - or any list of
 
172
        key-value tuples - so that it can be read by the next executing test case 
 
173
        (or test suite). The configuration data is not saved permanently but can only 
 
174
        be passed from one case (or suite) to the next.</p>
 
175
 
 
176
      <p>To save <c>Config</c> data, return the tuple:</p>
 
177
 
 
178
      <p><c>{save_config,ConfigList}</c></p>
 
179
      
 
180
      <p>from <c>end_per_testcase</c> or from the main test case function. To read data 
 
181
        saved by a previous test case, use the <c>config</c> macro with a 
 
182
        <c>saved_config</c> key:</p>
 
183
      
 
184
      <p><c>{Saver,ConfigList} = ?config(saved_config, Config)</c></p>
 
185
 
 
186
      <p><c>Saver</c> (<c>atom()</c>) is the name of the previous test case (where the
 
187
        data was saved). The <c>config</c> macro may be used to extract particular data
 
188
        also from the recalled <c>ConfigList</c>. It is strongly recommended that 
 
189
        <c>Saver</c> is always matched to the expected name of the saving test case. 
 
190
        This way problems due to restructuring of the test suite may be avoided. Also it 
 
191
        makes the dependency more explicit and the test suite easier to read and maintain.</p>
 
192
 
 
193
      <p>To pass data from one test suite to another, the same mechanism is used. The data
 
194
        should be saved by the <c>end_per_suite</c> function and read by <c>init_per_suite</c>
 
195
        in the suite that follows. When passing data between suites, <c>Saver</c> carries the 
 
196
        name of the test suite.</p>
 
197
 
 
198
      <p>Example:</p>
 
199
      
 
200
      <pre>
 
201
        -module(server_b_SUITE).
 
202
        -compile(export_all).
 
203
        -include_lib("ct.hrl").
 
204
 
 
205
        %%% init and end functions...
 
206
 
 
207
        init_per_suite(Config) ->
 
208
            %% read config saved by previous test suite
 
209
            {server_a_SUITE,OldConfig} = ?config(saved_config, Config),
 
210
            %% extract server identity (comes from server_a_SUITE)
 
211
            ServerId = ?config(server_id, OldConfig),
 
212
            SessionId = connect_to_server(ServerId),
 
213
            [{ids,{ServerId,SessionId}} | Config].
 
214
 
 
215
        end_per_suite(Config) ->
 
216
            %% save config for server_c_SUITE (session_id and server_id)
 
217
            {save_config,Config}
 
218
 
 
219
        %%% test cases...
 
220
 
 
221
        all() -> [allocate, deallocate].
 
222
 
 
223
        allocate(Config) ->
 
224
            {ServerId,SessionId} = ?config(ids, Config),
 
225
            {ok,Handle} = allocate_resource(ServerId, SessionId),
 
226
            %% save handle for deallocation test
 
227
            NewConfig = [{handle,Handle}],
 
228
            {save_config,NewConfig}.
 
229
 
 
230
        deallocate(Config) ->
 
231
            {ServerId,SessionId} = ?config(ids, Config),
 
232
            {allocate,OldConfig} = ?config(saved_config, Config),
 
233
            Handle = ?config(handle, OldConfig),
 
234
            ok = deallocate_resource(ServerId, SessionId, Handle). 
 
235
        </pre>
 
236
 
 
237
      <p>It is also possible to save <c>Config</c> data from a test case that is to be
 
238
        skipped. To accomplish this, return the following tuple:</p>
 
239
 
 
240
      <p><c>{skip_and_save,Reason,ConfigList}</c></p>
 
241
 
 
242
      <p>The result will be that the test case is skipped with <c>Reason</c> printed to
 
243
      the log file (as described in previous chapters), and <c>ConfigList</c> is saved 
 
244
      for the next test case. <c>ConfigList</c> may be read by means of 
 
245
      <c>?config(saved_config, Config)</c>, as described above. <c>skip_and_save</c>
 
246
      may also be returned from <c>init_per_suite</c>, in which case the saved data can
 
247
      be read by <c>init_per_suite</c> in the suite that follows.</p>
 
248
    </section>
 
249
 
 
250
    <section>
 
251
    <marker id="sequences"></marker>
 
252
      <title>Sequences</title>
 
253
 
 
254
      <p>It is possible that test cases depend on each other so that
 
255
        if one case fails, the following test(s) should not be executed.
 
256
        Typically, if the <c>save_config</c> facility is used and a test 
 
257
        case that is expected to save data crashes, the following 
 
258
        case can not run. CT offers a way to declare such dependencies, 
 
259
        called sequences.</p>
 
260
 
 
261
      <p>A sequence of test cases is declared by means of the function
 
262
        <c>sequences/0</c>. This function should return a list of
 
263
        tuples on the format: <c>{SeqTag,TestCases}</c>. <c>SeqTag</c>
 
264
        is an atom that identifies one particular sequence. <c>TestCases</c>
 
265
        is a list of test case names. Sequences must be included in the list 
 
266
        that <c>all/0</c> returns. They are declared as: <c>{sequence,SeqTag}</c>.</p>
 
267
 
 
268
      <p>For example, if we would like to make sure that if <c>allocate</c>
 
269
        in <c>server_b_SUITE</c> (above) crashes, <c>deallocate</c> is skipped,
 
270
        we may declare the sequence:</p>
 
271
      
 
272
      <pre>
 
273
        sequences() -> [{alloc_and_dealloc,[alloc,dealloc]}].
 
274
      </pre>
 
275
 
 
276
      <p>Let's also assume the suite contains the test case <c>get_resource_status</c>, 
 
277
        which is independent of the other two cases. The <c>all</c> function could look
 
278
        like this:</p>
 
279
 
 
280
      <pre>
 
281
        all() -> [{sequence,alloc_and_dealloc}, get_resource_status].
 
282
      </pre>
 
283
 
 
284
      <p>If <c>alloc</c> succeeds, <c>dealloc</c> is also executed. If <c>alloc</c> fails
 
285
        however, <c>dealloc</c> is not executed but marked as SKIPPED in the html log. 
 
286
        <c>get_resource_status</c> will run no matter what happens to the <c>alloc_and_dealloc</c>
 
287
        cases.</p>
 
288
 
 
289
      <p>Test cases in a sequence will be executed in order until they have all succeeded or 
 
290
        until one case fails. If one fails, all following cases in the sequence are skipped.
 
291
        The cases in the sequence that have succeeded up to that point are reported as successful
 
292
        in the log. An arbitrary number of sequence tuples may be specified. Example:</p>
 
293
 
 
294
      <pre>
 
295
        sequences() -> [{scenarioA, [testA1, testA2]}, 
 
296
                        {scenarioB, [testB1, testB2, testB3]}].
 
297
 
 
298
        all() -> [test1, 
 
299
                  test2, 
 
300
                  {sequence,scenarioA}, 
 
301
                  test3, 
 
302
                  {sequence,scenarioB}, 
 
303
                  test4].
 
304
        </pre>
 
305
 
 
306
        <note><p>It is not possible to execute a test case which is part of a sequence as a 
 
307
        regular (stand alone) test case. It is also not possible to use the same test case in
 
308
        multiple sequences. Remember that you can always work around these limitations if
 
309
        necessary by means of help functions common for the test cases in question.</p></note>
 
310
    </section>
 
311
</chapter>