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

« back to all changes in this revision

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

  • 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
%% This library is free software; you can redistribute it and/or modify
 
3
%% it under the terms of the GNU Lesser General Public License as
 
4
%% published by the Free Software Foundation; either version 2 of the
 
5
%% License, or (at your option) any later version.
 
6
%%
 
7
%% This library is distributed in the hope that it will be useful, but
 
8
%% WITHOUT ANY WARRANTY; without even the implied warranty of
 
9
%% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
 
10
%% Lesser General Public License for more details.
 
11
%%
 
12
%% You should have received a copy of the GNU Lesser General Public
 
13
%% License along with this library; if not, write to the Free Software
 
14
%% Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307
 
15
%% USA
 
16
%%
 
17
%% $Id$
 
18
%%
 
19
%% @private
 
20
%% @copyright 2001-2003 Richard Carlsson
 
21
%% @author Richard Carlsson <richardc@csd.uu.se>
 
22
%% @see edoc
 
23
%% @end
 
24
%% =====================================================================
 
25
 
 
26
%% @doc Datatype representation for EDoc.
 
27
 
 
28
-module(edoc_types).
 
29
 
 
30
-export([is_predefined/1, to_ref/1, to_xml/2, to_label/1, arg_names/1,
 
31
         set_arg_names/2]).
 
32
 
 
33
%% @headerfile "edoc_types.hrl"
 
34
 
 
35
-include("edoc_types.hrl").
 
36
-include("xmerl.hrl").
 
37
 
 
38
 
 
39
is_predefined(any) -> true;
 
40
is_predefined(atom) -> true;
 
41
is_predefined(binary) -> true;
 
42
is_predefined(bool) -> true;
 
43
is_predefined(char) -> true;
 
44
is_predefined(cons) -> true;
 
45
is_predefined(deep_string) -> true;
 
46
is_predefined(float) -> true;
 
47
is_predefined(function) -> true;
 
48
is_predefined(integer) -> true;
 
49
is_predefined(list) -> true;
 
50
is_predefined(nil) -> true;
 
51
is_predefined(none) -> true;
 
52
is_predefined(number) -> true;
 
53
is_predefined(pid) -> true;
 
54
is_predefined(port) -> true;
 
55
is_predefined(reference) -> true;
 
56
is_predefined(string) -> true;
 
57
is_predefined(term) -> true;
 
58
is_predefined(tuple) -> true;
 
59
is_predefined(_) -> false.
 
