~gdanix/telegram-bot-simple

2facb47770aca20daca8d76fdf83d7ba6ad40508 — Daniel Trujillo Viedma 3 years ago d89c8cb inline_mode
Add inline mode support to EchoBot
1 files changed, 25 insertions(+), 5 deletions(-)

M examples/EchoBot.hs
M examples/EchoBot.hs => examples/EchoBot.hs +25 -5
@@ 3,15 3,19 @@ module Main where

import           Data.Text                        (Text)
import qualified Data.Text                        as Text
import           Data.Maybe

import           Telegram.Bot.API
import           Telegram.Bot.Simple
import           Telegram.Bot.Simple.UpdateParser (updateMessageText)
import           Telegram.Bot.API.InlineMode.InlineQueryResult
import           Telegram.Bot.API.InlineMode.InputMessageContent (defaultInputTextMessageContent)

type Model = ()

data Action
  = NoOp
  | InlineEcho InlineQueryId Text
  | Echo Text

echoBot :: BotApp Model Action


@@ 23,14 27,30 @@ echoBot = BotApp
  }

updateToAction :: Update -> Model -> Maybe Action
updateToAction update _ =
  case updateMessageText update of
    Just text -> Just (Echo text)
    Nothing   -> Nothing
updateToAction update _
  | isJust $ updateInlineQuery update =  do
      query <- updateInlineQuery update
      let id = inlineQueryId query
      let msg =  inlineQueryQuery query
      Just $ InlineEcho id msg
  | otherwise = case updateMessageText update of
      Just text -> Just (Echo text)
      Nothing   -> Nothing

handleAction :: Action -> Model -> Eff Action Model
handleAction action model = case action of
  NoOp -> pure model
  InlineEcho id msg -> model <# do
    liftClientM (
      answerInlineQuery (
          AnswerInlineQueryRequest
            id
            [
              InlineQueryResult InlineQueryResultArticle (InlineQueryResultId msg) (Just msg) (Just (defaultInputTextMessageContent msg))
            ]
        )
      )
    return NoOp
  Echo msg -> model <# do
    replyText msg
    return NoOp


@@ 38,7 58,7 @@ handleAction action model = case action of
run :: Token -> IO ()
run token = do
  env <- defaultTelegramClientEnv token
  startBot_ (conversationBot updateChatId echoBot) env
  startBot_ echoBot env

main :: IO ()
main = do