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

« back to all changes in this revision

Viewing changes to lib/mnesia/test/mnesia_qlc_test.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:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 2004-2010. All Rights Reserved.
 
5
%%
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%%
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%%
 
17
%% %CopyrightEnd%
 
18
%%
 
19
 
 
20
%%
 
21
-module(mnesia_qlc_test).
 
22
 
 
23
-compile(export_all).
 
24
 
 
25
-export([all/0,groups/0,init_per_group/2,end_per_group/2]).
 
26
 
 
27
-include("mnesia_test_lib.hrl").
 
28
-include_lib("stdlib/include/qlc.hrl"). 
 
29
 
 
30
init_per_testcase(Func, Conf) ->
 
31
    setup(Conf),
 
32
    mnesia_test_lib:init_per_testcase(Func, Conf).
 
33
 
 
34
end_per_testcase(Func, Conf) ->
 
35
    mnesia_test_lib:end_per_testcase(Func, Conf).
 
36
 
 
37
all() -> 
 
38
    case code:which(qlc) of
 
39
        non_existing -> [];
 
40
        _ -> all_qlc()
 
41
    end.
 
42
 
 
43
groups() -> 
 
44
    [{dirty, [],
 
45
      [dirty_nice_ram_copies, dirty_nice_disc_copies,
 
46
       dirty_nice_disc_only_copies]},
 
47
     {trans, [],
 
48
      [trans_nice_ram_copies, trans_nice_disc_copies,
 
49
       trans_nice_disc_only_copies, {group, atomic}]},
 
50
     {atomic, [], [atomic_eval]}].
 
51
 
 
52
init_per_group(_GroupName, Config) ->
 
53
    Config.
 
54
 
 
55
end_per_group(_GroupName, Config) ->
 
56
    Config.
 
57
 
 
58
 
 
59
all_qlc() -> 
 
60
    [{group, dirty}, {group, trans}, frag, info,
 
61
     mnesia_down].
 
62
 
 
63
init_testcases(Type,Config) ->
 
64
    Nodes = [N1,N2] = ?acquire_nodes(2, Config),
 
65
    ?match({atomic, ok}, mnesia:create_table(a, [{Type,[N1]}, {index,[3]}])),
 
66
    ?match({atomic, ok}, mnesia:create_table(b, [{Type,[N2]}])),
 
67
    Write = fun(Id) -> 
 
68
                    ok = mnesia:write({a, {a,Id}, 100 - Id}),
 
69
                    ok = mnesia:write({b, {b,100-Id}, Id})
 
70
            end,
 
71
    All = fun() -> [Write(Id) || Id <- lists:seq(1,10)], ok end,
 
72
    ?match({atomic, ok}, mnesia:sync_transaction(All)),
 
73
    Nodes.
 
74
 
 
75
%% Test cases       
 
76
 
 
77
dirty_nice_ram_copies(Setup) -> dirty_nice(Setup,ram_copies).
 
78
dirty_nice_disc_copies(Setup) -> dirty_nice(Setup,disc_copies).
 
79
dirty_nice_disc_only_copies(Setup) -> dirty_nice(Setup,disc_only_copies).
 
80
 
 
81
dirty_nice(suite, _) -> [];
 
82
dirty_nice(doc, _) -> [];
 
83
dirty_nice(Config, Type) when is_list(Config) ->
 
84
    Ns = init_testcases(Type,Config),
 
85
    QA = handle(<<"[Q || Q = {_,{_,Key},Val} <- mnesia:table(a),"
 
86
                 "     Val == 90 + Key]">>),
 
87
    QB = handle(<<"[Q || Q = {_,{_,Key},Val} <- mnesia:table(b),"
 
88
                 "     Key == 90 + Val]">>),
 
89
    QC = qlc:sort(mnesia:table(a, [{n_objects,1}, {lock,write}, {traverse, select}])),
 
90
    QD = qlc:sort(mnesia:table(a, [{n_objects,1}, {traverse,{select,[{'$1',[],['$1']}]}}])),
 
91
 
 
92
    FA = fun() -> qlc:e(QA) end,
 
93
    FB = fun() -> qlc:e(QB) end,
 
94
    FC = fun() -> qlc:e(QC) end,
 
95
    FD = fun() -> qlc:e(QD) end,
 
96
 
 
97
    %% Currently unsupported
 
98
    ?match({'EXIT',{aborted,no_transaction}}, FA()),
 
99
    ?match({'EXIT',{aborted,no_transaction}}, FB()),
 
100
    %%
 
101
    CRes = lists:sort(mnesia:dirty_match_object(a, {'_','_','_'})),
 
102
    ?match([{a,{a,5},95}], mnesia:async_dirty(FA)),
 
103
    ?match([{b,{b,95},5}], mnesia:async_dirty(FB)),
 
104
    ?match(CRes, mnesia:async_dirty(FC)),
 
105
    ?match(CRes, mnesia:async_dirty(FD)),
 
106
    ?match([{a,{a,5},95}], mnesia:sync_dirty(FA)),
 
107
    ?match([{b,{b,95},5}], mnesia:sync_dirty(FB)),
 
108
    ?match(CRes, mnesia:sync_dirty(FC)),
 
109
    ?match([{a,{a,5},95}], mnesia:activity(async_dirty, FA)),
 
110
    ?match([{b,{b,95},5}], mnesia:activity(async_dirty, FB)),
 
111
    ?match([{a,{a,5},95}], mnesia:activity(sync_dirty, FA)),
 
112
    ?match([{b,{b,95},5}], mnesia:activity(sync_dirty, FB)),
 
113
    ?match(CRes, mnesia:activity(async_dirty,FC)),
 
114
    case Type of
 
115
        disc_only_copies -> skip;
 
116
        _ -> 
 
117
            ?match([{a,{a,5},95}], mnesia:ets(FA)),
 
118
            ?match([{a,{a,5},95}], mnesia:activity(ets, FA))
 
119
    end,
 
120
    ?verify_mnesia(Ns, []).
 
121
 
 
122
 
 
123
trans_nice_ram_copies(Setup) -> trans_nice(Setup,ram_copies).
 
124
trans_nice_disc_copies(Setup) -> trans_nice(Setup,disc_copies).
 
125
trans_nice_disc_only_copies(Setup) -> trans_nice(Setup,disc_only_copies).
 
126
 
 
127
trans_nice(suite, _) -> [];
 
128
trans_nice(doc, _) -> [];
 
129
trans_nice(Config, Type) when is_list(Config) ->
 
130
    Ns = init_testcases(Type,Config),
 
131
    QA = handle(<<"[Q || Q = {_,{_,Key},Val} <- mnesia:table(a),"
 
132
                 "     Val == 90 + Key]">>),
 
133
    QB = handle(<<"[Q || Q = {_,{_,Key},Val} <- mnesia:table(b),"
 
134
                 "     Key == 90 + Val]">>),
 
135
    QC = handle(recs(), 
 
136
                <<"[Q || Q = #a{v=91} <- mnesia:table(a)]"
 
137
                 >>),
 
138
 
 
139
    QD = qlc:sort(mnesia:table(a, [{n_objects,1}, {lock,write}, {traverse, select}])),
 
140
    QE = qlc:sort(mnesia:table(a, [{n_objects,1}, {traverse,{select,[{'$1',[],['$1']}]}}])),
 
141
 
 
142
    DRes = lists:sort(mnesia:dirty_match_object(a, {'_','_','_'})),
 
143
 
 
144
    FA = fun() -> qlc:e(QA) end,
 
145
    FB = fun() -> qlc:e(QB) end,
 
146
    FC = fun() -> qlc:e(QC) end,
 
147
    FD = fun() -> qlc:e(QD) end,
 
148
    FE = fun() -> qlc:e(QE) end,
 
149
                  
 
150
    ?match({atomic,[{a,{a,5},95}]}, mnesia:transaction(FA)),
 
151
    ?match({atomic,[{b,{b,95},5}]}, mnesia:transaction(FB)),
 
152
    ?match({atomic,[{a,{a,9},91}]}, mnesia:transaction(FC)),
 
153
    ?match({atomic,[{a,{a,5},95}]}, mnesia:sync_transaction(FA)),
 
154
    ?match({atomic,[{b,{b,95},5}]}, mnesia:sync_transaction(FB)),
 
155
    ?match({atomic,[{a,{a,9},91}]}, mnesia:sync_transaction(FC)),
 
156
    ?match([{a,{a,5},95}], mnesia:activity(transaction,FA)),
 
157
    ?match([{b,{b,95},5}], mnesia:activity(transaction,FB)),
 
158
    ?match([{a,{a,9},91}], mnesia:activity(transaction,FC)),
 
159
    ?match([{a,{a,5},95}], mnesia:activity(sync_transaction,FA)),
 
160
    ?match([{b,{b,95},5}], mnesia:activity(sync_transaction,FB)),
 
161
    ?match([{a,{a,9},91}], mnesia:activity(sync_transaction,FC)),
 
162
 
 
163
    ?match({atomic, DRes}, mnesia:transaction(FD)),
 
164
    ?match({atomic, DRes}, mnesia:transaction(FE)),
 
165
 
 
166
    Rest = fun(Cursor,Loop) -> 
 
167
                   case qlc:next_answers(Cursor, 1) of
 
168
                       [] -> [];
 
169
                       [A]-> [A|Loop(Cursor,Loop)] 
 
170
                   end
 
171
           end,
 
172
    Loop = fun() -> 
 
173
                   Cursor = qlc:cursor(QD),
 
174
                   Rest(Cursor,Rest)
 
175
           end,
 
176
    ?match({atomic, DRes}, mnesia:transaction(Loop)),
 
177
 
 
178
    ?verify_mnesia(Ns, []).
 
179
 
 
180
%% -record(a, {k,v}).
 
181
%% -record(b, {k,v}).
 
182
%% -record(k, {t,v}).
 
183
 
 
184
recs() ->
 
185
    <<"-record(a, {k,v}). "
 
186
      "-record(b, {k,v}). "
 
187
      "-record(k, {t,v}). "
 
188
     >>.
 
189
 
 
190
 
 
191
atomic_eval(suite) -> [];
 
192
atomic_eval(doc) -> []; 
 
193
atomic_eval(Config) ->
 
194
    Ns = init_testcases(ram_copies, Config),    
 
195
    Q1 = handle(recs(), 
 
196
                <<"[Q || Q = #a{k={_,9}} <- mnesia:table(a)]"
 
197
                 >>),
 
198
    Eval = fun(Q) -> 
 
199
                   {qlc:e(Q),
 
200
                    mnesia:system_info(held_locks)}
 
201
           end,
 
202
    Self = self(),
 
203
    ?match({[{a,{a,9},91}], [{{a,'______WHOLETABLE_____'},read,{tid,_,Self}}]},
 
204
           ok(Eval,[Q1])),
 
205
    
 
206
    Q2 = handle(recs(), 
 
207
                <<"[Q || Q = #a{k={a,9}} <- mnesia:table(a)]"
 
208
                 >>),
 
209
    
 
210
    ?match({[{a,{a,9},91}],[{{a,{a,9}},read,{tid,_,Self}}]},
 
211
           ok(Eval,[Q2])),
 
212
 
 
213
    Flush = fun(Loop) -> %% Clean queue
 
214
                    receive _ -> Loop(Loop) 
 
215
                    after 0 -> ok end
 
216
            end,
 
217
    
 
218
    Flush(Flush),
 
219
 
 
220
    GrabLock = fun(Father) ->  
 
221
                       mnesia:read(a, {a,9}, write),
 
222
                       Father ! locked,
 
223
                       receive cont -> ok end end,
 
224
 
 
225
    Pid1 = spawn(fun() -> ?match(ok, ok(GrabLock, [Self])) end),    
 
226
    ?match(locked,receive locked -> locked after 5000 -> timeout end), %% Wait
 
227
 
 
228
    put(count,0),
 
229
    Restart = fun(Locker,Fun) ->
 
230
                      Count = get(count),
 
