fix to thread support.
This commit is contained in:
@@ -150,7 +150,7 @@ check-process::
|
||||
( cd $(srcdir) && $(PL) -q -f test_process.pl -g true -t test_process )
|
||||
|
||||
check-read::
|
||||
( cd $(srcdir) && $(PL) -q -f test_readutil.pl -g true -t test_readutilw )
|
||||
( cd $(srcdir) && $(PL) -q -f test_readutil.pl -g true -t test_readutil )
|
||||
|
||||
################################################################
|
||||
# Documentation
|
||||
|
@@ -43,4 +43,7 @@
|
||||
memory_file_to_codes/3, % +Handle, -CodeList, +Encoding
|
||||
utf8_position_memory_file/3 % +Handle, -Here, -Size
|
||||
]).
|
||||
|
||||
:- use_module(library(shlib)).
|
||||
|
||||
:- use_foreign_library(foreign(memfile)).
|
||||
|
@@ -41,6 +41,7 @@
|
||||
process_kill/2 % +PID, -Signal
|
||||
]).
|
||||
:- use_module(library(shlib)).
|
||||
:- use_module(library(error)).
|
||||
:- use_module(library(lists)).
|
||||
:- use_module(library(option)).
|
||||
|
||||
|
@@ -37,6 +37,7 @@
|
||||
stream_pool_main_loop/0
|
||||
]).
|
||||
:- use_module(library(quintus)).
|
||||
:- use_module(library(debug)).
|
||||
|
||||
:- meta_predicate
|
||||
add_stream_to_pool(+, :).
|
||||
|
@@ -34,6 +34,8 @@
|
||||
]).
|
||||
:- asserta(user:file_search_path(foreign, '.')).
|
||||
|
||||
:- use_module(library(shlib)).
|
||||
|
||||
:- use_module(memfile).
|
||||
:- use_module(library(utf8)).
|
||||
|
||||
@@ -174,16 +176,16 @@ report_failed :-
|
||||
|
||||
runtest(Name) :-
|
||||
format('Running test set "~w" ', [Name]),
|
||||
flush,
|
||||
flush_output,
|
||||
functor(Head, Name, 1),
|
||||
nth_clause(Head, _N, R),
|
||||
clause(Head, _, R),
|
||||
( catch(Head, Except, true)
|
||||
-> ( var(Except)
|
||||
-> put(.), flush
|
||||
-> put(.), flush_output
|
||||
; Except = blocked(Reason)
|
||||
-> assert(blocked(Head, Reason)),
|
||||
put(!), flush
|
||||
put(!), flush_output
|
||||
; test_failed(R, Except)
|
||||
)
|
||||
; test_failed(R, fail)
|
||||
|
@@ -119,6 +119,8 @@ action(quit, _In, Out) :-
|
||||
* CLIENT SIDE *
|
||||
*******************************/
|
||||
|
||||
:- dynamic echo/1, slow/1, quit/1.
|
||||
|
||||
:- dynamic
|
||||
client/2.
|
||||
|
||||
@@ -182,7 +184,6 @@ reply(T, _, T).
|
||||
|
||||
receive_loop(Socket, Queue) :-
|
||||
repeat,
|
||||
writeln(hellorec),
|
||||
udp_receive(Socket, Data, From, [as(atom)]),
|
||||
thread_send_message(Queue, got(Data, From)),
|
||||
Data == quit, !,
|
||||
@@ -211,9 +212,7 @@ run_udp :-
|
||||
thread_get_message(got(X, _)),
|
||||
udp_send(S, 'quit', localhost:Port, []),
|
||||
thread_get_message(got(Q, _)),
|
||||
writeln(hello2),
|
||||
thread_join(ThreadId, Exit),
|
||||
writeln(hello2),
|
||||
tcp_close_socket(S),
|
||||
assertion(X=='hello world'),
|
||||
assertion(Q=='quit'),
|
||||
@@ -261,16 +260,16 @@ report_failed :-
|
||||
|
||||
runtest(Name) :-
|
||||
format('Running test set "~w" ', [Name]),
|
||||
flush,
|
||||
flush_output,
|
||||
functor(Head, Name, 1),
|
||||
nth_clause(Head, _N, R),
|
||||
clause(Head, _N, R),
|
||||
clause(Head, _, R),
|
||||
( catch(Head, Except, true)
|
||||
-> ( var(Except)
|
||||
-> put(.), flush
|
||||
-> put(.), flush_output
|
||||
; Except = blocked(Reason)
|
||||
-> assert(blocked(Head, Reason)),
|
||||
put(!), flush
|
||||
put(!), flush_output
|
||||
; test_failed(R, Except)
|
||||
)
|
||||
; test_failed(R, fail)
|
||||
|
@@ -46,6 +46,9 @@
|
||||
uri_file_name/2, % ?URI, ?Path
|
||||
uri_iri/2 % ?URI, ?IRI
|
||||
]).
|
||||
|
||||
:- use_module(library(shlib)).
|
||||
|
||||
:- use_foreign_library(foreign(uri)).
|
||||
|
||||
/** <module> Process URIs
|
||||
|
Reference in New Issue
Block a user