1:- module(irc_client_utilities, [
    2	run_det/1,
    3	priv_msg/3,
    4	priv_msg/4,
    5	priv_msg_rest/4,
    6	priv_msg_rest/5,
    7	priv_msg_paragraph/4
    8]).    9
   10
   11:- use_module(irc_client_info).   12:- use_module(irc_client_dispatch).   13:- use_module(library(func)).   14:- use_module(library(lambda)).   15:- use_module(library(dcg/basics)).   16:- use_module(library(predicate_options)).   17:- use_module(library(list_util)).   18
   19
   20:- meta_predicate run_det(0).   21run_det(Goal) :-
   22	ignore((Goal, fail)).
   23
   24
   25%--------------------------------------------------------------------------------%
   26% Sending Messages
   27%--------------------------------------------------------------------------------%
   28
   29
   30:- predicate_options(priv_msg/3, 3, [
   31	auto_nl(boolean),
   32	at_most(nonneg),
   33	encoding(encoding)
   34]).
 priv_message(+Id, +Text, +Recipient) is det
This is a convenience predicate for sending private messages to recipients on IRC channels. If there are any newlines they will be converted into individual messages (i.e. paragraph style handling). If the user is attempting to send a message longer than the limit they can send on one line, the message will be automatically segmented into multiple messages. The message will be delivered on the connection alias Id.
   46priv_msg(Id, Text, Recipient) :-
   47	priv_msg_rest(Id, Text, Recipient, _, [auto_nl(true)]).
 priv_msg(+Id, +Text, +Recipient, :Options) is det
Like priv_msg/3 except with explicit options.

Options include:

auto_nl(Boolean)
Boolean is true or false, if true messages will be automatically segmented for complete output via IRC (in order to avoid truncation by char limits).
at_most(N)
where N is the maximum amount of lines to print. Default is entire paragraph.
   61priv_msg(Id, Text, Recipient, Options) :-
   62	priv_msg_rest(Id, Text, Recipient, _, Options).
 priv_msg_rest(+Id, +Text, +Recipient, -Rest) is det
Same as priv_msg/3, except Rest is the remainder of a message.
   68priv_msg_rest(Id, Text, Recipient, Rest) :-
   69	priv_msg_rest(Id, Text, Recipient, Rest, [auto_nl(true)]).
   70
   71
   72%% priv_msg_rest(+Id, +Text, +Recipient, -Rest, :Options) is det.
   73%
   74%  Same as priv_msg/3, except Rest is unified with the remainder of a message
   75%  after printing out at most, N amount of lines specified by the user.
   76
   77priv_msg_rest(Id, Text, Recipient, Rest, Options) :-
   78	Send_msg = (\Msg^send_msg(Id, priv_msg, Msg, Recipient)),
   79	option(encoding(Encoding), Options, utf8),
   80	get_irc_write_stream(Id, Stream),
   81	set_stream(Stream, encoding(Encoding)),
   82	priv_msg_paragraph(Id, Text, Recipient, Paragraph),
   83	(	option(auto_nl(true), Options, true)
   84	->	option(at_most(Limit), Options, length $ Paragraph),  % auto-nl
   85		split_at(Limit, Paragraph, P, Rest),
   86		maplist(Send_msg, P)
   87	;	maplist(Send_msg, Paragraph) % no auto-nl
   88	),
   89	(	stream_property(Stream, encoding(utf8))
   90	->	true
   91	;	set_stream(Stream, encoding(utf8))
   92	).
   93
   94
   95%% priv_msg_paragraph(+Id, +Text, +Recipient, -Paragraph) is det.
   96%
   97%  True if Paragraph is a string list that represents a string formatted to write
   98%  an entire IRC message, filtering carriage returns and empty strings. The
   99%  string will be split into lists of strings that represent individually
  100%  segmented lines.
  101
  102priv_msg_paragraph(Id, Text, Recipient, Paragraph) :-
  103	min_msg_len(Id, Min),
  104	string_length(Recipient, N0),
  105	N is N0 + Min,
  106	Length is 508 - N,
  107	insert_nl_at(Length, string_codes $ Text, Formatted),
  108	Paragraph = exclude(\Str^(Str="", ! ; Str = "\r")) $ split_string(Formatted, "\n") $ "".
  109
  110
  111insert_nl_at(Num, Codes, Formatted) :-
  112	insert_nl_at(Codes, F, Num, Num),
  113	string_codes(Formatted, F).
  114
  115insert_nl_at([], [], _, _).
  116insert_nl_at([X|Xs], [X|Ys], N, N0) :-
  117	(	X = 10
  118	->	insert_nl_at(Xs, Ys, N, N), !
  119	;	N0 > 1,
  120		!,
  121		N1 is N0-1,
  122		insert_nl_at(Xs, Ys, N, N1)
  123	).
  124
  125insert_nl_at([X|Xs], [X,10|Ys], N, 1) :-
  126	insert_nl_at(Xs, Ys, N, N)