{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
module Telegram.Bot.API.Methods.SendLocation where
import Data.Aeson (FromJSON (..), ToJSON (..))
import Data.Proxy
import Data.Text (Text)
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
import Telegram.Bot.API.Internal.TH
data SendLocationRequest = SendLocationRequest
{ SendLocationRequest -> Maybe BusinessConnectionId
sendLocationBusinessConnectionId :: Maybe BusinessConnectionId
, SendLocationRequest -> SomeChatId
sendLocationChatId :: SomeChatId
, SendLocationRequest -> Maybe MessageThreadId
sendLocationMessageThreadId :: Maybe MessageThreadId
, SendLocationRequest -> Float
sendLocationLatitude :: Float
, SendLocationRequest -> Float
sendLocationLongitude :: Float
, SendLocationRequest -> Maybe Float
sendLocationHorizontalAccuracy :: Maybe Float
, SendLocationRequest -> Int
sendLocationLivePeriod :: Int
, SendLocationRequest -> Maybe Int
sendLocationHeading :: Maybe Int
, SendLocationRequest -> Maybe Int
sendLocationProximityAlertRadius :: Maybe Int
, SendLocationRequest -> Maybe Bool
sendLocationDisableNotification :: Maybe Bool
, SendLocationRequest -> Maybe Bool
sendLocationProtectContent :: Maybe Bool
, SendLocationRequest -> Maybe Text
sendLocationMessageEffectId :: Maybe Text
, SendLocationRequest -> Maybe MessageId
sendLocationReplyToMessageId :: Maybe MessageId
, SendLocationRequest -> Maybe ReplyParameters
sendLocationReplyParameters :: Maybe ReplyParameters
, SendLocationRequest -> Maybe InlineKeyboardMarkup
sendLocationReplyMarkup :: Maybe InlineKeyboardMarkup
}
deriving (forall x. SendLocationRequest -> Rep SendLocationRequest x)
-> (forall x. Rep SendLocationRequest x -> SendLocationRequest)
-> Generic SendLocationRequest
forall x. Rep SendLocationRequest x -> SendLocationRequest
forall x. SendLocationRequest -> Rep SendLocationRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SendLocationRequest -> Rep SendLocationRequest x
from :: forall x. SendLocationRequest -> Rep SendLocationRequest x
$cto :: forall x. Rep SendLocationRequest x -> SendLocationRequest
to :: forall x. Rep SendLocationRequest x -> SendLocationRequest
Generic
instance ToJSON SendLocationRequest where toJSON :: SendLocationRequest -> Value
toJSON = SendLocationRequest -> Value
forall a (d :: Meta) (f :: * -> *).
(Generic a, GToJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
a -> Value
gtoJSON
instance FromJSON SendLocationRequest where parseJSON :: Value -> Parser SendLocationRequest
parseJSON = Value -> Parser SendLocationRequest
forall a (d :: Meta) (f :: * -> *).
(Generic a, GFromJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
Value -> Parser a
gparseJSON
type SendLocation = "sendLocation"
:> ReqBody '[JSON] SendLocationRequest
:> Post '[JSON] (Response Message)
sendLocation :: SendLocationRequest -> ClientM (Response Message)
sendLocation :: SendLocationRequest -> ClientM (Response Message)
sendLocation = Proxy SendLocation -> Client ClientM SendLocation
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @SendLocation)
makeDefault ''SendLocationRequest