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

« back to all changes in this revision

Viewing changes to lib/eunit/src/eunit_proc.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%% This library is free software; you can redistribute it and/or modify
 
2
%% it under the terms of the GNU Lesser General Public License as
 
3
%% published by the Free Software Foundation; either version 2 of the
 
4
%% License, or (at your option) any later version.
 
5
%%
 
6
%% This library is distributed in the hope that it will be useful, but
 
7
%% WITHOUT ANY WARRANTY; without even the implied warranty of
 
8
%% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
 
9
%% Lesser General Public License for more details.
 
10
%%
 
11
%% You should have received a copy of the GNU Lesser General Public
 
12
%% License along with this library; if not, write to the Free Software
 
13
%% Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307
 
14
%% USA
 
15
%%
 
16
%% $Id$ 
 
17
%%
 
18
%% @author Richard Carlsson <richardc@it.uu.se>
 
19
%% @copyright 2006 Richard Carlsson
 
20
%% @private
 
21
%% @see eunit
 
22
%% @doc Test runner process tree functions
 
23
 
 
24
-module(eunit_proc).
 
25
 
 
26
-include("eunit.hrl").
 
27
-include("eunit_internal.hrl").
 
28
 
 
29
-export([start/4]).
 
30
 
 
31
 
 
32
-record(procstate, {ref, id, super, insulator, parent, order}).
 
33
 
 
34
 
 
35
%% Spawns test process and returns the process Pid; sends {done,
 
36
%% Reference, Pid} to caller when finished. See the function
 
37
%% wait_for_task/2 for details about the need for the reference.
 
38
%%
 
39
%% The `Super' process receives a stream of status messages; see
 
40
%% status_message/3 for details.
 
41
 
 
42
start(Tests, Order, Super, Reference)
 
43
  when is_pid(Super), is_reference(Reference) ->
 
44
    St = #procstate{ref = Reference,
 
45
                    id = [],
 
46
                    super = Super,
 
47
                    order = Order},
 
48
    spawn_group(local, #group{tests = Tests}, St).
 
49
 
 
50
 
 
51
%% Status messages sent to the supervisor process. (A supervisor does
 
52
%% not have to act on these messages - it can e.g. just log them, or
 
53
%% even discard them.) Each status message has the following form:
 
54
%%
 
55
%%   {status, Id, Info}
 
56
%%
 
57
%% where Id identifies the item that the message pertains to, and the
 
58
%% Info part can be one of:
 
59
%%
 
60
%%   {progress, 'begin', test | group}
 
61
%%       indicates that the item has been entered, and what type it is
 
62
%%
 
63
%%   {progress, 'end', {Status, Time::integer(), Output::io_list()}}
 
64
%%       Status = 'ok' | {error, Exception} | {skipped, Cause}
 
65
%%
 
66
%%       where Time is measured in milliseconds and Output is the data
 
67
%%       written to the standard output stream during the test; if
 
68
%%       Status is {skipped, Cause}, then Cause is a term thrown from
 
69
%%       eunit_test:run_testfun/1
 
70
%%
 
71
%%   {cancel, Descriptor}
 
72
%%       where Descriptor can be:
 
73
%%           timeout            a timeout occurred
 
74
%%           {blame, Id}        forced to terminate because of item `Id'
 
75
%%           {abort, Cause}     the test failed to execute
 
76
%%           {exit, Reason}     the test process terminated unexpectedly
 
77
%%           {startup, Reason}  failed to start a remote test process
 
78
%%
 
79
%%       where Cause is a term thrown from eunit_data:enter_context/4 or
 
80
%%       from eunit_data:iter_next/2, and Reason is an exit term from a
 
81
%%       crashed process
 
82
%%
 
83
%% Note that due to concurrent (and possibly distributed) execution,
 
84
%% there are *no* strict ordering guarantees on the status messages,
 
85
%% with one exception: a 'begin' message will always arrive before its
 
86
%% corresponding 'end' message.
 
87
 
 
88
status_message(Id, Info, St) ->
 
89
    St#procstate.super ! {status, Id, Info},
 
90
    ok.
 
91
 
 
92
 
 
93
%% @TODO implement synchronized mode for insulator/child execution
 
94
 
 
95
%% Ideas for synchronized mode:
 
96
%%
 
97
%% * At each "program point", i.e., before entering a test, entering a
 
98
%% group, or leaving a group, the child will synchronize with the
 
