module Web.Telegram.API.Bot.API.Get
(
getMe
, getMeM
, getFile
, getFileM
, getUserProfilePhotos
, getUserProfilePhotosM
, TelegramBotGetAPI
, getApi
) where
import Data.Proxy
import Data.Text (Text)
import Network.HTTP.Client (Manager)
import Servant.API
import Servant.Client
import Web.Telegram.API.Bot.API.Core
import Web.Telegram.API.Bot.Responses
type TelegramBotGetAPI =
TelegramToken :> "getMe"
:> Get '[JSON] GetMeResponse
:<|> TelegramToken :> "getFile"
:> QueryParam "file_id" Text
:> Get '[JSON] FileResponse
:<|> TelegramToken :> "getUserProfilePhotos"
:> QueryParam "user_id" Integer
:> QueryParam "offset" Int
:> QueryParam "limit" Int
:> Get '[JSON] UserProfilePhotosResponse
getApi :: Proxy TelegramBotGetAPI
getApi = Proxy
getMe_ :: Token -> ClientM GetMeResponse
getFile_ :: Token -> Maybe Text -> ClientM FileResponse
getUserProfilePhotos_ :: Token -> Maybe Integer -> Maybe Int -> Maybe Int -> ClientM UserProfilePhotosResponse
getMe_
:<|> getFile_
:<|> getUserProfilePhotos_
= client getApi
getMe :: Token -> Manager -> IO (Either ServantError GetMeResponse)
getMe = runClient getMeM
getMeM :: TelegramClient GetMeResponse
getMeM = asking getMe_
getFile :: Token -> Text -> Manager -> IO (Either ServantError FileResponse)
getFile token fileId = runClient (getFileM fileId) token
getFileM :: Text -> TelegramClient FileResponse
getFileM fileId = run_ getFile_ (Just fileId)
getUserProfilePhotos :: Token -> Integer -> Maybe Int -> Maybe Int -> Manager -> IO (Either ServantError UserProfilePhotosResponse)
getUserProfilePhotos token userId offset limit = runClient (getUserProfilePhotosM userId offset limit) token
getUserProfilePhotosM :: Integer -> Maybe Int -> Maybe Int -> TelegramClient UserProfilePhotosResponse
getUserProfilePhotosM userId offset limit = asking $ \t -> getUserProfilePhotos_ t (Just userId) offset limit