60
 
 
61
to_ref(#t_typedef{name = N}) ->
 
62
    to_ref(N);
 
63
to_ref(#t_def{name = N}) ->
 
64
    to_ref(N);
 
65
to_ref(#t_type{name = N}) ->
 
66
    to_ref(N);
 
67
to_ref(#t_name{module = [], name = N}) ->
 
68
    edoc_refs:type(N);
 
69
to_ref(#t_name{app = [], module = M, name = N}) ->
 
70
    edoc_refs:type(M, N);
 
71
to_ref(#t_name{app = A, module = M, name = N}) ->
 
72
    edoc_refs:type(A, M, N).
 
73
 
 
74
to_label(N) ->
 
75
    edoc_refs:to_label(to_ref(N)).
 
76
 
 
77
get_uri(Name, Env) ->
 
78
    edoc_refs:get_uri(to_ref(Name), Env).
 
79
 
 
80
to_xml(#t_var{name = N}, _Env) ->
 
81
    {typevar, [{name, atom_to_list(N)}], []};
 
82
to_xml(#t_name{module = [], name = N}, _Env) ->
 
83
    {erlangName, [{name, atom_to_list(N)}], []};
 
84
to_xml(#t_name{app = [], module = M, name = N}, _Env) ->
 
85
    {erlangName, [{module, atom_to_list(M)},
 
86
                  {name, atom_to_list(N)}], []};
 
87
to_xml(#t_name{app = A, module = M, name = N}, _Env) ->
 
88
    {erlangName, [{app, atom_to_list(A)},
 
89
                  {module, atom_to_list(M)},
 
90
                  {name, atom_to_list(N)}], []};
 
91
to_xml(#t_type{name = N, args = As}, Env) ->
 
92
    Predef = case N of
 
93
                 #t_name{module = [], name = T} ->
 
94
                     is_predefined(T);
 
95
                 _ ->
 
96
                     false
 
97
             end,
 
98
    HRef = case Predef of
 
99
               true -> [];
 
100
               false -> [{href, get_uri(N, Env)}]
 
101
           end,
 
102
    {abstype, HRef, [to_xml(N, Env) | map(fun wrap_utype/2, As, Env)]};
 
103
to_xml(#t_fun{args = As, range = T}, Env) ->
 
104
    {'fun', [{argtypes, map(fun wrap_utype/2, As, Env)},
 
105
             wrap_utype(T, Env)]};
 
106
to_xml(#t_tuple{types = Ts}, Env) ->
 
107
    {tuple, map(fun wrap_utype/2, Ts, Env)};
 
108
to_xml(#t_list{type = T}, Env) ->
 
109
    {list, [wrap_utype(T, Env)]};
 
110
to_xml(#t_nil{}, _Env) ->
 
111
    nil;
 
112
to_xml(#t_atom{val = V}, _Env) ->
 
113
    {atom, [{value, io_lib:write(V)}], []};
 
114
to_xml(#t_integer{val = V}, _Env) ->
 
115
    {integer, [{value, integer_to_list(V)}], []};
 
116
to_xml(#t_float{val = V}, _Env) ->
 
117
    {float, [{value, io_lib:write(V)}], []};
 
118
to_xml(#t_union{types = Ts}, Env) ->
 
119
    {union, map(fun wrap_type/2, Ts, Env)};
 
120
to_xml(#t_record{name = N = #t_atom{}, fields = Fs}, Env) ->
 
121
    {record, [to_xml(N, Env) | map(fun to_xml/2, Fs, Env)]};
 
122
to_xml(#t_field{name = N = #t_atom{}, type = T}, Env) ->
 
123
    {field, [to_xml(N, Env), wrap_type(T, Env)]};
 
124
to_xml(#t_def{name = N = #t_var{}, type = T}, Env) ->
 
125
    {localdef, [to_xml(N, Env), wrap_type(T, Env)]};
 
126
to_xml(#t_def{name = N, type = T}, Env) ->
 
127
    {localdef, [{label, to_label(N)}],
 
128
     [to_xml(N, Env), wrap_type(T, Env)]};
 
129
to_xml(#t_spec{name = N, type = T, defs = Ds}, Env) ->
 
130
    {typespec, [to_xml(N, Env), wrap_utype(T, Env)
 
131
                | map(fun to_xml/2, Ds, Env)]};
 
132
to_xml(#t_typedef{name = N, args = As, type = undefined, defs = Ds},
 
133
         Env) ->
 
134
    {typedef, [to_xml(N, Env),
 
135
               {argtypes, map(fun wrap_utype/2, As, Env)}
 
136
               | map(fun to_xml/2, Ds, Env)]};
 
137
to_xml(#t_typedef{name = N, args = As, type = T, defs = Ds}, Env) ->
 
138
    {typedef, [to_xml(N, Env),
 
139
               {argtypes, map(fun wrap_utype/2, As, Env)},
 
140
               wrap_type(T, Env)
 
141
               | map(fun to_xml/2, Ds, Env)]};
 
142
to_xml(#t_throws{type = T, defs = Ds}, Env) ->
 
143
    {throws, [wrap_type(T, Env)
 
144
              | map(fun to_xml/2, Ds, Env)]}.
 
145
 
 
146
wrap_type(T, Env) ->
 
147
    {type, [to_xml(T, Env)]}.
 
148
 
 
149
wrap_utype(T, Env) ->
 
150
    E = to_xml(T, Env),
 
151
    case ?t_ann(T) of
 
152
        [] -> {type, [E]};
 
153
        A -> {type, [{name, atom_to_list(A)}], [E]}
 
154
    end.
 
155
 
 
156
map(F, Xs, Env) ->
 
157
    [F(X, Env) || X <- Xs].
 
158
 
 
159
arg_names(#t_spec{type = #t_fun{args = As}}) ->
 
160
    [arg_name(A) || A <- As].
 
161
 
 
162
arg_name(T) ->
 
163
    case ?t_ann(T) of
 
164
        [] -> '_';
 
165
        N -> N
 
166
    end.
 
167
 
 
168
set_arg_names(#t_spec{type = #t_fun{args = As}=F}=S, As1) ->
 
169
    S#t_spec{type = F#t_fun{args = set_arg_names_1(As, As1)}}.
 
170
 
 
171
set_arg_names_1([A | As], [A1 | As1]) ->
 
172
    [?set_t_ann(A, A1) | set_arg_names_1(As, As1)];
 
173
set_arg_names_1([], []) ->
 
174
    [].