~rdoering/ubuntu/intrepid/erlang/fix-535090

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Soren Hansen
  • Date: 2007-05-01 16:57:10 UTC
  • mfrom: (1.1.9 upstream)
  • Revision ID: james.westby@ubuntu.com-20070501165710-2sapk0hp2gf3o0ip
Tags: 1:11.b.4-2ubuntu1
* Merge with Debian Unstable. Remaining changes:
  - Add -fno-stack-protector to fix broken crypto_drv.
* DebianMaintainerField update.

Show diffs side-by-side

added added

removed removed

Lines of Context:
32
32
 
33
33
-include("edoc.hrl").
34
34
 
35
 
%% @TODO report multiple definitions of the same type in the same module.
36
 
%% @TODO check that variables in @equiv are found in the signature
37
 
%% @TODO copy types from target (if missing) when using @equiv
 
35
%% TODO: report multiple definitions of the same type in the same module.
 
36
%% TODO: check that variables in @equiv are found in the signature
 
37
%% TODO: copy types from target (if missing) when using @equiv
38
38
 
39
39
%% <!ELEMENT module (description?, author*, copyright?, version?,
40
40
%%                   since?, deprecated?, see*, reference*, todo?,
175
175
                {arity, integer_to_list(A)}],
176
176
     []}.
177
177
 
178
 
%% <!ELEMENT function (args, typespec?, throws?, equiv?, description?,
179
 
%%                     since?, deprecated?, see*, todo?)>
 
178
%% <!ELEMENT function (args, typespec?, returns?, throws?, equiv?,
 
179
%%                     description?, since?, deprecated?, see*, todo?)>
180
180
%% <!ATTLIST function
181
181
%%   name CDATA #REQUIRED
182
182
%%   arity CDATA #REQUIRED
183
183
%%   exported NMTOKEN(yes | no) #REQUIRED
184
184
%%   label CDATA #IMPLIED>
185
185
%% <!ELEMENT args (arg*)>
186
 
%% <!ELEMENT arg description?>
187
 
%% <!ATTLIST arg name CDATA #REQUIRED>
188
 
%% <!ELEMENT equiv (expr, see?)>
 
186
%% <!ELEMENT arg (argName, description?)>
 
187
%% <!ELEMENT argName (#PCDATA)>
 
188
%% <!ELEMENT returns (description)>
 
189
%% <!ELEMENT throws (type, localdef*)>
189
190
%% <!ELEMENT equiv (expr, see?)>
190
191
%% <!ELEMENT expr (#PCDATA)>
191
192
 
192
193
function({N, A}, As, Export, Ts, Env, Opts) ->
193
 
    {As1, Spec} = signature(Ts, As, Env),
 
194
    {Args, Ret, Spec} = signature(Ts, As, Env),
194
195
    {function, [{name, atom_to_list(N)},
195
196
                {arity, integer_to_list(A)},
196
197
                {exported, case Export of
198
199
                               false -> "no"
199
200
                           end},
200
201
                {label, edoc_refs:to_label(edoc_refs:function(N, A))}],
201
 
     [{args, [{arg, [{argName, [atom_to_list(A)]}]} || A <- As1]}]
 
202
     [{args, [{arg, [{argName, [atom_to_list(A)]}] ++ description(D)}
 
203
              || {A, D} <- Args]}]
202
204
     ++ Spec
 
205
     ++ case Ret of
 
206
            [] -> [];
 
207
            _ -> [{returns, description(Ret)}]
 
208
        end
203
209
     ++ get_throws(Ts, Env)
204
210
     ++ get_equiv(Ts, Env)
205
211
     ++ get_doc(Ts)
264
270
%%       Spec = module | {F,A} | {F,A,Details}}
265
271
%%       Details = next_version | next_major_release | eventually
266
272
%%                 (EXTENSION: | string() | {M1,F1,A1}}
267
 
%% @TODO use info from '-deprecated(...)' (xref-)declarations.
 
273
%% TODO: use info from '-deprecated(...)' (xref-)declarations.
268
274
 
269
275
get_deprecated(Ts) ->
270
276
    case get_tags(deprecated, Ts) of
376
382
    case get_tags(spec, Ts) of
377
383
        [T] ->
378
384
            Spec = T#tag.data,
 
385
            R = merge_returns(Spec, Ts),
379
386
            As0 = edoc_types:arg_names(Spec),
380
 
            As1 = merge_argnames(As0, As),  % choose spec before code
381
 
            Spec1 = edoc_types:set_arg_names(Spec, As1),
382
 
            {As1, [edoc_types:to_xml(Spec1, Env)]};
 
387
            Ds0 = edoc_types:arg_descs(Spec),
 
388
            %% choose names in spec before names in code
 
389
            P = dict:from_list(params(Ts)),
 
390
            As1 = merge_args(As0, As, Ds0, P),
 
391
            %% check_params(As1, P),
 
392
            Spec1 = edoc_types:set_arg_names(Spec, [A || {A,_} <- As1]),
 
393
            {As1, R, [edoc_types:to_xml(Spec1, Env)]};
383
394
        [] ->
384
395
            S = sets:new(),
385
 
            {fix_argnames(As, S, 1), []}
386
 
    end.
387
 
 
388
 
%% Names are chosen from the first list if possible.
389
 
 
390
 
merge_argnames(As, As1) ->
391
 
    merge_argnames(As, As1, sets:new(), 1).
392
 
 
393
 
merge_argnames(['_' | As], ['_' | As1], S, N) ->
394
 
    A = make_name(N, S),
395
 
    [A | merge_argnames(As, As1, sets:add_element(A, S), N + 1)];
396
 
merge_argnames(['_' | As], [A | As1], S, N) ->
397
 
    [A | merge_argnames(As, As1, sets:add_element(A, S), N + 1)];
398
 
merge_argnames([A | As], [_ | As1], S, N) ->
399
 
    [A | merge_argnames(As, As1, sets:add_element(A, S), N + 1)];
400
 
merge_argnames([], [], _S, _N) ->
401
 
    [].
 
396
            {fix_argnames(As, S, 1), [], []}
 
397
    end.
 
398
 
 
399
params(Ts) ->
 
400
    [T#tag.data || T <- get_tags(param, Ts)].
 
401
 
 
402
%% check_params(As, P) ->
 
403
%%     case dict:keys(P) -- [N || {N,_} <- As] of
 
404
%%      [] -> ok;
 
405
%%      Ps -> error  %% TODO: report @param declarations with no match
 
406
%%     end.
 
407
 
 
408
merge_returns(Spec, Ts) ->
 
409
    case get_tags(return, Ts) of
 
410
        [] ->
 
411
            case edoc_types:range_desc(Spec) of
 
412
                "" -> [];
 
413
                Txt -> [Txt]
 
414
            end;
 
415
        [T] -> T#tag.data
 
416
    end.
 
417
 
 
418
%% Names are chosen from the first list (the specification) if possible.
 
419
%% Descriptions specified with @param (in P dict) override descriptions
 
420
%% from the spec (in Ds).
 
421
 
 
422
merge_args(As, As1, Ds, P) ->
 
423
    merge_args(As, As1, Ds, [], P, sets:new(), 1).
 
424
 
 
425
merge_args(['_' | As], ['_' | As1], [D | Ds], Rs, P, S, N) ->
 
426
    merge_args(As, As1, Ds, Rs, P, S, N, make_name(N, S), D);
 
427
merge_args(['_' | As], [A | As1], [D | Ds], Rs, P, S, N) ->
 
428
    merge_args(As, As1, Ds, Rs, P, S, N, A, D);
 
429
merge_args([A | As], [_ | As1], [D | Ds], Rs, P, S, N) ->
 
430
    merge_args(As, As1, Ds, Rs, P, S, N, A, D);
 
431
merge_args([], [], [], Rs, _P, _S, _N) ->
 
432
    lists:reverse(Rs).
 
433
 
 
434
merge_args(As, As1, Ds, Rs, P, S, N, A, D0) ->
 
435
    D = case dict:find(A, P) of
 
436
            {ok, D1} -> D1;
 
437
            error when D0 == [] -> [];  % no description
 
438
            error -> [D0]  % a simple-xml text element
 
439
        end,
 
440
    merge_args(As, As1, Ds, [{A, D} | Rs], P,
 
441
               sets:add_element(A, S), N + 1).
402
442
 
403
443
fix_argnames(['_' | As], S, N) ->
404
444
    A = make_name(N, S),