{-# LANGUAGE DeriveGeneric #-}
module Telegram.Bot.API.Types.InputPollOption where

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

import Telegram.Bot.API.Internal.Utils
import Telegram.Bot.API.Types.MessageEntity
import Telegram.Bot.API.Types.ParseMode

-- ** 'InputPollOption'

-- | This object contains information about one answer option in a poll to send.
data InputPollOption = InputPollOption
  { InputPollOption -> Text
inputPollOptionText :: Text -- ^ Option text, 1-100 characters.
  , InputPollOption -> Maybe ParseMode
inputPollOptionTextParseMode :: Maybe ParseMode -- ^ Mode for parsing entities in the text. See [formatting options](https://core.telegram.org/bots/api#formatting-options) for more details. Currently, only custom emoji entities are allowed.
  , InputPollOption -> Maybe [MessageEntity]
inputPollOptionTextEntities :: Maybe [MessageEntity] -- ^ A JSON-serialized list of special entities that appear in the poll option text. It can be specified instead of @text_parse_mode@.
  }
  deriving ((forall x. InputPollOption -> Rep InputPollOption x)
-> (forall x. Rep InputPollOption x -> InputPollOption)
-> Generic InputPollOption
forall x. Rep InputPollOption x -> InputPollOption
forall x. InputPollOption -> Rep InputPollOption x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. InputPollOption -> Rep InputPollOption x
from :: forall x. InputPollOption -> Rep InputPollOption x
$cto :: forall x. Rep InputPollOption x -> InputPollOption
to :: forall x. Rep InputPollOption x -> InputPollOption
Generic, Int -> InputPollOption -> ShowS
[InputPollOption] -> ShowS
InputPollOption -> String
(Int -> InputPollOption -> ShowS)
-> (InputPollOption -> String)
-> ([InputPollOption] -> ShowS)
-> Show InputPollOption
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InputPollOption -> ShowS
showsPrec :: Int -> InputPollOption -> ShowS
$cshow :: InputPollOption -> String
show :: InputPollOption -> String
$cshowList :: [InputPollOption] -> ShowS
showList :: [InputPollOption] -> ShowS
Show)

instance ToJSON   InputPollOption where toJSON :: InputPollOption -> Value
toJSON = InputPollOption -> Value
forall a (d :: Meta) (f :: * -> *).
(Generic a, GToJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
a -> Value
gtoJSON
instance FromJSON InputPollOption where parseJSON :: Value -> Parser InputPollOption
parseJSON = Value -> Parser InputPollOption
forall a (d :: Meta) (f :: * -> *).
(Generic a, GFromJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
Value -> Parser a
gparseJSON