Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data User = User {}
- data Message = Msg {}
- data MessageMetadata = MMetadata {
- messageId :: Integer
- from :: Maybe User
- date :: Integer
- chat :: Chat
- forwardFrom :: Maybe User
- forwardFromChat :: Maybe Chat
- forwardFromMessageId :: Maybe Integer
- forwardSignature :: Maybe Text
- forwardSenderName :: Maybe Text
- forwardDate :: Maybe Integer
- replyToMessage :: Maybe Message
- editDate :: Maybe Integer
- mediaGroupId :: Maybe Text
- authorSignature :: Maybe Text
- replyMarkup :: Maybe InlineKeyboardMarkup
- data MessageEntity = MessageEntity {}
- data MessageContent
- = TextM {
- text :: Text
- entities :: Maybe [MessageEntity]
- | AudioM {
- audio :: Audio
- caption :: Maybe Text
- captionEntities :: Maybe [MessageEntity]
- | DocumentM { }
- | AnimationM { }
- | GameM {
- game :: Game
- | PhotoM {
- photo :: [PhotoSize]
- caption :: Maybe Text
- captionEntities :: Maybe [MessageEntity]
- | StickerM { }
- | VideoM {
- video :: Video
- caption :: Maybe Text
- captionEntities :: Maybe [MessageEntity]
- | VoiceM {
- voice :: Voice
- caption :: Maybe Text
- captionEntities :: Maybe [MessageEntity]
- | VideoNoteM { }
- | ContactM { }
- | LocationM { }
- | VenueM { }
- | PollM { }
- | NewChatMembers {
- newChatMembers :: [User]
- | LeftChatMember { }
- | NewChatPhoto {
- newChatPhoto :: [PhotoSize]
- | DeleteChatPhoto { }
- | GroupChatCreated { }
- | SupergroupChatCreated { }
- | ChannelChatCreated { }
- | MigrateToChatId { }
- | MigrateFromChatId { }
- | PinnedMessage { }
- | InvoiceM {
- invoice :: Invoice
- | SuccessfulPaymentM { }
- | ConnectedWebsite { }
- | PassportData {
- passPortData :: PassportData
- = TextM {
- data ParseMode
- = MarkdownV2
- | HTML
- | Markdown
- data ChatId
- data Chat = Chat {
- chatId :: Integer
- chatType :: ChatType
- title :: Maybe Text
- username :: Maybe Text
- firstName :: Maybe Text
- lastName :: Maybe Text
- photo :: Maybe ChatPhoto
- description :: Maybe Text
- inviteLink :: Maybe Text
- pinnedMessage :: Maybe Message
- permissions :: Maybe ChatPermissions
- slowModeDelay :: Maybe Integer
- stickerSetName :: Maybe Integer
- canSetStickerSet :: Maybe Bool
- data ChatPermissions = ChatPermissions {}
- data ChatPhoto = ChatPhoto {}
- data ChatMember = ChatMember {
- user :: User
- status :: Text
- customTitle :: Text
- untilDate :: Maybe Integer
- canBeEdited :: Maybe Bool
- canPostMessages :: Maybe Bool
- canEditMessages :: Maybe Bool
- canDeleteMessages :: Maybe Bool
- canRestrictMembers :: Maybe Bool
- canPromoteMembers :: Maybe Bool
- canChangeInfo :: Maybe Bool
- canInviteUsers :: Maybe Bool
- canPinMessages :: Maybe Bool
- isMember :: Maybe Bool
- canSendMessages :: Maybe Bool
- canSendMediaMessages :: Maybe Bool
- canSendPolls :: Maybe Bool
- canSendOtherMesssages :: Maybe Bool
- canAddWebPagePreviews :: Maybe Bool
- data PhotoSize = PhotoSize {}
- data Audio = Audio {}
- data Animation = Animation {}
- data Document = Document {}
- data Video = Video {}
- data Voice = Voice {}
- data VideoNote = VideoNote {}
- data Contact = Contact {}
- data Location = Location {}
- data Venue = Venue {}
- data PollOption = PollOption {
- text :: Text
- voterCount :: Integer
- data Poll = Poll {
- pollId :: Text
- question :: Text
- options :: [PollOption]
- totalVoterCount :: Integer
- isClosed :: Bool
- isAnonymous :: Bool
- pollType :: PollType
- allowsMultipleAnswers :: Bool
- correctOptionId :: Maybe Integer
- data PollType
- data PollAnswer = PollAnswer {}
- data UserProfilePhotos = UserProfilePhotos {
- totalCount :: Integer
- photos :: [[PhotoSize]]
- data File = File {}
- data Sticker = Sticker {}
- data StickerSet = StickerSet {
- name :: Text
- title :: Text
- isAnimated :: Bool
- containsMasks :: Bool
- stickers :: [Sticker]
- data MaskPosition = MaskPosition {}
- data SuccessfulPayment = SuccessfulPayment {
- currency :: Text
- totalAmount :: Integer
- invoicePayload :: Text
- shippingOptionId :: Maybe Text
- orderInfo :: Maybe OrderInfo
- telegramPaymentChargeId :: Text
- providerPaymentChargeId :: Text
- coe :: Coercible a b => a -> b
- liftUnion :: (Typeable a, Elem a s) => a -> Union s
- type QueryR = QueryParam' '[Required, Strict]
- class Default a where
- def :: a
User
A Telegram user or bot.
User | |
|
Instances
Message
Instances
Eq Message Source # | |
Show Message Source # | |
Generic Message Source # | |
ToJSON Message Source # | |
Defined in Web.Telegram.Types.Internal.Common | |
FromJSON Message Source # | |
ToHttpApiData Message Source # | |
Defined in Web.Telegram.Types.Internal.Common toUrlPiece :: Message -> Text # toEncodedUrlPiece :: Message -> Builder # toHeader :: Message -> ByteString # toQueryParam :: Message -> Text # | |
Default Message Source # | |
Defined in Web.Telegram.Types.Internal.Common | |
type Rep Message Source # | |
Defined in Web.Telegram.Types.Internal.Common type Rep Message = D1 (MetaData "Message" "Web.Telegram.Types.Internal.Common" "telegram-types-0.1.0-6TiTf83FaoyKIwaUxcYK63" False) (C1 (MetaCons "Msg" PrefixI True) (S1 (MetaSel (Just "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MessageMetadata) :*: S1 (MetaSel (Just "content") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MessageContent))) |
data MessageMetadata Source #
MMetadata | |
|
Instances
data MessageEntity Source #
Instances
data MessageContent Source #
TextM | |
| |
AudioM | |
| |
DocumentM | |
| |
AnimationM | |
GameM | |
| |
PhotoM | |
| |
StickerM | |
VideoM | |
| |
VoiceM | |
| |
VideoNoteM | |
ContactM | |
LocationM | |
VenueM | |
PollM | |
NewChatMembers | |
| |
LeftChatMember | |
NewChatPhoto | |
| |
DeleteChatPhoto | |
GroupChatCreated | |
SupergroupChatCreated | |
ChannelChatCreated | |
MigrateToChatId | |
MigrateFromChatId | |
PinnedMessage | |
InvoiceM | |
| |
SuccessfulPaymentM | |
ConnectedWebsite | |
PassportData | |
|
Instances
Instances
Eq ParseMode Source # | |
Ord ParseMode Source # | |
Defined in Web.Telegram.Types.Internal.InputMedia | |
Show ParseMode Source # | |
Generic ParseMode Source # | |
ToJSON ParseMode Source # | |
Defined in Web.Telegram.Types.Internal.InputMedia | |
FromJSON ParseMode Source # | |
ToHttpApiData ParseMode Source # | |
Defined in Web.Telegram.Types.Internal.InputMedia toUrlPiece :: ParseMode -> Text # toEncodedUrlPiece :: ParseMode -> Builder # toHeader :: ParseMode -> ByteString # toQueryParam :: ParseMode -> Text # | |
Default ParseMode Source # | |
Defined in Web.Telegram.Types.Internal.InputMedia | |
type Rep ParseMode Source # | |
Defined in Web.Telegram.Types.Internal.InputMedia type Rep ParseMode = D1 (MetaData "ParseMode" "Web.Telegram.Types.Internal.InputMedia" "telegram-types-0.1.0-6TiTf83FaoyKIwaUxcYK63" False) (C1 (MetaCons "MarkdownV2" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "HTML" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Markdown" PrefixI False) (U1 :: Type -> Type))) |
Chat
Instances
Eq ChatId Source # | |
Show ChatId Source # | |
Generic ChatId Source # | |
ToJSON ChatId Source # | |
Defined in Web.Telegram.Types | |
FromJSON ChatId Source # | |
ToHttpApiData ChatId Source # | |
Defined in Web.Telegram.Types toUrlPiece :: ChatId -> Text # toEncodedUrlPiece :: ChatId -> Builder # toHeader :: ChatId -> ByteString # toQueryParam :: ChatId -> Text # | |
Default ChatId Source # | |
Defined in Web.Telegram.Types | |
type Rep ChatId Source # | |
Defined in Web.Telegram.Types type Rep ChatId = D1 (MetaData "ChatId" "Web.Telegram.Types" "telegram-types-0.1.0-6TiTf83FaoyKIwaUxcYK63" False) (C1 (MetaCons "ChatId" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)) :+: C1 (MetaCons "ChanId" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) |
Chat | |
|
Instances
Eq Chat Source # | |
Show Chat Source # | |
Generic Chat Source # | |
ToJSON Chat Source # | |
Defined in Web.Telegram.Types.Internal.Common | |
FromJSON Chat Source # | |
ToHttpApiData Chat Source # | |
Defined in Web.Telegram.Types.Internal.Common toUrlPiece :: Chat -> Text # toEncodedUrlPiece :: Chat -> Builder # toHeader :: Chat -> ByteString # toQueryParam :: Chat -> Text # | |
Default Chat Source # | |
Defined in Web.Telegram.Types.Internal.Common | |
type Rep Chat Source # | |
Defined in Web.Telegram.Types.Internal.Common |
data ChatPermissions Source #
Instances
ChatPhoto | |
|
Instances
data ChatMember Source #
ChatMember | |
|
Instances
Media Types
Image
Instances
Audio
Instances
Animation
Instances
Document
Instances
Video
Instances
Voice
Instances
VideoNote
Instances
Contact
Instances
Location
Instances
Eq Location Source # | |
Show Location Source # | |
Generic Location Source # | |
ToJSON Location Source # | |
Defined in Web.Telegram.Types.Internal.Media | |
FromJSON Location Source # | |
ToHttpApiData Location Source # | |
Defined in Web.Telegram.Types.Internal.Media toUrlPiece :: Location -> Text # toEncodedUrlPiece :: Location -> Builder # toHeader :: Location -> ByteString # toQueryParam :: Location -> Text # | |
Default Location Source # | |
Defined in Web.Telegram.Types.Internal.Media | |
type Rep Location Source # | |
Defined in Web.Telegram.Types.Internal.Media type Rep Location = D1 (MetaData "Location" "Web.Telegram.Types.Internal.Media" "telegram-types-0.1.0-6TiTf83FaoyKIwaUxcYK63" False) (C1 (MetaCons "Location" PrefixI True) (S1 (MetaSel (Just "longitude") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float) :*: S1 (MetaSel (Just "latitude") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float))) |
Venue
Instances
PollOption
data PollOption Source #
PollOption | |
|
Instances
Poll
Poll | |
|
Instances
Instances
Eq PollType Source # | |
Show PollType Source # | |
Generic PollType Source # | |
ToJSON PollType Source # | |
Defined in Web.Telegram.Types.Internal.Media | |
FromJSON PollType Source # | |
ToHttpApiData PollType Source # | |
Defined in Web.Telegram.Types.Internal.Media toUrlPiece :: PollType -> Text # toEncodedUrlPiece :: PollType -> Builder # toHeader :: PollType -> ByteString # toQueryParam :: PollType -> Text # | |
Default PollType Source # | |
Defined in Web.Telegram.Types.Internal.Media | |
type Rep PollType Source # | |
PollAnswer
data PollAnswer Source #
Instances
Avatar
data UserProfilePhotos Source #
UserProfilePhotos | |
|
Instances
File
Instances
Stickers
Instances
data StickerSet Source #
StickerSet | |
|
Instances
data MaskPosition Source #
Instances
Misc
data SuccessfulPayment Source #
SuccessfulPayment | |
|
Instances
Utilities
class Default a where Source #
A class for types with a default value.
Nothing