| Copyright | (c) Alexandre Moreno 2019 | 
|---|---|
| License | BSD3 | 
| 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 = PushMessageBody (Id a) [Message]
 - data MulticastMessageBody = MulticastMessageBody [Id User] [Message]
 - newtype BroadcastMessageBody = BroadcastMessageBody [Message]
 - data Profile = Profile {
- displayName :: Text
 - userId :: Id User
 - 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 {}
 
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 # | |
| 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 # | |
| 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
| Eq ReplyToken Source # | |
Defined in Line.Bot.Types  | |
| Show ReplyToken Source # | |
Defined in Line.Bot.Types Methods showsPrec :: Int -> ReplyToken -> ShowS # show :: ReplyToken -> String # showList :: [ReplyToken] -> ShowS #  | |
| Generic ReplyToken Source # | |
Defined in Line.Bot.Types Associated Types type Rep ReplyToken :: Type -> Type #  | |
| ToJSON ReplyToken Source # | |
Defined in Line.Bot.Types Methods toJSON :: ReplyToken -> Value # toEncoding :: ReplyToken -> Encoding # toJSONList :: [ReplyToken] -> Value # toEncodingList :: [ReplyToken] -> Encoding #  | |
| FromJSON ReplyToken Source # | |
Defined in Line.Bot.Types  | |
| type Rep ReplyToken Source # | |
Defined in Line.Bot.Types type Rep ReplyToken = D1 (MetaData "ReplyToken" "Line.Bot.Types" "line-bot-sdk-0.5.0.2-Ephb0hoif6sA1vi1Kfq0BS" True) (C1 (MetaCons "ReplyToken" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))  | |
data ReplyMessageBody Source #
Constructors
| ReplyMessageBody ReplyToken [Message] | 
Instances
data PushMessageBody Source #
Constructors
| 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 # | |
| type Rep Profile Source # | |
Defined in Line.Bot.Types type Rep Profile = D1 (MetaData "Profile" "Line.Bot.Types" "line-bot-sdk-0.5.0.2-Ephb0hoif6sA1vi1Kfq0BS" False) (C1 (MetaCons "Profile" PrefixI True) ((S1 (MetaSel (Just "displayName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "userId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Id User))) :*: (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 #  | |
| type Rep QuickReply Source # | |
Defined in Line.Bot.Types type Rep QuickReply = D1 (MetaData "QuickReply" "Line.Bot.Types" "line-bot-sdk-0.5.0.2-Ephb0hoif6sA1vi1Kfq0BS" True) (C1 (MetaCons "QuickReply" PrefixI True) (S1 (MetaSel (Just "items") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [QuickReplyButton])))  | |
data QuickReplyButton Source #
Instances
| Eq QuickReplyButton Source # | |
Defined in Line.Bot.Types Methods (==) :: QuickReplyButton -> QuickReplyButton -> Bool # (/=) :: QuickReplyButton -> QuickReplyButton -> Bool #  | |
| Show QuickReplyButton Source # | |
Defined in Line.Bot.Types Methods showsPrec :: Int -> QuickReplyButton -> ShowS # show :: QuickReplyButton -> String # showList :: [QuickReplyButton] -> ShowS #  | |
| ToJSON QuickReplyButton Source # | |
Defined in Line.Bot.Types Methods toJSON :: QuickReplyButton -> Value # toEncoding :: QuickReplyButton -> Encoding # toJSONList :: [QuickReplyButton] -> Value # toEncodingList :: [QuickReplyButton] -> Encoding #  | |
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  | |
| type Rep MessageQuota Source # | |
Defined in Line.Bot.Types type Rep MessageQuota = D1 (MetaData "MessageQuota" "Line.Bot.Types" "line-bot-sdk-0.5.0.2-Ephb0hoif6sA1vi1Kfq0BS" 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 # | |
| type Rep MemberIds Source # | |
Defined in Line.Bot.Types type Rep MemberIds = D1 (MetaData "MemberIds" "Line.Bot.Types" "line-bot-sdk-0.5.0.2-Ephb0hoif6sA1vi1Kfq0BS" 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))))  | |