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

Copyright(c) 2014 Takahiro Himura
LicenseBSD
MaintainerTakahiro Himura <taka@himura.jp>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell98

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.Twitter.Types.Lens
import Web.Authenticate.OAuth
import Network.HTTP.Conduit
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.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

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

timeline <- withManager $ \mgr -> call twInfo mgr 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 <- withManager $ \mgr -> call twInfo mgr $ 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 <- withManager $ \mgr -> sourceWithCursor twInfo mgr (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 = withManager $ mgr -> do
    sourceWithMaxId twInfo mgr 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

Base

call Source

Arguments

:: (MonadResource m, FromJSON responseType) 
=> TWInfo

Twitter Setting

-> Manager 
-> APIRequest apiName responseType 
-> m responseType 

Perform an APIRequest and then provide the response which is mapped to a suitable type of twitter-types.

Example:

withManager $ \mgr -> do
     user <- call twInfo mgr $ accountVerifyCredentials
     liftIO $ print user

If you need raw JSON value which is parsed by aeson, use call' to obtain it.

call' Source

Arguments

:: (MonadResource m, FromJSON value) 
=> TWInfo

Twitter Setting

-> Manager 
-> APIRequest apiName responseType 
-> m value 

Perform an APIRequest and then provide the response. The response of this function is not restrict to responseType, so you can choose an arbitrarily type of FromJSON instances.

callWithResponse Source

Arguments

:: (MonadResource m, FromJSON responseType) 
=> TWInfo

Twitter Setting

-> Manager 
-> APIRequest apiName responseType 
-> m (Response responseType) 

Perform an APIRequest and then provide the Response.

Example:

res <- withManager $ \mgr -> do
    callWithResponse twInfo mgr $ accountVerifyCredentials
print $ responseStatus res
print $ responseHeaders res
print $ responseBody res

callWithResponse' :: (MonadResource m, FromJSON value) => TWInfo -> Manager -> APIRequest apiName responseType -> m (Response value) Source

Perform an APIRequest and then provide the Response. The response of this function is not restrict to responseType, so you can choose an arbitrarily type of FromJSON instances.

Example:

res <- withManager $ \mgr -> do
    callWithResponse' twInfo mgr $ accountVerifyCredentials
print $ responseStatus res
print $ responseHeaders res
print $ responseBody (res :: Value)

sourceWithMaxId Source

Arguments

:: (MonadResource m, FromJSON responseType, AsStatus responseType, HasMaxIdParam (APIRequest apiName [responseType])) 
=> TWInfo

Twitter Setting

-> Manager 
-> APIRequest apiName [responseType] 
-> Source m responseType 

A wrapper function to perform multiple API request with changing max_id parameter.

This function cooperate with instances of HasMaxIdParam.

sourceWithMaxId' Source

Arguments

:: (MonadResource m, HasMaxIdParam (APIRequest apiName [responseType])) 
=> TWInfo

Twitter Setting

-> Manager 
-> APIRequest apiName [responseType] 
-> Source m Value 

A wrapper function to perform multiple API request with changing max_id parameter. The response of this function is not restrict to responseType, so you can choose an arbitrarily type of FromJSON instances.

This function cooperate with instances of HasMaxIdParam.

sourceWithCursor Source

Arguments

:: (MonadResource m, FromJSON responseType, CursorKey ck, HasCursorParam (APIRequest apiName (WithCursor ck responseType))) 
=> TWInfo

Twitter Setting

-> Manager 
-> APIRequest apiName (WithCursor ck responseType) 
-> Source m responseType 

A wrapper function to perform multiple API request with changing cursor parameter.

This function cooperate with instances of HasCursorParam.

sourceWithCursor' Source

Arguments

:: (MonadResource m, FromJSON responseType, CursorKey ck, HasCursorParam (APIRequest apiName (WithCursor ck responseType))) 
=> TWInfo

Twitter Setting

-> Manager 
-> APIRequest apiName (WithCursor ck responseType) 
-> Source m Value 

A wrapper function to perform multiple API request with changing cursor parameter. The response of this function is not restrict to responseType, so you can choose an arbitrarily type of FromJSON instances.

This function cooperate with instances of HasCursorParam.

Backward compativility

In the version below 0.1.0, twitter-conduit provides the TW monad, and every Twitter API functions are run in the TW monad.

For backward compatibility, TW monad and the functions are provided in the Web.Twitter.Conduit.Monad module.