{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
module Telegram.Bot.API.Methods.SendMediaGroup where

import Data.Aeson (ToJSON (..))
import Data.Proxy
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

-- ** 'sendMediaGroup'

-- | Request parameters for 'sendMediaGroup'.
data SendMediaGroupRequest = SendMediaGroupRequest
  { SendMediaGroupRequest -> SomeChatId
sendMediaGroupChatId :: SomeChatId -- ^ Unique identifier for the target chat or username of the target channel (in the format @channelusername).
  , SendMediaGroupRequest -> Maybe MessageThreadId
sendMediaGroupMessageThreadId :: Maybe MessageThreadId -- ^ Unique identifier for the target message thread (topic) of the forum; for forum supergroups only.
  , SendMediaGroupRequest -> [InputMedia]
sendMediaGroupMedia :: [InputMedia] -- ^ A JSON-serialized array describing messages to be sent, must include 2-10 items. InputMediaAudio, InputMediaDocument, InputMediaPhoto or InputMediaVideo.
  , SendMediaGroupRequest -> Maybe Bool
sendMediaGroupDisableNotification :: Maybe Bool -- ^ Sends the message silently. Users will receive a notification with no sound.
  , SendMediaGroupRequest -> Maybe Bool
sendMediaGroupProtectContent :: Maybe Bool -- ^ Protects the contents of the sent message from forwarding and saving
  , SendMediaGroupRequest -> Maybe MessageId
sendMediaGroupReplyToMessageId :: Maybe MessageId -- ^ If the message is a reply, ID of the original message
  , SendMediaGroupRequest -> Maybe Bool
sendMediaGroupAllowSendingWithoutReply :: Maybe Bool -- ^ Pass True, if the message should be sent even if the specified replied-to message is not found
  , SendMediaGroupRequest -> Maybe InlineKeyboardMarkup
sendMediaGroupReplyMarkup :: Maybe InlineKeyboardMarkup -- ^ Additional interface options. A JSON-serialized object for an inline keyboard, custom reply keyboard, instructions to remove reply keyboard or to force a reply from the user.
  }
  deriving forall x. Rep SendMediaGroupRequest x -> SendMediaGroupRequest
forall x. SendMediaGroupRequest -> Rep SendMediaGroupRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendMediaGroupRequest x -> SendMediaGroupRequest
$cfrom :: forall x. SendMediaGroupRequest -> Rep SendMediaGroupRequest x
Generic

instance ToJSON SendMediaGroupRequest where toJSON :: SendMediaGroupRequest -> Value
toJSON = forall a (d :: Meta) (f :: * -> *).
(Generic a, GToJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
a -> Value
gtoJSON

type SendMediaGroup = "sendMediaGroup"
  :> ReqBody '[JSON] SendMediaGroupRequest
  :> Post '[JSON] (Response [Message])

-- | Use this method to send a group of photos, videos,
--   documents or audios as an album. Documents
--   and audio files can be only grouped in an album
--   with messages of the same type.
--   On success, an array of Messages that were sent is returned.
sendMediaGroup :: SendMediaGroupRequest ->  ClientM (Response [Message])
sendMediaGroup :: SendMediaGroupRequest -> ClientM (Response [Message])
sendMediaGroup = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendMediaGroup)