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

« back to all changes in this revision

Viewing changes to lib/tools/doc/src/cover.xml

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (1.1.13 upstream)
  • Revision ID: james.westby@ubuntu.com-20090215164252-dxpjjuq108nz4noa
Tags: 1:12.b.5-dfsg-2
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 erlref SYSTEM "erlref.dtd">
 
3
 
 
4
<erlref>
 
5
  <header>
 
6
    <copyright>
 
7
      <year>2001</year>
 
8
      <year>2007</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>cover</title>
 
27
    <prepared></prepared>
 
28
    <docno></docno>
 
29
    <date></date>
 
30
    <rev></rev>
 
31
  </header>
 
32
  <module>cover</module>
 
33
  <modulesummary>A Coverage Analysis Tool for Erlang</modulesummary>
 
34
  <description>
 
35
    <p>The module <c>cover</c> provides a set of functions for coverage
 
36
      analysis of Erlang programs, counting how many times each
 
37
      <em>executable line</em> of code is executed when a program is run.      <br></br>
 
38
 
 
39
      An executable line contains an Erlang expression such as a matching
 
40
      or a function call. A blank line or a line containing a comment,
 
41
      function head or pattern in a <c>case</c>- or <c>receive</c> statement
 
42
      is not executable.</p>
 
43
    <p>Coverage analysis can be used to verify test cases, making sure all
 
44
      relevant code is covered, and may also be helpful when looking for
 
45
      bottlenecks in the code.</p>
 
46
    <p>Before any analysis can take place, the involved modules must be
 
47
      <em>Cover compiled</em>. This means that some extra information is
 
48
      added to the module before it is compiled into a binary which then
 
49
      is loaded. The source file of the module is not affected and no
 
50
      <c>.beam</c> file is created.</p>
 
51
    <p>Each time a function in a Cover compiled module is called,
 
52
      information about the call is added to an internal database of Cover.
 
53
      The coverage analysis is performed by examining the contents of
 
54
      the Cover database. The output <c>Answer</c> is determined by two
 
55
      parameters, <c>Level</c> and <c>Analysis</c>.</p>
 
56
    <list type="bulleted">
 
57
      <item>
 
58
        <p><c>Level = module</c></p>
 
59
        <p><c>Answer = {Module,Value}</c>, where <c>Module</c> is the module
 
60
          name.</p>
 
61
      </item>
 
62
      <item>
 
63
        <p><c>Level = function</c></p>
 
64
        <p><c>Answer = [{Function,Value}]</c>, one tuple for each function in
 
65
          the module. A function is specified by its module name <c>M</c>,
 
66
          function name <c>F</c> and arity <c>A</c> as a tuple
 
67
          <c>{M,F,A}</c>.</p>
 
68
      </item>
 
69
      <item>
 
70
        <p><c>Level = clause</c></p>
 
71
        <p><c>Answer = [{Clause,Value}]</c>, one tuple for each clause in
 
72
          the module. A clause is specified by its module name <c>M</c>,
 
73
          function name <c>F</c>, arity <c>A</c> and position in the function
 
74
          definition <c>C</c> as a tuple <c>{M,F,A,C}</c>.</p>
 
75
      </item>
 
76
      <item>
 
77
        <p><c>Level = line</c></p>
 
78
        <p><c>Answer = [{Line,Value}]</c>, one tuple for each executable
 
79
          line in the module. A line is specified by its module name <c>M</c>
 
80
          and line number in the source file <c>N</c> as a tuple
 
81
          <c>{M,N}</c>.</p>
 
82
      </item>
 
83
      <item>
 
84
        <p><c>Analysis = coverage</c></p>
 
85
        <p><c>Value = {Cov,NotCov}</c> where <c>Cov</c> is the number of
 
86
          executable lines in the module, function, clause or line that have
 
87
          been executed at least once and <c>NotCov</c> is the number of
 
88
          executable lines that have not been executed.</p>
 
89
      </item>
 
90
      <item>
 
91
        <p><c>Analysis = calls</c></p>
 
92
        <p><c>Value = Calls</c> which is the number of times the module,
 
93
          function, or clause has been called. In the case of line level
 
94
          analysis, <c>Calls</c> is the number of times the line has been
 
95
          executed.</p>
 
96
      </item>
 
97
    </list>
 
98
    <p><em>Distribution</em></p>
 
99
    <p>Cover can be used in a distributed Erlang system. One of the
 
100
      nodes in the system must then be selected as the <em>main node</em>, and all Cover commands must be executed from this
 
101
      node. The error reason <c>not_main_node</c> is returned if an
 
102
      interface function is called on one of the remote nodes.</p>
 
103
    <p>Use <c>cover:start/1</c> and <c>cover:stop/1</c> to add or
 
104
      remove nodes. The same Cover compiled code will be loaded on each
 
105
      node, and analysis will collect and sum up coverage data results
 
106
      from all nodes.</p>
 
107
  </description>
 
108
  <funcs>
 
109
    <func>
 
110
      <name>start() -> {ok,Pid} | {error,Reason}</name>
 
111
      <fsummary>Start Cover.</fsummary>
 
112
      <type>
 
113
        <v>Pid = pid()</v>
 
114
        <v>Reason = {already_started,Pid}</v>
 
115
      </type>
 
116
      <desc>
 
117
        <p>Starts the Cover server which owns the Cover internal database.
 
118
          This function is called automatically by the other functions in
 
119
          the module.</p>
 
120
      </desc>
 
121
    </func>
 
122
    <func>
 
123
      <name>start(Nodes) -> {ok,StartedNodes} | {error,not_main_node}</name>
 
124
      <fsummary>Start Cover on remote nodes.</fsummary>
 
125
      <type>
 
126
        <v>Nodes = StartedNodes = [atom()]</v>
 
127
      </type>
 
128
      <desc>
 
129
        <p>Starts a Cover server on the each of given nodes, and loads
 
130
          all cover compiled modules.</p>
 
131
      </desc>
 
132
    </func>
 
133
    <func>
 
134
      <name>compile(ModFile) -> Result</name>
 
135
      <name>compile(ModFile, Options) -> Result</name>
 
136
      <name>compile_module(ModFile) -> Result</name>
 
137
      <name>compile_module(ModFile, Options) -> Result</name>
 
138
      <fsummary>Compile a module for Cover analysis.</fsummary>
 
139
      <type>
 
140
        <v>ModFile = Module | File</v>
 
141
        <v>&nbsp;Module = atom()</v>
 
142
        <v>&nbsp;File = string()</v>
 
143
        <v>Options = [Option]</v>
 
144
        <v>&nbsp;Option = {i,Dir} | {d,Macro} | {d,Macro,Value}</v>
 
145
        <d>See <c>compile:file/2.</c></d>
 
146
        <v>Result = {ok,Module} | {error,File} | {error,not_main_node}</v>
 
147
      </type>
 
148
      <desc>
 
149
        <p>Compiles a module for Cover analysis. The module is given by its
 
150
          module name <c>Module</c> or by its file name <c>File</c>.
 
151
          The <c>.erl</c> extension may be omitted. If the module is
 
152
          located in another directory, the path has to be specified.</p>
 
153
        <p><c>Options</c> is a list of compiler options which defaults to
 
154
          <c>[]</c>. Only options defining include file directories and
 
155
          macros are passed to <c>compile:file/2</c>, everything else is
 
156
          ignored.</p>
 
157
        <p>If the module is successfully Cover compiled, the function
 
158
          returns <c>{ok,Module}</c>. Otherwise the function returns
 
159
          <c>{error,File}</c>. Errors and warnings are printed as they
 
160
          occur.</p>
 
161
        <p>Note that the internal database is (re-)initiated during
 
162
          the compilation, meaning any previously collected coverage data
 
163
          for the module will be lost.</p>
 
164
      </desc>
 
165
    </func>
 
166
    <func>
 
167
      <name>compile_directory() -> [Result] | {error,Reason}</name>
 
168
      <name>compile_directory(Dir) -> [Result] | {error,Reason}</name>
 
