1:- module(irc_client, [
    2	assert_handlers/2,
    3	connect/6,
    4	disconnect/1
    5]).    6
    7
    8:- use_module(library(socket)).    9:- use_module(library(func)).   10:- use_module(irc_client_info).   11:- reexport(irc_client_info).   12
   13:- use_module(irc_client_parser).   14:- reexport(irc_client_parser, [
   15	prefix_id/2,
   16	prefix_id/4
   17]).   18
   19:- use_module(irc_client_dispatch).   20:- reexport(irc_client_dispatch, [
   21	send_msg/2,
   22	send_msg/3,
   23	send_msg/4
   24]).   25
   26:- use_module(irc_client_utilities).   27:- reexport(irc_client_utilities, [
   28	priv_msg/3,
   29	priv_msg/4,
   30	priv_msg_rest/4,
   31	priv_msg_rest/5,
   32	priv_msg_paragraph/4
   33]).

irc_client main interface

This is the main interface to irc_client. Connections and their respective information sets are maintained here.

author
- Ebrahim Azarisooreh
license
- MIT
To be done
- More documentation of pack useage is needed, perhaps even wiki
- Add direct support for CTCP actions */
   48%--------------------------------------------------------------------------------%
   49% Connection Details
   50%--------------------------------------------------------------------------------%
 connect(+Host, +Port, +Pass, +Nick, +Names, +Chans) is nondet
Open socket on host, port, nick, user, with the specified password, names, and channels to be joined.
Arguments:
Host- An atom that represents the address of the IRC host to connect to
Port- A positive integer that represents the port to connect to
Pass- An atom that represents the password of the connection
Nick- an atom that represents the nickname of the user's connection
Names- A list containing three three atoms of the format: [Hostname, Servername, Realname]
Chans- A list of atoms, each atom representing a channel to connect to
   66connect(Host, Port, Pass, Nick, Names, Chans) :-
   67	setup_call_cleanup(
   68		setup_connection(Me, Host, Port, Pass, Nick, Names, Chans),
   69		start,
   70		disconnect(Me)
   71	).
   72
   73setup_connection(Me, Host, Port, Pass, Nick, Names, Chans) :-
   74	thread_self(Me),
   75	init_structs(Pass, Nick, Names, Chans),
   76	tcp_socket(Socket),
   77	tcp_connect(Socket, Host:Port, Stream),
   78	set_stream(Stream, timeout(300)),
   79	stream_pair(Stream, _Read, Write),
   80	assert_irc_write_stream(Me, Write),
   81	set_stream(Write, encoding(utf8)),
   82	assert_irc_stream(Me, Stream).
   83
   84start :-
   85	register_and_join,
   86	read_server_loop.
   87
   88register_and_join :-
   89	thread_self(Me),
   90	maplist(send_msg(Me), [pass, user, nick, join]).
   91
   92init_structs(P_, N_, Names, Chans_) :-
   93	thread_self(Me),
   94	Names = [Hn_, Sn_, Rn_],
   95	maplist(atom_string, Chans_, Chans),
   96	maplist(atom_string, [N_, P_, Hn_, Sn_, Rn_], Strs),
   97	Strs = [N, P, Hn, Sn, Rn],
   98	assert_connection(Me, N, P, Chans, Hn, Sn, Rn).
   99
  100
  101%---------------------------------------------------------------------------------------------------%
  102% Server Routing
  103%---------------------------------------------------------------------------------------------------%
  104
  105
  106read_server_loop :-
  107	thread_self(Me),
  108	get_irc_stream(Me, Stream),
  109	repeat,
  110		read_server(Stream),
  111		!.
  112read_server(Stream) :-
  113	read_line_to_codes(Stream, Reply),
  114	(	Reply = end_of_file
  115	->	true
  116	;	read_server_handle(Reply),
  117		fail
  118	).
  119
  120read_server_handle(Reply) :-
  121	thread_self(Me),
  122	parse_line(Reply, Msg),
  123	thread_create(run_det(process_server(Me, Msg)), _Id, [detached(true)]).
  124
  125process_server(Me, msg("PING", [], O)) :-
  126	% handle pings
  127	string_codes(Origin, O),
  128	send_msg(Me, pong, Origin).
  129process_server(Me, msg(Server, "001", _, _)) :-
  130	% get irc server and assert info
  131	retractall(get_irc_server(Me, _)),
  132	assert_irc_server(Me, Server),
  133	% request own user info
  134	connection(Me, Nick, _, _, _, _, _),
  135	send_msg(Me, who, atom_string $ Nick).
  136process_server(Me, msg(_Server, "352", Params, _)) :-
  137	% get own host and nick info
  138	\+ min_msg_len(Me, _),
  139	connection(Me, N, _, _, _, _, _),
  140	atom_string(N, Nick),
  141	Params = [_Asker, _Chan, H, Host, _, Nick|_],
  142	% calculate the minimum length for a private message and assert info
  143	format(string(Template), ':~s!~s@~s PRIVMSG :\r\n ', [Nick,H,Host]),
  144	assert_min_msg_len(Me, string_length $ Template),
  145	catch(
  146		thread_create(ping_loop(Nick, 180), _Status, [detached(true), alias(checker)]),
  147		_Any,
  148		true
  149	).
  150process_server(Me, Msg) :-
  151	% run user's custom goals
  152	handle_server(Me, [Goal|Goals]),
  153	maplist(process_msg(Me-Msg), [Goal|Goals]).
  154
  155ping_loop(Nick, Timeout) :-
  156	repeat,
  157		send_msg(irc, ping, Nick),
  158		sleep(Timeout),
  159		fail.
 assert_handlers(+Id, +Handlers) is det
Assert handlers at the toplevel, where Handlers is a potentially empty list of goals to be called as irc messages come in. This is meant to be used as a directive in the user's program; however, there are plenty of cases where it's acceptable to call this as a normal goal during runtime.
Arguments:
Id- The identity or alias of the connection; this should match the alias of the thread started to initiate the connection via connect/6
Handlers- A list of goals that are made available to irc_client. All goals should have an arity of 1, and deal with processing an Id-Msg pair that an IRC server relays to the client
throws
- instantiation_error if Id is not ground
  176assert_handlers(Id, Handlers) :-
  177	must_be(ground, Id),
  178	retractall(handle_server(Id,_)),
  179	assert_handle_server(Id, Handlers).
  180
  181
  182:- meta_predicate process_msg(+, 1).  183process_msg(Msg, Goal) :-
  184	call(Goal, Msg).
  185
  186
  187%---------------------------------------------------------------------------------------------------%
  188% Cleanup/Termination
  189%---------------------------------------------------------------------------------------------------%
 disconnect(+Id) is semidet
Issue a disconnect (quit) command, and clean up all unneeded information from the top level. This process will only be handled for the connection that contains the alias Id.
  198disconnect(Me) :-
  199	catch(send_msg(Me, quit), _E0, true),
  200	catch(thread_signal(checker, throw(abort)), _E1, true),
  201	info_cleanup(Me),
  202	retractall(get_irc_stream(Me,Stream)),
  203	(	catch(stream_property(Stream, _), _Error, fail)
  204	->	close(Stream)
  205	;	true
  206	).
  207
  208info_cleanup(Me) :-
  209	maplist(
  210		retractall,
  211		[
  212			connection(Me,_,_,_,_,_,_),
  213			min_msg_len(Me,_),
  214			handle_server(Me,_),
  215			get_irc_server(Me,_),
  216			get_irc_write_stream(Me,_)
  217		]
  218	)