{-# 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 Telegram.Bot.API.Internal.Utils
import Telegram.Bot.API.MakingRequests
import Telegram.Bot.API.Types
import Telegram.Bot.API.InlineMode.InlineQueryResult
data InlineQuery = InlineQuery
{ InlineQuery -> InlineQueryId
inlineQueryId :: InlineQueryId
, InlineQuery -> User
inlineQueryFrom :: User
, InlineQuery -> Maybe Location
inlineQueryLocation :: Maybe Location
, InlineQuery -> Text
inlineQueryQuery :: Text
, InlineQuery -> Text
inlineQueryOffset :: Text
, InlineQuery -> Maybe ChatType
inlineQueryChatType :: Maybe ChatType
} deriving (forall x. Rep InlineQuery x -> InlineQuery
forall x. InlineQuery -> Rep InlineQuery x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InlineQuery x -> InlineQuery
$cfrom :: forall x. InlineQuery -> Rep InlineQuery x
Generic, Int -> InlineQuery -> ShowS
[InlineQuery] -> ShowS
InlineQuery -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InlineQuery] -> ShowS
$cshowList :: [InlineQuery] -> ShowS
show :: InlineQuery -> String
$cshow :: InlineQuery -> String
showsPrec :: Int -> InlineQuery -> ShowS
$cshowsPrec :: Int -> InlineQuery -> ShowS
Show)
newtype InlineQueryId = InlineQueryId Text
deriving (InlineQueryId -> InlineQueryId -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InlineQueryId -> InlineQueryId -> Bool
$c/= :: InlineQueryId -> InlineQueryId -> Bool
== :: InlineQueryId -> InlineQueryId -> Bool
$c== :: InlineQueryId -> InlineQueryId -> Bool
Eq, Int -> InlineQueryId -> ShowS
[InlineQueryId] -> ShowS
InlineQueryId -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InlineQueryId] -> ShowS
$cshowList :: [InlineQueryId] -> ShowS
show :: InlineQueryId -> String
$cshow :: InlineQueryId -> String
showsPrec :: Int -> InlineQueryId -> ShowS
$cshowsPrec :: Int -> InlineQueryId -> ShowS
Show, [InlineQueryId] -> Encoding
[InlineQueryId] -> Value
InlineQueryId -> Encoding
InlineQueryId -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [InlineQueryId] -> Encoding
$ctoEncodingList :: [InlineQueryId] -> Encoding
toJSONList :: [InlineQueryId] -> Value
$ctoJSONList :: [InlineQueryId] -> Value
toEncoding :: InlineQueryId -> Encoding
$ctoEncoding :: InlineQueryId -> Encoding
toJSON :: InlineQueryId -> Value
$ctoJSON :: InlineQueryId -> Value
ToJSON, Value -> Parser [InlineQueryId]
Value -> Parser InlineQueryId
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [InlineQueryId]
$cparseJSONList :: Value -> Parser [InlineQueryId]
parseJSON :: Value -> Parser InlineQueryId
$cparseJSON :: Value -> Parser InlineQueryId
FromJSON, Eq InlineQueryId
Int -> InlineQueryId -> Int
InlineQueryId -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: InlineQueryId -> Int
$chash :: InlineQueryId -> Int
hashWithSalt :: Int -> InlineQueryId -> Int
$chashWithSalt :: Int -> InlineQueryId -> Int
Hashable, forall x. Rep InlineQueryId x -> InlineQueryId
forall x. InlineQueryId -> Rep InlineQueryId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InlineQueryId x -> InlineQueryId
$cfrom :: forall x. InlineQueryId -> Rep InlineQueryId x
Generic)
type AnswerInlineQuery
= "answerInlineQuery" :> ReqBody '[JSON] AnswerInlineQueryRequest :> Post '[JSON] (Response Bool)
answerInlineQuery :: AnswerInlineQueryRequest -> ClientM (Response Bool)
answerInlineQuery :: AnswerInlineQueryRequest -> ClientM (Response Bool)
answerInlineQuery = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @AnswerInlineQuery)
data AnswerInlineQueryRequest = AnswerInlineQueryRequest
{ AnswerInlineQueryRequest -> InlineQueryId
answerInlineQueryRequestInlineQueryId :: InlineQueryId
, AnswerInlineQueryRequest -> [InlineQueryResult]
answerInlineQueryRequestResults :: [InlineQueryResult]
, AnswerInlineQueryRequest -> Maybe Seconds
answerInlineQueryCacheTime :: Maybe Seconds
, AnswerInlineQueryRequest -> Maybe Bool
answerInlineQueryIsPersonal :: Maybe Bool
, AnswerInlineQueryRequest -> Maybe Text
answerInlineQueryNextOffset :: Maybe Text
, AnswerInlineQueryRequest -> Maybe Text
answerInlineQuerySwitchPmText :: Maybe Text
, AnswerInlineQueryRequest -> Maybe Text
answerInlineQuerySwitchPmParameter :: Maybe Text
} deriving (forall x.
Rep AnswerInlineQueryRequest x -> AnswerInlineQueryRequest
forall x.
AnswerInlineQueryRequest -> Rep AnswerInlineQueryRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AnswerInlineQueryRequest x -> AnswerInlineQueryRequest
$cfrom :: forall x.
AnswerInlineQueryRequest -> Rep AnswerInlineQueryRequest x
Generic)
instance ToJSON AnswerInlineQueryRequest where toJSON :: AnswerInlineQueryRequest -> Value
toJSON = forall a (d :: Meta) (f :: * -> *).
(Generic a, GToJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
a -> Value
gtoJSON
instance FromJSON AnswerInlineQueryRequest where parseJSON :: Value -> Parser AnswerInlineQueryRequest
parseJSON = forall a (d :: Meta) (f :: * -> *).
(Generic a, GFromJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
Value -> Parser a
gparseJSON
data ChosenInlineResult = ChosenInlineResult
{ ChosenInlineResult -> InlineQueryResultId
chosenInlineResultResultId :: InlineQueryResultId
, ChosenInlineResult -> User
chosenInlineResultFrom :: User
, ChosenInlineResult -> Maybe Location
chosenInlineResultLocation :: Maybe Location
, ChosenInlineResult -> Maybe MessageId
chosenInlineResultInlineMessageId :: Maybe MessageId
, ChosenInlineResult -> InlineQueryId
chosenInlineResultQuery :: InlineQueryId
} deriving (forall x. Rep ChosenInlineResult x -> ChosenInlineResult
forall x. ChosenInlineResult -> Rep ChosenInlineResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChosenInlineResult x -> ChosenInlineResult
$cfrom :: forall x. ChosenInlineResult -> Rep ChosenInlineResult x
Generic, Int -> ChosenInlineResult -> ShowS
[ChosenInlineResult] -> ShowS
ChosenInlineResult -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChosenInlineResult] -> ShowS
$cshowList :: [ChosenInlineResult] -> ShowS
show :: ChosenInlineResult -> String
$cshow :: ChosenInlineResult -> String
showsPrec :: Int -> ChosenInlineResult -> ShowS
$cshowsPrec :: Int -> ChosenInlineResult -> ShowS
Show)
instance ToJSON ChosenInlineResult where toJSON :: ChosenInlineResult -> Value
toJSON = forall a (d :: Meta) (f :: * -> *).
(Generic a, GToJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
a -> Value
gtoJSON
instance FromJSON ChosenInlineResult where parseJSON :: Value -> Parser ChosenInlineResult
parseJSON = forall a (d :: Meta) (f :: * -> *).
(Generic a, GFromJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
Value -> Parser a
gparseJSON
deriveJSON' ''InlineQuery