{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
module Telegram.Bot.API.Methods.SendAnimation where
import Control.Monad.IO.Class (liftIO)
import Data.Aeson (ToJSON (..))
import Data.Aeson.Text (encodeToLazyText)
import Data.Bool
import Data.Maybe (catMaybes)
import Data.Functor ((<&>))
import Data.Proxy
import Data.Text
import GHC.Generics (Generic)
import Servant.API
import Servant.Multipart.API
import Servant.Multipart.Client
import Servant.Client hiding (Response)
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import Telegram.Bot.API.Internal.Utils
import Telegram.Bot.API.MakingRequests
import Telegram.Bot.API.Types
import Telegram.Bot.API.Types.ParseMode
data SendAnimationRequest = SendAnimationRequest
{ SendAnimationRequest -> SomeChatId
sendAnimationChatId :: SomeChatId
, SendAnimationRequest -> Maybe MessageThreadId
sendAnimationMessageThreadId :: Maybe MessageThreadId
, SendAnimationRequest -> InputFile
sendAnimationAnimation :: InputFile
, SendAnimationRequest -> Maybe Int
sendAnimationDuration :: Maybe Int
, SendAnimationRequest -> Maybe Int
sendAnimationWidth :: Maybe Int
, SendAnimationRequest -> Maybe Int
sendAnimationHeight :: Maybe Int
, SendAnimationRequest -> Maybe InputFile
sendAnimationThumb :: Maybe InputFile
, SendAnimationRequest -> Maybe Text
sendAnimationCaption :: Maybe Text
, SendAnimationRequest -> Maybe ParseMode
sendAnimationParseMode :: Maybe ParseMode
, SendAnimationRequest -> Maybe [MessageEntity]
sendAnimationCaptionEntities :: Maybe [MessageEntity]
, SendAnimationRequest -> Maybe Bool
sendAnimationHasSpoiler :: Maybe Bool
, SendAnimationRequest -> Maybe Bool
sendAnimationDisableNotification :: Maybe Bool
, SendAnimationRequest -> Maybe Bool
sendAnimationProtectContent :: Maybe Bool
, SendAnimationRequest -> Maybe MessageId
sendAnimationReplyToMessageId :: Maybe MessageId
, SendAnimationRequest -> Maybe Bool
sendAnimationAllowSendingWithoutReply :: Maybe Bool
, SendAnimationRequest -> Maybe InlineKeyboardMarkup
sendAnimationReplyMarkup :: Maybe InlineKeyboardMarkup
}
deriving forall x. Rep SendAnimationRequest x -> SendAnimationRequest
forall x. SendAnimationRequest -> Rep SendAnimationRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendAnimationRequest x -> SendAnimationRequest
$cfrom :: forall x. SendAnimationRequest -> Rep SendAnimationRequest x
Generic
instance ToJSON SendAnimationRequest where toJSON :: SendAnimationRequest -> Value
toJSON = forall a (d :: Meta) (f :: * -> *).
(Generic a, GToJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
a -> Value
gtoJSON
instance ToMultipart Tmp SendAnimationRequest where
toMultipart :: SendAnimationRequest -> MultipartData Tmp
toMultipart SendAnimationRequest{Maybe Bool
Maybe Int
Maybe [MessageEntity]
Maybe Text
Maybe MessageThreadId
Maybe MessageId
Maybe InlineKeyboardMarkup
Maybe ParseMode
Maybe InputFile
SomeChatId
InputFile
sendAnimationReplyMarkup :: Maybe InlineKeyboardMarkup
sendAnimationAllowSendingWithoutReply :: Maybe Bool
sendAnimationReplyToMessageId :: Maybe MessageId
sendAnimationProtectContent :: Maybe Bool
sendAnimationDisableNotification :: Maybe Bool
sendAnimationHasSpoiler :: Maybe Bool
sendAnimationCaptionEntities :: Maybe [MessageEntity]
sendAnimationParseMode :: Maybe ParseMode
sendAnimationCaption :: Maybe Text
sendAnimationThumb :: Maybe InputFile
sendAnimationHeight :: Maybe Int
sendAnimationWidth :: Maybe Int
sendAnimationDuration :: Maybe Int
sendAnimationAnimation :: InputFile
sendAnimationMessageThreadId :: Maybe MessageThreadId
sendAnimationChatId :: SomeChatId
sendAnimationReplyMarkup :: SendAnimationRequest -> Maybe InlineKeyboardMarkup
sendAnimationAllowSendingWithoutReply :: SendAnimationRequest -> Maybe Bool
sendAnimationReplyToMessageId :: SendAnimationRequest -> Maybe MessageId
sendAnimationProtectContent :: SendAnimationRequest -> Maybe Bool
sendAnimationDisableNotification :: SendAnimationRequest -> Maybe Bool
sendAnimationHasSpoiler :: SendAnimationRequest -> Maybe Bool
sendAnimationCaptionEntities :: SendAnimationRequest -> Maybe [MessageEntity]
sendAnimationParseMode :: SendAnimationRequest -> Maybe ParseMode
sendAnimationCaption :: SendAnimationRequest -> Maybe Text
sendAnimationThumb :: SendAnimationRequest -> Maybe InputFile
sendAnimationHeight :: SendAnimationRequest -> Maybe Int
sendAnimationWidth :: SendAnimationRequest -> Maybe Int
sendAnimationDuration :: SendAnimationRequest -> Maybe Int
sendAnimationAnimation :: SendAnimationRequest -> InputFile
sendAnimationMessageThreadId :: SendAnimationRequest -> Maybe MessageThreadId
sendAnimationChatId :: SendAnimationRequest -> SomeChatId
..} =
forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (Text -> InputFile -> MultipartData Tmp -> MultipartData Tmp
makeFile Text
"thumb") Maybe InputFile
sendAnimationThumb forall a b. (a -> b) -> a -> b
$
Text -> InputFile -> MultipartData Tmp -> MultipartData Tmp
makeFile Text
"animation" InputFile
sendAnimationAnimation forall a b. (a -> b) -> a -> b
$
forall tag. [Input] -> [FileData tag] -> MultipartData tag
MultipartData [Input]
fields [] where
fields :: [Input]
fields =
[ Text -> Text -> Input
Input Text
"chat_id" forall a b. (a -> b) -> a -> b
$ case SomeChatId
sendAnimationChatId of
SomeChatId (ChatId Integer
chat_id) -> String -> Text
T.pack forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show Integer
chat_id
SomeChatUsername Text
txt -> Text
txt
] forall a. Semigroup a => a -> a -> a
<> forall a. [Maybe a] -> [a]
catMaybes
[ Maybe MessageThreadId
sendAnimationMessageThreadId forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\MessageThreadId
t -> Text -> Text -> Input
Input Text
"message_thread_id" (String -> Text
T.pack forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show MessageThreadId
t)
, Maybe Text
sendAnimationCaption forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Text
t -> Text -> Text -> Input
Input Text
"caption" Text
t
, Maybe ParseMode
sendAnimationParseMode forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\ParseMode
t -> Text -> Text -> Input
Input Text
"parse_mode" (Text -> Text
TL.toStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Text -> Text
TL.replace Text
"\"" Text
"" forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText ParseMode
t)
, Maybe [MessageEntity]
sendAnimationCaptionEntities forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\[MessageEntity]
t -> Text -> Text -> Input
Input Text
"caption_entities" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText [MessageEntity]
t)
, Maybe Bool
sendAnimationHasSpoiler forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Bool
t -> Text -> Text -> Input
Input Text
"has_spoiler" (forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
, Maybe Int
sendAnimationDuration forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Int
t -> Text -> Text -> Input
Input Text
"duration" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText Int
t)
, Maybe Int
sendAnimationWidth forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Int
t -> Text -> Text -> Input
Input Text
"width" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText Int
t)
, Maybe Int
sendAnimationHeight forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Int
t -> Text -> Text -> Input
Input Text
"height" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText Int
t)
, Maybe Bool
sendAnimationDisableNotification forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Bool
t -> Text -> Text -> Input
Input Text
"disable_notification" (forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
, Maybe Bool
sendAnimationProtectContent forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Bool
t -> Text -> Text -> Input
Input Text
"protect_content" (forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
, Maybe MessageId
sendAnimationReplyToMessageId forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\MessageId
t -> Text -> Text -> Input
Input Text
"reply_to_message_id" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText MessageId
t)
, Maybe Bool
sendAnimationAllowSendingWithoutReply forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Bool
t -> Text -> Text -> Input
Input Text
"allow_sending_without_reply" (forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
, Maybe InlineKeyboardMarkup
sendAnimationReplyMarkup forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\InlineKeyboardMarkup
t -> Text -> Text -> Input
Input Text
"reply_markup" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText InlineKeyboardMarkup
t)
]
type SendAnimationContent
= "sendAnimation"
:> MultipartForm Tmp SendAnimationRequest
:> Post '[JSON] (Response Message)
type SendAnimationLink
= "sendAnimation"
:> ReqBody '[JSON] SendAnimationRequest
:> Post '[JSON] (Response Message)
sendAnimation :: SendAnimationRequest -> ClientM (Response Message)
sendAnimation :: SendAnimationRequest -> ClientM (Response Message)
sendAnimation SendAnimationRequest
r = case (SendAnimationRequest -> InputFile
sendAnimationAnimation SendAnimationRequest
r, SendAnimationRequest -> Maybe InputFile
sendAnimationThumb SendAnimationRequest
r) of
(InputFile{}, Maybe InputFile
_) -> do
ByteString
boundary <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ByteString
genBoundary
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendAnimationContent) (ByteString
boundary, SendAnimationRequest
r)
(InputFile
_, Just InputFile{}) -> do
ByteString
boundary <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ByteString
genBoundary
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendAnimationContent) (ByteString
boundary, SendAnimationRequest
r)
(InputFile, Maybe InputFile)
_ -> forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendAnimationLink) SendAnimationRequest
r