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

« back to all changes in this revision

Viewing changes to system/doc/reference_manual/typespec.xml

  • 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
<?xml version="1.0" encoding="latin1" ?>
 
2
<!DOCTYPE chapter SYSTEM "chapter.dtd">
 
3
 
 
4
<chapter>
 
5
  <header>
 
6
    <copyright>
 
7
      <year>2003</year><year>2009</year>
 
8
      <holder>Ericsson AB. All Rights Reserved.</holder>
 
9
    </copyright>
 
10
    <legalnotice>
 
11
      The contents of this file are subject to the Erlang Public License,
 
12
      Version 1.1, (the "License"); you may not use this file except in
 
13
      compliance with the License. You should have received a copy of the
 
14
      Erlang Public License along with this software. If not, it can be
 
15
      retrieved online at http://www.erlang.org/.
 
16
    
 
17
      Software distributed under the License is distributed on an "AS IS"
 
18
      basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
19
      the License for the specific language governing rights and limitations
 
20
      under the License.
 
21
    
 
22
    </legalnotice>
 
23
 
 
24
    <title>Types and Function Specifications</title>
 
25
    <prepared>Kostis Sagonas, Tobias Lindahl, Kenneth Lundin</prepared>
 
26
    <docno></docno>
 
27
    <date></date>
 
28
    <rev></rev>
 
29
    <file>typespec.xml</file>
 
30
  </header>
 
31
 
 
32
  <section>
 
33
  <title>Introduction of Types</title>
 
34
  <p>
 
35
  Although Erlang is a dynamically typed language this section describes
 
36
  an extension to the Erlang language for declaring sets of Erlang terms 
 
37
  to form a particular type, effectively forming a specific sub-type of the 
 
38
  set of all Erlang terms.
 
39
  </p>
 
40
  <p> 
 
41
  Subsequently, these types can be used to specify types of record fields 
 
42
  and the argument and return types of functions.
 
43
  </p>
 
44
  <p>
 
45
  Type information can be used to document function interfaces, 
 
46
  provide more information for bug detection tools such as <c>Dialyzer</c>, 
 
47
  and can be exploited by documentation tools such as <c>Edoc</c> for 
 
48
  generating program documentation of various forms. 
 
49
  It is expected that the type language described in this document will 
 
50
  supersede and replace the purely comment-based <c>@type</c> and 
 
51
  <c>@spec</c> declarations used by <c>Edoc</c>.
 
52
  </p>
 
53
  <warning>
 
54
    The syntax and semantics described here is still preliminary and might be 
 
55
    slightly changed and extended before it becomes officially supported.
 
56
    The plan is that this will happen in R14B.
 
57
  </warning>
 
58
  </section>
 
59
  <section>
 
60
    <marker id="syntax"></marker>
 
61
    <title>Types and their Syntax</title>
 
62
    <p>
 
63
    Types describe sets of Erlang terms. 
 
64
    Types consist and are built from a set of predefined types (e.g. <c>integer()</c>, 
 
65
    <c>atom()</c>, <c>pid()</c>, ...) described below. 
 
66
    Predefined types represent a typically infinite set of Erlang terms which 
 
67
    belong to this type. 
 
68
    For example, the type <c>atom()</c> stands for the set of all Erlang atoms.
 
69
        </p>
 
70
        <p>
 
71
    For integers and atoms, we allow for singleton types (e.g. the integers <c>-1</c> 
 
72
    and <c>42</c> or the atoms <c>'foo'</c> and <c>'bar'</c>).
 
73
 
 
74
    All other types are built using unions of either predefined types or singleton 
 
75
    types. In a type union between a type and one of its sub-types the sub-type is 
 
76
    absorbed by the super-type and the union is subsequently treated as if the 
 
77
    sub-type was not a constituent of the union. For example, the type union:
 
78
    </p>
 
79
    <pre>
 
80
 atom() | 'bar' | integer() | 42</pre>
 
81
    <p>
 
82
    describes the same set of terms as the type union:
 
83
    </p>
 
84
        <pre>
 
85
atom() | integer()</pre>
 
86
        <p>
 
87
        Because of sub-type relations that exist between types, types form a lattice 
 
88
        where the topmost element, any(), denotes the set of all Erlang terms and 
 
89
        the bottom-most element, none(), denotes the empty set of terms.
 
90
        </p>
 
91
        <p>
 
92
        The set of predefined types and the syntax for types is given below:
 
93
        </p>
 
94
        <pre><![CDATA[
 
95
Type :: any()            %% The top type, the set of all Erlang terms.
 
96
      | none()           %% The bottom type, contains no terms.
 
97
      | pid()
 
98
      | port()
 
99
      | ref()
 
100
      | []               %% nil
 
101
      | Atom
 
102
      | Binary
 
103
      | float()
 
104
      | Fun
 
105
      | Integer
 
106
      | List
 
107
      | Tuple
 
108
      | Union
 
109
      | UserDefined      %% described in Section 2
 
110
 
 
111
Union :: Type1 | Type2
 
112
 
 
113
Atom :: atom()
 
114
      | Erlang_Atom      %% 'foo', 'bar', ...
 
115
 
 
116
Binary :: binary()                        %% <<_:_ * 8>>
 
117
        | <<>>
 
118
        | <<_:Erlang_Integer>>            %% Base size
 
119
        | <<_:_*Erlang_Integer>>          %% Unit size
 
120
        | <<_:Erlang_Integer, _:_*Erlang_Integer>>
 
121
 
 
122
Fun :: fun()                              %% any function
 
123
     | fun((...) -> Type)                 %% any arity, returning Type
 
124
     | fun(() -> Type)
 
125
     | fun((TList) -> Type)
 
126
 
 
127
Integer :: integer()
 
128
         | Erlang_Integer                 %% ..., -1, 0, 1, ... 42 ...
 
129
         | Erlang_Integer..Erlang_Integer %% specifies an integer range
 
130
 
 
131
List :: list(Type)                        %% Proper list ([]-terminated)
 
132
      | improper_list(Type1, Type2)       %% Type1=contents, Type2=termination
 
133
      | maybe_improper_list(Type1, Type2) %% Type1 and Type2 as above
 
134
 
 
135
Tuple :: tuple()                          %% stands for a tuple of any size
 
136
       | {}
 
137
       | {TList}
 
138
 
 
139
TList :: Type
 
140
       | Type, TList
 
141
]]></pre>
 
142
        <p>
 
143
        Because lists are commonly used, they have shorthand type notations. 
 
144
        The type <c>list(T)</c> has the shorthand <c>[T]</c>. The shorthand <c>[T,...]</c> stands for 
 
145
        the set of non-empty proper lists whose elements are of type <c>T</c>. 
 
146
        The only difference between the two shorthands is that <c>[T]</c> may be an 
 
147
        empty list but <c>[T,...]</c> may not.
 
148
        </p>
 
149
        <p>
 
150
        Notice that the shorthand for <c>list()</c>, i.e. the list of elements of unknown type,
 
151
        is <c>[_]</c> (or <c>[any()]</c>), not <c>[]</c>. 
 
152
        The notation <c>[]</c> specifies the singleton type for the empty list.
 
153
        </p>
 
154
        <p>
 
155
        For convenience, the following types are also built-in. 
 
156
        They can be thought as predefined aliases for the type unions also shown in 
 
157
        the table. (Some type unions below slightly abuse the syntax of types.)
 
158
        </p>
 
159
        <table>
 
160
                <row>
 
161
                <cell><b>Built-in type</b></cell><cell><b>Stands for</b></cell>
 
162
                </row>
 
163
                <row>
 
164
                <cell><c>term()</c></cell><cell><c>any()</c></cell>
 
165
                </row>
 
166
                <row> 
 
167
                <cell><c>bool()</c></cell><cell><c>'false' | 'true'</c></cell>
 
168
                </row>
 
169
                <row> 
 
170
                <cell><c>byte()</c></cell><cell><c>0..255</c></cell>
 
171
                </row>
 
172
                <row>
 
173
                <cell><c>char()</c></cell><cell><c>0..16#10ffff</c></cell>
 
174
                </row>
 
175
                <row> 
 
176
                <cell><c>non_neg_integer()</c></cell><cell><c>0..</c></cell>
 
177
                </row>
 
178
                <row> 
 
179
                <cell><c>pos_integer()</c></cell><cell><c>1..</c></cell>
 
180
                </row>
 
181
                <row> 
 
182
                <cell><c>neg_integer()</c></cell><cell><c>..-1</c></cell>
 
183
                </row>
 
184
                <row> 
 
185
                <cell><c>number()</c></cell><cell><c>integer() | float()</c></cell>
 
186
                </row>
 
187
                <row> 
 
188
                <cell><c>list()</c></cell><cell><c>[any()]</c></cell>
 
189
                </row>
 
190
                <row> 
 
191
                <cell><c>maybe_improper_list()</c></cell><cell><c>maybe_improper_list(any(), any())</c></cell>
 
192
                </row>
 
193
                <row> 
 
194
                <cell><c>maybe_improper_list(T)</c></cell><cell><c>maybe_improper_list(T, any())</c></cell> 
 
195
                </row>
 
196
                <row>
 
197
                <cell><c>string()</c></cell><cell><c>[char()]</c></cell>
 
198
                </row>
 
199
                <row> 
 
200
                <cell><c>nonempty_string()</c></cell><cell><c>[char(),...]</c></cell>
 
201
                </row>
 
202
                <row> 
 
203
                <cell><c>iolist()</c></cell><cell><c>maybe_improper_list( 
 
204
char() | binary() | iolist(), binary() | [])</c></cell>
 
205
                </row>
 
206
                <row>
 
207
                <cell><c>module()</c></cell><cell><c>atom()</c></cell>
 
208
                </row>
 
209
                <row> 
 
210
                <cell><c>mfa()</c></cell><cell><c>{atom(),atom(),byte()}</c></cell>
 
211
                </row>
 
212
                <row>
 
213
                <cell><c>node()</c></cell><cell><c>atom()</c></cell>
 
214
                </row>
 
215
                <row>
 
216
                <cell><c>timeout()</c></cell><cell><c>'infinity' | non_neg_integer()</c></cell>
 
217
                </row>
 
218
                <row>
 
219
                <cell><c>no_return()</c></cell><cell><c>none()</c></cell> 
 
220
                </row>
 
221
        </table>
 
222
        
 
223
        <p>
 
224
        Users are not allowed to define types with the same names as the predefined or 
 
225
        built-in ones. 
 
226
        This is checked by the compiler and its violation results in a compilation 
 
227
        error. 
 
228
        (For bootstrapping purposes, it can also result to just a warning if this 
 
229
        involves a built-in type which has just been introduced.)
 
230
        </p>
 
231
        <note>
 
232
        The following built-in list types also exist, 
 
233
        but they are expected to be rarely used. Hence, they have long names:
 
234
        </note>
 
235
        <pre>
 
236
nonempty_maybe_improper_list(Type) :: nonempty_maybe_improper_list(Type, any())
 
237
nonempty_maybe_improper_list() :: nonempty_maybe_improper_list(any())
 
238
        </pre>
 
239
        <p>
 
240
          where the following two types
 
241
          define the set of Erlang terms one would expect:
 
242
        </p>
 
243
        <pre>
 
244
nonempty_improper_list(Type1, Type2)
 
245
nonempty_maybe_improper_list(Type1, Type2)
 
246
        </pre>
 
247
        <p>
 
248
        Also for convenience, we allow for record notation to be used. 
 
249
        Records are just shorthands for the corresponding tuples.
 
250
        </p>
 
251
        <pre>
 
252
Record :: #Erlang_Atom{}
 
253
        | #Erlang_Atom{Fields}
 
254
    </pre>
 
255
    <p>
 
256
        Records have been extended to possibly contain type information. 
 
257
        This is described in the sub-section <seealso marker="#typeinrecords">"Type information in record declarations"</seealso> below.
 
258
        </p>
 
259
        </section>
 
260
        
 
261
        <section>
 
262
                <title>Type declarations of user-defined types</title>
 
263
                <p>
 
