line-bot-sdk-0.5.0.0: Haskell SDK for LINE Messaging API

Copyright(c) Alexandre Moreno 2019
LicenseBSD3
Maintaineralexmorenocano@gmail.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Line.Bot.Types

Description

 
Synopsis

Documentation

newtype ChannelToken Source #

Constructors

ChannelToken 

Fields

Instances
Eq ChannelToken Source # 
Instance details

Defined in Line.Bot.Types

Show ChannelToken Source # 
Instance details

Defined in Line.Bot.Types

IsString ChannelToken Source # 
Instance details

Defined in Line.Bot.Types

Generic ChannelToken Source # 
Instance details

Defined in Line.Bot.Types

Associated Types

type Rep ChannelToken :: Type -> Type #

FromJSON ChannelToken Source # 
Instance details

Defined in Line.Bot.Types

ToForm ChannelToken Source # 
Instance details

Defined in Line.Bot.Types

Methods

toForm :: ChannelToken -> Form #

ToHttpApiData ChannelToken Source # 
Instance details

Defined in Line.Bot.Types

type Rep ChannelToken Source # 
Instance details

Defined in Line.Bot.Types

type Rep ChannelToken = D1 (MetaData "ChannelToken" "Line.Bot.Types" "line-bot-sdk-0.5.0.0-6zcgXmqrPUo8GmUQ4si8vQ" True) (C1 (MetaCons "ChannelToken" PrefixI True) (S1 (MetaSel (Just "unChannelToken") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype ChannelId Source #

Constructors

ChannelId 

Fields

Instances
Eq ChannelId Source # 
Instance details

Defined in Line.Bot.Types

Show ChannelId Source # 
Instance details

Defined in Line.Bot.Types

IsString ChannelId Source # 
Instance details

Defined in Line.Bot.Types

Generic ChannelId Source # 
Instance details

Defined in Line.Bot.Types

Associated Types

type Rep ChannelId :: Type -> Type #

ToHttpApiData ChannelId Source # 
Instance details

Defined in Line.Bot.Types

type Rep ChannelId Source # 
Instance details

Defined in Line.Bot.Types

type Rep ChannelId = D1 (MetaData "ChannelId" "Line.Bot.Types" "line-bot-sdk-0.5.0.0-6zcgXmqrPUo8GmUQ4si8vQ" True) (C1 (MetaCons "ChannelId" PrefixI True) (S1 (MetaSel (Just "unChannelId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data ChatType Source #

Constructors

User 
Group 
Room 

data Id :: ChatType -> * where Source #

ID of a chat user, group or room

Constructors

UserId :: Text -> Id User 
GroupId :: Text -> Id Group 
RoomId :: Text -> Id Room 
Instances
Eq (Id a) Source # 
Instance details

Defined in Line.Bot.Types

Methods

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

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

Show (Id a) Source # 
Instance details

Defined in Line.Bot.Types

Methods

showsPrec :: Int -> Id a -> ShowS #

show :: Id a -> String #

showList :: [Id a] -> ShowS #

IsString (Id User) Source # 
Instance details

Defined in Line.Bot.Types

Methods

fromString :: String -> Id User #

IsString (Id Group) Source # 
Instance details

Defined in Line.Bot.Types

Methods

fromString :: String -> Id Group #

IsString (Id Room) Source # 
Instance details

Defined in Line.Bot.Types

Methods

fromString :: String -> Id Room #

ToJSON (Id a) Source # 
Instance details

Defined in Line.Bot.Types

Methods

toJSON :: Id a -> Value #

toEncoding :: Id a -> Encoding #

toJSONList :: [Id a] -> Value #

toEncodingList :: [Id a] -> Encoding #

FromJSON (Id User) Source # 
Instance details

Defined in Line.Bot.Types

FromJSON (Id Group) Source # 
Instance details

Defined in Line.Bot.Types

FromJSON (Id Room) Source # 
Instance details

Defined in Line.Bot.Types

ToHttpApiData (Id a) Source # 
Instance details

Defined in Line.Bot.Types

FromHttpApiData (Id User) Source # 
Instance details

Defined in Line.Bot.Types

FromHttpApiData (Id Group) Source # 
Instance details

Defined in Line.Bot.Types

FromHttpApiData (Id Room) Source # 
Instance details

Defined in Line.Bot.Types

newtype URL Source #

Constructors

URL Text 
Instances
Eq URL Source # 
Instance details

Defined in Line.Bot.Types

Methods

(==) :: URL -> URL -> Bool #

(/=) :: URL -> URL -> Bool #

Show URL Source # 
Instance details

Defined in Line.Bot.Types

Methods

showsPrec :: Int -> URL -> ShowS #

show :: URL -> String #

showList :: [URL] -> ShowS #

Generic URL Source # 
Instance details

Defined in Line.Bot.Types

Associated Types

type Rep URL :: Type -> Type #

Methods

from :: URL -> Rep URL x #

to :: Rep URL x -> URL #

ToJSON URL Source # 
Instance details

Defined in Line.Bot.Types

FromJSON URL Source # 
Instance details

Defined in Line.Bot.Types

type Rep URL Source # 
Instance details

Defined in Line.Bot.Types

type Rep URL = D1 (MetaData "URL" "Line.Bot.Types" "line-bot-sdk-0.5.0.0-6zcgXmqrPUo8GmUQ4si8vQ" True) (C1 (MetaCons "URL" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data Message Source #

Instances
Eq Message Source # 
Instance details

Defined in Line.Bot.Types

Methods

(==) :: Message -> Message -> Bool #

(/=) :: Message -> Message -> Bool #

Show Message Source # 
Instance details

Defined in Line.Bot.Types

Generic Message Source # 
Instance details

Defined in Line.Bot.Types

Associated Types

type Rep Message :: Type -> Type #

Methods

from :: Message -> Rep Message x #

to :: Rep Message x -> Message #

ToJSON Message Source # 
Instance details

Defined in Line.Bot.Types

type Rep Message Source # 
Instance details

Defined in Line.Bot.Types

type Rep Message = D1 (MetaData "Message" "Line.Bot.Types" "line-bot-sdk-0.5.0.0-6zcgXmqrPUo8GmUQ4si8vQ" False) ((C1 (MetaCons "MessageText" PrefixI True) (S1 (MetaSel (Just "text") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "quickReply") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe QuickReply))) :+: (C1 (MetaCons "MessageSticker" PrefixI True) (S1 (MetaSel (Just "packageId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: (S1 (MetaSel (Just "stickerId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "quickReply") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe QuickReply)))) :+: C1 (MetaCons "MessageImage" PrefixI True) (S1 (MetaSel (Just "originalContentUrl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 URL) :*: (S1 (MetaSel (Just "previewImageUrl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 URL) :*: S1 (MetaSel (Just "quickReply") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe QuickReply)))))) :+: (C1 (MetaCons "MessageVideo" PrefixI True) (S1 (MetaSel (Just "originalContentUrl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 URL) :*: (S1 (MetaSel (Just "previewImageUrl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 URL) :*: S1 (MetaSel (Just "quickReply") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe QuickReply)))) :+: (C1 (MetaCons "MessageAudio" PrefixI True) (S1 (MetaSel (Just "originalContentUrl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 URL) :*: (S1 (MetaSel (Just "duration") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "quickReply") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe QuickReply)))) :+: C1 (MetaCons "MessageLocation" PrefixI True) ((S1 (MetaSel (Just "title") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "address") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) :*: (S1 (MetaSel (Just "latitude") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double) :*: (S1 (MetaSel (Just "longitude") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double) :*: S1 (MetaSel (Just "quickReply") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe QuickReply))))))))

newtype ReplyToken Source #

Constructors

ReplyToken Text 
Instances
Eq ReplyToken Source # 
Instance details

Defined in Line.Bot.Types

Show ReplyToken Source # 
Instance details

Defined in Line.Bot.Types

Generic ReplyToken Source # 
Instance details

Defined in Line.Bot.Types

Associated Types

type Rep ReplyToken :: Type -> Type #

ToJSON ReplyToken Source # 
Instance details

Defined in Line.Bot.Types

FromJSON ReplyToken Source # 
Instance details

Defined in Line.Bot.Types

type Rep ReplyToken Source # 
Instance details

Defined in Line.Bot.Types

type Rep ReplyToken = D1 (MetaData "ReplyToken" "Line.Bot.Types" "line-bot-sdk-0.5.0.0-6zcgXmqrPUo8GmUQ4si8vQ" True) (C1 (MetaCons "ReplyToken" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype LinkToken Source #

Constructors

LinkToken 

Fields

Instances
Eq LinkToken Source # 
Instance details

Defined in Line.Bot.Types

Show LinkToken Source # 
Instance details

Defined in Line.Bot.Types

Generic LinkToken Source # 
Instance details

Defined in Line.Bot.Types

Associated Types

type Rep LinkToken :: Type -> Type #

FromJSON LinkToken Source # 
Instance details

Defined in Line.Bot.Types

type Rep LinkToken Source # 
Instance details

Defined in Line.Bot.Types

type Rep LinkToken = D1 (MetaData "LinkToken" "Line.Bot.Types" "line-bot-sdk-0.5.0.0-6zcgXmqrPUo8GmUQ4si8vQ" True) (C1 (MetaCons "LinkToken" PrefixI True) (S1 (MetaSel (Just "linkToken") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data Profile Source #

Constructors

Profile 
Instances
Eq Profile Source # 
Instance details

Defined in Line.Bot.Types

Methods

(==) :: Profile -> Profile -> Bool #

(/=) :: Profile -> Profile -> Bool #

Show Profile Source # 
Instance details

Defined in Line.Bot.Types

Generic Profile Source # 
Instance details

Defined in Line.Bot.Types

Associated Types

type Rep Profile :: Type -> Type #

Methods

from :: Profile -> Rep Profile x #

to :: Rep Profile x -> Profile #

FromJSON Profile Source # 
Instance details

Defined in Line.Bot.Types

type Rep Profile Source # 
Instance details

Defined in Line.Bot.Types

newtype QuickReply Source #

Constructors

QuickReply 

Fields

Instances
Eq QuickReply Source # 
Instance details

Defined in Line.Bot.Types

Show QuickReply Source # 
Instance details

Defined in Line.Bot.Types

Generic QuickReply Source # 
Instance details

Defined in Line.Bot.Types

Associated Types

type Rep QuickReply :: Type -> Type #

ToJSON QuickReply Source # 
Instance details

Defined in Line.Bot.Types

type Rep QuickReply Source # 
Instance details

Defined in Line.Bot.Types

type Rep QuickReply = D1 (MetaData "QuickReply" "Line.Bot.Types" "line-bot-sdk-0.5.0.0-6zcgXmqrPUo8GmUQ4si8vQ" True) (C1 (MetaCons "QuickReply" PrefixI True) (S1 (MetaSel (Just "items") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [QuickReplyButton])))

data Action Source #

Constructors

ActionPostback 
ActionMessage 

Fields

ActionUri 

Fields

ActionCamera 

Fields

ActionCameraRoll 

Fields

ActionLocation 

Fields

Instances
Eq Action Source # 
Instance details

Defined in Line.Bot.Types

Methods

(==) :: Action -> Action -> Bool #

(/=) :: Action -> Action -> Bool #

Show Action Source # 
Instance details

Defined in Line.Bot.Types

Generic Action Source # 
Instance details

Defined in Line.Bot.Types

Associated Types

type Rep Action :: Type -> Type #

Methods

from :: Action -> Rep Action x #

to :: Rep Action x -> Action #

ToJSON Action Source # 
Instance details

Defined in Line.Bot.Types

type Rep Action Source # 
Instance details

Defined in Line.Bot.Types

data ShortLivedChannelToken Source #

newtype LineDate Source #

Constructors

LineDate 

Fields

Instances
Eq LineDate Source # 
Instance details

Defined in Line.Bot.Types

Show LineDate Source # 
Instance details

Defined in Line.Bot.Types

ToHttpApiData LineDate Source # 
Instance details

Defined in Line.Bot.Types