~ubuntu-branches/ubuntu/hardy/swi-prolog/hardy

« back to all changes in this revision

Viewing changes to packages/zlib/ztest.pl

  • Committer: Bazaar Package Importer
  • Author(s): Chris Lamb
  • Date: 2007-12-02 23:26:00 UTC
  • mfrom: (1.1.3 upstream)
  • Revision ID: james.westby@ubuntu.com-20071202232600-b7d3d1i4kzfqmipf
Tags: 5.6.47-1
* New upstream version (Closes: #295209, #308325, #425580)
* New maintainer (Closes: #422576)
* Bump Debhelper compatibility to 5
* debian/rules:
   * Update config.sub and config.guess from autotools-dev
       (Closes: #408076, #414181)
   * Desist from blindly ignoring "clean" target
* debian/control:
   * Use ${binary:Version} instead of ${Source-Version}
   * Add new Homepage: field
   * Add XS-Vcs-* fields
* Change ".menu" sections from
     "Apps/Programming" -> "Applications/Programming"
* Documentation:
   * Remove some SGML documentation now missing from upstream
   * Add Sicstus and SWI-Prolog v4.8 -related XPCE documentation

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
:- module(ztest,
 
2
          [
 
3
          ]).
 
4
:- asserta(user:file_search_path(foreign, '.')).
 
5
:- asserta(user:file_search_path(foreign, '../clib')).
 
6
:- asserta(user:file_search_path(library, '.')).
 
7
:- asserta(user:file_search_path(library, '../plunit')).
 
8
:- asserta(user:file_search_path(library, '../clib')).
 
9
 
 
10
:- use_module(user:library(zlib)).
 
11
:- use_module(user:library(plunit)).
 
12
:- use_module(user:library(readutil)).
 
13
:- use_module(user:library(socket)).
 
14
:- use_module(library(debug)).
 
15
 
 
16
read_file_to_codes(File, Codes) :-
 
17
        open(File, read, In),
 
18
        call_cleanup(read_stream_to_codes(In, Codes), close(In)).
 
19
 
 
20
:- begin_tests(zlib).
 
21
 
 
22
%       gunzip: can we read a file compressed with gzip
 
23
 
 
24
test(gunzip,
 
25
     [ setup(shell('gzip < ztest.pl > plunit-tmp.gz')),
 
26
       cleanup(delete_file('plunit-tmp.gz'))
 
27
     ]) :-
 
28
        gzopen('plunit-tmp.gz', read, ZIn),
 
29
        call_cleanup(read_stream_to_codes(ZIn, Codes0), close(ZIn)),
 
30
        read_file_to_codes('ztest.pl', Codes1),
 
31
        Codes0 == Codes1.
 
32
        
 
33
%       gzip: Can gunzip read our compressed file
 
34
 
 
35
test(gzip,
 
36
     [ cleanup(delete_file('plunit-tmp.gz'))
 
37
     ]) :-
 
38
        read_file_to_codes('ztest.pl', Codes),
 
39
        gzopen('plunit-tmp.gz', write, ZOut),
 
40
        format(ZOut, '~s', [Codes]),
 
41
        close(ZOut),
 
42
        read_file_to_codes(pipe('gunzip < plunit-tmp.gz'), Codes1),
 
43
        Codes == Codes1.
 
44
 
 
45
%       deflate: test read/write of deflate format
 
46
 
 
47
test(deflate,
 
48
     [ cleanup(delete_file('plunit-tmp.z'))
 
49
     ]) :-
 
50
        read_file_to_codes('ztest.pl', Codes),
 
51
        open('plunit-tmp.z', write, Out),
 
52
        zopen(Out, ZOut, []),
 
53
        format(ZOut, '~s', [Codes]),
 
54
        close(ZOut),
 
55
        open('plunit-tmp.z', read, In),
 
56
        zopen(In, ZIn, []),
 
57
        read_stream_to_codes(ZIn, Codes1),
 
58
        close(ZIn),
 
59
        Codes == Codes1.
 
60
 
 
61
%       zstream: test compressed stream flushing and processing
 
62
 
 
63
test(zstream) :-
 
64
        server(Port),
 
65
        debug(server, 'Server at ~w~n', [Port]),
 
66
        client(Port),
 
67
        thread_join(server, Exit),
 
68
        Exit == true.
 
69
 
 
70
server(Port) :-
 
71
        tcp_socket(S),
 
72
        tcp_bind(S, Port),
 
73
        tcp_listen(S, 5),
 
74
        tcp_open_socket(S, AcceptFd, _),
 
75
        thread_create(process(AcceptFd), _, [alias(server)]).
 
76
 
 
77
process(AcceptFd) :-
 
78
        tcp_accept(AcceptFd, S2, _Peer),
 
79
        tcp_open_socket(S2, ZIn, ZOut),
 
80
        zopen(ZIn, In, []),
 
81
        zopen(ZOut, Out, []),
 
82
        loop(In, Out),
 
83
        close(Out), close(In).
 
84
 
 
85
loop(In, Out) :-
 
86
        read(In, Term),
 
87
        debug(server, 'Read ~w', [Term]),
 
88
        format(Out, '~q.~n', [Term]),
 
89
        flush_output(Out),
 
90
        debug(server, 'Replied', [Term]),
 
91
        (   Term == quit
 
92
        ->  true
 
93
        ;   loop(In, Out)
 
94
        ).
 
95
 
 
96
client(Port) :-
 
97
        integer(Port), !,
 
98
        client(localhost:Port).
 
99
client(Address) :-
 
100
        tcp_socket(S),
 
101
        tcp_connect(S, Address),
 
102
        tcp_open_socket(S, ZIn, ZOut),
 
103
        zopen(ZIn, In, []),
 
104
        zopen(ZOut, Out, []),
 
105
        process_client(In, Out),
 
106
        close(Out),
 
107
        close(In).
 
108
 
 
109
process_client(In, Out) :-
 
110
        forall(between(0, 50, X),
 
111
               (   format(Out, '~q.~n', [X]),
 
112
                   flush_output(Out),
 
113
                   read(In, Term),
 
114
                   %put(user_error, .),
 
115
                   (   X == Term
 
116
                   ->  true
 
117
                   ;   format('Wrong reply~n'),
 
118
                       fail
 
119
                   )
 
120
               )),
 
121
        format(Out, 'quit.~n', []).
 
122
 
 
123
 
 
124
                 /*******************************
 
125
                 *            BIG DATA          *
 
126
                 *******************************/
 
127
 
 
128
test(big) :-
 
129
        forall(between(1, 5, I),
 
130
               (   Max is 10**I,
 
131
                   big(_, Max))).
 
132
 
 
133
big(Port, N):- 
 
134
        tcp_socket(SockFd),
 
135
        tcp_setopt(SockFd, reuseaddr),
 
136
        tcp_bind(SockFd, Port),
 
137
        tcp_listen(SockFd, 5),
 
138
        thread_create(client_test(Port, N), Client, []),
 
139
        tcp_accept(SockFd, ClientFd, _Peer),
 
140
        tcp_open_socket(ClientFd, InStream, OutStream),
 
141
        zopen(OutStream, ZOut, [close_parent(false), format(deflate)]),
 
142
        send_data(1, N, ZOut),
 
143
        close(InStream),
 
144
        character_count(ZOut, RawCnt),
 
145
        close(ZOut),
 
146
        character_count(OutStream, CompressedCnt),
 
147
        debug(zlib, 'compressed ~d into ~d bytes~n',
 
148
              [RawCnt, CompressedCnt]),
 
149
        close(OutStream),
 
150
        tcp_close_socket(SockFd),
 
151
        thread_join(Client, Status),
 
152
        assertion(Status == true).
 
153
        
 
154
send_data(I, N, ZOut) :-
 
155
        I =< N, !,
 
156
        format(ZOut, '~d.~n', [I]),
 
157
        I2 is I + 1,
 
158
        send_data(I2, N, ZOut).
 
159
send_data(_, _, _).
 
160
 
 
161
 
 
162
client_test(Port, N) :-
 
163
        tcp_socket(SockFd),
 
164
        tcp_connect(SockFd, localhost:Port),
 
165
        tcp_open_socket(SockFd, In, Out),
 
166
        zopen(In, ZIn, [format(deflate)]),
 
167
        get_data(ZIn, N),
 
168
        close(ZIn),
 
169
        close(Out).
 
170
        
 
171
get_data(ZIn, _) :-
 
172
        debugging(data), !,
 
173
        between(0, inf, X),
 
174
        get_byte(ZIn, C),
 
175
        (   C == -1
 
176
        ->  !,
 
177
            format('EOF at ~w~n', [X])
 
178
        ;   put_byte(C),
 
179
            fail
 
180
        ).
 
181
get_data(ZIn, N) :-
 
182
        between(1, inf, X),
 
183
        read(ZIn, Term),
 
184
        (   Term == end_of_file
 
185
        ->  !,
 
186
            assertion(X =:= N + 1)
 
187
        ;   assertion(Term == X),
 
188
            fail
 
189
        ).
 
190
 
 
191
:- end_tests(zlib).