264
                As seen, the basic syntax of a type is an atom followed by closed 
 
265
                parentheses. New types are declared using '-type' compiler attributes 
 
266
                as in the following:
 
267
                </p>
 
268
                <pre>
 
269
-type my_type() :: Type.
 
270
                </pre>
 
271
                <p>
 
272
                where the type name is an atom (<c>'my_type'</c> in the above) followed by 
 
273
                parenthesis. Type is a type as defined in the previous section. 
 
274
                A current restriction is that Type can contain only predefined types 
 
275
                or user-defined types which have been previously defined. 
 
276
                This restriction is enforced by the compiler and results in a 
 
277
                compilation error. (A similar restriction currently exists for records).
 
278
                </p>
 
279
                <p>
 
280
                This means that currently general recursive types cannot be defined. 
 
281
                Lifting this restriction is future work.
 
282
                </p>
 
283
                <p>
 
284
                Type declarations can also be parameterized by including type variables 
 
285
                between the parentheses. The syntax of type variables is the same as 
 
286
                Erlang variables (starts with an upper case letter). 
 
287
                Naturally, these variables can - and should - appear on the RHS of the 
 
288
                definition. A concrete example appears below:
 
289
                </p>
 
290
                <pre>
 
291
-type orddict(Key, Val) :: [{Key, Val}].
 
292
                </pre>
 
293
                
 
294
                </section>
 
295
 
 
296
                <marker id="typeinrecords"/>
 
297
                <section>
 
298
                        <title>
 
299
                          Type information in record declarations
 
300
                        </title>
 
301
                <p>
 
302
                The types of record fields can be specified in the declaration of the 
 
303
                record. The syntax for this is:
 
304
                </p>
 
305
                <pre>
 
306
-record(rec, {field1 :: Type1, field2, field3 :: Type3}).
 
307
                </pre>
 
308
                <p>
 
309
                For fields without type annotations, their type defaults to any(). 
 
310
                I.e., the above is a shorthand for:
 
311
                </p>
 
312
                <pre>
 
313
-record(rec, {field1 :: Type1, field2 :: any(), field3 :: Type3}).              
 
314
                </pre>
 
315
                <p>
 
316
                In the presence of initial values for fields, 
 
317
                the type must be declared after the initialization as in the following:
 
318
                </p>
 
319
                <pre>
 
320
-record(rec, {field1 = [] :: Type1, field2, field3 = 42 :: Type3}).
 
321
                </pre>
 
322
                <p>
 
323
                Naturally, the initial values for fields should be compatible 
 
324
                with (i.e. a member of) the corresponding types. 
 
325
                This is checked by the compiler and results in a compilation error 
 
326
                if a violation is detected. For fields without initial values, 
 
327
                the singleton type <c>'undefined'</c> is added to all declared types. 
 
328
                In other words, the following two record declarations have identical 
 
329
                effects:
 
330
                </p>
 
331
                <pre>
 