231
                      case {Count,(catch Fun())}  of
 
232
                          {0, {'EXIT', R}} ->
 
233
                              Locker ! cont,
 
234
                              put(count, Count+1),
 
235
                              erlang:yield(),
 
236
                              exit(R);
 
237
                          Else ->
 
238
                              Else
 
239
                      end
 
240
              end,
 
241
    
 
242
    ?match({1,{[{a,{a,9},91}], [{{a,'______WHOLETABLE_____'},read,{tid,_,Self}}]}},
 
243
           ok(Restart,[Pid1,fun() -> Eval(Q1) end])),
 
244
    
 
245
    Pid2 = spawn(fun() -> ?match(ok, ok(GrabLock, [Self])) end),
 
246
    ?match(locked,receive locked -> locked after 5000 -> timeout end), %% Wait
 
247
    put(count,0),
 
248
    ?match({1,{[{a,{a,9},91}],[{{a,{a,9}},read,{tid,_,Self}}]}},
 
249
           ok(Restart,[Pid2, fun() -> Eval(Q2) end])),
 
250
 
 
251
%% Basic test     
 
252
    Cursor = fun() ->
 
253
                     QC = qlc:cursor(Q1),
 
254
                     qlc:next_answers(QC) 
 
255
             end,
 
256
 
 
257
    ?match([{a,{a,9},91}], ok(Cursor, [])),
 
258
    %% Lock 
 
259
 
 
260
    Pid3 = spawn(fun() -> ?match(ok, ok(GrabLock, [Self])) end),    
 
261
    ?match(locked,receive locked -> locked after 5000 -> timeout end), %% Wait
 
262
    put(count,0),
 
263
    
 
264
    ?match({1,[{a,{a,9},91}]}, ok(Restart,[Pid3, Cursor])),
 
265
    QC1 = ok(fun() -> qlc:cursor(Q1) end, []),
 
266
    ?match({'EXIT', _},  qlc:next_answers(QC1)),
 
267
    ?match({aborted,_},  ok(fun()->qlc:next_answers(QC1)end,[])),
 
268
    ?verify_mnesia(Ns, []).
 
269
 
 
270
 
 
271
frag(suite) -> [];
 
272
frag(doc) -> [];
 
273
frag(Config) ->
 
274
    Ns = init_testcases(ram_copies,Config),
 
275
    QA = handle(<<"[Q || Q = {_,{_,Key},Val} <- mnesia:table(a),"
 
276
                 "     Val == 90 + Key]">>),
 
277
    QB = handle(<<"[Q || Q = {_,{_,Key},Val} <- mnesia:table(b),"
 
278
                 "     Key == 90 + Val]">>),
 
279
    
 
280
    Activate = 
 
281
        fun(Tab) ->
 
282
                ?match({atomic,ok},mnesia:change_table_frag(Tab, {activate, []})),
 
283
                Dist = mnesia_frag_test:frag_dist(Tab),
 
284
                ?match({atomic,ok},mnesia:change_table_frag(Tab,{add_frag,Dist}))
 
285
        end,
 
286
    Activate(a),
 
287
    Activate(b),
 
288
 
 
289
    Fun = fun(Tab) -> mnesia:table_info(Tab, frag_names) end,
 
290
    FTs = mnesia:activity(sync_dirty, Fun, [a], mnesia_frag) ++
 
291
        mnesia:activity(sync_dirty, Fun, [b], mnesia_frag),
 
292
    Size = fun(Tab) -> mnesia:dirty_rpc(Tab, mnesia, table_info, [Tab,size]) end,
 
293
 
 
294
    %% Verify that all data doesn't belong to the same frag.
 
295
    ?match([], [{Tab,Size(Tab)} || Tab <- FTs,
 
296
                                   Size(Tab) =< 0]),
 
297
    
 
298
    FA = fun() -> qlc:e(QA) end,
 
299
    FB = fun() -> qlc:e(QB) end,
 
300
    ?match([{a,{a,5},95}], mnesia:activity(transaction,FA,[],mnesia_frag)),
 
301
    ?match([{b,{b,95},5}], mnesia:activity(transaction,FB,[],mnesia_frag)),
 
302
    
 
303
    ?verify_mnesia(Ns, []).
 
304
 
 
305
info(suite) -> [];
 
306
info(doc) -> [];
 
307
info(Config) ->
 
308
    Ns = init_testcases(ram_copies, Config),
 
309
    Q1 = handle(recs(), 
 
310
                <<"[Q || Q = #a{k={_,9}} <- mnesia:table(a)]"
 
311
                 >>),
 
312
    
 
313
    Q2 = handle(recs(), 
 
314
                <<"[Q || Q = #a{k={a,9}} <- mnesia:table(a)]"
 
315
                 >>),
 
316
    
 
317
    Q3 = handle(recs(), 
 
318
                <<"[Q || Q = #a{v=91} <- mnesia:table(a)]"
 
319
                 >>),
 
320
    
 
321
    %% FIXME compile and check results!
 
322
    
 
323
    ?match(ok,io:format("~s~n",[qlc:info(Q1)])),
 
324
    ?match(ok,io:format("~s~n",[qlc:info(Q2)])),
 
325
    ?match(ok,io:format("~s~n",[qlc:info(Q3)])),
 
326
 
 
327
    ?verify_mnesia(Ns, []).
 
328
 
 
329
ok(Fun,A) ->
 
330
    case mnesia:transaction(Fun,A) of
 
331
        {atomic, R} -> R;
 
332
        E -> E
 
333
    end.
 
334
 
 
335
 
 
336
mnesia_down(suite) -> [];
 
337
mnesia_down(doc) ->
 
338
    ["Test bug OTP-7968, which crashed mnesia when a"
 
339
     "mnesia_down came after qlc had been invoked"];
 
340
mnesia_down(Config) when is_list(Config) ->
 
341
    [N1,N2] = init_testcases(ram_copies,Config),
 
342
    QB = handle(<<"[Q || Q = {_,{_,Key},Val} <- mnesia:table(b),"
 
343
                 "     Val == Key - 90]">>),
 
344
 
 
345
    Tester = self(),    
 
346
    
 
347
    Eval = fun() -> 
 
348
                   Cursor = qlc:cursor(QB), %% Forces another process
 
349
                   Res = qlc:next_answers(Cursor),
 
350
                   Tester ! {qlc, self(), Res},
 
351
                   {Mod, Tid, Ts} = get(mnesia_activity_state),
 
352
                   receive
 
353
                       continue ->
 
354
                           io:format("Continuing ~p ~p ~n",[self(), {Mod, Tid, Ts}]),
 
355
                           io:format("ETS ~p~n",[ets:tab2list(element(2,Ts))]),
 
356
                           io:format("~p~n",[process_info(self(),messages)]),
 
357
                           Res
 
358
                   end
 
359
           end,
 
360
    spawn(fun() -> TransRes = mnesia:transaction(Eval), Tester ! {test,TransRes} end),
 
361
 
 
362
    TMInfo = fun() ->
 
363
                     TmInfo = mnesia_tm:get_info(5000),
 
364
                     mnesia_tm:display_info(user, TmInfo)
 
365
             end,
 
366
    receive
 
367
        {qlc, QPid, QRes} ->
 
368
            ?match([{b,{b,95},5}], QRes),
 
369
            TMInfo(),
 
370
            mnesia_test_lib:kill_mnesia([N2]),
 
371
            %%timer:sleep(1000),
 
372
            QPid ! continue
 
373
    after 2000 ->
 
374
            exit(timeout1)
 
375
    end,
 
376
 
 
377
    receive
 
378
        {test, QRes2} ->
 
379
            ?match({atomic, [{b,{b,95},5}]}, QRes2)
 
380
    after 2000 ->
 
381
            exit(timeout2)
 
382
    end,
 
383
    
 
384
    ?verify_mnesia([N1], [N2]).
 
385
 
 
386
 
 
387
nested_qlc(suite) -> [];
 
388
nested_qlc(doc) ->
 
389
    ["Test bug in OTP-7968 (the second problem) where nested"
 
390
     "transaction don't work as expected"];
 
