Copyright | (c) 2014 Takahiro Himura |
---|---|
License | BSD |
Maintainer | Takahiro Himura <taka@himura.jp> |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Web.Twitter.Conduit
Description
A client library for Twitter APIs (see https://dev.twitter.com/).
- module Web.Twitter.Conduit.Api
- module Web.Twitter.Conduit.Cursor
- module Web.Twitter.Conduit.Request
- module Web.Twitter.Conduit.Response
- module Web.Twitter.Conduit.Status
- module Web.Twitter.Conduit.Stream
- module Web.Twitter.Conduit.Types
- call :: FromJSON responseType => TWInfo -> Manager -> APIRequest apiName responseType -> IO responseType
- call' :: FromJSON value => TWInfo -> Manager -> APIRequest apiName responseType -> IO value
- callWithResponse :: FromJSON responseType => TWInfo -> Manager -> APIRequest apiName responseType -> IO (Response responseType)
- callWithResponse' :: FromJSON value => TWInfo -> Manager -> APIRequest apiName responseType -> IO (Response value)
- sourceWithMaxId :: (MonadIO m, FromJSON responseType, AsStatus responseType, HasMaxIdParam (APIRequest apiName [responseType])) => TWInfo -> Manager -> APIRequest apiName [responseType] -> Source m responseType
- sourceWithMaxId' :: (MonadIO m, HasMaxIdParam (APIRequest apiName [responseType])) => TWInfo -> Manager -> APIRequest apiName [responseType] -> Source m Value
- sourceWithCursor :: (MonadIO m, FromJSON responseType, CursorKey ck, HasCursorParam (APIRequest apiName (WithCursor ck responseType))) => TWInfo -> Manager -> APIRequest apiName (WithCursor ck responseType) -> Source m responseType
- sourceWithCursor' :: (MonadIO m, CursorKey ck, HasCursorParam (APIRequest apiName (WithCursor ck responseType))) => TWInfo -> Manager -> APIRequest apiName (WithCursor ck responseType) -> Source m Value
- sourceWithSearchResult :: (MonadIO m, FromJSON responseType) => TWInfo -> Manager -> APIRequest apiName (SearchResult [responseType]) -> m (SearchResult (Source m responseType))
- sourceWithSearchResult' :: MonadIO m => TWInfo -> Manager -> APIRequest apiName (SearchResult [responseType]) -> m (SearchResult (Source m Value))
- data ListParam
- data MediaData
- data UserListParam
- data UserParam
- data OAuth :: *
- newtype Credential :: * = Credential {
- unCredential :: [(ByteString, ByteString)]
- def :: Default a => a
- data Manager :: *
- newManager :: ManagerSettings -> IO Manager
- tlsManagerSettings :: ManagerSettings
- contributorDetails :: HasContributorDetailsParam a => Lens' a (Maybe Bool)
- count :: HasCountParam a => Lens' a (Maybe Integer)
- cursor :: HasCursorParam a => Lens' a (Maybe Integer)
- displayCoordinates :: HasDisplayCoordinatesParam a => Lens' a (Maybe Bool)
- excludeReplies :: HasExcludeRepliesParam a => Lens' a (Maybe Bool)
- filterLevel :: HasFilterLevelParam a => Lens' a (Maybe Text)
- follow :: HasFollowParam a => Lens' a (Maybe Bool)
- inReplyToStatusId :: HasInReplyToStatusIdParam a => Lens' a (Maybe Integer)
- includeEntities :: HasIncludeEntitiesParam a => Lens' a (Maybe Bool)
- includeMyRetweet :: HasIncludeMyRetweetParam a => Lens' a (Maybe Bool)
- includeRts :: HasIncludeRtsParam a => Lens' a (Maybe Bool)
- includeUserEntities :: HasIncludeUserEntitiesParam a => Lens' a (Maybe Bool)
- lang :: HasLangParam a => Lens' a (Maybe Text)
- language :: HasLanguageParam a => Lens' a (Maybe Text)
- locale :: HasLocaleParam a => Lens' a (Maybe Text)
- map :: HasMapParam a => Lens' a (Maybe Bool)
- maxId :: HasMaxIdParam a => Lens' a (Maybe Integer)
- mediaIds :: HasMediaIdsParam a => Lens' a (Maybe [Integer])
- page :: HasPageParam a => Lens' a (Maybe Integer)
- possiblySensitive :: HasPossiblySensitiveParam a => Lens' a (Maybe Bool)
- replies :: HasRepliesParam a => Lens' a (Maybe Text)
- sinceId :: HasSinceIdParam a => Lens' a (Maybe Integer)
- skipStatus :: HasSkipStatusParam a => Lens' a (Maybe Bool)
- stallWarnings :: HasStallWarningsParam a => Lens' a (Maybe Bool)
- trimUser :: HasTrimUserParam a => Lens' a (Maybe Bool)
- until :: HasUntilParam a => Lens' a (Maybe Day)
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 mgrhomeTimeline
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 mgrhomeTimeline
$= CL.isolate 60 $$ CL.mapM_ $ \status -> liftIO $ do T.putStrLn $ T.concat [ T.pack . show $ status ^. statusId , ": " , status ^. statusUser . userScreenName , ": " , status ^. statusText ]
Re-exports
module Web.Twitter.Conduit.Api
module Web.Twitter.Conduit.Cursor
module Web.Twitter.Conduit.Request
module Web.Twitter.Conduit.Response
module Web.Twitter.Conduit.Status
module Web.Twitter.Conduit.Stream
module Web.Twitter.Conduit.Types
Base
Arguments
:: FromJSON 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.
Arguments
:: FromJSON 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.
Arguments
:: FromJSON 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
responseStatus
resresponseHeaders
resresponseBody
res
callWithResponse' :: FromJSON 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
responseStatus
resresponseHeaders
resresponseBody
(res :: Value)
Arguments
:: (MonadIO 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
.
Arguments
:: (MonadIO 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
.
Arguments
:: (MonadIO 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
.
Arguments
:: (MonadIO m, 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
.
sourceWithSearchResult Source #
Arguments
:: (MonadIO m, FromJSON responseType) | |
=> TWInfo | Twitter Setting |
-> Manager | |
-> APIRequest apiName (SearchResult [responseType]) | |
-> m (SearchResult (Source m responseType)) |
A wrapper function to perform multiple API request with SearchResult
.
sourceWithSearchResult' Source #
Arguments
:: MonadIO m | |
=> TWInfo | Twitter Setting |
-> Manager | |
-> APIRequest apiName (SearchResult [responseType]) | |
-> m (SearchResult (Source m Value)) |
A wrapper function to perform multiple API request with SearchResult
.
Parameters
Constructors
ListIdParam Integer | |
ListNameParam String |
Constructors
MediaFromFile FilePath | |
MediaRequestBody FilePath RequestBody |
data UserListParam Source #
Constructors
UserIdListParam [UserId] | |
ScreenNameListParam [String] |
Instances
Constructors
UserIdParam UserId | |
ScreenNameParam String |
re-exports
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.
newtype Credential :: * #
Data type for redential.
Constructors
Credential | |
Fields
|
Instances
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
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
deprecated
contributorDetails :: HasContributorDetailsParam a => Lens' a (Maybe Bool) Source #
Deprecated: Please use Web.Twitter.Conduit.Parameters.contributorDetails
count :: HasCountParam a => Lens' a (Maybe Integer) Source #
Deprecated: Please use Web.Twitter.Conduit.Parameters.count
cursor :: HasCursorParam a => Lens' a (Maybe Integer) Source #
Deprecated: Please use Web.Twitter.Conduit.Parameters.cursor
displayCoordinates :: HasDisplayCoordinatesParam a => Lens' a (Maybe Bool) Source #
Deprecated: Please use Web.Twitter.Conduit.Parameters.displayCoordinates
excludeReplies :: HasExcludeRepliesParam a => Lens' a (Maybe Bool) Source #
Deprecated: Please use Web.Twitter.Conduit.Parameters.excludeReplies
filterLevel :: HasFilterLevelParam a => Lens' a (Maybe Text) Source #
Deprecated: Please use Web.Twitter.Conduit.Parameters.filterLevel
follow :: HasFollowParam a => Lens' a (Maybe Bool) Source #
Deprecated: Please use Web.Twitter.Conduit.Parameters.follow
inReplyToStatusId :: HasInReplyToStatusIdParam a => Lens' a (Maybe Integer) Source #
Deprecated: Please use Web.Twitter.Conduit.Parameters.inReplyToStatusId
includeEntities :: HasIncludeEntitiesParam a => Lens' a (Maybe Bool) Source #
Deprecated: Please use Web.Twitter.Conduit.Parameters.includeEntities
includeMyRetweet :: HasIncludeMyRetweetParam a => Lens' a (Maybe Bool) Source #
Deprecated: Please use Web.Twitter.Conduit.Parameters.includeMyRetweet
includeRts :: HasIncludeRtsParam a => Lens' a (Maybe Bool) Source #
Deprecated: Please use Web.Twitter.Conduit.Parameters.includeRts
includeUserEntities :: HasIncludeUserEntitiesParam a => Lens' a (Maybe Bool) Source #
Deprecated: Please use Web.Twitter.Conduit.Parameters.includeUserEntities
lang :: HasLangParam a => Lens' a (Maybe Text) Source #
Deprecated: Please use Web.Twitter.Conduit.Parameters.lang
language :: HasLanguageParam a => Lens' a (Maybe Text) Source #
Deprecated: Please use Web.Twitter.Conduit.Parameters.language
locale :: HasLocaleParam a => Lens' a (Maybe Text) Source #
Deprecated: Please use Web.Twitter.Conduit.Parameters.locale
map :: HasMapParam a => Lens' a (Maybe Bool) Source #
Deprecated: Please use Web.Twitter.Conduit.Parameters.map
maxId :: HasMaxIdParam a => Lens' a (Maybe Integer) Source #
Deprecated: Please use Web.Twitter.Conduit.Parameters.maxId
mediaIds :: HasMediaIdsParam a => Lens' a (Maybe [Integer]) Source #
Deprecated: Please use Web.Twitter.Conduit.Parameters.mediaIds
page :: HasPageParam a => Lens' a (Maybe Integer) Source #
Deprecated: Please use Web.Twitter.Conduit.Parameters.page
possiblySensitive :: HasPossiblySensitiveParam a => Lens' a (Maybe Bool) Source #
Deprecated: Please use Web.Twitter.Conduit.Parameters.possiblySensitive
replies :: HasRepliesParam a => Lens' a (Maybe Text) Source #
Deprecated: Please use Web.Twitter.Conduit.Parameters.replies
sinceId :: HasSinceIdParam a => Lens' a (Maybe Integer) Source #
Deprecated: Please use Web.Twitter.Conduit.Parameters.sinceId
skipStatus :: HasSkipStatusParam a => Lens' a (Maybe Bool) Source #
Deprecated: Please use Web.Twitter.Conduit.Parameters.skipStatus
stallWarnings :: HasStallWarningsParam a => Lens' a (Maybe Bool) Source #
Deprecated: Please use Web.Twitter.Conduit.Parameters.stallWarnings