{-# 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.Types (Contact)
import Telegram.Bot.API.InlineMode.InputMessageContent
data InlineQueryResult = InlineQueryResult
{ InlineQueryResult -> InlineQueryResultType
inlineQueryResultType :: InlineQueryResultType
, InlineQueryResult -> InlineQueryResultId
inlineQueryResultId :: InlineQueryResultId
, InlineQueryResult -> Maybe Text
inlineQueryResultTitle :: Maybe Text
, InlineQueryResult -> Maybe InputMessageContent
inlineQueryResultInputMessageContent :: Maybe InputMessageContent
, InlineQueryResult -> Maybe Contact
inlineQueryResultContact :: Maybe Contact
} deriving (forall x. Rep InlineQueryResult x -> InlineQueryResult
forall x. InlineQueryResult -> Rep InlineQueryResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InlineQueryResult x -> InlineQueryResult
$cfrom :: forall x. InlineQueryResult -> Rep InlineQueryResult x
Generic, Int -> InlineQueryResult -> ShowS
[InlineQueryResult] -> ShowS
InlineQueryResult -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InlineQueryResult] -> ShowS
$cshowList :: [InlineQueryResult] -> ShowS
show :: InlineQueryResult -> String
$cshow :: InlineQueryResult -> String
showsPrec :: Int -> InlineQueryResult -> ShowS
$cshowsPrec :: Int -> InlineQueryResult -> ShowS
Show)
newtype InlineQueryResultId = InlineQueryResultId Text
deriving (InlineQueryResultId -> InlineQueryResultId -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InlineQueryResultId -> InlineQueryResultId -> Bool
$c/= :: InlineQueryResultId -> InlineQueryResultId -> Bool
== :: InlineQueryResultId -> InlineQueryResultId -> Bool
$c== :: InlineQueryResultId -> InlineQueryResultId -> Bool
Eq, Int -> InlineQueryResultId -> ShowS
[InlineQueryResultId] -> ShowS
InlineQueryResultId -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InlineQueryResultId] -> ShowS
$cshowList :: [InlineQueryResultId] -> ShowS
show :: InlineQueryResultId -> String
$cshow :: InlineQueryResultId -> String
showsPrec :: Int -> InlineQueryResultId -> ShowS
$cshowsPrec :: Int -> InlineQueryResultId -> ShowS
Show, forall x. Rep InlineQueryResultId x -> InlineQueryResultId
forall x. InlineQueryResultId -> Rep InlineQueryResultId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InlineQueryResultId x -> InlineQueryResultId
$cfrom :: forall x. InlineQueryResultId -> Rep InlineQueryResultId x
Generic, [InlineQueryResultId] -> Encoding
[InlineQueryResultId] -> Value
InlineQueryResultId -> Encoding
InlineQueryResultId -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [InlineQueryResultId] -> Encoding
$ctoEncodingList :: [InlineQueryResultId] -> Encoding
toJSONList :: [InlineQueryResultId] -> Value
$ctoJSONList :: [InlineQueryResultId] -> Value
toEncoding :: InlineQueryResultId -> Encoding
$ctoEncoding :: InlineQueryResultId -> Encoding
toJSON :: InlineQueryResultId -> Value
$ctoJSON :: InlineQueryResultId -> Value
ToJSON, Value -> Parser [InlineQueryResultId]
Value -> Parser InlineQueryResultId
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [InlineQueryResultId]
$cparseJSONList :: Value -> Parser [InlineQueryResultId]
parseJSON :: Value -> Parser InlineQueryResultId
$cparseJSON :: Value -> Parser InlineQueryResultId
FromJSON, Eq InlineQueryResultId
Int -> InlineQueryResultId -> Int
InlineQueryResultId -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: InlineQueryResultId -> Int
$chash :: InlineQueryResultId -> Int
hashWithSalt :: Int -> InlineQueryResultId -> Int
$chashWithSalt :: Int -> InlineQueryResultId -> Int
Hashable)
instance ToJSON InlineQueryResult where toJSON :: InlineQueryResult -> 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 InlineQueryResult where parseJSON :: Value -> Parser InlineQueryResult
parseJSON = forall a (d :: Meta) (f :: * -> *).
(Generic a, GFromJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
Value -> Parser a
gparseJSON
data InlineQueryResultType
= InlineQueryResultCachedAudio
| InlineQueryResultCachedDocument
| InlineQueryResultCachedGif
| InlineQueryResultCachedMpeg4Gif
| InlineQueryResultCachedPhoto
| InlineQueryResultCachedSticker
| InlineQueryResultCachedVideo
| InlineQueryResultCachedVoice
| InlineQueryResultArticle
| InlineQueryResultAudio
| InlineQueryResultContact
| InlineQueryResultGame
| InlineQueryResultDocument
| InlineQueryResultGif
| InlineQueryResultLocation
| InlineQueryResultMpeg4Gif
| InlineQueryResultPhoto
| InlineQueryResultVenue
| InlineQueryResultVideo
| InlineQueryResultVoice
deriving (InlineQueryResultType -> InlineQueryResultType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InlineQueryResultType -> InlineQueryResultType -> Bool
$c/= :: InlineQueryResultType -> InlineQueryResultType -> Bool
== :: InlineQueryResultType -> InlineQueryResultType -> Bool
$c== :: InlineQueryResultType -> InlineQueryResultType -> Bool
Eq, Int -> InlineQueryResultType -> ShowS
[InlineQueryResultType] -> ShowS
InlineQueryResultType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InlineQueryResultType] -> ShowS
$cshowList :: [InlineQueryResultType] -> ShowS
show :: InlineQueryResultType -> String
$cshow :: InlineQueryResultType -> String
showsPrec :: Int -> InlineQueryResultType -> ShowS
$cshowsPrec :: Int -> InlineQueryResultType -> ShowS
Show, forall x. Rep InlineQueryResultType x -> InlineQueryResultType
forall x. InlineQueryResultType -> Rep InlineQueryResultType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InlineQueryResultType x -> InlineQueryResultType
$cfrom :: forall x. InlineQueryResultType -> Rep InlineQueryResultType x
Generic)
getType :: InlineQueryResultType -> Text
getType :: InlineQueryResultType -> Text
getType InlineQueryResultType
InlineQueryResultCachedAudio = Text
"audio"
getType InlineQueryResultType
InlineQueryResultCachedDocument = Text
"document"
getType InlineQueryResultType
InlineQueryResultCachedGif = Text
"gif"
getType InlineQueryResultType
InlineQueryResultCachedMpeg4Gif = Text
"mpeg4_gif"
getType InlineQueryResultType
InlineQueryResultCachedPhoto = Text
"photo"
getType InlineQueryResultType
InlineQueryResultCachedSticker = Text
"sticker"
getType InlineQueryResultType
InlineQueryResultCachedVideo = Text
"video"
getType InlineQueryResultType
InlineQueryResultCachedVoice = Text
"voice"
getType InlineQueryResultType
InlineQueryResultArticle = Text
"article"
getType InlineQueryResultType
InlineQueryResultAudio = Text
"audio"
getType InlineQueryResultType
InlineQueryResultContact = Text
"contact"
getType InlineQueryResultType
InlineQueryResultGame = Text
"game"
getType InlineQueryResultType
InlineQueryResultDocument = Text
"document"
getType InlineQueryResultType
InlineQueryResultGif = Text
"gif"
getType InlineQueryResultType
InlineQueryResultLocation = Text
"location"
getType InlineQueryResultType
InlineQueryResultMpeg4Gif = Text
"mpeg4_gif"
getType InlineQueryResultType
InlineQueryResultPhoto = Text
"photo"
getType InlineQueryResultType
InlineQueryResultVenue = Text
"venue"
getType InlineQueryResultType
InlineQueryResultVideo = Text
"video"
getType InlineQueryResultType
InlineQueryResultVoice = Text
"voice"
instance ToJSON InlineQueryResultType where
toJSON :: InlineQueryResultType -> Value
toJSON = Text -> Value
String forall b c a. (b -> c) -> (a -> b) -> a -> c
. InlineQueryResultType -> Text
getType
instance FromJSON InlineQueryResultType where parseJSON :: Value -> Parser InlineQueryResultType
parseJSON = forall a (d :: Meta) (f :: * -> *).
(Generic a, GFromJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
Value -> Parser a
gparseJSON