391
nested_qlc(Config) when is_list(Config) ->
 
392
    Ns = init_testcases(ram_copies,Config),    
 
393
    Res = as_with_bs(),
 
394
    ?match([_|_], Res),
 
395
    top_as_with_some_bs(10),
 
396
    
 
397
    ?verify_mnesia(Ns, []).
 
398
 
 
399
 
 
400
%% Code from Daniel 
 
401
bs_by_a_id(A_id) ->
 
402
    find(qlc:q([ B || B={_,_,F_id} <- mnesia:table(b), F_id == A_id])).
 
403
 
 
404
as_with_bs() ->
 
405
    find(qlc:q([ {A,bs_by_a_id(Id)} ||
 
406
                   A = {_, {a,Id}, _} <- mnesia:table(a)])).
 
407
 
 
408
top_as_with_some_bs(Limit) ->
 
409
    top(
 
410
      qlc:q([ {A,bs_by_a_id(Id)} ||
 
411
                A = {_, {a,Id}, _} <- mnesia:table(a)]),
 
412
      Limit,
 
413
      fun(A1,A2) -> A1 < A2  end
 
414
     ).
 
415
 
 
416
% --- utils
 
417
 
 
418
find(Q) ->
 
419
    F = fun() -> qlc:e(Q) end,
 
420
    {atomic, Res} = mnesia:transaction(F),
 
421
    Res.
 
422
 
 
423
% --- it returns top Limit results from query Q ordered by Order sort function
 
424
top(Q, Limit, Order) ->
 
425
    Do = fun() ->
 
426
                 OQ = qlc:sort(Q, [{order,Order}]),
 
427
                 QC = qlc:cursor(OQ),
 
428
                 Res = qlc:next_answers(QC, Limit),
 
429
                 qlc:delete_cursor(QC),
 
430
                 Res
 
431
         end,
 
432
    {atomic, Res} = mnesia:transaction(Do),
 
433
    Res.
 
434
 
 
435
%% To keep mnesia suite backward compatible,
 
436
%% we compile the queries in runtime when qlc is available
 
437
%% Compiles and returns a handle to a qlc
 
438
handle(Expr) ->
 
439
    handle(<<>>,Expr).
 
440
handle(Records,Expr) ->
 
441
    case catch handle2(Records,Expr) of
 
442
        {ok, Handle} ->
 
443
            Handle;
 
444
        Else ->
 
445
            ?match(ok, Else)
 
446
    end.
 
447
 
 
448
handle2(Records,Expr) ->
 
449
    {FN,Mod} = temp_name(),
 
450
    ModStr = list_to_binary("-module(" ++ atom_to_list(Mod) ++ ").\n"),
 
451
    Prog = <<
 
452
            ModStr/binary,
 
453
            "-include_lib(\"stdlib/include/qlc.hrl\").\n",
 
454
            "-export([tmp/0]).\n",
 
455
            Records/binary,"\n",
 
456
            "tmp() ->\n",
 
457
%%          "   _ = (catch throw(fvalue_not_reset)),"
 
458
            "   qlc:q( ",
 
459
            Expr/binary,").\n">>,
 
460
 
 
461
    ?match(ok,file:write_file(FN,Prog)),
 
462
    {ok,Forms} = epp:parse_file(FN,"",""),
 
463
    {ok,Mod,Bin} = compile:forms(Forms),
 
464
    code:load_binary(Mod,FN,Bin),
 
465
    {ok, Mod:tmp()}.
 
466
 
 
467
setup(Config) ->
 
468
    put(mts_config,Config),
 
469
    put(mts_tf_counter,0).
 
470
 
 
471
temp_name() ->
 
472
    Conf = get(mts_config),
 
473
    C = get(mts_tf_counter),
 
474
    put(mts_tf_counter,C+1),
 
475
    {filename:join([proplists:get_value(priv_dir,Conf, "."),
 
476
                    "tempfile"++integer_to_list(C)++".tmp"]),
 
477
     list_to_atom("tmp" ++ integer_to_list(C))}.