telegram-raw-api-0.3.0: Servant bindings to the Telegram bot API

Safe HaskellNone
LanguageHaskell2010

Web.Telegram.API.Sending

Description

Sending stuff

Documentation

type SendMessage = Base :> ("sendMessage" :> (ReqBody '[JSON] SMessage :> Res)) Source #

type ForwardMessage = Base :> ("forwardMessage" :> (ReqBody '[JSON] FwdMessage :> Res)) Source #

type SendPhoto = Base :> ("sendPhoto" :> (ReqBody '[JSON] (PhotoMessage Text) :> Res)) Source #

type SendPhoto' photo = Base :> ("sendPhoto" :> (QueryR "chat_id" ChatId :> (MultipartForm Mem Photo :> (QueryParam "caption" Text :> MessageR)))) Source #

type SendAudio = Base :> ("sendAudio" :> (ReqBody '[JSON] (AudioMessage Text) :> Res)) Source #

type SendAudio' audio = Base :> ("sendAudio" :> (QueryR "chat_id" ChatId :> (MultipartForm Mem Audio :> (QueryParam "caption" Text :> (QueryParam "duration" Int :> (QueryParam "performer" Text :> (QueryParam "title" Text :> MessageR))))))) Source #

type SendDocument = Base :> ("sendDocument" :> (ReqBody '[JSON] (DocMessage Text) :> Res)) Source #

type SendDocument' doc = Base :> ("sendDocument" :> (QueryR "chat_id" ChatId :> (MultipartForm Mem Doc :> (QueryParam "caption" Text :> MessageR)))) Source #

type SendVideo = Base :> ("sendVideo" :> (ReqBody '[JSON] (VidMessage Text) :> Res)) Source #

type SendVideo' = Base :> ("sendVideo" :> (QueryR "chat_id" ChatId :> (MultipartForm Mem Video :> (QueryParam "duration" Int :> (QueryParam "width" Int :> (QueryParam "height" Int :> (QueryParam "caption" Text :> (QueryParam "supports_streaming" Bool :> MessageR)))))))) Source #

type SendAnimation = Base :> ("sendAnimation" :> (ReqBody '[JSON] (AnimationMessage Text) :> Res)) Source #

type SendAnimation' = Base :> ("sendAnimation" :> (QueryR "chat_id" ChatId :> (MultipartForm Mem Animation :> (QueryParam "duration" Int :> (QueryParam "width" Int :> (QueryParam "height" Int :> (QueryParam "caption" Text :> MessageR))))))) Source #

type SendVoice = Base :> ("sendVoice" :> (ReqBody '[JSON] (VoiceMessage Text) :> Res)) Source #

type SendVoice' = Base :> ("sendVoice" :> (QueryR "chat_id" ChatId :> (MultipartForm Mem Voice :> (QueryParam "duration" Int :> (QueryParam "caption" Text :> MessageR))))) Source #

type SendVideoNote = Base :> ("sendVideoNote" :> (ReqBody '[JSON] (VNMessage Text) :> Res)) Source #

type SendVideoNote' = Base :> ("sendVideoNote" :> (QueryR "chat_id" ChatId :> (MultipartForm Mem VideoNote :> (QueryParam "duration" Int :> (QueryParam "length" Int :> MessageR))))) Source #

type SendMediaGroup = Base :> ("sendMediaGroup" :> (QueryR "chat_id" ChatId :> (CompoundParams Mem "media" VideoOrPhoto :> (QueryParam "disable_notification" Bool :> (QueryParam "reply_to_message_id" Int :> Get '[JSON] (ReqResult [Message])))))) Source #

type SendLocation = Base :> ("sendLocation" :> (ReqBody '[JSON] LocationMessage :> Res)) Source #

type EditMessageLiveLocation = Base :> ("editMessageLiveLocation" :> (ReqBody '[JSON] LocationEdit :> Get '[JSON] (ReqResult (ReqEither Message Bool)))) Source #

type StopMessageLiveLocation = Base :> ("stopMessageLiveLocation" :> (ReqBody '[JSON] LocationStop :> Get '[JSON] (ReqResult (ReqEither Message Bool)))) Source #

type SendVenue = Base :> ("sendVenue" :> (ReqBody '[JSON] VenueMessage :> Res)) Source #

type SendContact = Base :> ("sendContact" :> (ReqBody '[JSON] ContactMessage :> Res)) Source #

type SendPoll = Base :> ("sendPoll" :> (ReqBody '[JSON] PollMessage :> Res)) Source #

type SendDice = Base :> ("sendDice" :> (ReqBody '[JSON] DiceMessage :> Res)) Source #

type SendChatAction = Base :> ("sendChatAction" :> (ReqBody '[JSON] ChatAction :> Get '[JSON] (ReqResult Bool))) Source #

type SendSticker = Base :> ("sendSticker" :> (ReqBody '[JSON] StickerMessage :> Res)) Source #

type SendSticker' sticker = Base :> ("sendSticker" :> (QueryR "chat_id" ChatId :> (MultipartForm Mem Sticker :> MessageR'))) Source #

data SMessage Source #

Instances
Eq SMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Show SMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Generic SMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Associated Types

type Rep SMessage :: Type -> Type #

Methods

from :: SMessage -> Rep SMessage x #

to :: Rep SMessage x -> SMessage #

ToJSON SMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Default SMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Methods

def :: SMessage #

type Rep SMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

data FwdMessage Source #

Instances
Eq FwdMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Show FwdMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Generic FwdMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Associated Types

type Rep FwdMessage :: Type -> Type #

ToJSON FwdMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

FromJSON FwdMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Default FwdMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Methods

def :: FwdMessage #

type Rep FwdMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

type Rep FwdMessage = D1 (MetaData "FwdMessage" "Web.Telegram.API.Sending.Data" "telegram-raw-api-0.3.0-CeC2zg6UYPuLfYfz1lUNhE" False) (C1 (MetaCons "FwdMsg" PrefixI True) ((S1 (MetaSel (Just "chatId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ChatId) :*: S1 (MetaSel (Just "fromChatId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ChatId)) :*: (S1 (MetaSel (Just "messageId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "disableNotification") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool)))))

data PhotoMessage a Source #

Instances
Eq a => Eq (PhotoMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Show a => Show (PhotoMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Generic (PhotoMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Associated Types

type Rep (PhotoMessage a) :: Type -> Type #

Methods

from :: PhotoMessage a -> Rep (PhotoMessage a) x #

to :: Rep (PhotoMessage a) x -> PhotoMessage a #

ToJSON a => ToJSON (PhotoMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Default a => Default (PhotoMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Methods

def :: PhotoMessage a #

type Rep (PhotoMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

data AudioMessage a Source #

Instances
Eq a => Eq (AudioMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Show a => Show (AudioMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Generic (AudioMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Associated Types

type Rep (AudioMessage a) :: Type -> Type #

Methods

from :: AudioMessage a -> Rep (AudioMessage a) x #

to :: Rep (AudioMessage a) x -> AudioMessage a #

ToJSON a => ToJSON (AudioMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Default a => Default (AudioMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Methods

def :: AudioMessage a #

type Rep (AudioMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

data DocMessage a Source #

Instances
Eq a => Eq (DocMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Methods

(==) :: DocMessage a -> DocMessage a -> Bool #

(/=) :: DocMessage a -> DocMessage a -> Bool #

Show a => Show (DocMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Generic (DocMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Associated Types

type Rep (DocMessage a) :: Type -> Type #

Methods

from :: DocMessage a -> Rep (DocMessage a) x #

to :: Rep (DocMessage a) x -> DocMessage a #

ToJSON a => ToJSON (DocMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Default a => Default (DocMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Methods

def :: DocMessage a #

type Rep (DocMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

data VidMessage a Source #

Instances
Eq a => Eq (VidMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Methods

(==) :: VidMessage a -> VidMessage a -> Bool #

(/=) :: VidMessage a -> VidMessage a -> Bool #

Show a => Show (VidMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Generic (VidMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Associated Types

type Rep (VidMessage a) :: Type -> Type #

Methods

from :: VidMessage a -> Rep (VidMessage a) x #

to :: Rep (VidMessage a) x -> VidMessage a #

ToJSON a => ToJSON (VidMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Default a => Default (VidMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Methods

def :: VidMessage a #

type Rep (VidMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

data AnimationMessage a Source #

Instances
Eq a => Eq (AnimationMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Show a => Show (AnimationMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Generic (AnimationMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Associated Types

type Rep (AnimationMessage a) :: Type -> Type #

ToJSON a => ToJSON (AnimationMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Default a => Default (AnimationMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Methods

def :: AnimationMessage a #

type Rep (AnimationMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

data VoiceMessage a Source #

Instances
Eq a => Eq (VoiceMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Show a => Show (VoiceMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Generic (VoiceMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Associated Types

type Rep (VoiceMessage a) :: Type -> Type #

Methods

from :: VoiceMessage a -> Rep (VoiceMessage a) x #

to :: Rep (VoiceMessage a) x -> VoiceMessage a #

ToJSON a => ToJSON (VoiceMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Default a => Default (VoiceMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Methods

def :: VoiceMessage a #

type Rep (VoiceMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

data VNMessage a Source #

Instances
Eq (VNMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Methods

(==) :: VNMessage a -> VNMessage a -> Bool #

(/=) :: VNMessage a -> VNMessage a -> Bool #

Show (VNMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Generic (VNMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Associated Types

type Rep (VNMessage a) :: Type -> Type #

Methods

from :: VNMessage a -> Rep (VNMessage a) x #

to :: Rep (VNMessage a) x -> VNMessage a #

ToJSON (VNMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Default (VNMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Methods

def :: VNMessage a #

type Rep (VNMessage a) Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

data LocationEdit Source #

Instances
Eq LocationEdit Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Show LocationEdit Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Generic LocationEdit Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Associated Types

type Rep LocationEdit :: Type -> Type #

ToJSON LocationEdit Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Default LocationEdit Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Methods

def :: LocationEdit #

type Rep LocationEdit Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

data LocationStop Source #

Instances
Eq LocationStop Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Show LocationStop Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Generic LocationStop Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Associated Types

type Rep LocationStop :: Type -> Type #

ToJSON LocationStop Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Default LocationStop Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Methods

def :: LocationStop #

type Rep LocationStop Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

type Rep LocationStop = D1 (MetaData "LocationStop" "Web.Telegram.API.Sending.Data" "telegram-raw-api-0.3.0-CeC2zg6UYPuLfYfz1lUNhE" False) (C1 (MetaCons "LocationStop" PrefixI True) ((S1 (MetaSel (Just "chatId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ChatId)) :*: S1 (MetaSel (Just "messageId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int))) :*: (S1 (MetaSel (Just "inlineMessageId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "replyMarkup") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ReplyMarkup)))))

data VenueMessage Source #

Instances
Eq VenueMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Show VenueMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Generic VenueMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Associated Types

type Rep VenueMessage :: Type -> Type #

ToJSON VenueMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Default VenueMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Methods

def :: VenueMessage #

type Rep VenueMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

data ContactMessage Source #

Instances
Eq ContactMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Show ContactMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Generic ContactMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Associated Types

type Rep ContactMessage :: Type -> Type #

ToJSON ContactMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Default ContactMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Methods

def :: ContactMessage #

type Rep ContactMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

data PollMessage Source #

Instances
Eq PollMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Show PollMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Generic PollMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Associated Types

type Rep PollMessage :: Type -> Type #

ToJSON PollMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Default PollMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Methods

def :: PollMessage #

type Rep PollMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

data DiceMessage Source #

Instances
Eq DiceMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Show DiceMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Generic DiceMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Associated Types

type Rep DiceMessage :: Type -> Type #

ToJSON DiceMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Default DiceMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Methods

def :: DiceMessage #

type Rep DiceMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

type Rep DiceMessage = D1 (MetaData "DiceMessage" "Web.Telegram.API.Sending.Data" "telegram-raw-api-0.3.0-CeC2zg6UYPuLfYfz1lUNhE" False) (C1 (MetaCons "DiceMessage" PrefixI True) ((S1 (MetaSel (Just "chatId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ChatId) :*: S1 (MetaSel (Just "disableNotification") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool))) :*: (S1 (MetaSel (Just "replyToMessageId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int)) :*: S1 (MetaSel (Just "replyMarkup") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ReplyMarkup)))))

data ChatAction Source #

Instances
Eq ChatAction Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Show ChatAction Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Generic ChatAction Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Associated Types

type Rep ChatAction :: Type -> Type #

ToJSON ChatAction Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Default ChatAction Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Methods

def :: ChatAction #

type Rep ChatAction Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

type Rep ChatAction = D1 (MetaData "ChatAction" "Web.Telegram.API.Sending.Data" "telegram-raw-api-0.3.0-CeC2zg6UYPuLfYfz1lUNhE" False) (C1 (MetaCons "ChatAction" PrefixI True) (S1 (MetaSel (Just "chatId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ChatId) :*: S1 (MetaSel (Just "action") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Action)))

data StickerMessage Source #

Instances
Eq StickerMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Show StickerMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Generic StickerMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Associated Types

type Rep StickerMessage :: Type -> Type #

ToJSON StickerMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Default StickerMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

Methods

def :: StickerMessage #

type Rep StickerMessage Source # 
Instance details

Defined in Web.Telegram.API.Sending.Data

type Rep StickerMessage = D1 (MetaData "StickerMessage" "Web.Telegram.API.Sending.Data" "telegram-raw-api-0.3.0-CeC2zg6UYPuLfYfz1lUNhE" False) (C1 (MetaCons "StickerMessage" PrefixI True) ((S1 (MetaSel (Just "chatId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ChatId) :*: S1 (MetaSel (Just "sticker") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) :*: (S1 (MetaSel (Just "disableNotification") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool)) :*: (S1 (MetaSel (Just "replyToMessageId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int)) :*: S1 (MetaSel (Just "replyMarkup") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ReplyMarkup))))))