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

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

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

-- ** 'ReplyParameters'

-- | Describes reply parameters for the message that is being sent.
data ReplyParameters = ReplyParameters
  { ReplyParameters -> MessageId
replyParametersMessageId :: MessageId -- ^ Identifier of the message that will be replied to in the current chat, or in the chat @chat_id@ if it is specified.
  , ReplyParameters -> Maybe SomeChatId
replyParametersChatId :: Maybe SomeChatId -- ^ f the message to be replied to is from a different chat, unique identifier for the chat or username of the channel (in the format \@channelusername).
  , ReplyParameters -> Maybe Bool
replyParametersAllowSendingWithoutReply :: Maybe Bool -- ^ Pass 'True' if the message should be sent even if the specified message to be replied to is not found; can be used only for replies in the same chat and forum topic.
  , ReplyParameters -> Maybe Text
replyParametersQuote :: Maybe Text -- ^ Quoted part of the message to be replied to; 0-1024 characters after entities parsing. The quote must be an exact substring of the message to be replied to, including @bold@, @italic@, @underline@, @strikethrough@, @spoiler@, and @custom_emoji@ entities. The message will fail to send if the quote isn't found in the original message.
  , ReplyParameters -> Maybe ParseMode
replyParametersQuoteParseMode :: Maybe ParseMode -- ^ Mode for parsing entities in the quote. See formatting options for more details.
  , ReplyParameters -> Maybe [MessageEntity]
replyParametersQuoteEntities :: Maybe [MessageEntity] -- ^ A JSON-serialized list of special entities that appear in the quote. It can be specified instead of @quote_parse_mode@.
  , ReplyParameters -> Maybe Int
replyParametersQuotePosition :: Maybe Int -- ^ Position of the quote in the original message in UTF-16 code units.
  } deriving ((forall x. ReplyParameters -> Rep ReplyParameters x)
-> (forall x. Rep ReplyParameters x -> ReplyParameters)
-> Generic ReplyParameters
forall x. Rep ReplyParameters x -> ReplyParameters
forall x. ReplyParameters -> Rep ReplyParameters x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ReplyParameters -> Rep ReplyParameters x
from :: forall x. ReplyParameters -> Rep ReplyParameters x
$cto :: forall x. Rep ReplyParameters x -> ReplyParameters
to :: forall x. Rep ReplyParameters x -> ReplyParameters
Generic, Int -> ReplyParameters -> ShowS
[ReplyParameters] -> ShowS
ReplyParameters -> String
(Int -> ReplyParameters -> ShowS)
-> (ReplyParameters -> String)
-> ([ReplyParameters] -> ShowS)
-> Show ReplyParameters
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ReplyParameters -> ShowS
showsPrec :: Int -> ReplyParameters -> ShowS
$cshow :: ReplyParameters -> String
show :: ReplyParameters -> String
$cshowList :: [ReplyParameters] -> ShowS
showList :: [ReplyParameters] -> ShowS
Show)

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