99
%% insulator to make sure it is ok to proceed.
 
100
%%
 
101
%% * The insulator can receive controlling messages from higher up in
 
102
%% the hierarchy, telling it to pause, resume, single-step, repeat, etc.
 
103
%%
 
104
%% * Synchronization on entering/leaving groups is necessary in order to
 
105
%% get control over things such as subprocess creation/termination and
 
106
%% setup/cleanup, making it possible to, e.g., repeat all the tests
 
107
%% within a particular subprocess without terminating and restarting it,
 
108
%% or repeating tests without repeating the setup/cleanup.
 
109
%%
 
110
%% * Some tests that depend on state will not be possible to repeat, but
 
111
%% require a fresh context setup. There is nothing that can be done
 
112
%% about this, and the many tests that are repeatable should not be
 
113
%% punished because of it. The user must decide which level to restart.
 
114
%%
 
115
%% * Question: How propagate control messages down the hierarchy
 
116
%% (preferably only to the correct insulator process)? An insulator does
 
117
%% not currenctly know whether its child process has spawned subtasks.
 
118
%% (The "supervisor" process does not know the Pids of the controlling
 
119
%% insulator processes in the tree, and it probably should not be
 
120
%% responsible for this anyway.)
 
121
 
 
122
 
 
123
%% ---------------------------------------------------------------------
 
124
%% Process tree primitives
 
125
 
 
126
%% A "task" consists of an insulator process and a child process which
 
127
%% handles the actual work. When the child terminates, the insulator
 
128
%% process sends {done, Reference, self()} to the process which started
 
129
%% the task (the "parent"). The child process is given a State record
 
130
%% which contains the process id:s of the parent, the insulator, and the
 
131
%% supervisor.
 
