~gdanix/telegram-bot-simple

d89c8cbfb3bb8d9a50ee9cce31904d7ef903d601 — Daniel Trujillo Viedma 2 years ago fb56661
Initial support for inline mode
M src/Telegram/Bot/API.hs => src/Telegram/Bot/API.hs +3 -3
@@ 11,8 11,8 @@ module Telegram.Bot.API (
  module Telegram.Bot.API.UpdatingMessages,
--   -- * Stickers
--   module Telegram.Bot.API.Stickers,
--   -- * Inline mode
--   module Telegram.Bot.API.InlineMode,
  -- * Inline mode
  module Telegram.Bot.API.InlineMode,
--   -- * Payments
--   module Telegram.Bot.API.Payments,
--   -- * Games


@@ 25,6 25,6 @@ import           Telegram.Bot.API.Methods
import           Telegram.Bot.API.Types
import           Telegram.Bot.API.UpdatingMessages
-- import Telegram.Bot.API.Stickers
-- import Telegram.Bot.API.InlineMode
import Telegram.Bot.API.InlineMode
-- import Telegram.Bot.API.Payments
-- import Telegram.Bot.API.Games

M src/Telegram/Bot/API/GettingUpdates.hs => src/Telegram/Bot/API/GettingUpdates.hs +2 -1
@@ 18,6 18,7 @@ import           Servant.Client                  hiding (Response)
import           Telegram.Bot.API.Internal.Utils
import           Telegram.Bot.API.MakingRequests
import           Telegram.Bot.API.Types
import           Telegram.Bot.API.InlineMode

-- ** 'Update'



@@ 33,7 34,7 @@ data Update = Update
  , updateChannelPost       :: Maybe Message -- ^ New incoming channel post of any kind — text, photo, sticker, etc.
  , updateEditedChannelPost :: Maybe Message -- ^ New version of a channel post that is known to the bot and was edited

--  , updateInlineQuery :: Maybe InlineQuery -- ^ New incoming inline query
  , updateInlineQuery :: Maybe InlineQuery -- ^ New incoming inline query
--   , updateChosenInlineResult :: Maybe ChosenInlineResult -- ^ The result of an inline query that was chosen by a user and sent to their chat partner. Please see our documentation on the feedback collecting for details on how to enable these updates for your bot.

  , updateCallbackQuery     :: Maybe CallbackQuery -- ^ New incoming callback query

M src/Telegram/Bot/API/InlineMode.hs => src/Telegram/Bot/API/InlineMode.hs +61 -0
@@ 1,1 1,62 @@
{-# LANGUAGE DataKinds                  #-}
{-# LANGUAGE DeriveGeneric              #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings          #-}
{-# LANGUAGE TemplateHaskell            #-}
{-# LANGUAGE TypeApplications           #-}
{-# LANGUAGE TypeOperators              #-}
module Telegram.Bot.API.InlineMode where

import           Data.Aeson                      (FromJSON (..), ToJSON (..))
import           Data.Hashable                   (Hashable)
import           Data.Proxy
import           Data.Text                       (Text)
import           GHC.Generics                    (Generic)

import           Servant.API
import           Servant.Client                  hiding (Response)
import           Servant.Multipart

import           Telegram.Bot.API.Internal.Utils
import           Telegram.Bot.API.MakingRequests
import           Telegram.Bot.API.Types
import           Telegram.Bot.API.InlineMode.InlineQueryResult
import           Telegram.Bot.API.InlineMode.InputMessageContent
-- * Available types
-- ** User
--
-- | This object represents an incoming inline query. When the user sends an empty query, your bot could return some default or trending results.
--
-- <https://core.telegram.org/bots/api#inline-mode>
data InlineQuery = InlineQuery
  { inlineQueryId       :: InlineQueryId -- ^ Unique query identifier
  , inlineQueryFrom     :: User -- ^ Sender
  , inlineQueryLocation :: Maybe Location -- ^ For bots that require user location, sender location
  , inlineQueryQuery    :: Text -- ^ Text of the query, up to 256 characters
  , inlineQueryOffset   :: Text -- ^ Offset of the results to be returned, can be controlled by bot
  } deriving (Generic, Show)

-- | Unique identifier for this query
newtype InlineQueryId = InlineQueryId Text
  deriving (Eq, Show, ToJSON, FromJSON, Hashable, Generic)


-- * Available methods

-- ** answerInlineQuery

type AnswerInlineQuery
  = "answerInlineQuery" :> ReqBody '[JSON] AnswerInlineQueryRequest :> Post '[JSON] (Response Bool)

answerInlineQuery :: AnswerInlineQueryRequest -> ClientM (Response Bool)
answerInlineQuery = client (Proxy @AnswerInlineQuery)

data AnswerInlineQueryRequest = AnswerInlineQueryRequest
  { answerInlineQueryRequestInlineQueryId :: InlineQueryId
  , answerInlineQueryRequestResults       :: [InlineQueryResult]
  } deriving (Generic)

instance ToJSON AnswerInlineQueryRequest where toJSON = gtoJSON
instance FromJSON AnswerInlineQueryRequest where parseJSON = gparseJSON

deriveJSON' ''InlineQuery

A src/Telegram/Bot/API/InlineMode/InlineQueryResult.hs => src/Telegram/Bot/API/InlineMode/InlineQueryResult.hs +87 -0
@@ 0,0 1,87 @@
{-# LANGUAGE DeriveGeneric              #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings          #-}
module Telegram.Bot.API.InlineMode.InlineQueryResult where

import           Data.Aeson                      (FromJSON (..), ToJSON (..), Value (String))
import           Data.Hashable                   (Hashable)
import           Data.Text                       (Text)
import           GHC.Generics                    (Generic)

import           Telegram.Bot.API.Internal.Utils
import           Telegram.Bot.API.InlineMode.InputMessageContent



-- | This object represents one result of an inline query
data InlineQueryResult = InlineQueryResult
  { inlineQueryResultType     :: InlineQueryResultType -- ^ Type of the result
  , inlineQueryResultId :: InlineQueryResultId -- ^ Unique identifier for this result, 1-64 Bytes
  , inlineQueryResultTitle :: Maybe Text -- ^ Title of the result (only valid for "Article", "Photo", "Gif", "Mpeg4Gif", "Video", "Audio", "Voice", "Document", "Location", "Venue", "CachedPhoto", "CachedGif", "CachedMpeg4Gif", "CachedDocument", "CachedVideo", "CachedVoice" types of results)
  , inlineQueryResultInputMessageContent :: Maybe InputMessageContent
--  , inlineQueryResultContact  :: Maybe Contact
  } deriving (Generic, Show)

newtype InlineQueryResultId = InlineQueryResultId Text
  deriving (Eq, Show, Generic, ToJSON, FromJSON, Hashable)

instance ToJSON InlineQueryResult where toJSON = gtoJSON
instance FromJSON InlineQueryResult where parseJSON = gparseJSON




-- | Type of inline query result
data InlineQueryResultType
  = InlineQueryResultCachedAudio
  | InlineQueryResultCachedDocument
  | InlineQueryResultCachedGif
  | InlineQueryResultCachedMpeg4Gif
  | InlineQueryResultCachedPhoto
  | InlineQueryResultCachedSticker
  | InlineQueryResultCachedVideo
  | InlineQueryResultCachedVoice
  | InlineQueryResultArticle
  | InlineQueryResultAudio
  | InlineQueryResultContact
  | InlineQueryResultGame
  | InlineQueryResultDocument
  | InlineQueryResultGif
  | InlineQueryResultLocation
  | InlineQueryResultMpeg4Gif
  | InlineQueryResultPhoto
  | InlineQueryResultVenue
  | InlineQueryResultVideo
  | InlineQueryResultVoice
  deriving (Eq, Show, Generic)

getType :: InlineQueryResultType -> Text
getType InlineQueryResultCachedAudio = "audio"
getType InlineQueryResultCachedDocument = "document"
getType InlineQueryResultCachedGif = "gif"
getType InlineQueryResultCachedMpeg4Gif = "mpeg4_gif"
getType InlineQueryResultCachedPhoto = "photo"
getType InlineQueryResultCachedSticker = "sticker"
getType InlineQueryResultCachedVideo = "video"
getType InlineQueryResultCachedVoice = "voice"
getType InlineQueryResultArticle = "article"
getType InlineQueryResultAudio = "audio"
getType InlineQueryResultContact = "contact"
getType InlineQueryResultGame = "game"
getType InlineQueryResultDocument = "document"
getType InlineQueryResultGif = "gif"
getType InlineQueryResultLocation = "location"
getType InlineQueryResultMpeg4Gif = "mpeg4_gif"
getType InlineQueryResultPhoto = "photo"
getType InlineQueryResultVenue = "venue"
getType InlineQueryResultVideo = "video"
getType InlineQueryResultVoice = "voice"


instance ToJSON InlineQueryResultType where
  toJSON = String . getType

instance FromJSON InlineQueryResultType where parseJSON = gparseJSON




A src/Telegram/Bot/API/InlineMode/InputMessageContent.hs => src/Telegram/Bot/API/InlineMode/InputMessageContent.hs +53 -0
@@ 0,0 1,53 @@
{-# LANGUAGE DeriveGeneric              #-}
module Telegram.Bot.API.InlineMode.InputMessageContent (InputMessageContent(..), defaultInputTextMessageContent, defaultInputLocationMessageContent) where

import           Data.Aeson                      (FromJSON (..), ToJSON (..))
import           Data.Text                       (Text)
import           GHC.Generics                    (Generic)

import           Telegram.Bot.API.Internal.Utils


-- | Represents the content of a text message to be sent as the result of an inline query.
data InputMessageContent =
  InputTextMessageContent -- ^ Represents the [content](https://core.telegram.org/bots/api#inputmessagecontent) of a text message to be sent as the result of an inline query.
  { inputMessageContentMessageText :: Text -- ^ Text of the message to be sent, 1-4096 characters
  , inputMessageContentParseMode :: Maybe Text -- ^ Mode for parsing entities in the message text. See [formatting options](https://core.telegram.org/bots/api#formatting-options) for more details.
  , inputMessageContentDisableWebPagePrefiew :: Maybe Bool -- ^ Disables link previews for links in the sent message
  }
  | InputLocationMessageContent                                      -- ^ Represents the [content](https://core.telegram.org/bots/api#inputmessagecontent) of a location message to be sent as the result of an inline query.
  { inputMessageContentLatitude :: Float                     -- ^ Latitude of the location in degrees
  , inputMessageContentLongitude :: Float                    -- ^ Longitude of the location in degrees
  , inputMessageContentHorizontalAccuracy :: Maybe Float     -- ^ The radius of uncertainty for the location, measured in meters; 0-1500
  , inputMessageContentLivePeriod :: Maybe Integer           -- ^ Period in seconds for which the location can be updated, should be between 60 and 86400.
  , inputMessageContentHeading :: Maybe Integer              -- ^ For live locations, a direction in which the user is moving, in degrees. Must be between 1 and 360 if specified.
  , inputMessageContentProximityAlertRadius :: Maybe Integer -- ^ For live locations, a maximum distance for proximity alerts about approaching another chat member, in meters. Must be between 1 and 100000 if specified.
  }
  | InputVenueMessageContent                              -- ^ Represents the content of a [venue](https://core.telegram.org/bots/api#inputmessagecontent) message to be sent as the result of an inline query.
  { inputMessageContentLatitude :: Float             -- ^ Latitude of the venue in degrees
  , inputMessageContentLongitude :: Float            -- ^ Longitude of the venue in degrees
  , inputMessageContentTitle :: Text                 -- ^ Name of the venue
  , inputMessageContentAddress :: Text               -- ^ Address of the venue
  , inputMessageContentFoursquareId :: Maybe Text    -- ^ Foursquare identifier of the venue, if known
  , inputMessageContentFoursquareType :: Maybe Text  -- ^ Foursquare type of the venue, if known. (For example, “arts_entertainment\/default”, “arts_entertainment\/aquarium” or “food\/icecream”.)
  , inputMessageContentGooglePlaceId :: Maybe Text   -- ^ Google Places identifier of the venue
  , inputMessageContentGooglePlaceType :: Maybe Text -- ^ Google Places type of the venue. (See [supported types](https://developers.google.com/places/web-service/supported_types).)
  }
  | InputContactMessageContent                         -- ^ Represents the [content](https://core.telegram.org/bots/api#inputmessagecontent) of a contact message to be sent as the result of an inline query.
  { inputMessageContentPhoneNumber :: Text      -- ^ Contact's phone number
  , inputMessageContentFirstName :: Text        -- ^ Contact's first name
  , inputMessageContentSecondName :: Maybe Text -- ^ Contact's last name
  , inputMessageContentVcard :: Maybe Text      -- ^ Additional data about the contact in the form of a [vCard](https://en.wikipedia.org/wiki/VCard), 0-2048 bytes
  } deriving (Generic, Show)


-- ** Helper functions to easily construct 'InputMessageContent'

defaultInputTextMessageContent :: Text -> InputMessageContent
defaultInputTextMessageContent text = InputTextMessageContent text Nothing Nothing

defaultInputLocationMessageContent :: Float -> Float -> InputMessageContent
defaultInputLocationMessageContent lat long = InputLocationMessageContent lat long Nothing Nothing Nothing Nothing 

instance ToJSON InputMessageContent where toJSON = gtoJSON
instance FromJSON InputMessageContent where parseJSON = gparseJSON

M telegram-bot-simple.cabal => telegram-bot-simple.cabal +2 -0
@@ 35,6 35,8 @@ library
      Telegram.Bot.API.Games
      Telegram.Bot.API.GettingUpdates
      Telegram.Bot.API.InlineMode
      Telegram.Bot.API.InlineMode.InlineQueryResult
      Telegram.Bot.API.InlineMode.InputMessageContent
      Telegram.Bot.API.Internal.Utils
      Telegram.Bot.API.MakingRequests
      Telegram.Bot.API.Methods