Copyright | (c) Alexandre Moreno 2019-2021 |
---|---|
License | BSD-3-Clause |
Maintainer | alexmorenocano@gmail.com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Line.Bot.Types
Description
Synopsis
- newtype ChannelToken = ChannelToken {}
- newtype ChannelSecret = ChannelSecret {}
- newtype ChannelId = ChannelId {
- unChannelId :: Text
- data ChatType
- data Id :: ChatType -> * where
- type MessageId = Text
- newtype URL = URL Text
- data Message
- = MessageText {
- text :: Text
- quickReply :: Maybe QuickReply
- | MessageSticker {
- packageId :: Text
- stickerId :: Text
- quickReply :: Maybe QuickReply
- | MessageImage { }
- | MessageVideo { }
- | MessageAudio { }
- | MessageLocation { }
- | MessageFlex {
- altText :: Text
- contents :: Value
- quickReply :: Maybe QuickReply
- = MessageText {
- newtype ReplyToken = ReplyToken Text
- newtype LinkToken = LinkToken {}
- data ReplyMessageBody = ReplyMessageBody ReplyToken [Message]
- data PushMessageBody = forall a. PushMessageBody (Id a) [Message]
- data MulticastMessageBody = MulticastMessageBody [Id 'User] [Message]
- newtype BroadcastMessageBody = BroadcastMessageBody [Message]
- data Profile = Profile {
- displayName :: Text
- userId :: Text
- pictureUrl :: URL
- statusMessage :: Maybe Text
- newtype QuickReply = QuickReply {
- items :: [QuickReplyButton]
- data QuickReplyButton = QuickReplyButton {}
- data Action
- = ActionPostback {
- label :: Text
- postbackData :: Text
- displayText :: Text
- | ActionMessage { }
- | ActionUri { }
- | ActionCamera { }
- | ActionCameraRoll { }
- | ActionLocation { }
- = ActionPostback {
- data ClientCredentials = ClientCredentials {}
- data ShortLivedChannelToken = ShortLivedChannelToken {}
- newtype LineDate = LineDate {
- unLineDate :: Day
- data MessageCount = MessageCount {}
- newtype MessageQuota = MessageQuota {
- totalUsage :: Int
- data MemberIds = MemberIds {}
- data JPEG
- data RichMenuSize = RichMenuSize {}
- data RichMenuBounds = RichMenuBounds {}
- data RichMenuArea = RichMenuArea {
- bounds :: RichMenuBounds
- action :: Action
- data RichMenu = RichMenu {
- size :: RichMenuSize
- selected :: Bool
- name :: Text
- chatBarText :: Text
- areas :: [RichMenuArea]
- data RichMenuResponse = RichMenuResponse {
- richMenuId :: Text
- richMenu :: RichMenu
- newtype RichMenuId = RichMenuId {
- richMenuId :: Text
- newtype RichMenuResponseList = RichMenuResponseList {}
- data RichMenuBulkLinkBody = RichMenuBulkLinkBody {
- richMenuId :: Text
- userIds :: [Id 'User]
- newtype RichMenuBulkUnlinkBody = RichMenuBulkUnlinkBody {}
Documentation
newtype ChannelToken Source #
Constructors
ChannelToken | |
Fields |
Instances
newtype ChannelSecret Source #
Constructors
ChannelSecret | |
Fields |
Instances
IsString ChannelSecret Source # | |
Defined in Line.Bot.Types Methods fromString :: String -> ChannelSecret # | |
ToHttpApiData ChannelSecret Source # | |
Defined in Line.Bot.Types Methods toUrlPiece :: ChannelSecret -> Text # toEncodedUrlPiece :: ChannelSecret -> Builder # toHeader :: ChannelSecret -> ByteString # toQueryParam :: ChannelSecret -> Text # |
Constructors
ChannelId | |
Fields
|
Instances
Eq ChannelId Source # | |
Show ChannelId Source # | |
IsString ChannelId Source # | |
Defined in Line.Bot.Types Methods fromString :: String -> ChannelId # | |
Generic ChannelId Source # | |
NFData ChannelId Source # | |
Defined in Line.Bot.Types | |
ToHttpApiData ChannelId Source # | |
Defined in Line.Bot.Types Methods toUrlPiece :: ChannelId -> Text # toEncodedUrlPiece :: ChannelId -> Builder # toHeader :: ChannelId -> ByteString # toQueryParam :: ChannelId -> Text # | |
type Rep ChannelId Source # | |
Defined in Line.Bot.Types |
data Id :: ChatType -> * where Source #
ID of a chat user, group or room
Instances
Eq (Id a) Source # | |
Show (Id a) Source # | |
IsString (Id 'User) Source # | |
Defined in Line.Bot.Types Methods fromString :: String -> Id 'User # | |
IsString (Id 'Group) Source # | |
Defined in Line.Bot.Types Methods fromString :: String -> Id 'Group # | |
IsString (Id 'Room) Source # | |
Defined in Line.Bot.Types Methods fromString :: String -> Id 'Room # | |
ToJSON (Id a) Source # | |
Defined in Line.Bot.Types | |
FromJSON (Id 'User) Source # | |
FromJSON (Id 'Group) Source # | |
FromJSON (Id 'Room) Source # | |
NFData (Id a) Source # | |
Defined in Line.Bot.Types | |
ToHttpApiData (Id a) Source # | |
Defined in Line.Bot.Types Methods toUrlPiece :: Id a -> Text # toEncodedUrlPiece :: Id a -> Builder # toHeader :: Id a -> ByteString # toQueryParam :: Id a -> Text # | |
FromHttpApiData (Id 'User) Source # | |
Defined in Line.Bot.Types | |
FromHttpApiData (Id 'Group) Source # | |
Defined in Line.Bot.Types | |
FromHttpApiData (Id 'Room) Source # | |
Defined in Line.Bot.Types |
Constructors
MessageText | |
Fields
| |
MessageSticker | |
Fields
| |
MessageImage | |
Fields | |
MessageVideo | |
Fields | |
MessageAudio | |
Fields
| |
MessageLocation | |
MessageFlex | |
Fields
|
Instances
newtype ReplyToken Source #
Constructors
ReplyToken Text |
Instances
data ReplyMessageBody Source #
Constructors
ReplyMessageBody ReplyToken [Message] |
Instances
data PushMessageBody Source #
Constructors
forall a. PushMessageBody (Id a) [Message] |
Instances
Show PushMessageBody Source # | |
Defined in Line.Bot.Types Methods showsPrec :: Int -> PushMessageBody -> ShowS # show :: PushMessageBody -> String # showList :: [PushMessageBody] -> ShowS # | |
ToJSON PushMessageBody Source # | |
Defined in Line.Bot.Types Methods toJSON :: PushMessageBody -> Value # toEncoding :: PushMessageBody -> Encoding # toJSONList :: [PushMessageBody] -> Value # toEncodingList :: [PushMessageBody] -> Encoding # |
data MulticastMessageBody Source #
Constructors
MulticastMessageBody [Id 'User] [Message] |
Instances
newtype BroadcastMessageBody Source #
Constructors
BroadcastMessageBody [Message] |
Instances
Constructors
Profile | |
Fields
|
Instances
Eq Profile Source # | |
Show Profile Source # | |
Generic Profile Source # | |
FromJSON Profile Source # | |
NFData Profile Source # | |
Defined in Line.Bot.Types | |
type Rep Profile Source # | |
Defined in Line.Bot.Types type Rep Profile = D1 ('MetaData "Profile" "Line.Bot.Types" "line-bot-sdk-0.7.2-F2yyxMh5BFY9DcEGbfR99r" 'False) (C1 ('MetaCons "Profile" 'PrefixI 'True) ((S1 ('MetaSel ('Just "displayName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "userId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "pictureUrl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 URL) :*: S1 ('MetaSel ('Just "statusMessage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))))) |
newtype QuickReply Source #
Constructors
QuickReply | |
Fields
|
Instances
Eq QuickReply Source # | |
Defined in Line.Bot.Types | |
Show QuickReply Source # | |
Defined in Line.Bot.Types Methods showsPrec :: Int -> QuickReply -> ShowS # show :: QuickReply -> String # showList :: [QuickReply] -> ShowS # | |
Generic QuickReply Source # | |
Defined in Line.Bot.Types Associated Types type Rep QuickReply :: Type -> Type # | |
ToJSON QuickReply Source # | |
Defined in Line.Bot.Types Methods toJSON :: QuickReply -> Value # toEncoding :: QuickReply -> Encoding # toJSONList :: [QuickReply] -> Value # toEncodingList :: [QuickReply] -> Encoding # | |
NFData QuickReply Source # | |
Defined in Line.Bot.Types Methods rnf :: QuickReply -> () # | |
type Rep QuickReply Source # | |
Defined in Line.Bot.Types type Rep QuickReply = D1 ('MetaData "QuickReply" "Line.Bot.Types" "line-bot-sdk-0.7.2-F2yyxMh5BFY9DcEGbfR99r" 'True) (C1 ('MetaCons "QuickReply" 'PrefixI 'True) (S1 ('MetaSel ('Just "items") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [QuickReplyButton]))) |
data QuickReplyButton Source #
Instances
Constructors
ActionPostback | |
Fields
| |
ActionMessage | |
ActionUri | |
ActionCamera | |
ActionCameraRoll | |
ActionLocation | |
Instances
data ClientCredentials Source #
Constructors
ClientCredentials | |
Fields |
Instances
ToForm ClientCredentials Source # | |
Defined in Line.Bot.Types Methods toForm :: ClientCredentials -> Form # |
data ShortLivedChannelToken Source #
Constructors
ShortLivedChannelToken | |
Fields
|
Instances
Constructors
LineDate | |
Fields
|
Instances
Eq LineDate Source # | |
Show LineDate Source # | |
ToHttpApiData LineDate Source # | |
Defined in Line.Bot.Types Methods toUrlPiece :: LineDate -> Text # toEncodedUrlPiece :: LineDate -> Builder # toHeader :: LineDate -> ByteString # toQueryParam :: LineDate -> Text # |
data MessageCount Source #
Instances
Eq MessageCount Source # | |
Defined in Line.Bot.Types | |
Show MessageCount Source # | |
Defined in Line.Bot.Types Methods showsPrec :: Int -> MessageCount -> ShowS # show :: MessageCount -> String # showList :: [MessageCount] -> ShowS # | |
FromJSON MessageCount Source # | |
Defined in Line.Bot.Types |
newtype MessageQuota Source #
Constructors
MessageQuota | |
Fields
|
Instances
Eq MessageQuota Source # | |
Defined in Line.Bot.Types | |
Show MessageQuota Source # | |
Defined in Line.Bot.Types Methods showsPrec :: Int -> MessageQuota -> ShowS # show :: MessageQuota -> String # showList :: [MessageQuota] -> ShowS # | |
Generic MessageQuota Source # | |
Defined in Line.Bot.Types Associated Types type Rep MessageQuota :: Type -> Type # | |
FromJSON MessageQuota Source # | |
Defined in Line.Bot.Types | |
NFData MessageQuota Source # | |
Defined in Line.Bot.Types Methods rnf :: MessageQuota -> () # | |
type Rep MessageQuota Source # | |
Defined in Line.Bot.Types type Rep MessageQuota = D1 ('MetaData "MessageQuota" "Line.Bot.Types" "line-bot-sdk-0.7.2-F2yyxMh5BFY9DcEGbfR99r" 'True) (C1 ('MetaCons "MessageQuota" 'PrefixI 'True) (S1 ('MetaSel ('Just "totalUsage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) |
Instances
Eq MemberIds Source # | |
Show MemberIds Source # | |
Generic MemberIds Source # | |
FromJSON MemberIds Source # | |
NFData MemberIds Source # | |
Defined in Line.Bot.Types | |
type Rep MemberIds Source # | |
Defined in Line.Bot.Types type Rep MemberIds = D1 ('MetaData "MemberIds" "Line.Bot.Types" "line-bot-sdk-0.7.2-F2yyxMh5BFY9DcEGbfR99r" 'False) (C1 ('MetaCons "MemberIds" 'PrefixI 'True) (S1 ('MetaSel ('Just "memberIds") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Id 'User]) :*: S1 ('MetaSel ('Just "next") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)))) |
Instances
Accept JPEG Source # | |
Defined in Line.Bot.Types | |
MimeRender JPEG ByteString Source # | |
Defined in Line.Bot.Types Methods mimeRender :: Proxy JPEG -> ByteString -> ByteString0 # |
data RichMenuSize Source #
Constructors
RichMenuSize | |
Instances
data RichMenuBounds Source #
Instances
data RichMenuArea Source #
Constructors
RichMenuArea | |
Fields
|
Instances
Constructors
RichMenu | |
Fields
|
Instances
Eq RichMenu Source # | |
Show RichMenu Source # | |
Generic RichMenu Source # | |
ToJSON RichMenu Source # | |
Defined in Line.Bot.Types | |
FromJSON RichMenu Source # | |
NFData RichMenu Source # | |
Defined in Line.Bot.Types | |
type Rep RichMenu Source # | |
Defined in Line.Bot.Types type Rep RichMenu = D1 ('MetaData "RichMenu" "Line.Bot.Types" "line-bot-sdk-0.7.2-F2yyxMh5BFY9DcEGbfR99r" 'False) (C1 ('MetaCons "RichMenu" 'PrefixI 'True) ((S1 ('MetaSel ('Just "size") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RichMenuSize) :*: S1 ('MetaSel ('Just "selected") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "chatBarText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "areas") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RichMenuArea]))))) |
data RichMenuResponse Source #
Constructors
RichMenuResponse | |
Fields
|
Instances
newtype RichMenuId Source #
Constructors
RichMenuId | |
Fields
|
Instances
newtype RichMenuResponseList Source #
Constructors
RichMenuResponseList | |
Fields |
Instances
data RichMenuBulkLinkBody Source #
Constructors
RichMenuBulkLinkBody | |
Fields
|
Instances
newtype RichMenuBulkUnlinkBody Source #
Constructors
RichMenuBulkUnlinkBody | |