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

« back to all changes in this revision

Viewing changes to lib/edoc/src/edoc_types.hrl

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%% =====================================================================
 
2
%% Header file for EDoc Type Representations
 
3
%% 
 
4
%% Copyright (C) 2001-2005 Richard Carlsson
 
5
%%
 
6
%% This library is free software; you can redistribute it and/or modify
 
7
%% it under the terms of the GNU Lesser General Public License as
 
8
%% published by the Free Software Foundation; either version 2 of the
 
9
%% License, or (at your option) any later version.
 
10
%%
 
11
%% This library is distributed in the hope that it will be useful, but
 
12
%% WITHOUT ANY WARRANTY; without even the implied warranty of
 
13
%% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
 
14
%% Lesser General Public License for more details.
 
15
%%
 
16
%% You should have received a copy of the GNU Lesser General Public
 
17
%% License along with this library; if not, write to the Free Software
 
18
%% Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307
 
19
%% USA
 
20
%%
 
21
%% Author contact: richardc@csd.uu.se
 
22
%% =====================================================================
 
23
 
 
24
%% Type specification data structures
 
25
 
 
26
%% @type t_spec() = #t_spec{name = t_name(),
 
27
%%                          type = t_type(),
 
28
%%                          defs = [t_def()]}
 
29
 
 
30
-record(t_spec, {name, type, defs=[]}).         % function specification
 
31
 
 
32
%% @type type() = t_atom() | t_fun() | t_integer() | t_list() | t_nil()
 
33
%%              | t_tuple() | t_type() | t_union() | t_var()
 
34
 
 
35
%% @type t_typedef() = #t_typedef{name = t_name(),
 
36
%%                                args = [type()],
 
37
%%                                type = type(),
 
38
%%                                defs = [t_def()]}
 
39
 
 
40
-record(t_typedef, {name, args, type,
 
41
                    defs=[]}).                  % type declaration/definition
 
42
 
 
43
%% @type t_throws() = #t_throws{type = type(),
 
44
%%                              defs = [t_def()]}
 
45
 
 
46
-record(t_throws, {type, defs=[]}).             % exception declaration
 
47
 
 
48
%% @type t_def() = #t_def{name = t_name(),
 
49
%%                        type = type()}
 
50
 
 
51
-record(t_def, {name, type}).                   % local definition 'name = type'
 
52
%% @type t_name() = #t_name{app = [] | atom(),
 
53
%%                          module = [] | atom(),
 
54
%%                          name = [] | atom()}
 
55
 
 
56
-record(t_name, {app = [],                      % app = [] if module = []
 
57
                 module=[],                     % unqualified if module = []
 
58
                 name=[]}).
 
59
 
 
60
%% The following records all have 'a=[]' as their first field.
 
61
%% This is used for name annotations; in particular, the fun-argument
 
62
%% types of a function specification (t_spec) are often annotated with
 
63
%% the names of the corresponding formal parameters.
 
64
 
 
65
-define(t_ann(X), element(2, X)).
 
66
-define(set_t_ann(X, Y), setelement(2, X, Y)).
 
67
 
 
68
%% @type t_var() = #t_var{a = list(), name = [] | atom()}
 
69
 
 
70
-record(t_var, {a=[], name=[]}).        % type variable
 
71
 
 
72
%% @type t_type() = #t_type{a = list(),
 
73
%%                          name = t_name(),
 
74
%%                          args = [type()]}
 
75
 
 
76
-record(t_type, {a=[], name, args = []}).       % abstract type 'name(...)'
 
77
 
 
78
%% @type t_union() = #t_union{a = list(),
 
79
%%                            types = [type()]}
 
80
 
 
81
-record(t_union, {a=[], types = []}).   % union type 't1|...|tN'
 
82
 
 
83
%% @type t_fun() = #t_fun{a = list(),
 
84
%%                        args = [type()],
 
85
%%                        range = type()}
 
86
 
 
87
-record(t_fun, {a=[], args, range}).    % function '(t1,...,tN) -> range'
 
88
 
 
89
%% @type t_tuple() = #t_tuple{a = list(),
 
90
%%                            types = [type()]}
 
91
 
 
92
-record(t_tuple, {a=[], types = []}).   % tuple type '{t1,...,tN}'
 
93
 
 
94
%% @type t_list() = #t_list{a = list(),
 
95
%%                          type = type()}
 
96
 
 
97
-record(t_list, {a=[], type}).          % list type '[type]'
 
98
 
 
99
%% @type t_nil() = #t_nil{a = list()}
 
100
 
 
101
-record(t_nil, {a=[]}).                 % empty-list constant '[]'
 
102
 
 
103
%% @type t_atom() = #t_atom{a = list(),
 
104
%%                          val = atom()}
 
105
 
 
106
-record(t_atom, {a=[], val}).           % atom constant
 
107
 
 
108
%% @type t_integer() = #t_integer{a = list(),
 
109
%%                                val = integer()}
 
110
 
 
111
-record(t_integer, {a=[], val}).        % integer constant
 
112
 
 
113
%% @type t_float() = #t_float{a = list(),
 
114
%%                            val = float()}
 
115
 
 
116
-record(t_float, {a=[], val}).          % floating-point constant
 
117
 
 
118
%% @type t_record() = #t_list{a = list(),
 
119
%%                            name = type(),
 
120
%%                            fields = [field()]}
 
121
 
 
122
-record(t_record, {a=[], name, fields = []}).   % record type '#r{f1,...,fN}'
 
123
 
 
124
%% @type t_field() = #t_field{a = list(),
 
125
%%                            name = type(),
 
126
%%                            type = type()}
 
127
 
 
128
-record(t_field, {a=[], name, type}).   % named field 'n1=t1'