| 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/).
Synopsis
- module Web.Twitter.Conduit.Api
- module Web.Twitter.Conduit.Cursor
- module Web.Twitter.Conduit.Request
- module Web.Twitter.Conduit.Response
- module Web.Twitter.Conduit.Stream
- module Web.Twitter.Conduit.Types
- call :: ResponseBodyType responseType => TWInfo -> Manager -> APIRequest apiName responseType -> IO responseType
- call' :: ResponseBodyType value => TWInfo -> Manager -> APIRequest apiName responseType -> IO value
- callWithResponse :: ResponseBodyType responseType => TWInfo -> Manager -> APIRequest apiName responseType -> IO (Response responseType)
- callWithResponse' :: ResponseBodyType value => TWInfo -> Manager -> APIRequest apiName responseType -> IO (Response value)
- sourceWithMaxId :: (MonadIO m, FromJSON responseType, AsStatus responseType, HasParam "max_id" Integer supports) => TWInfo -> Manager -> APIRequest supports [responseType] -> ConduitT () responseType m ()
- sourceWithMaxId' :: (MonadIO m, HasParam "max_id" Integer supports) => TWInfo -> Manager -> APIRequest supports [responseType] -> ConduitT () Value m ()
- sourceWithCursor :: (MonadIO m, FromJSON responseType, KnownSymbol ck, HasParam "cursor" Integer supports) => TWInfo -> Manager -> APIRequest supports (WithCursor Integer ck responseType) -> ConduitT () responseType m ()
- sourceWithCursor' :: (MonadIO m, KnownSymbol ck, HasParam "cursor" Integer supports) => TWInfo -> Manager -> APIRequest supports (WithCursor Integer ck responseType) -> ConduitT () Value m ()
- sourceWithSearchResult :: (MonadIO m, FromJSON responseType) => TWInfo -> Manager -> APIRequest supports (SearchResult [responseType]) -> m (SearchResult (ConduitT () responseType m ()))
- sourceWithSearchResult' :: MonadIO m => TWInfo -> Manager -> APIRequest supports (SearchResult [responseType]) -> m (SearchResult (ConduitT () Value m ()))
- data ListParam
- data MediaData
- data UserListParam
- data UserParam
- data TweetMode = Extended
- data OAuth
- newtype Credential = Credential {
- unCredential :: [(ByteString, ByteString)]
- def :: Default a => a
- data Manager
- newManager :: ManagerSettings -> IO Manager
- tlsManagerSettings :: ManagerSettings
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:
{--}
{--}
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
Authentication
First, you should obtain consumer token and secret from Twitter,
and prepare OAuth variables as follows:
tokens ::OAuthtokens =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 ::Credentialcredential =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 ::TWInfotwInfo =def{twToken=def{twOAuth= tokens,twCredential= credential } ,twProxy= Nothing }
Or, simply as follows:
twInfo =setCredentialtokens credentialdef
How to call API
Twitter API requests are performed by call function.
For example, GET statuses/home_timeline
could be obtained by:
mgr <-newManagertlsManagerSettingstimeline <-calltwInfo mgrstatusesHomeTimeline
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 <-calltwInfo mgr$statusesHomeTimeline&#count?~200
How to specify API parameters
The parameters which can be specified for this API, is able to be obtained from type parameters of APIRequest. For example,
statusesHomeTimeline::APIRequestStatusesHomeTimeline[Status]
- The 2nd type parameter of
APIRequestrepresents acceptable parameters in this API request. - The 3nd type parameter of
APIRequestdenotes a return type of this API request.
The 2nd type parameter of statusesHomeTimeline is StatusesHomeTimeline defined as below:
type StatusesHomeTimeline =
'[ "count" ':= Integer
, "since_id" ':= Integer
, "max_id" ':= Integer
, "trim_user" ':= Bool
, "exclude_replies" ':= Bool
, "contributor_details" ':= Bool
, "include_entities" ':= Bool
, "tweet_mode" ':= TweetMode
]
Each element of list represents the name and type of API parameters.
You can specify those parameter with OverloadedLabels extension.
In the above example, it shows that statusesHomeTimeline API supports "tweet_mode" parameter with TweetMode type, so
you can specify "tweet_mode" parameter as:
statusesHomeTimeline& #tweet_mode ?~Extended
Conduit API: Recursive API call with changing cursor parameter
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 <-
runConduit $
sourceWithMaxId twInfo mgr (friendsList (ScreenNameParam "thimura") & #count ?~ 200)
.| consume
Statuses APIs, for instance, homeTimeline, are also wrapped by sourceWithMaxId.
For example, you can print 60 tweets from your home timeline, as below:
main :: IO ()
main = do
mgr <- newManager tlsManagerSettings
runConduit $ sourceWithMaxId twInfo mgr homeTimeline
.| CL.isolate 60
.| CL.mapM_
(\status -> 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.Stream
module Web.Twitter.Conduit.Types
Base
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 <-calltwInfo mgr $accountVerifyCredentialsprint user
If you need raw JSON value which is parsed by aeson,
use call' to obtain it.
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.
Arguments
| :: ResponseBodyType responseType | |
| => TWInfo | Twitter Setting |
| -> Manager | |
| -> APIRequest apiName responseType | |
| -> IO (Response responseType) |
Perform an APIRequest and then provide the Response.
Example:
res <-callWithResponsetwInfo mgr $accountVerifyCredentialsresponseStatusresresponseHeadersresresponseBodyres
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 $accountVerifyCredentialsresponseStatusresresponseHeadersresresponseBody(res :: Value)
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.
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.
Arguments
| :: (MonadIO m, FromJSON responseType, KnownSymbol 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.
Arguments
| :: (MonadIO m, KnownSymbol 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
Constructors
| ListIdParam Integer | |
| ListNameParam String |
Constructors
| MediaFromFile FilePath | |
| MediaRequestBody FilePath RequestBody |
data UserListParam Source #
Constructors
| UserIdListParam [UserId] | |
| ScreenNameListParam [String] |
Instances
| Eq UserListParam Source # | |
Defined in Web.Twitter.Conduit.Parameters Methods (==) :: UserListParam -> UserListParam -> Bool # (/=) :: UserListParam -> UserListParam -> Bool # | |
| Show UserListParam Source # | |
Defined in Web.Twitter.Conduit.Parameters Methods showsPrec :: Int -> UserListParam -> ShowS # show :: UserListParam -> String # showList :: [UserListParam] -> ShowS # | |
Constructors
| UserIdParam UserId | |
| ScreenNameParam String |
Constructors
| Extended |
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.
Instances
| Eq OAuth | |
| Data OAuth | |
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 # 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 | |
| Show OAuth | |
| Default OAuth | |
Defined in Web.Authenticate.OAuth | |
newtype Credential #
Data type for credential.
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
| HasHttpManager Manager | |
Defined in Network.HTTP.Client.Types Methods getHttpManager :: Manager -> Manager # | |
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