~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

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