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

« back to all changes in this revision

Viewing changes to lib/syntax_tools/src/igor.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:
117
117
 
118
118
-define(record_name(R), {record, R}).
119
119
 
 
120
%% =====================================================================
120
121
 
121
122
%% Data structure for module information
122
123
 
123
 
-record(module, {name,          % = atom()
124
 
                 vars = none,   % = [atom()] | none
125
 
                 functions,     % = ordset({atom(), int()})
126
 
                 exports,       % = ordset({atom(), int()})
127
 
                                % | ordset({{atom(), int()},
128
 
                                %           term()})
129
 
                 aliases,       % = ordset({{atom(), int()},
130
 
                                %           {atom(),
131
 
                                %            {atom(), int()}}})
132
 
                 attributes,    % = ordset({atom(), term()})
133
 
                 records        % = [{atom(), [{atom(), term()}]}]
 
124
-record(module, {name        :: atom(),
 
125
                 vars = none :: [atom()] | 'none',
 
126
                 functions   :: ordsets:ordset({atom(), arity()}),
 
127
                 exports     :: ordsets:ordset({atom(), arity()})
 
128
                              | ordsets:ordset({{atom(), arity()}, term()}),
 
129
                 aliases     :: ordsets:ordset({{atom(), arity()},
 
130
                                                {atom(), {atom(), arity()}}}),
 
131
                 attributes  :: ordsets:ordset({atom(), term()}),
 
132
                 records     :: [{atom(), [{atom(), term()}]}]
134
133
                }).
135
134
 
136
135
%% The default pretty-printing function.
138
137
default_printer(Tree, Options) ->
139
138
    erl_prettypr:format(Tree, Options).
140
139
 
 
140
%% =====================================================================
 
141
 
 
142
-type option() :: atom() | {atom(), term()}.
 
143
 
 
144
-type attribute()      :: {atom(), term()}.
 
145
-type moduleName()     :: atom().
 
146
-type functionName()   :: {atom(), arity()}.
 
147
-type functionPair()   :: {functionName(), {moduleName(), functionName()}}.
 
148
-type stubDescriptor() :: {moduleName(), [functionPair()], [attribute()]}.
 
149
 
 
150
-type notes() :: 'always' | 'yes' | 'no'.
141
151
 
142
152
%% =====================================================================
143
153
%% @spec parse_transform(Forms::[syntaxTree()], Options::[term()]) ->
169
179
%% @see merge_files/4
170
180
%% @see //compiler/compile:file/2
171
181
 
 
182
-spec parse_transform(erl_syntax:forms(), [option()]) ->
 
183
        [erl_syntax:syntaxTree()].
 
184
 
172
185
parse_transform(Forms, Options) ->
173
186
    M = get_module_info(Forms),
174
187
    Name = M#module.name,
192
205
%% @spec merge(Name::atom(), Files::[filename()]) -> [filename()]
193
206
%% @equiv merge(Name, Files, [])
194
207
 
 
208
-spec merge(atom(), [file:filename()]) -> [file:filename(),...].
 
209
 
195
210
merge(Name, Files) ->
196
211
    merge(Name, Files, []).
197
212
 
251
266
%%     <dd>Specifies the file name suffix to be used when a backup file
252
267
%%     is created; the default value is `".bak"'.</dd>
253
268
%%
254
 
%%   <dt>`{backups, bool()}'</dt>
 
269
%%   <dt>`{backups, boolean()}'</dt>
255
270
%%
256
271
%%     <dd>If the value is `true', existing files will be
257
272
%%     renamed before new files are opened for writing. The new names
271
286
%%     resulting source code is to be written. By default, this is the
272
287
%%     same as the `Name' argument.</dd>
273
288
%%
274
 
%%   <dt>`{preprocess, bool()}'</dt>
 
289
%%   <dt>`{preprocess, boolean()}'</dt>
275
290
%%
276
291
%%     <dd>If the value is `true', preprocessing will be done
277
292
%%     when reading the source code. See `merge_files/4' for
294
309
%%     stub module files are written. The default value is
295
310
%%     `"stubs"'.</dd>
296
311
%%
297
 
%%   <dt>`{stubs, bool()}'</dt>
 
312
%%   <dt>`{stubs, boolean()}'</dt>
298
313
%%
299
314
%%     <dd>If the value is `true', stub module files will be
300
315
%%     automatically generated for all exported modules that do not have
324
339
         {suffix, ?DEFAULT_SUFFIX},
325
340
         {verbose, false}]).
326
341
 
 
342
-spec merge(atom(), [file:filename()], [option()]) -> [file:filename(),...].
 
343
 
327
344
merge(Name, Files, Opts) ->
328
345
    Opts1 = Opts ++ ?DEFAULT_MERGE_OPTS,
329
346
    {Tree, Stubs} = merge_files(Name, Files, Opts1),
339
356
%%           {syntaxTree(), [stubDescriptor()]}
340
357
%% @equiv merge_files(Name, [], Files, Options)
341
358
 
 
359
-spec merge_files(atom(), [file:filename()], [option()]) ->
 
360
        {erl_syntax:syntaxTree(), [stubDescriptor()]}.
 
361
 
342
362
merge_files(Name, Files, Options) ->
343
363
    merge_files(Name, [], Files, Options).
344
364
 
380
400
%%
381
401
%% Options:
382
402
%% <dl>
383
 
%%   <dt>`{comments, bool()}'</dt>
 
403
%%   <dt>`{comments, boolean()}'</dt>
384
404
%%
385
405
%%     <dd>If the value is `true', source code comments in
386
406
%%     the original files will be preserved in the output. The default
409
429
%%     Erlang preprocessor, if used (cf. the `preprocess'
410
430
%%     option). The default value is the empty list.</dd>
411
431
%%
412
 
%%   <dt>`{preprocess, bool()}'</dt>
 
432
%%   <dt>`{preprocess, boolean()}'</dt>
413
433
%%
414
434
%%     <dd>If the value is `false', Igor will read source
415
435
%%     files without passing them through the Erlang preprocessor
438
458
%% @see //stdlib/filename:find_src/2
439
459
%% @see epp_dodger
440
460
 
 
461
-spec merge_files(atom(), erl_syntax:forms(), [file:filename()], [option()]) ->
 
462
        {erl_syntax:syntaxTree(), [stubDescriptor()]}.
 
463
 
441
464
merge_files(_, _Trees, [], _) ->
442
465
    report_error("no files to merge."),
443
466
    exit(badarg);
457
480
%%
458
481
%%     Forms = syntaxTree() | [syntaxTree()]
459
482
%%
460
 
%% @type stubDescriptor() = [{ModuleName, Functions, [Attribute]}]
 
483
%% @type stubDescriptor() = {ModuleName, Functions, [Attribute]}
461
484
%%          ModuleName = atom()
462
485
%%          Functions = [{FunctionName, {ModuleName, FunctionName}}]
463
486
%%          FunctionName = {atom(), integer()}
512
535
%%     `Sources' will be exported. The default value is the
513
536
%%     empty list.</dd>
514
537
%%
515
 
%%   <dt>`{export_all, bool()}'</dt>
 
538
%%   <dt>`{export_all, boolean()}'</dt>
516
539
%%
517
540
%%     <dd>If the value is `true', this is equivalent to
518
541
%%     listing all of the input modules in the `export'
532
555
%%     they will be handled as in the `comment' case. The
533
556
%%     default value is `no'.</dd>
534
557
%%
535
 
%% <dt>`{no_banner, bool()}'</dt>
 
558
%% <dt>`{no_banner, boolean()}'</dt>
536
559
%%
537
560
%%     <dd>If the value is `true', no banner comment will be
538
561
%%     added at the top of the resulting module, even if the target
541
564
%%     code is at the top of the output. The default value is
542
565
%%     `false'.</dd>
543
566
%%
544
 
%% <dt>`{no_headers, bool()}'</dt>
 
567
%% <dt>`{no_headers, boolean()}'</dt>
545
568
%%
546
569
%%     <dd>If the value is `true', no header comments will be
547
570
%%     added to the resulting module at the beginning of each section of
550
573
%%     normally added whenever more than two or more modules are
551
574
%%     merged.</dd>
552
575
%%
553
 
%% <dt>`{no_imports, bool()}'</dt>
 
576
%% <dt>`{no_imports, boolean()}'</dt>
554
577
%%
555
578
%%     <dd>If the value is `true', all
556
579
%%     `-import(...)' declarations in the original code will
599
622
%%     regarded as "static", regardless of the value of this option. By
600
623
%%     default, all involved modules are assumed to be static.</dd>
601
624
%%
602
 
%% <dt>`{tidy, bool()}'</dt>
 
625
%% <dt>`{tidy, boolean()}'</dt>
603
626
%%
604
627
%%     <dd>If the value is `true', the resulting code will be
605
628
%%     processed using the `erl_tidy' module, which removes
607
630
%%     `erl_tidy:module/2' for additional options.) The
608
631
%%     default value is `true'.</dd>
609
632
%%
610
 
%% <dt>`{verbose, bool()}'</dt>
 
633
%% <dt>`{verbose, boolean()}'</dt>
611
634
%%
612
635
%%     <dd>If the value is `true', progress messages will be
613
636
%%     output while the program is running; the default value is
659
682
 
660
683
%% Data structure for merging environment.
661
684
 
662
 
-record(merge, {target,         % = atom()
663
 
                sources,        % = ordset(atom())
664
 
                export,         % = ordset(atom())
665
 
                static,         % = ordset(atom())
666
 
                safe,           % = ordset(atom())
667
 
                preserved,      % = bool()
668
 
                no_headers,     % = bool()
669
 
                notes,          % = bool()
670
 
                redirect,       % = dict(atom(), atom())
671
 
                no_imports,     % = ordset(atom())
672
 
                options         % = [term()]
 
685
-record(merge, {target     :: atom(),
 
686
                sources    :: ordsets:ordset(atom()),
 
687
                export     :: ordsets:ordset(atom()),
 
688
                static     :: ordsets:ordset(atom()),
 
689
                safe       :: ordsets:ordset(atom()),
 
690
                preserved  :: boolean(),
 
691
                no_headers :: boolean(),
 
692
                notes      :: notes(),
 
693
                redirect   :: dict(),   % = dict(atom(), atom())
 
694
                no_imports :: ordsets:ordset(atom()),
 
695
                options    :: [option()]
673
696
               }).
674
697
 
 
698
-spec merge_sources(atom(), [erl_syntax:forms()], [option()]) ->
 
699
        {erl_syntax:syntaxTree(), [stubDescriptor()]}.
 
700
 
675
701
merge_sources(Name, Sources, Opts) ->
676
702
    %% Prepare the options and the inputs.
677
703
    Opts1 = Opts ++ [{export_all, false},
696
722
 
697
723
%% Data structure for keeping state during transformation.
698
724
 
699
 
-record(state, {export}).
 
725
-record(state, {export :: set()}).
700
726
 
701
727
state__add_export(Name, Arity, S) ->
702
728
    S#state{export = sets:add_element({Name, Arity},
752
778
    %% however not "safe" by default. If no modules are explicitly
753
779
    %% specified as static, it is assumed that *all* are static.
754
780
    Static0 = ordsets:from_list(proplists:append_values(static, Opts)),
755
 
    case proplists:is_defined(static, Opts) of
756
 
        false ->
757
 
            Static = All;
758
 
        true ->
759
 
            Static = ordsets:add_element(Name, Static0)
760
 
    end,
 
781
    Static = case proplists:is_defined(static, Opts) of
 
782
                 false ->
 
783
                     All;
 
784
                 true ->
 
785
                     ordsets:add_element(Name, Static0)
 
786
             end,
761
787
    check_module_names(Static, All, "declared 'static'"),
762
788
    verbose("static modules: ~p.", [Static], Opts),
763
789
 
776
802
    verbose("safe modules: ~p.", [Safe], Opts),
777
803
 
778
804
    Preserved = (ordsets:is_element(Name, Sources)
779
 
                 and ordsets:is_element(Name, Export))
780
 
        or proplists:get_bool(no_banner, Opts),
 
805
                 andalso ordsets:is_element(Name, Export))
 
806
        orelse proplists:get_bool(no_banner, Opts),
781
807
    NoHeaders = proplists:get_bool(no_headers, Opts),
782
808
    Notes = proplists:get_value(notes, Opts, always),
783
809
    Rs = proplists:append_values(redirect, Opts),
981
1007
 
982
1008
make_stubs_1([M | Ms], Renaming, Env) ->
983
1009
    Name = M#module.name,
984
 
    if Name /= Env#merge.target ->
 
1010
    if Name =/= Env#merge.target ->
985
1011
            case ordsets:is_element(Name, Env#merge.export) of
986
1012
                true ->
987
1013
                    [make_stub(M, Renaming(Name), Env)
1005
1031
%% Removing and/or out-commenting program forms. The returned form
1006
1032
%% sequence tree is not necessarily flat.
1007
1033
 
1008
 
-record(filter, {records, file_attributes, attributes}).
 
1034
-type atts()      :: 'delete' | 'kill'.
 
1035
-type file_atts() :: 'delete' | 'keep' | 'kill'.
 
1036
 
 
1037
-record(filter, {records         :: set(),
 
1038
                 file_attributes :: file_atts(),
 
1039
                 attributes      :: atts()}).
1009
1040
 
1010
1041
filter_forms(Tree, Env) ->
1011
1042
    Forms = erl_syntax:form_list_elements(
1098
1129
kill_form(F) ->
1099
1130
    F1 = erl_syntax:set_precomments(F, []),
1100
1131
    F2 = erl_syntax_lib:to_comment(F1, ?KILL_PREFIX),
1101
 
    erl_syntax:set_precomments(F2,
1102
 
                               erl_syntax:get_precomments(F)).
 
1132
    erl_syntax:set_precomments(F2, erl_syntax:get_precomments(F)).
1103
1133
 
1104
1134
 
1105
1135
%% ---------------------------------------------------------------------
1138
1168
        [] ->
1139
1169
            ok;
1140
1170
        Fs ->
1141
 
            report_warning("interface functions renamed:\n\t~p.",
1142
 
                           [Fs])
 
1171
            report_warning("interface functions renamed:\n\t~p.", [Fs])
1143
1172
    end,
1144
1173
    {M4, Acc2} = merge_namespaces_1(M2, Acc1),
1145
1174
    Ms = M3 ++ M4,
1548
1577
%% ---------------------------------------------------------------------
1549
1578
%% Merging the source code.
1550
1579
 
 
1580
-type map_fun() :: fun(({atom(), integer()}) -> {atom(), integer()}).
 
1581
 
1551
1582
%% Data structure for code transformation environment.
1552
1583
 
1553
 
-record(code, {module,          % = atom()
1554
 
               target,          % = atom()
1555
 
               sources,         % = ordset(atom())
1556
 
               static,          % = ordset(atom())
1557
 
               safe,            % = ordset(atom())
1558
 
               preserved,       % = bool()
1559
 
               no_headers,      % = bool()
1560
 
               notes,           % = bool()
1561
 
               map,             % = ({atom(), int()}) -> {atom(), int()}
1562
 
               renaming,        % = (atom()) -> ({atom(), int()}) ->
1563
 
                                %               {atom(), int()}
1564
 
               expand,          % = dict({atom(), int()},
1565
 
                                %      {atom(), {atom(), int()}})
1566
 
               redirect         % = dict(atom(), atom())
 
1584
-record(code, {module     :: atom(),
 
1585
               target     :: atom(),
 
1586
               sources    :: set(),     % set(atom()),
 
1587
               static     :: set(),     % set(atom()),
 
1588
               safe       :: set(),     % set(atom()),
 
1589
               preserved  :: boolean(),
 
1590
               no_headers :: boolean(),
 
1591
               notes      :: notes(),
 
1592
               map        :: map_fun(),
 
1593
               renaming   :: fun((atom()) -> map_fun()),
 
1594
               expand     :: dict(),    % = dict({atom(), integer()},
 
1595
                                        %      {atom(), {atom(), integer()}})
 
1596
               redirect   :: dict()     % = dict(atom(), atom())
1567
1597
              }).
1568
1598
 
1569
1599
%% `Trees' must be a list of syntax trees of type `form_list'. The
1657
1687
 
1658
1688
section_header(Name, Tree, Env) ->
1659
1689
    N = sets:size(Env#code.sources),
1660
 
    if N > 1, Name /= Env#code.target, Env#code.notes /= no,
1661
 
       Env#code.no_headers /= true ->
 
1690
    if N > 1, Name =/= Env#code.target, Env#code.notes =/= no,
 
1691
       Env#code.no_headers =/= true ->
1662
1692
            Text = io_lib:fwrite("The following code stems "
1663
1693
                                 "from module `~w'.", [Name]),
1664
1694
            Header = comment([?COMMENT_BAR, "",
2292
2322
%% Options:
2293
2323
%% <dl>
2294
2324
%%   <dt>`{backup_suffix, string()}'</dt>
2295
 
%%   <dt>`{backups, bool()}'</dt>
 
2325
%%   <dt>`{backups, boolean()}'</dt>
2296
2326
%%   <dt>`{printer, Function}'</dt>
2297
2327
%%   <dt>`{stub_dir, filename()}'</dt>
2298
2328
%%   <dt>`{suffix, string()}'</dt>
2299
 
%%   <dt>`{verbose, bool()}'</dt>
 
2329
%%   <dt>`{verbose, boolean()}'</dt>
2300
2330
%% </dl>
2301
2331
%% 
2302
2332
%% See `merge/3' for details on these options.
2304
2334
%% @see merge/3
2305
2335
%% @see merge_sources/3
2306
2336
 
 
2337
-spec create_stubs([stubDescriptor()], [option()]) -> [string()].
 
2338
 
2307
2339
create_stubs(Stubs, Opts) ->
2308
2340
    Opts1 = Opts ++ ?DEFAULT_MERGE_OPTS,
2309
2341
    lists:foldl(fun (S, Fs) ->
2365
2397
 
2366
2398
 
2367
2399
%% =====================================================================
 
2400
 
 
2401
-type renamings() :: [{atom(), atom()}].
 
2402
 
 
2403
%% =====================================================================
2368
2404
%% @spec rename(Files::[filename()], Renamings) -> [string()]
2369
2405
%% @equiv rename(Files, Renamings, [])
2370
2406
 
 
2407
-spec rename([file:filename()], renamings()) -> [string()].
 
2408
 
2371
2409
rename(Files, Renamings) ->
2372
2410
    rename(Files, Renamings, []).
2373
2411
 
2408
2446
%% Options:
2409
2447
%% <dl>
2410
2448
%%   <dt>`{backup_suffix, string()}'</dt>
2411
 
%%   <dt>`{backups, bool()}'</dt>
 
2449
%%   <dt>`{backups, boolean()}'</dt>
2412
2450
%%   <dt>`{printer, Function}'</dt>
2413
 
%%   <dt>`{stubs, bool()}'</dt>
 
2451
%%   <dt>`{stubs, boolean()}'</dt>
2414
2452
%%   <dt>`{suffix, string()}'</dt>
2415
2453
%% </dl>
2416
2454
%% See `merge/3' for details on these options.
2417
2455
%%
2418
2456
%% <dl>
2419
 
%%   <dt>`{comments, bool()}'</dt>
2420
 
%%   <dt>`{preprocess, bool()}'</dt>
 
2457
%%   <dt>`{comments, boolean()}'</dt>
 
2458
%%   <dt>`{preprocess, boolean()}'</dt>
2421
2459
%% </dl>
2422
2460
%% See `merge_files/4' for details on these options.
2423
2461
%%
2424
2462
%% <dl>
2425
 
%%   <dt>`{no_banner, bool()}'</dt>
 
2463
%%   <dt>`{no_banner, boolean()}'</dt>
2426
2464
%% </dl>
2427
2465
%% For the `rename' function, this option is
2428
2466
%% `true' by default. See `merge_sources/3' for
2429
2467
%% details.
2430
2468
%%
2431
2469
%% <dl>
2432
 
%%   <dt>`{tidy, bool()}'</dt>
 
2470
%%   <dt>`{tidy, boolean()}'</dt>
2433
2471
%% </dl>
2434
2472
%% For the `rename' function, this option is
2435
2473
%% `false' by default. See `merge_sources/3' for
2436
2474
%% details.
2437
2475
%%
2438
2476
%% <dl>
2439
 
%%   <dt>`{no_headers, bool()}'</dt>
 
2477
%%   <dt>`{no_headers, boolean()}'</dt>
2440
2478
%%   <dt>`{stub_dir, filename()}'</dt>
2441
2479
%% </dl>
2442
2480
%% These options are preset by the `rename' function and
2448
2486
%% @see merge_sources/3
2449
2487
%% @see merge_files/4
2450
2488
 
 
2489
-spec rename([file:filename()], renamings(), [term()]) -> [string()].
 
2490
 
2451
2491
rename(Files, Renamings, Opts) ->
2452
2492
    Dict = case is_atom_map(Renamings) of
2453
2493
               true ->
2886
2926
                         [erl_syntax:abstract(Term)]).
2887
2927
 
2888
2928
is_auto_import({F, A}) ->
2889
 
    erl_internal:bif(F, A);
2890
 
is_auto_import(_) ->
2891
 
    false.
 
2929
    erl_internal:bif(F, A).
2892
2930
 
2893
2931
timestamp() ->
2894
2932
    {{Yr, Mth, Dy}, {Hr, Mt, Sc}} = erlang:localtime(),