~ubuntu-branches/ubuntu/intrepid/swi-prolog/intrepid

« back to all changes in this revision

Viewing changes to packages/clib/test_process.pl

  • Committer: Bazaar Package Importer
  • Author(s): Chris Lamb
  • Date: 2008-05-14 02:47:49 UTC
  • mfrom: (1.1.5 upstream)
  • Revision ID: james.westby@ubuntu.com-20080514024749-out53uysriunvn32
Tags: 5.6.55-1
* New upstream release.
* Use correct shared object file extension on HPPA to fix FTBFS on this
  architecture since 5.6.53-2. Patch backported from upstream repository.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
:- module(test_process,
 
2
          [ test_process/0
 
3
          ]).
 
4
 
 
5
:- asserta(user:file_search_path(foreign, '.')).
 
6
:- asserta(user:file_search_path(library, '.')).
 
7
:- asserta(user:file_search_path(library, '../plunit')).
 
8
 
 
9
:- use_module(library(plunit)).
 
10
:- use_module(library(readutil)).
 
11
:- use_module(process).
 
12
 
 
13
test_process :-
 
14
        run_tests([ process_create,
 
15
                    process_wait
 
16
                  ]).
 
17
 
 
18
read_process(In, Text) :-
 
19
        read_stream_to_codes(In, Codes),
 
20
        close(In),
 
21
        atom_codes(Text, Codes).
 
22
 
 
23
:- begin_tests(process_create, [sto(rational_trees)]).
 
24
 
 
25
test(echo, true) :-
 
26
        process_create(path(true), [], []).
 
27
test(null_input, Codes == []) :-
 
28
        process_create(path(cat), [], [stdin(null), stdout(pipe(Out))]),
 
29
        read_stream_to_codes(Out, Codes),
 
30
        close(Out).
 
31
test(null_output, true) :-
 
32
        process_create(path(sh), 
 
33
                       ['-c', 'echo THIS IS AN ERROR'],
 
34
                       [stdout(null)]).
 
35
test(null_error, true) :-
 
36
        process_create(path(sh),
 
37
                       ['-c', 'echo "THIS IS AN ERROR" 1>&2'],
 
38
                       [stderr(null)]).
 
39
test(read_error, X == 'error\n') :-
 
40
        process_create(path(sh),
 
41
                       ['-c', 'echo "error" 1>&2'],
 
42
                       [stderr(pipe(Out))]),
 
43
        read_process(Out, X).
 
44
test(echo, X == 'hello\n') :-
 
45
        process_create(path(sh),
 
46
                       ['-c', 'echo hello'],
 
47
                       [ stdout(pipe(Out))
 
48
                       ]),
 
49
        read_process(Out, X).
 
50
test(lwr, X == 'HELLO') :-
 
51
        process_create(path(tr), ['a-z', 'A-Z'],
 
52
                       [ stdin(pipe(In)),
 
53
                         stdout(pipe(Out))
 
54
                       ]),
 
55
        format(In, hello, []),
 
56
        close(In),
 
57
        read_process(Out, X).
 
58
test(cwd, [true, condition(\+current_prolog_flag(windows, true))]) :-
 
59
        tmp_dir(Tmp),
 
60
        process_create(path(pwd), [],
 
61
                       [ stdout(pipe(Out)),
 
62
                         cwd(Tmp)
 
63
                       ]),
 
64
        read_process(Out, CWD0),
 
65
        normalize_space(atom(CWD), CWD0),
 
66
        same_file(CWD, Tmp).
 
67
test(cwd, [true, condition(current_prolog_flag(windows, true))]) :-
 
68
        tmp_dir(Tmp),
 
69
        getenv('COMSPEC', Shell),
 
70
        process_create(Shell, ['/c', cd],
 
71
                       [ stdout(pipe(Out)),
 
72
                         cwd(Tmp)
 
73
                       ]),
 
74
        read_process(Out, CWD0),
 
75
        normalize_space(atom(CWD), CWD0),
 
76
        same_file(CWD, Tmp).
 
77
 
 
78
tmp_dir(Dir) :-
 
79
        getenv('TEMP', Dir), !.
 
80
tmp_dir('/tmp').
 
81
 
 
82
:- end_tests(process_create).
 
83
 
 
84
 
 
85
:- begin_tests(process_wait, [sto(rational_trees)]).
 
86
 
 
87
test(wait_ok, X == exit(0)) :-
 
88
        process_create(path(sh), ['-c', 'exit 0'], [process(PID)]),
 
89
        process_wait(PID, X).
 
90
test(wait_ok, X == exit(42)) :-
 
91
        process_create(path(sh), ['-c', 'exit 42'], [process(PID)]),
 
92
        process_wait(PID, X).
 
93
test(kill_ok, [ X == killed(9),
 
94
                condition(\+current_prolog_flag(windows, true))]) :-
 
95
        process_create(path(sleep), [2], [process(PID)]),
 
96
        process_kill(PID, 9),
 
97
        process_wait(PID, X).
 
98
test(kill_ok, [ X = exit(_),
 
99
                condition(current_prolog_flag(windows, true))]) :-
 
100
        process_create(path(sleep), [2], [process(PID)]),
 
101
        process_kill(PID, 9),
 
102
        process_wait(PID, X).
 
103
test(wait_timeout, [ X = timeout ]) :-
 
104
        process_create(path(sleep), [2], [process(PID)]),
 
105
        (   current_prolog_flag(windows, true)
 
106
        ->  TMO = 0.1
 
107
        ;   TMO = 0
 
108
        ),
 
109
        process_wait(PID, X, [timeout(TMO)]),
 
110
        process_kill(PID, 9),
 
111
        process_wait(PID, _).
 
112
 
 
113
:- end_tests(process_wait).