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 ]).
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)).
77:- dynamic token/1. 78 79:- dynamic bot_command/2. 80:- dynamic bot_text/2.
87use_token(Token) :-
88 retractall(telegrambot:token(_)),
89 asserta(telegrambot:token(Token)).
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, []).
Example:
send_message(12345, 'Hello *world*', [parse_mode='Markdown'], Return).
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, []).
154command_handler(Command, Pred) :-
155 asserta(bot_command(Command, Pred)).
163text_handler(DCG, Pred) :-
164 asserta(bot_text(DCG, Pred)).
A command starts with '/' symbol, the name and can have parameters.
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)}.
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).
207process_update_message(Message) :-
208 is_command(Message, Command, Params),
209 bot_command(Command, Pred),!,
210 ignore(call(Pred, Message, Params)).
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).
238bot_loop :-
239 repeat,
240 get_updates(Updates, []),
241 process_update_json(Updates),
242 sleep(30),
243 fail
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: