Safe Haskell | None |
---|---|
Language | Haskell2010 |
Various utilities to tweet using the twitter api
Make sure you have a file credentials file (default the executable looks for is `.cred`) with the following info:
api-key: API_KEY api-sec: API_SECRE tok: OAUTH_TOKEN tok-sec: TOKEN_SECRET
- basicTweet :: String -> FilePath -> IO Int
- thread :: String -> [String] -> Maybe Int -> Int -> FilePath -> IO ()
- data Tweet = Tweet {}
- data TweetEntity = TweetEntity {
- _text :: String
- _name :: String
- _screenName :: String
- _tweetId :: Int
- _quoted :: Maybe TweetEntity
- _retweets :: Int
- _favorites :: Int
- type Timeline = [TweetEntity]
- type Config = (OAuth, Credential)
- status :: Lens' Tweet String
- replyID :: Lens' Tweet (Maybe Int)
- handles :: Lens' Tweet [String]
- tweetId :: Lens' TweetEntity Int
- text :: Lens' TweetEntity String
- screenName :: Lens' TweetEntity String
- retweets :: Lens' TweetEntity Int
- quoted :: Lens' TweetEntity (Maybe TweetEntity)
- name :: Lens' TweetEntity String
- favorites :: Lens' TweetEntity Int
- getMarkov :: String -> Maybe Int -> FilePath -> IO [String]
- getAll :: String -> Maybe Int -> FilePath -> IO Timeline
- tweetData :: Tweet -> FilePath -> IO Int
- getProfileMax :: String -> Int -> FilePath -> Maybe Int -> IO (Either (ParseError Char Dec) Timeline)
- getProfileRaw :: String -> Int -> FilePath -> Maybe Int -> IO ByteString
- mentions :: Int -> FilePath -> IO (Either (ParseError Char Dec) Timeline)
- mentionsRaw :: Int -> FilePath -> IO ByteString
- getProfile :: String -> Int -> FilePath -> IO (Either (ParseError Char Dec) Timeline)
- showProfile :: String -> Int -> Bool -> FilePath -> IO String
- showBest :: String -> Int -> Bool -> FilePath -> IO String
- showTimeline :: Int -> Bool -> FilePath -> IO String
- showTweets :: Bool -> Either (ParseError Char Dec) Timeline -> String
- getDMsRaw :: Show t => t -> FilePath -> IO ByteString
- getTimeline :: Int -> FilePath -> IO (Either (ParseError Char Dec) Timeline)
- getTimelineRaw :: Int -> FilePath -> IO ByteString
- deleteTweet :: Integer -> FilePath -> IO ()
- deleteTweetResponse :: Integer -> FilePath -> IO (Either (ParseError Char Dec) Timeline)
- favoriteTweet :: Integer -> FilePath -> IO ()
- favoriteTweetResponse :: Integer -> FilePath -> IO (Either (ParseError Char Dec) Timeline)
- unfavoriteTweet :: Integer -> FilePath -> IO ()
- unfavoriteTweetResponse :: Integer -> FilePath -> IO (Either (ParseError Char Dec) Timeline)
- unretweetTweet :: Integer -> FilePath -> IO ()
- unretweetTweetResponse :: Integer -> FilePath -> IO (Either (ParseError Char Dec) Timeline)
- unfollow :: String -> FilePath -> IO ()
- follow :: String -> FilePath -> IO ()
- block :: String -> FilePath -> IO ()
- unblock :: String -> FilePath -> IO ()
- retweetTweet :: Integer -> FilePath -> IO ()
- retweetTweetResponse :: Integer -> FilePath -> IO (Either (ParseError Char Dec) Timeline)
- favoriteTweetRaw :: Integer -> FilePath -> IO ByteString
- retweetTweetRaw :: Integer -> FilePath -> IO ByteString
- sendDMRaw :: String -> [Char] -> FilePath -> IO ByteString
- getDMs :: Int -> FilePath -> IO ByteString
- followUserRaw :: String -> FilePath -> IO ByteString
- blockUserRaw :: String -> FilePath -> IO ByteString
- unblockUserRaw :: String -> FilePath -> IO ByteString
- unfollowUserRaw :: String -> FilePath -> IO ByteString
- unretweetTweetRaw :: Integer -> FilePath -> IO ByteString
- unfavoriteTweetRaw :: Integer -> FilePath -> IO ByteString
- deleteTweetRaw :: Integer -> FilePath -> IO ByteString
- signRequest :: FilePath -> Request -> IO Request
- urlString :: Tweet -> String
Functions to tweet
basicTweet :: String -> FilePath -> IO Int Source #
Tweet a string given a path to credentials; return the id of the status.
basicTweet "On the airplane." ".cred"
thread :: String -> [String] -> Maybe Int -> Int -> FilePath -> IO () Source #
thread tweets together nicely. Takes a string, a list of handles to reply to, plus the ID of the status you're replying to.
If you need to thread tweets without replying, pass a Nothing
as the third argument.
thread "Hi I'm back in New York!" ["friend1","friend2"] Nothing 1 ".cred"
Data type for a tweet
Data type for our request: consists of the status text, whether to trium user information in the response, the handles to mention, and optionally the id of the status to reply to.
data TweetEntity Source #
Data type for tweets as they are returned
TweetEntity | |
|
type Timeline = [TweetEntity] Source #
Stores data like (name, text, favoriteCount, retweetCount)
type Config = (OAuth, Credential) Source #
Contains an OAuth
and a Credential
; encapsulates everything needed to sign a request.
Various API calls
getMarkov :: String -> Maybe Int -> FilePath -> IO [String] Source #
Get tweets (text only) for some user
tweetData :: Tweet -> FilePath -> IO Int Source #
tweet, given a Tweet
and path to credentials. Return id of posted tweet.
getProfileMax :: String -> Int -> FilePath -> Maybe Int -> IO (Either (ParseError Char Dec) Timeline) Source #
Gets user profile with max_id set.
getProfileRaw :: String -> Int -> FilePath -> Maybe Int -> IO ByteString Source #
Gets user profile with max_id set.
mentions :: Int -> FilePath -> IO (Either (ParseError Char Dec) Timeline) Source #
Get mentions and parse response as a list of tweets
mentionsRaw :: Int -> FilePath -> IO ByteString Source #
Gets mentions
getProfile :: String -> Int -> FilePath -> IO (Either (ParseError Char Dec) Timeline) Source #
Get user profile given screen name and how many tweets to return
showProfile :: String -> Int -> Bool -> FilePath -> IO String Source #
Show a user profile given screen name, how many tweets to return, and whether to print them in color.
showBest :: String -> Int -> Bool -> FilePath -> IO String Source #
Show the most successful tweets by a given user, given their screen name.
showTweets :: Bool -> Either (ParseError Char Dec) Timeline -> String Source #
Display user timeline in color, as appropriate
getTimelineRaw :: Int -> FilePath -> IO ByteString Source #
Get a user's timeline and return response as a bytestring
deleteTweetResponse :: Integer -> FilePath -> IO (Either (ParseError Char Dec) Timeline) Source #
Get response, i.e. the tweet deleted
favoriteTweetResponse :: Integer -> FilePath -> IO (Either (ParseError Char Dec) Timeline) Source #
Favorite a tweet and returned the (parsed) response
unfavoriteTweetResponse :: Integer -> FilePath -> IO (Either (ParseError Char Dec) Timeline) Source #
Unfavorite a tweet and returned the (parsed) response
unretweetTweetResponse :: Integer -> FilePath -> IO (Either (ParseError Char Dec) Timeline) Source #
Unretweet a tweet and returned the (parsed) response
retweetTweetResponse :: Integer -> FilePath -> IO (Either (ParseError Char Dec) Timeline) Source #
Retweet a tweet and returned the (parsed) response
favoriteTweetRaw :: Integer -> FilePath -> IO ByteString Source #
Favorite a tweet given its id; return bytestring response
retweetTweetRaw :: Integer -> FilePath -> IO ByteString Source #
Retweet a tweet given its id; return bytestring response
sendDMRaw :: String -> [Char] -> FilePath -> IO ByteString Source #
Send a DM given text, screen name of recipient.
followUserRaw :: String -> FilePath -> IO ByteString Source #
Follow a user given their screen name
blockUserRaw :: String -> FilePath -> IO ByteString Source #
Block a user given their screen name
unblockUserRaw :: String -> FilePath -> IO ByteString Source #
Unblock a user given their screen name
unfollowUserRaw :: String -> FilePath -> IO ByteString Source #
Follow a user given their screen name
unretweetTweetRaw :: Integer -> FilePath -> IO ByteString Source #
Unretweet a tweet given its id; return bytestring response
unfavoriteTweetRaw :: Integer -> FilePath -> IO ByteString Source #
Favorite a tweet given its id; return bytestring response
deleteTweetRaw :: Integer -> FilePath -> IO ByteString Source #
Delete a tweet given its id; return bytestring response
Functions to sign API requests
signRequest :: FilePath -> Request -> IO Request Source #
Sign a request using your OAuth dev token. Uses the IO monad because signatures require a timestamp