1/*   telegrambot
    2     Author: Giménez, Christian.
    3
    4     Copyright (C) 2019 Giménez, Christian
    5
    6     This program is free software: you can redistribute it and/or modify
    7     it under the terms of the GNU General Public License as published by
    8     the Free Software Foundation, either version 3 of the License, or
    9     at your option) any later version.
   10
   11     This program is distributed in the hope that it will be useful,
   12     but WITHOUT ANY WARRANTY; without even the implied warranty of
   13     MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   14     GNU General Public License for more details.
   15
   16     You should have received a copy of the GNU General Public License
   17     along with this program.  If not, see <http://www.gnu.org/licenses/>.
   18
   19     6 aug 2019
   20*/
   21:- module(telegrambot, [
   22	      use_token/1,
   23	      get_chat/2,
   24	      get_me/1,
   25	      get_updates/2,
   26	      send_message/4,
   27	      command_handler/2,
   28	      bot_loop/0
   29          ]).

telegrambot: API for Telegram

Predicates to use the Telegram Bot API.

The following example sends a "Message Received" text in response to the /start command from any client:

:- use_module(library(telegrambot)).

use_token('the bot Token from the BotFather here').

get_chat_id(json(Lst), Id) :-
  member(message=json(A), Lst),
  member(chat=json(B), A),
  member(id=Id, B).

start_handler(Message, Params) :-
  write('start received'),
  write(Message),
  get_chat_id(Message, ChatId),
  send_message(ChatId, 'Message Received', [], _).

command_handler(start, start_handler).

main_pred :-
  bot_loop.

:- initialization(main_pred, main).
author
- Gimenez, Christian
license
- GPLv3 */
   65:- license(gplv3).   66
   67:- use_module(library(uri)).   68:- use_module(library(http/http_client)).   69:- use_module(library(http/http_json)).   70:- use_module(library(dcg/basics)).
 token(?Token:term)
The token used for registering the bot with Telegram. */
   77:- dynamic token/1.   78
   79:- dynamic bot_command/2.   80:- dynamic bot_text/2.
 use_token(+Token:term)
Set the token. This is needed for authenticating the bot with Telegram. */
   87use_token(Token) :-
   88    retractall(telegrambot:token(_)),
   89    asserta(telegrambot:token(Token)).
 url(?URL:term)
Is the URL used by Telegram. */
   97url(Url) :-
   98    telegrambot:token(Token),
   99    format(atom(Url), 'https://api.telegram.org/bot~s/', [Token]).
  100
  101method_url(Url, Method, Params) :-
  102    url(BaseUrl),
  103    uri_query_components(Query, Params),
  104    format(atom(Url), '~s~s?~s', [BaseUrl, Method, Query]).
  105
  106get_chat(Chat_id, Chat) :-
  107    method_url(Url, 'getChat', [chat_id=Chat_id]),
  108    http_get(Url, Chat, []).
  109
  110get_me(Info) :-
  111    method_url(Url, 'getMe', []),
  112    http_get(Url, Info, []).
  113
  114get_updates(Updates, Options) :-
  115    method_url(Url, 'getUpdates', Options),
  116    http_get(Url, Updates, []).
 send_message(+Chat_id:number, +Text:term, +Options:list, -Return:term)
Instruct the bot to send a message.

Example:

send_message(12345, 'Hello *world*', [parse_mode='Markdown'], Return).
Arguments:
Chat_id- A term or number.
Text- A term with the text to send.
Options- A list of a=b elements.
Return- A json/1 term with the answer parsed. */
  134send_message(Chat_id, Text, Options, Return) :-
  135    append([
  136		  chat_id=Chat_id,
  137		  text=Text
  138	      ],
  139	   Options,
  140	   Params),
  141    method_url(Url, 'sendMessage', Params),
  142    http_get(Url, Return, []).
 command_handler(+Command:term, +Pred:term)
Register a command handler.
Arguments:
Command- The command name (without /).
Pred- The predicate name to be executed. It must posses two parameters, the command name term and the parameters. */
  154command_handler(Command, Pred) :-
  155    asserta(bot_command(Command, Pred)).
 text_handler(+DCG:term, +Pred:term)
*/
  163text_handler(DCG, Pred) :-
  164    asserta(bot_text(DCG, Pred)).
 command(?Cmd:term, ?Params:list)// is det
Matches the command syntax.

A command starts with '/' symbol, the name and can have parameters.

Arguments:
Cmd- The comand name.
Params- The list of parameters (each one in term format). */
  177command(Cmd, []) --> "/", nonblanks(CmdS), blanks, eos, !,
  178		   {term_string(Cmd, CmdS)}.
  179command(Cmd, Params) --> "/", nonblanks(CmdS),
  180 		       blanks, string(Params), eos, !,
  181		       {term_string(Cmd, CmdS)}.
 is_command(+MsgData:pred, ?Command:term, ?Params:list) is det
True iff MsgData is the json message that represents a command text.
Arguments:
MsgData- A Json parsed data from the get_updates.
Command- The command name.
Params- The list of params in term format. */
  193is_command(json(Data), Command, Params) :-
  194    member(message=json(MsgData), Data),!,
  195    member(text=CmdText, MsgData),!,
  196    atom_codes(CmdText, CmdTextCodes),
  197    phrase(command(Command, Params), CmdTextCodes, _Rest).
 process_update_message(+Message:pred)
Call the appropiate handle depending if the Message is a command or a chat.
Arguments:
Message- A json/1 predicate returned by get_updates/2. */
  207process_update_message(Message) :-
  208    is_command(Message, Command, Params),
  209    bot_command(Command, Pred),!,
  210    ignore(call(Pred, Message, Params)).
 process_update_list(+Lst_Updates:list)
Process a list of Update structures in JSON format.
Arguments:
Lst_Updates- The list of json/1 terms. */
  219process_update_list(Lst) :-
  221    maplist(process_update_message, Lst)
  221.
  222
  229process_update_json(json(Lst)) :-
  230    member(result=Res, Lst),
  231    process_update_list(Res).
 bot_loop
Start the loop. Gathers the last messages and process them. */
  238bot_loop :-
  239    repeat,
  240    get_updates(Updates, []),
  241    process_update_json(Updates),
  242    sleep(30),
  243    fail