{-# 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.SendVideo 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
import Telegram.Bot.API.Internal.TH
data SendVideoRequest = SendVideoRequest
  { SendVideoRequest -> Maybe BusinessConnectionId
sendVideoBusinessConnectionId :: Maybe BusinessConnectionId 
  , SendVideoRequest -> SomeChatId
sendVideoChatId :: SomeChatId 
  , SendVideoRequest -> Maybe MessageThreadId
sendVideoMessageThreadId :: Maybe MessageThreadId 
  , SendVideoRequest -> InputFile
sendVideoVideo :: InputFile 
  , SendVideoRequest -> Maybe Int
sendVideoDuration :: Maybe Int 
  , SendVideoRequest -> Maybe Int
sendVideoWidth :: Maybe Int 
  , SendVideoRequest -> Maybe Int
sendVideoHeight :: Maybe Int 
  , SendVideoRequest -> Maybe InputFile
sendVideoThumbnail :: Maybe InputFile 
  , SendVideoRequest -> Maybe Text
sendVideoCaption :: Maybe Text 
  , SendVideoRequest -> Maybe ParseMode
sendVideoParseMode :: Maybe ParseMode  
  , SendVideoRequest -> Maybe [MessageEntity]
sendVideoCaptionEntities :: Maybe [MessageEntity] 
  , SendVideoRequest -> Maybe Bool
sendVideoShowCaptionAboveMedia :: Maybe Bool 
  , SendVideoRequest -> Maybe Bool
sendVideoHasSpoiler :: Maybe Bool 
  , SendVideoRequest -> Maybe Bool
sendVideoSupportsStreaming :: Maybe Bool 
  , SendVideoRequest -> Maybe Bool
sendVideoDisableNotification :: Maybe Bool 
  , SendVideoRequest -> Maybe Bool
sendVideoProtectContent :: Maybe Bool 
  , SendVideoRequest -> Maybe Text
sendVideoMessageEffectId :: Maybe Text 
  , SendVideoRequest -> Maybe MessageId
sendVideoReplyToMessageId :: Maybe MessageId 
  , SendVideoRequest -> Maybe ReplyParameters
sendVideoReplyParameters :: Maybe ReplyParameters 
  , SendVideoRequest -> Maybe InlineKeyboardMarkup
sendVideoReplyMarkup :: Maybe InlineKeyboardMarkup 
  }
  deriving (forall x. SendVideoRequest -> Rep SendVideoRequest x)
-> (forall x. Rep SendVideoRequest x -> SendVideoRequest)
-> Generic SendVideoRequest
forall x. Rep SendVideoRequest x -> SendVideoRequest
forall x. SendVideoRequest -> Rep SendVideoRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SendVideoRequest -> Rep SendVideoRequest x
from :: forall x. SendVideoRequest -> Rep SendVideoRequest x
$cto :: forall x. Rep SendVideoRequest x -> SendVideoRequest
to :: forall x. Rep SendVideoRequest x -> SendVideoRequest
Generic
instance ToJSON SendVideoRequest where toJSON :: SendVideoRequest -> Value
toJSON = SendVideoRequest -> Value
forall a (d :: Meta) (f :: * -> *).
(Generic a, GToJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
a -> Value
gtoJSON
instance ToMultipart Tmp SendVideoRequest where
  toMultipart :: SendVideoRequest -> MultipartData Tmp
toMultipart SendVideoRequest{Maybe Bool
Maybe Int
Maybe [MessageEntity]
Maybe Text
Maybe BusinessConnectionId
Maybe MessageThreadId
Maybe MessageId
Maybe ParseMode
Maybe InlineKeyboardMarkup
Maybe ReplyParameters
Maybe InputFile
SomeChatId
InputFile
sendVideoBusinessConnectionId :: SendVideoRequest -> Maybe BusinessConnectionId
sendVideoChatId :: SendVideoRequest -> SomeChatId
sendVideoMessageThreadId :: SendVideoRequest -> Maybe MessageThreadId
sendVideoVideo :: SendVideoRequest -> InputFile
sendVideoDuration :: SendVideoRequest -> Maybe Int
sendVideoWidth :: SendVideoRequest -> Maybe Int
sendVideoHeight :: SendVideoRequest -> Maybe Int
sendVideoThumbnail :: SendVideoRequest -> Maybe InputFile
sendVideoCaption :: SendVideoRequest -> Maybe Text
sendVideoParseMode :: SendVideoRequest -> Maybe ParseMode
sendVideoCaptionEntities :: SendVideoRequest -> Maybe [MessageEntity]
sendVideoShowCaptionAboveMedia :: SendVideoRequest -> Maybe Bool
sendVideoHasSpoiler :: SendVideoRequest -> Maybe Bool
sendVideoSupportsStreaming :: SendVideoRequest -> Maybe Bool
sendVideoDisableNotification :: SendVideoRequest -> Maybe Bool
sendVideoProtectContent :: SendVideoRequest -> Maybe Bool
sendVideoMessageEffectId :: SendVideoRequest -> Maybe Text
sendVideoReplyToMessageId :: SendVideoRequest -> Maybe MessageId
sendVideoReplyParameters :: SendVideoRequest -> Maybe ReplyParameters
sendVideoReplyMarkup :: SendVideoRequest -> Maybe InlineKeyboardMarkup
sendVideoBusinessConnectionId :: Maybe BusinessConnectionId
sendVideoChatId :: SomeChatId
sendVideoMessageThreadId :: Maybe MessageThreadId
sendVideoVideo :: InputFile
sendVideoDuration :: Maybe Int
sendVideoWidth :: Maybe Int
sendVideoHeight :: Maybe Int
sendVideoThumbnail :: Maybe InputFile
sendVideoCaption :: Maybe Text
sendVideoParseMode :: Maybe ParseMode
sendVideoCaptionEntities :: Maybe [MessageEntity]
sendVideoShowCaptionAboveMedia :: Maybe Bool
sendVideoHasSpoiler :: Maybe Bool
sendVideoSupportsStreaming :: Maybe Bool
sendVideoDisableNotification :: Maybe Bool
sendVideoProtectContent :: Maybe Bool
sendVideoMessageEffectId :: Maybe Text
sendVideoReplyToMessageId :: Maybe MessageId
sendVideoReplyParameters :: Maybe ReplyParameters
sendVideoReplyMarkup :: Maybe InlineKeyboardMarkup
..} =
    (MultipartData Tmp -> MultipartData Tmp)
-> (InputFile -> MultipartData Tmp -> MultipartData Tmp)
-> Maybe InputFile
-> MultipartData Tmp
-> MultipartData Tmp
forall b a. b -> (a -> b) -> Maybe a -> b
maybe MultipartData Tmp -> MultipartData Tmp
forall a. a -> a
id (Text -> InputFile -> MultipartData Tmp -> MultipartData Tmp
makeFile Text
"thumbnail") Maybe InputFile
sendVideoThumbnail (MultipartData Tmp -> MultipartData Tmp)
-> MultipartData Tmp -> MultipartData Tmp
forall a b. (a -> b) -> a -> b
$
    Text -> InputFile -> MultipartData Tmp -> MultipartData Tmp
makeFile Text
"video" InputFile
sendVideoVideo (MultipartData Tmp -> MultipartData Tmp)
-> MultipartData Tmp -> MultipartData Tmp
forall a b. (a -> b) -> a -> b
$
    [Input] -> [FileData Tmp] -> MultipartData Tmp
forall tag. [Input] -> [FileData tag] -> MultipartData tag
MultipartData [Input]
fields [] where
    fields :: [Input]
fields =
      [ Text -> Text -> Input
Input Text
"chat_id" (Text -> Input) -> Text -> Input
forall a b. (a -> b) -> a -> b
$ case SomeChatId
sendVideoChatId of
          SomeChatId (ChatId Integer
chat_id) -> String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> String
forall a. Show a => a -> String
show Integer
chat_id
          SomeChatUsername Text
txt -> Text
txt
      ] [Input] -> [Input] -> [Input]
forall a. Semigroup a => a -> a -> a
<> [Maybe Input] -> [Input]
forall a. [Maybe a] -> [a]
catMaybes
      [ Maybe MessageThreadId
sendVideoMessageThreadId Maybe MessageThreadId -> (MessageThreadId -> Input) -> Maybe Input
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 (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ MessageThreadId -> String
forall a. Show a => a -> String
show MessageThreadId
t)
      , Maybe Text
sendVideoCaption Maybe Text -> (Text -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Text
t -> Text -> Text -> Input
Input Text
"caption" Text
t
      , Maybe ParseMode
sendVideoParseMode Maybe ParseMode -> (ParseMode -> Input) -> Maybe Input
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 (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HasCallStack => Text -> Text -> Text -> Text
Text -> Text -> Text -> Text
TL.replace Text
"\"" Text
"" (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ ParseMode -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText ParseMode
t)
      , Maybe [MessageEntity]
sendVideoCaptionEntities Maybe [MessageEntity] -> ([MessageEntity] -> Input) -> Maybe Input
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 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ [MessageEntity] -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText [MessageEntity]
t)
      , Maybe Bool
sendVideoHasSpoiler Maybe Bool -> (Bool -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Bool
t -> Text -> Text -> Input
Input Text
"has_spoiler" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
      , Maybe Int
sendVideoDuration Maybe Int -> (Int -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Int
t -> Text -> Text -> Input
Input Text
"duration" (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Int -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText Int
t)
      , Maybe Int
sendVideoWidth Maybe Int -> (Int -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Int
t -> Text -> Text -> Input
Input Text
"width" (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Int -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText Int
t)
      , Maybe Int
sendVideoHeight Maybe Int -> (Int -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Int
t -> Text -> Text -> Input
Input Text
"height" (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Int -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText Int
t)
      , Maybe Bool
sendVideoDisableNotification Maybe Bool -> (Bool -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Bool
t -> Text -> Text -> Input
Input Text
"disable_notification" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
      , Maybe Bool
sendVideoSupportsStreaming Maybe Bool -> (Bool -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Bool
t -> Text -> Text -> Input
Input Text
"supports_streaming" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
      , Maybe Bool
sendVideoProtectContent Maybe Bool -> (Bool -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Bool
t -> Text -> Text -> Input
Input Text
"protect_content" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
      , Maybe MessageId
sendVideoReplyToMessageId Maybe MessageId -> (MessageId -> Input) -> Maybe Input
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 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ MessageId -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText MessageId
t)
      , Maybe ReplyParameters
sendVideoReplyParameters Maybe ReplyParameters -> (ReplyParameters -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \ReplyParameters
t -> Text -> Text -> Input
Input Text
"reply_parameters" (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ ReplyParameters -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText ReplyParameters
t)
      , Maybe InlineKeyboardMarkup
sendVideoReplyMarkup Maybe InlineKeyboardMarkup
-> (InlineKeyboardMarkup -> Input) -> Maybe Input
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 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ InlineKeyboardMarkup -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText InlineKeyboardMarkup
t)
      ]
type SendVideoContent
  = "sendVideo"
  :> MultipartForm Tmp SendVideoRequest
  :> Post '[JSON] (Response Message)
type SendVideoLink
  = "sendVideo"
  :> ReqBody '[JSON] SendVideoRequest
  :> Post '[JSON] (Response Message)
sendVideo :: SendVideoRequest ->  ClientM (Response Message)
sendVideo :: SendVideoRequest -> ClientM (Response Message)
sendVideo SendVideoRequest
r = case (SendVideoRequest -> InputFile
sendVideoVideo SendVideoRequest
r, SendVideoRequest -> Maybe InputFile
sendVideoThumbnail SendVideoRequest
r) of
  (InputFile{}, Maybe InputFile
_) -> do
    ByteString
boundary <- IO ByteString -> ClientM ByteString
forall a. IO a -> ClientM a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ByteString
genBoundary
    Proxy SendVideoContent -> Client ClientM SendVideoContent
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @SendVideoContent) (ByteString
boundary, SendVideoRequest
r)
  (InputFile
_, Just InputFile{}) -> do
    ByteString
boundary <- IO ByteString -> ClientM ByteString
forall a. IO a -> ClientM a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ByteString
genBoundary
    Proxy SendVideoContent -> Client ClientM SendVideoContent
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @SendVideoContent) (ByteString
boundary, SendVideoRequest
r)
  (InputFile, Maybe InputFile)
_ ->  Proxy SendVideoLink -> Client ClientM SendVideoLink
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @SendVideoLink) SendVideoRequest
r
makeDefault ''SendVideoRequest