twitter-conduit-0.5.1: 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
LanguageHaskell2010

Web.Twitter.Conduit

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 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:

mgr <- newManager tlsManagerSettings
timeline <- 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 <- 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 <- 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 = do
    mgr <- newManager tlsManagerSettings
    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

:: ResponseBodyType responseType 
=> TWInfo

Twitter Setting

-> Manager 
-> APIRequest apiName responseType 
-> IO responseType 

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

Example:

user <- call twInfo mgr $ accountVerifyCredentials
print user

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

call' Source #

Arguments

:: ResponseBodyType value 
=> TWInfo

Twitter Setting

-> Manager 
-> APIRequest apiName responseType 
-> IO 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

:: ResponseBodyType responseType 
=> TWInfo

Twitter Setting

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

Perform an APIRequest and then provide the Response.

Example:

res <- callWithResponse twInfo mgr $ accountVerifyCredentials
print $ responseStatus res
print $ responseHeaders res
print $ responseBody res

callWithResponse' :: ResponseBodyType value => TWInfo -> Manager -> APIRequest apiName responseType -> IO (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 <- callWithResponse' twInfo mgr $ accountVerifyCredentials
print $ responseStatus res
print $ responseHeaders res
print $ responseBody (res :: Value)

sourceWithMaxId Source #

Arguments

:: (MonadIO m, FromJSON responseType, AsStatus responseType, HasParam "max_id" Integer supports) 
=> TWInfo

Twitter Setting

-> Manager 
-> APIRequest supports [responseType] 
-> ConduitT () responseType m () 

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

This function cooperate with instances of HasMaxIdParam.

sourceWithMaxId' Source #

Arguments

:: (MonadIO m, HasParam "max_id" Integer supports) 
=> TWInfo

Twitter Setting

-> Manager 
-> APIRequest supports [responseType] 
-> ConduitT () Value m () 

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

:: (MonadIO m, FromJSON responseType, CursorKey ck, HasParam "cursor" Integer supports) 
=> TWInfo

Twitter Setting

-> Manager 
-> APIRequest supports (WithCursor Integer ck responseType) 
-> ConduitT () responseType m () 

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

This function cooperate with instances of HasCursorParam.

sourceWithCursor' Source #

Arguments

:: (MonadIO m, CursorKey ck, HasParam "cursor" Integer supports) 
=> TWInfo

Twitter Setting

-> Manager 
-> APIRequest supports (WithCursor Integer ck responseType) 
-> ConduitT () Value m () 

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.

sourceWithSearchResult Source #

Arguments

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

Twitter Setting

-> Manager 
-> APIRequest supports (SearchResult [responseType]) 
-> m (SearchResult (ConduitT () responseType m ())) 

A wrapper function to perform multiple API request with SearchResult.

sourceWithSearchResult' Source #

Arguments

:: MonadIO m 
=> TWInfo

Twitter Setting

-> Manager 
-> APIRequest supports (SearchResult [responseType]) 
-> m (SearchResult (ConduitT () Value m ())) 

A wrapper function to perform multiple API request with SearchResult.

Parameters

data ListParam Source #

Instances

Instances details
Eq ListParam Source # 
Instance details

Defined in Web.Twitter.Conduit.Parameters

Show ListParam Source # 
Instance details

Defined in Web.Twitter.Conduit.Parameters

data UserParam Source #

Instances

Instances details
Eq UserParam Source # 
Instance details

Defined in Web.Twitter.Conduit.Parameters

Show UserParam Source # 
Instance details

Defined in Web.Twitter.Conduit.Parameters

re-exports

data OAuth #

Data type for OAuth client (consumer).

The constructor for this data type is not exposed. Instead, you should use the def method or newOAuth function to retrieve a default instance, and then use the records below to make modifications. This approach allows us to add configuration options without breaking backwards compatibility.

Instances

Instances details
Eq OAuth 
Instance details

Defined in Web.Authenticate.OAuth

Methods

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

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

Data OAuth 
Instance details

Defined in Web.Authenticate.OAuth

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OAuth -> c OAuth #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OAuth #

toConstr :: OAuth -> Constr #

dataTypeOf :: OAuth -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OAuth) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OAuth) #

gmapT :: (forall b. Data b => b -> b) -> OAuth -> OAuth #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OAuth -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OAuth -> r #

gmapQ :: (forall d. Data d => d -> u) -> OAuth -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OAuth -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OAuth -> m OAuth #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OAuth -> m OAuth #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OAuth -> m OAuth #

Read OAuth 
Instance details

Defined in Web.Authenticate.OAuth

Show OAuth 
Instance details

Defined in Web.Authenticate.OAuth

Methods

showsPrec :: Int -> OAuth -> ShowS #

show :: OAuth -> String #

showList :: [OAuth] -> ShowS #

Default OAuth 
Instance details

Defined in Web.Authenticate.OAuth

Methods

def :: OAuth #

newtype Credential #

Data type for credential.

Constructors

Credential 

Instances

Instances details
Eq Credential 
Instance details

Defined in Web.Authenticate.OAuth

Data Credential 
Instance details

Defined in Web.Authenticate.OAuth

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Credential -> c Credential #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Credential #

toConstr :: Credential -> Constr #

dataTypeOf :: Credential -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Credential) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Credential) #

gmapT :: (forall b. Data b => b -> b) -> Credential -> Credential #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Credential -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Credential -> r #

gmapQ :: (forall d. Data d => d -> u) -> Credential -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Credential -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Credential -> m Credential #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Credential -> m Credential #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Credential -> m Credential #

Ord Credential 
Instance details

Defined in Web.Authenticate.OAuth

Read Credential 
Instance details

Defined in Web.Authenticate.OAuth

Show Credential 
Instance details

Defined in Web.Authenticate.OAuth

def :: Default a => a #

The default value for this type.

data Manager #

Keeps track of open connections for keep-alive.

If possible, you should share a single Manager between multiple threads and requests.

Since 0.1.0

Instances

Instances details
HasHttpManager Manager 
Instance details

Defined in Network.HTTP.Client.Types

newManager :: ManagerSettings -> IO Manager #

Create a Manager. The Manager will be shut down automatically via garbage collection.

Creating a new Manager is a relatively expensive operation, you are advised to share a single Manager between requests instead.

The first argument to this function is often defaultManagerSettings, though add-on libraries may provide a recommended replacement.

Since 0.1.0

tlsManagerSettings :: ManagerSettings #

Default TLS-enabled manager settings