{-# 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.SendDocument where
import Control.Monad.IO.Class (liftIO)
import Data.Aeson (ToJSON (..))
import Data.Aeson.Text (encodeToLazyText)
import Data.Bool
import Data.Proxy
import Data.Text
import GHC.Generics (Generic)
import Servant.API
import Servant.Multipart.API
import Servant.Multipart.Client
import System.FilePath
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.Types.SomeReplyMarkup
type SendDocumentContent
= "sendDocument"
:> MultipartForm Tmp SendDocumentRequest
:> Post '[JSON] (Response Message)
type SendDocumentLink
= "sendDocument"
:> ReqBody '[JSON] SendDocumentRequest
:> Post '[JSON] (Response Message)
sendDocument :: SendDocumentRequest -> ClientM (Response Message)
sendDocument :: SendDocumentRequest -> ClientM (Response Message)
sendDocument SendDocumentRequest
r = do
case SendDocumentRequest -> DocumentFile
sendDocumentDocument SendDocumentRequest
r of
DocumentFile{} -> 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 @SendDocumentContent) (ByteString
boundary, SendDocumentRequest
r)
DocumentFile
_ -> forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendDocumentLink) SendDocumentRequest
r
data SendDocumentRequest = SendDocumentRequest
{ SendDocumentRequest -> SomeChatId
sendDocumentChatId :: SomeChatId
, SendDocumentRequest -> Maybe MessageThreadId
sendDocumentMessageThreadId :: Maybe MessageThreadId
, SendDocumentRequest -> DocumentFile
sendDocumentDocument :: DocumentFile
, SendDocumentRequest -> Maybe FilePath
sendDocumentThumb :: Maybe FilePath
, SendDocumentRequest -> Maybe Text
sendDocumentCaption :: Maybe Text
, SendDocumentRequest -> Maybe ParseMode
sendDocumentParseMode :: Maybe ParseMode
, SendDocumentRequest -> Maybe [MessageEntity]
sendDocumentCaptionEntities :: Maybe [MessageEntity]
, SendDocumentRequest -> Maybe Bool
sendDocumentDisableContentTypeDetection :: Maybe Bool
, SendDocumentRequest -> Maybe Bool
sendDocumentDisableNotification :: Maybe Bool
, SendDocumentRequest -> Maybe Bool
sendDocumentProtectContent :: Maybe Bool
, SendDocumentRequest -> Maybe MessageId
sendDocumentReplyToMessageId :: Maybe MessageId
, SendDocumentRequest -> Maybe Bool
sendDocumentAllowSendingWithoutReply :: Maybe Bool
, SendDocumentRequest -> Maybe SomeReplyMarkup
sendDocumentReplyMarkup :: Maybe SomeReplyMarkup
}
deriving forall x. Rep SendDocumentRequest x -> SendDocumentRequest
forall x. SendDocumentRequest -> Rep SendDocumentRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendDocumentRequest x -> SendDocumentRequest
$cfrom :: forall x. SendDocumentRequest -> Rep SendDocumentRequest x
Generic
newtype DocumentFile = MakeDocumentFile InputFile
deriving newtype [DocumentFile] -> Encoding
[DocumentFile] -> Value
DocumentFile -> Encoding
DocumentFile -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [DocumentFile] -> Encoding
$ctoEncodingList :: [DocumentFile] -> Encoding
toJSONList :: [DocumentFile] -> Value
$ctoJSONList :: [DocumentFile] -> Value
toEncoding :: DocumentFile -> Encoding
$ctoEncoding :: DocumentFile -> Encoding
toJSON :: DocumentFile -> Value
$ctoJSON :: DocumentFile -> Value
ToJSON
pattern DocumentFileId :: FileId -> DocumentFile
pattern $bDocumentFileId :: FileId -> DocumentFile
$mDocumentFileId :: forall {r}. DocumentFile -> (FileId -> r) -> ((# #) -> r) -> r
DocumentFileId x = MakeDocumentFile (InputFileId x)
pattern DocumentUrl :: Text -> DocumentFile
pattern $bDocumentUrl :: Text -> DocumentFile
$mDocumentUrl :: forall {r}. DocumentFile -> (Text -> r) -> ((# #) -> r) -> r
DocumentUrl x = MakeDocumentFile (FileUrl x)
pattern DocumentFile :: FilePath -> ContentType -> DocumentFile
pattern $bDocumentFile :: FilePath -> Text -> DocumentFile
$mDocumentFile :: forall {r}.
DocumentFile -> (FilePath -> Text -> r) -> ((# #) -> r) -> r
DocumentFile x y = MakeDocumentFile (InputFile x y)
instance ToMultipart Tmp SendDocumentRequest where
toMultipart :: SendDocumentRequest -> MultipartData Tmp
toMultipart SendDocumentRequest{Maybe Bool
Maybe FilePath
Maybe [MessageEntity]
Maybe Text
Maybe MessageThreadId
Maybe MessageId
Maybe ParseMode
Maybe SomeReplyMarkup
SomeChatId
DocumentFile
sendDocumentReplyMarkup :: Maybe SomeReplyMarkup
sendDocumentAllowSendingWithoutReply :: Maybe Bool
sendDocumentReplyToMessageId :: Maybe MessageId
sendDocumentProtectContent :: Maybe Bool
sendDocumentDisableNotification :: Maybe Bool
sendDocumentDisableContentTypeDetection :: Maybe Bool
sendDocumentCaptionEntities :: Maybe [MessageEntity]
sendDocumentParseMode :: Maybe ParseMode
sendDocumentCaption :: Maybe Text
sendDocumentThumb :: Maybe FilePath
sendDocumentDocument :: DocumentFile
sendDocumentMessageThreadId :: Maybe MessageThreadId
sendDocumentChatId :: SomeChatId
sendDocumentReplyMarkup :: SendDocumentRequest -> Maybe SomeReplyMarkup
sendDocumentAllowSendingWithoutReply :: SendDocumentRequest -> Maybe Bool
sendDocumentReplyToMessageId :: SendDocumentRequest -> Maybe MessageId
sendDocumentProtectContent :: SendDocumentRequest -> Maybe Bool
sendDocumentDisableNotification :: SendDocumentRequest -> Maybe Bool
sendDocumentDisableContentTypeDetection :: SendDocumentRequest -> Maybe Bool
sendDocumentCaptionEntities :: SendDocumentRequest -> Maybe [MessageEntity]
sendDocumentParseMode :: SendDocumentRequest -> Maybe ParseMode
sendDocumentCaption :: SendDocumentRequest -> Maybe Text
sendDocumentThumb :: SendDocumentRequest -> Maybe FilePath
sendDocumentMessageThreadId :: SendDocumentRequest -> Maybe MessageThreadId
sendDocumentChatId :: SendDocumentRequest -> SomeChatId
sendDocumentDocument :: SendDocumentRequest -> DocumentFile
..} = forall tag. [Input] -> [FileData tag] -> MultipartData tag
MultipartData [Input]
fields [FileData Tmp]
files where
fields :: [Input]
fields =
[ Text -> Text -> Input
Input Text
"document" forall a b. (a -> b) -> a -> b
$ FilePath -> Text
T.pack forall a b. (a -> b) -> a -> b
$ FilePath
"attach://file"
, Text -> Text -> Input
Input Text
"chat_id" forall a b. (a -> b) -> a -> b
$ case SomeChatId
sendDocumentChatId of
SomeChatId (ChatId Integer
chat_id) -> FilePath -> Text
T.pack forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> FilePath
show Integer
chat_id
SomeChatUsername Text
txt -> Text
txt
] forall a. Semigroup a => a -> a -> a
<>
( (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\MessageThreadId
t -> ((Text -> Text -> Input
Input Text
"message_thread_id") (FilePath -> Text
T.pack forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> FilePath
show MessageThreadId
t)forall a. a -> [a] -> [a]
:)) Maybe MessageThreadId
sendDocumentMessageThreadId)
forall a b. (a -> b) -> a -> b
$ (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\FilePath
_ -> ((Text -> Text -> Input
Input Text
"thumb" Text
"attach://thumb")forall a. a -> [a] -> [a]
:)) Maybe FilePath
sendDocumentThumb)
forall a b. (a -> b) -> a -> b
$ (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\Text
t -> ((Text -> Text -> Input
Input Text
"caption" Text
t)forall a. a -> [a] -> [a]
:)) Maybe Text
sendDocumentCaption)
forall a b. (a -> b) -> a -> b
$ (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\ParseMode
t -> ((Text -> Text -> Input
Input Text
"parse_mode" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText ParseMode
t))forall a. a -> [a] -> [a]
:)) Maybe ParseMode
sendDocumentParseMode)
forall a b. (a -> b) -> a -> b
$ (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\[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))forall a. a -> [a] -> [a]
:)) Maybe [MessageEntity]
sendDocumentCaptionEntities)
forall a b. (a -> b) -> a -> b
$ (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\Bool
t -> ((Text -> Text -> Input
Input Text
"disable_notification" (forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t))forall a. a -> [a] -> [a]
:)) Maybe Bool
sendDocumentDisableNotification)
forall a b. (a -> b) -> a -> b
$ (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\Bool
t -> ((Text -> Text -> Input
Input Text
"disable_content_type_detection" (forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t))forall a. a -> [a] -> [a]
:)) Maybe Bool
sendDocumentDisableContentTypeDetection)
forall a b. (a -> b) -> a -> b
$ (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\Bool
t -> ((Text -> Text -> Input
Input Text
"protect_content" (forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t))forall a. a -> [a] -> [a]
:)) Maybe Bool
sendDocumentProtectContent)
forall a b. (a -> b) -> a -> b
$ (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\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))forall a. a -> [a] -> [a]
:)) Maybe MessageId
sendDocumentReplyToMessageId)
forall a b. (a -> b) -> a -> b
$ (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\Bool
t -> ((Text -> Text -> Input
Input Text
"allow_sending_without_reply" (forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t))forall a. a -> [a] -> [a]
:)) Maybe Bool
sendDocumentAllowSendingWithoutReply)
forall a b. (a -> b) -> a -> b
$ (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\SomeReplyMarkup
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 SomeReplyMarkup
t))forall a. a -> [a] -> [a]
:)) Maybe SomeReplyMarkup
sendDocumentReplyMarkup)
[])
files :: [FileData Tmp]
files
= (forall tag.
Text -> Text -> Text -> MultipartResult tag -> FileData tag
FileData Text
"file" (FilePath -> Text
T.pack forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
takeFileName FilePath
path) Text
ct FilePath
path)
forall a. a -> [a] -> [a]
: forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\FilePath
t -> [forall tag.
Text -> Text -> Text -> MultipartResult tag -> FileData tag
FileData Text
"thumb" (FilePath -> Text
T.pack forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
takeFileName FilePath
t) Text
"image/jpeg" FilePath
t]) Maybe FilePath
sendDocumentThumb
DocumentFile FilePath
path Text
ct = DocumentFile
sendDocumentDocument
instance ToJSON SendDocumentRequest where toJSON :: SendDocumentRequest -> Value
toJSON = forall a (d :: Meta) (f :: * -> *).
(Generic a, GToJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
a -> Value
gtoJSON
toSendDocument :: SomeChatId -> DocumentFile -> SendDocumentRequest
toSendDocument :: SomeChatId -> DocumentFile -> SendDocumentRequest
toSendDocument SomeChatId
ch DocumentFile
df = SendDocumentRequest
{ sendDocumentChatId :: SomeChatId
sendDocumentChatId = SomeChatId
ch
, sendDocumentMessageThreadId :: Maybe MessageThreadId
sendDocumentMessageThreadId = forall a. Maybe a
Nothing
, sendDocumentDocument :: DocumentFile
sendDocumentDocument = DocumentFile
df
, sendDocumentThumb :: Maybe FilePath
sendDocumentThumb = forall a. Maybe a
Nothing
, sendDocumentCaption :: Maybe Text
sendDocumentCaption = forall a. Maybe a
Nothing
, sendDocumentParseMode :: Maybe ParseMode
sendDocumentParseMode = forall a. Maybe a
Nothing
, sendDocumentCaptionEntities :: Maybe [MessageEntity]
sendDocumentCaptionEntities = forall a. Maybe a
Nothing
, sendDocumentDisableContentTypeDetection :: Maybe Bool
sendDocumentDisableContentTypeDetection = forall a. Maybe a
Nothing
, sendDocumentDisableNotification :: Maybe Bool
sendDocumentDisableNotification = forall a. Maybe a
Nothing
, sendDocumentProtectContent :: Maybe Bool
sendDocumentProtectContent = forall a. Maybe a
Nothing
, sendDocumentReplyToMessageId :: Maybe MessageId
sendDocumentReplyToMessageId = forall a. Maybe a
Nothing
, sendDocumentAllowSendingWithoutReply :: Maybe Bool
sendDocumentAllowSendingWithoutReply = forall a. Maybe a
Nothing
, sendDocumentReplyMarkup :: Maybe SomeReplyMarkup
sendDocumentReplyMarkup = forall a. Maybe a
Nothing
}