File: simple.hs

package info (click to toggle)
haskell-twitter-conduit 0.6.1-3
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 284 kB
  • sloc: haskell: 2,066; makefile: 6
file content (69 lines) | stat: -rw-r--r-- 2,167 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE OverloadedStrings #-}

module Main where

import Web.Twitter.Conduit
import Web.Twitter.Types.Lens

import Control.Lens
import qualified Data.ByteString.Char8 as B8
import Data.Conduit
import qualified Data.Conduit.List as CL
import qualified Data.Text as T
import qualified Data.Text.IO as T
import System.IO (hFlush, stdout)
import qualified Web.Authenticate.OAuth as OA

tokens :: OAuth
tokens =
    twitterOAuth
        { oauthConsumerKey = error "You MUST specify oauthConsumerKey parameter."
        , oauthConsumerSecret = error "You MUST specify oauthConsumerSecret parameter."
        }

authorize ::
    -- | OAuth Consumer key and secret
    OAuth ->
    -- | PIN prompt
    (String -> IO String) ->
    Manager ->
    IO Credential
authorize oauth getPIN mgr = do
    cred <- OA.getTemporaryCredential oauth mgr
    let url = OA.authorizeUrl oauth cred
    pin <- getPIN url
    OA.getAccessToken oauth (OA.insert "oauth_verifier" (B8.pack pin) cred) mgr

getTWInfo :: Manager -> IO TWInfo
getTWInfo mgr = do
    Credential cred <- authorize tokens getPIN mgr
    let cred' = filter (\(k, _) -> k == "oauth_token" || k == "oauth_token_secret") cred
    return $ setCredential tokens (Credential cred') def
  where
    getPIN url = do
        putStrLn $ "browse URL: " ++ url
        putStr "> what was the PIN twitter provided you with? "
        hFlush stdout
        getLine

main :: IO ()
main = do
    mgr <- newManager tlsManagerSettings
    twInfo <- getTWInfo mgr
    putStrLn $ "# your home timeline (up to 800 tweets):"
    runConduit $
        sourceWithMaxId twInfo mgr (statusesHomeTimeline & #count ?~ 200)
            .| CL.isolate 800
            .| CL.mapM_
                ( \status -> do
                    T.putStrLn $
                        T.concat
                            [ T.pack . show $ status ^. statusId
                            , ": "
                            , status ^. statusUser . userScreenName
                            , ": "
                            , status ^. statusText
                            ]
                )