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

« back to all changes in this revision

Viewing changes to lib/docbuilder/src/docb_main.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:
34
34
%% Parses the source file File and transforms the result to html,
35
35
%% latex and/or man page format.
36
36
process(File, Opts) ->
 
37
    
 
38
    SrcType = docb_util:lookup_option(src_type, Opts),
37
39
 
38
 
    File1 = File ++ ".tmpconv",
39
 
    os:cmd("sed -e 's/xi:include[ \t]*href/include file/g' -e 's/xmlns:xi=\"http:\\/\\/www.w3.org\\/2001\\/XInclude\"//g' < " ++ 
40
 
           File ++ ".xml > " ++ File1 ++ ".xml"), %LATH
 
40
    File1 = 
 
41
        case SrcType of
 
42
            ".xml" ->
 
43
                FileTmp = File ++ ".tmpconv",
 
44
                os:cmd("sed -e 's/xi:include[ \t]*href/include file/g' -e 's/xmlns:xi=\"http:\\/\\/www.w3.org\\/2001\\/XInclude\"//g' < " ++ 
 
45
                       File ++ ".xml > " ++ FileTmp ++ ".xml"),
 
46
                FileTmp;
 
47
            ".sgml"  ->
 
48
                File
 
49
        end,            
41
50
    
42
51
    case parse1(File1, Opts) of
43
52
        errors ->
44
 
            file:delete(File1 ++ ".xml"),
 
53
            delete_tmp_file(SrcType, File1),
45
54
            errors;
46
55
        {ok, Tree} ->
47
56
            From = element(1, Tree),
55
64
 
56
65
            %% If no target format is specified, assume HTML:
57
66
            Tos = if
58
 
                      Tos0==[] -> [html];
 
67
                      Tos0 =:= [] -> [html];
59
68
                      true -> Tos0
60
69
                  end,
61
70
 
62
71
            Result = [transform(From, To, Opts, File, Tree)||To <- Tos], 
63
72
            case lists:member(transformation_error,Result) of 
64
73
                true ->         
65
 
                    file:delete(File1 ++ ".xml"),
 
74
                    delete_tmp_file(SrcType, File1),
66
75
                    errors;
67
76
                _ -> 
68
 
                    file:delete(File1 ++ ".xml"),
 
77
                    delete_tmp_file(SrcType, File1),
69
78
                    ok
70
79
            end
71
80
    
72
81
    end.
73
82
 
 
83
 
 
84
delete_tmp_file(".xml", File) ->
 
85
    file:delete(File ++ ".xml");
 
86
delete_tmp_file(_, _) ->
 
87
    ok.
 
88
 
74
89
%%----------------------------------------------------------------------
75
90
 
76
91
%% parse(File, Opts) -> {ok, Tree} | errors
327
342
verify({pcdata, Optional, _}, Path, Level) ->
328
343
    verify_optional(Optional, Path, Level);
329
344
verify({Tag, Optional, Args}, Path, Level) when is_list(Args) ->
330
 
    case verify_optional(Optional, Path, Level) of
331
 
        true ->
332
 
            verify_list(Args, [Tag|Path], Level);
333
 
        false ->
334
 
            false
335
 
    end;
 
345
    verify_optional(Optional, Path, Level)
 
346
        andalso verify_list(Args, [Tag|Path], Level);
336
347
verify(Other, Path, Level) ->
337
348
    verify_error(Other, Path, Level).
338
349
 
342
353
    false.
343
354
 
344
355
verify_list([H|T], Path, Level) ->
345
 
    case verify(H, Path, Level) of
346
 
        true ->
347
 
            verify_list(T, Path, Level +1);
348
 
        false ->
349
 
            false
350
 
    end;
 
356
    verify(H, Path, Level) andalso verify_list(T, Path, Level + 1);
351
357
verify_list([], _, _) ->
352
358
    true.
353
359
 
419
425
%% Actual transformation of tree structure to desired format.
420
426
transform(From, To, Opts, File, Tree) ->
421
427
    Filter = if
422
 
                 To==html; To==kwic ->
 
428
                 To =:= html; To =:= kwic ->
423
429
                     list_to_atom("docb_tr_" ++ atom_to_list(From) ++
424
430
                                  [$2|atom_to_list(To)]);
425
431
                 true ->
427
433
                                  [$2|atom_to_list(To)])
428
434
             end,
429
435
 
430
 
    case catch apply(Filter, transform, [File, Tree, Opts]) of
 
436
    case catch Filter:transform(File, Tree, Opts) of
431
437
 
432
438
        %% R5C
433
439
        {'EXIT', {undef, [{Filter, transform, [File, Tree, Opts]}|_]}}->
459
465
finish_transform(Tree, File, Opts, Filter) ->
460
466
    {Str, NewOpts} = pp(Tree, [], 1, Filter, Opts),
461
467
    Extension =
462
 
        case catch apply(Filter, extension, [NewOpts]) of
 
468
        case catch Filter:extension(NewOpts) of
463
469
            {'EXIT', _} ->
464
 
                apply(Filter, extension, []);
 
470
                Filter:extension();
465
471
            Others ->
466
472
                Others
467
473
        end,
606
612
        eof ->
607
613
            [];
608
614
        ListOfChars ->
609
 
            lists:append(ListOfChars, include_all(Fd))
 
615
            ListOfChars ++ include_all(Fd)
610
616
    end.
611
617
 
612
618
extract(File, Fd, StartTag, StopTag, State) ->