{-# 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
data InlineQueryResult = InlineQueryResult
{ InlineQueryResult -> InlineQueryResultType
inlineQueryResultType :: InlineQueryResultType
, InlineQueryResult -> InlineQueryResultId
inlineQueryResultId :: InlineQueryResultId
, InlineQueryResult -> Maybe Text
inlineQueryResultTitle :: Maybe Text
, InlineQueryResult -> Maybe InputMessageContent
inlineQueryResultInputMessageContent :: Maybe InputMessageContent
} deriving ((forall x. InlineQueryResult -> Rep InlineQueryResult x)
-> (forall x. Rep InlineQueryResult x -> InlineQueryResult)
-> Generic InlineQueryResult
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
(Int -> InlineQueryResult -> ShowS)
-> (InlineQueryResult -> String)
-> ([InlineQueryResult] -> ShowS)
-> Show InlineQueryResult
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
(InlineQueryResultId -> InlineQueryResultId -> Bool)
-> (InlineQueryResultId -> InlineQueryResultId -> Bool)
-> Eq InlineQueryResultId
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
(Int -> InlineQueryResultId -> ShowS)
-> (InlineQueryResultId -> String)
-> ([InlineQueryResultId] -> ShowS)
-> Show InlineQueryResultId
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. InlineQueryResultId -> Rep InlineQueryResultId x)
-> (forall x. Rep InlineQueryResultId x -> InlineQueryResultId)
-> Generic InlineQueryResultId
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
(InlineQueryResultId -> Value)
-> (InlineQueryResultId -> Encoding)
-> ([InlineQueryResultId] -> Value)
-> ([InlineQueryResultId] -> Encoding)
-> ToJSON InlineQueryResultId
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
(Value -> Parser InlineQueryResultId)
-> (Value -> Parser [InlineQueryResultId])
-> FromJSON 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, Int -> InlineQueryResultId -> Int
InlineQueryResultId -> Int
(Int -> InlineQueryResultId -> Int)
-> (InlineQueryResultId -> Int) -> Hashable InlineQueryResultId
forall 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 = InlineQueryResult -> Value
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 = Value -> Parser InlineQueryResult
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
(InlineQueryResultType -> InlineQueryResultType -> Bool)
-> (InlineQueryResultType -> InlineQueryResultType -> Bool)
-> Eq InlineQueryResultType
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
(Int -> InlineQueryResultType -> ShowS)
-> (InlineQueryResultType -> String)
-> ([InlineQueryResultType] -> ShowS)
-> Show InlineQueryResultType
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. InlineQueryResultType -> Rep InlineQueryResultType x)
-> (forall x. Rep InlineQueryResultType x -> InlineQueryResultType)
-> Generic InlineQueryResultType
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 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 :: InlineQueryResultType -> Value
toJSON = Text -> Value
String (Text -> Value)
-> (InlineQueryResultType -> Text)
-> InlineQueryResultType
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InlineQueryResultType -> Text
getType
instance FromJSON InlineQueryResultType where parseJSON :: Value -> Parser InlineQueryResultType
parseJSON = Value -> Parser InlineQueryResultType
forall a (d :: Meta) (f :: * -> *).
(Generic a, GFromJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
Value -> Parser a
gparseJSON