tweet-hs-0.6.1.3: Command-line tool for twitter

Safe HaskellNone
LanguageHaskell2010

Web.Tweet

Contents

Description

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

Synopsis

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 Tweet Source #

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.

Constructors

Tweet 

Instances

Generic Tweet Source # 

Associated Types

type Rep Tweet :: * -> * #

Methods

from :: Tweet -> Rep Tweet x #

to :: Rep Tweet x -> Tweet #

Default Tweet Source # 

Methods

def :: Tweet #

type Rep Tweet Source # 

data TweetEntity Source #

Data type for tweets as they are returned

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.

status :: Lens' Tweet String Source #

Lens for Tweet accessing the status field.

handles :: Lens' Tweet [String] Source #

Lens for Tweet accessing the handles field.

replyID :: Lens' Tweet (Maybe Int) Source #

Lens for Tweet accessing the _replyID field.

text :: Lens' TweetEntity String Source #

Lens for TweetEntity accessing the _text field.

name :: Lens' TweetEntity String Source #

Lens for TweetEntity accessing the _name field.

tweetId :: Lens' TweetEntity Int Source #

Lens for TweetEntity accessing the _tweetId field.

quoted :: Lens' TweetEntity (Maybe TweetEntity) Source #

Lens for TweetEntity accessing the _quoted field.

retweets :: Lens' TweetEntity Int Source #

Lens for TweetEntity accessing the _retweets field.

favorites :: Lens' TweetEntity Int Source #

Lens for TweetEntity accessing the _favorites field.

Various API calls

getMarkov :: String -> Maybe Int -> FilePath -> IO [String] Source #

Get tweets (text only) for some user

getAll :: String -> Maybe Int -> FilePath -> IO Timeline Source #

Get all tweets by 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.

showBest' :: String -> Int -> Bool -> FilePath -> IO String Source #

Show the most successful tweets by a given user, given their screen name. Additionally filter out replies.

mute :: String -> FilePath -> IO () Source #

Mute a user given their screen name

unmute :: String -> FilePath -> IO () Source #

Unmute a user given their screen name

muteUserRaw :: String -> FilePath -> IO ByteString Source #

Mute a user given their screen name

unmuteUserRaw :: String -> FilePath -> IO ByteString Source #

Unmute a user given their screen name

showTimeline :: Int -> Bool -> FilePath -> IO String Source #

Display user timeline

showTweets :: Bool -> Either (ParseError Char Dec) Timeline -> String Source #

Display user timeline in color, as appropriate

getDMsRaw :: Show t => t -> FilePath -> IO ByteString Source #

Get user's DMs.

getTimelineRaw :: Int -> FilePath -> IO ByteString Source #

Get a user's timeline and return response as a bytestring

deleteTweet :: Integer -> FilePath -> IO () Source #

Delete a tweet given its id

deleteTweetResponse :: Integer -> FilePath -> IO (Either (ParseError Char Dec) Timeline) Source #

Get response, i.e. the tweet deleted

favoriteTweet :: Integer -> FilePath -> IO () Source #

Favorite a tweet given its id

favoriteTweetResponse :: Integer -> FilePath -> IO (Either (ParseError Char Dec) Timeline) Source #

Favorite a tweet and returned the (parsed) response

unfavoriteTweet :: Integer -> FilePath -> IO () Source #

Unfavorite a tweet given its id

unfavoriteTweetResponse :: Integer -> FilePath -> IO (Either (ParseError Char Dec) Timeline) Source #

Unfavorite a tweet and returned the (parsed) response

unretweetTweet :: Integer -> FilePath -> IO () Source #

Unretweet a tweet given its id

unretweetTweetResponse :: Integer -> FilePath -> IO (Either (ParseError Char Dec) Timeline) Source #

Unretweet a tweet and returned the (parsed) response

unfollow :: String -> FilePath -> IO () Source #

Unfollow a user given their screen name

follow :: String -> FilePath -> IO () Source #

Follow a user given their screen name

block :: String -> FilePath -> IO () Source #

Block a user given their screen name

unblock :: String -> FilePath -> IO () Source #

Unblock a user given their screen name

retweetTweet :: Integer -> FilePath -> IO () Source #

Retweet a tweet given its id

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.

getDMs :: Int -> FilePath -> IO ByteString Source #

Get DMs, return bytestring of response

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, as stored in a config file. Uses the IO monad because signatures require a timestamp

Functions to generate a URL string from a Tweet

urlString :: Tweet -> String Source #

Convert a tweet to a percent-encoded url for querying an API

Helper function to print a bird