169
      <name>compile_directory(Dir, Options) -> [Result] | {error,Reason}</name>
 
170
      <fsummary>Compile all modules in a directory for Cover analysis.</fsummary>
 
171
      <type>
 
172
        <v>Dir = string()</v>
 
173
        <v>Options = [Option]</v>
 
174
        <d>See <c>compile_module/1,2</c></d>
 
175
        <v>Result = {ok,Module} | {error,File} | {error,not_main_node}</v>
 
176
        <d>See <c>compile_module/1,2</c></d>
 
177
        <v>Reason = eacces | enoent</v>
 
178
      </type>
 
179
      <desc>
 
180
        <p>Compiles all modules (<c>.erl</c> files) in a directory
 
181
          <c>Dir</c> for Cover analysis the same way as
 
182
          <c>compile_module/1,2</c> and returns a list with the return
 
183
          values.</p>
 
184
        <p><c>Dir</c> defaults to the current working directory.</p>
 
185
        <p>The function returns <c>{error,eacces}</c> if the directory is not
 
186
          readable or <c>{error,enoent}</c> if the directory does not exist.</p>
 
187
      </desc>
 
188
    </func>
 
189
    <func>
 
190
      <name>compile_beam(ModFile) -> Result</name>
 
191
      <fsummary>Compile a module for Cover analysis, using an existing beam.</fsummary>
 
192
      <type>
 
193
        <v>ModFile = Module | BeamFile</v>
 
194
        <v>&nbsp;Module = atom()</v>
 
195
        <v>&nbsp;BeamFile = string()</v>
 
196
        <v>Result = {ok,Module} | {error,BeamFile} | {error,Reason}</v>
 
197
        <v>&nbsp;Reason = non_existing | {no_abstract_code,BeamFile} | {encrypted_abstract_code,BeamFile} | {already_cover_compiled,no_beam_found,Module} | not_main_node</v>
 
198
      </type>
 
199
      <desc>
 
200
        <p>Does the same as <c>compile/1,2</c>, but uses an existing
 
201
          <c>.beam</c> file as base, i.e. the module is not compiled
 
202
          from source. Thus <c>compile_beam/1</c> is faster than
 
203
          <c>compile/1,2</c>.</p>
 
204
        <p>Note that the existing <c>.beam</c> file must contain
 
205
          <em>abstract code</em>, i.e. it must have been compiled with
 
206
          the <c>debug_info</c> option. If not, the error reason
 
207
          <c>{no_abstract_code,BeamFile}</c> is returned.
 
208
          If the abstract code is encrypted, and no key is available
 
209
          for decrypting it, the error reason 
 
210
          <c><![CDATA[{encrypted_abstract_code,BeamFile} is returned. <p>If only the module name (i.e. not the full name of the <c>.beam]]></c> file) is given to this function, the
 
211
          <c>.beam</c> file is found by calling
 
212
          <c>code:which(Module)</c>. If no <c>.beam</c> file is found,
 
213
          the error reason <c>non_existing</c> is returned. If the
 
214
          module is already cover compiled with <c>compile_beam/1</c>,
 
215
          the <c>.beam</c> file will be picked from the same location
 
216
          as the first time it was compiled. If the module is already
 
217
          cover compiled with <c>compile/1,2</c>, there is no way to
 
218
          find the correct <c>.beam</c> file, so the error reason
 
219
          <c>{already_cover_compiled,no_beam_found,Module}</c> is
 
220
          returned.</p>
 
221
        <p><c>{error,BeamFile}</c> is returned if the compiled code
 
222
          can not be loaded on the node.</p>
 
223
      </desc>
 
224
    </func>
 
225
    <func>
 
226
      <name>compile_beam_directory() -> [Result] | {error,Reason}</name>
 
227
      <name>compile_beam_directory(Dir) -> [Result] | {error,Reason}</name>
 
228
      <fsummary>Compile all .beam files in a directory for Cover analysis.</fsummary>
 
229
      <type>
 
230
        <v>Dir = string()</v>
 
231
        <v>Result = See compile_beam/1</v>
 
232
        <v>Reason = eacces | enoent</v>
 
233
      </type>
 
234
      <desc>
 
235
        <p>Compiles all modules (<c>.beam</c> files) in a directory
 
236
          <c>Dir</c> for Cover analysis the same way as
 
237
          <c>compile_beam/1</c> and returns a list with the return
 
238
          values.</p>
 
239
        <p><c>Dir</c> defaults to the current working directory.</p>
 
240
        <p>The function returns <c>{error,eacces}</c> if the directory is not
 
241
          readable or <c>{error,enoent}</c> if the directory does not exist.</p>
 
242
      </desc>
 
243
    </func>
 
244
    <func>
 
245
      <name>analyse(Module) -> {ok,Answer} | {error,Error}</name>
 
246
      <name>analyse(Module, Analysis) -> {ok,Answer} | {error,Error}</name>
 
247
      <name>analyse(Module, Level) -> {ok,Answer} | {error,Error}</name>
 
248
      <name>analyse(Module, Analysis, Level) -> {ok,Answer} | {error,Error}</name>
 
249
      <fsummary>Analyse a Cover compiled module.</fsummary>
 
250
      <type>
 
251
        <v>Module = atom()</v>
 
252
        <v>Analysis = coverage | calls</v>
 
253
        <v>Level = line | clause | function | module</v>
 
254
        <v>Answer = {Module,Value} | [{Item,Value}]</v>
 
255
        <v>&nbsp;Item = Line | Clause | Function</v>
 
256
        <v>&nbsp;&nbsp;Line = {M,N}</v>
 
257
        <v>&nbsp;&nbsp;Clause = {M,F,A,C}</v>
 
258
        <v>&nbsp;&nbsp;Function = {M,F,A}</v>
 
259
        <v>&nbsp;&nbsp;&nbsp;M = F = atom()</v>
 
260
        <v>&nbsp;&nbsp;&nbsp;N = A = C = integer()</v>
 
261
        <v>&nbsp;Value = {Cov,NotCov} | Calls</v>
 
262
        <v>&nbsp;&nbsp;Cov = NotCov = Calls = integer()</v>
 
263
        <v>Error = {not_cover_compiled,Module} | not_main_node</v>
 
264
      </type>
 
265
      <desc>
 
266
        <p>Performs analysis of a Cover compiled module <c>Module</c>, as
 
267
          specified by <c>Analysis</c> and <c>Level</c> (see above), by
 
268
          examining the contents of the internal database.</p>
 
269
        <p><c>Analysis</c> defaults to <c>coverage</c> and <c>Level</c>
 
270
          defaults to <c>function</c>.</p>
 
271
        <p>If <c>Module</c> is not Cover compiled, the function returns
 
272
          <c>{error,{not_cover_compiled,Module}}</c>.</p>
 
273
      </desc>
 
274
    </func>
 
275
    <func>
 
276
      <name>analyse_to_file(Module) -> </name>
 
277
      <name>analyse_to_file(Module,Options) -> </name>
 
278
      <name>analyse_to_file(Module, OutFile) -> </name>
 
279
      <name>analyse_to_file(Module, OutFile, Options) ->  {ok,OutFile} | {error,Error}</name>
 
280
      <fsummary>Detailed coverage analysis of a Cover compiled module.</fsummary>
 
281
      <type>
 
282
        <v>Module = atom()</v>
 
283
        <v>OutFile = string()</v>
 
284
        <v>Options = [Option]</v>
 
285
        <v>Option = html</v>
 
286
        <v>Error = {not_cover_compiled,Module} | {file,File,Reason} | no_source_code_found | not_main_node</v>
 
287
        <v>&nbsp;File = string()</v>
 
288
        <v>&nbsp;Reason = term()</v>
 
289
      </type>
 
290
      <desc>
 
291
        <p>Makes a copy <c>OutFile</c> of the source file for a module
 
292
          <c>Module</c>, where it for each executable line is specified
 
293
          how many times it has been executed.</p>
 