332
-record(rec, {f1 = 42 :: integer(),
 
333
              f2      :: float(),
 
334
              f3      :: 'a' | 'b').
 
335
 
 
336
-record(rec, {f1 = 42 :: integer(),
 
337
              f2      :: 'undefined' | float(),
 
338
              f3      :: 'undefined' | 'a' | 'b').
 
339
                </pre>
 
340
                <p>
 
341
                For this reason, it is recommended that records contain initializers, 
 
342
                whenever possible.
 
343
                </p>
 
344
                <p>
 
345
                Any record, containing type information or not, once defined, 
 
346
                can be used as a type using the syntax:
 
347
                </p>
 
348
                <pre>
 
349
#rec{}
 
350
                </pre>
 
351
                <p>
 
352
                In addition, the record fields can be further specified when using 
 
353
                a record type by adding type information about the field in the following 
 
354
                manner:
 
355
                </p>
 
356
                <pre>
 
357
#rec{some_field :: Type}
 
358
                </pre>
 
359
                <p>
 
360
                Any unspecified fields are assumed to have the type in the original 
 
361
                record declaration.
 
362
                </p>
 
363
        </section>
 
364
        
 
365
        <section>
 
366
                <title>Specifications (contracts) for functions</title>
 
367
                <p>
 
368
                A contract (or specification) for a function is given using the new 
 
369
                compiler attribute <c>'-spec'</c>. The basic format is as follows:
 
370
                </p>
 
371
                <pre>
 
372
-spec Module:Function(ArgType1, ..., ArgTypeN) -> ReturnType.
 
373
                </pre>
 
374
                <p>
 
375
                The arity of the function has to match the number of arguments, 
 
376
                or else a compilation error occurs.
 
377
                </p>
 
378
                <p>
 
379
                This form can also be used in header files (.hrl) to declare type 
 
380
                information for exported functions. 
 
381
                Then these header files can be included in files that (implicitly or 
 
382
                explicitly) import these functions.
 
383
                </p>
 
384
                <p>
 
385
                For most uses within a given module, the following shorthand is allowed:
 
386
                </p>
 
387
                <pre>
 
388
-spec Function(ArgType1, ..., ArgTypeN) -> ReturnType.
 
389
                </pre>
 
390
                <p>
 
391
                Also, for documentation purposes, argument names can be given:
 
392
                </p>
 
393
                <pre>
 
394
-spec Function(ArgName1 :: Type1, ..., ArgNameN :: TypeN) -> RT.
 
395
                </pre>
 
396
                <p>
 
397
                A function specification can be overloaded. 
 
398
                That is, it can have several types, separated by a semicolon (<c>;</c>):
 
399
                </p>
 
400
                <pre>
 
401
-spec foo(T1, T2) -> T3
 
402
       ; (T4, T5) -> T6.
 
403
       </pre>
 
404
       <p>
 
405
                A current restriction, which currently results in a warning 
 
406
                (OBS: not an error) by the compiler, is that the domains of the argument 
 
407
                types cannot be overlapping. 
 
408
                For example, the following specification results in a warning:
 
409
                </p>
 
410
                <pre>
 
411
-spec foo(pos_integer()) -> pos_integer()
 
412
       ; (integer()) -> integer().
 
413
        </pre>
 
414
        <p>
 
415
                Type variables can be used in specifications to specify relations for 
 
416
                the input and output arguments of a function. 
 
417
                For example, the following specification defines the type of a 
 
418
                polymorphic identity function:
 
419
                </p>
 
420
                <pre>
 
421
-spec id(X) -> X.
 
422
                </pre>
 
423
                <p>
 
424
                However, note that the above specification does not restrict the input 
 
425
                and output type in any way. 
 
426
                We can constrain these types by guard-like subtype constraints:
 
427
                </p>
 
428
                <pre>
 
429
-spec id(X) -> X when is_subtype(X, tuple()).
 
430
                </pre>
 
431
                <p>
 
432
                and provide bounded quantification. Currently, 
 
433
                the <c>is_subtype/2</c> guard is the only guard which can 
 
434
                be used in a <c>'-spec'</c> attribute.
 
435
                </p>
 
436
                <p>
 
437
                The scope of an <c>is_subtype/2</c> constraint is the 
 
438
                <c>(...) -> RetType</c> 
 
439
                specification after which it appears. To avoid confusion, 
 
440
                we suggest that different variables are used in different constituents of 
 
441
                an overloaded contract as in the example below:
 
442
                </p>
 
443
                <pre>
 
444
-spec foo({X, integer()}) -> X when is_subtype(X, atom())
 
445
       ; ([Y]) -> Y when is_subtype(Y, number()).
 
446
                </pre>
 
447
                <p>
 
448
                Some functions in Erlang are not meant to return; 
 
449
                either because they define servers or because they are used to 
 
450
                throw exceptions as the function below:
 
451
                </p>
 
452
                <pre>
 
453
my_error(Err) -> erlang:throw({error, Err}).
 
454
                </pre>
 
455
                <p>
 
456
                For such functions we recommend the use of the special no_return() 
 
457
                type for their "return", via a contract of the form:
 
458
                </p>
 
459
                <pre>
 
460
-spec my_error(term()) -> no_return().
 
461
                </pre>
 
462
              </section>
 
463
</chapter>
 
464