twitter-conduit-0.0.2.1: Twitter API package with conduit interface and Streaming API support.

Portabilityportable
Stabilityexperimental
MaintainerTakahiro Himura <taka@himura.jp>
Safe HaskellNone

Web.Twitter.Conduit

Contents

Description

A client library for Twitter APIs (see https://dev.twitter.com/).

Synopsis

How to use this library

The main module of twitter-conduit is Web.Twitter.Conduit. This library cooperate with twitter-types, authenticate-oauth, and conduit. All of following examples import modules as below:

 {-# LANGUAGE OverloadedStrings #-}

 import Web.Twitter.Conduit
 import Web.Authenticate.OAuth
 import Data.Conduit
 import qualified Data.Conduit.List as CL
 import qualified Data.Text as T
 import qualified Data.Text.IO as T
 import Control.Monad.Logger
 import Control.Monad.IO.Class
 import Control.Lens

First, you should obtain consumer token and secret from Twitter, and prepare OAuth variables as follows:

 tokens :: OAuth
 tokens = twitterOAuth
     { oauthConsumerKey = "YOUR CONSUMER KEY"
     , oauthConsumerSecret = "YOUR CONSUMER SECRET"
     }

Second, you should obtain access token and secret. You can find examples obtaining those tokens in sample directry, for instance, oauth_pin.hs, and oauth_callback.hs. If you need more information, see https://dev.twitter.com/docs/auth/obtaining-access-tokens.

You should set an access token to Credential variable:

 credential :: Credential
 credential = Credential
     [ ("oauth_token", "YOUR ACCESS TOKEN")
     , ("oauth_token_secret", "YOUR ACCESS TOKEN SECRET")
     ]

You should also set up the TWToken and TWInfo variables as below:

 twInfo :: TWInfo
 twInfo = def
     { twToken = def { twOAuth = tokens, twCredential = credential }
     , twProxy = Nothing
     }

Or, simply as follows:

 twInfo = setCredential tokens credential def

Every twitter API functions are run in the TW monad. By using runTW function, you can perform computation in TW monad.

Twitter API requests are performed by call function. For example, GET statuses/home_timeline could be obtained by:

 timeline <- call homeTimeline

The response of call function is wrapped by the suitable type of twitter-types. In this case, timeline has a type of [Status]. If you need raw JSON Value which is parsed by aeson, use call' to obtain it.

By default, the response of GET statuses/home_timeline includes 20 tweets, and you can change the number of tweets by the count parameter.

 timeline <- call $ homeTimeline & count ?~ 200

If you need more statuses, you can obtain those with multiple API requests. This library provides the wrapper for multiple requests with conduit interfaces. For example, if you intend to fetch the all friends information, you may perform multiple API requests with changing cursor parameter, or use the conduit wrapper sourceWithCursor as below:

 friends <- sourceWithCursor (friendsList (ScreenNameParam "thimura") & count ?~ 200) $$ consume

Statuses APIs, for instance, homeTimeline, are also wrapped by sourceWithMaxId.

For example, you can print 1000 tweets from your home timeline, as below:

 main :: IO ()
 main = runNoLoggingT . runTW twInfo $ do
     sourceWithMaxId homeTimeline
         $= CL.isolate 60
         $$ CL.mapM_ $ status -> liftIO $ do
             T.putStrLn $ T.concat [ T.pack . show $ status ^. statusId
                                   , ": "
                                   , status ^. statusUser . userScreenName
                                   , ": "
                                   , status ^. statusText
                                   ]

Re-exports