:- use_module(library(charsio)). :- use_module(library(dcgs)). :- use_module(newscryer). /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - Aioe.org is a public news server. See http://www.aioe.org/ for more information. We connect on port 563 via TLS. - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */ authenticate --> connect('news.aioe.org':563), ok. /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - Example 1: Fetch high watermark (number of latest message). ?- nntp_sequence(high_message(High)). High = 7710. This suffices to build a simple notification mechanism when new messages arrive. - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */ high_message(High) --> authenticate, command("group comp.lang.prolog"), ok(Line), { once(phrase((integer(_Status),ws,integer(_Estimate),ws, integer(_Low),ws,integer(High)), Line, _)) }, done. integer(I) --> digits(Ds), !, % single solution: longest match { number_chars(I, Ds) }. digits([D|Ds]) --> [D], { char_type(D, decimal_digit) }, digits(Ds). digits([]) --> []. ws --> [W], { char_type(W, whitespace) }, ws. ws --> []. /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - Example 2: Fetch overview information starting *after* From. ?- nntp_sequence(xover(7707)). true. The overview information is written to xover.txt: 7708 Re: Parsing & Unparsing etc. 7709 Re: Parsing & Unparsing etc. 7710 comp.lang.prolog Freque etc. - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */ xover(From) --> authenticate, command("group comp.lang.prolog"), ok, command("xover ~d-", [From+1]), ok, slurp('xover.txt'), done.