line-3.1.0: Haskell SDK for the LINE API

Safe HaskellNone
LanguageHaskell2010

Line.Messaging.API

Contents

Description

This module provides functions corresponding to the LINE Messaging APIs, nearly one on one.

For more details about the APIs themselves, please refer to the API references.

Synopsis

Types

Re-exported for convenience.

Monad transformer for APIs

type APIIO a = ReaderT ChannelAccessToken (ExceptT APIError IO) a Source #

A monad transformer for API calls. If translated into a human-readable form, it means:

  1. An API call needs a channel access token to specify through which channel it should send the call (ReaderT ChannelAccessToken).
  2. An API call effectfully returns a result if successful, APIError otherwise (ExceptT APIError).

runAPI :: IO ChannelAccessToken -> APIIO a -> IO (Either APIError a) Source #

runAPI resolves the APIIO monad transformer, and turns it into a plain IO with ChannelAccessToken provided.

The reason the type of the first parameter is not ChannelAccessToken, but IO ChannelAccessToken, is that it is usually loaded via effectful actions such as parsing command line arguments or reading a config file.

An example usage is like below:

api :: APIIO a -> IO (Either APIError a)
api = runAPI getChannelAccessTokenFromConfig

main :: IO ()
main = do
  result <- api $ push "some_receiver_id" [ Message $ Text "Hello, world!" ]
  case result of
    Right _ -> return ()
    Left err -> print err

LINE Messaging APIs

Every API call returns its result with APIIO. About the usage of APIIO, please refer to the previous section.

push :: ID -> [Message] -> APIIO () Source #

Push messages into a receiver. The receiver can be a user, a room or a group, specified by ID.

A Message represents a message object. For types of the message object, please refer to the Send message object section of the LINE documentation.

An example usage of Message is like below:

messages :: [Message]
messages = [ Message $ Image imageURL previewURL
           , Message $ Text "hello, world!"
           , Message $ Template "an example template"
               Confirm "a confirm template"
                 [ TplMessageAction "ok label" "print this"
                 , TplURIAction "link label" linkURL
                 ]
           ]

For more information about the API, please refer to the API reference.

multicast :: [ID] -> [Message] -> APIIO () Source #

Send messages to multiple users at any time.

Messages cannot be sent to groups or rooms.

For more information, please refer to its API reference.

reply :: ReplyToken -> [Message] -> APIIO () Source #

Send messages as a reply to specific webhook event.

It works similarly to how push does for messages, except that it can only reply through a specific reply token. The token can be obtained from replyable events on a webhook server.

For more information, please refer to its API reference.

getContent :: ID -> APIIO ByteString Source #

Get content body of images, videos and audios sent with event messages, specified by ID.

In the event messages, the content body is not included. Users should use getContent to downloaded the content only when it is really needed.

For more information, please refer to its API reference.

getProfile :: ID -> APIIO Profile Source #

Get a profile of a user, specified by ID.

The user identifier can be obtained via EventSource.

For more information, please refer to its API reference.

leaveRoom :: ID -> APIIO () Source #

Leave a room, specified by ID.

For more information, please refer to its API reference.

leaveGroup :: ID -> APIIO () Source #

Leave a group, specified by ID.

For more information, please refer to its API reference.