~ubuntu-branches/ubuntu/lucid/erlang/lucid-proposed

« back to all changes in this revision

Viewing changes to lib/syntax_tools/src/epp_dodger.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-06-11 12:18:07 UTC
  • mfrom: (1.2.2 upstream)
  • Revision ID: james.westby@ubuntu.com-20090611121807-ks7eb4xrt7dsysgx
Tags: 1:13.b.1-dfsg-1
* New upstream release.
* Removed unnecessary dependency of erlang-os-mon on erlang-observer and
  erlang-tools and added missing dependency of erlang-nox on erlang-os-mon
  (closes: #529512).
* Removed a patch to eunit application because the bug was fixed upstream.

Show diffs side-by-side

added added

removed removed

Lines of Context:
176
176
            try Parser(Dev, 1, Options)
177
177
            after ok = file:close(Dev)
178
178
            end;
179
 
        {error, IoErr} ->
180
 
            {error, IoErr}
 
179
        {error, _} = Error ->
 
180
            Error
181
181
    end.
182
182
 
183
183
 
350
350
quick_parse_form(Dev, L0, Options) ->
351
351
    parse_form(Dev, L0, fun quick_parser/2, Options).
352
352
 
353
 
-record(opt, {clever = false}).
 
353
-record(opt, {clever = false :: bool()}).
354
354
 
355
355
parse_form(Dev, L0, Parser, Options) ->
356
356
    NoFail = proplists:get_bool(no_fail, Options),
373
373
                {ok, F} ->
374
374
                    {ok, F, L1}
375
375
            end;
376
 
        {error, IoErr, L1} ->
377
 
            {error, IoErr, L1};
378
 
        {eof, L1} ->
379
 
            {eof, L1}
 
376
        {error, _IoErr, _L1} = Err -> Err;
 
377
        {eof, _L1} = Eof -> Eof
380
378
    end.
381
379
 
382
380
io_error(L, Desc) ->
431
429
quickscan_form([{'-', _L}, {atom, La, endif} | _Ts]) ->
432
430
    kill_form(La);
433
431
quickscan_form([{'-', L}, {'?', _}, {Type, _, _}=N | [{'(', _} | _]=Ts])
434
 
  when Type == atom; Type == var ->
 
432
  when Type =:= atom; Type =:= var ->
435
433
    %% minus, macro and open parenthesis at start of form - assume that
436
434
    %% the macro takes no arguments; e.g. `-?foo(...).'
437
435
    quickscan_macros_1(N, Ts, [{'-', L}]);
438
436
quickscan_form([{'?', _L}, {Type, _, _}=N | [{'(', _} | _]=Ts])
439
 
  when Type == atom; Type == var ->
 
437
  when Type =:= atom; Type =:= var ->
440
438
    %% macro and open parenthesis at start of form - assume that the
441
439
    %% macro takes no arguments (see scan_macros for details)
442
440
    quickscan_macros_1(N, Ts, []);
451
449
    quickscan_macros(Ts, []).
452
450
 
453
451
quickscan_macros([{'?',_}, {Type, _, A} | Ts], [{string, L, S} | As])
454
 
  when Type == atom; Type == var ->
 
452
  when Type =:= atom; Type =:= var ->
455
453
    %% macro after a string literal: change to a single string
456
454
    {_, Ts1} = skip_macro_args(Ts),
457
455
    S1 = S ++ quick_macro_string(A),
458
456
    quickscan_macros(Ts1, [{string, L, S1} | As]);
459
457
quickscan_macros([{'?',_}, {Type, _, _}=N | [{'(',_}|_]=Ts],
460
458
                 [{':',_}|_]=As)
461
 
  when Type == atom; Type == var ->
 
459
  when Type =:= atom; Type =:= var ->
462
460
    %% macro and open parenthesis after colon - check the token
463
461
    %% following the arguments (see scan_macros for details)
464
462
    Ts1 = case skip_macro_args(Ts) of
468
466
          end,
469
467
    quickscan_macros_1(N, Ts1, As);
470
468
quickscan_macros([{'?',_}, {Type, _, _}=N | Ts], As)
471
 
  when Type == atom; Type == var ->
 
469
  when Type =:= atom; Type =:= var ->
472
470
    %% macro with or without arguments
473
471
    {_, Ts1} = skip_macro_args(Ts),
474
472
    quickscan_macros_1(N, Ts1, As);
567
565
    [{atom, La, ?pp_form}, {'(', La}, {')', La}, {'->', La},
568
566
     {atom, La, endif} | scan_macros(Ts, Opt)];
569
567
scan_form([{'-', L}, {'?', L1}, {Type, _, _}=N | [{'(', _} | _]=Ts], Opt)
570
 
  when Type == atom; Type == var ->
 
568
  when Type =:= atom; Type =:= var ->
571
569
    %% minus, macro and open parenthesis at start of form - assume that
572
570
    %% the macro takes no arguments; e.g. `-?foo(...).'
573
571
    macro(L1, N, Ts, [{'-', L}], Opt);
574
572
scan_form([{'?', L}, {Type, _, _}=N | [{'(', _} | _]=Ts], Opt)
575
 
  when Type == atom; Type == var ->
 
573
  when Type =:= atom; Type =:= var ->
576
574
    %% macro and open parenthesis at start of form - assume that the
577
575
    %% macro takes no arguments; probably a function declaration on the
578
576
    %% form `?m(...) -> ...', which will not parse if it is rewritten as
586
584
 
587
585
scan_macros([{'?', _}=M, {Type, _, _}=N | Ts], [{string, L, _}=S | As],
588
586
            #opt{clever = true}=Opt)
589
 
  when Type == atom; Type == var ->
 
587
  when Type =:= atom; Type =:= var ->
590
588
    %% macro after a string literal: be clever and insert ++
591
589
    scan_macros([M, N | Ts], [{'++', L}, S | As], Opt);
592
590
scan_macros([{'?', L}, {Type, _, _}=N | [{'(',_}|_]=Ts],
593
591
            [{':',_}|_]=As, Opt)
594
 
  when Type == atom; Type == var ->
 
592
  when Type =:= atom; Type =:= var ->
595
593
    %% macro and open parentheses after colon - probably a call
596
594
    %% `m:?F(...)' so the argument list might belong to the call, not
597
595
    %% the macro - but it could also be a try-clause pattern
607
605
            macro(L, N, Ts, As, Opt)
608
606
    end;
609
607
scan_macros([{'?', L}, {Type, _, _}=N | [{'(',_}|_]=Ts], As, Opt)
610
 
  when Type == atom; Type == var ->
 
608
  when Type =:= atom; Type =:= var ->
611
609
    %% macro with arguments
612
610
    {Args, Rest} = skip_macro_args(Ts),
613
611
    macro_call(Args, L, N, Rest, As, Opt);
614
612
scan_macros([{'?', L }, {Type, _, _}=N | Ts], As, Opt)
615
 
  when Type == atom; Type == var ->
 
613
  when Type =:= atom; Type =:= var ->
616
614
    %% macro without arguments
617
615
    macro(L, N, Ts, As, Opt);
618
616
scan_macros([T | Ts], As, Opt) ->