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

« back to all changes in this revision

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

  • 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:
16
16
%%
17
17
%% $Id$
18
18
%%
19
 
%% @private
20
19
%% @copyright 2001-2003 Richard Carlsson
21
20
%% @author Richard Carlsson <richardc@it.uu.se>
22
21
%% @see edoc
49
48
%% ---------------------------------------------------------------------
50
49
%% List and string utilities
51
50
 
 
51
%% @private
52
52
timestr({H,M,Sec}) ->
53
53
    lists:flatten(io_lib:fwrite("~2.2.0w:~2.2.0w:~2.2.0w",[H,M,Sec])).
54
54
 
 
55
%% @private
55
56
datestr({Y,M,D}) ->
56
57
    Ms = ["Jan", "Feb", "Mar", "Apr", "May", "Jun", "Jul", "Aug", "Sep",
57
58
          "Oct", "Nov", "Dec"],
58
59
    lists:flatten(io_lib:fwrite("~s ~w ~w",[lists:nth(M, Ms),D,Y])).
59
60
 
 
61
%% @private
60
62
count(X, Xs) ->
61
63
    count(X, Xs, 0).
62
64
 
67
69
count(_X, [], N) ->
68
70
    N.
69
71
 
 
72
%% @private
70
73
lines(Cs) ->
71
74
    lines(Cs, [], []).
72
75
 
77
80
lines([], As, Ls) ->
78
81
    lists:reverse([lists:reverse(As) | Ls]).
79
82
 
 
83
%% @private
80
84
split_at(Cs, K) ->
81
85
    split_at(Cs, K, []).
82
86
 
87
91
split_at([], _K, As) ->
88
92
    {lists:reverse(As), []}.
89
93
 
 
94
%% @private
90
95
split_at_stop(Cs) ->
91
96
    split_at_stop(Cs, []).
92
97
 
103
108
split_at_stop([], As) ->
104
109
    {lists:reverse(As), []}.
105
110
 
 
111
%% @private
106
112
split_at_space(Cs) ->
107
113
    split_at_space(Cs, []).
108
114
 
117
123
split_at_space([], As) ->
118
124
    {lists:reverse(As), []}.
119
125
 
 
126
%% @private
120
127
is_space([$\s | Cs]) -> is_space(Cs);
121
128
is_space([$\t | Cs]) -> is_space(Cs);
122
129
is_space([$\n | Cs]) -> is_space(Cs);
123
130
is_space([_C | _Cs]) -> false;
124
131
is_space([]) -> true.
125
132
 
 
133
%% @private
126
134
strip_space([$\s | Cs]) -> strip_space(Cs);
127
135
strip_space([$\t | Cs]) -> strip_space(Cs);
128
136
strip_space([$\n | Cs]) -> strip_space(Cs);
129
137
strip_space(Cs) -> Cs.
130
138
 
 
139
%% @private
131
140
segment(Es, N) ->
132
141
    segment(Es, [], [], 0, N).
133
142
 
140
149
segment([], As, Cs, _N, _M) ->
141
150
    lists:reverse([lists:reverse(As) | Cs]).
142
151
 
 
152
%% @private
143
153
transpose([]) -> [];
144
154
transpose([[] | Xss]) -> transpose(Xss);
145
155
transpose([[X | Xs] | Xss]) ->
151
161
%% end of the summary sentence only if it is also the last segment in
152
162
%% the list, or is followed by a 'p' or 'br' ("whitespace") element.
153
163
 
 
164
%% @private
154
165
get_first_sentence([#xmlElement{name = p, content = Es} | _]) ->
155
166
    %% Descend into initial paragraph.
156
167
    get_first_sentence_1(Es);
230
241
%% Names must begin with a lowercase letter and contain only
231
242
%% alphanumerics and underscores.
232
243
 
 
244
%% @private
233
245
is_name([C | Cs]) when C >= $a, C =< $z ->
234
246
    is_name_1(Cs);
235
247
is_name([C | Cs]) when C >= $\337, C =< $\377, C =/= $\367 ->
252
264
to_atom(A) when is_atom(A) -> A;
253
265
to_atom(S) when is_list(S) -> list_to_atom(S).
254
266
    
 
267
%% @private
255
268
unique([X | Xs]) -> [X | unique(Xs, X)];
256
269
unique([]) -> [].
257
270
 
267
280
%% content of <a href="overview-summary.html#ftag-equiv">`@equiv'</a>
268
281
%% tags, and strings denoting file names, e.g. in @headerfile. Also used
269
282
%% by {@link edoc_run}.
 
283
%% @private
270
284
 
271
285
parse_expr(S, L) ->
272
286
    case erl_scan:string(S ++ ".", L) of
287
301
%% @doc EDoc "contact information" parsing. This is the type of the
288
302
%% content in e.g.
289
303
%% <a href="overview-summary.html#mtag-author">`@author'</a> tags.
290
 
 
291
 
%% @type info() = #info{name = string(),
292
 
%%                      mail = string(),
293
 
%%                      uri = string()}
294
 
 
295
 
-record(info, {name = "", email = "", uri = ""}).
 
304
%% @private
 
305
 
 
306
%% % @type info() = #info{name  = string(),
 
307
%% %                      email = string(),
 
308
%% %                      uri   = string()}
 