294
        <p>The output file <c>OutFile</c> defaults to
 
295
          <c>Module.COVER.out</c>, or <c>Module.COVER.html</c> if the
 
296
          option <c>html</c> was used.</p>
 
297
        <p>If <c>Module</c> is not Cover compiled, the function returns
 
298
          <c>{error,{not_cover_compiled,Module}}</c>.</p>
 
299
        <p>If the source file and/or the output file cannot be opened using
 
300
          <c>file:open/2</c>, the function returns
 
301
          <c>{error,{file,File,Reason}}</c> where <c>File</c> is the file
 
302
          name and <c>Reason</c> is the error reason.</p>
 
303
        <p>If the module was cover compiled from the <c>.beam</c>
 
304
          file, i.e. using <c>compile_beam/1</c> or
 
305
          <c>compile_beam_directory/0,1</c>, it is assumed that the
 
306
          source code can be found in the same directory as the
 
307
          <c>.beam</c> file, or in <c>../src</c> relative to that
 
308
          directory. If no source code is found, 
 
309
          <c>,{error,no_source_code_found}</c> is returned.</p>
 
310
      </desc>
 
311
    </func>
 
312
    <func>
 
313
      <name>modules() -> [Module] | {error,not_main_node}</name>
 
314
      <fsummary>Return all Cover compiled modules.</fsummary>
 
315
      <type>
 
316
        <v>Module = atom()</v>
 
317
      </type>
 
318
      <desc>
 
319
        <p>Returns a list with all modules that are currently Cover
 
320
          compiled.</p>
 
321
      </desc>
 
322
    </func>
 
323
    <func>
 
324
      <name>imported_modules() -> [Module] | {error,not_main_node}</name>
 
325
      <fsummary>Return all modules for which there are imported data.</fsummary>
 
326
      <type>
 
327
        <v>Module = atom()</v>
 
328
      </type>
 
329
      <desc>
 
330
        <p>Returns a list with all modules for which there are
 
331
          imported data.</p>
 
332
      </desc>
 
333
    </func>
 
334
    <func>
 
335
      <name>imported() -> [File] | {error,not_main_node}</name>
 
336
      <fsummary>Return all imported files.</fsummary>
 
337
      <type>
 
338
        <v>File = string()</v>
 
339
      </type>
 
340
      <desc>
 
341
        <p>Returns a list with all imported files.</p>
 
342
      </desc>
 
343
    </func>
 
344
    <func>
 
345
      <name>which_nodes() -> [Node] | {error,not_main_node}</name>
 
346
      <fsummary>Return all nodes that are part of the coverage analysis.</fsummary>
 
347
      <type>
 
348
        <v>Node = atom()</v>
 
349
      </type>
 
350
      <desc>
 
351
        <p>Returns a list with all nodes that are part of the coverage
 
352
          analysis. Note that the current node is not returned. This
 
353
          node is always part of the analysis.</p>
 
354
      </desc>
 
355
    </func>
 
356
    <func>
 
357
      <name>is_compiled(Module) -> {file,File} | false |  {error,not_main_node}</name>
 
358
      <fsummary>Check if a module is Cover compiled.</fsummary>
 
359
      <type>
 
360
        <v>Module = atom()</v>
 
361
        <v>Beam = string()</v>
 
362
      </type>
 
363
      <desc>
 
364
        <p>Returns <c>{file,File}</c> if the module <c>Module</c> is
 
365
          Cover compiled, or <c>false</c> otherwise. <c>File</c> is
 
366
          the <c>.erl</c> file used by <c>cover:compile_module/1,2</c>
 
367
          or the <c>.beam</c> file used by <c>compile_beam/1</c>.</p>
 
368
      </desc>
 
369
    </func>
 
370
    <func>
 
371
      <name>reset(Module) -></name>
 
372
      <name>reset() ->  ok | {error,not_main_node}</name>
 
373
      <fsummary>Reset coverage data for Cover compiled modules.</fsummary>
 
374
      <type>
 
375
        <v>Module = atom()</v>
 
376
      </type>
 
377
      <desc>
 
