1:-module(chatscript, [talk/4,
2 start_conversation/3,
3 set_chatscript_address/1]).
12:- multifile license:license/3. 13
14license:license(mit, lgpl,
15 [ comment('MIT License'),
16 url('http://opensource.org/licenses/MIT')
17 ]).
18:- license(mit). 19
20:- use_module(library(http/http_client)). 21:- use_module(library(http/http_open)). 22:- use_module(library(http/http_header)). 23
24:- dynamic server_address/1.
32set_chatscript_address(Address) :-
33 retractall(server_address(_)),
34 asserta(server_address(Address)).
47talk(User, Bot, Message, Reply) :-
48 Message \= '',
49 talk_(User, Bot, Message, Reply).
50
51talk_(User, Bot, Message, Reply) :-
52 format(string(S), '~w\x00~w\x00\~w\x00', [User, Bot, Message]),
53 server_address(Address),
54 setup_call_cleanup(
55 ( tcp_connect(Address, StreamPair, []),
56 stream_pair(StreamPair, Read, Write)),
57 ( write(Write, S),
58 flush_output(Write),
59 read_stream_to_codes(Read, Codes1),
60 delete(Codes1, 0, Codes2), 61 delete(Codes2, 0xFF, Codes3),
62 delete(Codes3, 0xFE, Codes4),
63 string_codes(Reply, Codes4)),
64 close(StreamPair)).
78start_conversation(User, Bot, Reply) :-
79 talk_(User, Bot, '', Reply)
Connection to chatscript server
http://chatscript.sourceforge.net/