]> gitweb.michael.orlitzky.com - dead/halcyon.git/blobdiff - src/Twitter/Http.hs
Fix remaining hlint suggestions.
[dead/halcyon.git] / src / Twitter / Http.hs
index 2fe24bdd7c9579738b0d7a05eaa7a94d03b4eaa2..3b834859f37fcdbeeec0892588024da794238d60 100644 (file)
@@ -1,45 +1,98 @@
 module Twitter.Http
 where
 
-import Network.Curl
-import System.IO (hPutStrLn, stderr)
+import qualified Data.ByteString.Lazy as B
+import qualified Data.ByteString.Char8 as BC
+import qualified Data.Conduit as C
+import Data.Conduit.Binary (sinkLbs)
+import Network.HTTP.Conduit
+import Web.Authenticate.OAuth (
+  OAuth(..),
+  Credential,
+  newCredential,
+  newOAuth,
+  signOAuth)
 
+import Configuration
+
+-- |The API URL of username's timeline.
+--
+-- See,
 --
--- http://dev.twitter.com/doc/get/statuses/user_timeline
+--   <https://dev.twitter.com/docs/api/1.1/get/statuses/user_timeline>
 --
 user_timeline_url :: String -> String
 user_timeline_url username =
-    concat [ "http://api.twitter.com/1/statuses/user_timeline.xml",
-             "?screen_name=" ++ username,
-             "&include_rts=true",
-             "&count=10" ]
+  concat [ "https://api.twitter.com/",
+           "1.1/",
+           "statuses/",
+           "user_timeline.json?",
+           "screen_name=",
+           username,
+           "&include_rts=true&",
+           "count=10" ]
 
+status_url :: Integer -> String
+status_url status_id =
+  concat [ "https://api.twitter.com/",
+           "1.1/",
+           "statuses/",
+           "show.json?id=",
+           (show status_id) ]
+
+-- | Given username's last status id, constructs the API URL for
+--   username's new statuses. Essentially, 'user_timeline_url' with a
+--   "since_id" parameter tacked on.
 user_new_statuses_url :: String -> Integer -> String
 user_new_statuses_url username last_status_id =
-    concat [ user_timeline_url username,
-             "&since_id=" ++ (show last_status_id) ]
+  url ++ "&since_id=" ++ since_id
+  where
+    url = user_timeline_url username
+    since_id = show last_status_id
+
+get_status :: Cfg -> Integer -> IO B.ByteString
+get_status cfg status_id = do
+  let uri = status_url status_id
+  http_get cfg uri
+
+
+-- | Return's username's timeline.
+get_user_timeline :: Cfg -> String -> IO B.ByteString
+get_user_timeline cfg username = do
+  let uri = user_timeline_url username
+  http_get cfg uri
+
 
+-- | Returns the JSON representing all of username's statuses that are
+--   newer than last_status_id.
+get_user_new_statuses :: Cfg -> String -> Integer -> IO B.ByteString
+get_user_new_statuses cfg username last_status_id = do
+  let uri = user_new_statuses_url username last_status_id
+  http_get cfg uri
 
-get_user_timeline :: String -> IO (Maybe String)
-get_user_timeline username = do
-  let uri = (user_timeline_url username)
-  timeline <- (http_get uri)
-  return timeline
 
+-- | Retrieve a URL, or crash.
+http_get :: Cfg -> String -> IO B.ByteString
+http_get cfg url = do
+  manager <- newManager def
+  request <- parseUrl url
 
-get_user_new_statuses :: String -> Integer -> IO (Maybe String)
-get_user_new_statuses username last_status_id = do
-  let uri = (user_new_statuses_url username last_status_id)
-  new_statuses <- (http_get uri)
-  return new_statuses
+  C.runResourceT $ do
+    signed_request <- signOAuth oauth credential request
+    response <- http signed_request manager
+    responseBody response C.$$+- sinkLbs
 
+  where
+    consumer_key' = BC.pack (consumer_key cfg)
+    consumer_secret' = BC.pack (consumer_secret cfg)
+    access_token' = BC.pack (access_token cfg)
+    access_secret' = BC.pack (access_secret cfg)
 
-http_get :: String -> IO (Maybe String)
-http_get uri = withCurlDo $ do
-  resp <- curlGetString uri [CurlTimeout 45]
+    oauth :: OAuth
+    oauth = newOAuth {
+              oauthConsumerKey = consumer_key',
+              oauthConsumerSecret = consumer_secret'
+            }
 
-  case resp of
-    (CurlOK, body) -> return (Just body)
-    (code, _) -> do
-        hPutStrLn stderr ("HTTP Error: " ++ (show code))
-        return Nothing
+    credential :: Credential
+    credential = newCredential access_token' access_secret'