309
 
 
310
-record(info, {name = ""  :: string(),
 
311
               email = "" :: string(),
 
312
               uri = ""   :: string()}).
296
313
 
297
314
parse_contact(S, L) ->
298
315
    I = scan_name(S, L, #info{}, []),
365
382
%%
366
383
%% TODO: general utf-8 encoding for all of Unicode (0-16#10ffff)
367
384
 
 
385
%% @private
368
386
escape_uri([C | Cs]) when C >= $a, C =< $z ->
369
387
    [C | escape_uri(Cs)];
370
388
escape_uri([C | Cs]) when C >= $A, C =< $Z ->
407
425
%% Please note that URI are *not* file names. Don't use the stdlib
408
426
%% 'filename' module for operations on (any parts of) URI.
409
427
 
 
428
%% @private
410
429
join_uri(Base, "") ->
411
430
    Base;
412
431
join_uri("", Path) ->
416
435
 
417
436
%% Check for relative URI; "network paths" ("//...") not included!
418
437
 
 
438
%% @private
419
439
is_relative_uri([$: | _]) ->
420
440
    false;
421
441
is_relative_uri([$/, $/ | _]) ->
431
451
is_relative_uri([]) ->
432
452
    true.
433
453
 
 
454
%% @private
434
455
uri_get("file:///" ++ Path) ->
435
456
    uri_get_file(Path);
436
457
uri_get("file://localhost/" ++ Path) ->
472
493
 
473
494
uri_get_http(URI) ->
474
495
    %% Try using option full_result=false
475
 
    case catch {ok, http:request(get, {URI,[]}, [],
 
496
    case catch {ok, httpc:request(get, {URI,[]}, [],
476
497
                                 [{full_result, false}])} of
477
498
        {'EXIT', _} ->
478
499
            uri_get_http_r10(URI);
482
503
 
483
504
uri_get_http_r10(URI) ->
484
505
    %% Try most general form of request
485
 
    Result = (catch {ok, http:request(get, {URI,[]}, [], [])}),
 
506
    Result = (catch {ok, httpc:request(get, {URI,[]}, [], [])}),
486
507
    uri_get_http_1(Result, URI).
487
508
 
488
509
uri_get_http_1(Result, URI) ->
530
551
    Msg = io_lib:format("cannot access ftp scheme yet: '~s'.", [URI]),
531
552
    {error, Msg}.
532
553
 
 
554
%% @private
533
555
to_label([$\s | Cs]) ->
534
556
    to_label(Cs);
535
557
to_label([$\t | Cs]) ->
562
584
%% ---------------------------------------------------------------------
563
585
%% Files
564
586
 
 
587
%% @private
565
588
filename([C | T]) when is_integer(C), C > 0 ->
566
589
    [C | filename(T)];
567
590
filename([H|T]) ->
574
597
    report("bad filename: `~P'.", [N, 25]),
575
598
    exit(error).
576
599
 
 
600
%% @private
577
601
copy_file(From, To) ->
578
602
    case file:copy(From, To) of
579
603
        {ok, _} -> ok;
598
622
            F("could not read directory '~s': ~s.", [filename(Dir), R1])
599
623
    end.
600
624
 
 
625
%% @private
601
626
simplify_path(P) ->
602
627
    case filename:basename(P) of
603
628
        "." ->
634
659
%%          exit(error)
635
660
%%     end.
636
661
 
 
662
%% @private
637
663
try_subdir(Dir, Subdir) ->
638
664
    D = filename:join(Dir, Subdir),
639
665
    case filelib:is_dir(D) of
646
672
%%
647
673
%% @doc Write the given `Text' to the file named by `Name' in directory
648
674
%% `Dir'. If the target directory does not exist, it will be created.
 
675
%% @private
649
676
 
650
677
write_file(Text, Dir, Name) ->
651
678
    write_file(Text, Dir, Name, '').
655
682
%%        Name::edoc:filename(), Package::atom()|string()) -> ok
656
683
%% @doc Like {@link write_file/3}, but adds path components to the target
657
684
%% directory corresponding to the specified package.
 
685
%% @private
658
686
 
659
687
write_file(Text, Dir, Name, Package) ->
660
688
    Dir1 = filename:join([Dir | packages:split(Package)]),
670
698
            exit(error)
671
699
    end.
672
700
 
 
701
%% @private
673
702
write_info_file(App, Packages, Modules, Dir) ->
674
703
    Ts = [{packages, Packages},
675
704
          {modules, Modules}],
701
730
 
702
731
%% Local file access - don't complain if file does not exist.
703
732
 
 
733
%% @private
704
734
read_info_file(Dir) ->
705
735
    File = filename:join(Dir, ?INFO_FILE),
706
736
    case filelib:is_file(File) of
767
797
%% ---------------------------------------------------------------------
768
798
%% Source files and packages
769
799
 
 
800
%% @private
770
801
find_sources(Path, Opts) ->
771
802
    find_sources(Path, "", Opts).
772
803
 
773
804
%% @doc See {@link edoc:run/3} for a description of the options
774
805
%% `subpackages', `source_suffix' and `exclude_packages'.
 
806
%% @private
775
807
 
776
808
%% NEW-OPTIONS: subpackages, source_suffix, exclude_packages
777
809
%% DEFER-OPTIONS: edoc:run/3
825
857
    is_name(filename:rootname(filename:basename(Name)))
826
858
        andalso filelib:is_dir(filename:join(Dir, Name)).
827
859
 
 
860
%% @private
828
861
find_file([P | Ps], Pkg, Name) ->
829
862
    Dir = filename:join(P, filename:join(packages:split(Pkg))),
830
863
    File = filename:join(Dir, Name),
837
870
find_file([], _Pkg, _Name) ->
838
871
    "".
839
872
 
 
873
%% @private
840
874
find_doc_dirs() ->
841
875
    find_doc_dirs(code:get_path()).
842
876
 
902
936
 
903
937
%% @spec (Options::proplist()) -> edoc_env()
904
938
%% @equiv get_doc_env([], [], [], Opts)
 
939
%% @private
905
940
 
906
941
get_doc_env(Opts) ->
907
942
    get_doc_env([], [], [], Opts).
912
947
%%     Modules = [atom()]
913
948
%%     proplist() = [term()]
914
949
%%
 
950
%% @type proplist() = proplists:property().
915
951
%% @type edoc_env(). Environment information needed by EDoc for
916
952
%% generating references. The data representation is not documented.
917
953
%%
950
986
%% NEW-OPTIONS: doclet
951
987
%% DEFER-OPTIONS: edoc:run/3
952
988
 
 
989
%% @private
953
990
run_doclet(Fun, Opts) ->
954
991
    run_plugin(doclet, ?DEFAULT_DOCLET, Fun, Opts).
955
992
 
959
996
%% NEW-OPTIONS: layout
960
997
%% DEFER-OPTIONS: edoc:layout/2
961
998
 
 
999
%% @private
962
1000
run_layout(Fun, Opts) ->
963
1001
    run_plugin(layout, ?DEFAULT_LAYOUT, Fun, Opts).
964
1002
 
988
1026
%% ---------------------------------------------------------------------
989
1027
%% Error handling
990
1028
 
 
1029
-type line() :: erl_scan:line().
 
1030
-type err()  :: 'eof'
 
1031
              | {'missing', char()}
 
1032
              | {line(), atom(), string()}
 
1033
              | string().
 
1034
 
 
1035
-spec throw_error(err(), line()) -> no_return().
 
1036
 
991
1037
throw_error({missing, C}, L) ->
992
1038
    throw_error({"missing '~c'.", [C]}, L);
993
1039
throw_error(eof, L) ->