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

« back to all changes in this revision

Viewing changes to lib/stdlib/src/epp.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:
58
58
    epp_request(Epp).
59
59
 
60
60
close(Epp) ->
61
 
    epp_request(Epp, close).
 
61
    %% Make sure that close is synchronous as a courtesy to test
 
62
    %% cases that test for resource leaks.
 
63
    Ref = erlang:monitor(process, Epp),
 
64
    R = epp_request(Epp, close),
 
65
    receive {'DOWN',Ref,_,_,_} -> ok end,
 
66
    R.
62
67
 
63
68
scan_erl_form(Epp) ->
64
69
    epp_request(Epp, scan_erl_form).
126
131
    case parse_erl_form(Epp) of
127
132
        {ok,Form} ->
128
133
            case Form of
129
 
                {attribute,La,typed_record,{Record, Val}} ->
 
134
                {attribute,La,record,{Record, Val}} ->
130
135
                    case lists:member(typed_record,Options) of
131
136
                        false ->
132
137
                            [{attribute, La, record,
133
138
                              {Record, normalize_typed_record_fields(Val)}}
134
 
                             | parse_file(Epp, Options)];
 
139
                             |parse_file(Epp, Options)];
135
140
                        true ->
136
 
                            [{attribute, La, record,
137
 
                              {Record, normalize_typed_record_fields(Val)}},
138
 
                            Form | parse_file(Epp, Options)]
 
141
                            [Form|parse_file(Epp, Options)]
139
142
                    end;
140
143
                _ ->
141
144
                    [Form|parse_file(Epp, Options)]
151
154
    [Field|normalize_typed_record_fields(Rest)];
152
155
normalize_typed_record_fields([Field|Rest]) ->
153
156
    [Field|normalize_typed_record_fields(Rest)].
154
 
 
 
157
 
155
158
%% server(StarterPid, FileName, Path, PreDefMacros)
156
159
 
157
160
server(Pid, Name, Path, Pdm) ->
158
161
    process_flag(trap_exit, true),
159
 
    case file:open(Name, read) of
 
162
    case file:open(Name, [read]) of
160
163
        {ok,File} ->
161
164
            Ms0 = predef_macros(Name),
162
165
            case user_predef(Pdm, Ms0) of
223
226
            epp_reply(From, dict:to_list(St#epp.macs)),
224
227
            wait_request(St);
225
228
        {epp_request,From,close} ->
 
229
            file:close(St#epp.file),
226
230
            epp_reply(From, ok),
227
231
            exit(normal);
228
232
        {'EXIT',_,R} ->
529
533
            case catch find_lib_dir(NewName) of
530
534
                {LibDir, Rest} when is_list(LibDir) ->
531
535
                    LibName = filename:join([LibDir | Rest]),
532
 
                    case file:open(LibName, read) of
 
536
                    case file:open(LibName, [read]) of
533
537
                        {ok,NewF} ->
534
538
                            ExtraPath = [filename:dirname(LibName)],
535
539
                            wait_req_scan(enter_file2(NewF, LibName, From,