378
        <p>Resets all coverage data for a Cover compiled module
 
379
          <c>Module</c> in the Cover database on all nodes. If the
 
380
          argument is omitted, the coverage data will be reset for all
 
381
          modules known by Cover.</p>
 
382
        <p>If <c>Module</c> is not Cover compiled, the function returns
 
383
          <c>{error,{not_cover_compiled,Module}}</c>.</p>
 
384
      </desc>
 
385
    </func>
 
386
    <func>
 
387
      <name>export(ExportFile)</name>
 
388
      <name>export(ExportFile,Module) -> ok | {error,Reason}</name>
 
389
      <fsummary>Reset coverage data for Cover compiled modules.</fsummary>
 
390
      <type>
 
391
        <v>ExportFile = string()</v>
 
392
        <v>Module = atom()</v>
 
393
        <v>Reason = {not_cover_compiled,Module} | {cant_open_file,ExportFile,Reason} | not_main_node</v>
 
394
      </type>
 
395
      <desc>
 
396
        <p>Exports the current coverage data for <c>Module</c> to the
 
397
          file <c>ExportFile</c>. It is recommended to name the
 
398
          <c>ExportFile</c> with the extension <c>.coverdata</c>, since
 
399
          other filenames can not be read by the web based interface to
 
400
          cover.</p>
 
401
        <p>If <c>Module</c> is not given, data for all Cover compiled
 
402
          or earlier imported modules is exported.</p>
 
403
        <p>This function is useful if coverage data from different
 
404
          systems is to be merged.</p>
 
405
        <p>See also <c>cover:import/1</c></p>
 
406
      </desc>
 
407
    </func>
 
408
    <func>
 
409
      <name>import(ExportFile) -> ok | {error,Reason}</name>
 
410
      <fsummary>Reset coverage data for Cover compiled modules.</fsummary>
 
411
      <type>
 
412
        <v>ExportFile = string()</v>
 
413
        <v>Reason = {cant_open_file,ExportFile,Reason} | not_main_node</v>
 
414
      </type>
 
415
      <desc>
 
416
        <p>Imports coverage data from the file <c>ExportFile</c>
 
417
          created with <c>cover:export/1,2</c>. Any analysis performed
 
418
          after this will include the imported data.</p>
 
419
        <p>Note that when compiling a module <em>all existing coverage data is removed</em>, including imported data. If a module is
 
420
          already compiled when data is imported, the imported data is
 
421
          <em>added</em> to the existing coverage data.</p>
 
422
        <p>Coverage data from several export files can be imported
 
423
          into one system. The coverage data is then added up when
 
424
          analysing.</p>
 
425
        <p>Coverage data for a module can not be imported from the
 
426
          same file twice unless the module is first reset or
 
427
          compiled. The check is based on the filename, so you can
 
428
          easily fool the system by renaming your export file.</p>
 
429
        <p>See also <c>cover:export/1,2</c></p>
 
430
      </desc>
 
431
    </func>
 
432
    <func>
 
433
      <name>stop() -> ok | {error,not_main_node}</name>
 
434
      <fsummary>Stop Cover.</fsummary>
 
435
      <desc>
 
436
        <p>Stops the Cover server and unloads all Cover compiled code.</p>
 
437
      </desc>
 
438
    </func>
 
439
    <func>
 
440
      <name>stop(Nodes) -> ok | {error,not_main_node}</name>
 
441
      <fsummary>Stop Cover on remote nodes.</fsummary>
 
442
      <type>
 
443
        <v>Nodes = [atom()]</v>
 
444
      </type>
 
445
      <desc>
 
446
        <p>Stops the Cover server and unloads all Cover compiled code
 
447
          on the given nodes. Data stored in the Cover database on the
 
448
          remote nodes is fetched and stored on the main node.</p>
 
449
      </desc>
 
450
    </func>
 
451
  </funcs>
 
452
 
 
453
  <section>
 
454
    <title>SEE ALSO</title>
 
455
    <p>code(3), compile(3)</p>
 
456
  </section>
 
457
</erlref>
 
458