132
 
 
133
%% @spec (Type, (#procstate{}) -> () -> term(), #procstate{}) -> pid()
 
134
%%   Type = local | {remote, Node::atom()}
 
135
 
 
136
start_task(Type, Fun, St0) ->
 
137
    St = St0#procstate{parent = self()},
 
138
    %% (note: the link here is mainly to propagate signals *downwards*,
 
139
    %% so that the insulator can detect if the process that started the
 
140
    %% task dies before the task is done)
 
141
    F = fun () -> insulator_process(Type, Fun, St) end,
 
142
    case Type of
 
143
        local ->
 
144
            %% we assume (at least for now) that local spawns can never
 
145
            %% fail in such a way that the process does not start, so a
 
146
            %% new local insulator does not need to synchronize here
 
147
            spawn_link(F);
 
148
        {remote, Node} ->
 
149
            Pid = spawn_link(Node, F),
 
150
            %% See below for the need for the {ok, Reference, Pid}
 
151
            %% message.
 
152
            Reference = St#procstate.ref,
 
153
            Monitor = erlang:monitor(process, Pid),
 
154
            %% (the DOWN message is guaranteed to arrive after any
 
155
            %% messages sent by the process itself)
 
156
            receive
 
157
                {ok, Reference, Pid} ->
 
158
                    ok;
 
159
                {'DOWN', Monitor, process, Pid, Reason} ->
 
160
                    %% send messages as if the insulator process was
 
161
                    %% started, but terminated on its own accord
 
162
                    Msg = {startup, Reason},
 
163
                    status_message(St#procstate.id, {cancel, Msg}, St),
 
164
                    self() ! {done, Reference, Pid},
 
165
                    ok
 
166
            end,
 
167
            erlang:demonitor(Monitor, [flush]),
 
168
            Pid
 
169
    end.
 
170
 
 
171
%% Relatively simple, and hopefully failure-proof insulator process
 
172
%% (This is cleaner than temporarily setting up the caller to trap
 
173
%% signals, and does not affect the caller's mailbox or other state.)
 
174
%%
 
175
%% We assume that nobody does a 'kill' on an insulator process - if that
 
176
%% should happen, the test framework will hang since the insulator will
 
177
%% never send a reply; see below for more.
 
178
%%
 
179
%% Note that even if the insulator process itself never fails, it is
 
180
%% still possible that it does not start properly, if it is spawned
 
181
%% remotely (e.g., if the remote node is down). Therefore, remote
 
182
%% insulators must always immediately send an {ok, Reference, self()}
 
183
%% message to the parent as soon as it is spawned.
 
184
 
 
185
%% @spec (Type, Fun::() -> term(), St::#procstate{}) -> ok
 
186
%%  Type = local | {remote, Node::atom()}
 
187
 
 
188
insulator_process(Type, Fun, St0) ->
 
189
    process_flag(trap_exit, true),
 
190
    Parent = St0#procstate.parent,
 
191
    if Type =:= local -> ok;
 
192
       true -> Parent ! {ok, St0#procstate.ref, self()}
 
193
    end,
 
194
    St = St0#procstate{insulator = self()},
 
195
    Child = spawn_link(fun () -> child_process(Fun(St), St) end),
 
196
    insulator_wait(Child, Parent, [], St).
 
197
 
 
198
%% Normally, child processes exit with the reason 'normal' even if the
 
199
%% executed tests failed (by throwing exceptions), since the tests are
 
200
%% executed within a try-block. Child processes can terminate abnormally
 
201
%% by the following reasons:
 
202
%%   1) an error in the processing of the test descriptors (a malformed
 
203
%%      descriptor, failure in a setup, cleanup or initialization, a
 
204
%%      missing module or function, or a failing generator function);
 
205
%%   2) an internal error in the test running framework itself;
 
206
%%   3) receiving a non-trapped error signal as a consequence of running
 
207
%%      test code.
 
208
%% Those under point 1 are "expected errors", handled specially in the
 
209
%% protocol, while the other two are unexpected errors. (Since alt. 3
 
210
%% implies that the test neither reported success nor failure, it can
 
211
%% never be considered "proper" behaviour of a test.) Abnormal
 
212
%% termination is reported to the supervisor process but otherwise does
 
213
%% not affect the insulator compared to normal termination. Child
 
214
%% processes can also be killed abruptly by their insulators, in case of
 
215
%% a timeout or if a parent process dies.
 
216
%%
 
217
%% The insulator is the group leader for the child process, and gets all
 
218
%% of its standard I/O. The output is buffered and associated with the
 
219
%% currently active test or group, and is sent along with the 'end'
 
220
%% progress message when the test or group has finished.
 
221
 
 
222
insulator_wait(Child, Parent, Buf, St) ->
 
223
    receive
 
224
        {io_request, From, ReplyAs, Req} when is_pid(From) ->
 
225
            Buf1 = io_request(From, ReplyAs, Req, hd(Buf)),
 
226
            insulator_wait(Child, Parent, [Buf1 | tl(Buf)], St);
 
227
        {progress, Child, Id, 'begin', Class} ->
 
228
            status_message(Id, {progress, 'begin', Class}, St),
 
229
            insulator_wait(Child, Parent, [[] | Buf], St);
 
230
        {progress, Child, Id, 'end', {Status, Time}} ->
 
231
            Msg = {Status, Time, lists:reverse(hd(Buf))},
 
232
            status_message(Id, {progress, 'end', Msg}, St),
 
233
            insulator_wait(Child, Parent, tl(Buf), St);
 
234
        {cancel, Child, Id, Reason} ->
 
235
            status_message(Id, {cancel, Reason}, St),
 
236
            insulator_wait(Child, Parent, Buf, St);
 
237
        {abort, Child, Id, Cause} ->
 
238
            exit_messages(Id, {abort, Cause}, St),
 
239
            %% no need to wait for the {'EXIT',Child,_} message
 
240
            terminate_insulator(St);
 
241
        {timeout, Child, Id} ->
 
242
            exit_messages(Id, timeout, St),
 
243
            kill_task(Child, St);
 
244
        {'EXIT', Child, normal} ->
 
245
            terminate_insulator(St);
 
246
        {'EXIT', Child, Reason} ->
 
247
            exit_messages(St#procstate.id, {exit, Reason}, St),
 
248
            terminate_insulator(St);
 
249
        {'EXIT', Parent, _} ->
 
250
            %% make sure child processes are cleaned up recursively
 
251
            kill_task(Child, St)
 
252
    end.
 
253
 
 
254
-spec kill_task(pid(), #procstate{}) -> no_return().
 
255
kill_task(Child, St) ->
 
256
    exit(Child, kill),
 
257
    terminate_insulator(St).
 
258
 
 
259
%% Unlinking before exit avoids polluting the parent process with exit
 
260
%% signals from the insulator. The child process is already dead here.
 
261
 
 
262
-spec terminate_insulator(#procstate{}) -> no_return().
 
263
terminate_insulator(St) ->
 
264
    %% messaging/unlinking is ok even if the parent is already dead
 
265
    Parent = St#procstate.parent,
 
266
    Parent ! {done, St#procstate.ref, self()},
 
267
    unlink(Parent),
 
268
    exit(normal).
 
269
 
 
270
%% send cancel messages for the Id of the "causing" item, and also for
 
271
%% the Id of the insulator itself, if they are different
 
272
exit_messages(Id, Cause, St) ->
 
273
    %% the message for the most specific Id is always sent first
 
274
    status_message(Id, {cancel, Cause}, St),
 
275
    case St#procstate.id of
 
276
        Id -> ok;
 
277
        Id1 -> status_message(Id1, {cancel, {blame, Id}}, St)
 
278
    end.
 
279
 
 
280
%% Child processes send all messages via the insulator to ensure proper
 
281
%% sequencing with timeouts and exit signals.
 
282
 
 
283
abort_message(Cause, St) ->
 
284
    St#procstate.insulator ! {abort, self(), St#procstate.id, Cause},
 
285
    ok.
 
286
 
 
287
cancel_message(Msg, St) ->
 
288
    St#procstate.insulator ! {cancel, self(), St#procstate.id, Msg},
 
289
    ok.
 
290
 
 
291
progress_message(Type, Data, St) ->
 
292
    St#procstate.insulator ! {progress, self(), St#procstate.id,
 
293
                              Type, Data},
 
294
    ok.
 
295
 
 
296
%% Timeout handling
 
297
 
 
298
set_timeout(Time, St) ->
 
299
    erlang:send_after(Time, St#procstate.insulator,
 
300
                      {timeout, self(), St#procstate.id}).
 
301
 
 
302
clear_timeout(Ref) ->
 
303
    erlang:cancel_timer(Ref).
 
304
 
 
305
with_timeout(undefined, Default, F, St) ->
 
306
    with_timeout(Default, F, St);
 
307
with_timeout(Time, _Default, F, St) ->
 
308
    with_timeout(Time, F, St).
 
309
 
 
310
with_timeout(infinity, F, _St) ->
 
311
    %% don't start timers unnecessarily
 
312
    {T0, _} = statistics(wall_clock),
 
313
    Value = F(),
 
314
    {T1, _} = statistics(wall_clock),
 
315
    {Value, T1 - T0};
 
316
with_timeout(Time, F, St) when is_integer(Time), Time > 16#FFFFffff ->
 
317
    with_timeout(16#FFFFffff, F, St);
 
318
with_timeout(Time, F, St) when is_integer(Time), Time < 0 ->
 
319
    with_timeout(0, F, St);
 
320
with_timeout(Time, F, St) when is_integer(Time) ->
 
321
    Ref = set_timeout(Time, St),
 
322
    {T0, _} = statistics(wall_clock),
 
323
    try F() of
 
324
        Value ->
 
325
            %% we could also read the timer, but this is simpler
 
326
            {T1, _} = statistics(wall_clock),
 
327
            {Value, T1 - T0}
 
328
    after
 
329
        clear_timeout(Ref)
 
330
    end.
 
331
 
 
332
%% The normal behaviour of a child process is to trap exit signals. This
 
333
%% makes it easier to write tests that spawn off separate (linked)
 
334
%% processes and test whether they terminate as expected. The testing
 
335
%% framework is not dependent on this, however, so the test code is
 
336
%% allowed to disable signal trapping as it pleases.
 
337
%% Note that I/O is redirected to the insulator process.
 
338
 
 
339
%% @spec (() -> term(), #procstate{}) -> ok
 
340
 
 
341
child_process(Fun, St) ->
 
342
    process_flag(trap_exit, true),
 
343
    group_leader(St#procstate.insulator, self()),
 
344
    try Fun() of
 
345
        _ -> ok
 
346
    catch
 
347
        %% the only "normal" way for a child process to bail out is to
 
348
        %% throw an {eunit_abort, Reason} exception; any other exception
 
349
        %% will be reported as an unexpected termination of the test
 
350
        {eunit_abort, Cause} ->
 
351
            abort_message(Cause, St),
 
352
            exit(aborted)
 
353
    end.
 
354
 
 
355
%% @throws abortException()
 
356
%% @type abortException() = {abort, Cause::term()}
 
357
 
 
358
abort_task(Cause) ->
 
359
    throw({eunit_abort, Cause}).
 
360
 
 
361
%% Typically, the process that executes this code is trapping signals,
 
362
%% but it might not be - it is outside of our control, since test code
 
363
%% could turn off trapping. That is why the insulator process of a task
 
364
%% must be guaranteed to always send a reply before it terminates.
 
365
%%
 
366
%% The unique reference guarantees that we don't extract any message
 
367
%% from the mailbox unless it belongs to the test framework (and not to
 
368
%% the running tests) - it is not possible to use selective receive to
 
369
%% match only messages tagged with some pid in a dynamically varying set
 
370
%% of pids. When the wait-loop terminates, no such message should remain
 
371
%% in the mailbox.
 
372
 
 
373
wait_for_task(Pid, St) ->
 
374
    wait_for_tasks(sets:from_list([Pid]), St).
 
375
 
 
376
wait_for_tasks(PidSet, St) ->
 
377
    case sets:size(PidSet) of
 
378
        0 ->
 
379
            ok;
 
380
        _ ->
 
381
            %% (note that when we receive this message for some task, we
 
382
            %% are guaranteed that the insulator process of the task has
 
383
            %% already informed the supervisor about any anomalies)
 
384
            Reference = St#procstate.ref,
 
385
            receive
 
386
                {done, Reference, Pid} ->
 
387
                    %% (if Pid is not in the set, del_element has no
 
388
                    %% effect, so this is always safe)
 
389
                    Rest = sets:del_element(Pid, PidSet),
 
390
                    wait_for_tasks(Rest, St)
 
391
            end
 
392
    end.
 
393
 
 
394
 
 
395
%% ---------------------------------------------------------------------
 
396
%% Separate testing process
 
397
 
 
398
tests(T, St) ->
 
399
    I = eunit_data:iter_init(T, St#procstate.id),
 
400
    case St#procstate.order of
 
401
        inorder -> tests_inorder(I, St);
 
402
        inparallel -> tests_inparallel(I, 0, St);
 
403
        {inparallel, N} when is_integer(N), N >= 0 ->
 
404
            tests_inparallel(I, N, St)
 
405
    end.
 
406
 
 
407
set_id(I, St) ->
 
408
    St#procstate{id = eunit_data:iter_id(I)}.
 
409
 
 
410
tests_inorder(I, St) ->
 
411
    tests_inorder(I, 0, St).
 
412
 
 
413
tests_inorder(I, N, St) ->
 
414
    case get_next_item(I) of
 
415
        {T, I1} ->
 
416
            handle_item(T, set_id(I1, St)),
 
417
            tests_inorder(I1, N+1, St);
 
418
        none ->
 
419
            N
 
420
    end.
 
421
 
 
422
tests_inparallel(I, K0, St) ->
 
423
    tests_inparallel(I, 0, St, K0, K0, sets:new()).
 
424
 
 
425
tests_inparallel(I, N, St, K, K0, Children) when K =< 0, K0 > 0 ->
 
426
    wait_for_tasks(Children, St),
 
427
    tests_inparallel(I, N, St, K0, K0, sets:new());
 
428
tests_inparallel(I, N, St, K, K0, Children) ->
 
429
    case get_next_item(I) of
 
430
        {T, I1} ->
 
431
            Child = spawn_item(T, set_id(I1, St)),
 
432
            tests_inparallel(I1, N+1, St, K - 1, K0,
 
433
                             sets:add_element(Child, Children));
 
434
        none ->
 
435
            wait_for_tasks(Children, St),
 
436
            N
 
437
    end.
 
438
 
 
439
spawn_item(T, St0) ->
 
440
    Fun = fun (St) ->
 
441
                  fun () -> handle_item(T, St) end
 
442
          end,
 
443
    %% inparallel-items are always spawned locally
 
444
    start_task(local, Fun, St0).
 
445
 
 
446
get_next_item(I) ->
 
447
    eunit_data:iter_next(I, fun abort_task/1).
 
448
 
 
449
handle_item(T, St) ->
 
450
    case T of
 
451
        #test{} -> handle_test(T, St);
 
452
        #group{} -> handle_group(T, St)
 
453
    end.
 
454
 
 
455
handle_test(T, St) ->
 
456
    progress_message('begin', test, St),
 
457
    {Status, Time} = with_timeout(T#test.timeout, ?DEFAULT_TEST_TIMEOUT,
 
458
                                  fun () -> run_test(T) end, St),
 
459
    progress_message('end', {Status, Time}, St),
 
460
    ok.
 
461
 
 
462
%% @spec (#test{}) -> ok | {error, eunit_lib:exception()}
 
463
%%                  | {skipped, eunit_test:wrapperError()}
 
464
 
 
465
run_test(#test{f = F}) ->
 
466
    try eunit_test:run_testfun(F) of
 
467
        {ok, _Value} ->
 
468
            %% just throw away the return value
 
469
            ok;
 
470
        {error, Exception} ->
 
471
            {error, Exception}
 
472
    catch
 
473
        throw:WrapperError -> {skipped, WrapperError}
 
474
    end.
 
475
 
 
476
set_group_order(#group{order = undefined}, St) ->
 
477
    St;
 
478
set_group_order(#group{order = Order}, St) ->
 
479
    St#procstate{order = Order}.
 
480
 
 
481
handle_group(T, St0) ->
 
482
    St = set_group_order(T, St0),
 
483
    case T#group.spawn of
 
484
        undefined ->
 
485
            run_group(T, St);
 
486
        Type ->
 
487
            Child = spawn_group(Type, T, St),
 
488
            wait_for_task(Child, St)
 
489
    end.
 
490
 
 
491
spawn_group(Type, T, St0) ->
 
492
    Fun = fun (St) ->
 
493
                  fun () -> run_group(T, St) end
 
494
          end,
 
495
    start_task(Type, Fun, St0).
 
496
 
 
497
run_group(T, St) ->
 
498
    %% note that the setup/cleanup is outside the group timeout; if the
 
499
    %% setup fails, we do not start any timers
 
500
    Timeout = T#group.timeout,
 
501
    progress_message('begin', group, St),
 
502
    F = fun (T) -> enter_group(T, Timeout, St) end,
 
503
    try with_context(T, F) of
 
504
        {Status, Time} ->
 
505
            progress_message('end', {Status, Time}, St)
 
506
    catch
 
507
        throw:Cause ->
 
508
            cancel_message({abort, Cause}, St)
 
509
    end,
 
510
    ok.
 
511
 
 
512
enter_group(T, Timeout, St) ->
 
513
    with_timeout(Timeout, ?DEFAULT_GROUP_TIMEOUT,
 
514
                 fun () -> tests(T, St) end, St).
 
515
 
 
516
with_context(#group{context = undefined, tests = T}, F) ->
 
517
    F(T);
 
518
with_context(#group{context = #context{} = C, tests = I}, F) ->
 
519
    eunit_data:enter_context(C, I, F).
 
520
 
 
521
%% Implementation of buffering I/O for the insulator process. (Note that
 
522
%% each batch of characters is just pushed on the buffer, so it needs to
 
523
%% be reversed when it is flushed.)
 
524
 
 
525
io_request(From, ReplyAs, Req, Buf) ->
 
526
    {Reply, Buf1} = io_request(Req, Buf),
 
527
    io_reply(From, ReplyAs, Reply),
 
528
    Buf1.
 
529
 
 
530
io_reply(From, ReplyAs, Reply) ->
 
531
    From ! {io_reply, ReplyAs, Reply}.
 
532
 
 
533
io_request({put_chars, Chars}, Buf) ->
 
534
    {ok, [Chars | Buf]};
 
535
io_request({put_chars, M, F, As}, Buf) ->
 
536
    try apply(M, F, As) of
 
537
        Chars -> {ok, [Chars | Buf]}
 
538
    catch
 
539
        C:T -> {{error, {C,T,erlang:get_stacktrace()}}, Buf}
 
540
    end;
 
541
io_request({get_chars, _Prompt, _N}, Buf) ->
 
542
    {eof, Buf};
 
543
io_request({get_chars, _Prompt, _M, _F, _Xs}, Buf) ->
 
544
    {eof, Buf};
 
545
io_request({get_line, _Prompt}, Buf) ->
 
546
    {eof, Buf};
 
547
io_request({get_until, _Prompt, _M, _F, _As}, Buf) ->
 
548
    {eof, Buf};
 
549
io_request({setopts, _Opts}, Buf) ->
 
550
    {ok, Buf};
 
551
io_request({requests, Reqs}, Buf) ->
 
552
    io_requests(Reqs, {ok, Buf});
 
553
io_request(_, Buf) ->
 
554
    {{error, request}, Buf}.
 
555
 
 
556
io_requests([R | Rs], {ok, Buf}) ->
 
557
    io_requests(Rs, io_request(R, Buf));
 
558
io_requests(_, Result) ->
 
559
    Result.