Last active
August 29, 2015 14:20
-
-
Save rnons/73a5dcb42a67b071656d to your computer and use it in GitHub Desktop.
Track twitter stream and send to BearyChat
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE OverloadedStrings #-} | |
{-# LANGUAGE PatternGuards #-} | |
import Control.Lens hiding ((.=)) | |
import Control.Monad | |
import Control.Monad.IO.Class | |
import Data.Aeson ((.=), object, encode) | |
import qualified Data.ByteString.Lazy as L | |
import qualified Data.Conduit as C | |
import qualified Data.Conduit.List as CL | |
import Data.Monoid ((<>)) | |
import qualified Data.Text as T | |
import qualified Data.Text.Lazy as TL | |
import Data.Text.Format (format) | |
import qualified Data.Text.IO as T | |
import Network.HTTP.Conduit as HTTP | |
import Web.Authenticate.OAuth | |
import Web.Twitter.Conduit | |
import Web.Twitter.Types.Lens | |
tokens :: OAuth | |
tokens = twitterOAuth | |
{ oauthConsumerKey = "key" | |
, oauthConsumerSecret = "secret" | |
} | |
credential :: Credential | |
credential = Credential | |
[ ("oauth_token", "token") | |
, ("oauth_token_secret", "secret") | |
] | |
twInfo :: TWInfo | |
twInfo = def | |
{ twToken = def { twOAuth = tokens, twCredential = credential } | |
, twProxy = Nothing | |
} | |
main :: IO () | |
main = withManager $ \mgr -> do | |
src <- stream twInfo mgr $ statusesFilterByTrack "bearyinnovative, bearychat, 一熊" | |
src C.$$+- CL.mapM_ (liftIO . printTL) | |
showStatus :: AsStatus s => s -> T.Text | |
showStatus s = TL.toStrict $ | |
format "[{}]({}): {} :point_right: [View Tweet]({})" (userName', userProfileUrl, text', tweetUrl) | |
where | |
userName' = s ^. user . userName | |
userProfileUrl = "https://twitter.com/" <> s ^. user . userScreenName | |
tweetUrl = format "{}/status/{}" (userProfileUrl, s ^. status_id) | |
text' = s ^. text | |
sendToBearyChat :: T.Text -> IO () | |
sendToBearyChat tweet = do | |
req' <- parseUrl botUrl | |
let payload = object [ "text" .= tweet | |
] | |
query = [("payload", L.toStrict $ encode payload)] | |
req = urlEncodedBody query req' | |
void $ withManager $ httpLbs req | |
where | |
botUrl = "https://hook.bearychat.com/incoming-bot-token" | |
printTL :: StreamingAPI -> IO () | |
printTL (SStatus s) = (T.putStrLn >> sendToBearyChat) $ showStatus s | |
printTL (SRetweetedStatus s) = T.putStrLn $ T.concat [ s ^. user . userScreenName | |
, ": RT @" | |
, showStatus (s ^. rsRetweetedStatus) | |
] | |
printTL (SEvent event) | |
| (event^.evEvent) == "favorite" || (event^.evEvent) == "unfavorite", | |
Just (ETStatus st) <- event ^. evTargetObject = do | |
let fromUser = evUserInfo (event^.evSource) | |
toUser = evUserInfo (event^.evTarget) | |
evUserInfo (ETUser u) = u ^. userScreenName | |
evUserInfo _ = "" | |
header = T.concat [ event ^. evEvent, "[", fromUser, " -> ", toUser, "]"] | |
T.putStrLn $ T.concat [ header, " :: ", showStatus st ] | |
printTL s = print s |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment